~ubuntu-branches/ubuntu/precise/ghc/precise

« back to all changes in this revision

Viewing changes to compiler/types/TyCon.lhs

  • Committer: Bazaar Package Importer
  • Author(s): Joachim Breitner
  • Date: 2011-01-17 12:49:24 UTC
  • Revision ID: james.westby@ubuntu.com-20110117124924-do1pym1jlf5o636m
Tags: upstream-7.0.1
ImportĀ upstreamĀ versionĀ 7.0.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%
 
2
% (c) The University of Glasgow 2006
 
3
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 
4
%
 
5
 
 
6
The @TyCon@ datatype
 
7
 
 
8
\begin{code}
 
9
module TyCon(
 
10
        -- * Main TyCon data types
 
11
        TyCon, FieldLabel, 
 
12
 
 
13
        AlgTyConRhs(..), visibleDataCons, 
 
14
        TyConParent(..), isNoParent,
 
15
        SynTyConRhs(..),
 
16
        CoTyConDesc(..),
 
17
 
 
18
        -- ** Constructing TyCons
 
19
        mkAlgTyCon,
 
20
        mkClassTyCon,
 
21
        mkFunTyCon,
 
22
        mkPrimTyCon,
 
23
        mkKindTyCon,
 
24
        mkLiftedPrimTyCon,
 
25
        mkTupleTyCon,
 
26
        mkSynTyCon,
 
27
        mkSuperKindTyCon,
 
28
        mkCoercionTyCon,
 
29
        mkForeignTyCon,
 
30
        mkAnyTyCon,
 
31
 
 
32
        -- ** Predicates on TyCons
 
33
        isAlgTyCon,
 
34
        isClassTyCon, isFamInstTyCon, 
 
35
        isFunTyCon, 
 
36
        isPrimTyCon,
 
37
        isTupleTyCon, isUnboxedTupleTyCon, isBoxedTupleTyCon, 
 
38
        isSynTyCon, isClosedSynTyCon, 
 
39
        isSuperKindTyCon, isDecomposableTyCon,
 
40
        isCoercionTyCon, isCoercionTyCon_maybe,
 
41
        isForeignTyCon, isAnyTyCon, tyConHasKind,
 
42
 
 
43
        isInjectiveTyCon,
 
44
        isDataTyCon, isProductTyCon, isEnumerationTyCon, 
 
45
        isNewTyCon, isAbstractTyCon, 
 
46
        isFamilyTyCon, isSynFamilyTyCon, isDataFamilyTyCon,
 
47
        isUnLiftedTyCon,
 
48
        isGadtSyntaxTyCon,
 
49
        isTyConAssoc,
 
50
        isRecursiveTyCon,
 
51
        isHiBootTyCon,
 
52
        isImplicitTyCon, tyConHasGenerics,
 
53
 
 
54
        -- ** Extracting information out of TyCons
 
55
        tyConName,
 
56
        tyConKind,
 
57
        tyConUnique,
 
58
        tyConTyVars,
 
59
        tyConDataCons, tyConDataCons_maybe, tyConSingleDataCon_maybe,
 
60
        tyConFamilySize,
 
61
        tyConStupidTheta,
 
62
        tyConArity,
 
63
        tyConParent,
 
64
        tyConClass_maybe,
 
65
        tyConFamInst_maybe, tyConFamilyCoercion_maybe,tyConFamInstSig_maybe,
 
66
        synTyConDefn, synTyConRhs, synTyConType, 
 
67
        tyConExtName,           -- External name for foreign types
 
68
        algTyConRhs,
 
69
        newTyConRhs, newTyConEtadRhs, unwrapNewTyCon_maybe, 
 
70
        tupleTyConBoxity,
 
71
 
 
72
        -- ** Manipulating TyCons
 
73
        tcExpandTyCon_maybe, coreExpandTyCon_maybe,
 
74
        makeTyConAbstract,
 
75
        newTyConCo_maybe,
 
76
 
 
77
        -- * Primitive representations of Types
 
78
        PrimRep(..),
 
79
        tyConPrimRep,
 
80
        primRepSizeW
 
81
) where
 
82
 
 
83
#include "HsVersions.h"
 
84
 
 
85
import {-# SOURCE #-} TypeRep ( Kind, Type, PredType )
 
86
import {-# SOURCE #-} DataCon ( DataCon, isVanillaDataCon )
 
87
 
 
88
import Var
 
89
import Class
 
90
import BasicTypes
 
91
import Name
 
92
import PrelNames
 
93
import Maybes
 
94
import Outputable
 
95
import FastString
 
96
import Constants
 
97
import Util
 
98
import qualified Data.Data as Data
 
99
\end{code}
 
100
 
 
101
-----------------------------------------------
 
102
        Notes about type families
 
103
-----------------------------------------------
 
104
 
 
105
Note [Type synonym families]
 
106
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
107
* Type synonym families, also known as "type functions", map directly
 
108
  onto the type functions in FC:
 
109
 
 
110
        type family F a :: *
 
111
        type instance F Int = Bool
 
112
        ..etc...
 
113
 
 
114
* Reply "yes" to isSynFamilyTyCon, and isFamilyTyCon
 
115
 
 
116
* From the user's point of view (F Int) and Bool are simply 
 
117
  equivalent types.
 
118
 
 
119
* A Haskell 98 type synonym is a degenerate form of a type synonym
 
120
  family.
 
121
 
 
122
* Type functions can't appear in the LHS of a type function:
 
123
        type instance F (F Int) = ...   -- BAD!
 
124
 
 
125
* Translation of type family decl:
 
126
        type family F a :: *
 
127
  translates to
 
128
    a SynTyCon 'F', whose SynTyConRhs is SynFamilyTyCon
 
129
 
 
130
* Translation of type instance decl:
 
131
        type instance F [a] = Maybe a
 
132
  translates to
 
133
    A SynTyCon 'R:FList a', whose 
 
134
       SynTyConRhs is (SynonymTyCon (Maybe a))
 
135
       TyConParent is (FamInstTyCon F [a] co)
 
136
         where co :: F [a] ~ R:FList a
 
137
    Notice that we introduce a gratuitous vanilla type synonym
 
138
       type R:FList a = Maybe a
 
139
    solely so that type and data families can be treated more
 
140
    uniformly, via a single FamInstTyCon descriptor        
 
141
 
 
142
* In the future we might want to support
 
143
    * closed type families (esp when we have proper kinds)
 
144
    * injective type families (allow decomposition)
 
145
  but we don't at the moment [2010]
 
146
 
 
147
Note [Data type families]
 
148
~~~~~~~~~~~~~~~~~~~~~~~~~
 
149
See also Note [Wrappers for data instance tycons] in MkId.lhs
 
150
 
 
151
* Data type families are declared thus
 
152
        data family T a :: *
 
153
        data instance T Int = T1 | T2 Bool
 
154
 
 
155
  Here T is the "family TyCon".
 
156
 
 
157
* Reply "yes" to isDataFamilyTyCon, and isFamilyTyCon
 
158
 
 
159
* The user does not see any "equivalent types" as he did with type
 
160
  synonym families.  He just sees constructors with types
 
161
        T1 :: T Int
 
162
        T2 :: Bool -> T Int
 
163
 
 
164
* Here's the FC version of the above declarations:
 
165
 
 
166
        data T a
 
167
        data R:TInt = T1 | T2 Bool
 
168
        axiom ax_ti : T Int ~ R:TInt
 
169
 
 
170
  The R:TInt is the "representation TyCons".
 
171
  It has an AlgTyConParent of
 
172
        FamInstTyCon T [Int] ax_ti
 
173
 
 
174
* The data contructor T2 has a wrapper (which is what the 
 
175
  source-level "T2" invokes):
 
176
 
 
177
        $WT2 :: Bool -> T Int
 
178
        $WT2 b = T2 b `cast` sym ax_ti
 
179
 
 
180
* A data instance can declare a fully-fledged GADT:
 
181
 
 
182
        data instance T (a,b) where
 
183
          X1 :: T (Int,Bool)
 
184
          X2 :: a -> b -> T (a,b)
 
185
 
 
186
  Here's the FC version of the above declaration:
 
187
 
 
188
        data R:TPair a where
 
189
          X1 :: R:TPair Int Bool
 
190
          X2 :: a -> b -> R:TPair a b
 
191
        axiom ax_pr :: T (a,b) ~ R:TPair a b
 
192
 
 
193
        $WX1 :: forall a b. a -> b -> T (a,b)
 
194
        $WX1 a b (x::a) (y::b) = X2 a b x y `cast` sym (ax_pr a b)
 
195
 
 
196
  The R:TPair are the "representation TyCons".
 
197
  We have a bit of work to do, to unpick the result types of the
 
198
  data instance declaration for T (a,b), to get the result type in the
 
199
  representation; e.g.  T (a,b) --> R:TPair a b
 
200
 
 
201
  The representation TyCon R:TList, has an AlgTyConParent of
 
202
 
 
203
        FamInstTyCon T [(a,b)] ax_pr
 
204
 
 
205
* Notice that T is NOT translated to a FC type function; it just
 
206
  becomes a "data type" with no constructors, which can be coerced inot
 
207
  into R:TInt, R:TPair by the axioms.  These axioms
 
208
  axioms come into play when (and *only* when) you
 
209
        - use a data constructor
 
210
        - do pattern matching
 
211
  Rather like newtype, in fact
 
212
 
 
213
  As a result
 
214
 
 
215
  - T behaves just like a data type so far as decomposition is concerned
 
216
 
 
217
  - (T Int) is not implicitly converted to R:TInt during type inference. 
 
218
    Indeed the latter type is unknown to the programmer.
 
219
 
 
220
  - There *is* an instance for (T Int) in the type-family instance 
 
221
    environment, but it is only used for overlap checking
 
222
 
 
223
  - It's fine to have T in the LHS of a type function:
 
224
    type instance F (T a) = [a]
 
225
 
 
226
  It was this last point that confused me!  The big thing is that you
 
227
  should not think of a data family T as a *type function* at all, not
 
228
  even an injective one!  We can't allow even injective type functions
 
229
  on the LHS of a type function:
 
230
        type family injective G a :: *
 
231
        type instance F (G Int) = Bool
 
232
  is no good, even if G is injective, because consider
 
233
        type instance G Int = Bool
 
234
        type instance F Bool = Char
 
235
 
 
236
  So a data type family is not an injective type function. It's just a
 
237
  data type with some axioms that connect it to other data types. 
 
238
 
 
239
%************************************************************************
 
240
%*                                                                      *
 
241
\subsection{The data type}
 
242
%*                                                                      *
 
243
%************************************************************************
 
244
 
 
245
\begin{code}
 
246
-- | TyCons represent type constructors. Type constructors are introduced by things such as:
 
247
--
 
248
-- 1) Data declarations: @data Foo = ...@ creates the @Foo@ type constructor of kind @*@
 
249
--
 
250
-- 2) Type synonyms: @type Foo = ...@ creates the @Foo@ type constructor
 
251
--
 
252
-- 3) Newtypes: @newtype Foo a = MkFoo ...@ creates the @Foo@ type constructor of kind @* -> *@
 
253
--
 
254
-- 4) Class declarations: @class Foo where@ creates the @Foo@ type constructor of kind @*@
 
255
--
 
256
-- 5) Type coercions! This is because we represent a coercion from @t1@ to @t2@ 
 
257
--    as a 'Type', where that type has kind @t1 ~ t2@. See "Coercion" for more on this
 
258
--
 
259
-- This data type also encodes a number of primitive, built in type constructors such as those
 
260
-- for function and tuple types.
 
261
data TyCon
 
262
  = -- | The function type constructor, @(->)@
 
263
    FunTyCon {
 
264
        tyConUnique :: Unique,
 
265
        tyConName   :: Name,
 
266
        tc_kind   :: Kind,
 
267
        tyConArity  :: Arity
 
268
    }
 
269
 
 
270
  -- | Algebraic type constructors, which are defined to be those
 
271
  -- arising @data@ type and @newtype@ declarations.  All these
 
272
  -- constructors are lifted and boxed. See 'AlgTyConRhs' for more
 
273
  -- information.
 
274
  | AlgTyCon {          
 
275
        tyConUnique :: Unique,
 
276
        tyConName   :: Name,
 
277
        tc_kind   :: Kind,
 
278
        tyConArity  :: Arity,
 
279
 
 
280
        tyConTyVars :: [TyVar],   -- ^ The type variables used in the type constructor.
 
281
                                  -- Invariant: length tyvars = arity
 
282
                                  -- Precisely, this list scopes over:
 
283
                                  --
 
284
                                  -- 1. The 'algTcStupidTheta'
 
285
                                  -- 2. The cached types in 'algTyConRhs.NewTyCon'
 
286
                                  -- 3. The family instance types if present
 
287
                                  --
 
288
                                  -- Note that it does /not/ scope over the data constructors.
 
289
 
 
290
        algTcGadtSyntax  :: Bool,       -- ^ Was the data type declared with GADT syntax? 
 
291
                                        -- If so, that doesn't mean it's a true GADT; 
 
292
                                        -- only that the "where" form was used. 
 
293
                                        -- This field is used only to guide pretty-printing
 
294
 
 
295
        algTcStupidTheta :: [PredType], -- ^ The \"stupid theta\" for the data type 
 
296
                                        -- (always empty for GADTs).
 
297
                                        -- A \"stupid theta\" is the context to the left 
 
298
                                        -- of an algebraic type declaration, 
 
299
                                        -- e.g. @Eq a@ in the declaration 
 
300
                                        --    @data Eq a => T a ...@.
 
301
 
 
302
        algTcRhs :: AlgTyConRhs,  -- ^ Contains information about the 
 
303
                                  -- data constructors of the algebraic type
 
304
 
 
305
        algTcRec :: RecFlag,      -- ^ Tells us whether the data type is part 
 
306
                                  -- of a mutually-recursive group or not
 
307
 
 
308
        hasGenerics :: Bool,      -- ^ Whether generic (in the -XGenerics sense) 
 
309
                                  -- to\/from functions are available in the exports 
 
310
                                  -- of the data type's source module.
 
311
 
 
312
        algTcParent :: TyConParent      -- ^ Gives the class or family declaration 'TyCon' 
 
313
                                        -- for derived 'TyCon's representing class 
 
314
                                        -- or family instances, respectively. 
 
315
                                        -- See also 'synTcParent'
 
316
    }
 
317
 
 
318
  -- | Represents the infinite family of tuple type constructors, 
 
319
  --   @()@, @(a,b)@, @(# a, b #)@ etc.
 
320
  | TupleTyCon {
 
321
        tyConUnique :: Unique,
 
322
        tyConName   :: Name,
 
323
        tc_kind   :: Kind,
 
324
        tyConArity  :: Arity,
 
325
        tyConBoxed  :: Boxity,
 
326
        tyConTyVars :: [TyVar],
 
327
        dataCon     :: DataCon, -- ^ Corresponding tuple data constructor
 
328
        hasGenerics :: Bool
 
329
    }
 
330
 
 
331
  -- | Represents type synonyms
 
332
  | SynTyCon {
 
333
        tyConUnique  :: Unique,
 
334
        tyConName    :: Name,
 
335
        tc_kind    :: Kind,
 
336
        tyConArity   :: Arity,
 
337
 
 
338
        tyConTyVars  :: [TyVar],        -- Bound tyvars
 
339
 
 
340
        synTcRhs     :: SynTyConRhs,    -- ^ Contains information about the 
 
341
                                        -- expansion of the synonym
 
342
 
 
343
        synTcParent  :: TyConParent     -- ^ Gives the family declaration 'TyCon'
 
344
                                        -- of 'TyCon's representing family instances
 
345
 
 
346
    }
 
347
 
 
348
  -- | Primitive types; cannot be defined in Haskell. This includes
 
349
  -- the usual suspects (such as @Int#@) as well as foreign-imported
 
350
  -- types and kinds
 
351
  | PrimTyCon {                 
 
352
        tyConUnique   :: Unique,
 
353
        tyConName     :: Name,
 
354
        tc_kind       :: Kind,
 
355
        tyConArity    :: Arity,         -- SLPJ Oct06: I'm not sure what the significance
 
356
                                        --             of the arity of a primtycon is!
 
357
 
 
358
        primTyConRep  :: PrimRep,       -- ^ Many primitive tycons are unboxed, but some are
 
359
                                        --   boxed (represented by pointers). This 'PrimRep'
 
360
                                        --   holds that information.
 
361
                                        -- Only relevant if tc_kind = *
 
362
 
 
363
        isUnLifted   :: Bool,           -- ^ Most primitive tycons are unlifted 
 
364
                                        --   (may not contain bottom)
 
365
                                        --   but foreign-imported ones may be lifted
 
366
 
 
367
        tyConExtName :: Maybe FastString   -- ^ @Just e@ for foreign-imported types, 
 
368
                                           --   holds the name of the imported thing
 
369
    }
 
370
 
 
371
  -- | Type coercions, such as @(~)@, @sym@, @trans@, @left@ and @right@.
 
372
  -- INVARIANT: Coercion TyCons are always fully applied
 
373
  --            But note that a CoTyCon can be *over*-saturated in a type.
 
374
  --            E.g.  (sym g1) Int  will be represented as (TyConApp sym [g1,Int])
 
375
  | CoTyCon {   
 
376
        tyConUnique :: Unique,
 
377
        tyConName   :: Name,
 
378
        tyConArity  :: Arity,
 
379
        coTcDesc    :: CoTyConDesc
 
380
    }
 
381
 
 
382
  -- | Any types.  Like tuples, this is a potentially-infinite family of TyCons
 
383
  --   one for each distinct Kind. They have no values at all.
 
384
  --   Because there are infinitely many of them (like tuples) they are 
 
385
  --   defined in GHC.Prim and have names like "Any(*->*)".  
 
386
  --   Their Unique is derived from the OccName.
 
387
  -- See Note [Any types] in TysPrim
 
388
  | AnyTyCon {
 
389
        tyConUnique  :: Unique,
 
390
        tyConName    :: Name,
 
391
        tc_kind    :: Kind      -- Never = *; that is done via PrimTyCon
 
392
                                -- See Note [Any types] in TysPrim
 
393
    }
 
394
 
 
395
  -- | Super-kinds. These are "kinds-of-kinds" and are never seen in
 
396
  -- Haskell source programs.  There are only two super-kinds: TY (aka
 
397
  -- "box"), which is the super-kind of kinds that construct types
 
398
  -- eventually, and CO (aka "diamond"), which is the super-kind of
 
399
  -- kinds that just represent coercions.
 
400
  --
 
401
  -- Super-kinds have no kind themselves, and have arity zero
 
402
  | SuperKindTyCon {
 
403
        tyConUnique :: Unique,
 
404
        tyConName   :: Name
 
405
    }
 
406
 
 
407
-- | Names of the fields in an algebraic record type
 
408
type FieldLabel = Name
 
409
 
 
410
-- | Represents right-hand-sides of 'TyCon's for algebraic types
 
411
data AlgTyConRhs
 
412
 
 
413
    -- | Says that we know nothing about this data type, except that
 
414
    -- it's represented by a pointer.  Used when we export a data type
 
415
    -- abstractly into an .hi file.
 
416
  = AbstractTyCon
 
417
 
 
418
    -- | Represents an open type family without a fixed right hand
 
419
    -- side.  Additional instances can appear at any time.
 
420
    -- 
 
421
    -- These are introduced by either a top level declaration:
 
422
    --
 
423
    -- > data T a :: *
 
424
    --
 
425
    -- Or an associated data type declaration, within a class declaration:
 
426
    --
 
427
    -- > class C a b where
 
428
    -- >   data T b :: *
 
429
  | DataFamilyTyCon
 
430
 
 
431
    -- | Information about those 'TyCon's derived from a @data@
 
432
    -- declaration. This includes data types with no constructors at
 
433
    -- all.
 
434
  | DataTyCon {
 
435
        data_cons :: [DataCon],
 
436
                          -- ^ The data type constructors; can be empty if the user 
 
437
                          --   declares the type to have no constructors
 
438
                          --
 
439
                          -- INVARIANT: Kept in order of increasing 'DataCon' tag
 
440
                          --      (see the tag assignment in DataCon.mkDataCon)
 
441
 
 
442
        is_enum :: Bool   -- ^ Cached value: is this an enumeration type? 
 
443
                          --   See Note [Enumeration types]
 
444
    }
 
445
 
 
446
  -- | Information about those 'TyCon's derived from a @newtype@ declaration
 
447
  | NewTyCon {
 
448
        data_con :: DataCon,    -- ^ The unique constructor for the @newtype@. 
 
449
                                --   It has no existentials
 
450
 
 
451
        nt_rhs :: Type,         -- ^ Cached value: the argument type of the constructor, 
 
452
                                -- which is just the representation type of the 'TyCon'
 
453
                                -- (remember that @newtype@s do not exist at runtime 
 
454
                                -- so need a different representation type).
 
455
                                --
 
456
                                -- The free 'TyVar's of this type are the 'tyConTyVars' 
 
457
                                -- from the corresponding 'TyCon'
 
458
 
 
459
        nt_etad_rhs :: ([TyVar], Type),
 
460
                        -- ^ Same as the 'nt_rhs', but this time eta-reduced. 
 
461
                        -- Hence the list of 'TyVar's in this field may be 
 
462
                        -- shorter than the declared arity of the 'TyCon'.
 
463
                        
 
464
                        -- See Note [Newtype eta]
 
465
      
 
466
        nt_co :: Maybe TyCon   -- ^ A 'TyCon' (which is always a 'CoTyCon') that can 
 
467
                               -- have a 'Coercion' extracted from it to create 
 
468
                               -- the @newtype@ from the representation 'Type'.
 
469
                               --
 
470
                               -- This field is optional for non-recursive @newtype@s only.
 
471
                               
 
472
                               -- See Note [Newtype coercions]
 
473
                               -- Invariant: arity = #tvs in nt_etad_rhs;
 
474
                               --       See Note [Newtype eta]
 
475
                               -- Watch out!  If any newtypes become transparent
 
476
                               -- again check Trac #1072.
 
477
    }
 
478
 
 
479
-- | Extract those 'DataCon's that we are able to learn about.  Note
 
480
-- that visibility in this sense does not correspond to visibility in
 
481
-- the context of any particular user program!
 
482
visibleDataCons :: AlgTyConRhs -> [DataCon]
 
483
visibleDataCons AbstractTyCon                 = []
 
484
visibleDataCons DataFamilyTyCon {}                    = []
 
485
visibleDataCons (DataTyCon{ data_cons = cs }) = cs
 
486
visibleDataCons (NewTyCon{ data_con = c })    = [c]
 
487
 
 
488
-- ^ Both type classes as well as family instances imply implicit
 
489
-- type constructors.  These implicit type constructors refer to their parent
 
490
-- structure (ie, the class or family from which they derive) using a type of
 
491
-- the following form.  We use 'TyConParent' for both algebraic and synonym 
 
492
-- types, but the variant 'ClassTyCon' will only be used by algebraic 'TyCon's.
 
493
data TyConParent 
 
494
  = -- | An ordinary type constructor has no parent.
 
495
    NoParentTyCon
 
496
 
 
497
  -- | Type constructors representing a class dictionary.
 
498
  | ClassTyCon          
 
499
        Class           -- INVARIANT: the classTyCon of this Class is the current tycon
 
500
 
 
501
  -- | An *associated* type of a class.  
 
502
  | AssocFamilyTyCon   
 
503
        Class           -- The class in whose declaration the family is declared
 
504
                        -- The 'tyConTyVars' of this 'TyCon' may mention some
 
505
                        -- of the same type variables as the classTyVars of the
 
506
                        -- parent 'Class'.  E.g.
 
507
                        --
 
508
                        -- @
 
509
                        --    class C a b where
 
510
                        --      data T c a
 
511
                        -- @
 
512
                        --
 
513
                        -- Here the 'a' is shared with the 'Class', and that is
 
514
                        -- important. In an instance declaration we expect the
 
515
                        -- two to be instantiated the same way.  Eg.
 
516
                        --
 
517
                        -- @
 
518
                        --    instanc C [x] (Tree y) where
 
519
                        --      data T c [x] = T1 x | T2 c
 
520
                        -- @
 
521
 
 
522
  -- | Type constructors representing an instance of a type family. Parameters:
 
523
  --
 
524
  --  1) The type family in question
 
525
  --
 
526
  --  2) Instance types; free variables are the 'tyConTyVars'
 
527
  --  of the current 'TyCon' (not the family one). INVARIANT: 
 
528
  --  the number of types matches the arity of the family 'TyCon'
 
529
  --
 
530
  --  3) A 'CoTyCon' identifying the representation
 
531
  --  type with the type instance family
 
532
  | FamInstTyCon          -- See Note [Data type families]
 
533
                          -- and Note [Type synonym families]
 
534
        TyCon   -- The family TyCon
 
535
        [Type]  -- Argument types (mentions the tyConTyVars of this TyCon)
 
536
        TyCon   -- The coercion constructor
 
537
 
 
538
        -- E.g.  data intance T [a] = ...
 
539
        -- gives a representation tycon:
 
540
        --      data R:TList a = ...
 
541
        --      axiom co a :: T [a] ~ R:TList a
 
542
        -- with R:TList's algTcParent = FamInstTyCon T [a] co
 
543
 
 
544
-- | Checks the invariants of a 'TyConParent' given the appropriate type class name, if any
 
545
okParent :: Name -> TyConParent -> Bool
 
546
okParent _       NoParentTyCon                    = True
 
547
okParent tc_name (AssocFamilyTyCon cls)           = tc_name `elem` map tyConName (classATs cls)
 
548
okParent tc_name (ClassTyCon cls)                 = tc_name == tyConName (classTyCon cls)
 
549
okParent _       (FamInstTyCon fam_tc tys _co_tc) = tyConArity fam_tc == length tys
 
550
 
 
551
isNoParent :: TyConParent -> Bool
 
552
isNoParent NoParentTyCon = True
 
553
isNoParent _             = False
 
554
 
 
555
--------------------
 
556
 
 
557
-- | Information pertaining to the expansion of a type synonym (@type@)
 
558
data SynTyConRhs
 
559
  = -- | An ordinary type synonyn.
 
560
    SynonymTyCon      
 
561
       Type           -- This 'Type' is the rhs, and may mention from 'tyConTyVars'. 
 
562
                      -- It acts as a template for the expansion when the 'TyCon' 
 
563
                      -- is applied to some types.
 
564
 
 
565
   -- | A type synonym family  e.g. @type family F x y :: * -> *@
 
566
   | SynFamilyTyCon
 
567
 
 
568
--------------------
 
569
data CoTyConDesc
 
570
  = CoSym   | CoTrans
 
571
  | CoLeft  | CoRight
 
572
  | CoCsel1 | CoCsel2 | CoCselR
 
573
  | CoInst
 
574
 
 
575
  | CoAxiom     -- C tvs : F lhs-tys ~ rhs-ty
 
576
      { co_ax_tvs :: [TyVar]
 
577
      , co_ax_lhs :: Type
 
578
      , co_ax_rhs :: Type }
 
579
 
 
580
  | CoUnsafe 
 
581
\end{code}
 
582
 
 
583
Note [Enumeration types]
 
584
~~~~~~~~~~~~~~~~~~~~~~~~
 
585
We define datatypes with no constructors to not be
 
586
enumerations; this fixes trac #2578,  Otherwise we
 
587
end up generating an empty table for
 
588
  <mod>_<type>_closure_tbl
 
589
which is used by tagToEnum# to map Int# to constructors
 
590
in an enumeration. The empty table apparently upset
 
591
the linker.
 
592
 
 
593
Note [Newtype coercions]
 
594
~~~~~~~~~~~~~~~~~~~~~~~~
 
595
The NewTyCon field nt_co is a a TyCon (a coercion constructor in fact)
 
596
which is used for coercing from the representation type of the
 
597
newtype, to the newtype itself. For example,
 
598
 
 
599
   newtype T a = MkT (a -> a)
 
600
 
 
601
the NewTyCon for T will contain nt_co = CoT where CoT t : T t ~ t ->
 
602
t.  This TyCon is a CoTyCon, so it does not have a kind on its
 
603
own; it basically has its own typing rule for the fully-applied
 
604
version.  If the newtype T has k type variables then CoT has arity at
 
605
most k.  In the case that the right hand side is a type application
 
606
ending with the same type variables as the left hand side, we
 
607
"eta-contract" the coercion.  So if we had
 
608
 
 
609
   newtype S a = MkT [a]
 
610
 
 
611
then we would generate the arity 0 coercion CoS : S ~ [].  The
 
612
primary reason we do this is to make newtype deriving cleaner.
 
613
 
 
614
In the paper we'd write
 
615
        axiom CoT : (forall t. T t) ~ (forall t. [t])
 
616
and then when we used CoT at a particular type, s, we'd say
 
617
        CoT @ s
 
618
which encodes as (TyConApp instCoercionTyCon [TyConApp CoT [], s])
 
619
 
 
620
But in GHC we instead make CoT into a new piece of type syntax, CoTyCon,
 
621
(like instCoercionTyCon, symCoercionTyCon etc), which must always
 
622
be saturated, but which encodes as
 
623
        TyConApp CoT [s]
 
624
In the vocabulary of the paper it's as if we had axiom declarations
 
625
like
 
626
        axiom CoT t :  T t ~ [t]
 
627
 
 
628
Note [Newtype eta]
 
629
~~~~~~~~~~~~~~~~~~
 
630
Consider
 
631
        newtype Parser m a = MkParser (Foogle m a)
 
632
Are these two types equal (to Core)?
 
633
        Monad (Parser m) 
 
634
        Monad (Foogle m)
 
635
Well, yes.  But to see that easily we eta-reduce the RHS type of
 
636
Parser, in this case to ([], Froogle), so that even unsaturated applications
 
637
of Parser will work right.  This eta reduction is done when the type 
 
638
constructor is built, and cached in NewTyCon.  The cached field is
 
639
only used in coreExpandTyCon_maybe.
 
640
 
 
641
Here's an example that I think showed up in practice
 
642
Source code:
 
643
        newtype T a = MkT [a]
 
644
        newtype Foo m = MkFoo (forall a. m a -> Int)
 
645
 
 
646
        w1 :: Foo []
 
647
        w1 = ...
 
648
        
 
649
        w2 :: Foo T
 
650
        w2 = MkFoo (\(MkT x) -> case w1 of MkFoo f -> f x)
 
651
 
 
652
After desugaring, and discarding the data constructors for the newtypes,
 
653
we get:
 
654
        w2 :: Foo T
 
655
        w2 = w1
 
656
And now Lint complains unless Foo T == Foo [], and that requires T==[]
 
657
 
 
658
This point carries over to the newtype coercion, because we need to
 
659
say 
 
660
        w2 = w1 `cast` Foo CoT
 
661
 
 
662
so the coercion tycon CoT must have 
 
663
        kind:    T ~ []
 
664
 and    arity:   0
 
665
 
 
666
 
 
667
%************************************************************************
 
668
%*                                                                      *
 
669
\subsection{PrimRep}
 
670
%*                                                                      *
 
671
%************************************************************************
 
672
 
 
673
A PrimRep is somewhat similar to a CgRep (see codeGen/SMRep) and a
 
674
MachRep (see cmm/CmmExpr), although each of these types has a distinct
 
675
and clearly defined purpose:
 
676
 
 
677
  - A PrimRep is a CgRep + information about signedness + information
 
678
    about primitive pointers (AddrRep).  Signedness and primitive
 
679
    pointers are required when passing a primitive type to a foreign
 
680
    function, but aren't needed for call/return conventions of Haskell
 
681
    functions.
 
682
 
 
683
  - A MachRep is a basic machine type (non-void, doesn't contain
 
684
    information on pointerhood or signedness, but contains some
 
685
    reps that don't have corresponding Haskell types).
 
686
 
 
687
\begin{code}
 
688
-- | A 'PrimRep' is an abstraction of a type.  It contains information that
 
689
-- the code generator needs in order to pass arguments, return results,
 
690
-- and store values of this type.
 
691
data PrimRep
 
692
  = VoidRep
 
693
  | PtrRep
 
694
  | IntRep              -- ^ Signed, word-sized value
 
695
  | WordRep             -- ^ Unsigned, word-sized value
 
696
  | Int64Rep            -- ^ Signed, 64 bit value (with 32-bit words only)
 
697
  | Word64Rep           -- ^ Unsigned, 64 bit value (with 32-bit words only)
 
698
  | AddrRep             -- ^ A pointer, but /not/ to a Haskell value (use 'PtrRep')
 
699
  | FloatRep
 
700
  | DoubleRep
 
701
  deriving( Eq, Show )
 
702
 
 
703
instance Outputable PrimRep where
 
704
  ppr r = text (show r)
 
705
 
 
706
-- | Find the size of a 'PrimRep', in words
 
707
primRepSizeW :: PrimRep -> Int
 
708
primRepSizeW IntRep   = 1
 
709
primRepSizeW WordRep  = 1
 
710
primRepSizeW Int64Rep = wORD64_SIZE `quot` wORD_SIZE
 
711
primRepSizeW Word64Rep= wORD64_SIZE `quot` wORD_SIZE
 
712
primRepSizeW FloatRep = 1    -- NB. might not take a full word
 
713
primRepSizeW DoubleRep= dOUBLE_SIZE `quot` wORD_SIZE
 
714
primRepSizeW AddrRep  = 1
 
715
primRepSizeW PtrRep   = 1
 
716
primRepSizeW VoidRep  = 0
 
717
\end{code}
 
718
 
 
719
%************************************************************************
 
720
%*                                                                      *
 
721
\subsection{TyCon Construction}
 
722
%*                                                                      *
 
723
%************************************************************************
 
724
 
 
725
Note: the TyCon constructors all take a Kind as one argument, even though
 
726
they could, in principle, work out their Kind from their other arguments.
 
727
But to do so they need functions from Types, and that makes a nasty
 
728
module mutual-recursion.  And they aren't called from many places.
 
729
So we compromise, and move their Kind calculation to the call site.
 
730
 
 
731
\begin{code}
 
732
-- | Given the name of the function type constructor and it's kind, create the
 
733
-- corresponding 'TyCon'. It is reccomended to use 'TypeRep.funTyCon' if you want 
 
734
-- this functionality
 
735
mkFunTyCon :: Name -> Kind -> TyCon
 
736
mkFunTyCon name kind 
 
737
  = FunTyCon { 
 
738
        tyConUnique = nameUnique name,
 
739
        tyConName   = name,
 
740
        tc_kind   = kind,
 
741
        tyConArity  = 2
 
742
    }
 
743
 
 
744
-- | This is the making of an algebraic 'TyCon'. Notably, you have to
 
745
-- pass in the generic (in the -XGenerics sense) information about the
 
746
-- type constructor - you can get hold of it easily (see Generics
 
747
-- module)
 
748
mkAlgTyCon :: Name
 
749
           -> Kind              -- ^ Kind of the resulting 'TyCon'
 
750
           -> [TyVar]           -- ^ 'TyVar's scoped over: see 'tyConTyVars'. 
 
751
                                --   Arity is inferred from the length of this list
 
752
           -> [PredType]        -- ^ Stupid theta: see 'algTcStupidTheta'
 
753
           -> AlgTyConRhs       -- ^ Information about dat aconstructors
 
754
           -> TyConParent
 
755
           -> RecFlag           -- ^ Is the 'TyCon' recursive?
 
756
           -> Bool              -- ^ Does it have generic functions? See 'hasGenerics'
 
757
           -> Bool              -- ^ Was the 'TyCon' declared with GADT syntax?
 
758
           -> TyCon
 
759
mkAlgTyCon name kind tyvars stupid rhs parent is_rec gen_info gadt_syn
 
760
  = AlgTyCon {  
 
761
        tyConName        = name,
 
762
        tyConUnique      = nameUnique name,
 
763
        tc_kind          = kind,
 
764
        tyConArity       = length tyvars,
 
765
        tyConTyVars      = tyvars,
 
766
        algTcStupidTheta = stupid,
 
767
        algTcRhs         = rhs,
 
768
        algTcParent      = ASSERT( okParent name parent ) parent,
 
769
        algTcRec         = is_rec,
 
770
        algTcGadtSyntax  = gadt_syn,
 
771
        hasGenerics      = gen_info
 
772
    }
 
773
 
 
774
-- | Simpler specialization of 'mkAlgTyCon' for classes
 
775
mkClassTyCon :: Name -> Kind -> [TyVar] -> AlgTyConRhs -> Class -> RecFlag -> TyCon
 
776
mkClassTyCon name kind tyvars rhs clas is_rec =
 
777
  mkAlgTyCon name kind tyvars [] rhs (ClassTyCon clas) is_rec False False
 
778
 
 
779
mkTupleTyCon :: Name 
 
780
             -> Kind    -- ^ Kind of the resulting 'TyCon'
 
781
             -> Arity   -- ^ Arity of the tuple
 
782
             -> [TyVar] -- ^ 'TyVar's scoped over: see 'tyConTyVars'
 
783
             -> DataCon 
 
784
             -> Boxity  -- ^ Whether the tuple is boxed or unboxed
 
785
             -> Bool    -- ^ Does it have generic functions? See 'hasGenerics'
 
786
             -> TyCon
 
787
mkTupleTyCon name kind arity tyvars con boxed gen_info
 
788
  = TupleTyCon {
 
789
        tyConUnique = nameUnique name,
 
790
        tyConName = name,
 
791
        tc_kind = kind,
 
792
        tyConArity = arity,
 
793
        tyConBoxed = boxed,
 
794
        tyConTyVars = tyvars,
 
795
        dataCon = con,
 
796
        hasGenerics = gen_info
 
797
    }
 
798
 
 
799
-- ^ Foreign-imported (.NET) type constructors are represented
 
800
-- as primitive, but /lifted/, 'TyCons' for now. They are lifted
 
801
-- because the Haskell type @T@ representing the (foreign) .NET
 
802
-- type @T@ is actually implemented (in ILX) as a @thunk<T>@
 
803
mkForeignTyCon :: Name 
 
804
               -> Maybe FastString -- ^ Name of the foreign imported thing, maybe
 
805
               -> Kind 
 
806
               -> Arity 
 
807
               -> TyCon
 
808
mkForeignTyCon name ext_name kind arity
 
809
  = PrimTyCon {
 
810
        tyConName    = name,
 
811
        tyConUnique  = nameUnique name,
 
812
        tc_kind    = kind,
 
813
        tyConArity   = arity,
 
814
        primTyConRep = PtrRep, -- they all do
 
815
        isUnLifted   = False,
 
816
        tyConExtName = ext_name
 
817
    }
 
818
 
 
819
 
 
820
-- | Create an unlifted primitive 'TyCon', such as @Int#@
 
821
mkPrimTyCon :: Name  -> Kind -> Arity -> PrimRep -> TyCon
 
822
mkPrimTyCon name kind arity rep
 
823
  = mkPrimTyCon' name kind arity rep True  
 
824
 
 
825
-- | Kind constructors
 
826
mkKindTyCon :: Name -> Kind -> TyCon
 
827
mkKindTyCon name kind
 
828
  = mkPrimTyCon' name kind 0 VoidRep True  
 
829
 
 
830
-- | Create a lifted primitive 'TyCon' such as @RealWorld@
 
831
mkLiftedPrimTyCon :: Name  -> Kind -> Arity -> PrimRep -> TyCon
 
832
mkLiftedPrimTyCon name kind arity rep
 
833
  = mkPrimTyCon' name kind arity rep False
 
834
 
 
835
mkPrimTyCon' :: Name  -> Kind -> Arity -> PrimRep -> Bool -> TyCon
 
836
mkPrimTyCon' name kind arity rep is_unlifted
 
837
  = PrimTyCon {
 
838
        tyConName    = name,
 
839
        tyConUnique  = nameUnique name,
 
840
        tc_kind    = kind,
 
841
        tyConArity   = arity,
 
842
        primTyConRep = rep,
 
843
        isUnLifted   = is_unlifted,
 
844
        tyConExtName = Nothing
 
845
    }
 
846
 
 
847
-- | Create a type synonym 'TyCon'
 
848
mkSynTyCon :: Name -> Kind -> [TyVar] -> SynTyConRhs -> TyConParent -> TyCon
 
849
mkSynTyCon name kind tyvars rhs parent
 
850
  = SynTyCon {  
 
851
        tyConName = name,
 
852
        tyConUnique = nameUnique name,
 
853
        tc_kind = kind,
 
854
        tyConArity = length tyvars,
 
855
        tyConTyVars = tyvars,
 
856
        synTcRhs = rhs,
 
857
        synTcParent = parent
 
858
    }
 
859
 
 
860
-- | Create a coercion 'TyCon'
 
861
mkCoercionTyCon :: Name -> Arity 
 
862
                -> CoTyConDesc
 
863
                -> TyCon
 
864
mkCoercionTyCon name arity desc
 
865
  = CoTyCon {
 
866
        tyConName   = name,
 
867
        tyConUnique = nameUnique name,
 
868
        tyConArity  = arity,
 
869
        coTcDesc    = desc }
 
870
 
 
871
mkAnyTyCon :: Name -> Kind -> TyCon
 
872
mkAnyTyCon name kind 
 
873
  = AnyTyCon {  tyConName = name,
 
874
                tc_kind = kind,
 
875
                tyConUnique = nameUnique name }
 
876
 
 
877
-- | Create a super-kind 'TyCon'
 
878
mkSuperKindTyCon :: Name -> TyCon -- Super kinds always have arity zero
 
879
mkSuperKindTyCon name
 
880
  = SuperKindTyCon {
 
881
        tyConName = name,
 
882
        tyConUnique = nameUnique name
 
883
  }
 
884
\end{code}
 
885
 
 
886
\begin{code}
 
887
isFunTyCon :: TyCon -> Bool
 
888
isFunTyCon (FunTyCon {}) = True
 
889
isFunTyCon _             = False
 
890
 
 
891
-- | Test if the 'TyCon' is algebraic but abstract (invisible data constructors)
 
892
isAbstractTyCon :: TyCon -> Bool
 
893
isAbstractTyCon (AlgTyCon { algTcRhs = AbstractTyCon }) = True
 
894
isAbstractTyCon _ = False
 
895
 
 
896
-- | Make an algebraic 'TyCon' abstract. Panics if the supplied 'TyCon' is not algebraic
 
897
makeTyConAbstract :: TyCon -> TyCon
 
898
makeTyConAbstract tc@(AlgTyCon {}) = tc { algTcRhs = AbstractTyCon }
 
899
makeTyConAbstract tc = pprPanic "makeTyConAbstract" (ppr tc)
 
900
 
 
901
-- | Does this 'TyCon' represent something that cannot be defined in Haskell?
 
902
isPrimTyCon :: TyCon -> Bool
 
903
isPrimTyCon (PrimTyCon {}) = True
 
904
isPrimTyCon _              = False
 
905
 
 
906
-- | Is this 'TyCon' unlifted (i.e. cannot contain bottom)? Note that this can only
 
907
-- be true for primitive and unboxed-tuple 'TyCon's
 
908
isUnLiftedTyCon :: TyCon -> Bool
 
909
isUnLiftedTyCon (PrimTyCon  {isUnLifted = is_unlifted}) = is_unlifted
 
910
isUnLiftedTyCon (TupleTyCon {tyConBoxed = boxity})      = not (isBoxed boxity)
 
911
isUnLiftedTyCon _                                       = False
 
912
 
 
913
-- | Returns @True@ if the supplied 'TyCon' resulted from either a
 
914
-- @data@ or @newtype@ declaration
 
915
isAlgTyCon :: TyCon -> Bool
 
916
isAlgTyCon (AlgTyCon {})   = True
 
917
isAlgTyCon (TupleTyCon {}) = True
 
918
isAlgTyCon _               = False
 
919
 
 
920
isDataTyCon :: TyCon -> Bool
 
921
-- ^ Returns @True@ for data types that are /definitely/ represented by 
 
922
-- heap-allocated constructors.  These are scrutinised by Core-level 
 
923
-- @case@ expressions, and they get info tables allocated for them.
 
924
-- 
 
925
-- Generally, the function will be true for all @data@ types and false
 
926
-- for @newtype@s, unboxed tuples and type family 'TyCon's. But it is
 
927
-- not guarenteed to return @True@ in all cases that it could.
 
928
-- 
 
929
-- NB: for a data type family, only the /instance/ 'TyCon's
 
930
--     get an info table.  The family declaration 'TyCon' does not
 
931
isDataTyCon (AlgTyCon {algTcRhs = rhs})
 
932
  = case rhs of
 
933
        DataFamilyTyCon {}  -> False
 
934
        DataTyCon {}  -> True
 
935
        NewTyCon {}   -> False
 
936
        AbstractTyCon -> False   -- We don't know, so return False
 
937
isDataTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
 
938
isDataTyCon _ = False
 
939
 
 
940
-- | Is this 'TyCon' that for a @newtype@
 
941
isNewTyCon :: TyCon -> Bool
 
942
isNewTyCon (AlgTyCon {algTcRhs = NewTyCon {}}) = True
 
943
isNewTyCon _                                   = False
 
944
 
 
945
-- | Take a 'TyCon' apart into the 'TyVar's it scopes over, the 'Type' it expands
 
946
-- into, and (possibly) a coercion from the representation type to the @newtype@.
 
947
-- Returns @Nothing@ if this is not possible.
 
948
unwrapNewTyCon_maybe :: TyCon -> Maybe ([TyVar], Type, Maybe TyCon)
 
949
unwrapNewTyCon_maybe (AlgTyCon { tyConTyVars = tvs, 
 
950
                                 algTcRhs = NewTyCon { nt_co = mb_co, 
 
951
                                                       nt_rhs = rhs }})
 
952
                           = Just (tvs, rhs, mb_co)
 
953
unwrapNewTyCon_maybe _     = Nothing
 
954
 
 
955
isProductTyCon :: TyCon -> Bool
 
956
-- | A /product/ 'TyCon' must both:
 
957
--
 
958
-- 1. Have /one/ constructor
 
959
-- 
 
960
-- 2. /Not/ be existential
 
961
-- 
 
962
-- However other than this there are few restrictions: they may be @data@ or @newtype@ 
 
963
-- 'TyCon's of any boxity and may even be recursive.
 
964
isProductTyCon tc@(AlgTyCon {}) = case algTcRhs tc of
 
965
                                    DataTyCon{ data_cons = [data_con] } 
 
966
                                                -> isVanillaDataCon data_con
 
967
                                    NewTyCon {} -> True
 
968
                                    _           -> False
 
969
isProductTyCon (TupleTyCon {})  = True   
 
970
isProductTyCon _                = False
 
971
 
 
972
-- | Is this a 'TyCon' representing a type synonym (@type@)?
 
973
isSynTyCon :: TyCon -> Bool
 
974
isSynTyCon (SynTyCon {}) = True
 
975
isSynTyCon _             = False
 
976
 
 
977
-- As for newtypes, it is in some contexts important to distinguish between
 
978
-- closed synonyms and synonym families, as synonym families have no unique
 
979
-- right hand side to which a synonym family application can expand.
 
980
--
 
981
 
 
982
isDecomposableTyCon :: TyCon -> Bool
 
983
-- True iff we can decompose (T a b c) into ((T a b) c)
 
984
-- Specifically NOT true of synonyms (open and otherwise) and coercions
 
985
isDecomposableTyCon (SynTyCon {}) = False
 
986
isDecomposableTyCon (CoTyCon {})  = False
 
987
isDecomposableTyCon _other        = True
 
988
 
 
989
-- | Is this an algebraic 'TyCon' declared with the GADT syntax?
 
990
isGadtSyntaxTyCon :: TyCon -> Bool
 
991
isGadtSyntaxTyCon (AlgTyCon { algTcGadtSyntax = res }) = res
 
992
isGadtSyntaxTyCon _                                    = False
 
993
 
 
994
-- | Is this an algebraic 'TyCon' which is just an enumeration of values?
 
995
isEnumerationTyCon :: TyCon -> Bool
 
996
-- See Note [Enumeration types] in TyCon
 
997
isEnumerationTyCon (AlgTyCon {algTcRhs = DataTyCon { is_enum = res }}) = res
 
998
isEnumerationTyCon (TupleTyCon {tyConArity = arity}) = arity == 0
 
999
isEnumerationTyCon _                                                   = False
 
1000
 
 
1001
-- | Is this a 'TyCon', synonym or otherwise, that may have further instances appear?
 
1002
isFamilyTyCon :: TyCon -> Bool
 
1003
isFamilyTyCon (SynTyCon {synTcRhs = SynFamilyTyCon {}})  = True
 
1004
isFamilyTyCon (AlgTyCon {algTcRhs = DataFamilyTyCon {}}) = True
 
1005
isFamilyTyCon _ = False
 
1006
 
 
1007
-- | Is this a synonym 'TyCon' that can have may have further instances appear?
 
1008
isSynFamilyTyCon :: TyCon -> Bool
 
1009
isSynFamilyTyCon (SynTyCon {synTcRhs = SynFamilyTyCon {}}) = True
 
1010
isSynFamilyTyCon _ = False
 
1011
 
 
1012
-- | Is this a synonym 'TyCon' that can have may have further instances appear?
 
1013
isDataFamilyTyCon :: TyCon -> Bool
 
1014
isDataFamilyTyCon (AlgTyCon {algTcRhs = DataFamilyTyCon {}}) = True
 
1015
isDataFamilyTyCon _ = False
 
1016
 
 
1017
-- | Is this a synonym 'TyCon' that can have no further instances appear?
 
1018
isClosedSynTyCon :: TyCon -> Bool
 
1019
isClosedSynTyCon tycon = isSynTyCon tycon && not (isFamilyTyCon tycon)
 
1020
 
 
1021
-- | Injective 'TyCon's can be decomposed, so that
 
1022
--     T ty1 ~ T ty2  =>  ty1 ~ ty2
 
1023
isInjectiveTyCon :: TyCon -> Bool
 
1024
isInjectiveTyCon tc = not (isSynTyCon tc)
 
1025
        -- Ultimately we may have injective associated types
 
1026
        -- in which case this test will become more interesting
 
1027
        --
 
1028
        -- It'd be unusual to call isInjectiveTyCon on a regular H98
 
1029
        -- type synonym, because you should probably have expanded it first
 
1030
        -- But regardless, it's not injective!
 
1031
 
 
1032
-- | Are we able to extract informationa 'TyVar' to class argument list
 
1033
-- mappping from a given 'TyCon'?
 
1034
isTyConAssoc :: TyCon -> Bool
 
1035
isTyConAssoc tc = case tyConParent tc of
 
1036
                     AssocFamilyTyCon {} -> True
 
1037
                     _                   -> False
 
1038
 
 
1039
-- The unit tycon didn't used to be classed as a tuple tycon
 
1040
-- but I thought that was silly so I've undone it
 
1041
-- If it can't be for some reason, it should be a AlgTyCon
 
1042
isTupleTyCon :: TyCon -> Bool
 
1043
-- ^ Does this 'TyCon' represent a tuple?
 
1044
--
 
1045
-- NB: when compiling @Data.Tuple@, the tycons won't reply @True@ to
 
1046
-- 'isTupleTyCon', becuase they are built as 'AlgTyCons'.  However they
 
1047
-- get spat into the interface file as tuple tycons, so I don't think
 
1048
-- it matters.
 
1049
isTupleTyCon (TupleTyCon {}) = True
 
1050
isTupleTyCon _               = False
 
1051
 
 
1052
-- | Is this the 'TyCon' for an unboxed tuple?
 
1053
isUnboxedTupleTyCon :: TyCon -> Bool
 
1054
isUnboxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = not (isBoxed boxity)
 
1055
isUnboxedTupleTyCon _                                  = False
 
1056
 
 
1057
-- | Is this the 'TyCon' for a boxed tuple?
 
1058
isBoxedTupleTyCon :: TyCon -> Bool
 
1059
isBoxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
 
1060
isBoxedTupleTyCon _                                  = False
 
1061
 
 
1062
-- | Extract the boxity of the given 'TyCon', if it is a 'TupleTyCon'.
 
1063
-- Panics otherwise
 
1064
tupleTyConBoxity :: TyCon -> Boxity
 
1065
tupleTyConBoxity tc = tyConBoxed tc
 
1066
 
 
1067
-- | Is this a recursive 'TyCon'?
 
1068
isRecursiveTyCon :: TyCon -> Bool
 
1069
isRecursiveTyCon (AlgTyCon {algTcRec = Recursive}) = True
 
1070
isRecursiveTyCon _                                 = False
 
1071
 
 
1072
-- | Did this 'TyCon' originate from type-checking a .h*-boot file?
 
1073
isHiBootTyCon :: TyCon -> Bool
 
1074
-- Used for knot-tying in hi-boot files
 
1075
isHiBootTyCon (AlgTyCon {algTcRhs = AbstractTyCon}) = True
 
1076
isHiBootTyCon _                                     = False
 
1077
 
 
1078
-- | Is this the 'TyCon' of a foreign-imported type constructor?
 
1079
isForeignTyCon :: TyCon -> Bool
 
1080
isForeignTyCon (PrimTyCon {tyConExtName = Just _}) = True
 
1081
isForeignTyCon _                                   = False
 
1082
 
 
1083
-- | Is this a super-kind 'TyCon'?
 
1084
isSuperKindTyCon :: TyCon -> Bool
 
1085
isSuperKindTyCon (SuperKindTyCon {}) = True
 
1086
isSuperKindTyCon _                   = False
 
1087
 
 
1088
-- | Is this an AnyTyCon?
 
1089
isAnyTyCon :: TyCon -> Bool
 
1090
isAnyTyCon (AnyTyCon {}) = True
 
1091
isAnyTyCon _              = False
 
1092
 
 
1093
-- | Attempt to pull a 'TyCon' apart into the arity and 'coKindFun' of
 
1094
-- a coercion 'TyCon'. Returns @Nothing@ if the 'TyCon' is not of the
 
1095
-- appropriate kind
 
1096
isCoercionTyCon_maybe :: TyCon -> Maybe (Arity, CoTyConDesc)
 
1097
isCoercionTyCon_maybe (CoTyCon {tyConArity = ar, coTcDesc = desc}) 
 
1098
  = Just (ar, desc)
 
1099
isCoercionTyCon_maybe _ = Nothing
 
1100
 
 
1101
-- | Is this a 'TyCon' that represents a coercion?
 
1102
isCoercionTyCon :: TyCon -> Bool
 
1103
isCoercionTyCon (CoTyCon {}) = True
 
1104
isCoercionTyCon _            = False
 
1105
 
 
1106
-- | Identifies implicit tycons that, in particular, do not go into interface
 
1107
-- files (because they are implicitly reconstructed when the interface is
 
1108
-- read).
 
1109
--
 
1110
-- Note that:
 
1111
--
 
1112
-- * Associated families are implicit, as they are re-constructed from
 
1113
--   the class declaration in which they reside, and 
 
1114
--
 
1115
-- * Family instances are /not/ implicit as they represent the instance body
 
1116
--   (similar to a @dfun@ does that for a class instance).
 
1117
isImplicitTyCon :: TyCon -> Bool
 
1118
isImplicitTyCon tycon | isTyConAssoc tycon           = True
 
1119
                      | isSynTyCon tycon             = False
 
1120
                      | isAlgTyCon tycon             = isClassTyCon tycon ||
 
1121
                                                       isTupleTyCon tycon
 
1122
isImplicitTyCon _other                               = True
 
1123
        -- catches: FunTyCon, PrimTyCon, 
 
1124
        -- CoTyCon, SuperKindTyCon
 
1125
\end{code}
 
1126
 
 
1127
 
 
1128
-----------------------------------------------
 
1129
--      Expand type-constructor applications
 
1130
-----------------------------------------------
 
1131
 
 
1132
\begin{code}
 
1133
tcExpandTyCon_maybe, coreExpandTyCon_maybe 
 
1134
        :: TyCon 
 
1135
        -> [Type]                       -- ^ Arguments to 'TyCon'
 
1136
        -> Maybe ([(TyVar,Type)],       
 
1137
                  Type,                 
 
1138
                  [Type])               -- ^ Returns a 'TyVar' substitution, the body type
 
1139
                                        -- of the synonym (not yet substituted) and any arguments
 
1140
                                        -- remaining from the application
 
1141
 
 
1142
-- ^ Used to create the view the /typechecker/ has on 'TyCon's. We expand (closed) synonyms only, cf. 'coreExpandTyCon_maybe'
 
1143
tcExpandTyCon_maybe (SynTyCon {tyConTyVars = tvs, 
 
1144
                               synTcRhs = SynonymTyCon rhs }) tys
 
1145
   = expand tvs rhs tys
 
1146
tcExpandTyCon_maybe _ _ = Nothing
 
1147
 
 
1148
---------------
 
1149
 
 
1150
-- ^ Used to create the view /Core/ has on 'TyCon's. We expand not only closed synonyms like 'tcExpandTyCon_maybe',
 
1151
-- but also non-recursive @newtype@s
 
1152
coreExpandTyCon_maybe (AlgTyCon {
 
1153
         algTcRhs = NewTyCon { nt_etad_rhs = etad_rhs, nt_co = Nothing }}) tys
 
1154
   = case etad_rhs of   -- Don't do this in the pattern match, lest we accidentally
 
1155
                        -- match the etad_rhs of a *recursive* newtype
 
1156
        (tvs,rhs) -> expand tvs rhs tys
 
1157
 
 
1158
coreExpandTyCon_maybe tycon tys = tcExpandTyCon_maybe tycon tys
 
1159
 
 
1160
 
 
1161
----------------
 
1162
expand  :: [TyVar] -> Type                      -- Template
 
1163
        -> [Type]                               -- Args
 
1164
        -> Maybe ([(TyVar,Type)], Type, [Type]) -- Expansion
 
1165
expand tvs rhs tys
 
1166
  = case n_tvs `compare` length tys of
 
1167
        LT -> Just (tvs `zip` tys, rhs, drop n_tvs tys)
 
1168
        EQ -> Just (tvs `zip` tys, rhs, [])
 
1169
        GT -> Nothing
 
1170
   where
 
1171
     n_tvs = length tvs
 
1172
\end{code}
 
1173
 
 
1174
\begin{code}
 
1175
-- | Does this 'TyCon' have any generic to\/from functions available? See also 'hasGenerics'
 
1176
tyConHasGenerics :: TyCon -> Bool
 
1177
tyConHasGenerics (AlgTyCon {hasGenerics = hg})   = hg
 
1178
tyConHasGenerics (TupleTyCon {hasGenerics = hg}) = hg
 
1179
tyConHasGenerics _                               = False        -- Synonyms
 
1180
 
 
1181
tyConKind :: TyCon -> Kind
 
1182
tyConKind (FunTyCon   { tc_kind = k }) = k
 
1183
tyConKind (AlgTyCon   { tc_kind = k }) = k
 
1184
tyConKind (TupleTyCon { tc_kind = k }) = k
 
1185
tyConKind (SynTyCon   { tc_kind = k }) = k
 
1186
tyConKind (PrimTyCon  { tc_kind = k }) = k
 
1187
tyConKind (AnyTyCon   { tc_kind = k }) = k
 
1188
tyConKind tc = pprPanic "tyConKind" (ppr tc)    -- SuperKindTyCon and CoTyCon
 
1189
 
 
1190
tyConHasKind :: TyCon -> Bool
 
1191
tyConHasKind (SuperKindTyCon {}) = False
 
1192
tyConHasKind (CoTyCon {})        = False
 
1193
tyConHasKind _                   = True
 
1194
 
 
1195
-- | As 'tyConDataCons_maybe', but returns the empty list of constructors if no constructors
 
1196
-- could be found
 
1197
tyConDataCons :: TyCon -> [DataCon]
 
1198
-- It's convenient for tyConDataCons to return the
 
1199
-- empty list for type synonyms etc
 
1200
tyConDataCons tycon = tyConDataCons_maybe tycon `orElse` []
 
1201
 
 
1202
-- | Determine the 'DataCon's originating from the given 'TyCon', if the 'TyCon' is the
 
1203
-- sort that can have any constructors (note: this does not include abstract algebraic types)
 
1204
tyConDataCons_maybe :: TyCon -> Maybe [DataCon]
 
1205
tyConDataCons_maybe (AlgTyCon {algTcRhs = DataTyCon { data_cons = cons }}) = Just cons
 
1206
tyConDataCons_maybe (AlgTyCon {algTcRhs = NewTyCon { data_con = con }})    = Just [con]
 
1207
tyConDataCons_maybe (TupleTyCon {dataCon = con})                           = Just [con]
 
1208
tyConDataCons_maybe _                                                      = Nothing
 
1209
 
 
1210
-- | Determine the number of value constructors a 'TyCon' has. Panics if the 'TyCon'
 
1211
-- is not algebraic or a tuple
 
1212
tyConFamilySize  :: TyCon -> Int
 
1213
tyConFamilySize (AlgTyCon   {algTcRhs = DataTyCon {data_cons = cons}}) = 
 
1214
  length cons
 
1215
tyConFamilySize (AlgTyCon   {algTcRhs = NewTyCon {}})        = 1
 
1216
tyConFamilySize (AlgTyCon   {algTcRhs = DataFamilyTyCon {}}) = 0
 
1217
tyConFamilySize (TupleTyCon {})                              = 1
 
1218
tyConFamilySize other = pprPanic "tyConFamilySize:" (ppr other)
 
1219
 
 
1220
-- | Extract an 'AlgTyConRhs' with information about data constructors from an algebraic or tuple
 
1221
-- 'TyCon'. Panics for any other sort of 'TyCon'
 
1222
algTyConRhs :: TyCon -> AlgTyConRhs
 
1223
algTyConRhs (AlgTyCon {algTcRhs = rhs}) = rhs
 
1224
algTyConRhs (TupleTyCon {dataCon = con, tyConArity = arity})
 
1225
    = DataTyCon { data_cons = [con], is_enum = arity == 0 }
 
1226
algTyConRhs other = pprPanic "algTyConRhs" (ppr other)
 
1227
\end{code}
 
1228
 
 
1229
\begin{code}
 
1230
-- | Extract the bound type variables and type expansion of a type synonym 'TyCon'. Panics if the
 
1231
-- 'TyCon' is not a synonym
 
1232
newTyConRhs :: TyCon -> ([TyVar], Type)
 
1233
newTyConRhs (AlgTyCon {tyConTyVars = tvs, algTcRhs = NewTyCon { nt_rhs = rhs }}) = (tvs, rhs)
 
1234
newTyConRhs tycon = pprPanic "newTyConRhs" (ppr tycon)
 
1235
 
 
1236
-- | Extract the bound type variables and type expansion of an eta-contracted type synonym 'TyCon'.
 
1237
-- Panics if the 'TyCon' is not a synonym
 
1238
newTyConEtadRhs :: TyCon -> ([TyVar], Type)
 
1239
newTyConEtadRhs (AlgTyCon {algTcRhs = NewTyCon { nt_etad_rhs = tvs_rhs }}) = tvs_rhs
 
1240
newTyConEtadRhs tycon = pprPanic "newTyConEtadRhs" (ppr tycon)
 
1241
 
 
1242
-- | Extracts the @newtype@ coercion from such a 'TyCon', which can be used to construct something
 
1243
-- with the @newtype@s type from its representation type (right hand side). If the supplied 'TyCon'
 
1244
-- is not a @newtype@, returns @Nothing@
 
1245
newTyConCo_maybe :: TyCon -> Maybe TyCon
 
1246
newTyConCo_maybe (AlgTyCon {algTcRhs = NewTyCon { nt_co = co }}) = co
 
1247
newTyConCo_maybe _                                               = Nothing
 
1248
 
 
1249
-- | Find the primitive representation of a 'TyCon'
 
1250
tyConPrimRep :: TyCon -> PrimRep
 
1251
tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep
 
1252
tyConPrimRep tc = ASSERT(not (isUnboxedTupleTyCon tc)) PtrRep
 
1253
\end{code}
 
1254
 
 
1255
\begin{code}
 
1256
-- | Find the \"stupid theta\" of the 'TyCon'. A \"stupid theta\" is the context to the left of
 
1257
-- an algebraic type declaration, e.g. @Eq a@ in the declaration @data Eq a => T a ...@
 
1258
tyConStupidTheta :: TyCon -> [PredType]
 
1259
tyConStupidTheta (AlgTyCon {algTcStupidTheta = stupid}) = stupid
 
1260
tyConStupidTheta (TupleTyCon {})                        = []
 
1261
tyConStupidTheta tycon = pprPanic "tyConStupidTheta" (ppr tycon)
 
1262
\end{code}
 
1263
 
 
1264
\begin{code}
 
1265
-- | Extract the 'TyVar's bound by a type synonym and the corresponding (unsubstituted) right hand side.
 
1266
-- If the given 'TyCon' is not a type synonym, panics
 
1267
synTyConDefn :: TyCon -> ([TyVar], Type)
 
1268
synTyConDefn (SynTyCon {tyConTyVars = tyvars, synTcRhs = SynonymTyCon ty}) 
 
1269
  = (tyvars, ty)
 
1270
synTyConDefn tycon = pprPanic "getSynTyConDefn" (ppr tycon)
 
1271
 
 
1272
-- | Extract the information pertaining to the right hand side of a type synonym (@type@) declaration. Panics
 
1273
-- if the given 'TyCon' is not a type synonym
 
1274
synTyConRhs :: TyCon -> SynTyConRhs
 
1275
synTyConRhs (SynTyCon {synTcRhs = rhs}) = rhs
 
1276
synTyConRhs tc                          = pprPanic "synTyConRhs" (ppr tc)
 
1277
 
 
1278
-- | Find the expansion of the type synonym represented by the given 'TyCon'. The free variables of this
 
1279
-- type will typically include those 'TyVar's bound by the 'TyCon'. Panics if the 'TyCon' is not that of
 
1280
-- a type synonym
 
1281
synTyConType :: TyCon -> Type
 
1282
synTyConType tc = case synTcRhs tc of
 
1283
                    SynonymTyCon t -> t
 
1284
                    _              -> pprPanic "synTyConType" (ppr tc)
 
1285
\end{code}
 
1286
 
 
1287
\begin{code}
 
1288
-- | If the given 'TyCon' has a /single/ data constructor, i.e. it is a @data@ type with one
 
1289
-- alternative, a tuple type or a @newtype@ then that constructor is returned. If the 'TyCon'
 
1290
-- has more than one constructor, or represents a primitive or function type constructor then
 
1291
-- @Nothing@ is returned. In any other case, the function panics
 
1292
tyConSingleDataCon_maybe :: TyCon -> Maybe DataCon
 
1293
tyConSingleDataCon_maybe (TupleTyCon {dataCon = c})                            = Just c
 
1294
tyConSingleDataCon_maybe (AlgTyCon {algTcRhs = DataTyCon { data_cons = [c] }}) = Just c
 
1295
tyConSingleDataCon_maybe (AlgTyCon {algTcRhs = NewTyCon { data_con = c }})     = Just c
 
1296
tyConSingleDataCon_maybe _                                                     = Nothing
 
1297
\end{code}
 
1298
 
 
1299
\begin{code}
 
1300
-- | Is this 'TyCon' that for a class instance?
 
1301
isClassTyCon :: TyCon -> Bool
 
1302
isClassTyCon (AlgTyCon {algTcParent = ClassTyCon _}) = True
 
1303
isClassTyCon _                                       = False
 
1304
 
 
1305
-- | If this 'TyCon' is that for a class instance, return the class it is for.
 
1306
-- Otherwise returns @Nothing@
 
1307
tyConClass_maybe :: TyCon -> Maybe Class
 
1308
tyConClass_maybe (AlgTyCon {algTcParent = ClassTyCon clas}) = Just clas
 
1309
tyConClass_maybe _                                          = Nothing
 
1310
 
 
1311
----------------------------------------------------------------------------
 
1312
tyConParent :: TyCon -> TyConParent
 
1313
tyConParent (AlgTyCon {algTcParent = parent}) = parent
 
1314
tyConParent (SynTyCon {synTcParent = parent}) = parent
 
1315
tyConParent _                                 = NoParentTyCon
 
1316
 
 
1317
-- | Is this 'TyCon' that for a family instance, be that for a synonym or an
 
1318
-- algebraic family instance?
 
1319
isFamInstTyCon :: TyCon -> Bool
 
1320
isFamInstTyCon tc = case tyConParent tc of
 
1321
                      FamInstTyCon {} -> True
 
1322
                      _               -> False
 
1323
 
 
1324
tyConFamInstSig_maybe :: TyCon -> Maybe (TyCon, [Type], TyCon)
 
1325
tyConFamInstSig_maybe tc
 
1326
  = case tyConParent tc of
 
1327
      FamInstTyCon f ts co_tc -> Just (f, ts, co_tc)
 
1328
      _                       -> Nothing
 
1329
 
 
1330
-- | If this 'TyCon' is that of a family instance, return the family in question
 
1331
-- and the instance types. Otherwise, return @Nothing@
 
1332
tyConFamInst_maybe :: TyCon -> Maybe (TyCon, [Type])
 
1333
tyConFamInst_maybe tc
 
1334
  = case tyConParent tc of
 
1335
      FamInstTyCon f ts _ -> Just (f, ts)
 
1336
      _                   -> Nothing
 
1337
 
 
1338
-- | If this 'TyCon' is that of a family instance, return a 'TyCon' which represents 
 
1339
-- a coercion identifying the representation type with the type instance family.
 
1340
-- Otherwise, return @Nothing@
 
1341
tyConFamilyCoercion_maybe :: TyCon -> Maybe TyCon
 
1342
tyConFamilyCoercion_maybe tc
 
1343
  = case tyConParent tc of
 
1344
      FamInstTyCon _ _ co -> Just co
 
1345
      _                   -> Nothing
 
1346
\end{code}
 
1347
 
 
1348
 
 
1349
%************************************************************************
 
1350
%*                                                                      *
 
1351
\subsection[TyCon-instances]{Instance declarations for @TyCon@}
 
1352
%*                                                                      *
 
1353
%************************************************************************
 
1354
 
 
1355
@TyCon@s are compared by comparing their @Unique@s.
 
1356
 
 
1357
The strictness analyser needs @Ord@. It is a lexicographic order with
 
1358
the property @(a<=b) || (b<=a)@.
 
1359
 
 
1360
\begin{code}
 
1361
instance Eq TyCon where
 
1362
    a == b = case (a `compare` b) of { EQ -> True;   _ -> False }
 
1363
    a /= b = case (a `compare` b) of { EQ -> False;  _ -> True  }
 
1364
 
 
1365
instance Ord TyCon where
 
1366
    a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
 
1367
    a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
 
1368
    a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
 
1369
    a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
 
1370
    compare a b = getUnique a `compare` getUnique b
 
1371
 
 
1372
instance Uniquable TyCon where
 
1373
    getUnique tc = tyConUnique tc
 
1374
 
 
1375
instance Outputable CoTyConDesc where
 
1376
    ppr CoSym    = ptext (sLit "SYM")
 
1377
    ppr CoTrans  = ptext (sLit "TRANS")
 
1378
    ppr CoLeft   = ptext (sLit "LEFT")
 
1379
    ppr CoRight  = ptext (sLit "RIGHT")
 
1380
    ppr CoCsel1  = ptext (sLit "CSEL1")
 
1381
    ppr CoCsel2  = ptext (sLit "CSEL2")
 
1382
    ppr CoCselR  = ptext (sLit "CSELR")
 
1383
    ppr CoInst   = ptext (sLit "INST")
 
1384
    ppr CoUnsafe = ptext (sLit "UNSAFE")
 
1385
    ppr (CoAxiom {}) = ptext (sLit "AXIOM")
 
1386
 
 
1387
instance Outputable TyCon where
 
1388
    ppr tc  = ppr (getName tc) 
 
1389
 
 
1390
instance NamedThing TyCon where
 
1391
    getName = tyConName
 
1392
 
 
1393
instance Data.Typeable TyCon where
 
1394
    typeOf _ = Data.mkTyConApp (Data.mkTyCon "TyCon") []
 
1395
 
 
1396
instance Data.Data TyCon where
 
1397
    -- don't traverse?
 
1398
    toConstr _   = abstractConstr "TyCon"
 
1399
    gunfold _ _  = error "gunfold"
 
1400
    dataTypeOf _ = mkNoRepType "TyCon"
 
1401
\end{code}