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