{-# LANGUAGE OverloadedStrings #-}
module LLVM.Transforms where
import LLVM.Prelude
data Pass
= AggressiveDeadCodeElimination
| BreakCriticalEdges
| CodeGenPrepare
| ConstantPropagation
| CorrelatedValuePropagation
| DeadCodeElimination
| DeadInstructionElimination
| DeadStoreElimination
| DemoteRegisterToMemory
| EarlyCommonSubexpressionElimination
| GlobalValueNumbering { noLoads :: Bool }
| InductionVariableSimplify
| InstructionCombining
| JumpThreading
| LoopClosedSingleStaticAssignment
| LoopInvariantCodeMotion
| LoopDeletion
| LoopIdiom
| LoopInstructionSimplify
| LoopRotate
| LoopStrengthReduce
| LoopUnroll { loopUnrollThreshold :: Maybe Word, count :: Maybe Word, allowPartial :: Maybe Bool }
| LoopUnswitch { optimizeForSize :: Bool }
| LowerAtomic
| LowerInvoke
| LowerSwitch
| LowerExpectIntrinsic
| MemcpyOptimization
| PromoteMemoryToRegister
| Reassociate
| ScalarReplacementOfAggregates { requiresDominatorTree :: Bool }
| OldScalarReplacementOfAggregates {
oldScalarReplacementOfAggregatesThreshold :: Maybe Word,
useDominatorTree :: Bool,
structMemberThreshold :: Maybe Word,
arrayElementThreshold :: Maybe Word,
scalarLoadThreshold :: Maybe Word
}
| SparseConditionalConstantPropagation
| SimplifyLibCalls
| SimplifyControlFlowGraph
| Sinking
| TailCallElimination
| AlwaysInline { insertLifetime :: Bool }
| ArgumentPromotion
| ConstantMerge
| FunctionAttributes
| FunctionInlining {
functionInliningThreshold :: Word
}
| GlobalDeadCodeElimination
| InternalizeFunctions { exportList :: [String] }
| InterproceduralConstantPropagation
| InterproceduralSparseConditionalConstantPropagation
| MergeFunctions
| PartialInlining
| PruneExceptionHandling
| StripDeadDebugInfo
| StripDebugDeclare
| StripNonDebugSymbols
| StripSymbols { onlyDebugInfo :: Bool }
| LoopVectorize {
noUnrolling :: Bool,
alwaysVectorize :: Bool
}
| SuperwordLevelParallelismVectorize
| GCOVProfiler {
emitNotes :: Bool,
emitData :: Bool,
version :: GCOVVersion,
useCfgChecksum :: Bool,
noRedZone :: Bool,
functionNamesInData :: Bool
}
| AddressSanitizer
| AddressSanitizerModule
| MemorySanitizer {
trackOrigins :: Bool
}
| ThreadSanitizer
| BoundsChecking
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
defaultLoopVectorize :: Pass
defaultLoopVectorize = LoopVectorize {
noUnrolling = False,
alwaysVectorize = True
}
newtype GCOVVersion = GCOVVersion ShortByteString
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
defaultGCOVProfiler :: Pass
defaultGCOVProfiler = GCOVProfiler {
emitNotes = True,
emitData = True,
version = GCOVVersion "402*",
useCfgChecksum = False,
noRedZone = False,
functionNamesInData = True
}
defaultAddressSanitizer :: Pass
defaultAddressSanitizer = AddressSanitizer
defaultAddressSanitizerModule :: Pass
defaultAddressSanitizerModule = AddressSanitizerModule
defaultMemorySanitizer :: Pass
defaultMemorySanitizer = MemorySanitizer {
trackOrigins = False
}
defaultThreadSanitizer :: Pass
defaultThreadSanitizer = ThreadSanitizer