[Haskell-cafe] LLVM: function pointer in global struct
Tom Schouten
tom at zwizwa.be
Thu Sep 29 19:12:38 CEST 2011
Hi everyone,
Using the LLVM bindings, I'm trying to create an initialized global
struct variable containing a pointer to a function.
> {-# LANGUAGE ScopedTypeVariables #-}
> import LLVM.Core
> import Data.Word
> import LLVM.Util.File(writeCodeGenModule)
> sm_module = do
> tick :: Function (Word32 -> IO Word32) <- createFunction
ExternalLinkage $ \x -> ret x
> info <- createNamedGlobal False ExternalLinkage "sm_info" $
constStruct (tick & ())
> return info
I run into a complaint that this pointer isn't constant when it's part
of a global variable initializer.
No instance for (llvm-0.10.0.1:LLVM.Core.CodeGen.IsConstStruct
(Function (Word32 -> IO Word32) :& ()) a0)
arising from a use of `constStruct'
Possible fix:
add an instance declaration for
(llvm-0.10.0.1:LLVM.Core.CodeGen.IsConstStruct
(Function (Word32 -> IO Word32) :& ()) a0)
In the second argument of `($)', namely `constStruct (tick & ())'
In a stmt of a 'do' expression:
info <- createNamedGlobal False ExternalLinkage "sm_info"
$ constStruct (tick & ())
In a stmt of a 'do' expression:
tick :: Function (Word32 -> IO Word32) <- createFunction
ExternalLinkage
$ \ x -> ret x
I suppose this is because of
> -- |A function is simply a pointer to the function.
> type Function a = Value (Ptr a)
being a Value instead of ConstValue. Is there a way around this?
Cheers
Tom
More information about the Haskell-Cafe
mailing list