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