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