diff options
author | Ian Lynagh <igloo@earth.li> | 2012-06-20 16:42:12 +0100 |
---|---|---|
committer | Ian Lynagh <igloo@earth.li> | 2012-06-20 16:42:12 +0100 |
commit | 5045cfbc96315e3bc645c563bcd8df8e548d66ae (patch) | |
tree | ca2a4848c504c81f38719a0f83366dd50ec6b01d | |
parent | 158c3530eb4ec3b770f293341c4817fc7ea4094d (diff) | |
download | haskell-5045cfbc96315e3bc645c563bcd8df8e548d66ae.tar.gz |
Remove some redundant Platform arguments
-rw-r--r-- | compiler/cmm/PprCmmDecl.hs | 8 | ||||
-rw-r--r-- | compiler/cmm/PprCmmExpr.hs | 25 |
2 files changed, 16 insertions, 17 deletions
diff --git a/compiler/cmm/PprCmmDecl.hs b/compiler/cmm/PprCmmDecl.hs index 41653dcd9f..0b22e5369a 100644 --- a/compiler/cmm/PprCmmDecl.hs +++ b/compiler/cmm/PprCmmDecl.hs @@ -81,7 +81,7 @@ instance Outputable CmmStatics where ppr x = sdocWithPlatform $ \platform -> pprStatics platform x instance Outputable CmmStatic where - ppr x = sdocWithPlatform $ \platform -> pprStatic platform x + ppr = pprStatic instance Outputable CmmInfoTable where ppr = pprInfoTable @@ -153,9 +153,9 @@ pprStatics :: Platform -> CmmStatics -> SDoc pprStatics platform (Statics lbl ds) = vcat ((pprCLabel platform lbl <> colon) : map ppr ds) -pprStatic :: Platform -> CmmStatic -> SDoc -pprStatic platform s = case s of - CmmStaticLit lit -> nest 4 $ ptext (sLit "const") <+> pprLit platform lit <> semi +pprStatic :: CmmStatic -> SDoc +pprStatic s = case s of + CmmStaticLit lit -> nest 4 $ ptext (sLit "const") <+> pprLit lit <> semi CmmUninitialised i -> nest 4 $ text "I8" <> brackets (int i) CmmString s' -> nest 4 $ text "I8[]" <+> text (show s') diff --git a/compiler/cmm/PprCmmExpr.hs b/compiler/cmm/PprCmmExpr.hs index 7eddc948c1..fd47520f96 100644 --- a/compiler/cmm/PprCmmExpr.hs +++ b/compiler/cmm/PprCmmExpr.hs @@ -39,7 +39,6 @@ module PprCmmExpr where import CmmExpr -import CLabel import Outputable import Platform @@ -57,7 +56,7 @@ instance Outputable CmmReg where ppr e = pprReg e instance Outputable CmmLit where - ppr l = sdocWithPlatform $ \platform -> pprLit platform l + ppr l = pprLit l instance Outputable LocalReg where ppr e = pprLocalReg e @@ -79,7 +78,7 @@ pprExpr platform e pprExpr platform (CmmMachOp (MO_Add rep) [CmmReg reg, CmmLit (CmmInt (fromIntegral i) rep)]) where rep = typeWidth (cmmRegType reg) - CmmLit lit -> pprLit platform lit + CmmLit lit -> pprLit lit _other -> pprExpr1 platform e -- Here's the precedence table from CmmParse.y: @@ -137,7 +136,7 @@ infixMachOp8 _ = Nothing pprExpr9 :: Platform -> CmmExpr -> SDoc pprExpr9 platform e = case e of - CmmLit lit -> pprLit1 platform lit + CmmLit lit -> pprLit1 lit CmmLoad expr rep -> ppr rep <> brackets (ppr expr) CmmReg reg -> ppr reg CmmRegOff reg off -> parens (ppr reg <+> char '+' <+> int off) @@ -186,24 +185,24 @@ infixMachOp mop -- To minimise line noise we adopt the convention that if the literal -- has the natural machine word size, we do not append the type -- -pprLit :: Platform -> CmmLit -> SDoc -pprLit platform lit = case lit of +pprLit :: CmmLit -> SDoc +pprLit lit = case lit of CmmInt i rep -> hcat [ (if i < 0 then parens else id)(integer i) , ppUnless (rep == wordWidth) $ space <> dcolon <+> ppr rep ] CmmFloat f rep -> hsep [ double (fromRat f), dcolon, ppr rep ] - CmmLabel clbl -> pprCLabel platform clbl - CmmLabelOff clbl i -> pprCLabel platform clbl <> ppr_offset i - CmmLabelDiffOff clbl1 clbl2 i -> pprCLabel platform clbl1 <> char '-' - <> pprCLabel platform clbl2 <> ppr_offset i + CmmLabel clbl -> ppr clbl + CmmLabelOff clbl i -> ppr clbl <> ppr_offset i + CmmLabelDiffOff clbl1 clbl2 i -> ppr clbl1 <> char '-' + <> ppr clbl2 <> ppr_offset i CmmBlock id -> ppr id CmmHighStackMark -> text "<highSp>" -pprLit1 :: Platform -> CmmLit -> SDoc -pprLit1 platform lit@(CmmLabelOff {}) = parens (pprLit platform lit) -pprLit1 platform lit = pprLit platform lit +pprLit1 :: CmmLit -> SDoc +pprLit1 lit@(CmmLabelOff {}) = parens (pprLit lit) +pprLit1 lit = pprLit lit ppr_offset :: Int -> SDoc ppr_offset i |