llvm-hs-pure-6.2.1: Pure Haskell LLVM functionality (no FFI).

Safe HaskellSafe
LanguageHaskell2010

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

Documentation

data ParameterAttribute Source #

Instances
Eq ParameterAttribute Source # 
Instance details

Defined in LLVM.AST.ParameterAttribute

Data ParameterAttribute Source # 
Instance details

Defined in LLVM.AST.ParameterAttribute

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParameterAttribute -> c ParameterAttribute #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParameterAttribute #

toConstr :: ParameterAttribute -> Constr #

dataTypeOf :: ParameterAttribute -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ParameterAttribute) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParameterAttribute) #

gmapT :: (forall b. Data b => b -> b) -> ParameterAttribute -> ParameterAttribute #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParameterAttribute -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParameterAttribute -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParameterAttribute -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParameterAttribute -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParameterAttribute -> m ParameterAttribute #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParameterAttribute -> m ParameterAttribute #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParameterAttribute -> m ParameterAttribute #

Ord ParameterAttribute Source # 
Instance details

Defined in LLVM.AST.ParameterAttribute

Read ParameterAttribute Source # 
Instance details

Defined in LLVM.AST.ParameterAttribute

Show ParameterAttribute Source # 
Instance details

Defined in LLVM.AST.ParameterAttribute

Generic ParameterAttribute Source # 
Instance details

Defined in LLVM.AST.ParameterAttribute

Associated Types

type Rep ParameterAttribute :: * -> * #

type Rep ParameterAttribute Source # 
Instance details

Defined in LLVM.AST.ParameterAttribute

type Rep ParameterAttribute = D1 (MetaData "ParameterAttribute" "LLVM.AST.ParameterAttribute" "llvm-hs-pure-6.2.1-8ETY0EFB21q8SO4DjmfkXC" False) ((((C1 (MetaCons "ZeroExt" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SignExt" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "InReg" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SRet" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Alignment" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64))))) :+: ((C1 (MetaCons "NoAlias" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ByVal" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "NoCapture" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Nest" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ReadNone" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "ReadOnly" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "WriteOnly" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "InAlloca" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "NonNull" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Dereferenceable" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64))))) :+: ((C1 (MetaCons "DereferenceableOrNull" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) :+: C1 (MetaCons "Returned" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "SwiftSelf" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SwiftError" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "StringAttribute" PrefixI True) (S1 (MetaSel (Just "stringAttributeKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShortByteString) :*: S1 (MetaSel (Just "stringAttributeValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShortByteString)))))))

data FunctionAttribute Source #

Instances
Eq FunctionAttribute Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

Data FunctionAttribute Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunctionAttribute -> c FunctionAttribute #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunctionAttribute #

toConstr :: FunctionAttribute -> Constr #

dataTypeOf :: FunctionAttribute -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunctionAttribute) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunctionAttribute) #

gmapT :: (forall b. Data b => b -> b) -> FunctionAttribute -> FunctionAttribute #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunctionAttribute -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunctionAttribute -> r #

gmapQ :: (forall d. Data d => d -> u) -> FunctionAttribute -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunctionAttribute -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunctionAttribute -> m FunctionAttribute #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionAttribute -> m FunctionAttribute #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionAttribute -> m FunctionAttribute #

Ord FunctionAttribute Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

Read FunctionAttribute Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

Show FunctionAttribute Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

Generic FunctionAttribute Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

Associated Types

type Rep FunctionAttribute :: * -> * #

type Rep FunctionAttribute Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

type Rep FunctionAttribute = D1 (MetaData "FunctionAttribute" "LLVM.AST.FunctionAttribute" "llvm-hs-pure-6.2.1-8ETY0EFB21q8SO4DjmfkXC" False) (((((C1 (MetaCons "NoReturn" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NoUnwind" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "ReadNone" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ReadOnly" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NoInline" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "NoRecurse" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AlwaysInline" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "MinimizeSize" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OptimizeForSize" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OptimizeNone" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "StackProtect" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "StackProtectReq" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "StackProtectStrong" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "StrictFP" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NoRedZone" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "NoImplicitFloat" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Naked" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "InlineHint" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "StackAlignment" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) :+: C1 (MetaCons "ReturnsTwice" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "UWTable" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NonLazyBind" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Builtin" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "NoBuiltin" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Cold" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "JumpTable" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NoDuplicate" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "SanitizeAddress" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SanitizeHWAddress" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SanitizeThread" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "SanitizeMemory" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Speculatable" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "StringAttribute" PrefixI True) (S1 (MetaSel (Just "stringAttributeKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShortByteString) :*: S1 (MetaSel (Just "stringAttributeValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShortByteString)) :+: (C1 (MetaCons "AllocSize" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word32))) :+: C1 (MetaCons "WriteOnly" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "ArgMemOnly" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Convergent" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "InaccessibleMemOnly" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "InaccessibleMemOrArgMemOnly" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SafeStack" PrefixI False) (U1 :: * -> *)))))))

newtype GroupID Source #

Constructors

GroupID Word 
Instances
Eq GroupID Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

Methods

(==) :: GroupID -> GroupID -> Bool #

(/=) :: GroupID -> GroupID -> Bool #

Data GroupID Source # 
Instance details

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 :: (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 #

Ord GroupID Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

Read GroupID Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

Show GroupID Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

Generic GroupID Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

Associated Types

type Rep GroupID :: * -> * #

Methods

from :: GroupID -> Rep GroupID x #

to :: Rep GroupID x -> GroupID #

type Rep GroupID Source # 
Instance details

Defined in LLVM.AST.FunctionAttribute

type Rep GroupID = D1 (MetaData "GroupID" "LLVM.AST.FunctionAttribute" "llvm-hs-pure-6.2.1-8ETY0EFB21q8SO4DjmfkXC" True) (C1 (MetaCons "GroupID" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)))