Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data FloatABI
- data FloatingPointOperationFusionMode
- data DebugCompressionType
- data ThreadModel
- data DebuggerKind
- data EABIVersion
- data FloatingPointDenormalMode
- data ExceptionHandling
- data Options = Options {
- printMachineCode :: Bool
- unsafeFloatingPointMath :: Bool
- noInfinitiesFloatingPointMath :: Bool
- noNaNsFloatingPointMath :: Bool
- noTrappingFloatingPointMath :: Bool
- noSignedZeroesFloatingPointMath :: Bool
- honorSignDependentRoundingFloatingPointMathOption :: Bool
- noZerosInBSS :: Bool
- guaranteedTailCallOptimization :: Bool
- stackSymbolOrdering :: Bool
- enableFastInstructionSelection :: Bool
- useInitArray :: Bool
- disableIntegratedAssembler :: Bool
- compressDebugSections :: DebugCompressionType
- relaxELFRelocations :: Bool
- functionSections :: Bool
- dataSections :: Bool
- uniqueSectionNames :: Bool
- trapUnreachable :: Bool
- emulatedThreadLocalStorage :: Bool
- enableInterProceduralRegisterAllocation :: Bool
- stackAlignmentOverride :: Word32
- floatABIType :: FloatABI
- allowFloatingPointOperationFusion :: FloatingPointOperationFusionMode
- threadModel :: ThreadModel
- eabiVersion :: EABIVersion
- debuggerTuning :: DebuggerKind
- floatingPointDenormalMode :: FloatingPointDenormalMode
- exceptionModel :: ExceptionHandling
- machineCodeOptions :: MachineCodeOptions
- data MachineCodeOptions = MachineCodeOptions {
- sanitizeAddresses :: Bool
- relaxAll :: Bool
- noExecutableStack :: Bool
- fatalWarnings :: Bool
- noWarnings :: Bool
- noDeprecatedWarning :: Bool
- saveTemporaryLabels :: Bool
- useDwarfDirectory :: Bool
- incrementalLinkerCompatible :: Bool
- pieCopyRelocations :: Bool
- showMachineCodeEncoding :: Bool
- showMachineCodeInstructions :: Bool
- verboseAssembly :: Bool
- preserveComentsInAssembly :: Bool
Documentation
Instances
Bounded FloatABI Source # | |
Enum FloatABI Source # | |
Eq FloatABI Source # | |
Data FloatABI Source # | |
Defined in LLVM.Target.Options 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 # | |
Defined in LLVM.Target.Options | |
Read FloatABI Source # | |
Show FloatABI Source # | |
Generic FloatABI Source # | |
Monad m => DecodeM m FloatABI FloatABIType Source # | |
Defined in LLVM.Internal.Target decodeM :: FloatABIType -> m FloatABI Source # | |
Monad m => EncodeM m FloatABI FloatABIType Source # | |
Defined in LLVM.Internal.Target encodeM :: FloatABI -> m FloatABIType Source # | |
type Rep FloatABI Source # | |
Defined in LLVM.Target.Options type Rep FloatABI = D1 (MetaData "FloatABI" "LLVM.Target.Options" "llvm-hs-6.1.0-39V6SSB6h7AKwWVWHSecih" False) (C1 (MetaCons "FloatABIDefault" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "FloatABISoft" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "FloatABIHard" PrefixI False) (U1 :: * -> *))) |
data FloatingPointOperationFusionMode Source #
FloatingPointOperationFusionFast | |
FloatingPointOperationFusionStandard | |
FloatingPointOperationFusionStrict |
Instances
data DebugCompressionType Source #
CompressNone | No compression |
CompressGNU | zlib-gnu style compression |
CompressZ | zlib style compression |
Instances
data ThreadModel Source #
Instances
data DebuggerKind Source #
Instances
data EABIVersion Source #
Instances
data FloatingPointDenormalMode Source #
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
data ExceptionHandling Source #
ExceptionHandlingNone | No exception support |
ExceptionHandlingDwarfCFI | DWARF-like instruction based exceptions |
ExceptionHandlingSjLj | setjmp/longjmp based exceptions |
ExceptionHandlingARM | ARM EHABI |
ExceptionHandlingWinEH | Windows Exception Handling |
Instances
The options of a TargetOptions
http://llvm.org/doxygen/classllvm_1_1TargetOptions.html
data MachineCodeOptions Source #
Instances
Eq MachineCodeOptions Source # | |
Defined in LLVM.Target.Options (==) :: MachineCodeOptions -> MachineCodeOptions -> Bool # (/=) :: MachineCodeOptions -> MachineCodeOptions -> Bool # | |
Ord MachineCodeOptions Source # | |
Defined in LLVM.Target.Options compare :: MachineCodeOptions -> MachineCodeOptions -> Ordering # (<) :: MachineCodeOptions -> MachineCodeOptions -> Bool # (<=) :: MachineCodeOptions -> MachineCodeOptions -> Bool # (>) :: MachineCodeOptions -> MachineCodeOptions -> Bool # (>=) :: MachineCodeOptions -> MachineCodeOptions -> Bool # max :: MachineCodeOptions -> MachineCodeOptions -> MachineCodeOptions # min :: MachineCodeOptions -> MachineCodeOptions -> MachineCodeOptions # | |
Read MachineCodeOptions Source # | |
Defined in LLVM.Target.Options | |
Show MachineCodeOptions Source # | |
Defined in LLVM.Target.Options showsPrec :: Int -> MachineCodeOptions -> ShowS # show :: MachineCodeOptions -> String # showList :: [MachineCodeOptions] -> ShowS # |