[haskell-llvm] Crashes in Array, Vector, DotProd
Henning Thielemann
lemming at henning-thielemann.de
Sun Nov 14 10:04:24 EST 2010
Bryan O'Sullivan schrieb:
> On Tue, Oct 26, 2010 at 12:52 PM, Henning Thielemann
> <lemming at henning-thielemann.de <mailto:lemming at henning-thielemann.de>>
> wrote:
>
> Sure, the account is still 'thielema'. :-)
>
>
> Sorry for the delay - you're in the llvm-p group now.
>
>
> Do you have an suggestion, what Haskell type I should use for 'i1'
> arguments, as needed for the 'volatile' argument of the memset
> intrinsic?
>
>
> Bool?
Ok, I use Bool now and pushed the patches to the repository.
In order to prevent a crash due to changed intrinsics interface I
propose to add a new Utility module for memory related intrinsics.
{-# LANGUAGE ScopedTypeVariables #-}
module LLVM.Util.Memory (
memcpy,
memmove,
memset,
IsLengthType,
) where
import LLVM.Core
import Data.Word (Word8, Word32, Word64, )
class IsFirstClass len => IsLengthType len where
instance IsLengthType Word32 where
instance IsLengthType Word64 where
memcpyFunc ::
forall len.
IsLengthType len =>
TFunction (Ptr Word8 -> Ptr Word8 -> len -> Word32 -> Bool -> IO ())
memcpyFunc =
newNamedFunction ExternalLinkage $
"llvm.memcpy.p0i8.p0i8." ++ typeName (undefined :: len)
memcpy ::
IsLengthType len =>
CodeGenModule
(Value (Ptr Word8) ->
Value (Ptr Word8) ->
Value len ->
Value Word32 ->
Value Bool ->
CodeGenFunction r ())
memcpy =
fmap
(\f dest src len align volatile ->
fmap (const()) $ call f dest src len align volatile)
memcpyFunc
memmoveFunc ::
forall len.
IsLengthType len =>
TFunction (Ptr Word8 -> Ptr Word8 -> len -> Word32 -> Bool -> IO ())
memmoveFunc =
newNamedFunction ExternalLinkage $
"llvm.memmove.p0i8.p0i8." ++ typeName (undefined :: len)
memmove ::
IsLengthType len =>
CodeGenModule
(Value (Ptr Word8) ->
Value (Ptr Word8) ->
Value len ->
Value Word32 ->
Value Bool ->
CodeGenFunction r ())
memmove =
fmap
(\f dest src len align volatile ->
fmap (const()) $ call f dest src len align volatile)
memmoveFunc
memsetFunc ::
forall len.
IsLengthType len =>
TFunction (Ptr Word8 -> Word8 -> len -> Word32 -> Bool -> IO ())
memsetFunc =
newNamedFunction ExternalLinkage $
"llvm.memset.p0i8." ++ typeName (undefined :: len)
memset ::
IsLengthType len =>
CodeGenModule
(Value (Ptr Word8) ->
Value Word8 ->
Value len ->
Value Word32 ->
Value Bool ->
CodeGenFunction r ())
memset =
fmap
(\f dest val len align volatile ->
fmap (const()) $ call f dest val len align volatile)
memsetFunc
More information about the Haskell-llvm
mailing list