Re: [GHC] #2289: Needless reboxing of values when returning from a tight loop

2009-04-14 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|Owner:  
Type:  run-time performance bug|   Status:  new 
Priority:  normal  |Milestone:  6.12 branch 
   Component:  Compiler|  Version:  6.8.2   
Severity:  normal  |   Resolution:  
Keywords:  boxing, loops, performance  |   Difficulty:  Unknown 
Testcase:  |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple|  
---+
Comment (by simonpj):

 See also #2387, and #1600

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2289#comment:15
GHC http://www.haskell.org/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] #1600: Optimisation: CPR the results of IO

2009-04-14 Thread GHC
#1600: Optimisation: CPR the results of IO
-+--
Reporter:  simonmar  |Owner:  
Type:  task  |   Status:  new 
Priority:  normal|Milestone:  6.12 branch 
   Component:  Compiler  |  Version:  6.6.1   
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Moderate (1 day)
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by simonpj):

 See also #2387 and #2289

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1600#comment:4
GHC http://www.haskell.org/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] #3008: Strange behavior when using newtyped version of IO monad in FFI import declarations

2009-04-14 Thread GHC
#3008: Strange behavior when using newtyped version of IO monad in FFI import
declarations
---+
Reporter:  waern   |Owner: 
Type:  bug |   Status:  new
Priority:  normal  |Milestone:  6.12.1 
   Component:  Compiler|  Version:  6.10.1 
Severity:  normal  |   Resolution: 
Keywords:  FFI |   Difficulty:  Unknown
Testcase:  |   Os:  Linux  
Architecture:  x86_64 (amd64)  |  
---+
Changes (by simonpj):

  * milestone:  6.12 branch = 6.12.1

Comment:

 Let's try to resolve this for 6.21.1

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3008#comment:4
GHC http://www.haskell.org/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] #1544: Derived Read instances for recursive datatypes with infix constructors are too inefficient

2009-04-14 Thread GHC
#1544: Derived Read instances for recursive datatypes with infix constructors 
are
too inefficient
-+--
Reporter:  jcpetru...@gmail.com  |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.12.1  
   Component:  Compiler  |  Version:  6.6.1   
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by simonpj):

 Doaitse, Marcos, and Eelco tackle precisely this issue:
 {{{
 @inproceedings{1411296,
   author = {Marcos Viera and S. Doaitse Swierstra and Eelco Lempsink},
   title = {Haskell, do you read me?: constructing and composing
 efficient top-down parsers at runtime},
   booktitle = {Haskell '08: Proceedings of the first ACM SIGPLAN
 symposium on Haskell},
   year = {2008},
   isbn = {978-1-60558-064-7},
   pages = {63--74},
   location = {Victoria, BC, Canada},
   doi = {http://doi.acm.org/10.1145/1411286.1411296},
   publisher = {ACM},
   address = {New York, NY, USA},
   }
 }}}
 I'm not sure whether they regard their solution as suitable to directly
 incorporate in (say) GHC, but it's certainly a substantial contribution to
 this ticket!

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1544#comment:18
GHC http://www.haskell.org/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] #2765: unsetenv not found under Solaris 8 when building ghc-6.10.1

2009-04-14 Thread GHC
#2765: unsetenv not found under Solaris 8 when building ghc-6.10.1
-+--
Reporter:  maeder|Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone:  6.12.1 
   Component:  Compiler  |  Version:  6.10.1 
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Solaris
Architecture:  sparc |  
-+--
Comment (by maeder):

 I think, it is only a problem under our old Solaris 8. I did not find a
 work around, but simple gave up using Solaris 8 and switched to using
 Solaris 10 machines which don't have this problem:

 http://www.informatik.uni-
 bremen.de/agbkb/forschung/formal_methods/CoFI/hets/solaris/ghcs/ghc-6.10.2
 -sparc-sun-solaris2.tar.bz2

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2765#comment:3
GHC http://www.haskell.org/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] #3163: GADTs should not allow polymorphism in return type

2009-04-14 Thread GHC
#3163: GADTs should not allow polymorphism in return type
+---
Reporter:  Scott Turner |Owner: 
Type:  bug  |   Status:  new
Priority:  normal   |Milestone: 
   Component:  Compiler (Type checker)  |  Version:  6.10.1 
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Unknown
Testcase:   |   Os:  Linux  
Architecture:  x86  |  
+---
Changes (by simonpj):

  * difficulty:  = Unknown
  * summary:  quantified types fail to match in GADT case = GADTs should
  not allow polymorphism in return type

Comment:

 GADTs shouldn't allow for-all types in the return type, even with
 `-XImpredicativeTypes`, I'm afraid.  It's hard enough doing the equality
 reasoning over monotypes, and I have no idea what additional complications
 are introduced by polytypes.

 So I'll re-title this ticket!

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3163#comment:1
GHC http://www.haskell.org/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] #3168: Unhelpful error message about hidden packages

2009-04-14 Thread GHC
#3168: Unhelpful error message about hidden packages
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.12.1  
   Component:  Compiler  |  Version:  6.10.2  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Easy (1 hr) 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by simonpj):

  * difficulty:  Unknown = Easy (1 hr)
  * milestone:  = 6.12.1

Comment:

 I think this is readily fixable.  Line 601 of Finder.lhs has
 {{{
 pkg_hidden pkg =
 ptext (sLit it is a member of the hidden package) + quotes
 (ppr pkg)
 }}}
 I suggest instead:
 {{{
   Since it is a member of package bytestring-0.9.1.4,
perhaps you intended to say '-package bytestring',
or (if using Cabal) perhaps you omitted 'bytestring' from the
build-depends in your .cabal file.
 }}}
 If there are multiple hidden packages that contain the module, we probably
 don't want all this blurb for each one; but some simple rewording should
 do, and all the info is available in `Finder.cantFindError`.

 Better wordings welcome.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3168#comment:1
GHC http://www.haskell.org/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] #1544: Derived Read instances for recursive datatypes with infix constructors are too inefficient

2009-04-14 Thread GHC
#1544: Derived Read instances for recursive datatypes with infix constructors 
are
too inefficient
-+--
Reporter:  jcpetru...@gmail.com  |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.12.1  
   Component:  Compiler  |  Version:  6.6.1   
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by Doaitse):

 We consider this problem basically solved by the ChristmasTree library we
 uploaded to Hackage, with its associated packages.

 See:

 http://hackage.haskell.org/packages/archive/ChristmasTree/0.1/doc/html
 /Text-GRead.html

 I am currently doubtful whether this should be incorporated in the GHC as
 it stands now. We think it is better to find some other uses of the TTTAS
 library before we decide how to proceed. Thus far we got no questions
 about these packages, which implies either that they solve the problem or
 that they are not used at all. In neither case this provides information
 to us on how to proceed. At least the severity could be lowered to
 minor?

 Doaitse

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1544#comment:19
GHC http://www.haskell.org/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] #3168: Unhelpful error message about hidden packages

2009-04-14 Thread GHC
#3168: Unhelpful error message about hidden packages
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.12.1  
   Component:  Compiler  |  Version:  6.10.2  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Easy (1 hr) 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by igloo):

 Or perhaps Cabal should pass GHC a `-cabal` flag, and we could give a
 different error when that flag is given. Might be useful in other cases
 too.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3168#comment:2
GHC http://www.haskell.org/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] #3160: No exception safety in Control.Concurrent.QSem QSemN and SampleVar

2009-04-14 Thread GHC
#3160: No exception safety in Control.Concurrent.QSem QSemN and SampleVar
-+--
Reporter:  ChrisKuklewicz|Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  libraries/base|  Version:  6.10.2  
Severity:  major |   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * difficulty:  = Unknown

Comment:

 See also http://haskell.org/haskellwiki/SafeConcurrent

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3160#comment:2
GHC http://www.haskell.org/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] #3168: Unhelpful error message about hidden packages

2009-04-14 Thread GHC
#3168: Unhelpful error message about hidden packages
---+
  Reporter:  simonpj   |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  6.10.2  
  Severity:  normal|   Keywords:  
Difficulty:  Unknown   |   Testcase:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
---+
 Anatoly Yakonenko [http://www.haskell.org/pipermail/haskell-
 cafe/2009-April/059677.html reported]: I am trying to build `ParseP` on
 the latest ghc, and I am getting this error:
 {{{

  Text/ParserCombinators/ParseP/Interface.hs:26:17:
 Could not find module `Data.ByteString.Char8':
   it is a member of package bytestring-0.9.1.4, which is hidden
 }}}
 Ross Mellgren responded (correctly): I assume you're using cabal, which
 hides all packages by default. Add bytestring or bytestring = 0.9.*
 or something along those lines to Build-Depends in your .cabal file.

 Suggestion: improve GHC's error message.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3168
GHC http://www.haskell.org/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] #3016: Long compile times, large memory use with static data in 6.10

2009-04-14 Thread GHC
#3016: Long compile times, large memory use with static data in 6.10
---+
Reporter:  dons|Owner:  igloo   
Type:  bug |   Status:  new 
Priority:  normal  |Milestone:  
   Component:  Compiler|  Version:  6.10.1  
Severity:  normal  |   Resolution:  
Keywords:  static data |   Difficulty:  Unknown 
Testcase:  simplCore/should_compile/T3016  |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple|  
---+
Comment (by igloo):

 It actually looks not far off linear:
 {{{
 # constants  peak heap usage  bytes allocated
 160   63874448 3193731536
 320   86003152 6609305256
 640  18613459214211355072
 1280 stack overflow
 }}}
 and the heap usage is lower here than the heap profile showed.

 So I think that all we need to do here is make sure the testsuite test is
 OK.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3016#comment:6
GHC http://www.haskell.org/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] #3169: Type families occurs check

2009-04-14 Thread GHC
#3169: Type families occurs check
---+
  Reporter:  simonpj   |  Owner:  chak
  Type:  bug   | Status:  new 
  Priority:  normal|  Milestone:  6.12.1  
 Component:  Compiler  |Version:  6.10.2  
  Severity:  normal|   Keywords:  
Difficulty:  Unknown   |   Testcase:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
---+
 Consider this:
 {{{
 {-# LANGUAGE  TypeFamilies, ScopedTypeVariables #-}
 module Map where

 import Prelude hiding ( lookup )

 class Key k where
   type Map k :: * - *
   lookup :: k - Map k elt - Maybe elt

 instance (Key a, Key b) = Key (a,b) where
   type Map (a,b) = MP a b
   lookup (a,b) (m :: Map (a,b) elt)
  = case lookup a m :: Maybe (Map b elt) of
   Just (m2 :: Map b elt) - lookup b m2 :: Maybe elt

 data MP a b elt = MP (Map a (Map b elt))
 }}}
 This ought to typecheck, even in the absence of all those type signatures.
 But alas:
 {{{
 Map.hs:13:12:
 Occurs check: cannot construct the infinite type: elt = t elt
 In the expression: lookup a m :: Maybe (Map b elt)
 In the expression:
 case lookup a m :: Maybe (Map b elt) of {
   Just (m2 :: Map b elt) - lookup b m2 :: Maybe elt }
 }}}
 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3169
GHC http://www.haskell.org/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] #1962: make binary-dist creates nested directories under solaris

2009-04-14 Thread GHC
#1962: make binary-dist creates nested directories under solaris
-+--
Reporter:  maeder|Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone:  6.12.1 
   Component:  Build System  |  Version:  6.8.1  
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Solaris
Architecture:  x86   |  
-+--
Comment (by maeder):

 I think, this can be closed. I'll attach my log for `gmake binary-dist`.
 http://www.informatik.uni-
 bremen.de/agbkb/forschung/formal_methods/CoFI/hets/intel-
 mac/ghcs/ghc-6.10.2-i386-apple-darwin.tar.bz2

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1962#comment:9
GHC http://www.haskell.org/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] #1962: make binary-dist creates nested directories under solaris

2009-04-14 Thread GHC
#1962: make binary-dist creates nested directories under solaris
-+--
Reporter:  maeder|Owner: 
Type:  bug   |   Status:  closed 
Priority:  normal|Milestone:  6.12.1 
   Component:  Build System  |  Version:  6.8.1  
Severity:  normal|   Resolution:  fixed  
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Solaris
Architecture:  x86   |  
-+--
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed

Comment:

 Great, thanks! And thanks too for the bindist; I've added it to the 6.10.2
 download page.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1962#comment:10
GHC http://www.haskell.org/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] #2765: unsetenv not found under Solaris 8 when building ghc-6.10.1

2009-04-14 Thread GHC
#2765: unsetenv not found under Solaris 8 when building ghc-6.10.1
-+--
Reporter:  maeder|Owner: 
Type:  bug   |   Status:  closed 
Priority:  normal|Milestone:  6.12.1 
   Component:  Compiler  |  Version:  6.10.1 
Severity:  normal|   Resolution:  fixed  
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Solaris
Architecture:  sparc |  
-+--
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed

Comment:

 OK, I'll close this ticket then. And thanks for the bindist; I've added it
 to the 6.10.2 download page.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2765#comment:4
GHC http://www.haskell.org/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] #2349: SIZET_FMT in includes/mkDerivedConstants.c needs to be d under older Solaris version

2009-04-14 Thread GHC
#2349: SIZET_FMT in includes/mkDerivedConstants.c needs to be d under older
Solaris version
-+--
Reporter:  maeder|Owner: 
Type:  bug   |   Status:  closed 
Priority:  normal|Milestone:  6.12.1 
   Component:  Compiler  |  Version:  6.10.1 
Severity:  normal|   Resolution:  fixed  
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Solaris
Architecture:  sparc |  
-+--
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed

Comment:

 We decided in #2765 not to worry about Solaris 8 problems, so I'm closing
 this as fixed in Solaris 10.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2349#comment:6
GHC http://www.haskell.org/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] #2965: GHC on OS X does not compile 64-bit

2009-04-14 Thread GHC
#2965: GHC on OS X does not compile 64-bit
+---
Reporter:  Axman6   |Owner:  thoughtpolice
Type:  feature request  |   Status:  new  
Priority:  normal   |Milestone:  6.12 branch  
   Component:  Compiler |  Version:   
Severity:  normal   |   Resolution:   
Keywords:  64bit|   Difficulty:  Unknown  
Testcase:   |   Os:  MacOS X  
Architecture:  x86_64 (amd64)   |  
+---
Changes (by pumpkin):

 * cc: pumpkin...@gmail.com (added)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2965#comment:4
GHC http://www.haskell.org/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] #2658: Extreme memory usage (probably type functions)

2009-04-14 Thread GHC
#2658: Extreme memory usage (probably type functions)
+---
Reporter:  guest|Owner:  chak   
Type:  bug  |   Status:  closed 
Priority:  low  |Milestone:  6.12.1 
   Component:  Compiler (Type checker)  |  Version:  6.9
Severity:  major|   Resolution:  invalid
Keywords:   |   Difficulty:  Unknown
Testcase:   |   Os:  Linux  
Architecture:  x86_64 (amd64)   |  
+---
Changes (by igloo):

  * status:  new = closed
  * resolution:  = invalid

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2658#comment:13
GHC http://www.haskell.org/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] #3170: -fregs-graph: GraphOps.coalesceNodes: can't coalesce the same node.

2009-04-14 Thread GHC
#3170: -fregs-graph: GraphOps.coalesceNodes: can't coalesce the same node.
---+
  Reporter:  igloo |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  high  |  Milestone:  6.12.1  
 Component:  Compiler  |Version:  6.10.2  
  Severity:  normal|   Keywords:  
Difficulty:  Unknown   |   Testcase:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
---+
 If `-fregs-graph` is used then the build fails when compiling
 `PrimOps.cmm`:
 {{{
 $ /home/ian/ghc/darcs/ghc/ghc/stage1-inplace/ghc  -Werror -H64m -O0 -fasm
 -optc-O2 -I../includes -I. -Iparallel -Ism -Ieventlog -DCOMPILING_RTS
 -package-name rts -static  -I../gmp/gmpbuild -I../libffi/build/include -I.
 -dcmm-lint -c PrimOps.cmm -o PrimOps.o -fregs-graph
 ghc: panic! (the 'impossible' happened)
   (GHC version 6.11.20090409 for x86_64-unknown-linux):
 GraphOps.coalesceNodes: can't coalesce the same node.

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

 This blocks #2790.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3170
GHC http://www.haskell.org/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] #2790: Use -fregs-graph by default

2009-04-14 Thread GHC
#2790: Use -fregs-graph by default
-+--
Reporter:  igloo |Owner:  
Type:  task  |   Status:  new 
Priority:  high  |Milestone:  6.12.1  
   Component:  Compiler  |  Version:  6.8.3   
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by igloo):

 Blocked by #3170.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2790#comment:4
GHC http://www.haskell.org/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] #3015: Building packages using ghc (6.8.2) results in inconsistent error assembler messages

2009-04-14 Thread GHC
#3015: Building packages using ghc (6.8.2) results in inconsistent error 
assembler
messages
---+
Reporter:  akrohit |Owner: 
Type:  bug |   Status:  new
Priority:  low |Milestone:  6.12.1 
   Component:  Compiler|  Version:  6.8.2  
Severity:  normal  |   Resolution: 
Keywords:  |   Difficulty:  Unknown
Testcase:  |   Os:  Linux  
Architecture:  x86_64 (amd64)  |  
---+
Changes (by igloo):

  * priority:  normal = low
  * milestone:  = 6.12.1

Comment:

 Hmm, curious. Are you able to test with 6.10.2?

 If you try to compile a simple file, e.g.
 {{{
 main = putStrLn Foo
 }}}
 with
 {{{
 ghc -O -c test.hs
 }}}
 then do you get the error?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3015#comment:3
GHC http://www.haskell.org/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] #3016: Long compile times, large memory use with static data in 6.10

2009-04-14 Thread GHC
#3016: Long compile times, large memory use with static data in 6.10
---+
Reporter:  dons|Owner:  igloo   
Type:  bug |   Status:  new 
Priority:  normal  |Milestone:  6.12.1  
   Component:  Compiler|  Version:  6.10.1  
Severity:  normal  |   Resolution:  
Keywords:  static data |   Difficulty:  Unknown 
Testcase:  simplCore/should_compile/T3016  |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple|  
---+
Changes (by igloo):

  * milestone:  = 6.12.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3016#comment:7
GHC http://www.haskell.org/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] #3021: A way to programmatically insert marks into heap profiling output

2009-04-14 Thread GHC
#3021: A way to programmatically insert marks into heap profiling output
-+--
Reporter:  SamB  |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  6.12.1  
   Component:  Profiling |  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:  profiling |   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * milestone:  = 6.12.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3021#comment:10
GHC http://www.haskell.org/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] #3024: Rewrite hp2ps in Haskell

2009-04-14 Thread GHC
#3024: Rewrite hp2ps in Haskell
-+--
Reporter:  SamB  |Owner:  
Type:  task  |   Status:  new 
Priority:  normal|Milestone:  6.12 branch 
   Component:  Profiling |  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * milestone:  = 6.12 branch

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3024#comment:5
GHC http://www.haskell.org/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] #3026: GHCi segfault

2009-04-14 Thread GHC
#3026: GHCi segfault
---+
Reporter:  porges  |Owner: 
Type:  bug |   Status:  new
Priority:  normal  |Milestone: 
   Component:  GHCi|  Version:  6.10.1 
Severity:  major   |   Resolution: 
Keywords:  |   Difficulty:  Unknown
Testcase:  |   Os:  Linux  
Architecture:  x86 |  
---+
Changes (by igloo):

  * difficulty:  = Unknown

Old description:

 This may be libedit's fault, but I can't tell :)

 How to replicate:
 Load up GHCi, hold the up-arrow. Segfault!

 Here's a backtrace:

 Program received signal SIGSEGV, Segmentation fault.
 [Switching to Thread 0xb7e546b0 (LWP 9959)]
 0xb808133c in ?? () from /usr/lib/libedit.so.2
 (gdb) bt
 #0  0xb808133c in ?? () from /usr/lib/libedit.so.2
 #1  0xb8085e1a in ?? () from /usr/lib/libedit.so.2
 #2  0xb8088164 in el_gets () from /usr/lib/libedit.so.2
 #3  0xb8095d24 in readline () from /usr/lib/libedit.so.2
 #4  0x08aaea00 in ?? ()
 Backtrace stopped: previous frame inner to this frame (corrupt
 stack?)
 (gdb)

New description:

 This may be libedit's fault, but I can't tell :)

 How to replicate:
 Load up GHCi, hold the up-arrow. Segfault!

 Here's a backtrace:
 {{{
 Program received signal SIGSEGV, Segmentation fault.
 [Switching to Thread 0xb7e546b0 (LWP 9959)]
 0xb808133c in ?? () from /usr/lib/libedit.so.2
 (gdb) bt
 #0  0xb808133c in ?? () from /usr/lib/libedit.so.2
 #1  0xb8085e1a in ?? () from /usr/lib/libedit.so.2
 #2  0xb8088164 in el_gets () from /usr/lib/libedit.so.2
 #3  0xb8095d24 in readline () from /usr/lib/libedit.so.2
 #4  0x08aaea00 in ?? ()
 Backtrace stopped: previous frame inner to this frame (corrupt stack?)
 (gdb)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3026#comment:2
GHC http://www.haskell.org/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] #3026: GHCi segfault

2009-04-14 Thread GHC
#3026: GHCi segfault
---+
Reporter:  porges  |Owner: 
Type:  bug |   Status:  new
Priority:  normal  |Milestone:  6.12.1 
   Component:  GHCi|  Version:  6.10.1 
Severity:  major   |   Resolution: 
Keywords:  |   Difficulty:  Unknown
Testcase:  |   Os:  Linux  
Architecture:  x86 |  
---+
Changes (by igloo):

  * milestone:  = 6.12.1

Comment:

 I can't reproduce this, but I think we should assume it's editline for
 now, and test again once the head has stopped using it.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3026#comment:3
GHC http://www.haskell.org/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] #3030: GHCI Loading Compiled Modules Under Windows XP Crashes

2009-04-14 Thread GHC
#3030: GHCI Loading Compiled Modules Under Windows XP Crashes
---+
Reporter:  jburck  |Owner: 
Type:  bug |   Status:  closed 
Priority:  normal  |Milestone: 
   Component:  GHCi|  Version:  6.10.1 
Severity:  normal  |   Resolution:  invalid
Keywords:  |   Difficulty:  Unknown
Testcase:  |   Os:  Windows
Architecture:  x86 |  
---+
Changes (by igloo):

  * status:  new = closed
  * resolution:  = invalid

Comment:

 No response, so closing.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3030#comment:2
GHC http://www.haskell.org/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] #3034: divInt# floated into a position which leads to low arity

2009-04-14 Thread GHC
#3034: divInt# floated into a position which leads to low arity
-+--
Reporter:  batterseapower|Owner:  
Type:  run-time performance bug  |   Status:  new 
Priority:  normal|Milestone:  6.12 branch 
   Component:  Compiler  |  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * difficulty:  = Unknown
  * milestone:  = 6.12 branch

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3034#comment:4
GHC http://www.haskell.org/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] #3032: would be nice if -fno-code and --make worked together

2009-04-14 Thread GHC
#3032: would be nice if -fno-code and --make worked together
-+--
Reporter:  duncan|Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  6.12 branch 
   Component:  Compiler  |  Version:  6.8.2   
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * difficulty:  = Unknown
  * milestone:  = 6.12 branch

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3032#comment:1
GHC http://www.haskell.org/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] #1884: Win64 Port

2009-04-14 Thread GHC
#1884: Win64 Port
---+
Reporter:  simonmar|Owner: 
Type:  task|   Status:  new
Priority:  normal  |Milestone:  6.12.1 
   Component:  Compiler|  Version:  6.8.1  
Severity:  normal  |   Resolution: 
Keywords:  |   Difficulty:  Unknown
Testcase:  |   Os:  Windows
Architecture:  x86_64 (amd64)  |  
---+
Changes (by PVerswyvelen):

 * cc: peter.verswyve...@gmail.com (added)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1884#comment:3
GHC http://www.haskell.org/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] #3036: Max/Min Monoids

2009-04-14 Thread GHC
#3036: Max/Min Monoids
-+--
Reporter:  whpearson |Owner:  
Type:  proposal  |   Status:  new 
Priority:  normal|Milestone:  Not GHC 
   Component:  libraries/base|  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * difficulty:  = Unknown
  * milestone:  = Not GHC

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3036#comment:2
GHC http://www.haskell.org/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] #3041: Arch independent binary representations

2009-04-14 Thread GHC
#3041: Arch independent binary representations
-+--
Reporter:  nomeata   |Owner: 
Type:  feature request   |   Status:  new
Priority:  normal|Milestone:  6.12.1 
   Component:  Compiler  |  Version:  6.10.1 
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Linux  
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * milestone:  = 6.12.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3041#comment:12
GHC http://www.haskell.org/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] #3045: GHCI Crashes Under Windows when loading compiled code

2009-04-14 Thread GHC
#3045: GHCI Crashes Under Windows when loading compiled code
-+--
Reporter:  jburck|Owner: 
Type:  bug   |   Status:  new
Priority:  low   |Milestone:  6.12.1 
   Component:  Compiler  |  Version:  6.10.1 
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Windows
Architecture:  x86   |  
-+--
Changes (by igloo):

  * priority:  normal = low
  * milestone:  = 6.12.1

Comment:

 Low priority while we're waiting for a response.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3045#comment:2
GHC http://www.haskell.org/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] #3049: STM with data invariants crashes GHC

2009-04-14 Thread GHC
#3049: STM with data invariants crashes GHC
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.12.1  
   Component:  Compiler  |  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * milestone:  = 6.12.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3049#comment:2
GHC http://www.haskell.org/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] #3050: parsec: bug in caret escape parsing

2009-04-14 Thread GHC
#3050: parsec: bug in caret escape parsing
--+-
Reporter:  sof|Owner:  
Type:  bug|   Status:  new 
Priority:  normal |Milestone:  Not GHC 
   Component:  libraries (other)  |  Version:  6.10.1  
Severity:  normal |   Resolution:  
Keywords: |   Difficulty:  Unknown 
Testcase: |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   |  
--+-
Changes (by igloo):

  * difficulty:  = Unknown
  * milestone:  = Not GHC

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3050#comment:1
GHC http://www.haskell.org/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] #3051: Add product/sum/maximum/minimum specialisations for more atomic types

2009-04-14 Thread GHC
#3051: Add product/sum/maximum/minimum specialisations for more atomic types
-+--
Reporter:  thorkilnaur   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.12.1  
   Component:  libraries/base|  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * difficulty:  = Unknown
  * milestone:  = 6.12.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3051#comment:1
GHC http://www.haskell.org/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] #3056: StrictAnal module naming issue

2009-04-14 Thread GHC
#3056: StrictAnal module naming issue
-+--
Reporter:  pumpkin   |Owner:  
Type:  proposal  |   Status:  closed  
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.10.1  
Severity:  trivial   |   Resolution:  wontfix 
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * status:  new = closed
  * resolution:  = wontfix

Comment:

 Doesn't look like we have consensus to change it, so I'm closing this
 ticket. Perhaps the cvs-ghc mailing list would be a better place to
 discuss it if you disagree.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3056#comment:2
GHC http://www.haskell.org/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] #3058: Add a 'hex' function to the pretty printing

2009-04-14 Thread GHC
#3058: Add a 'hex' function to the pretty printing
-+--
Reporter:  TomMD |Owner:  
Type:  proposal  |   Status:  new 
Priority:  normal|Milestone:  Not GHC 
   Component:  libraries/base|  Version:  
Severity:  normal|   Resolution:  
Keywords:  pretty, prettyprint, library  |   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * difficulty:  = Unknown
  * milestone:  = Not GHC

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3058#comment:1
GHC http://www.haskell.org/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] #3054: ghc crashes with unicode escape and literal character together

2009-04-14 Thread GHC
#3054: ghc crashes with unicode escape and literal character together
-+--
Reporter:  iamfishhead   |Owner: 
Type:  bug   |   Status:  closed 
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.8.2  
Severity:  normal|   Resolution:  fixed  
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Linux  
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * status:  new = closed
  * difficulty:  = Unknown
  * resolution:  = fixed

Comment:

 Thanks for the report. Happily, this already works in the HEAD and the
 6.10 branch.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3054#comment:1
GHC http://www.haskell.org/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] #3015: Building packages using ghc (6.8.2) results in inconsistent error assembler messages

2009-04-14 Thread GHC
#3015: Building packages using ghc (6.8.2) results in inconsistent error 
assembler
messages
---+
Reporter:  akrohit |Owner: 
Type:  bug |   Status:  new
Priority:  low |Milestone:  6.12.1 
   Component:  Compiler|  Version:  6.8.2  
Severity:  normal  |   Resolution: 
Keywords:  |   Difficulty:  Unknown
Testcase:  |   Os:  Linux  
Architecture:  x86_64 (amd64)  |  
---+
Comment (by akrohit):

 I just tested it with ghc-6.10.2 and is still reproducible.

 The interesting part is that the bus does not occur with files containing
 simple programs like the above one (test.hs).

 But while compiling any standard hackage package or any other complex
 program results in the error.

 I am attaching a sample output of the bug which might help. (produced with
 ghc-6.10.2)

 The lines marked with ** are my comments

 I am also attaching the portion of temporary file (as the original file is
 too big) that is reported in the error message. I have marked the first
 few error by giving a comment at the proper line no. To go to the error
 line just search the string error in file named ghc2061_0.s

 Thought it might help.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3015#comment:4
GHC http://www.haskell.org/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] #3059: 3 different behaviours depending on profiling settings and on a used-only-once form being top-level

2009-04-14 Thread GHC
#3059: 3 different behaviours depending on profiling settings and on a 
used-only-
once form being top-level
-+--
Reporter:  jkff  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone:  6.12 branch
   Component:  Compiler  |  Version:  6.10.1 
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Windows
Architecture:  x86   |  
-+--
Changes (by igloo):

  * milestone:  = 6.12 branch

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3059#comment:6
GHC http://www.haskell.org/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] #3064: Very long compile times with type functions

2009-04-14 Thread GHC
#3064: Very long compile times with type functions
-+--
Reporter:  simonpj   |Owner:  chak
Type:  compile-time performance bug  |   Status:  new 
Priority:  normal|Milestone:  6.12 branch 
   Component:  Compiler (Type checker)   |  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * milestone:  = 6.12 branch

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3064#comment:1
GHC http://www.haskell.org/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] #3070: floor(0/0) should not be defined

2009-04-14 Thread GHC
#3070: floor(0/0) should not be defined
-+--
Reporter:  carette   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.12.1  
   Component:  Prelude   |  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * difficulty:  = Unknown
  * milestone:  = 6.12.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3070#comment:1
GHC http://www.haskell.org/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] #3072: considerations for management of shared libs

2009-04-14 Thread GHC
#3072: considerations for management of shared libs
-+--
Reporter:  duncan|Owner: 
Type:  proposal  |   Status:  new
Priority:  normal|Milestone:  6.12.1 
   Component:  None  |  Version:  6.10.1 
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Linux  
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * difficulty:  = Unknown
  * milestone:  = 6.12.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3072#comment:2
GHC http://www.haskell.org/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] #3015: Building packages using ghc (6.8.2) results in inconsistent error assembler messages

2009-04-14 Thread GHC
#3015: Building packages using ghc (6.8.2) results in inconsistent error 
assembler
messages
---+
Reporter:  akrohit |Owner: 
Type:  bug |   Status:  new
Priority:  low |Milestone:  6.12.1 
   Component:  Compiler|  Version:  6.8.2  
Severity:  normal  |   Resolution: 
Keywords:  |   Difficulty:  Unknown
Testcase:  |   Os:  Linux  
Architecture:  x86_64 (amd64)  |  
---+
Comment (by igloo):

 OK, so some characters with least significant bit 0 are getting their
 least significant bit set to 1. We have `d` - `e`, `z` - `{` and `:` -
 `;`. I'd guess that this is the Ubuntu 6.8.2 and the 6.10.2 bindist, both
 of which work for other people, so it smells like a hardware problem to
 me. Have you tried running memtest or similar?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3015#comment:5
GHC http://www.haskell.org/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] #3073: Avoid reconstructing dictionaries in recursive instance methods

2009-04-14 Thread GHC
#3073: Avoid reconstructing dictionaries in recursive instance methods
-+--
Reporter:  simonpj   |Owner:  
Type:  run-time performance bug  |   Status:  new 
Priority:  normal|Milestone:  6.12 branch 
   Component:  Compiler  |  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * milestone:  = 6.12 branch

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3073#comment:1
GHC http://www.haskell.org/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] #3076: Make genericLength tail-recursive so it doesn't overflow stack

2009-04-14 Thread GHC
#3076: Make genericLength tail-recursive so it doesn't overflow stack
-+--
Reporter:  Syzygies  |Owner:  
Type:  run-time performance bug  |   Status:  closed  
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.10.1  
Severity:  normal|   Resolution:  wontfix 
Keywords:  genericLength |   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * status:  reopened = closed
  * resolution:  = wontfix

Comment:

 This assumes that `(==)` terminates, which it might not do, e.g. with some
 datatypes representing the reals.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3076#comment:4
GHC http://www.haskell.org/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] #3088: have ghc-pkg print less useless info when registering

2009-04-14 Thread GHC
#3088: have ghc-pkg print less useless info when registering
-+--
Reporter:  duncan|Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  6.12.1  
   Component:  Compiler  |  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * difficulty:  = Unknown
  * milestone:  = 6.12.1

Comment:

 This sounds easy, let's do it for 6.12.1.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3088#comment:1
GHC http://www.haskell.org/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] #1876: Complete shared library support

2009-04-14 Thread GHC
#1876: Complete shared library support
-+--
Reporter:  simonmar  |Owner:
Type:  task  |   Status:  new   
Priority:  high  |Milestone:  6.12.1
   Component:  Compiler  |  Version:  6.8.1 
Severity:  normal|   Resolution:
Keywords:|   Difficulty:  Difficult (1 week)
Testcase:|   Os:  Unknown/Multiple  
Architecture:  Unknown/Multiple  |  
-+--
Changes (by ttuegel):

 * cc: ttue...@gmail.com (added)

Comment:

 Since there hasn't been any chatter on this ticket in more than a month, I
 thought I would share some observations I made today testing shared
 library support on x86_64 Linux (I also have an x86 machine to test on
 later).  I apologize in advance if this information is redundant; keep in
 mind it comes from an only moderately well-informed outsider.

 1. ./configure --enable-shared  make successfully compiles a compiler!
 I nearly fell out of my chair in awe!

 2. make -jN does not work for N  1, but this may be a symptom of the
 build system in general, and not of shared library support.

 3. Because we need binaries bootstrapped as part of the compile process to
 install everything, make install fails because the operating system linker
 cannot find the shared libraries.

 I was able to use some LD_LIBRARY_PATH magic to include the relevant build
 directories and install anyway, but this only exposed the following:

 4. We put shared libraries for most packages into ${prefix}/lib but the
 rts and ffi shared-libraries go into ${prefix}/lib/ghc-6.11.20090409 where
 the dynamic linker won't find them by default.  Although we could use
 LD_LIBRARY_PATH to include the appropriate directory, that feels like a
 dirty hack: the standard Linux practice seems to be to put any shared
 libraries the linker needs to find where it will find them by default.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1876#comment:26
GHC http://www.haskell.org/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] #3163: GADTs should not allow polymorphism in return type

2009-04-14 Thread GHC
#3163: GADTs should not allow polymorphism in return type
+---
Reporter:  Scott Turner |Owner: 
Type:  bug  |   Status:  new
Priority:  normal   |Milestone: 
   Component:  Compiler (Type checker)  |  Version:  6.10.1 
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Unknown
Testcase:   |   Os:  Linux  
Architecture:  x86  |  
+---
Comment (by Scott Turner):

 The revised title is quite acceptable. Thanks.[[BR]]
 Scott

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3163#comment:2
GHC http://www.haskell.org/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] #3170: -fregs-graph: GraphOps.coalesceNodes: can't coalesce the same node.

2009-04-14 Thread GHC
#3170: -fregs-graph: GraphOps.coalesceNodes: can't coalesce the same node.
-+--
Reporter:  igloo |Owner:  benl
Type:  bug   |   Status:  assigned
Priority:  high  |Milestone:  6.12.1  
   Component:  Compiler  |  Version:  6.10.2  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by benl):

  * status:  new = assigned
  * owner:  = benl

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3170#comment:1
GHC http://www.haskell.org/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] #3169: Type families occurs check

2009-04-14 Thread GHC
#3169: Type families occurs check
-+--
Reporter:  simonpj   |Owner:  chak
Type:  bug   |   Status:  closed  
Priority:  normal|Milestone:  6.12.1  
   Component:  Compiler  |  Version:  6.10.2  
Severity:  normal|   Resolution:  worksforme  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by chak):

  * status:  new = closed
  * resolution:  = worksforme

Comment:

 I disagree.  GHC is perfectly right.  You forgot to match the ''data
 constructor'' `MP` in the second argument of `lookup`.
 {{{
 instance (Key a, Key b) = Key (a,b) where
   type Map (a,b) = MP a b
   lookup (a,b) (MP m)
  = case lookup a m of
   Just m2 - lookup b m2
 }}}
 works fine for me in the HEAD.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3169#comment:1
GHC http://www.haskell.org/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] #3015: Building packages using ghc (6.8.2) results in inconsistent error assembler messages

2009-04-14 Thread GHC
#3015: Building packages using ghc (6.8.2) results in inconsistent error 
assembler
messages
---+
Reporter:  akrohit |Owner: 
Type:  bug |   Status:  new
Priority:  low |Milestone:  6.12.1 
   Component:  Compiler|  Version:  6.10.2 
Severity:  normal  |   Resolution: 
Keywords:  |   Difficulty:  Unknown
Testcase:  |   Os:  Linux  
Architecture:  x86_64 (amd64)  |  
---+
Changes (by akrohit):

  * version:  6.8.2 = 6.10.2

Comment:

 Earlier I was using Fedora (Currently ubuntu 8.10) and the same errors
 were coming. So I guess it has got not much to do with any particular
 linux distro.

 Moreover I just did a memtest and it passed it without any errors.

 I have also used gcc for compiling other big large projects without any
 problem, moreover my system runs fine. I mean till yet I haven't seen any
 signs that might conclude to some hardware issues.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3015#comment:6
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs