[Haskell-cafe] LLVM, getElementPtr?

Lally Singh lally.singh at gmail.com
Sun Dec 5 21:45:17 CET 2010


No wait, sorry.

buildReaderFun :: String -> CodeGenModule (Function (IO ()))
buildReaderFun nm = do
  puts <- newNamedFunction ExternalLinkage "puts" :: TFunction (Ptr
Word8 -> IO Word32)
  let callPuts greetz = createFunction ExternalLinkage $ do
          tmp <- getElementPtr greetz (0 :: Word32,(0 :: Word32, ()))
          call puts  tmp -- Throw away return value.
          ret ()
  withStringNul nm callPuts

Is that how it's intended?

Cheers,
-Lally


On Sun, Dec 5, 2010 at 3:35 PM, Lally Singh <lally.singh at gmail.com> wrote:
> Thanks for your help.  Replying inline
>
> On Sun, Dec 5, 2010 at 1:28 PM, Henning Thielemann
> <lemming at henning-thielemann.de> wrote:
>>
>> On Sun, 5 Dec 2010, Lally Singh wrote:
>>
>>> Hey all, I'm trying to get started generating LLVM code, but I'm
>>> getting a rather cryptic error.
>>
>> Btw. there is haskell-llvm at projects.haskell.org
>>
>>> buildReaderFun :: String -> CodeGenModule (Function (IO ()))
>>> buildReaderFun nm = do
>>>  puts <- newNamedFunction ExternalLinkage "puts" :: TFunction (Ptr
>>> Word8 -> IO Word32)
>>>  greetz <- createStringNul nm
>>>  func <- createFunction ExternalLinkage $ do
>>>   tmp <- getElementPtr0 greetz (0 :: Word32, ())
>>
>> You have to add a type annotation to greetz like
>>   (greetz :: Array D42 Word8)
>>  which limits your string to a length of 42 bytes.
>>
>> If you do not know the length, better use withStringNul.
>> I implemented the current behavior, because the former implementation was
>> unsafe.
>
> I'm sorry, the type signature for withStringNul is over my head.
> withStringNul ::
>   String ->
>   (forall n. (Nat n) => Global (Array n Word8) -> CodeGenModule a) ->
>   CodeGenModule a
>
> On the LLVM side, I'm looking to simply create a string constant I can
> pass in, such as ConstantArray::get(..).
>
> I *think* withStringNul will generate code to build a runtime-length
> determined string?   Sorry, I'm a little thick.
>
>>>   call puts  tmp -- Throw away return value.
>>>   ret ()
>>>  return func
>>>
>>> My attempts at figuring out what type-level has to do with this, and
>>> how to satisfy it have so far proven unsuccessful.
>>
>> type-level provides type level integers, and thus allows for static checking
>> of sizes, such as the number of bits of an integer type.
>
> Thanks -- sorry -- I'm guessing it's to make sure we're generating valid code?
>
> Cheers,
> -Lally
>



More information about the Haskell-Cafe mailing list