Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
LLVM.AST.Attribute
Description
Module to allow importing Attribute
distinctly qualified.
Before LLVM 3.5, the attributes which could be used on functions
and those which could be used on parameters were disjoint. In
LLVM 3.5, two attributes (readonly and readnone) can be used
in both contexts. Because their interpretation is different in
the two contexts and only those two attributes can be used in
both contexts, I've opted to keep the Haskell types for parameter
and function attributes distinct, but move the two types into
separate modules so they can have contructors with the same names.
Synopsis
- data ParameterAttribute
- data FunctionAttribute
- = AllocSize Word32 (Maybe Word32)
- | AlwaysInline
- | ArgMemOnly
- | Builtin
- | Cold
- | Convergent
- | InaccessibleMemOnly
- | InaccessibleMemOrArgMemOnly
- | InlineHint
- | JumpTable
- | MinimizeSize
- | MustProgress
- | Naked
- | NoBuiltin
- | NoDuplicate
- | NoFree
- | NoImplicitFloat
- | NoInline
- | NonLazyBind
- | NoRecurse
- | NoRedZone
- | NoReturn
- | NoSync
- | NoUnwind
- | OptimizeForSize
- | OptimizeNone
- | ReadNone
- | ReadOnly
- | ReturnsTwice
- | SafeStack
- | SanitizeAddress
- | SanitizeHWAddress
- | SanitizeMemory
- | SanitizeThread
- | Speculatable
- | StackAlignment Word64
- | StackProtect
- | StackProtectReq
- | StackProtectStrong
- | StrictFP
- | StringAttribute { }
- | UWTable
- | WillReturn
- | WriteOnly
- newtype GroupID = GroupID Word
Documentation
data ParameterAttribute Source #
Constructors
Alignment Word64 | |
ByVal | |
Dereferenceable Word64 | |
DereferenceableOrNull Word64 | |
ImmArg | |
InAlloca | |
InReg | |
Nest | |
NoAlias | |
NoCapture | |
NonNull | |
Returned | |
SignExt | |
SRet | |
SwiftError | |
SwiftSelf | |
ZeroExt |
Instances
data FunctionAttribute Source #
Constructors
Instances
Instances
Data GroupID Source # | |
Defined in LLVM.AST.FunctionAttribute Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GroupID -> c GroupID # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GroupID # toConstr :: GroupID -> Constr # dataTypeOf :: GroupID -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GroupID) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GroupID) # gmapT :: (forall b. Data b => b -> b) -> GroupID -> GroupID # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GroupID -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GroupID -> r # gmapQ :: (forall d. Data d => d -> u) -> GroupID -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GroupID -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GroupID -> m GroupID # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GroupID -> m GroupID # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GroupID -> m GroupID # | |
Generic GroupID Source # | |
Read GroupID Source # | |
Show GroupID Source # | |
Eq GroupID Source # | |
Ord GroupID Source # | |
Defined in LLVM.AST.FunctionAttribute | |
EncodeM EncodeAST [Either GroupID FunctionAttribute] FunctionAttributeSet Source # | |
Defined in LLVM.Internal.Attribute Methods encodeM :: [Either GroupID FunctionAttribute] -> EncodeAST FunctionAttributeSet Source # | |
type Rep GroupID Source # | |
Defined in LLVM.AST.FunctionAttribute |