Re: [GHC] #1997: Stricter enumFrom instance for Integer, to match Int

2008-01-10 Thread GHC
#1997: Stricter enumFrom instance for Integer, to match Int
---+
 Reporter:  dons   |  Owner: 
 Type:  bug| Status:  new
 Priority:  normal |  Milestone:  6.10 branch
Component:  libraries/base |Version:  6.8.2  
 Severity:  normal | Resolution: 
 Keywords: | Difficulty:  Easy (1 hr)
 Testcase:  lib/should_run/enum04  |   Architecture:  Multiple   
   Os:  Multiple   |  
---+
Comment (by dons):

 Similary, there are other list functions on numeric types that should be
 strict in the
 accumulator:

 {{{
 Prelude> sum [1..100]
 *** Exception: stack overflow
 }}}

 maximum/minimum have rules for this:

 {{{
   "maximumInt" maximum = (strictMaximum :: [Int] -> Int);
   "maximumInteger" maximum = (strictMaximum :: [Integer] -> Integer)
 }}}

 and 'sum' works with -O, but none of them work in GHCi -- it would be good
 if
 this could be made more robust.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2032: SCC annotations cause compile errors

2008-01-10 Thread GHC
#2032: SCC annotations cause compile errors
--+-
 Reporter:  m4dc4p|  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone: 
Component:  Compiler  |Version:  6.8.2  
 Severity:  normal| Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Windows   |  
--+-
Comment (by Isaac Dupree):

 IMHO expression-pragmas should have a standard precedence that people will
 know what it is... I would tend towards "function application"
 {{{
 take 10 . {-# SCC "foo" #-} drop 10 $ s
 }}}
 becomes
 {{{
 take 10 . ({-# SCC "foo" #-} drop) 10 $ s
 }}}
 but
 {{{
 take 10 . drop {-# SCC "foo" #-} 10 $ s
 }}}
 becomes
 {{{
 take 10 . (drop {-# SCC "foo" #-}) 10 $ s
 }}}
 which is an error of course.  (except that pragmas shouldn't produce fatal
 errors, so it should be a warning. Isn't that how pragmas are supposed to
 work? Otherwise things tend to break between different compilers, e.g. I
 heard rumors about INLINE in `hbc`)

 Anyway with "function application" precedence it's just like the GHC-
 specific "inline"
 {{{
 take 10 . inline drop 10 $ s
 }}}
 ... why isn't it a pragma too? such as
 {{{
 take 10 . {-# INLINE #-} drop 10 $ s
 }}}

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2028: STM slightly conservative on write-only transactions

2008-01-10 Thread GHC
#2028: STM slightly conservative on write-only transactions
---+
 Reporter:  JulesBean  |  Owner: 
 Type:  proposal   | Status:  new
 Priority:  normal |  Milestone: 
Component:  Compiler   |Version:  6.8.1  
 Severity:  normal | Resolution: 
 Keywords: | Difficulty:  Unknown
 Testcase: |   Architecture:  Unknown
   Os:  Unknown|  
---+
Comment (by JulesBean):

 No.

 One them has to commit first. When it commits, it sets all the entries to
 something (say, 1). At this point, the other one has made no visible
 changes (all its changes are private, in its transaction log). Then, the
 other one commits, and it sets them all to 0.

 Committing is atomic.

 In the current situation what would happen is the first would commit, and
 then the second would say "erk! something has changed!" and not commit.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2028: STM slightly conservative on write-only transactions

2008-01-10 Thread GHC
#2028: STM slightly conservative on write-only transactions
---+
 Reporter:  JulesBean  |  Owner: 
 Type:  proposal   | Status:  new
 Priority:  normal |  Milestone: 
Component:  Compiler   |Version:  6.8.1  
 Severity:  normal | Resolution: 
 Keywords: | Difficulty:  Unknown
 Testcase: |   Architecture:  Unknown
   Os:  Unknown|  
---+
Comment (by Isaac Dupree):

 Probably I don't completely understand STM, but... if these happen at the
 same time, won't we potentially end up with an inconsistent state if no-
 one retries?

 {{{
 atomically $ mapM (\tv -> writeTVar tv 0) [tv1,tv2,tv3,tv4]
 }}}
 {{{
 atomically $ mapM (\tv -> writeTVar tv 1) [tv4,tv3,tv2,tv1]
 }}}

 (and don't single-word transactions depend on the hardware/architecture as
 for whether they are atomic?)

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2032: SCC annotations cause compile errors

2008-01-10 Thread GHC
#2032: SCC annotations cause compile errors
--+-
 Reporter:  m4dc4p|  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone: 
Component:  Compiler  |Version:  6.8.2  
 Severity:  normal| Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Windows   |  
--+-
Comment (by m4dc4p):

 I see what you are saying, but what I really expect is that SCC annotation
 don't affect parsing at all. I think of them the same way as comments.

 That is, I would expect {{{good1}}}, {{{good2}}} and {{{bad}}} to compile
 as is. Controlling the cost attributions for the annotation seems to be a
 separate issue, and something that is rightly solved by parentheses.

 p.s. That's really good to know that they bind less tightly than anything
 - I've always wondered.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2032: SCC annotations cause compile errors

2008-01-10 Thread GHC
#2032: SCC annotations cause compile errors
--+-
 Reporter:  m4dc4p|  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone: 
Component:  Compiler  |Version:  6.8.2  
 Severity:  normal| Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Windows   |  
--+-
Comment (by simonpj):

 Tricky.  Do you expect it to parse as:
 {{{
 take 10 . ({-# SCC "foo" #-} (drop 10 $ s)
 }}}
 (ie SCC binds less tightly than anything); or
 {{{
 take 10 . ({-# SCC "foo" #-} (drop 10)) $ s
 }}}
 (ie SCC binds more tightly than $ but less tightly than appilcation); or
 {{{
 take 10 . ({-# SCC "foo" #-} drop) 10 $ s
 }}}
 (ie SCC binds more tightly than anything, including application).

 You expected the middle case.  GHC is parsing it as the first case.  It
 isn't clear (to me) which of the three is "right".

 As usual, the way to avoid parsing ambiguities is to add parens.

 Simon

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2032: SCC annotations cause compile errors

2008-01-10 Thread GHC
#2032: SCC annotations cause compile errors
-+--
Reporter:  m4dc4p|   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone: 
   Component:  Compiler  | Version:  6.8.2  
Severity:  normal|Keywords: 
  Difficulty:  Unknown   |Testcase: 
Architecture:  Unknown   |  Os:  Windows
-+--
 The following program will not compile:

   bad s = take 10 . {-# SCC "foo" #-} drop 10 $ s

 It fails with the message

 {{{
 Couldn't match expected type `a -> [a1]'
against inferred type `[a2]'
 In the second argument of `(.)', namely `(drop 10 $ s)'
 In the expression: take 10 . (drop 10 $ s)
 In the definition of `bad': bad s = take 10 . (drop 10 $ s)
 }}}

 However, if the SCC annotation is removed it compiles:

   good s = take 10 . drop 10 $ s

 Adding parentheses can also fix it:

   good2 s = take 10 . ({-# SCC "foo" #-} drop 10) $ s

 but it's still annoying that adding an annotation can cause compilation to
 fail.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2028: STM slightly conservative on write-only transactions

2008-01-10 Thread GHC
#2028: STM slightly conservative on write-only transactions
---+
 Reporter:  JulesBean  |  Owner: 
 Type:  proposal   | Status:  new
 Priority:  normal |  Milestone: 
Component:  Compiler   |Version:  6.8.1  
 Severity:  normal | Resolution: 
 Keywords: | Difficulty:  Unknown
 Testcase: |   Architecture:  Unknown
   Os:  Unknown|  
---+
Comment (by simonpj):

 Comment from Tim Harris:

 This suggestion is OK from the point of view of correctness.

 There are several special cases where we could allow transactions to
 commit when we currently treat them as conflicting.  E.g. any single-word
 transaction is OK.

 I've avoided dealing with too many of these in the absence of code we care
 about performing badly (it'll add complexity and might slow down the
 hopefully-common case of non-conflicting transactions).

 No strong arguments against adding this one though: we could probably use
 a special value in the old-val field to indicate no-previous-value so we
 won't get a space code.  We could also handle it specially in "retry" --
 we don't need to watch for updates to a `TVar` that has been written to
 but not read.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2029: Add --with-libedit flag to the readline package

2008-01-10 Thread GHC
#2029: Add --with-libedit flag to the readline package
---+
 Reporter:  judah  |  Owner:  
 Type:  proposal   | Status:  new 
 Priority:  normal |  Milestone:  Not GHC 
Component:  libraries (other)  |Version:  
 Severity:  normal | Resolution:  
 Keywords: | Difficulty:  Unknown 
 Testcase: |   Architecture:  Multiple
   Os:  Multiple   |  
---+
Changes (by maeder):

 * cc: [EMAIL PROTECTED] (added)

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1990: Add 'subsequences' and 'permutations' to Data.List

2008-01-10 Thread GHC
#1990: Add 'subsequences' and 'permutations' to Data.List
+---
 Reporter:  twanvl  |  Owner: 
 Type:  proposal| Status:  new
 Priority:  high|  Milestone:  6.10 branch
Component:  libraries/base  |Version:  6.8.1  
 Severity:  normal  | Resolution: 
 Keywords:  | Difficulty:  Easy (1 hr)
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Changes (by simonmar):

  * priority:  normal => high
  * difficulty:  Unknown => Easy (1 hr)
  * milestone:  Not GHC => 6.10 branch

Comment:

 Deadline has passed, there were no complaints, apply this patch for 6.10.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2031: relocation overflow

2008-01-10 Thread GHC
#2031: relocation overflow
-+--
Reporter:  maeder|   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone: 
   Component:  Compiler  | Version:  6.8.2  
Severity:  normal|Keywords: 
  Difficulty:  Unknown   |Testcase: 
Architecture:  powerpc   |  Os:  MacOS X
-+--
 I've created a statically linked ghc-6.8.2 for PPC Mac OS 10.4 (Tiger).
 http://www.dfki.de/sks/hets/mac/versions/ghc-6.8.2-powerpc-apple-darwin-
 static-libs.tar.bz2

 When linking our big hets binary after compilation with optimization I get
 millions (actually 34999 lines) of entries like:

 {{{
 /usr/bin/ld: PGIP/XMLparsing.o relocation overflow for relocation entry 63
 in section (__TEXT,__text) (displacement too large)
 ...
 /usr/bin/ld: SoftFOL/Sign.o relocation overflow for relocation entry 45280
 in section (__TEXT,__text) (displacement too large)
 collect2: ld returned 1 exit status
 make: *** [hets] Error 1
 }}}

 I had such messages before and got rid of them by rearranging code and
 imports (just by wild guesses, a strategy would be helpful). It is sort of
 a known (Apple PPC) deficiency (and I misuse this ticket to document it
 here).

 Linking works fine after compilation without optimization or when linking
 against GMP and GNUreadline frameworks using my other binary distribution.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2030: GHC internal error: `m' is not in scope

2008-01-10 Thread GHC
#2030: GHC internal error: `m' is not in scope
-+--
 Reporter:  ToRA |  Owner:  igloo 
 Type:  merge| Status:  new   
 Priority:  normal   |  Milestone:
Component:  Compiler (Type checker)  |Version:  6.8.2 
 Severity:  normal   | Resolution:
 Keywords:   | Difficulty:  Unknown   
 Testcase:  tc242|   Architecture:  x86_64 (amd64)
   Os:  Linux|  
-+--
Changes (by simonpj):

  * testcase:  => tc242
  * owner:  => igloo
  * type:  bug => merge

Comment:

 Thanks.  The bug turns out to be that `-XScopedTypeVariables` should imply
 `-XRelaxedPolyRec`. If you add the latter flag you will be fine. I'll push
 a patch and some tests.

 Simon

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2013: ghci crash on startup: R_X86_64_32S relocation out of range.

2008-01-10 Thread GHC
#2013: ghci crash on startup: R_X86_64_32S relocation out of range.
-+--
 Reporter:  mboes|  Owner:
 Type:  bug  | Status:  new   
 Priority:  normal   |  Milestone:  6.8.3 
Component:  GHCi |Version:  6.9   
 Severity:  normal   | Resolution:
 Keywords:   | Difficulty:  Unknown   
 Testcase:   |   Architecture:  x86_64 (amd64)
   Os:  FreeBSD  |  
-+--
Comment (by wb.kloke):

 I can confirm that the patch is good for use for most of the testsuite
 with my system. I updated my FreeBSD-7.0-amd64 binary dist with the patch
 applied, and the testsuite output.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2013: ghci crash on startup: R_X86_64_32S relocation out of range.

2008-01-10 Thread GHC
#2013: ghci crash on startup: R_X86_64_32S relocation out of range.
-+--
 Reporter:  mboes|  Owner:
 Type:  bug  | Status:  new   
 Priority:  normal   |  Milestone:  6.8.3 
Component:  GHCi |Version:  6.9   
 Severity:  normal   | Resolution:
 Keywords:   | Difficulty:  Unknown   
 Testcase:   |   Architecture:  x86_64 (amd64)
   Os:  FreeBSD  |  
-+--
Comment (by simonmar):

 Thanks for the patch!  I'll take a look.

 Your patch will apply to 6.8.3, but in HEAD the previously mentioned patch
 "add PIC relocations for x86_64" has been applied, and the
 `x86_64_high_symbol()` hack has been replaced by the `symbol_extras`
 stuff.  If you were able to port your changes to the HEAD too, that would
 be great.  Currently the HEAD will not compile at all on x86_64 non-Linux.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs