Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/234a526fbaec8ed38ab0a0cfe17ddb3b4ba30105

>---------------------------------------------------------------

commit 234a526fbaec8ed38ab0a0cfe17ddb3b4ba30105
Author: David Terei <[email protected]>
Date:   Wed Jan 11 11:49:02 2012 -0800

    More improvements to llvm output style (#5750)

>---------------------------------------------------------------

 compiler/llvmGen/Llvm/PpLlvm.hs     |   27 ++++++++++++++-------------
 compiler/llvmGen/LlvmCodeGen/Ppr.hs |    2 +-
 2 files changed, 15 insertions(+), 14 deletions(-)

diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs
index b5c3ba8..ff701eb 100644
--- a/compiler/llvmGen/Llvm/PpLlvm.hs
+++ b/compiler/llvmGen/Llvm/PpLlvm.hs
@@ -88,7 +88,7 @@ ppLlvmAliases tys = vcat $ map ppLlvmAlias tys
 -- | Print out an LLVM type alias.
 ppLlvmAlias :: LlvmAlias -> Doc
 ppLlvmAlias (name, ty)
-  = text "%" <> ftext name <+> equals <+> text "type" <+> texts ty $+$ newLine
+  = text "%" <> ftext name <+> equals <+> text "type" <+> texts ty
 
 
 -- | Print out a list of function definitions.
@@ -168,24 +168,25 @@ ppLlvmBlock (LlvmBlock blockId stmts)
                          Just id2' -> go id2' rest
                          Nothing   -> empty
         in ppLlvmBlockLabel id
-               $+$ nest 4 (vcat $ map ppLlvmStatement block)
+           $+$ (vcat $ map ppLlvmStatement block)
            $+$ newLine
            $+$ ppRest
 
 -- | Print out an LLVM statement.
 ppLlvmStatement :: LlvmStatement -> Doc
-ppLlvmStatement stmt
-  = case stmt of
-        Assignment  dst expr      -> ppAssignment dst (ppLlvmExpression expr)
-        Branch      target        -> ppBranch target
-        BranchIf    cond ifT ifF  -> ppBranchIf cond ifT ifF
-        Comment     comments      -> ppLlvmComments comments
+ppLlvmStatement stmt =
+  let ind = (text "  " <>)
+  in case stmt of
+        Assignment  dst expr      -> ind $ ppAssignment dst (ppLlvmExpression 
expr)
+        Branch      target        -> ind $ ppBranch target
+        BranchIf    cond ifT ifF  -> ind $ ppBranchIf cond ifT ifF
+        Comment     comments      -> ind $ ppLlvmComments comments
         MkLabel     label         -> ppLlvmBlockLabel label
-        Store       value ptr     -> ppStore value ptr
-        Switch      scrut def tgs -> ppSwitch scrut def tgs
-        Return      result        -> ppReturn result
-        Expr        expr          -> ppLlvmExpression expr
-        Unreachable               -> text "unreachable"
+        Store       value ptr     -> ind $ ppStore value ptr
+        Switch      scrut def tgs -> ind $ ppSwitch scrut def tgs
+        Return      result        -> ind $ ppReturn result
+        Expr        expr          -> ind $ ppLlvmExpression expr
+        Unreachable               -> ind $ text "unreachable"
         Nop                       -> empty
 
 -- | Print out an LLVM block label.
diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs 
b/compiler/llvmGen/LlvmCodeGen/Ppr.hs
index e0cebe5..c914bb2 100644
--- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs
@@ -67,7 +67,7 @@ moduleLayout =
 -- | Header code for LLVM modules
 pprLlvmHeader :: Doc
 pprLlvmHeader =
-    moduleLayout $+$ ppLlvmFunctionDecls (map snd ghcInternalFunctions)
+    moduleLayout $+$ text "" $+$ ppLlvmFunctionDecls (map snd 
ghcInternalFunctions)
 
 -- | Pretty print LLVM data code
 pprLlvmData :: LlvmData -> Doc



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to