summaryrefslogtreecommitdiff
path: root/ghc/compiler/utils/Outputable.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>2002-09-13 15:02:50 +0000
committersimonpj <unknown>2002-09-13 15:02:50 +0000
commit9af77fa423926fbda946b31e174173d0ec5ebac8 (patch)
tree140cc94aa3e04f6e50c4bf07ceb0efe67d11b9c6 /ghc/compiler/utils/Outputable.lhs
parent69e55e7476392a2b59b243a32065350c258d4970 (diff)
downloadhaskell-9af77fa423926fbda946b31e174173d0ec5ebac8.tar.gz
[project @ 2002-09-13 15:02:25 by simonpj]
-------------------------------------- Make Template Haskell into the HEAD -------------------------------------- This massive commit transfers to the HEAD all the stuff that Simon and Tim have been doing on Template Haskell. The meta-haskell-branch is no more! WARNING: make sure that you * Update your links if you are using link trees. Some modules have been added, some have gone away. * Do 'make clean' in all library trees. The interface file format has changed, and you can get strange panics (sadly) if GHC tries to read old interface files: e.g. ghc-5.05: panic! (the `impossible' happened, GHC version 5.05): Binary.get(TyClDecl): ForeignType * You need to recompile the rts too; Linker.c has changed However the libraries are almost unaltered; just a tiny change in Base, and to the exports in Prelude. NOTE: so far as TH itself is concerned, expression splices work fine, but declaration splices are not complete. --------------- The main change --------------- The main structural change: renaming and typechecking have to be interleaved, because we can't rename stuff after a declaration splice until after we've typechecked the stuff before (and the splice itself). * Combine the renamer and typecheker monads into one (TcRnMonad, TcRnTypes) These two replace TcMonad and RnMonad * Give them a single 'driver' (TcRnDriver). This driver replaces TcModule.lhs and Rename.lhs * The haskell-src library package has a module Language/Haskell/THSyntax which defines the Haskell data type seen by the TH programmer. * New modules: hsSyn/Convert.hs converts THSyntax -> HsSyn deSugar/DsMeta.hs converts HsSyn -> THSyntax * New module typecheck/TcSplice type-checks Template Haskell splices. ------------- Linking stuff ------------- * ByteCodeLink has been split into ByteCodeLink (which links) ByteCodeAsm (which assembles) * New module ghci/ObjLink is the object-code linker. * compMan/CmLink is removed entirely (was out of place) Ditto CmTypes (which was tiny) * Linker.c initialises the linker when it is first used (no need to call initLinker any more). Template Haskell makes it harder to know when and whether to initialise the linker. ------------------------------------- Gathering the LIE in the type checker ------------------------------------- * Instead of explicitly gathering constraints in the LIE tcExpr :: RenamedExpr -> TcM (TypecheckedExpr, LIE) we now dump the constraints into a mutable varabiable carried by the monad, so we get tcExpr :: RenamedExpr -> TcM TypecheckedExpr Much less clutter in the code, and more efficient too. (Originally suggested by Mark Shields.) ----------------- Remove "SysNames" ----------------- Because the renamer and the type checker were entirely separate, we had to carry some rather tiresome implicit binders (or "SysNames") along inside some of the HsDecl data structures. They were both tiresome and fragile. Now that the typechecker and renamer are more intimately coupled, we can eliminate SysNames (well, mostly... default methods still carry something similar). ------------- Clean up HsPat ------------- One big clean up is this: instead of having two HsPat types (InPat and OutPat), they are now combined into one. This is more consistent with the way that HsExpr etc is handled; there are some 'Out' constructors for the type checker output. So: HsPat.InPat --> HsPat.Pat HsPat.OutPat --> HsPat.Pat No 'pat' type parameter in HsExpr, HsBinds, etc Constructor patterns are nicer now: they use HsPat.HsConDetails for the three cases of constructor patterns: prefix, infix, and record-bindings The *same* data type HsConDetails is used in the type declaration of the data type (HsDecls.TyData) Lots of associated clean-up operations here and there. Less code. Everything is wonderful.
Diffstat (limited to 'ghc/compiler/utils/Outputable.lhs')
-rw-r--r--ghc/compiler/utils/Outputable.lhs60
1 files changed, 52 insertions, 8 deletions
diff --git a/ghc/compiler/utils/Outputable.lhs b/ghc/compiler/utils/Outputable.lhs
index c837eb0321..782a679c91 100644
--- a/ghc/compiler/utils/Outputable.lhs
+++ b/ghc/compiler/utils/Outputable.lhs
@@ -9,12 +9,15 @@ Defines classes for pretty-printing and forcing, both forms of
\begin{code}
module Outputable (
- Outputable(..), -- Class
+ Outputable(..), OutputableBndr(..), -- Class
+
+ BindingSite(..),
PprStyle, CodeStyle(..), PrintUnqualified, alwaysQualify,
getPprStyle, withPprStyle, withPprStyleDoc, pprDeeper,
codeStyle, userStyle, debugStyle, asmStyle,
- ifPprDebug, unqualStyle,
+ ifPprDebug, unqualStyle,
+ mkErrStyle, defaultErrStyle,
SDoc, -- Abstract
docToSDoc,
@@ -102,6 +105,18 @@ neverQualify n = True
defaultUserStyle = mkUserStyle alwaysQualify AllTheWay
+mkErrStyle :: PrintUnqualified -> PprStyle
+-- Style for printing error messages
+mkErrStyle print_unqual = mkUserStyle print_unqual (PartWay opt_PprUserLength)
+
+defaultErrStyle :: PprStyle
+-- Default style for error messages
+-- It's a bit of a hack because it doesn't take into account what's in scope
+-- Only used for desugarer warnings, and typechecker errors in interface sigs
+defaultErrStyle
+ | opt_PprStyle_Debug = mkUserStyle alwaysQualify AllTheWay
+ | otherwise = mkUserStyle neverQualify (PartWay opt_PprUserLength)
+
mkUserStyle unqual depth | opt_PprStyle_Debug = PprDebug
| otherwise = PprUser unqual depth
\end{code}
@@ -174,12 +189,9 @@ printSDoc d sty = do
-- I'm not sure whether the direct-IO approach of Pretty.printDoc
-- above is better or worse than the put-big-string approach here
-printErrs :: PrintUnqualified -> SDoc -> IO ()
-printErrs unqual doc = do
- Pretty.printDoc PageMode stderr (doc style)
- hFlush stderr
- where
- style = mkUserStyle unqual (PartWay opt_PprUserLength)
+printErrs :: Doc -> IO ()
+printErrs doc = do Pretty.printDoc PageMode stderr doc
+ hFlush stderr
printDump :: SDoc -> IO ()
printDump doc = do
@@ -348,7 +360,39 @@ instance (Outputable a, Outputable b, Outputable c, Outputable d) =>
instance Outputable FastString where
ppr fs = text (unpackFS fs) -- Prints an unadorned string,
-- no double quotes or anything
+\end{code}
+
+
+%************************************************************************
+%* *
+\subsection{The @OutputableBndr@ class}
+%* *
+%************************************************************************
+
+When we print a binder, we often want to print its type too.
+The @OutputableBndr@ class encapsulates this idea.
+
+@BindingSite@ is used to tell the thing that prints binder what
+language construct is binding the identifier. This can be used
+to decide how much info to print.
+\begin{code}
+data BindingSite = LambdaBind | CaseBind | LetBind
+
+class Outputable a => OutputableBndr a where
+ pprBndr :: BindingSite -> a -> SDoc
+ pprBndr b x = ppr x
+\end{code}
+
+
+
+%************************************************************************
+%* *
+\subsection{Random printing helpers}
+%* *
+%************************************************************************
+
+\begin{code}
#if __GLASGOW_HASKELL__ < 410
-- Assume we have only 8-bit Chars.