It looks like TH has issues with mutually recursive modules. Now I
could understand this if I was actually trying to call functions in
modules imported with {-# SOURCE #-} from TH, but I'm not. What is
going on here? I am getting sick of seeing "expectJust
upsweep_mod:old_linkable".

% ghc --make RecClass.hs -c             
Chasing modules from: RecClass.hs
Compiling RecClass[boot]   ( RecClass.hs-boot, RecClass.o-boot )
Skipping  RecClassTHStuff  ( ./RecClassTHStuff.hs, ./RecClassTHStuff.o )
Compiling RecClass         ( RecClass.hs, RecClass.o )
Loading package base-1.0 ... linking ... done.
Loading package haskell98-1.0 ... linking ... done.
Loading package template-haskell-1.0 ... linking ... done.
ghc-6.4: panic! (the `impossible' happened, GHC version 6.4):
        expectJust upsweep_mod:old_linkable

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

-- Sam
{-# OPTIONS_GHC -fth #-}

module RecClass where

import RecClassTHStuff


class RecClass a where
    
$(recClassInst)


Attachment: RecClass.hs-boot
Description: Binary data

{-# OPTIONS_GHC -fth #-}

module RecClassTHStuff where

import {-# SOURCE #-} RecClass

recClassInst = [d| instance RecClass () where |]


_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to