7551596be0d9fe1b34fd99843370392d20897dcd
[ghc-hetmet.git] / ghc / compiler / basicTypes / BasicTypes.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1997-1998
3 %
4 \section[BasicTypes]{Miscellanous types}
5
6 This module defines a miscellaneously collection of very simple
7 types that
8
9 \begin{itemize}
10 \item have no other obvious home
11 \item don't depend on any other complicated types
12 \item are used in more than one "part" of the compiler
13 \end{itemize}
14
15 \begin{code}
16 module BasicTypes(
17         Version, bumpVersion, initialVersion, bogusVersion,
18
19         Arity, 
20
21         Unused, unused,
22
23         Fixity(..), FixityDirection(..),
24         defaultFixity, maxPrecedence, negateFixity, negatePrecedence,
25
26         NewOrData(..), 
27
28         RecFlag(..), isRec, isNonRec,
29
30         TopLevelFlag(..), isTopLevel, isNotTopLevel,
31
32         Boxity(..), isBoxed, tupleParens,
33
34         OccInfo(..), seqOccInfo, isFragileOcc, isDeadOcc, isLoopBreaker,
35
36         InsideLam, insideLam, notInsideLam,
37         OneBranch, oneBranch, notOneBranch,
38
39         EP(..),
40
41         GhciMode(..)
42    ) where
43
44 #include "HsVersions.h"
45
46 import Outputable
47 \end{code}
48
49 %************************************************************************
50 %*                                                                      *
51 \subsection[Unused]{Unused}
52 %*                                                                      *
53 %************************************************************************
54
55 Used as a placeholder in types.
56
57 \begin{code}
58 type Unused = ()
59
60 unused :: Unused
61 unused = error "Unused is used!"
62 \end{code}
63
64
65 %************************************************************************
66 %*                                                                      *
67 \subsection[Arity]{Arity}
68 %*                                                                      *
69 %************************************************************************
70
71 \begin{code}
72 type Arity = Int
73 \end{code}
74
75
76 %************************************************************************
77 %*                                                                      *
78 \subsection[Version]{Module and identifier version numbers}
79 %*                                                                      *
80 %************************************************************************
81
82 \begin{code}
83 type Version = Int
84
85 bogusVersion :: Version -- Shouldn't look at these
86 bogusVersion = error "bogusVersion"
87
88 bumpVersion :: Bool -> Version -> Version 
89 -- Bump if the predicate (typically equality between old and new) is false
90 bumpVersion False v = v+1
91 bumpVersion True  v = v
92
93 initialVersion :: Version
94 initialVersion = 1
95 \end{code}
96
97
98 %************************************************************************
99 %*                                                                      *
100 \subsection[Fixity]{Fixity info}
101 %*                                                                      *
102 %************************************************************************
103
104 \begin{code}
105 data Fixity = Fixity Int FixityDirection
106 data FixityDirection = InfixL | InfixR | InfixN 
107                      deriving(Eq)
108
109 instance Outputable Fixity where
110     ppr (Fixity prec dir) = hcat [ppr dir, space, int prec]
111
112 instance Outputable FixityDirection where
113     ppr InfixL = ptext SLIT("infixl")
114     ppr InfixR = ptext SLIT("infixr")
115     ppr InfixN = ptext SLIT("infix")
116
117 instance Eq Fixity where                -- Used to determine if two fixities conflict
118   (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2
119
120 maxPrecedence = (9::Int)
121 defaultFixity = Fixity maxPrecedence InfixL
122
123 negateFixity :: Fixity
124 negateFixity     = Fixity negatePrecedence InfixL       -- Precedence of unary negate is wired in as infixl 6!
125
126 negatePrecedence :: Int
127 negatePrecedence = 6
128 \end{code}
129
130
131 %************************************************************************
132 %*                                                                      *
133 \subsection[NewType/DataType]{NewType/DataType flag}
134 %*                                                                      *
135 %************************************************************************
136
137 \begin{code}
138 data NewOrData
139   = NewType     -- "newtype Blah ..."
140   | DataType    -- "data Blah ..."
141   deriving( Eq )        -- Needed because Demand derives Eq
142 \end{code}
143
144 %************************************************************************
145 %*                                                                      *
146 \subsection[Top-level/local]{Top-level/not-top level flag}
147 %*                                                                      *
148 %************************************************************************
149
150 \begin{code}
151 data TopLevelFlag
152   = TopLevel
153   | NotTopLevel
154
155 isTopLevel, isNotTopLevel :: TopLevelFlag -> Bool
156
157 isNotTopLevel NotTopLevel = True
158 isNotTopLevel TopLevel    = False
159
160 isTopLevel TopLevel     = True
161 isTopLevel NotTopLevel  = False
162 \end{code}
163
164 %************************************************************************
165 %*                                                                      *
166 \subsection[Top-level/local]{Top-level/not-top level flag}
167 %*                                                                      *
168 %************************************************************************
169
170 \begin{code}
171 data Boxity
172   = Boxed
173   | Unboxed
174   deriving( Eq )
175
176 isBoxed :: Boxity -> Bool
177 isBoxed Boxed   = True
178 isBoxed Unboxed = False
179
180 tupleParens :: Boxity -> SDoc -> SDoc
181 tupleParens Boxed   p = parens p
182 tupleParens Unboxed p = ptext SLIT("(#") <+> p <+> ptext SLIT("#)")
183 \end{code}
184
185
186 %************************************************************************
187 %*                                                                      *
188 \subsection[Recursive/Non-Recursive]{Recursive/Non-Recursive flag}
189 %*                                                                      *
190 %************************************************************************
191
192 \begin{code} 
193 data RecFlag = Recursive 
194              | NonRecursive
195
196 isRec :: RecFlag -> Bool
197 isRec Recursive    = True
198 isRec NonRecursive = False
199
200 isNonRec :: RecFlag -> Bool
201 isNonRec Recursive    = False
202 isNonRec NonRecursive = True
203 \end{code}
204
205 %************************************************************************
206 %*                                                                      *
207 \subsection[Interactive/Batch]{Interactive/Batch flag}
208 %*                                                                      *
209 %************************************************************************
210
211 \begin{code} 
212 data GhciMode = Batch
213               | Interactive
214 \end{code}
215
216 %************************************************************************
217 %*                                                                      *
218 \subsection[Generic]{Generic flag}
219 %*                                                                      *
220 %************************************************************************
221
222 This is the "Embedding-Projection pair" datatype, it contains 
223 two pieces of code (normally either RenamedHsExpr's or Id's)
224 If we have a such a pair (EP from to), the idea is that 'from' and 'to'
225 represents functions of type 
226
227         from :: T -> Tring
228         to   :: Tring -> T
229
230 And we should have 
231
232         to (from x) = x
233
234 T and Tring are arbitrary, but typically T is the 'main' type while
235 Tring is the 'representation' type.  (This just helps us remember 
236 whether to use 'from' or 'to'.
237
238 \begin{code}
239 data EP a = EP { fromEP :: a,   -- :: T -> Tring
240                  toEP   :: a }  -- :: Tring -> T
241 \end{code}
242
243 Embedding-projection pairs are used in several places:
244
245 First of all, each type constructor has an EP associated with it, the
246 code in EP converts (datatype T) from T to Tring and back again.
247
248 Secondly, when we are filling in Generic methods (in the typechecker, 
249 tcMethodBinds), we are constructing bimaps by induction on the structure
250 of the type of the method signature.
251
252
253 %************************************************************************
254 %*                                                                      *
255 \subsection{Occurrence information}
256 %*                                                                      *
257 %************************************************************************
258
259 This data type is used exclusively by the simplifier, but it appears in a
260 SubstResult, which is currently defined in VarEnv, which is pretty near
261 the base of the module hierarchy.  So it seemed simpler to put the
262 defn of OccInfo here, safely at the bottom
263
264 \begin{code}
265 data OccInfo 
266   = NoOccInfo
267
268   | IAmDead             -- Marks unused variables.  Sometimes useful for
269                         -- lambda and case-bound variables.
270
271   | OneOcc InsideLam
272
273            OneBranch
274
275   | IAmALoopBreaker     -- Used by the occurrence analyser to mark loop-breakers
276                         -- in a group of recursive definitions
277
278 seqOccInfo :: OccInfo -> ()
279 seqOccInfo (OneOcc in_lam once) = in_lam `seq` once `seq` ()
280 seqOccInfo occ                  = ()
281
282 type InsideLam = Bool   -- True <=> Occurs inside a non-linear lambda
283                         -- Substituting a redex for this occurrence is
284                         -- dangerous because it might duplicate work.
285 insideLam    = True
286 notInsideLam = False
287
288 type OneBranch = Bool   -- True <=> Occurs in only one case branch
289                         --      so no code-duplication issue to worry about
290 oneBranch    = True
291 notOneBranch = False
292
293 isLoopBreaker :: OccInfo -> Bool
294 isLoopBreaker IAmALoopBreaker = True
295 isLoopBreaker other           = False
296
297 isDeadOcc :: OccInfo -> Bool
298 isDeadOcc IAmDead = True
299 isDeadOcc other   = False
300
301 isFragileOcc :: OccInfo -> Bool
302 isFragileOcc (OneOcc _ _) = True
303 isFragileOcc other            = False
304 \end{code}
305
306 \begin{code}
307 instance Outputable OccInfo where
308   -- only used for debugging; never parsed.  KSW 1999-07
309   ppr NoOccInfo                                   = empty
310   ppr IAmALoopBreaker                             = ptext SLIT("_Kx")
311   ppr IAmDead                                     = ptext SLIT("_Kd")
312   ppr (OneOcc inside_lam one_branch) | inside_lam = ptext SLIT("_Kl")
313                                      | one_branch = ptext SLIT("_Ks")
314                                      | otherwise  = ptext SLIT("_Ks*")
315
316 instance Show OccInfo where
317   showsPrec p occ = showsPrecSDoc p (ppr occ)
318 \end{code}
319