Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
data MixedAttributeType Source #
data FunctionAttributeType Source #
Instances
DecodeM DecodeAST FunctionAttribute FunctionAttribute Source # | |
Defined in LLVM.Internal.Attribute | |
Monad m => EncodeM m FunctionAttribute (Ptr FunctionAttrBuilder -> EncodeAST ()) Source # | |
Defined in LLVM.Internal.Attribute encodeM :: FunctionAttribute -> m (Ptr FunctionAttrBuilder -> EncodeAST ()) Source # | |
EncodeM EncodeAST [Either GroupID FunctionAttribute] FunctionAttributeSet Source # | |
Defined in LLVM.Internal.Attribute |
data ParameterAttributeType Source #
Instances
DecodeM DecodeAST ParameterAttribute ParameterAttribute Source # | |
Defined in LLVM.Internal.Attribute | |
Monad m => EncodeM m ParameterAttribute (Ptr ParameterAttrBuilder -> EncodeAST ()) Source # | |
Defined in LLVM.Internal.Attribute encodeM :: ParameterAttribute -> m (Ptr ParameterAttrBuilder -> EncodeAST ()) Source # |
data AttributeImpl a Source #
Instances
DecodeM DecodeAST FunctionAttribute FunctionAttribute Source # | |
Defined in LLVM.Internal.Attribute | |
DecodeM DecodeAST ParameterAttribute ParameterAttribute Source # | |
Defined in LLVM.Internal.Attribute |
data AttributeSetImpl a Source #
Instances
EncodeM EncodeAST [Either GroupID FunctionAttribute] FunctionAttributeSet Source # | |
Defined in LLVM.Internal.Attribute | |
DecodeM DecodeAST a (Attribute b) => DecodeM DecodeAST [a] (AttributeSet b) Source # | |
Defined in LLVM.Internal.Attribute decodeM :: AttributeSet b -> DecodeAST [a] Source # | |
EncodeM EncodeAST a (Ptr (AttrBuilder b) -> EncodeAST ()) => EncodeM EncodeAST [a] (AttributeSet b) Source # | |
Defined in LLVM.Internal.Attribute encodeM :: [a] -> EncodeAST (AttributeSet b) Source # |
data AttributeListImpl Source #
Instances
EncodeM EncodeAST AttributeList AttributeList Source # | |
Defined in LLVM.Internal.Attribute |
type Attribute a = Ptr (AttributeImpl a) Source #
newtype AttributeIndex Source #
type AttributeSet a = Ptr (AttributeSetImpl a) Source #
type AttributeList = Ptr AttributeListImpl Source #
data AttrSetDecoder a Source #
AttrSetDecoder | |
|
Instances
DecodeM DecodeAST AttributeList (AttrSetDecoder a, a) Source # | |
Defined in LLVM.Internal.Attribute decodeM :: (AttrSetDecoder a, a) -> DecodeAST AttributeList Source # |
getNumAttributes :: AttributeSet a -> IO CUInt Source #
getAttributes :: AttributeSet a -> Ptr (Attribute a) -> IO () Source #
getAttributeList :: Ptr Context -> AttributeIndex -> AttributeSet a -> IO AttributeList Source #
buildAttributeList :: Ptr Context -> FunctionAttributeSet -> ParameterAttributeSet -> Ptr ParameterAttributeSet -> CUInt -> IO AttributeList Source #
disposeAttributeList :: AttributeList -> IO () Source #
getAttributeSet :: Ptr Context -> Ptr (AttrBuilder a) -> IO (AttributeSet a) Source #
disposeAttributeSet :: AttributeSet a -> IO () Source #
attributeSetsEqual :: AttributeSet a -> AttributeSet a -> IO LLVMBool Source #
data AttrBuilder a Source #
Instances
Monad m => EncodeM m FunctionAttribute (Ptr FunctionAttrBuilder -> EncodeAST ()) Source # | |
Defined in LLVM.Internal.Attribute encodeM :: FunctionAttribute -> m (Ptr FunctionAttrBuilder -> EncodeAST ()) Source # | |
Monad m => EncodeM m ParameterAttribute (Ptr ParameterAttrBuilder -> EncodeAST ()) Source # | |
Defined in LLVM.Internal.Attribute encodeM :: ParameterAttribute -> m (Ptr ParameterAttrBuilder -> EncodeAST ()) Source # |
attrBuilderFromSet :: AttributeSet a -> IO (Ptr (AttrBuilder a)) Source #
disposeAttrBuilder :: Ptr (AttrBuilder a) -> IO () Source #
mergeAttrBuilder :: Ptr (AttrBuilder a) -> Ptr (AttrBuilder a) -> IO () Source #
constructAttrBuilder :: Ptr Word8 -> IO (Ptr (AttrBuilder a)) Source #
destroyAttrBuilder :: Ptr (AttrBuilder a) -> IO () Source #
attrBuilderAddFunctionAttributeKind :: Ptr FunctionAttrBuilder -> FunctionAttributeKind -> IO () Source #
attrBuilderAddParameterAttributeKind :: Ptr ParameterAttrBuilder -> ParameterAttributeKind -> IO () Source #
attrBuilderAddStringAttribute :: Ptr (AttrBuilder a) -> Ptr CChar -> CSize -> Ptr CChar -> CSize -> IO () Source #
attrBuilderAddAlignment :: Ptr ParameterAttrBuilder -> Word64 -> IO () Source #
attrBuilderAddStackAlignment :: Ptr FunctionAttrBuilder -> Word64 -> IO () Source #
attrBuilderAddAllocSize' :: Ptr FunctionAttrBuilder -> CUInt -> CUInt -> LLVMBool -> IO () Source #
attrBuilderAddAllocSize :: Ptr FunctionAttrBuilder -> CUInt -> (CUInt, LLVMBool) -> IO () Source #
attrBuilderAddDereferenceable :: Ptr ParameterAttrBuilder -> Word64 -> IO () Source #
attributeGetAllocSizeArgs :: FunctionAttribute -> Ptr CUInt -> Ptr CUInt -> IO LLVMBool Source #