[haskell-llvm] Patches for constStruct, alternative bitcast, constant vector construction

Bryan O'Sullivan bos at serpentine.com
Fri Jul 23 09:47:06 EDT 2010


On Sat, Jul 17, 2010 at 10:00 AM, Henning Thielemann <
lemming at henning-thielemann.de> wrote:

>
> Attached are three patches, that I made to my private repository.


Thanks, Henning. I've applied those patches.


> There
> are some others that I have to adapt to recent changes in llvm-0.8.
> Please let me know, whether, when and how you apply these patches.
>
>
> New patches:
>
> [vector constructs Vector analogously to constVector
> llvm at henning-thielemann.de**20100210095124] {
> hunk ./LLVM/Core/Vector.hs 3
> -module LLVM.Core.Vector(MkVector(..)) where
> +module LLVM.Core.Vector(MkVector(..), vector, ) where
> hunk ./LLVM/Core/Vector.hs 54
> +-- |Make a constant vector.  Replicates or truncates the list to get
> length /n/.
> +-- This behaviour is consistent with that of
> 'LLVM.Core.CodeGen.constVector'.
> +vector :: forall a n. (Pos n) => [a] -> Vector n a
> +vector xs =
> +   Vector (take (toNum (undefined :: n)) (cycle xs))
> +
> +
> hunk ./LLVM/Core.hs 50
> -    toVector, fromVector,
> +    toVector, fromVector, vector,
> }
>
> [CodeGen.constStruct
> llvm at henning-thielemann.de**20100305082944] {
> hunk ./LLVM/Core/CodeGen.hs 23
> -    constVector, constArray,
> +    constVector, constArray, constStruct, constPackedStruct,
> hunk ./LLVM/Core/CodeGen.hs 409
> +-- |Make a constant struct.
> +constStruct :: (IsConstStruct c a) => c -> ConstValue (Struct a)
> +constStruct struct =
> +    ConstValue $ U.constStruct (constValueFieldsOf struct) False
> +
> +-- |Make a constant packed struct.
> +constPackedStruct :: (IsConstStruct c a) => c -> ConstValue (PackedStruct
> a)
> +constPackedStruct struct =
> +    ConstValue $ U.constStruct (constValueFieldsOf struct) True
> +
> +class IsConstStruct c a | a -> c, c -> a where
> +    constValueFieldsOf :: c -> [FFI.ValueRef]
> +
> +instance (IsConst a, IsConstStruct cs as) => IsConstStruct (ConstValue a,
> cs) (a, as) where
> +    constValueFieldsOf (a, as) = unConstValue a : constValueFieldsOf as
> +instance IsConstStruct () () where
> +    constValueFieldsOf _ = []
> +
> hunk ./LLVM/Core.hs 50
> +    constStruct, constPackedStruct,
> hunk ./LLVM/Core.hs 73
> -import LLVM.Core.Util hiding (Function, BasicBlock, createModule,
> constString, constStringNul, constVector, constArray, getModuleValues,
> valueHasType)
> +import LLVM.Core.Util hiding (Function, BasicBlock, createModule,
> constString, constStringNul, constVector, constArray, constStruct,
> getModuleValues, valueHasType)
> }
>
> [Core.Instruction.bitcastUnify: like bitcast but uses type unification for
> asserting equal size of source and target
> llvm at henning-thielemann.de**20100319134650] {
> hunk ./LLVM/Core/Instructions.hs 37
> -    bitcast,
> +    bitcast, bitcastUnify,
> hunk ./LLVM/Core/Instructions.hs 343
> +-- | Same as bitcast but instead of the '(:==:)' type class it uses type
> unification.
> +-- This way, properties like reflexivity, symmetry and transitivity
> +-- are obvious to the Haskell compiler.
> +bitcastUnify :: (IsFirstClass a, IsFirstClass b, IsSized a s, IsSized b s)
> +        => Value a -> CodeGenFunction r (Value b)
> +bitcastUnify = convert FFI.buildBitCast
> +
> }
>
> Context:
>
> [TAG 0.8.0.2
> Bryan O'Sullivan <bos at serpentine.com>**20100626055728
>  Ignore-this: 6136d73c998ace13b784082927997c50
> ]
> Patch bundle hash:
> 46a55497e709edd2174aaa6f862189cb73102a31
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://projects.haskell.org/pipermail/haskell-llvm/attachments/20100723/295d94dc/attachment.htm 


More information about the Haskell-llvm mailing list