Skip to content
Snippets Groups Projects
Commit 1f5257c1 authored by sof's avatar sof
Browse files

[project @ 1997-06-05 20:58:42 by sof]

ppr update
parent 27be51d1
No related merge requests found
......@@ -29,6 +29,8 @@ One per \tr{import} declaration in a module.
data ImportDecl name
= ImportDecl Module -- module name
Bool -- True => qualified
Bool -- True => source imported module
-- (current interpretation: ignore ufolding info)
(Maybe Module) -- as Module
(Maybe (Bool, [IE name])) -- (True => hiding, names)
SrcLoc
......@@ -36,10 +38,14 @@ data ImportDecl name
\begin{code}
instance (NamedThing name, Outputable name) => Outputable (ImportDecl name) where
ppr sty (ImportDecl mod qual as spec _)
= hang (hsep [ptext SLIT("import"), pp_qual qual, ptext mod, pp_as as])
ppr sty (ImportDecl mod qual as_source as spec _)
= hang (hsep [ptext SLIT("import"), pp_src as_source,
pp_qual qual, ptext mod, pp_as as])
4 (pp_spec spec)
where
pp_src False = empty
pp_src True = ptext SLIT("{-# SOURCE #-}")
pp_qual False = empty
pp_qual True = ptext SLIT("qualified")
......
......@@ -103,7 +103,7 @@ pprMatches sty print_info@(is_case, name) [match]
= if is_case then
pprMatch sty is_case match
else
hang name 4 (pprMatch sty is_case match)
name <+> (pprMatch sty is_case match)
pprMatches sty print_info (match1 : rest)
= ($$) (pprMatches sty print_info [match1])
......@@ -115,8 +115,8 @@ pprMatch :: (NamedThing id, Outputable id, Outputable pat,
PprStyle -> Bool -> Match tyvar uvar id pat -> Doc
pprMatch sty is_case first_match
= hang (sep (map (ppr sty) row_of_pats))
8 grhss_etc_stuff
= sep [(sep (map (ppr sty) row_of_pats)),
grhss_etc_stuff]
where
(row_of_pats, grhss_etc_stuff) = ppr_match sty is_case first_match
......@@ -129,8 +129,7 @@ pprMatch sty is_case first_match
= ([], pprGRHSsAndBinds sty is_case grhss_n_binds)
ppr_match sty is_case (SimpleMatch expr)
= ([], hang (text (if is_case then "->" else "="))
4 (ppr sty expr))
= ([], text (if is_case then "->" else "=") <+> ppr sty expr)
----------------------------------------------------------
......@@ -158,14 +157,13 @@ pprGRHS :: (NamedThing id, Outputable id, Outputable pat,
=> PprStyle -> Bool -> GRHS tyvar uvar id pat -> Doc
pprGRHS sty is_case (GRHS [] expr locn)
= hang (text (if is_case then "->" else "="))
4 (ppr sty expr)
= text (if is_case then "->" else "=") <+> ppr sty expr
pprGRHS sty is_case (GRHS guard expr locn)
= hang (hsep [char '|', ppr sty guard, text (if is_case then "->" else "=")])
4 (ppr sty expr)
= sep [char '|' <+> ppr sty guard,
text (if is_case then "->" else "=") <+> ppr sty expr
]
pprGRHS sty is_case (OtherwiseGRHS expr locn)
= hang (text (if is_case then "->" else "="))
4 (ppr sty expr)
= text (if is_case then "->" else "=") <+> ppr sty expr
\end{code}
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment