Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
What's new
10
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Open sidebar
jberryman
GHC
Commits
5045cfbc
Commit
5045cfbc
authored
Jun 20, 2012
by
Ian Lynagh
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Remove some redundant Platform arguments
parent
158c3530
Changes
2
Hide whitespace changes
Inline
Side-by-side
Showing
2 changed files
with
16 additions
and
17 deletions
+16
-17
compiler/cmm/PprCmmDecl.hs
compiler/cmm/PprCmmDecl.hs
+4
-4
compiler/cmm/PprCmmExpr.hs
compiler/cmm/PprCmmExpr.hs
+12
-13
No files found.
compiler/cmm/PprCmmDecl.hs
View file @
5045cfbc
...
...
@@ -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'
)
...
...
compiler/cmm/PprCmmExpr.hs
View file @
5045cfbc
...
...
@@ -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
->
ppr
CLabel
platform
clbl
CmmLabelOff
clbl
i
->
ppr
CLabel
platform
clbl
<>
ppr_offset
i
CmmLabelDiffOff
clbl1
clbl2
i
->
ppr
CLabel
platform
clbl1
<>
char
'-'
<>
ppr
CLabel
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
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment