Folks,

I'm getting this error:

./HOC/StdArgumentTypes.hs:1:0:
Not in scope: type constructor or class `HOC.Arguments:ObjCArgument'

But if you look through the output below you will see that HOC.Arguments is being loaded by ghc. I assume that's what the skipping of HOC.Arguments means.

The Arguments module starts like this so I believe it's exporting everything:

module HOC.Arguments where

import HOC.Base
import HOC.FFICallInterface

import Foreign.Storable
import Foreign.ForeignPtr
import Foreign.Ptr
import System.IO.Unsafe(unsafePerformIO)

import Language.Haskell.TH
import Language.Haskell.TH.Syntax

class (Storable b, FFITypeable b) => ObjCArgument a b | a -> b where
    withExportedArgument :: a -> (b -> IO c) -> IO c
    exportArgument :: a -> IO b
    importArgument :: b -> IO a

    objCTypeString :: a -> String

StdArgumentTypes.hs starts like this so you see that it's importing HOC.Arguments

module HOC.StdArgumentTypes where

import HOC.Base
import HOC.Invocation
import HOC.Arguments
import HOC.FFICallInterface

import Control.Exception        ( bracket )
import Foreign
import Foreign.C.Types
import Foreign.C.String

-- Objective C

-- ID: already defined

instance FFITypeable SEL where
    makeFFIType _ = makeFFIType (undefined :: Ptr ())

$(declareStorableObjCArgument [t| SEL |] ":")

instance ObjCArgument Bool CInt where
    exportArgument False = return 0
    exportArgument True = return 1
    importArgument 0 = return False
    importArgument _ = return True

    objCTypeString _ = "c"

The line 1 in the error below makes me guess that it could be a Template Haskell issue. Any pointers?

        Thanks, Joel

---
ghc --make HOC.hs -odir build/objects -hidir build/ imports -fglasgow-exts -package-name HOC ../ HOC_cbits/HOC_cbits.o -I../HOC_cbits -I../ libffi-src/build/include -framework Foundation -fth
Chasing modules from: HOC.hs
Skipping HOC.SelectorNameMangling ( ./HOC/SelectorNameMangling.hs, build/objects/HOC/SelectorNameMangling.o )
Skipping  HOC.Base         ( ./HOC/Base.hs, build/objects/HOC/Base.o )
Skipping HOC.FFICallInterface ( ./HOC/FFICallInterface.hs, build/ objects/HOC/FFICallInterface.o ) Skipping HOC.Arguments ( ./HOC/Arguments.hs, build/objects/HOC/ Arguments.o )Skipping HOC.Utilities ( ./HOC/Utilities.hs, build/ objects/HOC/Utilities.o )Skipping HOC.Invocation ( ./HOC/ Invocation.hs, build/objects/HOC/Invocation.o ) Skipping HOC.MsgSend ( ./HOC/MsgSend.hs, build/objects/HOC/ MsgSend.o ) Compiling HOC.StdArgumentTypes ( ./HOC/StdArgumentTypes.hs, build/ objects/HOC/StdArgumentTypes.o )
Loading package base-1.0 ... linking ... done.
Loading object (static) ../HOC_cbits/HOC_cbits.o ... done
Loading object (framework) Foundation ... done
final link ... done
Loading package haskell98-1.0 ... linking ... done.
Loading package template-haskell-1.0 ... linking ... done.

./HOC/StdArgumentTypes.hs:1:0:
Not in scope: type constructor or class `HOC.Arguments:ObjCArgument'

./HOC/StdArgumentTypes.hs:1:0:
`exportArgument' is not a (visible) method of class `Arguments:ObjCArgument'
./HOC/StdArgumentTypes.hs:1:0:
`importArgument' is not a (visible) method of class `Arguments:ObjCArgument'
./HOC/StdArgumentTypes.hs:1:0:
`objCTypeString' is not a (visible) method of class `Arguments:ObjCArgument'

--
http://wagerlabs.com/





_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to