ghc-6.4.1: panic - Prelude.last: empty list

Bulat Ziganshin bulatz at HotPOP.com
Sun Oct 30 15:26:47 EST 2005


Hello Einar,

Sunday, October 30, 2005, 4:20:20 PM, you wrote:

EK> I am having problems with GHC 6.4.1 dying with the message:

EK> ghc-6.4.1: panic! (the `impossible' happened, GHC version 6.4.1):
EK>         Prelude.last: empty list

EK> The source is nontrivial and contains template haskell. The error
EK> seems to appear after byte code generation.

are you will be glad to see trivial source of this problem? :)


{-# OPTIONS_GHC -fglasgow-exts -fth #-}
module Main where
main = return ()
$( [d| |] >>= return.tail)


C:\!\Haskell\!!!!>ghc --make -ddump-splices test-derive.hs
Chasing modules from: test-derive.hs
Compiling Main             ( test-derive.hs, test-derive.o )
Loading package base-1.0 ... linking ... done.
Loading package haskell98-1.0 ... linking ... done.
Loading package template-haskell-1.0 ... linking ... done.
ghc.EXE: panic! (the `impossible' happened, GHC version 6.4.1):
        Prelude.tail: empty list

Please report it as a compiler bug to glasgow-haskell-bugs at haskell.org,
or http://sourceforge.net/projects/ghc/.



as you see, TH sometimes just don't caught exceptions in your TH code.
moreover, with -ddump-splices TH can print code it generated and only
then panic on error in generation routine!

-- 
Best regards,
 Bulat                            mailto:bulatz at HotPOP.com





More information about the Glasgow-haskell-users mailing list