Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module provides an enumeration of the various transformation (e.g. optimization) passes
provided by LLVM. They can be used to create a PassManager
to, in turn,
run the passes on Module
s. If you don't know what passes you want, consider
instead using CuratedPassSetSpec
.
Synopsis
- data Pass
- = AggressiveDeadCodeElimination
- | BreakCriticalEdges
- | CodeGenPrepare
- | ConstantPropagation
- | CorrelatedValuePropagation
- | DeadCodeElimination
- | DeadInstructionElimination
- | DeadStoreElimination
- | DemoteRegisterToMemory
- | EarlyCommonSubexpressionElimination
- | GlobalValueNumbering { }
- | InductionVariableSimplify
- | InstructionCombining
- | JumpThreading
- | LoopClosedSingleStaticAssignment
- | LoopInvariantCodeMotion
- | LoopDeletion
- | LoopIdiom
- | LoopInstructionSimplify
- | LoopRotate
- | LoopStrengthReduce
- | LoopUnroll { }
- | LoopUnswitch { }
- | LowerAtomic
- | LowerInvoke
- | LowerSwitch
- | LowerExpectIntrinsic
- | MemcpyOptimization
- | PromoteMemoryToRegister
- | Reassociate
- | ScalarReplacementOfAggregates { }
- | OldScalarReplacementOfAggregates { }
- | SparseConditionalConstantPropagation
- | SimplifyLibCalls
- | SimplifyControlFlowGraph
- | Sinking
- | TailCallElimination
- | AlwaysInline { }
- | ArgumentPromotion
- | ConstantMerge
- | FunctionAttributes
- | FunctionInlining { }
- | GlobalDeadCodeElimination
- | InternalizeFunctions {
- exportList :: [String]
- | InterproceduralConstantPropagation
- | InterproceduralSparseConditionalConstantPropagation
- | MergeFunctions
- | PartialInlining
- | PruneExceptionHandling
- | StripDeadDebugInfo
- | StripDebugDeclare
- | StripNonDebugSymbols
- | StripSymbols { }
- | LoopVectorize { }
- | SuperwordLevelParallelismVectorize
- | GCOVProfiler { }
- | AddressSanitizer
- | AddressSanitizerModule
- | MemorySanitizer {
- trackOrigins :: Bool
- | ThreadSanitizer
- | BoundsChecking
- defaultLoopVectorize :: Pass
- newtype GCOVVersion = GCOVVersion ShortByteString
- defaultGCOVProfiler :: Pass
- defaultAddressSanitizer :: Pass
- defaultAddressSanitizerModule :: Pass
- defaultMemorySanitizer :: Pass
- defaultThreadSanitizer :: Pass
Documentation
http://llvm.org/docs/Passes.html#transform-passes
A few passes can make use of information in a TargetMachine
if one
is provided to createPassManager
.
http://llvm.org/doxygen/classllvm_1_1Pass.html
Instances
Eq Pass Source # | |
Data Pass Source # | |
Defined in LLVM.Transforms gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pass -> c Pass # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pass # dataTypeOf :: Pass -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pass) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pass) # gmapT :: (forall b. Data b => b -> b) -> Pass -> Pass # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r # gmapQ :: (forall d. Data d => d -> u) -> Pass -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pass -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pass -> m Pass # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass # | |
Ord Pass Source # | |
Read Pass Source # | |
Show Pass Source # | |
Generic Pass Source # | |
type Rep Pass Source # | |
Defined in LLVM.Transforms type Rep Pass = D1 (MetaData "Pass" "LLVM.Transforms" "llvm-hs-6.2.0-5nzXx6EeZOxK4tiIOeKBGx" False) (((((C1 (MetaCons "AggressiveDeadCodeElimination" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "BreakCriticalEdges" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CodeGenPrepare" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "ConstantPropagation" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CorrelatedValuePropagation" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "DeadCodeElimination" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DeadInstructionElimination" PrefixI False) (U1 :: * -> *)))) :+: (((C1 (MetaCons "DeadStoreElimination" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DemoteRegisterToMemory" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "EarlyCommonSubexpressionElimination" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "GlobalValueNumbering" PrefixI True) (S1 (MetaSel (Just "noLoads") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) :+: ((C1 (MetaCons "InductionVariableSimplify" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "InstructionCombining" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "JumpThreading" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LoopClosedSingleStaticAssignment" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "LoopInvariantCodeMotion" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "LoopDeletion" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LoopIdiom" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "LoopInstructionSimplify" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LoopRotate" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "LoopStrengthReduce" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LoopUnroll" PrefixI True) (S1 (MetaSel (Just "loopUnrollThreshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word)) :*: (S1 (MetaSel (Just "count") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word)) :*: S1 (MetaSel (Just "allowPartial") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))))))) :+: (((C1 (MetaCons "LoopUnswitch" PrefixI True) (S1 (MetaSel (Just "optimizeForSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: C1 (MetaCons "LowerAtomic" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "LowerInvoke" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LowerSwitch" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "LowerExpectIntrinsic" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MemcpyOptimization" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "PromoteMemoryToRegister" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Reassociate" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "ScalarReplacementOfAggregates" PrefixI True) (S1 (MetaSel (Just "requiresDominatorTree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: (C1 (MetaCons "OldScalarReplacementOfAggregates" PrefixI True) ((S1 (MetaSel (Just "oldScalarReplacementOfAggregatesThreshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word)) :*: S1 (MetaSel (Just "useDominatorTree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :*: (S1 (MetaSel (Just "structMemberThreshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word)) :*: (S1 (MetaSel (Just "arrayElementThreshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word)) :*: S1 (MetaSel (Just "scalarLoadThreshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word))))) :+: C1 (MetaCons "SparseConditionalConstantPropagation" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "SimplifyLibCalls" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SimplifyControlFlowGraph" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Sinking" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "TailCallElimination" PrefixI False) (U1 :: * -> *)))) :+: (((C1 (MetaCons "AlwaysInline" PrefixI True) (S1 (MetaSel (Just "insertLifetime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: C1 (MetaCons "ArgumentPromotion" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "ConstantMerge" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "FunctionAttributes" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "FunctionInlining" PrefixI True) (S1 (MetaSel (Just "functionInliningThreshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)) :+: C1 (MetaCons "GlobalDeadCodeElimination" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "InternalizeFunctions" PrefixI True) (S1 (MetaSel (Just "exportList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) :+: C1 (MetaCons "InterproceduralConstantPropagation" PrefixI False) (U1 :: * -> *))))) :+: ((((C1 (MetaCons "InterproceduralSparseConditionalConstantPropagation" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MergeFunctions" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "PartialInlining" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "PruneExceptionHandling" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "StripDeadDebugInfo" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "StripDebugDeclare" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "StripNonDebugSymbols" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "StripSymbols" PrefixI True) (S1 (MetaSel (Just "onlyDebugInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) :+: (((C1 (MetaCons "LoopVectorize" PrefixI True) (S1 (MetaSel (Just "noUnrolling") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "alwaysVectorize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: C1 (MetaCons "SuperwordLevelParallelismVectorize" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "GCOVProfiler" PrefixI True) ((S1 (MetaSel (Just "emitNotes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: (S1 (MetaSel (Just "emitData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "version") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GCOVVersion))) :*: (S1 (MetaSel (Just "useCfgChecksum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: (S1 (MetaSel (Just "noRedZone") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "functionNamesInData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) :+: C1 (MetaCons "AddressSanitizer" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "AddressSanitizerModule" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MemorySanitizer" PrefixI True) (S1 (MetaSel (Just "trackOrigins") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) :+: (C1 (MetaCons "ThreadSanitizer" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "BoundsChecking" PrefixI False) (U1 :: * -> *))))))) |
defaultLoopVectorize :: Pass Source #
Defaults for the LoopVectorize
pass
newtype GCOVVersion Source #
Instances
defaultGCOVProfiler :: Pass Source #
Defaults for GCOVProfiler
.
defaultAddressSanitizer :: Pass Source #
Defaults for AddressSanitizer
.
defaultAddressSanitizerModule :: Pass Source #
Defaults for AddressSanitizerModule
.
defaultMemorySanitizer :: Pass Source #
Defaults for MemorySanitizer
.
defaultThreadSanitizer :: Pass Source #
Defaults for ThreadSanitizer
.