module LLVM.Internal.FFI.Transforms where
import LLVM.Prelude
needsTargetMachine :: String -> Bool
needsTargetMachine "CodeGenPrepare" = True
needsTargetMachine _ = False
cName :: String -> String
cName n =
let core = case n of
"AddressSanitizer" -> "AddressSanitizerFunction"
"AggressiveDeadCodeElimination" -> "AggressiveDCE"
"AlwaysInline" -> "AlwaysInliner"
"DeadInstructionElimination" -> "DeadInstElimination"
"EarlyCommonSubexpressionElimination" -> "EarlyCSE"
"FunctionAttributes" -> "FunctionAttrs"
"GlobalDeadCodeElimination" -> "GlobalDCE"
"InductionVariableSimplify" -> "IndVarSimplify"
"InternalizeFunctions" -> "Internalize"
"InterproceduralConstantPropagation" -> "IPConstantPropagation"
"InterproceduralSparseConditionalConstantPropagation" -> "IPSCCP"
"LoopClosedSingleStaticAssignment" -> "LCSSA"
"LoopInvariantCodeMotion" -> "LICM"
"LoopInstructionSimplify" -> "LoopInstSimplify"
"MemcpyOptimization" -> "MemCpyOpt"
"PruneExceptionHandling" -> "PruneEH"
"ScalarReplacementOfAggregates" -> "SROA"
"OldScalarReplacementOfAggregates" -> "ScalarReplAggregates"
"SimplifyControlFlowGraph" -> "CFGSimplification"
"SparseConditionalConstantPropagation" -> "SCCP"
"SuperwordLevelParallelismVectorize" -> "SLPVectorize"
h -> h
patchImpls = [
"AddressSanitizer",
"AddressSanitizerModule",
"BoundsChecking",
"CodeGenPrepare",
"GlobalValueNumbering",
"InternalizeFunctions",
"BasicBlockVectorize",
"BlockPlacement",
"BreakCriticalEdges",
"DeadCodeElimination",
"DeadInstructionElimination",
"DemoteRegisterToMemory",
"EdgeProfiler",
"GCOVProfiler",
"LoopClosedSingleStaticAssignment",
"LoopInstructionSimplify",
"LoopStrengthReduce",
"LoopVectorize",
"LowerAtomic",
"LowerInvoke",
"LowerSwitch",
"MemorySanitizer",
"MergeFunctions",
"OptimalEdgeProfiler",
"PathProfiler",
"PartialInlining",
"ScalarReplacementOfAggregates",
"Sinking",
"StripDeadDebugInfo",
"StripDebugDeclare",
"StripNonDebugSymbols",
"ThreadSanitizer"
]
in
(if (n `elem` patchImpls) then "LLVM_Hs_" else "LLVM") ++ "Add" ++ core ++ "Pass"