[project @ 1997-03-14 07:52:06 by simonpj]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsCore.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1996
3 %
4 %************************************************************************
5 %*                                                                      *
6 \section[HsCore]{Core-syntax unfoldings in Haskell interface files}
7 %*                                                                      *
8 %************************************************************************
9
10 We could either use this, or parameterise @GenCoreExpr@ on @Types@ and
11 @TyVars@ as well.  Currently trying the former... MEGA SIGH.
12
13 \begin{code}
14 #include "HsVersions.h"
15
16 module HsCore (
17         UfExpr(..), UfAlts(..), UfBinder(..), UfCoercion(..),
18         UfDefault(..), UfBinding(..),
19         UfArg(..), UfPrimOp(..)
20     ) where
21
22 IMP_Ubiq()
23
24 -- friends:
25 import HsTypes          ( HsType, pprParendHsType )
26 import PrimOp           ( PrimOp, tagOf_PrimOp )
27 import Kind             ( Kind {- instance Outputable -} )
28 import Type             ( GenType {- instance Outputable -} )
29
30 -- others:
31 import Literal          ( Literal )
32 import Outputable       ( Outputable(..) )
33 import Pretty
34 import Util             ( panic )
35 \end{code}
36
37 %************************************************************************
38 %*                                                                      *
39 \subsection[HsCore-types]{Types for read/written Core unfoldings}
40 %*                                                                      *
41 %************************************************************************
42
43 \begin{code}
44 data UfExpr name
45   = UfVar       name
46   | UfLit       Literal
47   | UfCon       name [UfArg name]
48   | UfPrim      (UfPrimOp name) [UfArg name]
49   | UfLam       (UfBinder name)   (UfExpr name)
50   | UfApp       (UfExpr name) (UfArg name)
51   | UfCase      (UfExpr name) (UfAlts name)
52   | UfLet       (UfBinding name)  (UfExpr name)
53   | UfSCC       CostCentre (UfExpr name)
54   | UfCoerce    (UfCoercion name) (HsType name) (UfExpr name)
55
56 data UfPrimOp name
57   = UfCCallOp   FAST_STRING          -- callee
58                 Bool                 -- True <=> casm, rather than ccall
59                 Bool                 -- True <=> might cause GC
60                 [HsType name] -- arg types, incl state token
61                                      -- (which will be first)
62                 (HsType name) -- return type
63
64   | UfOtherOp   name
65
66 data UfCoercion name = UfIn name | UfOut name
67
68 data UfAlts name
69   = UfAlgAlts  [(name, [name], UfExpr name)]
70                 (UfDefault name)
71   | UfPrimAlts [(Literal, UfExpr name)]
72                 (UfDefault name)
73
74 data UfDefault name
75   = UfNoDefault
76   | UfBindDefault name (UfExpr name)
77
78 data UfBinding name
79   = UfNonRec    (UfBinder name)
80                 (UfExpr name)
81   | UfRec       [(UfBinder name, UfExpr name)]
82
83 data UfBinder name
84   = UfValBinder name (HsType name)
85   | UfTyBinder  name Kind
86   | UfUsageBinder name
87
88 data UfArg name
89   = UfVarArg    name
90   | UfLitArg    Literal
91   | UfTyArg     (HsType name)
92   | UfUsageArg  name
93 \end{code}
94
95 %************************************************************************
96 %*                                                                      *
97 \subsection[HsCore-print]{Printing Core unfoldings}
98 %*                                                                      *
99 %************************************************************************
100
101 \begin{code}
102 instance Outputable name => Outputable (UfExpr name) where
103     ppr sty (UfVar v) = ppr sty v
104     ppr sty (UfLit l) = ppr sty l
105
106     ppr sty (UfCon c as)
107       = ppCat [ppStr "UfCon", ppr sty c, ppr sty as, ppChar ')']
108     ppr sty (UfPrim o as)
109       = ppCat [ppStr "UfPrim", ppr sty o, ppr sty as, ppChar ')']
110
111     ppr sty (UfLam b body)
112       = ppCat [ppChar '\\', ppr sty b, ppPStr SLIT("->"), ppr sty body]
113
114     ppr sty (UfApp fun (UfTyArg ty))
115       = ppCat [ppr sty fun, ppChar '@', pprParendHsType sty ty]
116
117     ppr sty (UfApp fun (UfLitArg lit))
118       = ppCat [ppr sty fun, ppr sty lit]
119
120     ppr sty (UfApp fun (UfVarArg var))
121       = ppCat [ppr sty fun, ppr sty var]
122
123     ppr sty (UfCase scrut alts)
124       = ppCat [ppPStr SLIT("case"), ppr sty scrut, ppPStr SLIT("of {"), pp_alts alts, ppChar '}']
125       where
126         pp_alts (UfAlgAlts alts deflt)
127           = ppCat [ppInterleave ppSemi (map pp_alt alts), pp_deflt deflt]
128           where
129            pp_alt (c,bs,rhs) = ppCat [ppr sty c, ppr sty bs, ppr_arrow, ppr sty rhs]
130         pp_alts (UfPrimAlts alts deflt)
131           = ppCat [ppInterleave ppSemi (map pp_alt alts), pp_deflt deflt]
132           where
133            pp_alt (l,rhs) = ppCat [ppr sty l, ppr_arrow, ppr sty rhs]
134
135         pp_deflt UfNoDefault = ppNil
136         pp_deflt (UfBindDefault b rhs) = ppCat [ppr sty b, ppr_arrow, ppr sty rhs]
137
138         ppr_arrow = ppPStr SLIT("->")
139
140     ppr sty (UfLet (UfNonRec b rhs) body)
141       = ppCat [ppPStr SLIT("let"), ppr sty b, ppEquals, ppr sty rhs, ppPStr SLIT("in"), ppr sty body]
142     ppr sty (UfLet (UfRec pairs) body)
143       = ppCat [ppPStr SLIT("letrec {"), ppInterleave ppSemi (map pp_pair pairs), ppPStr SLIT("} in"), ppr sty body]
144       where
145         pp_pair (b,rhs) = ppCat [ppr sty b, ppEquals, ppr sty rhs]
146
147     ppr sty (UfSCC uf_cc body)
148       = ppCat [ppPStr SLIT("_scc_ <cost-centre[ToDo]>"), ppr sty body]
149
150 instance Outputable name => Outputable (UfPrimOp name) where
151     ppr sty (UfCCallOp str is_casm can_gc arg_tys result_ty)
152       = let
153             before = ppPStr (if is_casm then SLIT("_casm_ ``") else SLIT("_ccall_ "))
154             after  = if is_casm then ppStr "'' " else ppSP
155         in
156         ppBesides [before, ppPStr str, after,
157                    ppLbrack, ppr sty arg_tys, ppRbrack, ppSP, ppr sty result_ty]
158
159     ppr sty (UfOtherOp op)
160       = ppr sty op
161
162 instance Outputable name => Outputable (UfArg name) where
163     ppr sty (UfVarArg v)        = ppr sty v
164     ppr sty (UfLitArg l)        = ppr sty l
165     ppr sty (UfTyArg ty)        = pprParendHsType sty ty
166     ppr sty (UfUsageArg name)   = ppr sty name
167
168 instance Outputable name => Outputable (UfBinder name) where
169     ppr sty (UfValBinder name ty)  = ppCat [ppr sty name, ppPStr SLIT("::"), ppr sty ty]
170     ppr sty (UfTyBinder name kind) = ppCat [ppr sty name, ppPStr SLIT("::"), ppr sty kind]
171     ppr sty (UfUsageBinder name)   = ppr sty name
172 \end{code}
173