Re: [GHC] #4110: hsc2hs gives bad error message when it cannot execute the generated program

2010-06-07 Thread GHC
#4110: hsc2hs gives bad error message when it cannot execute the generated 
program
-+--
Reporter:  duncan|   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Component:  hsc2hs  
 Version:  6.12.2|Keywords:  
  Os:  Unknown/Multiple  |Testcase:  
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
-+--

Comment(by duncan):

 A fix for #3649 would likely also help this case.

-- 
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] #3649: inconsistent exception between unix/windows for running non-existant program

2010-06-07 Thread GHC
#3649: inconsistent exception between unix/windows for running non-existant
program
--+-
Reporter:  duncan |Owner:  
Type:  bug|   Status:  new 
Priority:  normal |Milestone:  6.14.1  
   Component:  libraries/process  |  Version:  6.10.4  
Keywords: |   Difficulty:  
  Os:  Unknown/Multiple   | Testcase:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by duncan):

 Another instance of the same problem is when we do not have permission to
 execute the program (see ticket #4110 where the original example is about
 /tmp being mounted "noexec").

-- 
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] #4118: GHC forces gcc version on mingw32

2010-06-07 Thread GHC
#4118: GHC forces gcc version on mingw32
+---
Reporter:  uzytkownik   |  Owner:  
Type:  bug  | Status:  closed  
Priority:  normal   |  Component:  Compiler
 Version:  6.12.1   | Resolution:  wontfix 
Keywords:   | Os:  Unknown/Multiple
Testcase:   |   Architecture:  Unknown/Multiple
 Failure:  Building GHC failed  |  
+---
Changes (by duncan):

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


Comment:

 This is the intended behaviour. We cannot by default rely on an existing
 mingw or cygwin installation. There are sometimes subtle compatibility
 issues.

 Of course if you specifically want to use a different gcc installation
 then that is fine. It is just that ghc should not use a different one
 automatically without the user knowing about it.

 You can override the gcc that ghc uses by using command line flags (see
 the [http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/options-
 phases.html#replacing-phases ghc user guide for details ] and note that
 you will need to specify all of `-pgmc`, `-pgma` and `-pgml`).

-- 
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] #2458: Unknown symbol `_environ' on MacOS X

2010-06-07 Thread GHC
#2458: Unknown symbol `_environ' on MacOS X
-+--
  Reporter:  IgorBoehm   |  Owner: 
  Type:  bug | Status:  new
  Priority:  high|  Milestone:  6.14.1 
 Component:  libraries/base  |Version:  6.10.1 
Resolution:  |   Keywords:  environ
Difficulty:  Unknown | Os:  MacOS X
  Testcase:  |   Architecture:  x86
   Failure:  None/Unknown|  
-+--
Changes (by igloo):

  * priority:  normal => high
  * milestone:  6.12.3 => 6.14.1


Comment:

 {{{
 [20:55] < safiire> Has anyone here ran into a problem of trying to link a
library compiled with ghc -c into a C++ project and
receiving an unresolved symbol _environ.  I am aware
 that
_environ is supposed to be defined in crt1.o, however
 the
C++ project I am building is an audio unit plugin on
 OSX, so
it never links against crt1.o as it is not an
 executable,
but a shared object itself.  There is something called
 the
osx _environ bug which is the cause of t
 [20:55] < safiire> his.  The work around is that OSX applications are not
supposed to call environ(), but are supposed to call
_NSGetEnviron(), or, that is the workaround at least.
HSBase4.2.0.0.a does not do this on OSX apparently.
 Does
anyone know how I can get my linker resolve this
 symbol, or
not care that it is undefined, short of recompling
 haskel
from source and manually patching it to not call
 environ()?
 }}}

-- 
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] #4115: hsc2hs puts linker flags before object file, causes linker errors

2010-06-07 Thread GHC
#4115: hsc2hs puts linker flags before object file, causes linker errors
-+--
Reporter:  guest |Owner:
Type:  bug   |   Status:  patch 
Priority:  normal|Milestone:
   Component:  hsc2hs|  Version:  6.10.2
Keywords:|   Difficulty:
  Os:  Unknown/Multiple  | Testcase:
Architecture:  Unknown/Multiple  |  Failure:  Other 
-+--
Changes (by igloo):

  * status:  new => 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] #4116: Type supplement for constructor specific uses of sum types

2010-06-07 Thread GHC
#4116: Type supplement for constructor specific uses of sum types
-+--
Reporter:  gabrielrf |   Owner:  
Type:  proposal  |  Status:  new 
Priority:  normal|   Component:  Compiler
 Version:  6.13  |Keywords:  
  Os:  Unknown/Multiple  |Testcase:  
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
-+--

Comment(by gabrielrf):

 Benefits: Avoid ''error'' calls (runtime), exception control and Maybe
 types
 in partially defined (constructor specific) functions on sum types

 Method: by refining function argument types with a list of constructors
 applyable
 and detecting the target constructor at the caller through pattern
 matching,
 flagging with compiler errors the unmatched cases.


 As an example, with

 {{{
data List a = Nil | Cons a (List a)
 }}}


 * Actual system: undefined cases are discriminated with runtime errors or
 exception throwing or optional Maybe results.

 {{{
hd :: List a -> a
hd (Cons x _) -> x
hd Nil -> error "error: hd: empty list" -- (as in GHC Data.List head)
 }}}

 * Proposed system: supplement types with
  a suffix ''@Constructor'' or ''@{Constructor1, Constructor2}''

 denoting the list of constructors to which the function can be applied.

 {{{
hd :: List @Cons a -> a
hd (Cons x _) = x

-- no definition for unappropriate constructors.
 }}}

 The caller must do pattern matching before applying the constructor-
 specific function.

 In a pattern ''var @ (Constructor {})''
 the compiler should set a ''constructorAt'' property for ''var''
 to the specified pattern constructor
 and when used in a constructor specific parameter position
 match the type supplement constructor list


 using it:

 {{{
accumulateHead :: (a->b) -> a -> List a -> b

accumulateHead f accum list = case list of

 li @ Cons {} -> f accum $ hd li  -- constructorAt li == 'Cons'
  -- should pass typechecker at ''hd'' for
 ''List @ Cons''

 li @ Nil  -> f accum $ hd li -- compiler error !!
 -- constructorAt li == 'Nil' ; no match

 _ -> f accum $ hd list   -- compiler error !!
 -- constructorAt list == Nothing ; no
 match

 _ -> accum   -- default option closing pattern matching
 exhaustivity.
 }}}

 >(from Jason Dagit contribution)
 >
 >Syntax {Cons, Cons2} for more than one constructor

 {{{
  data List2 a = Nil | Cons a (List2 a) | Cons2 a a (List2 a)

  hd :: List2 @ {Cons, Cons2} a -> a
 }}}

 Discussion thread:

 [http://thread.gmane.org/gmane.comp.lang.haskell.cafe/75586]

-- 
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] #3947: ghc: panic! (the 'impossible' happened)

2010-06-07 Thread GHC
#3947: ghc: panic! (the 'impossible' happened)
---+
  Reporter:  steenreem |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  6.10.4  
Resolution:  duplicate |   Keywords:  
Difficulty:| Os:  Unknown/Multiple
  Testcase:|   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  |  
---+
Changes (by simonmar):

  * status:  infoneeded => closed
  * version:  6.12.1 => 6.10.4
  * resolution:  => duplicate
  * milestone:  6.12.3 =>


Comment:

 Dup of #3435.

-- 
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] #4117: GHC does not accept --srcdir

2010-06-07 Thread GHC
#4117: GHC does not accept --srcdir
-+--
Reporter:  uzytkownik|   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Component:  Compiler   
 Version:  6.12.1|Keywords: 
  Os:  Unknown/Multiple  |Testcase: 
Architecture:  Unknown/Multiple  | Failure:  Building GHC failed
-+--
 GHC does not accept --srcdir during building. (Yes - I know of error but
 it should be fixed).

 PS. Priority is probably lower then normal
 PPS. For question why - I try to integrate it with takeoffgw so I try to
 write cygbuild which uses separate build directory.

-- 
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] #4118: GHC forces gcc version on mingw32

2010-06-07 Thread GHC
#4118: GHC forces gcc version on mingw32
-+--
Reporter:  uzytkownik|   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Component:  Compiler   
 Version:  6.12.1|Keywords: 
  Os:  Unknown/Multiple  |Testcase: 
Architecture:  Unknown/Multiple  | Failure:  Building GHC failed
-+--
 GHC forces internal gcc version on mingw32 instead of using system 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] #4106: undefined reference to `__stg_EAGER_BLACKHOLE_INFO'

2010-06-07 Thread GHC
#4106: undefined reference to `__stg_EAGER_BLACKHOLE_INFO'
---+
  Reporter:  Mikolaj   |  Owner:  simonmar
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  6.12.1  
Resolution:  fixed |   Keywords:  
Difficulty:| Os:  Linux   
  Testcase:|   Architecture:  powerpc 
   Failure:  Other |  
---+

Comment(by Mikolaj):

 Thank you. The problems with black hole are gone. I've recompiled Debian's
 ghc6_6.12.1-13 after applying your change, and the parallel tests now are:

 {{{
3 total tests, which gave rise to
   19 test cases, of which
0 caused framework failures
   15 were skipped

4 expected passes
0 expected failures
0 unexpected passes
0 unexpected failures
 }}}


 where the skipped tests are unrelated to black hole and probably due to
 the Ghostscript problem, as in the previously attached log.

-- 
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] #4119: File buffering isn't flushed at exit

2010-06-07 Thread GHC
#4119: File buffering isn't flushed at exit
---+
Reporter:  EyalLotem   |   Owner: 
Type:  bug |  Status:  new
Priority:  normal  |   Component:  libraries/base 
 Version:  6.12.1  |Keywords:  file buffers   
  Os:  Linux   |Testcase: 
Architecture:  x86_64 (amd64)  | Failure:  Incorrect result at runtime
---+
 In C, there's an atexit handler to fflush all FILE* files.

 In most other environments (e.g: Python files), file buffers are flushed
 in a graceful exit.  With GHC 6.12.1, they aren't.

-- 
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] #4115: hsc2hs puts linker flags before object file, causes linker errors

2010-06-07 Thread GHC
#4115: hsc2hs puts linker flags before object file, causes linker errors
-+--
Reporter:  guest |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Component:  hsc2hs
 Version:  6.10.2|Keywords:
  Os:  Unknown/Multiple  |Testcase:
Architecture:  Unknown/Multiple  | Failure:  Other 
-+--

Comment(by duncan):

 Patch needs testing.

-- 
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] #3984: interpret layout in GHCi

2010-06-07 Thread GHC
#3984: interpret layout in GHCi
--+-
  Reporter:  aavogt   |  Owner:  igloo   
  Type:  feature request  | Status:  closed  
  Priority:  normal   |  Milestone:  6.14.1  
 Component:  GHCi |Version:  6.12.1  
Resolution:  fixed|   Keywords:  
Difficulty:   | Os:  Unknown/Multiple
  Testcase:   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown |  
--+-
Changes (by igloo):

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


Comment:

 Applied, thanks!

-- 
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] #3982: Random instance for Double can generate values out of requested range

2010-06-07 Thread GHC
#3982: Random instance for Double can generate values out of requested range
--+-
  Reporter:  mokus|  Owner:  igloo   
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  6.14.1  
 Component:  libraries/random |Version:  6.12.1  
Resolution:  fixed|   Keywords:  
Difficulty:   | Os:  Unknown/Multiple
  Testcase:   |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  |  
--+-
Changes (by igloo):

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


Comment:

 Applied, thanks!

-- 
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] #3984: interpret layout in GHCi

2010-06-07 Thread GHC
#3984: interpret layout in GHCi
--+-
  Reporter:  aavogt   |  Owner:  
  Type:  feature request  | Status:  new 
  Priority:  normal   |  Milestone:  6.14.1  
 Component:  GHCi |Version:  6.12.1  
Resolution:   |   Keywords:  
Difficulty:   | Os:  Unknown/Multiple
  Testcase:   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown |  
--+-
Changes (by igloo):

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


Comment:

 We still need to fix the editing, e.g. "up" should give you the whole
 multi-line input at once, rather than giving it to you line-by-line.

-- 
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] #4120: Iface type variable out of scope in cast

2010-06-07 Thread GHC
#4120: Iface type variable out of scope in cast
-+--
Reporter:  benl  |   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Component:  Compiler (Type checker)
 Version:  6.13  |Keywords: 
  Os:  Unknown/Multiple  |Testcase: 
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
-+--
 Compiling the following module against vector-0.6 or 0.7:

 {{{
 module Thing where
 import Data.Vector.Unboxed
 import Data.Vector.Unboxed.Mutable  as MV

 thing :: Vector Int
 thing = create (MV.new 5)
 }}}

 Complains about:
 {{{
 desire:tmp benl$ ghc -O -c -fglasgow-exts Thing.hs -fforce-recomp
 /Users/benl/.cabal/lib/vector-0.7/ghc-6.13.20100607/Data/Vector/Unboxed.hi
 Declaration for create
 Unfolding of Data.Vector.Unboxed.create:
   Iface type variable out of scope:  s
 }}}

 Looking in the interface file we have:
 {{{
   create :: forall a.
 Data.Vector.Unboxed.Base.Unbox a =>
 (forall s. GHC.ST.ST s (Data.Vector.Unboxed.Base.MVector s a))
 -> Data.Vector.Unboxed.Base.Vector a
 {- Arity: 2, Strictness: U(SA)C(U(LL)),
Inline: INLINE (sat-args=0),
Unfolding: InlineRule (1, False, False)
   (\ @ a
  $dUnbox :: Data.Vector.Unboxed.Base.Unbox a
  eta :: forall s.
 GHC.ST.ST
 s
 (Data.Vector.Generic.Base.Mutable
  Data.Vector.Unboxed.Base.Vector s a)
 ->
Data.Vector.Generic.new
  @ Data.Vector.Unboxed.Base.Vector
  @ a
  (Data.Vector.Unboxed.Base.$p1Unbox @ a $dUnbox)
  (Data.Vector.Generic.New.New
 @ Data.Vector.Unboxed.Base.Vector
 @ a
 eta))
 `cast`
   (forall a.
Data.Vector.Unboxed.Base.Unbox a =>
GHC.ST.ST s
 (Data.Vector.Unboxed.Base.TFCo:R:MutableVector s a)
-> Data.Vector.Unboxed.Base.Vector a) -}
 }}}

 The variable `s` in the right of the cast is indeed not in scope.

 This prevents `create` being inlined into client modules, which kills
 performance for benchmarks that create lots of small vectors (like a
 version of quickhull in DPH).

-- 
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] #3822: guards in arrow notation (Arrows extension) case statement cause compiler panic

2010-06-07 Thread GHC
#3822: guards in arrow notation (Arrows extension) case statement cause compiler
panic
-+--
Reporter:  StephenBlackheath |Owner:  ross  
Type:  bug   |   Status:  new   
Priority:  high  |Milestone:  6.12.3
   Component:  Compiler  |  Version:  6.12.1
Keywords:  arrows guards case panic  |   Difficulty:
  Os:  Unknown/Multiple  | Testcase:  patternGuard.hs   
Architecture:  Unknown/Multiple  |  Failure:  Compile-time crash
-+--

Comment(by simonmar):

 Ross: sorry for the delay in getting back to you.  Which bit of code is
 responsible for recognising variables as being used?  Is it arrows-
 specific, or somewhere else?  Can you help us fix it?  (Cheers, Simon &
 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] #3972: ghc 6.12.1 and 6.13.20090922 consume a lot more memory than 6.10.4 when compiling language-python package

2010-06-07 Thread GHC
#3972: ghc 6.12.1 and 6.13.20090922 consume a lot more memory than 6.10.4 when
compiling language-python package
---+
Reporter:  bjpop   |Owner:  simonpj 
  
Type:  bug |   Status:  new 
  
Priority:  high|Milestone:  6.14.1  
  
   Component:  Compiler|  Version:  6.12.1  
  
Keywords:  memory usage|   Difficulty:  
  
  Os:  Linux   | Testcase:  
http://projects.haskell.org/language-python/language-python-0.2.tar.gz
Architecture:  x86_64 (amd64)  |  Failure:  Compile-time performance bug
  
---+
Changes (by simonmar):

  * milestone:  6.12.3 => 6.14.1


Comment:

 Punting to 6.14.1 for a real fix; for 6.12 use one of the workarounds
 (probably the `-fomit-interface-pragmas` one is better).

-- 
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] #3961: -O results in incorrect behavior

2010-06-07 Thread GHC
#3961: -O results in incorrect behavior
-+--
Reporter:  RichardG  |Owner:  simonpj
Type:  bug   |   Status:  new
Priority:  high  |Milestone:  6.14.1 
   Component:  Compiler  |  Version:  6.12.1 
Keywords:|   Difficulty: 
  Os:  MacOS X   | Testcase: 
Architecture:  x86   |  Failure:  Incorrect result at runtime
-+--
Changes (by simonmar):

  * milestone:  6.12.3 => 6.14.1


Comment:

 This won't be fixed for 6.12.3, but we almost have a fix ready for HEAD.

-- 
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] #4116: Type supplement for constructor specific uses of sum types

2010-06-07 Thread GHC
#4116: Type supplement for constructor specific uses of sum types
-+--
Reporter:  gabrielrf |   Owner:  
Type:  proposal  |  Status:  new 
Priority:  normal|   Component:  Compiler
 Version:  6.13  |Keywords:  
  Os:  Unknown/Multiple  |Testcase:  
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
-+--

Comment(by gabrielrf):

 Related theoretical article:
 http://winterkoninkje.livejournal.com/56979.html

-- 
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] #4121: Ghc stage1 panic, ASSERT failure: libraries/base/Control/Applicative.hs

2010-06-07 Thread GHC
#4121: Ghc stage1 panic, ASSERT failure: libraries/base/Control/Applicative.hs
-+--
Reporter:  dterei|   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Component:  Compiler   
 Version:  6.12.2|Keywords: 
  Os:  Unknown/Multiple  |Testcase: 
Architecture:  Unknown/Multiple  | Failure:  Building GHC failed
-+--
 While comping GHC Head using the devel1 flavour and ghc-6.12.2 as the
 bootstrap compiler, I get the following assertion failure:

 {{{
 "inplace/bin/ghc-stage1"   -H64m -O -fasm-package-name base-4.3.0.0
 -hide-all-packages -i -ilibraries/base/. -ilibraries/base/dist-
 install/build -ilibraries/base/dist-install/build/autogen -Ilibraries/base
 /dist-install/build -Ilibraries/base/dist-install/build/autogen
 -Ilibraries/base/include   -optP-DOPTIMISE_INTEGER_GCD_LCM -optP-include
 -optPlibraries/base/dist-install/build/autogen/cabal_macros.h -package
 ghc-prim-0.2.0.0 -package integer-gmp-0.2.0.0 -package rts-1.0  -package-
 name base -XMagicHash -XExistentialQuantification -XRank2Types
 -XScopedTypeVariables -XUnboxedTuples -XForeignFunctionInterface
 -XUnliftedFFITypes -XDeriveDataTypeable -XGeneralizedNewtypeDeriving
 -XFlexibleInstances -XStandaloneDeriving -XPatternGuards -XEmptyDataDecls
 -XNoImplicitPrelude -XCPP -no-user-package-conf -rtsopts -O -dcore-lint
 -fno-warn-deprecated-flags -odir libraries/base/dist-install/build
 -hidir libraries/base/dist-install/build -stubdir libraries/base/dist-
 install/build -hisuf hi -osuf  o -hcsuf hc -c
 libraries/base/./Control/Applicative.hs -o libraries/base/dist-
 install/build/Control/Applicative.o

 WARNING: file compiler/simplCore/CSE.lhs line 349 a_aup
 WARNING: file compiler/simplCore/CSE.lhs line 349 a_aup
 WARNING: file compiler/stgSyn/CoreToStg.lhs line 220
 Control.Applicative.$fAlternativeSTM
 ghc-stage1: panic! (the 'impossible' happened)
   (GHC version 6.13 for i386-unknown-linux):
 ASSERT failed! file compiler/stgSyn/CoreToStg.lhs line 187
 base:Control.Applicative.$fAlternativeSTM{v rk} [gid[DFunId]]
 let {
   sat_s1oj{v} [lid]
 :: forall a{tv 12} [tv].
ghc-prim:GHC.Prim.State#{(w) tc 32q}
  ghc-prim:GHC.Prim.RealWorld{(w) tc 31E}
-> (# ghc-prim:GHC.Prim.State#{(w) tc 32q}
ghc-prim:GHC.Prim.RealWorld{(w) tc 31E},
  a{tv 12} [tv] #)
   [LclId]
   sat_s1oj{v} [lid] =
 \ (@ a{tv 12} [tv])
   (eta_B1{v} [lid]
  :: ghc-prim:GHC.Prim.State#{(w) tc 32q}
   ghc-prim:GHC.Prim.RealWorld{(w) tc 31E}) ->
   ghc-prim:GHC.Prim.retry#{(w) v 93U} [gid[PrimOp]]
 @ a{tv 12} [tv] eta_B1{v} [lid] } in
 base:Control.Applicative.D:Alternative{v rrp} [gid[DataCon]]
   @ base:GHC.Conc.STM{tc r2r}
   base:Control.Applicative.$fApplicativeSTM{v r2q} [gid[DFunId]]
   (sat_s1oj{v} [lid]
`cast` (forall a{tv aIy} [tv].
ghc-prim:GHC.Prim.sym{(w) tc 34v}
  (base:GHC.Conc.NTCo:STM{tc r2m} a{tv aIy} [tv])
:: (forall a{tv aIy} [tv].
ghc-prim:GHC.Prim.State#{(w) tc 32q}
  ghc-prim:GHC.Prim.RealWorld{(w) tc 31E}
-> (# ghc-prim:GHC.Prim.State#{(w) tc 32q}
ghc-prim:GHC.Prim.RealWorld{(w) tc 31E},
  a{tv aIy} [tv] #))
 ~
   (forall a{tv aIy} [tv]. base:GHC.Conc.STM{tc r2r} a{tv aIy}
 [tv])))
   (base:GHC.Conc.orElse1{v re9} [gid]
`cast` (forall a{tv aIx} [tv].
base:GHC.Conc.STM{tc r2r} a{tv aIx} [tv]
-> base:GHC.Conc.STM{tc r2r} a{tv aIx} [tv]
-> ghc-prim:GHC.Prim.sym{(w) tc 34v}
 (base:GHC.Conc.NTCo:STM{tc r2m} a{tv aIx} [tv])
:: (forall a{tv aIx} [tv].
base:GHC.Conc.STM{tc r2r} a{tv aIx} [tv]
-> base:GHC.Conc.STM{tc r2r} a{tv aIx} [tv]
-> ghc-prim:GHC.Prim.State#{(w) tc 32q}
 ghc-prim:GHC.Prim.RealWorld{(w) tc 31E}
-> (# ghc-prim:GHC.Prim.State#{(w) tc 32q}
ghc-prim:GHC.Prim.RealWorld{(w) tc 31E},
  a{tv aIx} [tv] #))
 ~
   (forall a{tv aIx} [tv].
base:GHC.Conc.STM{tc r2r} a{tv aIx} [tv]
-> base:GHC.Conc.STM{tc r2r} a{tv aIx} [tv]
-> base:GHC.Conc.STM{tc r2r} a{tv aIx} [tv])))
   (base:Control.Applicative.$fAlternativeSTM3{v r2n} [gid]
`cast` (forall a{tv aup} [sk].
base:GHC.Conc.STM{tc r2r} a{tv aup} [sk]
-> ghc-prim:GHC.Prim.sym{(w) tc 34v}
 (base:GHC.Conc.NTCo:STM{tc r2m} [a{tv aup} [sk]])
:: (forall a{tv aup} [sk].
base:GHC.Conc.STM{tc