diff options
author | sof <unknown> | 1997-05-26 04:39:45 +0000 |
---|---|---|
committer | sof <unknown> | 1997-05-26 04:39:45 +0000 |
commit | 6be2543be79ab2a51fd646899de39e9e6ea731ac (patch) | |
tree | a0c31a119066354e7847d2a830e80929baa9935a /ghc/compiler/hsSyn/HsExpr.lhs | |
parent | e8e9742681b0ef189f4c18ec36cd47be26327755 (diff) | |
download | haskell-6be2543be79ab2a51fd646899de39e9e6ea731ac.tar.gz |
[project @ 1997-05-26 04:39:45 by sof]
Updated imports;improved ppr
Diffstat (limited to 'ghc/compiler/hsSyn/HsExpr.lhs')
-rw-r--r-- | ghc/compiler/hsSyn/HsExpr.lhs | 16 |
1 files changed, 10 insertions, 6 deletions
diff --git a/ghc/compiler/hsSyn/HsExpr.lhs b/ghc/compiler/hsSyn/HsExpr.lhs index db8e1304fa..e72c1fdb9f 100644 --- a/ghc/compiler/hsSyn/HsExpr.lhs +++ b/ghc/compiler/hsSyn/HsExpr.lhs @@ -9,20 +9,20 @@ module HsExpr where IMP_Ubiq(){-uitous-} -IMPORT_DELOOPER(HsLoop) -- for paranoia checking -- friends: +IMPORT_DELOOPER(HsLoop) ( pprMatches, pprMatch, Match ) import HsBinds ( HsBinds ) -import HsBasic ( HsLit, Fixity(..), FixityDirection(..) ) -import HsMatches ( pprMatches, pprMatch, Match ) +import HsBasic ( HsLit ) +import BasicTypes ( Fixity(..), FixityDirection(..) ) import HsTypes ( HsType ) -- others: import Id ( SYN_IE(DictVar), GenId, SYN_IE(Id) ) -import Outputable --( interppSP, interpp'SP, ifnotPprForUser ) +import Outputable ( pprQuote, interppSP, interpp'SP, ifnotPprForUser, + PprStyle(..), userStyle, Outputable(..) ) import PprType ( pprGenType, pprParendGenType, GenType{-instance-} ) import Pretty -import PprStyle ( PprStyle(..), userStyle ) import SrcLoc ( SrcLoc ) import Usage ( GenUsage{-instance-} ) --import Util ( panic{-ToDo:rm eventually-} ) @@ -199,6 +199,10 @@ instance (NamedThing id, Outputable id, Outputable pat, \end{code} \begin{code} +pprExpr :: (NamedThing id, Outputable id, Outputable pat, + Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar) + => PprStyle -> HsExpr tyvar uvar id pat -> Doc + pprExpr sty (HsVar v) = ppr sty v pprExpr sty (HsLit lit) = ppr sty lit @@ -209,7 +213,7 @@ pprExpr sty (HsLam match) pprExpr sty expr@(HsApp e1 e2) = let (fun, args) = collect_args expr [] in - hang (pprExpr sty fun) 4 (sep (map (pprExpr sty) args)) + (pprExpr sty fun) <+> (sep (map (pprExpr sty) args)) where collect_args (HsApp fun arg) args = collect_args fun (arg:args) collect_args fun args = (fun, args) |