#5533: panic! (the 'impossible' happened) ... splitFunTy ...
---------------------------------+------------------------------------------
Reporter: guest | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.0.3 | Keywords: splitFunTy
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
"MyModule.hs" containing these four lines:
{{{
module MyModule where
data T a = CT {f1 :: Int -> a, f2 :: Double}
f2 :: Int -> Double
g x = CT {f1 = \t -> f2 t + x, f2 = x}
}}}
yields:
{{{
C:\Tasks\Task_IsolateGhcBug>ghc --make MyModule.hs -v
Glasgow Haskell Compiler, Version 7.0.3, for Haskell 98, stage 2 booted by
GHC version 6.12.2
Using binary package database: C:\Programme\Haskell
Platform\2011.2.0.1\lib\package.conf.d\package.cache
wired-in package ghc-prim mapped to ghc-
prim-0.2.0.0-e1f7c380581d61d42b0360d440cc35ed
wired-in package integer-gmp mapped to integer-
gmp-0.2.0.3-91607778cf3ae8f3948a50062b4f8479
wired-in package base mapped to
base-4.3.1.0-f520cd232cc386346843c4a12b63f44b
wired-in package rts mapped to builtin_rts
wired-in package template-haskell mapped to template-
haskell-2.5.0.0-7d9b1443ac5ab69e5ed705a487990deb
wired-in package dph-seq not found.
wired-in package dph-par not found.
Hsc static flags: -static
*** Chasing dependencies:
Chasing modules from: *MyModule.hs
Stable obj: []
Stable BCO: []
Ready for upsweep
[NONREC
ModSummary {
ms_hs_date = Thu Oct 6 19:01:55 Westeuropäische Sommerzeit 2011
ms_mod = main:MyModule,
ms_imps = [import Prelude]
ms_srcimps = []
}]
compile: input file MyModule.hs
Created temporary directory: C:\Temp\ghc4956_0
*** Checking old interface for main:MyModule:
[1 of 1] Compiling MyModule ( MyModule.hs, MyModule.o )
*** Parser:
*** Renamer/typechecker:
*** Desugar:
*** Deleting temp files:
Deleting: C:\Temp\ghc4956_0\ghc4956_0.s
Warning: deleting non-existent C:\Temp\ghc4956_0\ghc4956_0.s
*** Deleting temp dirs:
Deleting: C:\Temp\ghc4956_0
ghc: panic! (the 'impossible' happened)
(GHC version 7.0.3 for i386-unknown-mingw32):
splitFunTy
forall a{tv aby} [tv].
main:MyModule.T{tc rbp} a{tv aby} [tv]
-> ghc-prim:GHC.Types.Double{(w) tc 3u}
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5533>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs