llvm-hs-5.1.1: General purpose LLVM bindings

Safe HaskellSafe
LanguageHaskell98

LLVM.Target.Options

Description

Synopsis

Documentation

data FloatABI Source #

Instances

Bounded FloatABI Source # 
Enum FloatABI Source # 
Eq FloatABI Source # 
Data FloatABI Source # 

Methods

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

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

toConstr :: FloatABI -> Constr #

dataTypeOf :: FloatABI -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FloatABI Source # 
Read FloatABI Source # 
Show FloatABI Source # 
Generic FloatABI Source # 

Associated Types

type Rep FloatABI :: * -> * #

Methods

from :: FloatABI -> Rep FloatABI x #

to :: Rep FloatABI x -> FloatABI #

type Rep FloatABI Source # 
type Rep FloatABI = D1 * (MetaData "FloatABI" "LLVM.Target.Options" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" False) ((:+:) * (C1 * (MetaCons "FloatABIDefault" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FloatABISoft" PrefixI False) (U1 *)) (C1 * (MetaCons "FloatABIHard" PrefixI False) (U1 *))))

data FloatingPointOperationFusionMode Source #

Instances

Bounded FloatingPointOperationFusionMode Source # 
Enum FloatingPointOperationFusionMode Source # 
Eq FloatingPointOperationFusionMode Source # 
Data FloatingPointOperationFusionMode Source # 

Methods

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

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

toConstr :: FloatingPointOperationFusionMode -> Constr #

dataTypeOf :: FloatingPointOperationFusionMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FloatingPointOperationFusionMode Source # 
Read FloatingPointOperationFusionMode Source # 
Show FloatingPointOperationFusionMode Source # 
Generic FloatingPointOperationFusionMode Source # 
type Rep FloatingPointOperationFusionMode Source # 
type Rep FloatingPointOperationFusionMode = D1 * (MetaData "FloatingPointOperationFusionMode" "LLVM.Target.Options" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" False) ((:+:) * (C1 * (MetaCons "FloatingPointOperationFusionFast" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FloatingPointOperationFusionStandard" PrefixI False) (U1 *)) (C1 * (MetaCons "FloatingPointOperationFusionStrict" PrefixI False) (U1 *))))

data DebugCompressionType Source #

Constructors

CompressNone

No compression

CompressGNU

zlib-gnu style compression

CompressZ

zlib style compression

Instances

Bounded DebugCompressionType Source # 
Enum DebugCompressionType Source # 
Eq DebugCompressionType Source # 
Data DebugCompressionType Source # 

Methods

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

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

toConstr :: DebugCompressionType -> Constr #

dataTypeOf :: DebugCompressionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DebugCompressionType Source # 
Read DebugCompressionType Source # 
Show DebugCompressionType Source # 
Generic DebugCompressionType Source # 
type Rep DebugCompressionType Source # 
type Rep DebugCompressionType = D1 * (MetaData "DebugCompressionType" "LLVM.Target.Options" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" False) ((:+:) * (C1 * (MetaCons "CompressNone" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CompressGNU" PrefixI False) (U1 *)) (C1 * (MetaCons "CompressZ" PrefixI False) (U1 *))))

data ThreadModel Source #

Instances

Bounded ThreadModel Source # 
Enum ThreadModel Source # 
Eq ThreadModel Source # 
Data ThreadModel Source # 

Methods

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

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

toConstr :: ThreadModel -> Constr #

dataTypeOf :: ThreadModel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ThreadModel Source # 
Read ThreadModel Source # 
Show ThreadModel Source # 
Generic ThreadModel Source # 

Associated Types

type Rep ThreadModel :: * -> * #

type Rep ThreadModel Source # 
type Rep ThreadModel = D1 * (MetaData "ThreadModel" "LLVM.Target.Options" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" False) ((:+:) * (C1 * (MetaCons "ThreadModelPOSIX" PrefixI False) (U1 *)) (C1 * (MetaCons "ThreadModelSingle" PrefixI False) (U1 *)))

data DebuggerKind Source #

Instances

Bounded DebuggerKind Source # 
Enum DebuggerKind Source # 
Eq DebuggerKind Source # 
Data DebuggerKind Source # 

Methods

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

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

toConstr :: DebuggerKind -> Constr #

dataTypeOf :: DebuggerKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DebuggerKind Source # 
Read DebuggerKind Source # 
Show DebuggerKind Source # 
Generic DebuggerKind Source # 

Associated Types

type Rep DebuggerKind :: * -> * #

type Rep DebuggerKind Source # 
type Rep DebuggerKind = D1 * (MetaData "DebuggerKind" "LLVM.Target.Options" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" False) ((:+:) * ((:+:) * (C1 * (MetaCons "DebuggerDefault" PrefixI False) (U1 *)) (C1 * (MetaCons "DebuggerGDB" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "DebuggerLLDB" PrefixI False) (U1 *)) (C1 * (MetaCons "DebuggerSCE" PrefixI False) (U1 *))))

data EABIVersion Source #

Instances

Bounded EABIVersion Source # 
Enum EABIVersion Source # 
Eq EABIVersion Source # 
Data EABIVersion Source # 

Methods

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

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

toConstr :: EABIVersion -> Constr #

dataTypeOf :: EABIVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EABIVersion Source # 
Read EABIVersion Source # 
Show EABIVersion Source # 
Generic EABIVersion Source # 

Associated Types

type Rep EABIVersion :: * -> * #

type Rep EABIVersion Source # 
type Rep EABIVersion = D1 * (MetaData "EABIVersion" "LLVM.Target.Options" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" False) ((:+:) * ((:+:) * (C1 * (MetaCons "EABIVersionUnknown" PrefixI False) (U1 *)) (C1 * (MetaCons "EABIVersionDefault" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "EABIVersion4" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EABIVersion5" PrefixI False) (U1 *)) (C1 * (MetaCons "EABIVersionGNU" PrefixI False) (U1 *)))))

data FloatingPointDenormalMode Source #

Constructors

FloatingPointDenormalIEEE

IEEE 754 denormal numbers

FloatingPointDenormalPreserveSign

The sign of a flushed-to-zero number is preserved in the sign of 0

FloatingPointDenormalPositiveZero

Denormals are flushed to positive zero

Instances

Bounded FloatingPointDenormalMode Source # 
Enum FloatingPointDenormalMode Source # 
Eq FloatingPointDenormalMode Source # 
Data FloatingPointDenormalMode Source # 

Methods

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

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

toConstr :: FloatingPointDenormalMode -> Constr #

dataTypeOf :: FloatingPointDenormalMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FloatingPointDenormalMode Source # 
Read FloatingPointDenormalMode Source # 
Show FloatingPointDenormalMode Source # 
Generic FloatingPointDenormalMode Source # 
type Rep FloatingPointDenormalMode Source # 
type Rep FloatingPointDenormalMode = D1 * (MetaData "FloatingPointDenormalMode" "LLVM.Target.Options" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" False) ((:+:) * (C1 * (MetaCons "FloatingPointDenormalIEEE" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FloatingPointDenormalPreserveSign" PrefixI False) (U1 *)) (C1 * (MetaCons "FloatingPointDenormalPositiveZero" PrefixI False) (U1 *))))

data ExceptionHandling Source #

Constructors

ExceptionHandlingNone

No exception support

ExceptionHandlingDwarfCFI

DWARF-like instruction based exceptions

ExceptionHandlingSjLj

setjmp/longjmp based exceptions

ExceptionHandlingARM

ARM EHABI

ExceptionHandlingWinEH

Windows Exception Handling

Instances

Bounded ExceptionHandling Source # 
Enum ExceptionHandling Source # 
Eq ExceptionHandling Source # 
Data ExceptionHandling Source # 

Methods

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

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

toConstr :: ExceptionHandling -> Constr #

dataTypeOf :: ExceptionHandling -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ExceptionHandling Source # 
Read ExceptionHandling Source # 
Show ExceptionHandling Source # 
Generic ExceptionHandling Source # 
type Rep ExceptionHandling Source # 
type Rep ExceptionHandling = D1 * (MetaData "ExceptionHandling" "LLVM.Target.Options" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ExceptionHandlingNone" PrefixI False) (U1 *)) (C1 * (MetaCons "ExceptionHandlingDwarfCFI" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ExceptionHandlingSjLj" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ExceptionHandlingARM" PrefixI False) (U1 *)) (C1 * (MetaCons "ExceptionHandlingWinEH" PrefixI False) (U1 *)))))

data Options Source #

data MachineCodeOptions Source #