-- | module LLVM.Target.Options where import LLVM.Prelude -- | data FloatABI = FloatABIDefault | FloatABISoft | FloatABIHard deriving (Eq, Ord, Read, Show, Enum, Bounded, Typeable, Data, Generic) -- | data FloatingPointOperationFusionMode = FloatingPointOperationFusionFast | FloatingPointOperationFusionStandard | FloatingPointOperationFusionStrict deriving (Eq, Ord, Read, Show, Enum, Bounded, Typeable, Data, Generic) -- | data DebugCompressionType = CompressNone -- ^ No compression | CompressGNU -- ^ zlib-gnu style compression | CompressZ -- ^ zlib style compression deriving (Eq, Ord, Read, Show, Enum, Bounded, Typeable, Data, Generic) -- | data ThreadModel = ThreadModelPOSIX | ThreadModelSingle deriving (Eq, Ord, Read, Show, Enum, Bounded, Typeable, Data, Generic) -- | data DebuggerKind = DebuggerDefault | DebuggerGDB | DebuggerLLDB | DebuggerSCE deriving (Eq, Ord, Read, Show, Enum, Bounded, Typeable, Data, Generic) -- | data EABIVersion = EABIVersionUnknown | EABIVersionDefault | EABIVersion4 | EABIVersion5 | EABIVersionGNU deriving (Eq, Ord, Read, Show, Enum, Bounded, Typeable, Data, Generic) -- | data FloatingPointDenormalMode = 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 deriving (Eq, Ord, Read, Show, Enum, Bounded, Typeable, Data, Generic) -- | data ExceptionHandling = ExceptionHandlingNone -- ^ No exception support | ExceptionHandlingDwarfCFI -- ^ DWARF-like instruction based exceptions | ExceptionHandlingSjLj -- ^ setjmp/longjmp based exceptions | ExceptionHandlingARM -- ^ ARM EHABI | ExceptionHandlingWinEH -- ^ Windows Exception Handling deriving (Eq, Ord, Read, Show, Enum, Bounded, Typeable, Data, Generic) -- | The options of a 'LLVM.Target.TargetOptions' -- 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 } deriving (Eq, Ord, Read, Show) -- | 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 } deriving (Eq, Ord, Read, Show)