update compiler using *->*->* as the kind of environment classifiers
[ghc-hetmet.git] / compiler / types / TyCon.lhs
index b552c24..adb0470 100644 (file)
@@ -129,15 +129,28 @@ Note [Type synonym families]
 
 * Translation of type instance decl:
        type instance F [a] = Maybe a
-  translates to
-    A SynTyCon 'R:FList a', whose 
+  translates to a "representation TyCon", 'R:FList', where
+     R:FList is a SynTyCon, whose 
        SynTyConRhs is (SynonymTyCon (Maybe a))
        TyConParent is (FamInstTyCon F [a] co)
          where co :: F [a] ~ R:FList a
-    Notice that we introduce a gratuitous vanilla type synonym
+
+  It's very much as if the user had written
+       type instance F [a] = R:FList a
        type R:FList a = Maybe a
-    solely so that type and data families can be treated more
-    uniformly, via a single FamInstTyCon descriptor        
+  Indeed, in GHC's internal representation, the RHS of every
+  'type instance' is simply an application of the representation
+  TyCon to the quantified varaibles.
+
+  The intermediate representation TyCon is a bit gratuitous, but 
+  it means that:
+
+        each 'type instance' decls is in 1-1 correspondance 
+       with its representation TyCon
+
+  So the result of typechecking a 'type instance' decl is just a
+  TyCon.  In turn this means that type and data families can be
+  treated uniformly.
 
 * In the future we might want to support
     * closed type families (esp when we have proper kinds)
@@ -440,7 +453,7 @@ data AlgTyConRhs
                          --      (see the tag assignment in DataCon.mkDataCon)
 
        is_enum :: Bool   -- ^ Cached value: is this an enumeration type? 
-                          --   (See 'isEnumerationTyCon')
+                          --   See Note [Enumeration types]
     }
 
   -- | Information about those 'TyCon's derived from a @newtype@ declaration
@@ -500,7 +513,24 @@ data TyConParent
 
   -- | An *associated* type of a class.  
   | AssocFamilyTyCon   
-        Class                  -- The class in whose declaration the family is declared
+        Class          -- The class in whose declaration the family is declared
+                        -- The 'tyConTyVars' of this 'TyCon' may mention some
+                        -- of the same type variables as the classTyVars of the
+                        -- parent 'Class'.  E.g.
+                        --
+                        -- @
+                        --    class C a b where
+                        --      data T c a
+                        -- @
+                        --
+                        -- Here the 'a' is shared with the 'Class', and that is
+                        -- important. In an instance declaration we expect the
+                        -- two to be instantiated the same way.  Eg.
+                        --
+                        -- @
+                        --    instanc C [x] (Tree y) where
+                        --      data T c [x] = T1 x | T2 c
+                        -- @
 
   -- | Type constructors representing an instance of a type family. Parameters:
   --
@@ -539,12 +569,14 @@ isNoParent _             = False
 
 -- | Information pertaining to the expansion of a type synonym (@type@)
 data SynTyConRhs
-  = SynonymTyCon      -- ^ An ordinary type synony
-       Type          -- ^ The rhs, which mentions head type variables. It acts as a
-                     -- template for the expansion when the 'TyCon' is applied to some
-                     -- types.
+  = -- | An ordinary type synonyn.
+    SynonymTyCon      
+       Type          -- This 'Type' is the rhs, and may mention from 'tyConTyVars'. 
+                     -- It acts as a template for the expansion when the 'TyCon' 
+                      -- is applied to some types.
 
-   | SynFamilyTyCon   -- A type synonym family  e.g. type family F x y :: * -> *
+   -- | A type synonym family  e.g. @type family F x y :: * -> *@
+   | SynFamilyTyCon
 
 --------------------
 data CoTyConDesc
@@ -561,6 +593,26 @@ data CoTyConDesc
   | CoUnsafe 
 \end{code}
 
+Note [Enumeration types]
+~~~~~~~~~~~~~~~~~~~~~~~~
+We define datatypes with no constructors to *not* be
+enumerations; this fixes trac #2578,  Otherwise we
+end up generating an empty table for
+  <mod>_<type>_closure_tbl
+which is used by tagToEnum# to map Int# to constructors
+in an enumeration. The empty table apparently upset
+the linker.
+
+Moreover, all the data constructor must be enumerations, meaning
+they have type  (forall abc. T a b c).  GADTs are not enumerations.
+For example consider
+    data T a where
+      T1 :: T Int
+      T2 :: T Bool
+      T3 :: T a
+What would [T1 ..] be?  [T1,T3] :: T Int? Easiest thing is to exclude them.
+See Trac #4528.
+
 Note [Newtype coercions]
 ~~~~~~~~~~~~~~~~~~~~~~~~
 The NewTyCon field nt_co is a a TyCon (a coercion constructor in fact)
@@ -964,6 +1016,7 @@ isGadtSyntaxTyCon _                                    = False
 
 -- | Is this an algebraic 'TyCon' which is just an enumeration of values?
 isEnumerationTyCon :: TyCon -> Bool
+-- See Note [Enumeration types] in TyCon
 isEnumerationTyCon (AlgTyCon {algTcRhs = DataTyCon { is_enum = res }}) = res
 isEnumerationTyCon (TupleTyCon {tyConArity = arity}) = arity == 0
 isEnumerationTyCon _                                                   = False