[project @ 2004-01-05 12:11:42 by simonpj]
[ghc-hetmet.git] / ghc / compiler / iface / BuildTyCl.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4
5 \begin{code}
6 module BuildTyCl (
7         buildSynTyCon, buildAlgTyCon, buildDataCon,
8         buildClass,
9         newTyConRhs     -- Just a useful little function with no obvious home
10     ) where
11
12 #include "HsVersions.h"
13
14 import IfaceEnv         ( newImplicitBinder )
15 import TcRnMonad
16
17 import Subst            ( substTyWith )
18 import Util             ( zipLazy )
19 import FieldLabel       ( allFieldLabelTags, mkFieldLabel, fieldLabelName )
20 import VarSet
21 import DataCon          ( DataCon, dataConOrigArgTys, mkDataCon, dataConFieldLabels )
22 import Var              ( tyVarKind, TyVar )
23 import TysWiredIn       ( unitTy )
24 import BasicTypes       ( RecFlag, NewOrData( ..), StrictnessMark(..) )
25 import Name             ( Name )
26 import OccName          ( mkDataConWrapperOcc, mkDataConWorkerOcc, mkClassTyConOcc,
27                           mkClassDataConOcc, mkSuperDictSelOcc )
28 import MkId             ( mkDataConIds, mkRecordSelId, mkDictSelId )
29 import Class            ( mkClass, Class( classTyCon), FunDep, DefMeth(..) )
30 import TyCon            ( mkSynTyCon, mkAlgTyCon, visibleDataCons,
31                           tyConDataCons, isNewTyCon, mkClassTyCon, TyCon( tyConTyVars ),
32                           ArgVrcs, DataConDetails( ..), AlgTyConFlavour(..) )
33 import Type             ( mkArrowKinds, liftedTypeKind, tyVarsOfTypes, typeKind,
34                           tyVarsOfPred, splitTyConApp_maybe, mkPredTys, ThetaType, Type )
35 import Outputable
36 import List             ( nubBy )
37
38 \end{code}
39         
40
41 \begin{code}
42 ------------------------------------------------------
43 buildSynTyCon name tvs rhs_ty arg_vrcs
44   = mkSynTyCon name kind tvs rhs_ty arg_vrcs
45   where
46     kind = mkArrowKinds (map tyVarKind tvs) (typeKind rhs_ty)
47
48
49 ------------------------------------------------------
50 buildAlgTyCon :: NewOrData -> Name -> [TyVar] -> ThetaType
51               -> DataConDetails DataCon
52               -> ArgVrcs -> RecFlag
53               -> Bool                   -- True <=> want generics functions
54               -> TcRnIf m n TyCon
55
56 buildAlgTyCon new_or_data tc_name tvs ctxt cons arg_vrcs is_rec want_generics
57   = do  { let { tycon = mkAlgTyCon tc_name kind tvs ctxt arg_vrcs
58                                    cons sel_ids flavour is_rec want_generics
59               ; kind    = mkArrowKinds (map tyVarKind tvs) liftedTypeKind
60               ; sel_ids = mkRecordSelectors tycon cons
61               ; flavour = case new_or_data of
62                                 NewType  -> NewTyCon (mkNewTyConRep tycon)
63                                 DataType -> DataTyCon (all_nullary cons)
64           }
65         ; return tycon }
66   where
67     all_nullary (DataCons cons) = all (null . dataConOrigArgTys) cons
68     all_nullary Unknown         = False -- Safe choice for unknown data types
69         -- NB (null . dataConOrigArgTys).  It used to say isNullaryDataCon
70         -- but that looks at the *representation* arity, and isEnumerationType
71         -- refers to the *source* code definition
72
73 ------------------------------------------------------
74 buildDataCon :: Name
75             -> [StrictnessMark] 
76             -> [Name]                   -- Field labels
77             -> [TyVar] -> ThetaType
78             -> [TyVar] -> ThetaType
79             -> [Type] -> TyCon
80             -> TcRnIf m n DataCon
81 -- A wrapper for DataCon.mkDataCon that
82 --   a) makes the worker Id
83 --   b) makes the wrapper Id if necessary, including
84 --      allocating its unique (hence monadic)
85 buildDataCon src_name arg_stricts field_lbl_names 
86              tyvars ctxt ex_tyvars ex_ctxt 
87              arg_tys tycon
88   = newImplicitBinder src_name mkDataConWrapperOcc      `thenM` \ wrap_name ->
89     newImplicitBinder src_name mkDataConWorkerOcc       `thenM` \ work_name -> 
90         -- This last one takes the name of the data constructor in the source
91         -- code, which (for Haskell source anyway) will be in the SrcDataName name
92         -- space, and makes it into a "real data constructor name"
93     let
94                 -- Make the FieldLabels
95                 -- The zipLazy avoids forcing the arg_tys too early
96         final_lbls = [ mkFieldLabel name tycon ty tag 
97                      | ((name, tag), ty) <- (field_lbl_names `zip` allFieldLabelTags)
98                                             `zipLazy` arg_tys
99                      ]
100
101         ctxt' = thinContext arg_tys ctxt
102         data_con = mkDataCon src_name arg_stricts final_lbls
103                              tyvars ctxt'
104                              ex_tyvars ex_ctxt
105                              arg_tys tycon dc_ids
106         dc_ids = mkDataConIds wrap_name work_name data_con
107     in
108     returnM data_con
109
110 -- The context for a data constructor should be limited to
111 -- the type variables mentioned in the arg_tys
112 thinContext arg_tys ctxt
113   = filter in_arg_tys ctxt
114   where
115       arg_tyvars = tyVarsOfTypes arg_tys
116       in_arg_tys pred = not $ isEmptyVarSet $ 
117                         tyVarsOfPred pred `intersectVarSet` arg_tyvars
118
119 ------------------------------------------------------
120 mkRecordSelectors tycon data_cons
121   =     -- We'll check later that fields with the same name 
122         -- from different constructors have the same type.
123      [ mkRecordSelId tycon field 
124      | field <- nubBy eq_name fields ]
125   where
126     fields = [ field | con <- visibleDataCons data_cons, 
127                        field <- dataConFieldLabels con ]
128     eq_name field1 field2 = fieldLabelName field1 == fieldLabelName field2
129
130
131 ------------------------------------------------------
132 newTyConRhs :: TyCon -> Type    -- The defn of a newtype, as written by the programmer
133 newTyConRhs tc = head (dataConOrigArgTys (head (tyConDataCons tc)))
134
135 mkNewTyConRep :: TyCon          -- The original type constructor
136               -> Type           -- Chosen representation type
137                                 -- (guaranteed not to be another newtype)
138
139 -- Find the representation type for this newtype TyCon
140 -- Remember that the representation type is the ultimate representation
141 -- type, looking through other newtypes.
142 -- 
143 -- The non-recursive newtypes are easy, because they look transparent
144 -- to splitTyConApp_maybe, but recursive ones really are represented as
145 -- TyConApps (see TypeRep).
146 -- 
147 -- The trick is to to deal correctly with recursive newtypes
148 -- such as      newtype T = MkT T
149
150 mkNewTyConRep tc
151   | null (tyConDataCons tc) = unitTy
152         -- External Core programs can have newtypes with no data constructors
153   | otherwise               = go [] tc
154   where
155         -- Invariant: tc is a NewTyCon
156         --            tcs have been seen before
157     go tcs tc 
158         | tc `elem` tcs = unitTy
159         | otherwise
160         = case splitTyConApp_maybe rep_ty of
161             Nothing -> rep_ty 
162             Just (tc', tys) | not (isNewTyCon tc') -> rep_ty
163                             | otherwise            -> go1 (tc:tcs) tc' tys
164         where
165           rep_ty = newTyConRhs tc
166           
167     go1 tcs tc tys = substTyWith (tyConTyVars tc) tys (go tcs tc)
168 \end{code}
169
170
171 \begin{code}
172 buildClass :: Name -> [TyVar] -> ThetaType
173            -> [FunDep TyVar]            -- Functional dependencies
174            -> [(Name, DefMeth, Type)]   -- Method info
175            -> RecFlag -> ArgVrcs        -- Info for type constructor
176            -> TcRnIf m n Class
177
178 buildClass class_name tvs sc_theta fds sig_stuff tc_isrec tc_vrcs
179   = do  { tycon_name <- newImplicitBinder class_name mkClassTyConOcc
180         ; datacon_name <- newImplicitBinder class_name mkClassDataConOcc
181                 -- The class name is the 'parent' for this datacon, not its tycon,
182                 -- because one should import the class to get the binding for 
183                 -- the datacon
184         ; sc_sel_names <- mapM (newImplicitBinder class_name . mkSuperDictSelOcc) 
185                                 [1..length sc_theta]
186               -- We number off the superclass selectors, 1, 2, 3 etc so that we 
187               -- can construct names for the selectors.  Thus
188               --      class (C a, C b) => D a b where ...
189               -- gives superclass selectors
190               --      D_sc1, D_sc2
191               -- (We used to call them D_C, but now we can have two different
192               --  superclasses both called C!)
193
194         ; fixM (\ clas -> do {  -- Only name generation inside loop
195
196           let { op_tys             = [ty | (_,_,ty) <- sig_stuff]
197               ; sc_tys             = mkPredTys sc_theta
198               ; dict_component_tys = sc_tys ++ op_tys
199               ; sc_sel_ids         = [mkDictSelId sc_name clas | sc_name <- sc_sel_names]
200               ; op_items = [ (mkDictSelId op_name clas, dm_info)
201                            | (op_name, dm_info, _) <- sig_stuff ] }
202                         -- Build the selector id and default method id
203
204         ; dict_con <- buildDataCon datacon_name
205                                    (map (const NotMarkedStrict) dict_component_tys)
206                                    [{- No labelled fields -}]
207                                    tvs [{-No context-}]
208                                    [{-No existential tyvars-}] [{-Or context-}]
209                                    dict_component_tys
210                                    (classTyCon clas)
211
212         ; let { clas = mkClass class_name tvs fds
213                        sc_theta sc_sel_ids op_items
214                        tycon
215
216               ; tycon = mkClassTyCon tycon_name clas_kind tvs
217                              tc_vrcs dict_con
218                              clas flavour tc_isrec
219                 -- A class can be recursive, and in the case of newtypes 
220                 -- this matters.  For example
221                 --      class C a where { op :: C b => a -> b -> Int }
222                 -- Because C has only one operation, it is represented by
223                 -- a newtype, and it should be a *recursive* newtype.
224                 -- [If we don't make it a recursive newtype, we'll expand the
225                 -- newtype like a synonym, but that will lead to an infinite type]
226
227               ; clas_kind = mkArrowKinds (map tyVarKind tvs) liftedTypeKind
228
229               ; flavour = case dict_component_tys of
230                             [rep_ty] -> NewTyCon (mkNewTyConRep tycon)
231                             other    -> DataTyCon False         -- Not an enumeration
232               }
233         ; return clas
234         })}
235 \end{code}
236
237