[project @ 2001-08-09 11:32:15 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         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    ) 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[Generic]{Generic flag}
208 %*                                                                      *
209 %************************************************************************
210
211 This is the "Embedding-Projection pair" datatype, it contains 
212 two pieces of code (normally either RenamedHsExpr's or Id's)
213 If we have a such a pair (EP from to), the idea is that 'from' and 'to'
214 represents functions of type 
215
216         from :: T -> Tring
217         to   :: Tring -> T
218
219 And we should have 
220
221         to (from x) = x
222
223 T and Tring are arbitrary, but typically T is the 'main' type while
224 Tring is the 'representation' type.  (This just helps us remember 
225 whether to use 'from' or 'to'.
226
227 \begin{code}
228 data EP a = EP { fromEP :: a,   -- :: T -> Tring
229                  toEP   :: a }  -- :: Tring -> T
230 \end{code}
231
232 Embedding-projection pairs are used in several places:
233
234 First of all, each type constructor has an EP associated with it, the
235 code in EP converts (datatype T) from T to Tring and back again.
236
237 Secondly, when we are filling in Generic methods (in the typechecker, 
238 tcMethodBinds), we are constructing bimaps by induction on the structure
239 of the type of the method signature.
240
241
242 %************************************************************************
243 %*                                                                      *
244 \subsection{Occurrence information}
245 %*                                                                      *
246 %************************************************************************
247
248 This data type is used exclusively by the simplifier, but it appears in a
249 SubstResult, which is currently defined in VarEnv, which is pretty near
250 the base of the module hierarchy.  So it seemed simpler to put the
251 defn of OccInfo here, safely at the bottom
252
253 \begin{code}
254 data OccInfo 
255   = NoOccInfo
256
257   | IAmDead             -- Marks unused variables.  Sometimes useful for
258                         -- lambda and case-bound variables.
259
260   | OneOcc InsideLam
261
262            OneBranch
263
264   | IAmALoopBreaker     -- Used by the occurrence analyser to mark loop-breakers
265                         -- in a group of recursive definitions
266
267 seqOccInfo :: OccInfo -> ()
268 seqOccInfo (OneOcc in_lam once) = in_lam `seq` once `seq` ()
269 seqOccInfo occ                  = ()
270
271 type InsideLam = Bool   -- True <=> Occurs inside a non-linear lambda
272                         -- Substituting a redex for this occurrence is
273                         -- dangerous because it might duplicate work.
274 insideLam    = True
275 notInsideLam = False
276
277 type OneBranch = Bool   -- True <=> Occurs in only one case branch
278                         --      so no code-duplication issue to worry about
279 oneBranch    = True
280 notOneBranch = False
281
282 isLoopBreaker :: OccInfo -> Bool
283 isLoopBreaker IAmALoopBreaker = True
284 isLoopBreaker other           = False
285
286 isDeadOcc :: OccInfo -> Bool
287 isDeadOcc IAmDead = True
288 isDeadOcc other   = False
289
290 isFragileOcc :: OccInfo -> Bool
291 isFragileOcc (OneOcc _ _) = True
292 isFragileOcc other            = False
293 \end{code}
294
295 \begin{code}
296 instance Outputable OccInfo where
297   -- only used for debugging; never parsed.  KSW 1999-07
298   ppr NoOccInfo                                   = empty
299   ppr IAmALoopBreaker                             = ptext SLIT("_Kx")
300   ppr IAmDead                                     = ptext SLIT("_Kd")
301   ppr (OneOcc inside_lam one_branch) | inside_lam = ptext SLIT("_Kl")
302                                      | one_branch = ptext SLIT("_Ks")
303                                      | otherwise  = ptext SLIT("_Ks*")
304
305 instance Show OccInfo where
306   showsPrec p occ = showsPrecSDoc p (ppr occ)
307 \end{code}
308
309 %************************************************************************
310 %*                                                                      *
311 \subsection{Strictness indication}
312 %*                                                                      *
313 %************************************************************************
314
315 The strictness annotations on types in data type declarations
316 e.g.    data T = MkT !Int !(Bool,Bool)
317
318 \begin{code}
319 data StrictnessMark
320    = MarkedUserStrict   -- "!"  in a source decl
321    | MarkedStrict       -- "!"  in an interface decl: strict but not unboxed
322    | MarkedUnboxed      -- "!!" in an interface decl: unboxed 
323    | NotMarkedStrict    -- No annotation at all
324    deriving( Eq )
325
326 isMarkedUnboxed MarkedUnboxed = True
327 isMarkedUnboxed other         = False
328
329 isMarkedStrict NotMarkedStrict = False
330 isMarkedStrict other           = True   -- All others are strict
331
332 instance Outputable StrictnessMark where
333   ppr MarkedUserStrict = ptext SLIT("!u")
334   ppr MarkedStrict     = ptext SLIT("!")
335   ppr MarkedUnboxed    = ptext SLIT("! !")
336   ppr NotMarkedStrict  = empty
337 \end{code}