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