Re: [GHC] #5844: Panic on generating Core code

2012-02-07 Thread GHC
#5844: Panic on generating Core code
-+--
Reporter:  JamesFisher   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Milestone:  7.6.1 
   Component:  External Core | Version:  7.4.1 
Keywords:|  Os:  Unknown/Multiple  
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--

Comment(by simonpj):

 Yes, your diagram is right, except that the arrow from .hi to Iface Core
 should be labelled `iface/BinIface` as well; `BinIface` does
 deserialisation as well a serialisation.

 And rather that "External Iface" I might say "the output of `ghc --show-
 iface` or something like that.

 Documenting in the user manual is slightly odd; but only slightly.  After
 all, it's simply documenting what `ghc -ext-core` does; in particular,
 defining the language it produces into the `.hcr` file.  The
 implementation diagram could form a useful part of the Commentary:
 http://hackage.haskell.org/trac/ghc/wiki/Commentary.

 Yes converting `core.tex` to `core.xml` would be a great start.

 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] #4385: Type-level natural numbers

2012-02-07 Thread GHC
#4385: Type-level natural numbers
+---
Reporter:  diatchki |   Owner:  diatchki
Type:  feature request  |  Status:  new 
Priority:  normal   |   Milestone:  7.4.1   
   Component:  Compiler (Type checker)  | Version:  
Keywords:   |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple | Failure:  None/Unknown
  Difficulty:   |Testcase:  
   Blockedby:   |Blocking:  
 Related:   |  
+---

Comment(by bjornbm):

 It seems this ticket needs an update by someone in the know. I understand
 TypeNats didn't make it into 7.4.1 in the end so at least the milestone is
 inaccurate(?). Can we still expect to see TypeNats in GHC?

-- 
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] #5856: numrun012 test fails on i686 works on x86_64

2012-02-07 Thread GHC
#5856: numrun012 test fails on i686 works on x86_64
--+-
 Reporter:  td123 |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Test Suite  
  Version:  7.4.1 |   Keywords:  numrun012 unexpected failure
   Os:  Linux |   Architecture:  x86 
  Failure:  None/Unknown  |   Testcase:  numrun012   
Blockedby:|   Blocking:  
  Related:|  
--+-

Comment(by td123):

 Side note: I found a person with what I'm guessing to be the same failure
 described here at
 http://hackage.haskell.org/trac/ghc/ticket/5757#comment:5
 It seems he is running on x86 windows.

 Also to add to my previous bug report: I compiled ghc with "BuildFlavour =
 perf".

-- 
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] #5856: numrun012 test fails on i686 works on x86_64

2012-02-07 Thread GHC
#5856: numrun012 test fails on i686 works on x86_64
--+-
 Reporter:  td123 |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Test Suite  
  Version:  7.4.1 |   Keywords:  numrun012 unexpected failure
   Os:  Linux |   Architecture:  x86 
  Failure:  None/Unknown  |   Testcase:  numrun012   
Blockedby:|   Blocking:  
  Related:|  
--+-
 I have built ghc on both x86_64 and i686 for archlinux.
 make test has no unexpected results on x86_64.
 On i686, make test has only the following unexpected failure:


 {{{
 => numrun012(normal) 831 of 3160 [0, 0, 0]
 cd ./numeric/should_run && '/build/src/ghc-7.4.1/inplace/bin/ghc-stage2'
 -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-
 conf -rtsopts  -fno-ghci-history -o numrun012 numrun012.hs
 >numrun012.comp.stderr 2>&1
 cd ./numeric/should_run && ./numrun012numrun012.run.stdout
 2>numrun012.run.stderr
 Actual stdout output differs from expected:
 --- ./numeric/should_run/numrun012.stdout   2012-02-01
 18:11:16.0 +
 +++ ./numeric/should_run/numrun012.run.stdout   2012-02-07
 23:06:57.413192194 +
 @@ -1,4 +1,4 @@
 -[0,1,5,9,10,14,31,31,32,32,32,32,33]
 +[0,1,5,9,10,14,31,31,31,32,32,32,33]
  -2.147483648e9
  -2.1474836e9
  -2.147483648e9
 *** unexpected failure for numrun012(normal)
 }}}

 I think I got the failure down to one line:

 The following returns 31.004 on x86_64 and 31.0 on i686:
 {{{
 logBase 2 (fromIntegral 2^31) :: Double
 }}}

 Please let me know if you need anything else from me.

-- 
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] #5844: Panic on generating Core code

2012-02-07 Thread GHC
#5844: Panic on generating Core code
-+--
Reporter:  JamesFisher   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Milestone:  7.6.1 
   Component:  External Core | Version:  7.4.1 
Keywords:|  Os:  Unknown/Multiple  
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--

Comment(by JamesFisher):

 Ignore me; [http://hackage.haskell.org/trac/ghc/browser/docs found it].
 Would it help if was to convert
 [http://hackage.haskell.org/trac/ghc/browser/docs/ext-core/core.tex ext-
 core/core.tex] into, say
 [http://hackage.haskell.org/trac/ghc/browser/docs/users_guide/core.xml
 users_guide/core.xml]?

-- 
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] #5844: Panic on generating Core code

2012-02-07 Thread GHC
#5844: Panic on generating Core code
-+--
Reporter:  JamesFisher   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Milestone:  7.6.1 
   Component:  External Core | Version:  7.4.1 
Keywords:|  Os:  Unknown/Multiple  
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--

Comment(by JamesFisher):

 (I ask because the user manual seems slightly strange place to document
 compiler internals.  Perhaps not though.)  Where is the source repository
 for the user manual?

-- 
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] #5808: nofib/spectral/hartel/transform is crashing with -fllvm

2012-02-07 Thread GHC
#5808: nofib/spectral/hartel/transform is crashing with -fllvm
+---
Reporter:  simonmar |   Owner:  dterei 
Type:  bug  |  Status:  new
Priority:  high |   Milestone:  7.4.2  
   Component:  Compiler (LLVM)  | Version:  7.4.1-rc1  
Keywords:   |  Os:  Linux  
Architecture:  x86  | Failure:  Runtime crash  
  Difficulty:  Unknown  |Testcase:  nofib/spectral/hartel/transform
   Blockedby:   |Blocking: 
 Related:   |  
+---

Comment(by dterei):

 Is this still happening? I can't replicate locally. What LLVM version is
 it? I've tested with 2.7, 2.8 and 3.0, unless 2.9 has a problem...

-- 
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] #5844: Panic on generating Core code

2012-02-07 Thread GHC
#5844: Panic on generating Core code
-+--
Reporter:  JamesFisher   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Milestone:  7.6.1 
   Component:  External Core | Version:  7.4.1 
Keywords:|  Os:  Unknown/Multiple  
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--

Comment(by JamesFisher):

 Replying to [comment:7 simonpj]:

 > We have a very old Latex document describing External Core (including is
 syntax); I'd like to see it become a full part of the documentation,
 perhaps by convrting it to SGML and making it a full part of the GHC user
 manual.

 Is [http://hackage.haskell.org/trac/ghc/browser/docs/ext-core/core.tex
 this] the document you mean?

 I'm a bit confused as to what the "official" GHC documentation is. There's
 the [http://hackage.haskell.org/trac/ghc/wiki Developer wiki],
 [http://www.haskell.org/haskellwiki/GHC Haskell wiki], and the
 [http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/index.html user
 guide].  Where would the External Core document go if converted?

-- 
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] #5844: Panic on generating Core code

2012-02-07 Thread GHC
#5844: Panic on generating Core code
-+--
Reporter:  JamesFisher   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Milestone:  7.6.1 
   Component:  External Core | Version:  7.4.1 
Keywords:|  Os:  Unknown/Multiple  
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--

Comment(by JamesFisher):

 Does my attached drawing summarize the situation accurately?

-- 
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] #5855: Computation Hangs Using PolyKinds

2012-02-07 Thread GHC
#5855: Computation Hangs Using PolyKinds
---+
 Reporter:  paf31  |  Owner:  
 Type:  bug| Status:  new 
 Priority:  normal |  Component:  Compiler
  Version:  7.4.1  |   Keywords:  
   Os:  Windows|   Architecture:  Unknown/Multiple
  Failure:  Runtime crash  |   Testcase:  
Blockedby: |   Blocking:  
  Related: |  
---+
 I have tried to distill this down to a minimal example. The following
 computation hangs in ghci when evaluating "toInt Zero":

 {{{
 > {-# LANGUAGE GADTs, DataKinds, PolyKinds, KindSignatures #-}

 > data Choice = Fst | Snd

 > data PHom p1 p2 = PHom (p1 Fst -> p2 Fst) (p1 Snd -> p2 Snd)

 > data FNat :: (Choice -> *) -> Choice -> * where
 >   FZero :: FNat p Fst
 >   FSucc1 :: p Snd -> FNat p Fst
 >   FSucc2 :: p Fst -> FNat p Snd

 > hmap (PHom f g) = PHom hf hg where
 >   hf FZero = FZero
 >   hf (FSucc1 x) = FSucc1 (g x)
 >   hg (FSucc2 x) = FSucc2 (f x)

 > data Nat :: Choice -> * where
 >   Zero :: Nat Fst
 >   Succ1 :: Nat Snd -> Nat Fst
 >   Succ2 :: Nat Fst -> Nat Snd

 > out = PHom f g where
 >   f Zero = FZero
 >   f (Succ1 n) = FSucc1 n
 >   g (Succ2 n) = FSucc2 n

 > compose (PHom f1 g1) (PHom f2 g2) = PHom (f2 . f1) (g2 . g1)

 > fold phi = compose out (compose (hmap (fold phi)) phi)

 > data EvenOdd :: Choice -> * where
 >   Even :: Int -> EvenOdd Fst
 >   Odd :: Int -> EvenOdd Snd

 > toInt :: Nat Fst -> Int
 > toInt x =
 >   let (PHom f g) = fold (PHom phi psi) in
 >   let (Even n) = f x in n where
 > phi FZero = Even 0
 > phi (FSucc1 (Odd n)) = Even (n + 1)
 > psi (FSucc2 (Even n)) = Odd (n + 1)
 }}}

 Setting a breakpoint in ghci seems to indicate that the expression (fold
 (PHom phi psi)) is being evaluated in full, which would obviously cause an
 unbounded recursion.

 However, the following version runs fine and terminates as expected:

 {{{
 > {-# LANGUAGE GADTs, DataKinds, PolyKinds, KindSignatures, RankNTypes #-}

 > data Choice = Fst | Snd

 > newtype PHom p1 p2 = PHom { runPHom :: forall r. ((p1 Fst -> p2 Fst) ->
 (p1 Snd -> p2 Snd) -> r) -> r }

 > mkPHom f g = PHom (\h -> h f g)
 > fstPHom p = runPHom p (\f -> \g -> f)
 > sndPHom p = runPHom p (\f -> \g -> g)

 > data FNat :: (Choice -> *) -> Choice -> * where
 >   FZero :: FNat p Fst
 >   FSucc1 :: p Snd -> FNat p Fst
 >   FSucc2 :: p Fst -> FNat p Snd

 > hmap p = mkPHom hf hg where
 >   hf FZero = FZero
 >   hf (FSucc1 x) = FSucc1 (sndPHom p x)
 >   hg (FSucc2 x) = FSucc2 (fstPHom p x)

 > data Nat :: Choice -> * where
 >   Zero :: Nat Fst
 >   Succ1 :: Nat Snd -> Nat Fst
 >   Succ2 :: Nat Fst -> Nat Snd

 > out = mkPHom f g where
 >   f Zero = FZero
 >   f (Succ1 n) = FSucc1 n
 >   g (Succ2 n) = FSucc2 n

 > compose f g = mkPHom (fstPHom g . fstPHom f) (sndPHom g . sndPHom f)

 > fold phi = compose out (compose (hmap (fold phi)) phi)

 > data EvenOdd :: Choice -> * where
 >   Even :: Int -> EvenOdd Fst
 >   Odd :: Int -> EvenOdd Snd

 > toInt :: Nat Fst -> Int
 > toInt x =
 >   let p = fold (mkPHom phi psi) in
 >   let (Even n) = fstPHom p x in n where
 > phi FZero = Even 0
 > phi (FSucc1 (Odd n)) = Even (n + 1)
 > psi (FSucc2 (Even n)) = Odd (n + 1)
 }}}

 The major change is that the data type PHom has been replaced with a
 newtype wrapper around a product encoded as a function.

-- 
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] #5849: Buliding on arm broke in 7.4.1

2012-02-07 Thread GHC
#5849: Buliding on arm broke in 7.4.1
---+
Reporter:  nomeata |   Owner: 
Type:  bug |  Status:  new
Priority:  high|   Milestone:  7.4.2  
   Component:  Runtime System  | Version:  7.4.1  
Keywords:  |  Os:  Linux  
Architecture:  arm | Failure:  Building GHC failed
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+

Comment(by nomeata):

 Replying to [comment:8 igloo]:
 > Unfortunately, we don't have the resources to support all platforms
 ourselves. While we will help where we can, we really rely on the
 community to support other platforms, both in terms of running buildbots,
 and in fixing any platform-specific issues that they reveal.

 Fair enough. Not sure how much I can help with fixing, but I’ll contact
 the GCC guys and see if I can manage a few buildbots there.

-- 
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] #5824: ARM StgRun register clobber list is broken

2012-02-07 Thread GHC
#5824: ARM StgRun register clobber list is broken
---+
Reporter:  bgamari |   Owner:  simonmar
Type:  bug |  Status:  patch   
Priority:  high|   Milestone:  7.4.2   
   Component:  Runtime System  | Version:  7.4.1-rc2   
Keywords:  |  Os:  Unknown/Multiple
Architecture:  arm | Failure:  None/Unknown
  Difficulty:  Unknown |Testcase:  
   Blockedby:  |Blocking:  
 Related:  |  
---+

Comment(by nomeata):

 Replying to [comment:10 igloo]:
 > Given the error, perhaps ''only'' `r11` should be used? nomeata, are you
 able to test please?

 Yes, but just to avoid round-trips after 10 hours of building due to
 misunderstandings: Can you provide a proper patch? I’ll start the build
 right away.

-- 
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] #5824: ARM StgRun register clobber list is broken

2012-02-07 Thread GHC
#5824: ARM StgRun register clobber list is broken
---+
Reporter:  bgamari |   Owner:  simonmar
Type:  bug |  Status:  patch   
Priority:  high|   Milestone:  7.4.2   
   Component:  Runtime System  | Version:  7.4.1-rc2   
Keywords:  |  Os:  Unknown/Multiple
Architecture:  arm | Failure:  None/Unknown
  Difficulty:  Unknown |Testcase:  
   Blockedby:  |Blocking:  
 Related:  |  
---+
Changes (by igloo):

 * cc: nomeata (added)


Comment:

 Given the error, perhaps ''only'' `r11` should be used? nomeata, are you
 able to test please?

-- 
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] #5849: Buliding on arm broke in 7.4.1

2012-02-07 Thread GHC
#5849: Buliding on arm broke in 7.4.1
---+
Reporter:  nomeata |   Owner: 
Type:  bug |  Status:  new
Priority:  high|   Milestone:  7.4.2  
   Component:  Runtime System  | Version:  7.4.1  
Keywords:  |  Os:  Linux  
Architecture:  arm | Failure:  Building GHC failed
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+

Comment(by igloo):

 Unfortunately, we don't have the resources to support all platforms
 ourselves. While we will help where we can, we really rely on the
 community to support other platforms, both in terms of running buildbots,
 and in fixing any platform-specific issues that they reveal.

-- 
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] #5824: ARM StgRun register clobber list is broken

2012-02-07 Thread GHC
#5824: ARM StgRun register clobber list is broken
---+
Reporter:  bgamari |   Owner:  simonmar
Type:  bug |  Status:  patch   
Priority:  high|   Milestone:  7.4.2   
   Component:  Runtime System  | Version:  7.4.1-rc2   
Keywords:  |  Os:  Unknown/Multiple
Architecture:  arm | Failure:  None/Unknown
  Difficulty:  Unknown |Testcase:  
   Blockedby:  |Blocking:  
 Related:  |  
---+

Comment(by bgamari):

 Bah, yes, you are right. Very obvious oversight on my part. Indeed this
 ought to be reverted. I'm still not certain why it compiled for me (or
 even why it failed to compile for the Debian folks), but the patch is
 certainly redundant.

-- 
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] #5824: ARM StgRun register clobber list is broken

2012-02-07 Thread GHC
#5824: ARM StgRun register clobber list is broken
---+
Reporter:  bgamari |   Owner:  simonmar
Type:  bug |  Status:  patch   
Priority:  high|   Milestone:  7.4.2   
   Component:  Runtime System  | Version:  7.4.1-rc2   
Keywords:  |  Os:  Unknown/Multiple
Architecture:  arm | Failure:  None/Unknown
  Difficulty:  Unknown |Testcase:  
   Blockedby:  |Blocking:  
 Related:  |  
---+

Comment(by kgardas):

 The patch:
 commit 5a984f4388ef85d5c3af973b21a12c12b36c1ed4
 Author: Ben Gamari 
 Date:   Mon Jan 30 16:52:40 2012 -0500

 ARM StgRun: Ensure r11 state is preserved

 looks wrong to me. I'm sorry to not review it more earlier, in fact ARM's
 r11 is the same reg as fp. So IMHO whole this patch might be reverted.
 Unfortunately I don't have debian here to check if it helps or not.

-- 
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] #5849: Buliding on arm broke in 7.4.1

2012-02-07 Thread GHC
#5849: Buliding on arm broke in 7.4.1
---+
Reporter:  nomeata |   Owner: 
Type:  bug |  Status:  new
Priority:  high|   Milestone:  7.4.2  
   Component:  Runtime System  | Version:  7.4.1  
Keywords:  |  Os:  Linux  
Architecture:  arm | Failure:  Building GHC failed
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+

Comment(by nomeata):

 First responses from Debian admins about providing a build service to
 upstream are negative (http://lists.debian.org/debian-
 haskell/2012/02/msg00029.html), but point to
 http://gcc.gnu.org/wiki/CompileFarm for a service that offers access to
 machines of various architectures to Free Software projects. Maybe the GHC
 team wants to use these for more build bots?

-- 
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] #5824: ARM StgRun register clobber list is broken

2012-02-07 Thread GHC
#5824: ARM StgRun register clobber list is broken
---+
Reporter:  bgamari |   Owner:  simonmar
Type:  bug |  Status:  patch   
Priority:  high|   Milestone:  7.4.2   
   Component:  Runtime System  | Version:  7.4.1-rc2   
Keywords:  |  Os:  Unknown/Multiple
Architecture:  arm | Failure:  None/Unknown
  Difficulty:  Unknown |Testcase:  
   Blockedby:  |Blocking:  
 Related:  |  
---+
Changes (by igloo):

 * cc: karel.gardas@… (added)


Comment:

 With these patches, the Debian guys found (#5849) that the build failed
 
https://buildd.debian.org/status/fetch.php?pkg=ghc&arch=armel&ver=7.4.1-1&stamp=1328355092
 :
 {{{
 "inplace/bin/ghc-stage1" -optc-Wall -optc-Wextra -optc-Wstrict-prototypes
 -optc-Wmissing-prototypes -optc-Wmissing-declarations -optc-Winline -optc-
 Waggregate-return -optc-Wpointer-arith -optc-Wmissing-noreturn -optc-
 Wnested-externs -optc-Wredundant-decls -optc-Iincludes -optc-Irts -optc-
 Irts/dist/build -optc-DCOMPILING_RTS -optc-DUSE_LIBFFI_FOR_ADJUSTORS
 -optc-fno-strict-aliasing -optc-fno-common -optc-g -optc-O0 -optc-
 DRtsWay=\"rts_debug\" -optc-w -optc-DDEBUG  -H32m -O -lffi -optl-pthread
 -optc-mlong-calls -Iincludes -Irts -Irts/dist/build -DCOMPILING_RTS
 -package-name rts  -dcmm-lint  -i -irts -irts/dist/build
 -irts/dist/build/autogen -Irts/dist/build -Irts/dist/build/autogen
 -c rts/StgCRun.c -o rts/dist/build/StgCRun.debug_o
 rts/StgCRun.c: In function 'StgRun':

 rts/StgCRun.c:678:1:  error: fp cannot be used in asm here
 make[2]: *** [rts/dist/build/StgCRun.debug_o] Error 1
 make[1]: *** [all] Error 2
 make[1]: Leaving directory `/build/buildd-ghc_7.4.1-1-armel-
 V2DeDU/ghc-7.4.1'
 make: *** [build-stamp] Error 2
 }}}

 Perhaps the difference is whether the LLVM compiler is being used or not?

 Regardless, we really need a solution that works for everyone.

-- 
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] #5849: Buliding on arm broke in 7.4.1

2012-02-07 Thread GHC
#5849: Buliding on arm broke in 7.4.1
---+
Reporter:  nomeata |   Owner: 
Type:  bug |  Status:  new
Priority:  high|   Milestone:  7.4.2  
   Component:  Runtime System  | Version:  7.4.1  
Keywords:  |  Os:  Linux  
Architecture:  arm | Failure:  Building GHC failed
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+

Comment(by igloo):

 See also #5824.

-- 
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] #5766: Asynchronous exception bugs in readProcess and readProcessWithExitCode

2012-02-07 Thread GHC
#5766: Asynchronous exception bugs in readProcess and readProcessWithExitCode
--+-
Reporter:  basvandijk |   Owner:  
Type:  bug|  Status:  patch   
Priority:  normal |   Milestone:  7.6.1   
   Component:  libraries/process  | Version:  7.2.2   
Keywords: |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
  Difficulty:  Unknown|Testcase:  
   Blockedby: |Blocking:  
 Related: |  
--+-

Comment(by basvandijk):

 Replying to [comment:3 simonmar]:
 > I think it should be documented that an asynchronous exception will
 trigger a `terminateProcess`;

 I added this to the documentation.

-- 
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] #5793: make nofib not suck

2012-02-07 Thread GHC
#5793: make nofib not suck
--+-
Reporter:  dterei |   Owner:  dterei  
Type:  task   |  Status:  new 
Priority:  normal |   Milestone:  _|_ 
   Component:  NoFib benchmark suite  | Version:  
Keywords: |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
  Difficulty:  Unknown|Testcase:  
   Blockedby: |Blocking:  5794
 Related: |  
--+-
Changes (by NeilMitchell):

 * cc: ndmitchell@… (added)


Comment:

 I might try and give a go at a Shake version of the makefile soup that is
 currently in there.

-- 
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] #2301: Proper handling of SIGINT/SIGQUIT

2012-02-07 Thread GHC
#2301: Proper handling of SIGINT/SIGQUIT
--+-
  Reporter:  duncan   |  Owner:  
  Type:  bug  | Status:  new 
  Priority:  normal   |  Milestone:  7.4.1   
 Component:  libraries/process|Version:  6.12.3  
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by basvandijk):

 * cc: v.dijk.bas@… (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] #5852: methods and associated types treated differently wrt. qualification

2012-02-07 Thread GHC
#5852: methods and associated types treated differently wrt. qualification
+---
Reporter:  jeltsch  |Owner: 
 
Type:  feature request  |   Status:  closed 
 
Priority:  normal   |Component:  Compiler   
 
 Version:  7.0.4|   Resolution:  fixed  
 
Keywords:  type families, qualified import  |   Os:  
Unknown/Multiple
Architecture:  Unknown/Multiple |  Failure:  Other  
 
Testcase:   |Blockedby: 
 
Blocking:   |  Related: 
 
+---
Changes (by jeltsch):

  * status:  new => closed
  * resolution:  => fixed


Comment:

 Now that I have installed GHC 7.4.1 (for a different reason than this
 bug), I see that this problem is fixed in this GHC version.

-- 
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] #5849: Buliding on arm broke in 7.4.1

2012-02-07 Thread GHC
#5849: Buliding on arm broke in 7.4.1
---+
Reporter:  nomeata |   Owner: 
Type:  bug |  Status:  new
Priority:  high|   Milestone:  7.4.2  
   Component:  Runtime System  | Version:  7.4.1  
Keywords:  |  Os:  Linux  
Architecture:  arm | Failure:  Building GHC failed
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+

Comment(by nomeata):

 Don’t worry, it is just a slight grumble, as long as a fix is found.

 Would it be helpful if we (Debian) set up a GHC builder on an armel
 machine? Is the builder software capable of handling builds that take
 longer than 24h, and can it be configured to run less often, e.g. once per
 week?

-- 
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] #5844: Panic on generating Core code

2012-02-07 Thread GHC
#5844: Panic on generating Core code
-+--
Reporter:  JamesFisher   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Milestone:  7.6.1 
   Component:  External Core | Version:  7.4.1 
Keywords:|  Os:  Unknown/Multiple  
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--

Comment(by simonpj):

 Short answer Yes... but there is a longer and more interesting answer.
 External Core is designed to round-trip, thus:
  * External Core is a '''data type''' defined in `coreSyn/ExternalCore`.
  * Core is converted to the External Core data type by
 `coreSyn/MkExternalCore`
  * The External Core data type is printed by `PprExternalCore` into
 concrete syntax.
  * The modified External Core can be parsed by `parser/ParserCore`.
 However, it is not parsed into the External Core data type, but rather
 into "Iface Core" defined in `iface/IfaceSyn`.
  * The Iface Core data type (thus parsed) can be converted to Core by
 `iface/TcIface`.

 What is Iface Core?  Iface Core is a data type that GHC uses every time
 you compile a module.  During compilation, GHC converts Core into Iface
 Core, and then serialises Iface Core into the "M.hi" interface file, in a
 binary format.  This is done by `iface/BinIface`.  Then, when GHC wants to
 read an interface file, it de-serialises M.hi into Iface Core, and then
 converts Iface Core into Core with `iface/TcIface`.  ''What this means is
 that Iface Core gets plenty of love: it is on our critical path.''

 Why does "External Core" do the round trip via the ''External Core'' data
 type on the way our, but via ''Iface Core'' data type on the way in?  This
 mis-match just an aretefact of an earlier era: when we first implemented
 External Core, there ''was'' no Iface Core.

 I think the Right Thing to do is to complete the change that we have
 already started:
  * Abandon the Exgternal Core data type entirely.
  * The conversion from Core to Iface Core is already done (in
 `iface/MkIface`), because GHC uses it every time it compiles a moudle.
  * Change the pretty-printer for External Core to pretty-print the Iface
 Core rarther than External Core. In fact there already ''is'' a pretty-
 printer for Iface Core, in `iface/LoadIface.pprModIface`, although it
 might require minor modification.

 The bottom line is that we'd be abandoning the External Core ''data type''
 (though not its concrete syntax), and switching entirely to Iface Core,
 which is much better maintained.  Less code, more robust to change; what's
 not to like?

 Now, while I say that there is a pretty printer for Iface Core already, it
 is designed mainly for humans; it is used when you say `ghc --show-iface
 M.hi`, and for no other purpose.  The External Core concrete syntax, on
 the other hand, is designed to be '''parseable''' as well, so that the
 round-trip mechanism (print Exgternal Core, modify it, and read it back
 in) works right.  But I think it would be quite acceptable to modify the
 Iface Core pretty-printer to use External Core syntax, because the Iface
 Core pretty printer has an output-only role in GHC.  (If you do this, I
 suggest you put the new pretty-printer in a module of its own, perhaps
 `iface/PprIface`.)

 If this was done, the maintenance burden of External Core, if/when we add
 new features to Core, would be reduced to
  * Designing new concrete (ASCII) syntax for the new features
  * Writing the pretty-printer and parser for this new syntax

 I do think that the concrete syntax of External Core should be described
 by a human-readable BNF grammar, not only by a Happy parser.  We have a
 very old Latex document describing External Core (including is syntax);
 I'd like to see it become a full part of the documentation, perhaps by
 convrting it to SGML and making it a full part of the GHC user manual.

 This isn't a big task, and it's one that is well separated from the rest
 of GHC.  Would anyone like to take it on?  I'd be happy to advise if so.

 I wonder who uses External Core?

-- 
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] #5854: TH: INLINABLE pragma support (patch)

2012-02-07 Thread GHC
#5854: TH: INLINABLE pragma support (patch)
+---
 Reporter:  mikhail.vorozhtsov  |  Owner:  
 Type:  feature request | Status:  new 
 Priority:  normal  |  Component:  Template Haskell
  Version:  7.4.1   |   Keywords:  
   Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
  Failure:  None/Unknown|   Testcase:  
Blockedby:  |   Blocking:  
  Related:  |  
+---
 I needed it for my [https://github.com/mvv/data-dword data-dword] library,
 so here it is:
 {{{
 GHCi, version 7.5.20120206: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 λ> import Language.Haskell.TH
 λ> (mapM_ print =<<) $ runQ [d| f1 = id; {-# NOINLINE f1 #-}; f2 = id; {-#
 INLINE f2 #-}; f3 = id; {-# INLINABLE f3 #-} |]
 Loading package array-0.3.0.3 ... linking ... done.
 Loading package deepseq-1.2.0.1 ... linking ... done.
 Loading package containers-0.4.2.0 ... linking ... done.
 Loading package pretty-1.1.1.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 ValD (VarP f1_2) (NormalB (VarE GHC.Base.id)) []
 PragmaD (InlineP f1_2 (InlineSpec NoInline False Nothing))
 ValD (VarP f2_1) (NormalB (VarE GHC.Base.id)) []
 PragmaD (InlineP f2_1 (InlineSpec Inline False Nothing))
 ValD (VarP f3_0) (NormalB (VarE GHC.Base.id)) []
 PragmaD (InlineP f3_0 (InlineSpec Inlinable False Nothing))
 }}}
 The other way around:
 {{{
 {-# LANGUAGE UnicodeSyntax #-}

 module TH where

 import Language.Haskell.TH

 noInlineP ∷ Name → DecsQ
 noInlineP n = fmap return $ pragInlD n $ inlineSpecNoPhase NoInline False

 inlineP ∷ Name → DecsQ
 inlineP n = fmap return $ pragInlD n $ inlineSpecNoPhase Inline False

 inlinableP ∷ Name → DecsQ
 inlinableP n = fmap return $ pragInlD n $ inlineSpecNoPhase Inlinable
 False
 }}}
 {{{
 {-# LANGUAGE UnicodeSyntax #-}
 {-# LANGUAGE TemplateHaskell #-}

 import TH

 f1, f2, f3 ∷ α → α
 f1 = id
 f2 = id
 f3 = id

 $(noInlineP 'f1)
 $(inlineP 'f2)
 $(inlinableP 'f3)

 main = return ()
 }}}
 {{{
 $ ghc-stage2 -ddump-splices -fforce-recomp TH.hs Main.hs
 [1 of 2] Compiling TH   ( TH.hs, TH.o )
 [2 of 2] Compiling Main ( Main.hs, Main.o )
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package pretty-1.1.1.0 ... linking ... done.
 Loading package array-0.3.0.3 ... linking ... done.
 Loading package deepseq-1.2.0.1 ... linking ... done.
 Loading package containers-0.4.2.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 Main.hs:1:1: Splicing declarations
 noInlineP 'f1
   ==>
 Main.hs:11:3-15
 {-# NOINLINE f1 #-}
 Main.hs:1:1: Splicing declarations
 inlineP 'f2
   ==>
 Main.hs:12:3-13
 {-# INLINE f2 #-}
 Main.hs:1:1: Splicing declarations
 inlinableP 'f3
   ==>
 Main.hs:13:3-16
 {-# INLINABLE[ALWAYS] f3 #-}
 Linking Main ...
 }}}
 Please review the patches.

-- 
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] #5849: Buliding on arm broke in 7.4.1

2012-02-07 Thread GHC
#5849: Buliding on arm broke in 7.4.1
---+
Reporter:  nomeata |   Owner: 
Type:  bug |  Status:  new
Priority:  high|   Milestone:  7.4.2  
   Component:  Runtime System  | Version:  7.4.1  
Keywords:  |  Os:  Linux  
Architecture:  arm | Failure:  Building GHC failed
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+

Comment(by igloo):

 Replying to [ticket:5849 nomeata]:
 > As you can see here:
 > https://buildd.debian.org/status/logs.php?pkg=ghc&arch=armel
 > the GHC build fails on armel on Debian, and the change was introduced
 between the last release candidate and the final release. This is not a
 good time to make such changes, as it makes testing the release candidates
 somewhat obsolete. *slightgrumble*

 Sorry. Other Arm users had reported that the compiler was broken without
 these patches. As the patches could only affect the Arm platform (as the
 changes are all inside CPP conditionals), and as the platform was
 apparently broken without them, it seemed safe to put them in.

 We could have put out another RC, but that would have meant more man
 hours, at least another week's delay, and there are diminishing returns on
 RCs - the more we put out, the fewer people are able to find time to test
 them.

 Incidentally, 4647278919ce724717db93af605741b4a419b3b2 is also involved.

-- 
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] #5757: zero unexpected failures on all tier 1 platforms

2012-02-07 Thread GHC
#5757: zero unexpected failures on all tier 1 platforms
-+--
Reporter:  simonmar  |   Owner:  
Type:  task  |  Status:  new 
Priority:  highest   |   Milestone:  7.4.2   
   Component:  Test Suite| Version:  7.2.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:  #5785, #5757  |  
-+--

Comment(by simonmar):

 FYI, at 7.4.1 the status was

 x86_64/Linux: zero

 x86/Linux:
 {{{
../../libraries/base/tests  CPUTime001 [bad stdout] (threaded2)
rts 5250 [bad exit code] (optllvm)
 }}}

 x86/Windows:
 {{{
../../libraries/hpc/tests/function  subdir/tough2 [bad stdout]
 (normal,hpc,optasm,threaded1,threaded2,dyn)
../../libraries/hpc/tests/function  tough [bad stdout]
 (normal,hpc,optasm,profasm,threaded1,threaded2,dyn,profthreaded)
../../libraries/hpc/tests/simplehpc001 [bad stdout]
 (normal,hpc,optasm,profasm,threaded1,threaded2,dyn,profthreaded)
driver  5313 [bad exit code] (dyn)
dynlibs T4464 [bad stderr] (normal)
ghc-api/dynCompileExpr  dynCompileExpr [bad exit code]
 (dyn)
ghci/linkingghcilink004 [bad exit code]
 (normal)
ghci/linkingghcilink005 [bad exit code]
 (normal)
lib/IO  T4113 [bad stdout]
 (normal,hpc,optasm,profasm,threaded1,threaded2,dyn,profthreaded)
lib/IO  T4113 [bad stdout or stderr] (ghci)
lib/should_run  stableptr003 [bad stdout] (dyn)
programs/barton-mangler-bug barton-mangler-bug [exit code
 non-0] (dyn)
rts derefnull [bad exit code] (ghci)
rts derefnull [bad profile]
 (profasm,profthreaded)
rts divbyzero [bad exit code] (ghci)
rts divbyzero [bad profile]
 (profasm,profthreaded)
typecheck/should_fail   T5300 [stderr mismatch] (normal)
 }}}

 x86/OSX and x86_64/OSX: anyone have results for these?

-- 
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] #5836: GHCi silently fails to import non-existing modules

2012-02-07 Thread GHC
#5836: GHCi silently fails to import non-existing modules
-+--
Reporter:  hvr   |   Owner:  simonmar
Type:  bug   |  Status:  merge   
Priority:  high  |   Milestone:  7.4.2   
   Component:  GHCi  | Version:  7.4.1-rc2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  Other   
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonmar):

 BTW, a test will be along soon.

-- 
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] #5836: GHCi silently fails to import non-existing modules

2012-02-07 Thread GHC
#5836: GHCi silently fails to import non-existing modules
-+--
Reporter:  hvr   |   Owner:  simonmar
Type:  bug   |  Status:  merge   
Priority:  high  |   Milestone:  7.4.2   
   Component:  GHCi  | Version:  7.4.1-rc2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  Other   
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonmar):

  * status:  new => merge


Comment:

 Fixed:

 commit e46d26686034448a311f48f7e685f159af865d7c
 {{{
 Author: Simon Marlow 
 Date:   Wed Feb 1 12:57:54 2012 +

 Check that imported modules actually exist (#5836)
 }}}

-- 
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] #5838: integer overflow in rts/RtsUtils:heapOverflow()

2012-02-07 Thread GHC
#5838: integer overflow in rts/RtsUtils:heapOverflow()
---+
Reporter:  hvr |   Owner:  simonmar   
Type:  bug |  Status:  merge  
Priority:  high|   Milestone:  7.4.2  
   Component:  Runtime System  | Version:  7.2.2  
Keywords:  |  Os:  Unknown/Multiple   
Architecture:  x86_64 (amd64)  | Failure:  Incorrect result at runtime
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+
Changes (by simonmar):

  * status:  patch => merge


Comment:

 Fixed (but I got the ticket number wrong in the commit log):

 commit bf456a09f9ef68436db48eb5ea25193d3b2f2ed5

 {{{
 Author: Simon Marlow 
 Date:   Thu Feb 2 10:28:34 2012 +

 avoid 32-bit integer overflow (#5831)
 }}}

-- 
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] #5813: Offer a compiler warning for failable pattern matches

2012-02-07 Thread GHC
#5813: Offer a compiler warning for failable pattern matches
-+--
Reporter:  snoyberg  |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.2.2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by snoyberg):

 Having a flag at all would definitely be an improvement. I would still
 prefer that it be on with -Wall, but I understand the hesitation in doing
 so.

-- 
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] #2301: Proper handling of SIGINT/SIGQUIT

2012-02-07 Thread GHC
#2301: Proper handling of SIGINT/SIGQUIT
--+-
  Reporter:  duncan   |  Owner:  
  Type:  bug  | Status:  new 
  Priority:  normal   |  Milestone:  7.4.1   
 Component:  libraries/process|Version:  6.12.3  
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-

Comment(by simonmar):

 See also #5766

-- 
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] #5766: Asynchronous exception bugs in readProcess and readProcessWithExitCode

2012-02-07 Thread GHC
#5766: Asynchronous exception bugs in readProcess and readProcessWithExitCode
--+-
Reporter:  basvandijk |   Owner:  
Type:  bug|  Status:  patch   
Priority:  normal |   Milestone:  7.6.1   
   Component:  libraries/process  | Version:  7.2.2   
Keywords: |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
  Difficulty:  Unknown|Testcase:  
   Blockedby: |Blocking:  
 Related: |  
--+-

Comment(by simonmar):

 Ok, let's go with the behaviour you've implemented.  However, I think it
 should be documented that an asynchronous exception will trigger a
 `terminateProcess`; if the programmer wants something different then they
 will have to implement their own version of `readProcess`.

 This ticket relates to #2301, but we haven't solved that yet.  When we do,
 we should take into account `readProcess` too.

-- 
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] #5820: defining instance in GHCi leads to duplicated instances

2012-02-07 Thread GHC
#5820: defining instance in GHCi leads to duplicated instances
-+--
Reporter:  guest |   Owner:  
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.4.2   
   Component:  GHCi  | Version:  7.4.1-rc1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by castor):

 * cc: castor@… (added)


Comment:

 This problem also occurs using non-user-defined types. Take a look at the
 snippet below:[[BR]]
 [[BR]]
 fernando@Castor ~/src $ cat Foo.hs[[BR]]
 instance Num Bool where[[BR]]
 fernando@Castor ~/src $ ghc/inplace/bin/ghc-stage2 --interactive -w
 Foo.hs[[BR]]
 GHCi, version 7.5.20120130: http://www.haskell.org/ghc/  :? for help[[BR]]
 Loading package ghc-prim ... linking ... done.[[BR]]
 Loading package integer-gmp ... linking ... done.[[BR]]
 Loading package base ... linking ... done.[[BR]]
 [1 of 1] Compiling Main ( Foo.hs, interpreted )[[BR]]
 Ok, modules loaded: Main.[[BR]]
 *Main> :info Bool[[BR]]
 data Bool = False | True-- Defined in `GHC.Types'[[BR]]
 instance Num Bool -- Defined at Foo.hs:1:10[[BR]]
 instance Bounded Bool -- Defined in `GHC.Enum'[[BR]]
 instance Enum Bool -- Defined in `GHC.Enum'[[BR]]
 instance Eq Bool -- Defined in `GHC.Classes'[[BR]]
 instance Ord Bool -- Defined in `GHC.Classes'[[BR]]
 instance Read Bool -- Defined in `GHC.Read'[[BR]]
 instance Show Bool -- Defined in `GHC.Show'[[BR]]
 *Main> instance Fractional Bool where[[BR]]
 *Main> :info Bool[[BR]]
 data Bool = False | True-- Defined in `GHC.Types'[[BR]]
 instance Fractional Bool -- Defined at :3:10[[BR]]
 instance Num Bool -- Defined at Foo.hs:1:10[[BR]]
 instance Num Bool -- Defined at Foo.hs:1:10[[BR]]
 instance Bounded Bool -- Defined in `GHC.Enum'[[BR]]
 instance Enum Bool -- Defined in `GHC.Enum'[[BR]]
 instance Eq Bool -- Defined in `GHC.Classes'[[BR]]
 instance Ord Bool -- Defined in `GHC.Classes'[[BR]]
 instance Read Bool -- Defined in `GHC.Read'[[BR]]
 instance Show Bool -- Defined in `GHC.Show'[[BR]]
 [[BR]]
 This was the simplest program with which I was able to reproduce the
 problem.

-- 
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] #5813: Offer a compiler warning for failable pattern matches

2012-02-07 Thread GHC
#5813: Offer a compiler warning for failable pattern matches
-+--
Reporter:  snoyberg  |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.2.2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by maeder):

 Replying to [comment:5 simonmar]:
 > In reply to maeder: the manual desugaring you describe is not semantics-
 preserving, so it's not surprising that you suddently get a new warning.

 I know, the missing cases are turned into nice _fail_ message (including
 the file position) that I would like to create explicitly by a suitable
 (non-pure?) function.

-- 
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] #5853: Out-of-memory crash when using RULES and type families

2012-02-07 Thread GHC
#5853: Out-of-memory crash when using RULES and type families
+---
 Reporter:  porges  |  Owner:
 Type:  bug | Status:  new   
 Priority:  normal  |  Component:  Compiler  
  Version:  7.4.1   |   Keywords:
   Os:  Windows |   Architecture:  x86_64 (amd64)
  Failure:  Compile-time crash  |   Testcase:
Blockedby:  |   Blocking:
  Related:  |  
+---
 GHC(i) 7.4.1 crashes with an OOM error on the following code:

 {{{
 {-# LANGUAGE NoImplicitPrelude, TypeFamilies #-}

 import Prelude (undefined,Bool(..),Show(..),(.))

 type family Elem f :: *
 type family Subst f b :: *

 class (Subst fa (Elem fa) ~ fa) => F fa where
 (<$>) :: (Elem fa ~ a, Elem fb ~ b,
   Subst fa b ~ fb, Subst fb a ~ fa) =>
  (a -> b) -> (fa -> fb)

 {-# RULES
 "map/map" forall f g xs. f <$> (g <$> xs) = (f.g) <$> xs
 #-}
 }}}

-- 
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] #5843: hGetBufSome blocks when all available input is buffered (on Windows only)

2012-02-07 Thread GHC
#5843: hGetBufSome blocks when all available input is buffered (on Windows only)
---+
Reporter:  joeyadams   |   Owner:  simonmar   
Type:  bug |  Status:  new
Priority:  high|   Milestone:  7.4.2  
   Component:  libraries/base  | Version:  7.2.2  
Keywords:  |  Os:  Windows
Architecture:  x86 | Failure:  Incorrect result at runtime
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+
Changes (by simonmar):

  * owner:  => simonmar
  * difficulty:  => Unknown
  * priority:  normal => high
  * milestone:  => 7.4.2


Comment:

 Thanks for the report.

-- 
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] #5816: static linking silently fails in ghc

2012-02-07 Thread GHC
#5816: static linking silently fails in ghc
---+
Reporter:  carter  |   Owner:  igloo   
Type:  bug |  Status:  infoneeded  
Priority:  normal  |   Milestone:  7.6.1   
   Component:  Compiler| Version:  7.2.2   
Keywords:  linking osx |  Os:  MacOS X 
Architecture:  x86_64 (amd64)  | Failure:  None/Unknown
  Difficulty:  Unknown |Testcase:  
   Blockedby:  |Blocking:  
 Related:  |  
---+

Comment(by simonmar):

 You started with a hypothesis about what the bug is: that GHC statically
 links C libraries, but GHCi dynamically links them.  That isn't true, or
 at least not usually true: GHC just calls the linker passing the
 appropriate `-lfoo` options, and the linker chooses which library to link.
 Typically the linker will choose the dynamic library over the static
 library.

 In any case, it isn't clear to me why this hypothesis (which may or may
 not be true) would give rise to a crash.  The dynamic and static versions
 of the libraries should have identical ABIs.

 So the upshot is, we need a simple reproducible example of something that
 goes wrong.

-- 
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] #5841: seg fault in ghci but not ghc when using chart-gtk code

2012-02-07 Thread GHC
#5841: seg fault in ghci but not ghc when using chart-gtk code
---+
Reporter:  carter  |   Owner:  
Type:  bug |  Status:  new 
Priority:  normal  |   Milestone:  
   Component:  Compiler| Version:  7.4.1   
Keywords:  |  Os:  MacOS X 
Architecture:  x86_64 (amd64)  | Failure:  None/Unknown
  Difficulty:  Unknown |Testcase:  
   Blockedby:  |Blocking:  
 Related:  5816|  
---+
Changes (by simonmar):

  * difficulty:  => Unknown


Comment:

 Note that GHCi is running the program with `-threaded`, I'm not sure if
 that has any bearing or not.

-- 
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] #5813: Offer a compiler warning for failable pattern matches

2012-02-07 Thread GHC
#5813: Offer a compiler warning for failable pattern matches
-+--
Reporter:  snoyberg  |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  7.6.1   
   Component:  Compiler  | Version:  7.2.2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonmar):

 For things like this we usually add a warning flag, but do ''not'' include
 it in `-Wall`.  We have a bunch of flags in this category already
 (cut/pasted from the docs):

 {{{
 -fwarn-tabs,
 -fwarn-incomplete-uni-patterns,
 -fwarn-incomplete-record-updates,
 -fwarn-monomorphism-restriction,
 -fwarn-unrecognised-pragmas,
 -fwarn-auto-orphans,
 -fwarn-implicit-prelude.
 }}}

 In reply to maeder: the manual desugaring you describe is not semantics-
 preserving, so it's not surprising that you suddently get a new warning.

-- 
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] #5851: RTS Crashes on Exit with double free

2012-02-07 Thread GHC
#5851: RTS Crashes on Exit with double free
---+
Reporter:  argiopeweb  |   Owner:  simonmar 
Type:  bug |  Status:  merge
Priority:  high|   Milestone:  7.4.2
   Component:  Runtime System  | Version:  7.4.1
Keywords:  glibc rts free pointer  |  Os:  Linux
Architecture:  x86_64 (amd64)  | Failure:  Runtime crash
  Difficulty:  Unknown |Testcase:   
   Blockedby:  |Blocking:   
 Related:  |  
---+
Changes (by simonmar):

  * status:  new => merge


Comment:

 I already fixed this in HEAD, but we forgot to merge it.

 commit dff852b1b65d07a4a400d3f20c854172c8fcecaf
 {{{
 Author: Simon Marlow 
 Date:   Wed Dec 14 10:42:47 2011 +

 Fix a memory allocation bug (rts_argv wasn't big enough)
 }}}

-- 
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] #5849: Buliding on arm broke in 7.4.1

2012-02-07 Thread GHC
#5849: Buliding on arm broke in 7.4.1
---+
Reporter:  nomeata |   Owner: 
Type:  bug |  Status:  new
Priority:  high|   Milestone:  7.4.2  
   Component:  Runtime System  | Version:  7.4.1  
Keywords:  |  Os:  Linux  
Architecture:  arm | Failure:  Building GHC failed
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+

Comment(by nomeata):

 Yes, I can test it, but not come up with one...

-- 
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] #5851: RTS Crashes on Exit with double free

2012-02-07 Thread GHC
#5851: RTS Crashes on Exit with double free
---+
Reporter:  argiopeweb  |   Owner:  simonmar 
Type:  bug |  Status:  new  
Priority:  high|   Milestone:  7.4.2
   Component:  Runtime System  | Version:  7.4.1
Keywords:  glibc rts free pointer  |  Os:  Linux
Architecture:  x86_64 (amd64)  | Failure:  Runtime crash
  Difficulty:  Unknown |Testcase:   
   Blockedby:  |Blocking:   
 Related:  |  
---+
Changes (by simonmar):

  * owner:  => simonmar
  * difficulty:  => Unknown
  * priority:  normal => high
  * milestone:  => 7.4.2


Comment:

 Thanks for the report, I'll investigate.

-- 
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] #5850: Greater customization of GHCi prompt

2012-02-07 Thread GHC
#5850: Greater customization of GHCi prompt
-+--
Reporter:  JamesFisher   |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  7.6.1   
   Component:  GHCi  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonmar):

  * difficulty:  => Unknown
  * milestone:  => 7.6.1


Comment:

 I think the 3rd option would be the most general, and fits nicely.

 I don't have plans to tackle this in the short term, but by all means
 submit a patch.

-- 
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] #5844: Panic on generating Core code

2012-02-07 Thread GHC
#5844: Panic on generating Core code
-+--
Reporter:  JamesFisher   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Milestone:  7.6.1 
   Component:  External Core | Version:  7.4.1 
Keywords:|  Os:  Unknown/Multiple  
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--
Changes (by simonmar):

  * milestone:  => 7.6.1


Comment:

 Replying to [comment:4 simonpj]:
 > Whenever we extend Core we have to invent new External Core syntax to
 match.  And we have not done that with type-level literals.

 I think in fact it's the new Integer literals, not type-level literals,
 causing the reported problem here.

 Replying to [comment:5 JamesFisher]:
 > Ah, I see.  Is this where we should be looking?:
 
[http://hackage.haskell.org/trac/ghc/browser/compiler/coreSyn/PprExternalCore.lhs]

 Yes.

-- 
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] #5849: Buliding on arm broke in 7.4.1

2012-02-07 Thread GHC
#5849: Buliding on arm broke in 7.4.1
---+
Reporter:  nomeata |   Owner: 
Type:  bug |  Status:  new
Priority:  high|   Milestone:  7.4.2  
   Component:  Runtime System  | Version:  7.4.1  
Keywords:  |  Os:  Linux  
Architecture:  arm | Failure:  Building GHC failed
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+
Changes (by simonmar):

  * priority:  normal => high
  * difficulty:  => Unknown
  * milestone:  => 7.4.2


Comment:

 Sorry about that.  Can you test a fix and send it to us, and we'll get it
 into 7.4.2?

-- 
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] #5852: methods and associated types treated differently wrt. qualification

2012-02-07 Thread GHC
#5852: methods and associated types treated differently wrt. qualification
--+-
 Reporter:  jeltsch   |  Owner: 
 Type:  feature request   | Status:  new
 Priority:  normal|  Component:  Compiler   
  Version:  7.0.4 |   Keywords:  type families, qualified import
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple   
  Failure:  Other |   Testcase: 
Blockedby:|   Blocking: 
  Related:|  
--+-
 Say I have the following module:
 {{{
 {-# LANGUAGE TypeFamilies #-}
 module M where

 class C a where

 type T a :: *

 m :: a
 }}}
 Now I use this module in another module via a qualified import:
 {{{
 {-# LANGUAGE TypeFamilies #-}
 module U where

 import qualified M

 instance M.C Integer where

 type M.T Integer = Integer

 m = 0
 }}}
 Note that in the instance declaration, the associated type {{{T}}} is
 qualified, while the method {{{m}}} is not. Removing the qualification of
 {{{T}}} is not accepted by GHC, but neither is adding a qualification to
 {{{m}}}. I think this inconsistency is unfortunate, so that it might be
 good to remove it.

-- 
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] #5818: gcd and fizzled reversed in event SparkCounters

2012-02-07 Thread GHC
#5818: gcd and fizzled reversed in event SparkCounters
--+-
  Reporter:  MikolajKonarski  |  Owner:  duncan  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  7.6.1   
 Component:  Runtime System   |Version:  7.4.1-rc1   
Resolution:  wontfix  |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonmar):

  * status:  new => closed
  * resolution:  => wontfix


Comment:

 Thanks!  I'll close the bug then.

-- 
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] #5818: gcd and fizzled reversed in event SparkCounters

2012-02-07 Thread GHC
#5818: gcd and fizzled reversed in event SparkCounters
-+--
Reporter:  MikolajKonarski   |   Owner:  duncan 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone:  7.6.1  
   Component:  Runtime System| Version:  7.4.1-rc1  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Incorrect result at runtime
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--

Comment(by MikolajKonarski):

 Duncan has chosen the last option. The minimal fix on the ghc-events side
 is here:

 [https://github.com/Mikolaj/ghc-
 events/commit/8f20e9f35d73507355f2c90440f5a367a5dcb0bc]

 dcoutts: if you don't mind I'd break the ghc-events API (the utility
 facing part, not the GHC facing part) to keep the order of fiz and gcd
 consistent across all code
 dcoutts: https://github.com/Mikolaj/ghc-
 events/commit/ec4dd1311502f52edce721ea1cefa1becc66706e
 dcoutts: about a dozen changes are required in TS to adapt to the changed
 API
 dcoutts: I think it's better to do the changes now when we remember about
 the fiz and gcd swap
 dcoutts: rather than hunt bugs stemming from the inconsistent order later
 on

-- 
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] #5851: RTS Crashes on Exit with double free

2012-02-07 Thread GHC
#5851: RTS Crashes on Exit with double free
---+
 Reporter:  argiopeweb |  Owner:
 Type:  bug| Status:  new   
 Priority:  normal |  Component:  Runtime System
  Version:  7.4.1  |   Keywords:  glibc rts free pointer
   Os:  Linux  |   Architecture:  x86_64 (amd64)
  Failure:  Runtime crash  |   Testcase:
Blockedby: |   Blocking:
  Related: |  
---+

Comment(by argiopeweb):

 Also confirmed present in GHC 7.2.2 on CentOS 5 with error message
 {{{
 *** glibc detected *** test: double free or corruption (out):
 0x17e744f0 ***
 *** glibc detected *** test: corrupted double-linked list:
 0x17e744c0 ***
 }}}

 Error does not occur if built with "-rtsopts" and run with "+RTS -N -A4m
 -H128m -G5"

-- 
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] #5851: RTS Crashes on Exit with double free

2012-02-07 Thread GHC
#5851: RTS Crashes on Exit with double free
---+
 Reporter:  argiopeweb |  Owner:
 Type:  bug| Status:  new   
 Priority:  normal |  Component:  Runtime System
  Version:  7.4.1  |   Keywords:  glibc rts free pointer
   Os:  Linux  |   Architecture:  x86_64 (amd64)
  Failure:  Runtime crash  |   Testcase:
Blockedby: |   Blocking:
  Related: |  
---+
 On compiling with
 {{{
 ghc -threaded -with-rtsopts="-N2 -A4m -H128m -G4"
 }}}
  or
 {{{
 ghc -threaded -with-rtsopts="-N2 -H128m -G4"
 }}}
 RTS crashes on exit (normal or sigINT) with glibc "free(): invalid
 pointer" and "double free or corruption (out)" errors, respectively.

-- 
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