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