summaryrefslogtreecommitdiff
path: root/ghc/compiler/codeGen/CgMonad.lhs
diff options
context:
space:
mode:
authorsof <unknown>1997-05-19 00:21:27 +0000
committersof <unknown>1997-05-19 00:21:27 +0000
commitdcef38bab91d45b56f7cf3ceeec96303d93728bb (patch)
treeef5cc7ac9b590d502c03f6906de2e66df01f8d34 /ghc/compiler/codeGen/CgMonad.lhs
parentf1815aa4bb218b92bc699d1355b6a704ee3e89ee (diff)
downloadhaskell-dcef38bab91d45b56f7cf3ceeec96303d93728bb.tar.gz
[project @ 1997-05-19 00:12:10 by sof]
2.04 changes
Diffstat (limited to 'ghc/compiler/codeGen/CgMonad.lhs')
-rw-r--r--ghc/compiler/codeGen/CgMonad.lhs26
1 files changed, 16 insertions, 10 deletions
diff --git a/ghc/compiler/codeGen/CgMonad.lhs b/ghc/compiler/codeGen/CgMonad.lhs
index 18902fc84b..c7e18cdfe8 100644
--- a/ghc/compiler/codeGen/CgMonad.lhs
+++ b/ghc/compiler/codeGen/CgMonad.lhs
@@ -57,22 +57,28 @@ import CmdLineOpts ( opt_SccProfilingOn, opt_DoTickyProfiling,
opt_OmitBlackHoling
)
import HeapOffs ( maxOff,
- SYN_IE(VirtualSpAOffset), SYN_IE(VirtualSpBOffset)
+ SYN_IE(VirtualSpAOffset), SYN_IE(VirtualSpBOffset),
+ HeapOffset
)
+import CLabel ( CLabel )
import Id ( idType,
nullIdEnv, mkIdEnv, addOneToIdEnv,
modifyIdEnv, lookupIdEnv, rngIdEnv, SYN_IE(IdEnv),
- SYN_IE(ConTag), GenId{-instance Outputable-}
+ SYN_IE(ConTag), GenId{-instance Outputable-},
+ SYN_IE(Id)
)
import Maybes ( maybeToBool )
import PprStyle ( PprStyle(..) )
import PprType ( GenType{-instance Outputable-} )
-import Pretty ( ppAboves, ppCat, ppPStr )
+import Pretty ( Doc, vcat, hsep, ptext )
import PrimRep ( getPrimRepSize, PrimRep(..) )
import StgSyn ( SYN_IE(StgLiveVars) )
import Type ( typePrimRep )
import UniqSet ( elementOfUniqSet )
import Util ( sortLt, panic, pprPanic )
+#if __GLASGOW_HASKELL__ >= 202
+import Outputable ( Outputable(..) )
+#endif
infixr 9 `thenC` -- Right-associative!
infixr 9 `thenFC`
@@ -688,13 +694,13 @@ lookupBindC name info_down@(MkCgInfoDown _ static_binds _)
Just this -> this
Nothing
-> pprPanic "lookupBindC:no info!\n"
- (ppAboves [
- ppCat [ppPStr SLIT("for:"), ppr PprShowAll name],
- ppPStr SLIT("(probably: data dependencies broken by an optimisation pass)"),
- ppPStr SLIT("static binds for:"),
- ppAboves [ ppr PprDebug i | (MkCgIdInfo i _ _ _) <- rngIdEnv static_binds ],
- ppPStr SLIT("local binds for:"),
- ppAboves [ ppr PprDebug i | (MkCgIdInfo i _ _ _) <- rngIdEnv local_binds ]
+ (vcat [
+ hsep [ptext SLIT("for:"), ppr PprShowAll name],
+ ptext SLIT("(probably: data dependencies broken by an optimisation pass)"),
+ ptext SLIT("static binds for:"),
+ vcat [ ppr PprDebug i | (MkCgIdInfo i _ _ _) <- rngIdEnv static_binds ],
+ ptext SLIT("local binds for:"),
+ vcat [ ppr PprDebug i | (MkCgIdInfo i _ _ _) <- rngIdEnv local_binds ]
])
\end{code}