RE: the impossible happened: splitTyConApp
A nice bug report, thank you. Turns out to be an obscure GADT case, and another reason for switching to System FC. I've fixed the STABLE branch, but I won't fix the HEAD because we're about to move to FC so it seems hardly worth it. BUT if we release the HEAD before the FC switch, we should apply the patch from the STABLE branch. Meanwhile, as a workaround, compile without -O. Or even just compile Vector.Fast without -O Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] | On Behalf Of Frederik Eaton | Sent: 11 June 2006 17:33 | To: glasgow-haskell-bugs@haskell.org | Subject: the impossible happened: splitTyConApp | | Hi, | | $ ghc -O3 --make LearnBinFactors.hs -package GSL -o lbf | Chasing modules from: LearnBinFactors.hs | Compiling Main ( LearnBinFactors.hs, LearnBinFactors.o ) | ghc-6.4.2: panic! (the `impossible' happened, GHC version 6.4.2): | splitTyConApp a{tv a8EX} | | I've attached the program LearnBinFactors.hs. | | The version of the GSL package which it uses can be downloaded from: | | http://ofb.net/~frederik/GSLHaskell2.tar.gz | | Frederik | | -- | http://ofb.net/~frederik/ | ___ | Glasgow-haskell-bugs mailing list | Glasgow-haskell-bugs@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
Re: the impossible happened: splitTyConApp
Attaching the file, sorry. When I comment out line 32: myXlogyx :: Dom a => FVector a -> FVector a -> FVector a then the error goes away. On Sun, Jun 11, 2006 at 05:32:49PM +0100, Frederik Eaton wrote: > Hi, > > $ ghc -O3 --make LearnBinFactors.hs -package GSL -o lbf > Chasing modules from: LearnBinFactors.hs > Compiling Main ( LearnBinFactors.hs, LearnBinFactors.o ) > ghc-6.4.2: panic! (the `impossible' happened, GHC version 6.4.2): > splitTyConApp a{tv a8EX} > > I've attached the program LearnBinFactors.hs. > > The version of the GSL package which it uses can be downloaded from: > > http://ofb.net/~frederik/GSLHaskell2.tar.gz > > Frederik > > -- > http://ofb.net/~frederik/ > -- http://ofb.net/~frederik/ {-# OPTIONS -fglasgow-exts #-} module Main where import Control.Exception import Debug.Trace import Random import Vector defaults = P {pY=undefined, pNumFactors=8, pMaxSteps=30, pIters=20} data Params v n d = P { pY :: v (n, d), pMaxSteps :: Int, pIters :: Int, pNumFactors :: Int } showParams p = show (pY p, pMaxSteps p, pIters p, pNumFactors p) data State v d k = S { sMu :: v (d, k), sSigma2 :: R, sPie :: v k } showState s = show (sMu s, sSigma2 s, sPie s) seqState s = vseq (sMu s) . vseq (sPie s) . seq (sSigma2 s) but = flip assert myXlogyx :: Dom a => FVector a -> FVector a -> FVector a myXlogyx x y = x * log (y/(x +. 1.0e-20)) --mstep :: (Dom n, Dom d, Dom k) => Params FVector n d -> FVector (n,k) -> FVector (k,k) -> State FVector d k --mstep :: (Dom n, Dom d, Dom k, Vector v R, Num (v (n,k)), Num (v (d,k)), Num (v (n,d)), FracVector v R) => Params v n d -> v (n,k) -> v (k,k) -> State v d k mstep (p::Params v n d) (es::v(n,k)) (ess::v(k,k)) = (s::State v d k) `but` (sigma2 > 0.0) where s = S {sMu = (mu::v(d,k)), sSigma2 = sigma2, sPie = pie} (y::v(n,d)) = pY p (mu::v(d,k)) = trans (pinv ess *> (trans es *> y)) --(mu::v(d,k)) = trans (pinv ess * (trans es *> y)) sigma2 = (vsumSq y + vsum (mu * (mu *> ess)) - 2 * vsum (es * (y *> mu))) / (fromIntegral $ vlen y) pie = fromRow $ unif *> es --meanFieldStep :: (Dom n, Dom d, Dom k) => Params FVector n d -> State FVector d k -> FVector (n,k) -> (FVector (n,k), R, R) meanFieldStep (p::Params v n d) (s::State v d k) (lambda0::(v (n,k))) = --trace ("(d,pieExpr,yExpr,lambda,f)"++show (d,pieExpr,yExpr,lambda,f)) $ (lambda::v(n,k), f::R, dist::R) where (mu,sigma2,pie) = (sMu s, sSigma2 s, sPie s) y = pY p d = fromIntegral $ cols y pieExpr = log (pie / (1-pie)) lambda = byRow $ \ (p::n) -> let y_p = getRow y p in vectorUpdate (fromRow $ getRow lambda0 p) domain $ \lambda_p' (i::k) -> sigm $ (pieExpr ! i) + (1/sigma2) * let mu_i = getCol mu i mu_ss = vsumSq mu_i / 2 lambda_p = toRow lambda_p' in fromS ((y_p - lambda_p *> trans mu + (lambda_p ! (0,i)) .* (trans mu_i)) *> mu_i) - mu_ss f = sum $ foreach $ \p -> let lp = getRow lambda p yp = getRow y p f_ = vsum (myXlogyx lp (toRow pie) + myXlogyx (1-lp) (toRow $ 1-pie)) - d * log sigma2 / 2 - (1/(2*sigma2)) * vsumSq (yp - lp*>(trans mu)) - (1/(2*sigma2))*(vsum ((lp-lp**2)*(sumCols (mu*mu - (d/2)*log(2*pi) in f_ dist = sqrt $ vsumSq (lambda-lambda0) --initState :: (Dom k, Dom d) => IO (State FVector d k) initState () = do -- :: IO (State v d k) = do (mu0::v(d,k)) <- randIO putStrLn $ "size of mu0: "++(show (rows mu0, cols mu0)) (sigma2_0::R) <- randomIO >>= (return.(+0.1)) (pie0::v k) <- randIO return $ S {sMu = mu0, sSigma2 = sigma2_0, sPie = pie0} --learnBinFactors :: (Dom k, Dom d, Dom n) => Params FVector n d -> IO (State FVector d k) learnBinFactors (p::Params v n d) = do s <- initState () doIters p 1 s --doIters :: (Dom n, Dom d, Dom k) => Params FVector n d -> Int -> State FVector d k -> IO (State FVector d k) doIters p n s | n >= (pIters p) = return s doIters (p::Params v n d) (n::Int) (s::State v d k) = seqState s $ trace ("EM iteration: "++show n) $ --trace ("s="++showState s) $ do let (mu,sigma2,pie) = (sMu s, sSigma2 s, sPie s) (lambda0::v(n,k)) <- randIO let (lambda::v(n,k), f) = meanField p s lambda0 let es = lambda let ess = (trans lambda) *> lambda + diag (fromRow $ sumCols lambda - sumCols (lambda * lambda)) let s' = mstep p es ess doIters p (n+1) s' --meanField :: (Dom n, Dom d, Dom k) => Params FVector n d -> State FVector d k -> FVector (n,k) -> (FVector (n,k), R) meanField (p::Params v n d) (s::State v d k) (lambda0::v(n,k)) = let {(lambda, f, n) = loopUntil (lambda0, minBound, 0) (\ (lambda, f, n) -> let (lambda', f', dist) = meanFieldStep p s lambda in (if f' < f then trace ("F decreased in Mean
RE: the impossible happened - size limits in template haskell?
Yes, this is a bug, with an unhelpful error message. We've opened a Trac bug for it, but at low priority. Thanks for reporting it. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-bugs- | [EMAIL PROTECTED] On Behalf Of Frederik Eaton | Sent: 05 June 2006 06:25 | To: glasgow-haskell-bugs@haskell.org | Subject: the impossible happened - size limits in template haskell? | | Here I'm reading a very large matrix from a file and turning it into a | template Haskell expression. Probably not the most efficient thing to | do, but the error message could be clearer... | | *Main> let y = $(qFast (\f -> runIO $ readMatrixFile "data.txt" (runQ.f))); | ghc-6.4.2: panic! (the `impossible' happened, GHC version 6.4.2): | linkBCO: >= 64k insns in BCO | | Please report this as a compiler bug. See: | http://www.haskell.org/ghc/reportabug | | | | -- | http://ofb.net/~frederik/ | ___ | Glasgow-haskell-bugs mailing list | Glasgow-haskell-bugs@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
RE: The impossible happened
This is a known bug in 6.4.1, I don't have a link off-hand (you should be able to find more info from Google though). You have a missing package dependency somewhere (the error message should be reporting a missing package rather than "unknown exceptino"). Cheers, Simon On 19 December 2005 09:08, Simon Peyton-Jones wrote: > That should never happen. It's 'impossible', after all. If you can > give us a little repro script we'll look into it. > > You are a genius at finding GHC bugs :-) > > Simon > >> -Original Message- >> From: [EMAIL PROTECTED] >> [mailto:glasgow-haskell-bugs- [EMAIL PROTECTED] On Behalf Of Joel >> Reymont >> Sent: 18 December 2005 11:20 >> To: glasgow-haskell-bugs@haskell.org >> Cc: Simon Marlow >> Subject: The impossible happened >> >> ghc -O --make -debug randomplay.hs -o randomplay -lssl -lcrypto -lz >> >> ghc-6.4.1: ghc-6.4.1: panic! (the `impossible' happened, GHC version >> 6.4.1): >> unknown exception >> >> Please report it as a compiler bug to >> glasgow-haskell-bugs@haskell.org, >> or http://sourceforge.net/projects/ghc/. >> >> I unregistered my library package, registered again and tried to make >> the program that was using it. The program consists of two modules >> and they were built and not touched, thus no rebuild. >> >> Got the error above. Removed *.o and *.hi for the two program modules >> and the rebuild went smoothly. >> >> -- >> http://wagerlabs.com/ >> >> >> >> >> >> ___ >> Glasgow-haskell-bugs mailing list >> Glasgow-haskell-bugs@haskell.org >> http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
Re: The impossible happened
I'm trying! Don't have a repro case for this one, though. Just as I'm done with my current project I'll take a more methodical approach to repro cases. My hope is that I'll become a genius at fixing GHC bugs as well. On Dec 19, 2005, at 9:08 AM, Simon Peyton-Jones wrote: That should never happen. It's 'impossible', after all. If you can give us a little repro script we'll look into it. You are a genius at finding GHC bugs :-) -- http://wagerlabs.com/ ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
RE: The impossible happened
That should never happen. It's 'impossible', after all. If you can give us a little repro script we'll look into it. You are a genius at finding GHC bugs :-) Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-bugs- | [EMAIL PROTECTED] On Behalf Of Joel Reymont | Sent: 18 December 2005 11:20 | To: glasgow-haskell-bugs@haskell.org | Cc: Simon Marlow | Subject: The impossible happened | | ghc -O --make -debug randomplay.hs -o randomplay -lssl -lcrypto -lz | | ghc-6.4.1: ghc-6.4.1: panic! (the `impossible' happened, GHC version | 6.4.1): | unknown exception | | Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org, | or http://sourceforge.net/projects/ghc/. | | I unregistered my library package, registered again and tried to make | the program that was using it. The program consists of two modules | and they were built and not touched, thus no rebuild. | | Got the error above. Removed *.o and *.hi for the two program modules | and the rebuild went smoothly. | | -- | http://wagerlabs.com/ | | | | | | ___ | Glasgow-haskell-bugs mailing list | Glasgow-haskell-bugs@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
RE: the `impossible' happened
On 28 June 2005 07:37, Frederik Eaton wrote: > On Mon, Jun 27, 2005 at 01:08:07PM +0100, Simon Marlow wrote: >> On 25 June 2005 21:09, Frederik Eaton wrote: >> >>> Skipping Version ( ./Version.hs, >>> dist/build/./fcq-www.cgi-tmp/Version.o ) Skipping ChangeLog >>> ( ./ChangeLog.hs, dist/build/./fcq-www.cgi-tmp/ChangeLog.o ) >>> Compiling Main ( fcq-www.hs, >>> dist/build/./fcq-www.cgi-tmp/Main.o ) >>> >>> >>> /home/frederik/arch/i386/lib/WASH-CGI-1.4.37/ghc-6-4/import/Cookie.hi Could not find module `StateItem': it is not a module in the >>> current program, or in any known package. >>> ghc-6.4: panic! (the `impossible' happened, GHC version 6.4): >>> forkM Declaration for check{v} >> >> This one is most likely caused by a problem in a package >> specification, namely a module missing from the "eposed-modules" or >> "hidden-modules" fields. > > That it was - but hopefuly ghc isn't supposed to print "panic!" when a > package is just misconfigured? Not that I found the problem hard to > debug... I think we've improved the error message now. Cheers, Simon ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
Re: the `impossible' happened
On Mon, Jun 27, 2005 at 01:08:07PM +0100, Simon Marlow wrote: > On 25 June 2005 21:09, Frederik Eaton wrote: > > > Skipping Version ( ./Version.hs, > > dist/build/./fcq-www.cgi-tmp/Version.o ) Skipping ChangeLog( > > ./ChangeLog.hs, dist/build/./fcq-www.cgi-tmp/ChangeLog.o ) Compiling > > Main ( fcq-www.hs, dist/build/./fcq-www.cgi-tmp/Main.o ) > > > > > > /home/frederik/arch/i386/lib/WASH-CGI-1.4.37/ghc-6-4/import/Cookie.hi > > : Could not find module `StateItem': it is not a module in the > > current program, or in any known package. > > ghc-6.4: panic! (the `impossible' happened, GHC version 6.4): > > forkM Declaration for check{v} > > This one is most likely caused by a problem in a package specification, > namely a module missing from the "eposed-modules" or "hidden-modules" > fields. That it was - but hopefuly ghc isn't supposed to print "panic!" when a package is just misconfigured? Not that I found the problem hard to debug... Frederik -- http://ofb.net/~frederik/ ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
RE: the `impossible' happened
On 25 June 2005 21:09, Frederik Eaton wrote: > Skipping Version ( ./Version.hs, > dist/build/./fcq-www.cgi-tmp/Version.o ) Skipping ChangeLog( > ./ChangeLog.hs, dist/build/./fcq-www.cgi-tmp/ChangeLog.o ) Compiling > Main ( fcq-www.hs, dist/build/./fcq-www.cgi-tmp/Main.o ) > > > /home/frederik/arch/i386/lib/WASH-CGI-1.4.37/ghc-6-4/import/Cookie.hi > : Could not find module `StateItem': it is not a module in the > current program, or in any known package. > ghc-6.4: panic! (the `impossible' happened, GHC version 6.4): > forkM Declaration for check{v} This one is most likely caused by a problem in a package specification, namely a module missing from the "eposed-modules" or "hidden-modules" fields. Cheers, Simon ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
Re: the impossible happened
bulatz: > also it will be cool to have ability to add such annotations to my own > functions, smthg like: > > head (x:xs) = x > head [] = superError "head []" > > which will print: "Error: head [] in Module.hs:155" You can do this already with GHC.Base.assert (almost): > import GHC.Base (assert) > > f [] = assert False () > f x = () *Main> f [1,2] () *Main> f [] *** Exception: t.hs:3:7-12: Assertion failed At least you can get the line number. -- Don ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
Re: the impossible happened
On Mon, May 23, 2005 at 09:38:58AM +0100, Simon Peyton-Jones wrote: > This "fromJust" bug is SourceForge 1177320. > > The trouble is that we've been unable to reproduce it here. It seems to > show up when compiling some large thing, like Darcs or WASH. > > If anyone would be willing to snapshot a tree exhibiting the bug, and > send it to us, we'd love to investigate. Until then we're a bit stuck. It seems that there are not that many uses of fromJust in GHC's sources. I guess that removing them or at least making them report a source location in case of failure (for example using a CPP macro like in darcs) would be an good task for a wannabe GHC hacker. Unfortunately, I can't volunteer at this moment. Best regards Tomasz ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
Re: the impossible happened
Hmm. I'm sorry, by now I've forgotten what it was that caused it. I think it may have gone away when I cleaned up some object files from a previous build, but I'm not sure. It seems like it shouldn't be hard to have ghc save everything about the execution context when an exception like this is triggered, maybe to a file in /tmp, so that the user could run a tool to submit a standardized bug report at his option later. Well, it would be a little hard - maybe you'd have to overload all of the file operations to keep track of every file ghc reads, and put these into a big tarball to send with the bug report... But I imagine that on the balance it would make your job easier. Frederik On Mon, May 23, 2005 at 09:38:58AM +0100, Simon Peyton-Jones wrote: > This "fromJust" bug is SourceForge 1177320. > > The trouble is that we've been unable to reproduce it here. It seems to > show up when compiling some large thing, like Darcs or WASH. > > If anyone would be willing to snapshot a tree exhibiting the bug, and > send it to us, we'd love to investigate. Until then we're a bit stuck. > > Simon > > > | -Original Message- > | From: [EMAIL PROTECTED] > [mailto:glasgow-haskell-bugs- > | [EMAIL PROTECTED] On Behalf Of Frederik Eaton > | Sent: 21 May 2005 11:49 > | To: glasgow-haskell-bugs@haskell.org > | Subject: the impossible happened > | > | ghc-6.4: panic! (the `impossible' happened, GHC version 6.4): > | Maybe.fromJust: Nothing > | > | Please report it as a compiler bug to > glasgow-haskell-bugs@haskell.org, > | or http://sourceforge.net/projects/ghc/. > | > | I think this was the command line: > | > | /home/frederik/arch/i386/bin/ghc -odir dist/build/../webpage.cgi-tmp > -hidir dist/build/../webpage.cgi- > | tmp -o dist/build/../webpage.cgi --make -i.. -O3 -fignore-asserts > -fglasgow-exts -package base-1.0 - > | package posix-1.0 -package haskell98-1.0 -package WASH-CGI -package > WASHHTML > | ../maint/webpage.hs -v > | > | Frederik > | > | -- > | http://ofb.net/~frederik/ > | ___ > | Glasgow-haskell-bugs mailing list > | Glasgow-haskell-bugs@haskell.org > | http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs > -- http://ofb.net/~frederik/ ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
RE: the impossible happened
This "fromJust" bug is SourceForge 1177320. The trouble is that we've been unable to reproduce it here. It seems to show up when compiling some large thing, like Darcs or WASH. If anyone would be willing to snapshot a tree exhibiting the bug, and send it to us, we'd love to investigate. Until then we're a bit stuck. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-bugs- | [EMAIL PROTECTED] On Behalf Of Frederik Eaton | Sent: 21 May 2005 11:49 | To: glasgow-haskell-bugs@haskell.org | Subject: the impossible happened | | ghc-6.4: panic! (the `impossible' happened, GHC version 6.4): | Maybe.fromJust: Nothing | | Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org, | or http://sourceforge.net/projects/ghc/. | | I think this was the command line: | | /home/frederik/arch/i386/bin/ghc -odir dist/build/../webpage.cgi-tmp -hidir dist/build/../webpage.cgi- | tmp -o dist/build/../webpage.cgi --make -i.. -O3 -fignore-asserts -fglasgow-exts -package base-1.0 - | package posix-1.0 -package haskell98-1.0 -package WASH-CGI -package WASHHTML | ../maint/webpage.hs -v | | Frederik | | -- | http://ofb.net/~frederik/ | ___ | Glasgow-haskell-bugs mailing list | Glasgow-haskell-bugs@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
RE: the impossible happened
I believe that the problem here is that the Wash distribution isn't right for GHC 6.4; in particular, the package-specification format changed a bit. Wash needs to be updated. Sorry about this -- the packaging story for Haskell is still in flux, and that means that old packages won't necessarily compile with new compilers. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-bugs- | [EMAIL PROTECTED] On Behalf Of Frederik Eaton | Sent: 17 May 2005 07:12 | To: glasgow-haskell-bugs@haskell.org | Subject: the impossible happened | | /home/frederik/arch/i386/bin/ghc -odir dist/build/../pp-web.cgi-tmp -hidir dist/build/../pp-web.cgi- | tmp -o dist/build/../pp-web.cgi --make -i.. -O3 -fignore-asserts -fglasgow-exts -package base-1.0 - | package WASH-CGI ../maint/webpage.hs -v | Glasgow Haskell Compiler, Version 6.4, for Haskell 98, compiled by GHC version 5.04.3 | Using package config file: /home/frederik/arch/i386/lib/ghc-6.4/package.conf | Using package config file: /home/frederik/.ghc/i386-linux-6.4/package.conf | Hsc static flags: -static | *** Chasing dependencies: | Chasing modules from: ../maint/webpage.hs | Stable modules: | *** Compiling Main ( ../maint/webpage.hs, interpreted ): | compile: input file ../maint/webpage.hs | *** Checking old interface for Main: | Compiling Main ( ../maint/webpage.hs, dist/build/../pp-web.cgi-tmp/Main.o ) | *** Parser: | *** Renamer/typechecker: | /home/frederik/arch/i386/lib/WASH-CGI-1.4.37/ghc-6-4/import/CGIInternals .hi : | Could not find module `HTMLMonadBase': | it is not a module in the current program, or in any known package. | *** Deleting temp files | Deleting: /tmp/ghc14692.hc | Warning: deleting non-existent /tmp/ghc14692.hc | ghc-6.4: panic! (the `impossible' happened, GHC version 6.4): | forkM Declaration for standardQuery{v} | | Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org, | or http://sourceforge.net/projects/ghc/. | | -- | http://ofb.net/~frederik/ | ___ | Glasgow-haskell-bugs mailing list | Glasgow-haskell-bugs@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs ___ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
RE: The impossible happened
Aha. You have a "\" in your rule name. That doesn't work in 5.02 for tiresome reasons; it's ok in 5.04 thanks for the clear report Simon | -Original Message- | From: Arjan van IJzendoorn [mailto:[EMAIL PROTECTED]] | Sent: 27 June 2002 15:46 | To: [EMAIL PROTECTED] | Subject: The impossible happened | | | Hi, | | GHC gives me this message when compiling with the -O flag (it | doesn't happen without it): | | ghc: panic! (the `impossible' happened, GHC version 5.02): | Rules/Deprecations parse failed | ./staticanalysis/Constraints.hi:63: error in character literal | | Please report it as a compiler bug to | [EMAIL PROTECTED], or | http://sourceforge.net/projects/ghc/. | | The platform is | Windows 2000. "Constraints.hi" is attached. | | Greetings, Arjan | | ___ Glasgow-haskell-bugs mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
RE: The impossible happened
Excellent bug report, thank you. It's a bug in 4.08. I hope we can ensure that it won't be in 4.08.1. Workaround: ermove the context from the newtype declaration. Simon | -Original Message- | From: Jose Emilio Labra Gayo [mailto:[EMAIL PROTECTED]] | Sent: 25 August 2000 12:05 | To: [EMAIL PROTECTED] | Subject: The impossible happened | | | | {- | | The following piece of program produces: | | panic! (the `impossible' happened): | applyTypeToArgs | (__coerce (f{-ar4-} (.FixTest.Fix{-r2,x-} f{-ar4-})) | zddFunctor{-ari-}) | x{-arb-} | | Some details: | | - It loads if I remove the context in the Fix declaration: | newtype Fix f = In {out :: f (Fix f) } | - It loads ok with Hugs98 | - I am using ghc 4.08 and the problem arises both in Debian | Linux and in | Win32 | | BTW, I was looking for a list of known bugs in ghc but I | couldn't find it. | Does it exist? | | Best Regards, Jose Labra | http://lsi.uniovi.es/~labra | | -} | module FixTest where | | newtype (Functor f) => Fix f = In { out :: f (Fix f) } | | para g x = g (fmap (para g) (out x)) x | | | | | |
Re: The impossible happened!
Colin Paul Adams writes: > > Trying to compile happy 1.5 using ghc 3.02: > ... > panic! (the `impossible' happened): > lookupBindC:no info! > for: actionFunction_sqBJ > (probably: data dependencies broken by an optimisation pass) > static binds for: Hi, see http://www.dcs.gla.ac.uk/mail-www/glasgow-haskell-bugs/msg01173.html for info on how to workaround this 3.02 bug. --Sigbjorn
Re: The impossible happened in 3.01
Sven Panne writes: > During the compilation of a small project with ghc-3.01 (Linux) I get: > >panic! (the `impossible' happened): >unboxArg: PrelBase.(){-40-} > > The code leading to this error is available at: > >http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne/impossible.tar.gz > Thanks, a bug alright; here's the offender: useLayer :: Layer -> IO () useLayer gc_arg1 = case (undefined gc_arg1) of { arg1 -> _casm_ ``do {int arg1; arg1 = %0; do {glutUseLayer(arg1);} while(0);} while(0);'' arg1} This shouldn't get past the type checker. The type checker is supposed to default polymorphic _ccall_/_casm_ results to (). It is doing something more general though, defaulting both (CCallable a => a) and (CReturnable a => a) to (), i.e., polymorphic results _and_ arguments. The enclosed patch restricts this to results only. I'm puzzled as to why this would only surface now with the introduction of the MPC-capable type checker. ghc-2.10 doesn't accept it, but it has the same defaulting code. --Sigbjorn *** ghc/compiler/typecheck/TcSimplify.lhs 1998/02/10 14:16:54 1.24 --- ghc/compiler/typecheck/TcSimplify.lhs 1998/03/05 19:19:23 *** *** 147,151 import Bag( Bag, bagToList, snocBag ) import Class ( Class, ClassInstEnv, classBigSig, classInstEnv ) ! import PrelInfo ( isNumericClass, isCcallishClass ) import Maybes ( maybeToBool ) --- 147,151 import Bag( Bag, bagToList, snocBag ) import Class ( Class, ClassInstEnv, classBigSig, classInstEnv ) ! import PrelInfo ( isNumericClass, isCreturnableClass ) import Maybes ( maybeToBool ) *** *** 926,932 returnTc binds ! | all isCcallishClass classes = -- Default CCall stuff to (); we don't even both to check that () is an ! -- instance of CCallable/CReturnable, because we know it is. unifyTauTy (mkTyVarTy tyvar) unitTy`thenTc_` returnTc EmptyMonoBinds --- 926,932 returnTc binds ! | all isCreturnableClass classes = -- Default CCall stuff to (); we don't even both to check that () is an ! -- instance of CReturnable, because we know it is. unifyTauTy (mkTyVarTy tyvar) unitTy`thenTc_` returnTc EmptyMonoBinds *** ghc/compiler/prelude/PrelInfo.lhs 1998/02/03 17:15:00 1.33 --- ghc/compiler/prelude/PrelInfo.lhs 1998/03/05 19:12:28 *** *** 34,38 needsDataDeclCtxtClassKeys, cCallishClassKeys, cCallishTyKeys, isNoDictClass, ! isNumericClass, isStandardClass, isCcallishClass ) where --- 34,38 needsDataDeclCtxtClassKeys, cCallishClassKeys, cCallishTyKeys, isNoDictClass, ! isNumericClass, isStandardClass, isCcallishClass, isCreturnableClass ) where *** *** 501,508 isCcallishClass, isNoDictClass, isNumericClass, isStandardClass :: Class -> Bool ! isNumericClass clas = classKey clas `is_elem` numericClassKeys ! isStandardClass clas = classKey clas `is_elem` standardClassKeys ! isCcallishClassclas = classKey clas `is_elem` cCallishClassKeys ! isNoDictClassclas = classKey clas `is_elem` noDictClassKeys is_elem = isIn "is_X_Class" --- 501,509 isCcallishClass, isCreturnableClass, isNoDictClass, isNumericClass, isStandardClass :: Class -> Bool ! isNumericClass clas = classKey clas `is_elem` numericClassKeys ! isStandardClassclas = classKey clas `is_elem` standardClassKeys ! isCcallishClass clas = classKey clas `is_elem` cCallishClassKeys ! isCreturnableClass clas = classKey clas == cReturnableClassKey ! isNoDictClass clas = classKey clas `is_elem` noDictClassKeys is_elem = isIn "is_X_Class"
Re: The impossible happened...
Laszlo Nemeth wrote: > I'm putting the static argument transformation (simplCore/SAT.lhs) > back to GHC 2.0899, which works as advertised but: > when it gets to code generation (codeGen/ClosureInfo.lhs) the > impossible happens. > > panic! (the `impossible' happened): > fun_result_ty: 1 $x4_s1bF [$x0_ts1bH] > > (a very helpful message indeed :( ) > > On the other hand when I compile the same file, with the same options > but -O on everything works fine. > > I guess that the code generator is not prepared to work if lambda > lifting hadn't been done before...(which should have happened in the > first place as part of the final simplification anyway!) Hi, I wrote the SAT code, 2+years ago :) Lambda Lifting is not needed in ghc/stg, actually (in general) it undoes SAT (when I tested SAT I either didn't do any LL, or had a selective LL on, check http://www.di.ufpe.br/~alms/ps/thesis.ps.gz for details on what I found out about SAT & LL). As far as I can remember (since I was just testing the effect of SAT :) it leaves some identifiers with the same unique id, that must be inlined. Therefore a call to the simplifier right after SAT is needed, since the simplifier will do the inlinings and will also give new uniques to all identifiers. If you don't call the simplifier right after SAT this might cause you problems further down the path. My guess is that with -O you somehow get the call to the simplifier that fixes things up...but it could be something completely different, since the message seems to be related to types... cheers, Andre. -- Andre SantosDepartamento de Informatica e-mail: [EMAIL PROTECTED] Universidade Federal de Pernambuco http://www.di.ufpe.br/~alms CP 7851, CEP 50732-970, Recife PE Brazil