Hello GHC bug fixers,

I just sent a program which ghc --make couldn't compile but
individual ghc -c commands could.

Now I have just tried to work around this, using Template Haskell
to use a "data" rather than "newtype" declaration for ghc6.2
Unfortunately the new code has the opposite problem!  It breaks
ghc -c, but ghc --make works.  This is also for both ghc6.2
and ghc6.2.20040915

with -c it doesn't work:

# ghc -c -fglasgow-exts ViewType.hs
# ghc -c -fglasgow-exts VersionGraphClient.hs

tcLookup: `VersionGraphClient.VersionGraphClient' is not in scope
In the data type declaration for `View'

with --make it does work:
# ghc --make -fglasgow-exts VersionGraphClient.hs
Chasing modules from: VersionGraphClient.hs
Compiling ViewType         ( ./ViewType.hs, ./ViewType.o )
Compiling VersionGraphClient ( VersionGraphClient.hs, VersionGr
Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package haskell-src ... linking ... done.





module VersionGraphClient where

data VersionGraphClient
module ViewType(

   View(..),
   ) where


import {-# SOURCE #-} VersionGraphClient

data View = View {
   graphClient1 :: VersionGraphClient
   }

module VersionGraphClient(
   VersionGraphClient,

   ) where

import ViewType

data Foo = Foo View

$(if False
   then
      [d|
         newtype VersionGraphClient = VersionGraphClient [Foo]
      |]
   else
      [d|
         data VersionGraphClient = VersionGraphClient [Foo]
      |]
   )
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to