#2631: Template Haskell weird error message
-----------------------------+----------------------------------------------
    Reporter:  NeilMitchell  |       Owner:                  
        Type:  bug           |      Status:  new             
    Priority:  normal        |   Component:  Template Haskell
     Version:  6.9           |    Severity:  normal          
    Keywords:                |    Testcase:                  
Architecture:  Unknown       |          Os:  Unknown         
-----------------------------+----------------------------------------------
 I've noticed quite a few bugs related to weird TemplateHaskell expressions
 crashing the compiler recently, so I thought I'd try and write a nice
 exhaustive test of []'s in all possible places. In doing so however, I got
 some fairly weird error messages:

 {{{
 C:\Neil\temp>cat Main.hs
 {-# LANGUAGE TemplateHaskell #-}
 module Main where
 import Language.Haskell.TH
 main _ = $( return $ CompE [])
 C:\Neil\temp>ghci Main.hs
 GHCi, version 6.9.20080916: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 [1 of 1] Compiling Main             ( Main.hs, interpreted )
 Loading package syb ... linking ... done.
 Loading package array-0.1 ... linking ... done.
 Loading package packedstring-0.1 ... linking ... done.
 Loading package containers-0.1 ... linking ... done.
 Loading package pretty-1.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 Ok, modules loaded: Main.
 *Main> main ()

 <interactive>:1:0:
     Can't find interface-file declaration for variable main
       Probable cause: bug in .hi-boot file, or inconsistent .hi file
       Use -ddump-if-trace to get an idea of which file caused the error
     In the expression: main ()
     In the definition of `it': it = main ()
 *Main> :q
 Leaving GHCi.

 C:\Neil\temp>ghc --make Main.hs
 [1 of 1] Compiling Main             ( Main.hs, Main.o )
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 Loading package syb ... linking ... done.
 Loading package array-0.1 ... linking ... done.
 Loading package packedstring-0.1 ... linking ... done.
 Loading package containers-0.1 ... linking ... done.
 Loading package pretty-1.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 Linking Main.exe ...
 Main.o:fake:(.text+0x4d): undefined reference to `Main_main_closure'
 Main.o:fake:(.data+0x4): undefined reference to `Main_main_closure'
 collect2: ld returned 1 exit status
 }}}

 The main binding seems to get dropped, but no warning is issued. Later on,
 when the main binding is needed, it can't be found.

 -- Neil

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2631>
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

Reply via email to