[project @ 2002-02-06 15:54:23 by simonpj]
[ghc-hetmet.git] / ghc / compiler / types / TypeRep.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1998
3 %
4 \section[TypeRep]{Type - friends' interface}
5
6 \begin{code}
7 module TypeRep (
8         Type(..), TyNote(..),           -- Representation visible 
9         SourceType(..),                 -- to friends
10         
11         Kind, PredType, ThetaType,              -- Synonyms
12         TyVarSubst,
13
14         superKind, superBoxity,                         -- KX and BX respectively
15         liftedBoxity, unliftedBoxity,                   -- :: BX
16         openKindCon,                                    -- :: KX
17         typeCon,                                        -- :: BX -> KX
18         liftedTypeKind, unliftedTypeKind, openTypeKind, -- :: KX
19         mkArrowKind, mkArrowKinds,                      -- :: KX -> KX -> KX
20
21         usageKindCon,                                   -- :: KX
22         usageTypeKind,                                  -- :: KX
23         usOnceTyCon, usManyTyCon,                       -- :: $
24         usOnce, usMany,                                 -- :: $
25
26         funTyCon
27     ) where
28
29 #include "HsVersions.h"
30
31 -- friends:
32 import Var        ( TyVar )
33 import VarEnv     ( TyVarEnv )
34 import VarSet     ( TyVarSet )
35 import Name       ( Name )
36 import BasicTypes ( IPName )
37 import TyCon      ( TyCon, KindCon, mkFunTyCon, mkKindCon, mkSuperKindCon )
38 import Class      ( Class )
39
40 -- others
41 import PrelNames        ( superKindName, superBoxityName, liftedConName, 
42                           unliftedConName, typeConName, openKindConName, 
43                           usageKindConName, usOnceTyConName, usManyTyConName,
44                           funTyConName
45                         )
46 \end{code}
47
48 %************************************************************************
49 %*                                                                      *
50 \subsection{Type Classifications}
51 %*                                                                      *
52 %************************************************************************
53
54 A type is
55
56         *unboxed*       iff its representation is other than a pointer
57                         Unboxed types are also unlifted.
58
59         *lifted*        A type is lifted iff it has bottom as an element.
60                         Closures always have lifted types:  i.e. any
61                         let-bound identifier in Core must have a lifted
62                         type.  Operationally, a lifted object is one that
63                         can be entered.
64
65                         Only lifted types may be unified with a type variable.
66
67         *algebraic*     A type with one or more constructors, whether declared
68                         with "data" or "newtype".   
69                         An algebraic type is one that can be deconstructed
70                         with a case expression.  
71                         *NOT* the same as lifted types,  because we also 
72                         include unboxed tuples in this classification.
73
74         *data*          A type declared with "data".  Also boxed tuples.
75
76         *primitive*     iff it is a built-in type that can't be expressed
77                         in Haskell.
78
79 Currently, all primitive types are unlifted, but that's not necessarily
80 the case.  (E.g. Int could be primitive.)
81
82 Some primitive types are unboxed, such as Int#, whereas some are boxed
83 but unlifted (such as ByteArray#).  The only primitive types that we
84 classify as algebraic are the unboxed tuples.
85
86 examples of type classifications:
87
88 Type            primitive       boxed           lifted          algebraic    
89 -----------------------------------------------------------------------------
90 Int#,           Yes             No              No              No
91 ByteArray#      Yes             Yes             No              No
92 (# a, b #)      Yes             No              No              Yes
93 (  a, b  )      No              Yes             Yes             Yes
94 [a]             No              Yes             Yes             Yes
95
96
97
98         ----------------------
99         A note about newtypes
100         ----------------------
101
102 Consider
103         newtype N = MkN Int
104
105 Then we want N to be represented as an Int, and that's what we arrange.
106 The front end of the compiler [TcType.lhs] treats N as opaque, 
107 the back end treats it as transparent [Type.lhs].
108
109 There's a bit of a problem with recursive newtypes
110         newtype P = MkP P
111         newtype Q = MkQ (Q->Q)
112
113 Here the 'implicit expansion' we get from treating P and Q as transparent
114 would give rise to infinite types, which in turn makes eqType diverge.
115 Similarly splitForAllTys and splitFunTys can get into a loop.  
116
117 Solution: for recursive newtypes use a coerce, and treat the newtype
118 and its representation as distinct right through the compiler.  That's
119 what you get if you use recursive newtypes.  (They are rare, so who
120 cares if they are a tiny bit less efficient.)
121
122 So: non-recursive newtypes are represented using a SourceTy (see below)
123     recursive newtypes are represented using a TyConApp
124
125 The TyCon still says "I'm a newtype", but we do not represent the
126 newtype application as a SourceType; instead as a TyConApp.
127
128
129 %************************************************************************
130 %*                                                                      *
131 \subsection{The data type}
132 %*                                                                      *
133 %************************************************************************
134
135
136 \begin{code}
137 type SuperKind = Type
138 type Kind      = Type
139
140 type TyVarSubst = TyVarEnv Type
141
142 data Type
143   = TyVarTy TyVar
144
145   | AppTy
146         Type            -- Function is *not* a TyConApp
147         Type
148
149   | TyConApp            -- Application of a TyCon
150         TyCon           -- *Invariant* saturated appliations of FunTyCon and
151                         --      synonyms have their own constructors, below.
152         [Type]          -- Might not be saturated.
153
154   | FunTy               -- Special case of TyConApp: TyConApp FunTyCon [t1,t2]
155         Type
156         Type
157
158   | ForAllTy            -- A polymorphic type
159         TyVar
160         Type    
161
162   | SourceTy            -- A high level source type 
163         SourceType      -- ...can be expanded to a representation type...
164
165   | NoteTy              -- A type with a note attached
166         TyNote
167         Type            -- The expanded version
168
169 data TyNote
170   = FTVNote TyVarSet    -- The free type variables of the noted expression
171
172   | SynNote Type        -- Used for type synonyms
173                         -- The Type is always a TyConApp, and is the un-expanded form.
174                         -- The type to which the note is attached is the expanded form.
175 \end{code}
176
177 -------------------------------------
178                 Source types
179
180 A type of the form
181         SourceTy sty
182 represents a value whose type is the Haskell source type sty.
183 It can be expanded into its representation, but: 
184
185         * The type checker must treat it as opaque
186         * The rest of the compiler treats it as transparent
187
188 There are two main uses
189         a) Haskell predicates
190         b) newtypes
191
192 Consider these examples:
193         f :: (Eq a) => a -> Int
194         g :: (?x :: Int -> Int) => a -> Int
195         h :: (r\l) => {r} => {l::Int | r}
196
197 Here the "Eq a" and "?x :: Int -> Int" and "r\l" are all called *predicates*
198 Predicates are represented inside GHC by PredType:
199
200 \begin{code}
201 data SourceType 
202   = ClassP Class [Type]         -- Class predicate
203   | IParam (IPName Name) Type   -- Implicit parameter
204   | NType TyCon [Type]          -- A *saturated*, *non-recursive* newtype application
205                                 -- [See notes at top about newtypes]
206
207 type PredType  = SourceType     -- A subtype for predicates
208 type ThetaType = [PredType]
209 \end{code}
210
211 (We don't support TREX records yet, but the setup is designed
212 to expand to allow them.)
213
214 A Haskell qualified type, such as that for f,g,h above, is
215 represented using 
216         * a FunTy for the double arrow
217         * with a PredTy as the function argument
218
219 The predicate really does turn into a real extra argument to the
220 function.  If the argument has type (PredTy p) then the predicate p is
221 represented by evidence (a dictionary, for example, of type (predRepTy p).
222
223
224 %************************************************************************
225 %*                                                                      *
226 \subsection{Kinds}
227 %*                                                                      *
228 %************************************************************************
229
230 Kinds
231 ~~~~~
232 kind :: KX = kind -> kind
233
234            | Type liftedness    -- (Type *) is printed as just *
235                                 -- (Type #) is printed as just #
236
237            | UsageKind          -- Printed '$'; used for usage annotations
238
239            | OpenKind           -- Can be lifted or unlifted
240                                 -- Printed '?'
241
242            | kv                 -- A kind variable; *only* happens during kind checking
243
244 boxity :: BX = *        -- Lifted
245              | #        -- Unlifted
246              | bv       -- A boxity variable; *only* happens during kind checking
247
248 There's a little subtyping at the kind level:  
249         forall b. Type b <: OpenKind
250
251 That is, a type of kind (Type b) is OK in a context requiring an OpenKind
252
253 OpenKind, written '?', is used as the kind for certain type variables,
254 in two situations:
255
256 1.  The universally quantified type variable(s) for special built-in 
257     things like error :: forall (a::?). String -> a. 
258     Here, the 'a' can be instantiated to a lifted or unlifted type.  
259
260 2.  Kind '?' is also used when the typechecker needs to create a fresh
261     type variable, one that may very well later be unified with a type.
262     For example, suppose f::a, and we see an application (f x).  Then a
263     must be a function type, so we unify a with (b->c).  But what kind
264     are b and c?  They can be lifted or unlifted types, or indeed type schemes,
265     so we give them kind '?'.
266
267     When the type checker generalises over a bunch of type variables, it
268     makes any that still have kind '?' into kind '*'.  So kind '?' is never
269     present in an inferred type.
270
271
272 ------------------------------------------
273 Define  KX, the type of a kind
274         BX, the type of a boxity
275
276 \begin{code}
277 superKind :: SuperKind          -- KX, the type of all kinds
278 superKind = TyConApp (mkSuperKindCon superKindName) []
279
280 superBoxity :: SuperKind                -- BX, the type of all boxities
281 superBoxity = TyConApp (mkSuperKindCon superBoxityName) []
282 \end{code}
283
284 ------------------------------------------
285 Define boxities: @*@ and @#@
286
287 \begin{code}
288 liftedBoxity, unliftedBoxity :: Kind            -- :: BX
289 liftedBoxity  = TyConApp (mkKindCon liftedConName superBoxity) []
290
291 unliftedBoxity  = TyConApp (mkKindCon unliftedConName superBoxity) []
292 \end{code}
293
294 ------------------------------------------
295 Define kinds: Type, Type *, Type #, OpenKind, and UsageKind
296
297 \begin{code}
298 typeCon :: KindCon      -- :: BX -> KX
299 typeCon     = mkKindCon typeConName (superBoxity `FunTy` superKind)
300
301 liftedTypeKind, unliftedTypeKind, openTypeKind :: Kind  -- Of superkind superKind
302
303 liftedTypeKind   = TyConApp typeCon [liftedBoxity]
304 unliftedTypeKind = TyConApp typeCon [unliftedBoxity]
305
306 openKindCon     = mkKindCon openKindConName superKind
307 openTypeKind    = TyConApp openKindCon []
308
309 usageKindCon     = mkKindCon usageKindConName superKind
310 usageTypeKind    = TyConApp usageKindCon []
311 \end{code}
312
313 ------------------------------------------
314 Define arrow kinds
315
316 \begin{code}
317 mkArrowKind :: Kind -> Kind -> Kind
318 mkArrowKind k1 k2 = k1 `FunTy` k2
319
320 mkArrowKinds :: [Kind] -> Kind -> Kind
321 mkArrowKinds arg_kinds result_kind = foldr mkArrowKind result_kind arg_kinds
322 \end{code}
323
324
325 %************************************************************************
326 %*                                                                      *
327 \subsection{Wired-in type constructors
328 %*                                                                      *
329 %************************************************************************
330
331 We define a few wired-in type constructors here to avoid module knots
332
333 \begin{code}
334 funTyCon = mkFunTyCon funTyConName (mkArrowKinds [liftedTypeKind, liftedTypeKind] liftedTypeKind)
335 \end{code}
336
337 ------------------------------------------
338 Usage tycons @.@ and @!@
339
340 The usage tycons are of kind usageTypeKind (`$').  The types contain
341 no values, and are used purely for usage annotation.  
342
343 \begin{code}
344 usOnceTyCon     = mkKindCon usOnceTyConName usageTypeKind
345 usOnce          = TyConApp usOnceTyCon []
346
347 usManyTyCon     = mkKindCon usManyTyConName usageTypeKind
348 usMany          = TyConApp usManyTyCon []
349 \end{code}
350