[Template-haskell] Possible problem with TH
Sean Seefried
seefried@itee.uq.edu.au
Tue, 07 Jan 2003 14:23:18 +1000
I read Simon's reply to Brian Kellar. Brian attempted to compile the
following program and got a segmentation fault
| {- metatest.hs -}
| import Splices
|
| main = do
| print $(len "foo")
|
|
|
| {- Splices.hs -}
|
| module Splices where
|
| import Language.Haskell.THSyntax
|
| len s = [| length s |]
I attempted to compile the same program using the snapshot from the 5th
January (before Simon made the fixes to make this program compile) and
found that I got a different error. I am running a different distro of
Linux though (Debian). My error message was
-----------
Compiling Splices ( Splices.hs, ./Splices.o )
Compiling Main ( Main.hs, ./Main.o )
Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package haskell-src ... linking ... done.
ghc-5.05.20030105: internal error: stg_ap_v_ret
Please report this as a bug to glasgow-haskell-bugs@haskell.org,
or http://www.sourceforge.net/projects/ghc/
make: *** [all] Error 254
-----------
I don't know if this is useful or not but I thought I'd better post.
For various reasons I am unable to build GHC from CVS sources so I have
been relying on the snapshots provided. I will try compiling this
program once the 01062003 (or 01072003) snapshot comes out.
Sean