llvm-hs-6.3.0: General purpose LLVM bindings

Safe HaskellSafe
LanguageHaskell2010

LLVM.Transforms

Description

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 Modules. If you don't know what passes you want, consider instead using CuratedPassSetSpec.

Synopsis

Documentation

data Pass Source #

Constructors

AggressiveDeadCodeElimination 
BreakCriticalEdges 
CodeGenPrepare

can use a TargetMachine

ConstantPropagation 
CorrelatedValuePropagation 
DeadCodeElimination 
DeadInstructionElimination 
DeadStoreElimination 
DemoteRegisterToMemory 
EarlyCommonSubexpressionElimination 
GlobalValueNumbering 

Fields

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 

Fields

ArgumentPromotion 
ConstantMerge 
FunctionAttributes 
FunctionInlining 
GlobalDeadCodeElimination 
InternalizeFunctions 

Fields

InterproceduralConstantPropagation 
InterproceduralSparseConditionalConstantPropagation 
MergeFunctions 
PartialInlining 
PruneExceptionHandling 
StripDeadDebugInfo 
StripDebugDeclare 
StripNonDebugSymbols 
StripSymbols 

Fields

LoopVectorize 
SuperwordLevelParallelismVectorize 
GCOVProfiler 
AddressSanitizer 
AddressSanitizerModule 
MemorySanitizer 

Fields

ThreadSanitizer 
BoundsChecking 
Instances
Eq Pass Source # 
Instance details

Defined in LLVM.Transforms

Methods

(==) :: Pass -> Pass -> Bool #

(/=) :: Pass -> Pass -> Bool #

Data Pass Source # 
Instance details

Defined in LLVM.Transforms

Methods

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 #

toConstr :: Pass -> Constr #

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 # 
Instance details

Defined in LLVM.Transforms

Methods

compare :: Pass -> Pass -> Ordering #

(<) :: Pass -> Pass -> Bool #

(<=) :: Pass -> Pass -> Bool #

(>) :: Pass -> Pass -> Bool #

(>=) :: Pass -> Pass -> Bool #

max :: Pass -> Pass -> Pass #

min :: Pass -> Pass -> Pass #

Read Pass Source # 
Instance details

Defined in LLVM.Transforms

Show Pass Source # 
Instance details

Defined in LLVM.Transforms

Methods

showsPrec :: Int -> Pass -> ShowS #

show :: Pass -> String #

showList :: [Pass] -> ShowS #

Generic Pass Source # 
Instance details

Defined in LLVM.Transforms

Associated Types

type Rep Pass :: * -> * #

Methods

from :: Pass -> Rep Pass x #

to :: Rep Pass x -> Pass #

type Rep Pass Source # 
Instance details

Defined in LLVM.Transforms

type Rep Pass = D1 (MetaData "Pass" "LLVM.Transforms" "llvm-hs-6.3.0-10kxq0eeZ97CyAz5daI3xT" 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 :: * -> *)))))))

newtype GCOVVersion Source #

Instances
Eq GCOVVersion Source # 
Instance details

Defined in LLVM.Transforms

Data GCOVVersion Source # 
Instance details

Defined in LLVM.Transforms

Methods

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

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

toConstr :: GCOVVersion -> Constr #

dataTypeOf :: GCOVVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GCOVVersion Source # 
Instance details

Defined in LLVM.Transforms

Read GCOVVersion Source # 
Instance details

Defined in LLVM.Transforms

Show GCOVVersion Source # 
Instance details

Defined in LLVM.Transforms

Generic GCOVVersion Source # 
Instance details

Defined in LLVM.Transforms

Associated Types

type Rep GCOVVersion :: * -> * #

(Monad m, MonadThrow m, MonadAnyCont IO m) => EncodeM m GCOVVersion CString Source # 
Instance details

Defined in LLVM.Internal.PassManager

type Rep GCOVVersion Source # 
Instance details

Defined in LLVM.Transforms

type Rep GCOVVersion = D1 (MetaData "GCOVVersion" "LLVM.Transforms" "llvm-hs-6.3.0-10kxq0eeZ97CyAz5daI3xT" True) (C1 (MetaCons "GCOVVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShortByteString)))