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