[project @ 2002-03-18 09:44:46 by simonmar]
[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         IPName(..), ipNameName, mapIPName,
27
28         NewOrData(..), 
29
30         RecFlag(..), isRec, isNonRec,
31
32         TopLevelFlag(..), isTopLevel, isNotTopLevel,
33
34         Boxity(..), isBoxed, tupleParens,
35
36         OccInfo(..), seqOccInfo, isFragileOcc, isOneOcc, 
37         isDeadOcc, isLoopBreaker,
38
39         InsideLam, insideLam, notInsideLam,
40         OneBranch, oneBranch, notOneBranch,
41
42         EP(..),
43
44         StrictnessMark(..), isMarkedUnboxed, isMarkedStrict,
45
46         CompilerPhase, 
47         Activation(..), isActive, isNeverActive, isAlwaysActive
48    ) where
49
50 #include "HsVersions.h"
51
52 import Outputable
53 \end{code}
54
55 %************************************************************************
56 %*                                                                      *
57 \subsection[Unused]{Unused}
58 %*                                                                      *
59 %************************************************************************
60
61 Used as a placeholder in types.
62
63 \begin{code}
64 type Unused = ()
65
66 unused :: Unused
67 unused = error "Unused is used!"
68 \end{code}
69
70
71 %************************************************************************
72 %*                                                                      *
73 \subsection[Arity]{Arity}
74 %*                                                                      *
75 %************************************************************************
76
77 \begin{code}
78 type Arity = Int
79 \end{code}
80
81
82 %************************************************************************
83 %*                                                                      *
84 \subsection[Version]{Module and identifier version numbers}
85 %*                                                                      *
86 %************************************************************************
87
88 \begin{code}
89 type Version = Int
90
91 bogusVersion :: Version -- Shouldn't look at these
92 bogusVersion = error "bogusVersion"
93
94 bumpVersion :: Bool -> Version -> Version 
95 -- Bump if the predicate (typically equality between old and new) is false
96 bumpVersion False v = v+1
97 bumpVersion True  v = v
98
99 initialVersion :: Version
100 initialVersion = 1
101 \end{code}
102
103
104 %************************************************************************
105 %*                                                                      *
106 \subsection{Implicit parameter identity}
107 %*                                                                      *
108 %************************************************************************
109
110 The @IPName@ type is here because it is used in TypeRep (i.e. very
111 early in the hierarchy), but also in HsSyn.
112
113 \begin{code}
114 data IPName name
115   = Dupable   name      -- ?x: you can freely duplicate this implicit parameter
116   | Linear name         -- %x: you must use the splitting function to duplicate it
117   deriving( Eq, Ord )   -- Ord is used in the IP name cache finite map
118                         --      (used in HscTypes.OrigIParamCache)
119
120
121 ipNameName :: IPName name -> name
122 ipNameName (Dupable n) = n
123 ipNameName (Linear  n) = n
124
125 mapIPName :: (a->b) -> IPName a -> IPName b
126 mapIPName f (Dupable n) = Dupable (f n)
127 mapIPName f (Linear  n) = Linear  (f n)
128 \end{code}
129
130                 
131 %************************************************************************
132 %*                                                                      *
133 \subsection[Fixity]{Fixity info}
134 %*                                                                      *
135 %************************************************************************
136
137 \begin{code}
138 data Fixity = Fixity Int FixityDirection
139 data FixityDirection = InfixL | InfixR | InfixN 
140                      deriving(Eq)
141
142 instance Outputable Fixity where
143     ppr (Fixity prec dir) = hcat [ppr dir, space, int prec]
144
145 instance Outputable FixityDirection where
146     ppr InfixL = ptext SLIT("infixl")
147     ppr InfixR = ptext SLIT("infixr")
148     ppr InfixN = ptext SLIT("infix")
149
150 instance Eq Fixity where                -- Used to determine if two fixities conflict
151   (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2
152
153 maxPrecedence = (9::Int)
154 defaultFixity = Fixity maxPrecedence InfixL
155
156 negateFixity :: Fixity
157 negateFixity     = Fixity negatePrecedence InfixL       -- Precedence of unary negate is wired in as infixl 6!
158
159 negatePrecedence :: Int
160 negatePrecedence = 6
161 \end{code}
162
163
164 %************************************************************************
165 %*                                                                      *
166 \subsection[NewType/DataType]{NewType/DataType flag}
167 %*                                                                      *
168 %************************************************************************
169
170 \begin{code}
171 data NewOrData
172   = NewType     -- "newtype Blah ..."
173   | DataType    -- "data Blah ..."
174   deriving( Eq )        -- Needed because Demand derives Eq
175 \end{code}
176
177
178 %************************************************************************
179 %*                                                                      *
180 \subsection[Top-level/local]{Top-level/not-top level flag}
181 %*                                                                      *
182 %************************************************************************
183
184 \begin{code}
185 data TopLevelFlag
186   = TopLevel
187   | NotTopLevel
188
189 isTopLevel, isNotTopLevel :: TopLevelFlag -> Bool
190
191 isNotTopLevel NotTopLevel = True
192 isNotTopLevel TopLevel    = False
193
194 isTopLevel TopLevel     = True
195 isTopLevel NotTopLevel  = False
196 \end{code}
197
198 %************************************************************************
199 %*                                                                      *
200 \subsection[Top-level/local]{Top-level/not-top level flag}
201 %*                                                                      *
202 %************************************************************************
203
204 \begin{code}
205 data Boxity
206   = Boxed
207   | Unboxed
208   deriving( Eq )
209
210 isBoxed :: Boxity -> Bool
211 isBoxed Boxed   = True
212 isBoxed Unboxed = False
213
214 tupleParens :: Boxity -> SDoc -> SDoc
215 tupleParens Boxed   p = parens p
216 tupleParens Unboxed p = ptext SLIT("(#") <+> p <+> ptext SLIT("#)")
217 \end{code}
218
219
220 %************************************************************************
221 %*                                                                      *
222 \subsection[Recursive/Non-Recursive]{Recursive/Non-Recursive flag}
223 %*                                                                      *
224 %************************************************************************
225
226 \begin{code} 
227 data RecFlag = Recursive 
228              | NonRecursive
229
230 isRec :: RecFlag -> Bool
231 isRec Recursive    = True
232 isRec NonRecursive = False
233
234 isNonRec :: RecFlag -> Bool
235 isNonRec Recursive    = False
236 isNonRec NonRecursive = True
237 \end{code}
238
239 %************************************************************************
240 %*                                                                      *
241 \subsection[Generic]{Generic flag}
242 %*                                                                      *
243 %************************************************************************
244
245 This is the "Embedding-Projection pair" datatype, it contains 
246 two pieces of code (normally either RenamedHsExpr's or Id's)
247 If we have a such a pair (EP from to), the idea is that 'from' and 'to'
248 represents functions of type 
249
250         from :: T -> Tring
251         to   :: Tring -> T
252
253 And we should have 
254
255         to (from x) = x
256
257 T and Tring are arbitrary, but typically T is the 'main' type while
258 Tring is the 'representation' type.  (This just helps us remember 
259 whether to use 'from' or 'to'.
260
261 \begin{code}
262 data EP a = EP { fromEP :: a,   -- :: T -> Tring
263                  toEP   :: a }  -- :: Tring -> T
264 \end{code}
265
266 Embedding-projection pairs are used in several places:
267
268 First of all, each type constructor has an EP associated with it, the
269 code in EP converts (datatype T) from T to Tring and back again.
270
271 Secondly, when we are filling in Generic methods (in the typechecker, 
272 tcMethodBinds), we are constructing bimaps by induction on the structure
273 of the type of the method signature.
274
275
276 %************************************************************************
277 %*                                                                      *
278 \subsection{Occurrence information}
279 %*                                                                      *
280 %************************************************************************
281
282 This data type is used exclusively by the simplifier, but it appears in a
283 SubstResult, which is currently defined in VarEnv, which is pretty near
284 the base of the module hierarchy.  So it seemed simpler to put the
285 defn of OccInfo here, safely at the bottom
286
287 \begin{code}
288 data OccInfo 
289   = NoOccInfo
290
291   | IAmDead             -- Marks unused variables.  Sometimes useful for
292                         -- lambda and case-bound variables.
293
294   | OneOcc InsideLam
295
296            OneBranch
297
298   | IAmALoopBreaker     -- Used by the occurrence analyser to mark loop-breakers
299                         -- in a group of recursive definitions
300
301 seqOccInfo :: OccInfo -> ()
302 seqOccInfo (OneOcc in_lam once) = in_lam `seq` once `seq` ()
303 seqOccInfo occ                  = ()
304
305 type InsideLam = Bool   -- True <=> Occurs inside a non-linear lambda
306                         -- Substituting a redex for this occurrence is
307                         -- dangerous because it might duplicate work.
308 insideLam    = True
309 notInsideLam = False
310
311 type OneBranch = Bool   -- True <=> Occurs in only one case branch
312                         --      so no code-duplication issue to worry about
313 oneBranch    = True
314 notOneBranch = False
315
316 isLoopBreaker :: OccInfo -> Bool
317 isLoopBreaker IAmALoopBreaker = True
318 isLoopBreaker other           = False
319
320 isDeadOcc :: OccInfo -> Bool
321 isDeadOcc IAmDead = True
322 isDeadOcc other   = False
323
324 isOneOcc (OneOcc _ _) = True
325 isOneOcc other        = False
326
327 isFragileOcc :: OccInfo -> Bool
328 isFragileOcc (OneOcc _ _) = True
329 isFragileOcc other        = False
330 \end{code}
331
332 \begin{code}
333 instance Outputable OccInfo where
334   -- only used for debugging; never parsed.  KSW 1999-07
335   ppr NoOccInfo                                   = empty
336   ppr IAmALoopBreaker                             = ptext SLIT("_Kx")
337   ppr IAmDead                                     = ptext SLIT("_Kd")
338   ppr (OneOcc inside_lam one_branch) | inside_lam = ptext SLIT("_Kl")
339                                      | one_branch = ptext SLIT("_Ks")
340                                      | otherwise  = ptext SLIT("_Ks*")
341
342 instance Show OccInfo where
343   showsPrec p occ = showsPrecSDoc p (ppr occ)
344 \end{code}
345
346 %************************************************************************
347 %*                                                                      *
348 \subsection{Strictness indication}
349 %*                                                                      *
350 %************************************************************************
351
352 The strictness annotations on types in data type declarations
353 e.g.    data T = MkT !Int !(Bool,Bool)
354
355 \begin{code}
356 data StrictnessMark
357    = MarkedUserStrict   -- "!"  in a source decl
358    | MarkedStrict       -- "!"  in an interface decl: strict but not unboxed
359    | MarkedUnboxed      -- "!!" in an interface decl: unboxed 
360    | NotMarkedStrict    -- No annotation at all
361    deriving( Eq )
362
363 isMarkedUnboxed MarkedUnboxed = True
364 isMarkedUnboxed other         = False
365
366 isMarkedStrict NotMarkedStrict = False
367 isMarkedStrict other           = True   -- All others are strict
368
369 instance Outputable StrictnessMark where
370   ppr MarkedUserStrict = ptext SLIT("!u")
371   ppr MarkedStrict     = ptext SLIT("!")
372   ppr MarkedUnboxed    = ptext SLIT("! !")
373   ppr NotMarkedStrict  = empty
374 \end{code}
375
376
377 %************************************************************************
378 %*                                                                      *
379 \subsection{Activation}
380 %*                                                                      *
381 %************************************************************************
382
383 When a rule or inlining is active
384
385 \begin{code}
386 type CompilerPhase = Int        -- Compilation phase
387                                 -- Phases decrease towards zero
388                                 -- Zero is the last phase
389
390 data Activation = NeverActive
391                 | AlwaysActive
392                 | ActiveBefore CompilerPhase    -- Active only *before* this phase
393                 | ActiveAfter CompilerPhase     -- Active in this phase and later
394                 deriving( Eq )                  -- Eq used in comparing rules in HsDecls
395
396 instance Outputable Activation where
397    ppr AlwaysActive     = empty         -- The default
398    ppr (ActiveBefore n) = brackets (char '~' <> int n)
399    ppr (ActiveAfter n)  = brackets (int n)
400    ppr NeverActive      = ptext SLIT("NEVER")
401     
402 isActive :: CompilerPhase -> Activation -> Bool
403 isActive p NeverActive      = False
404 isActive p AlwaysActive     = True
405 isActive p (ActiveAfter n)  = p <= n
406 isActive p (ActiveBefore n) = p >  n
407
408 isNeverActive, isAlwaysActive :: Activation -> Bool
409 isNeverActive NeverActive = True
410 isNeverActive act         = False
411
412 isAlwaysActive AlwaysActive = True
413 isAlwaysActive other        = False
414 \end{code}