summaryrefslogtreecommitdiff
path: root/ghc/compiler/basicTypes/PprEnv.lhs
blob: ed06d2ce15358fee8e1f36396c9de639e4376ccb (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
%
% (c) The AQUA Project, Glasgow University, 1996-1998
%
\section[PprEnv]{The @PprEnv@ type}

\begin{code}
module PprEnv (
	PprEnv,		-- 
	BindingSite(..),

	initPprEnv,

	pCon, pBndr, pOcc, pSCC, 
	pTy, pTyVarO
    ) where

#include "HsVersions.h"

import {-# SOURCE #-} Const ( Con )

import Var		( Id, TyVar )
import CostCentre	( CostCentre )
import Type  		( Type )
import Outputable
\end{code}

%************************************************************************
%*									*
\subsection{Public interfaces for Core printing (excluding instances)}
%*									*
%************************************************************************

\begin{code}
data PprEnv bndr
  = PE	{
	pCon :: Con        -> SDoc,
	pSCC :: CostCentre -> SDoc,

	pTyVarO :: TyVar -> SDoc,	-- to print tyvar occurrences
	pTy     :: Type -> SDoc,	-- to print types

	pBndr :: BindingSite -> bndr -> SDoc,	-- to print value binders
	pOcc  :: Id -> SDoc		-- to print value occurrences
   }
\end{code}

@BindingSite@ is used to tell the thing that prints binder what
language construct is binding the identifier.

\begin{code}
data BindingSite = LambdaBind | CaseBind | LetBind
\end{code}

\begin{code}
initPprEnv
	:: Maybe (Con -> SDoc)
	-> Maybe (CostCentre -> SDoc)
	-> Maybe (TyVar -> SDoc)
	-> Maybe (Type -> SDoc)
	-> Maybe (BindingSite -> bndr -> SDoc)
	-> Maybe (Id -> SDoc)
	-> PprEnv bndr

-- you can specify all the printers individually; if
-- you don't specify one, you get bottom

initPprEnv p c tvo ty bndr occ
  = PE (demaybe p)
       (demaybe c)
       (demaybe tvo)
       (demaybe ty)
       (demaybe bndr)
       (demaybe occ)
  where
    demaybe Nothing  = bottom
    demaybe (Just x) = x

    bottom = panic "PprEnv.initPprEnv: unspecified printing function"
\end{code}