X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2FllvmGen%2FLlvm%2FPpLlvm.hs;h=82c6bfa65e8c64cfe4a9d6e8b690d570f377a32c;hb=c648345e3d82c0c40333bfd8ddea2633e21b08dc;hp=80682477613f5f2b07805936b6956e736ef05b33;hpb=24a3fee9f3ff6cef6fe471ab6f0a7ba9ac001faf;p=ghc-hetmet.git diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index 8068247..82c6bfa 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -8,12 +8,10 @@ module Llvm.PpLlvm ( ppLlvmModule, ppLlvmComments, ppLlvmComment, - ppLlvmConstants, - ppLlvmConstant, ppLlvmGlobals, ppLlvmGlobal, - ppLlvmType, - ppLlvmTypes, + ppLlvmAlias, + ppLlvmAliases, ppLlvmFunctionDecls, ppLlvmFunctionDecl, ppLlvmFunctions, @@ -40,10 +38,11 @@ import Unique -- | Print out a whole LLVM module. ppLlvmModule :: LlvmModule -> Doc -ppLlvmModule (LlvmModule comments constants globals decls funcs) +ppLlvmModule (LlvmModule comments aliases globals decls funcs) = ppLlvmComments comments $+$ empty - $+$ ppLlvmConstants constants + $+$ ppLlvmAliases aliases + $+$ empty $+$ ppLlvmGlobals globals $+$ empty $+$ ppLlvmFunctionDecls decls @@ -65,10 +64,7 @@ ppLlvmGlobals ls = vcat $ map ppLlvmGlobal ls -- | Print out a global mutable variable definition ppLlvmGlobal :: LMGlobal -> Doc -ppLlvmGlobal = ppLlvmGlobal' (text "global") - -ppLlvmGlobal' :: Doc -> LMGlobal -> Doc -ppLlvmGlobal' vty (var@(LMGlobalVar _ _ link x a), cont) = +ppLlvmGlobal (var@(LMGlobalVar _ _ link x a c), dat) = let sect = case x of Just x' -> text ", section" <+> doubleQuotes (ftext x') Nothing -> empty @@ -77,38 +73,24 @@ ppLlvmGlobal' vty (var@(LMGlobalVar _ _ link x a), cont) = Just a' -> text ", align" <+> int a' Nothing -> empty - rhs = case cont of + rhs = case dat of Just stat -> texts stat Nothing -> texts (pLower $ getVarType var) - in ppAssignment var $ texts link <+> vty <+> rhs <> sect <> align - -ppLlvmGlobal' _ oth = error $ "Non Global var ppr as global! " ++ show oth + const' = if c then text "constant" else text "global" + in ppAssignment var $ texts link <+> const' <+> rhs <> sect <> align --- | Print out a list global constant variable -ppLlvmConstants :: [LMConstant] -> Doc -ppLlvmConstants cons = vcat $ map ppLlvmConstant cons - --- | Print out a global constant variable -ppLlvmConstant :: LMConstant -> Doc -ppLlvmConstant (v,s) = ppLlvmGlobal' (text "constant") (v, Just s) +ppLlvmGlobal oth = error $ "Non Global var ppr as global! " ++ show oth -- | Print out a list of LLVM type aliases. -ppLlvmTypes :: [LlvmType] -> Doc -ppLlvmTypes tys = vcat $ map ppLlvmType tys +ppLlvmAliases :: [LlvmAlias] -> Doc +ppLlvmAliases tys = vcat $ map ppLlvmAlias tys -- | Print out an LLVM type alias. -ppLlvmType :: LlvmType -> Doc - -ppLlvmType al@(LMAlias _ t) - = texts al <+> equals <+> text "type" <+> texts t - -ppLlvmType (LMFunction t) - = ppLlvmFunctionDecl t - -ppLlvmType _ = empty +ppLlvmAlias :: LlvmAlias -> Doc +ppLlvmAlias (name, ty) = text "%" <> ftext name <+> equals <+> text "type" <+> texts ty -- | Print out a list of function definitions. @@ -117,17 +99,30 @@ ppLlvmFunctions funcs = vcat $ map ppLlvmFunction funcs -- | Print out a function definition. ppLlvmFunction :: LlvmFunction -> Doc -ppLlvmFunction (LlvmFunction dec attrs sec body) = +ppLlvmFunction (LlvmFunction dec args attrs sec body) = let attrDoc = ppSpaceJoin attrs secDoc = case sec of - Just s' -> text "section " <+> (doubleQuotes $ ftext s') + Just s' -> text "section" <+> (doubleQuotes $ ftext s') Nothing -> empty - in text "define" <+> texts dec + in text "define" <+> ppLlvmFunctionHeader dec args <+> attrDoc <+> secDoc $+$ lbrace $+$ ppLlvmBlocks body $+$ rbrace +-- | Print out a function defenition header. +ppLlvmFunctionHeader :: LlvmFunctionDecl -> [LMString] -> Doc +ppLlvmFunctionHeader (LlvmFunctionDecl n l c r varg p a) args + = let varg' = if varg == VarArgs then text ", ..." else empty + align = case a of + Just a' -> space <> text "align" <+> texts a' + Nothing -> empty + args' = map (\((ty,p),n) -> texts ty <+> ppSpaceJoin p <+> text "%" + <> ftext n) + (zip p args) + in texts l <+> texts c <+> texts r <+> text "@" <> ftext n <> lparen <> + (hcat $ intersperse comma args') <> varg' <> rparen <> align + -- | Print out a list of function declaration. ppLlvmFunctionDecls :: LlvmFunctionDecls -> Doc @@ -166,6 +161,7 @@ ppLlvmStatement stmt Return result -> ppReturn result Expr expr -> ppLlvmExpression expr Unreachable -> text "unreachable" + Nop -> empty -- | Print out an LLVM expression. @@ -177,10 +173,11 @@ ppLlvmExpression expr Call tp fp args attrs -> ppCall tp fp args attrs Cast op from to -> ppCast op from to Compare op left right -> ppCmpOp op left right - GetElemPtr ptr indexes -> ppGetElementPtr ptr indexes + GetElemPtr inb ptr indexes -> ppGetElementPtr inb ptr indexes Load ptr -> ppLoad ptr Malloc tp amount -> ppMalloc tp amount Phi tp precessors -> ppPhi tp precessors + Asm asm c ty v se sk -> ppAsm asm c ty v se sk -------------------------------------------------------------------------------- @@ -196,7 +193,7 @@ ppCall ct fptr vals attrs = case fptr of LMLocalVar _ (LMPointer (LMFunction d)) -> ppCall' d -- should be function type otherwise - LMGlobalVar _ (LMFunction d) _ _ _ -> ppCall' d + LMGlobalVar _ (LMFunction d) _ _ _ _ -> ppCall' d -- not pointer or function, so error _other -> error $ "ppCall called with non LMFunction type!\nMust be " @@ -207,7 +204,8 @@ ppCall ct fptr vals attrs = case fptr of ppCall' (LlvmFunctionDecl _ _ cc ret argTy params _) = let tc = if ct == TailCall then text "tail " else empty ppValues = ppCommaJoin vals - ppArgTy = either ppCommaJoin (\x -> ppCommaJoin $ map getVarType x) params <> + ppParams = map (\(ty,p) -> texts ty <+> ppSpaceJoin p) params + ppArgTy = (hcat $ intersperse comma ppParams) <> (case argTy of VarArgs -> text ", ..." FixedArgs -> empty) @@ -229,9 +227,12 @@ ppCmpOp op left right = let cmpOp | isInt (getVarType left) && isInt (getVarType right) = text "icmp" | isFloat (getVarType left) && isFloat (getVarType right) = text "fcmp" + | otherwise = text "icmp" -- Just continue as its much easier to debug + {- | otherwise = error ("can't compare different types, left = " ++ (show $ getVarType left) ++ ", right = " ++ (show $ getVarType right)) + -} in cmpOp <+> texts op <+> texts (getVarType left) <+> (text $ getName left) <> comma <+> (text $ getName right) @@ -264,10 +265,11 @@ ppAlloca tp amount = in text "alloca" <+> texts tp <> comma <+> texts amount' -ppGetElementPtr :: LlvmVar -> [Int] -> Doc -ppGetElementPtr ptr idx = - let indexes = hcat $ map ((comma <+> texts i32 <+>) . texts) idx - in text "getelementptr" <+> texts ptr <> indexes +ppGetElementPtr :: Bool -> LlvmVar -> [LlvmVar] -> Doc +ppGetElementPtr inb ptr idx = + let indexes = comma <+> ppCommaJoin idx + inbound = if inb then text "inbounds" else empty + in text "getelementptr" <+> inbound <+> texts ptr <> indexes ppReturn :: Maybe LlvmVar -> Doc @@ -299,6 +301,18 @@ ppSwitch scrut dflt targets = <+> ppTargets targets +ppAsm :: LMString -> LMString -> LlvmType -> [LlvmVar] -> Bool -> Bool -> Doc +ppAsm asm constraints rty vars sideeffect alignstack = + let asm' = doubleQuotes $ ftext asm + cons = doubleQuotes $ ftext constraints + rty' = texts rty + vars' = lparen <+> ppCommaJoin vars <+> rparen + side = if sideeffect then text "sideeffect" else empty + align = if alignstack then text "alignstack" else empty + in text "call" <+> rty' <+> text "asm" <+> side <+> align <+> asm' <> comma + <+> cons <> vars' + + -------------------------------------------------------------------------------- -- * Misc functions --------------------------------------------------------------------------------