X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fiface%2FBuildTyCl.lhs;h=738a5e33bfcd9ff46e45160406f24bfe060e2e82;hp=12668abccc01c523448beac16f17889d9d284d10;hb=215ce9f15215399ce30ae55c9521087847d78646;hpb=5e5310b3cb4f78e30cc7b90879eb016e97c214cb diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index 12668ab..738a5e3 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -8,7 +8,7 @@ module BuildTyCl ( buildSynTyCon, buildAlgTyCon, buildDataCon, buildClass, mkAbstractTyConRhs, mkOpenDataTyConRhs, - mkNewTyConRhs, mkDataTyConRhs + mkNewTyConRhs, mkDataTyConRhs, setAssocFamilyPermutation ) where #include "HsVersions.h" @@ -20,7 +20,6 @@ import Var import VarSet import BasicTypes import Name -import OccName import MkId import Class import TyCon @@ -30,8 +29,6 @@ import Coercion import TcRnMonad import Util ( count ) import Outputable - -import Data.List \end{code} @@ -79,9 +76,8 @@ buildAlgTyCon tc_name tvs stupid_theta rhs is_rec want_generics gadt_syn ; tycon <- fixM (\ tycon_rec -> do { parent <- mkParentInfo mb_family tc_name tvs tycon_rec ; let { tycon = mkAlgTyCon tc_name kind tvs stupid_theta rhs - fields parent is_rec want_generics gadt_syn - ; kind = mkArrowKinds (map tyVarKind tvs) liftedTypeKind - ; fields = mkTyConSelIds tycon rhs + parent is_rec want_generics gadt_syn + ; kind = mkArrowKinds (map tyVarKind tvs) liftedTypeKind } ; return tycon }) @@ -122,7 +118,18 @@ mkOpenDataTyConRhs = OpenTyCon Nothing mkDataTyConRhs :: [DataCon] -> AlgTyConRhs mkDataTyConRhs cons - = DataTyCon { data_cons = cons, is_enum = all isNullarySrcDataCon cons } + = DataTyCon { + data_cons = cons, + is_enum = -- We define datatypes with no constructors to not be + -- enumerations; this fixes trac #2578, Otherwise we + -- end up generating an empty table for + -- __closure_tbl + -- which is used by tagToEnum# to map Int# to constructors + -- in an enumeration. The empty table apparently upset + -- the linker. + not (null cons) && + all isNullarySrcDataCon cons + } mkNewTyConRhs :: Name -> TyCon -> DataCon -> TcRnIf m n AlgTyConRhs -- Monadic because it makes a Name for the coercion TyCon @@ -175,22 +182,30 @@ mkNewTyConRhs tycon_name tycon con eta_reduce tvs ty = (reverse tvs, ty) +setAssocFamilyPermutation :: [TyVar] -> TyThing -> TyThing +setAssocFamilyPermutation clas_tvs (ATyCon tc) + = ATyCon (setTyConArgPoss clas_tvs tc) +setAssocFamilyPermutation _clas_tvs other + = pprPanic "setAssocFamilyPermutation" (ppr other) + + ------------------------------------------------------ buildDataCon :: Name -> Bool - -> [StrictnessMark] + -> [HsBang] -> [Name] -- Field labels -> [TyVar] -> [TyVar] -- Univ and ext -> [(TyVar,Type)] -- Equality spec -> ThetaType -- Does not include the "stupid theta" -- or the GADT equalities - -> [Type] -> TyCon + -> [Type] -> Type -- Argument and result types + -> TyCon -- Rep tycon -> TcRnIf m n DataCon -- A wrapper for DataCon.mkDataCon that -- a) makes the worker Id -- b) makes the wrapper Id if necessary, including -- allocating its unique (hence monadic) buildDataCon src_name declared_infix arg_stricts field_lbls - univ_tvs ex_tvs eq_spec ctxt arg_tys tycon + univ_tvs ex_tvs eq_spec ctxt arg_tys res_ty rep_tycon = do { wrap_name <- newImplicitBinder src_name mkDataConWrapperOcc ; work_name <- newImplicitBinder src_name mkDataConWorkerOcc -- This last one takes the name of the data constructor in the source @@ -198,11 +213,11 @@ buildDataCon src_name declared_infix arg_stricts field_lbls -- space, and puts it into the VarName name space ; let - stupid_ctxt = mkDataConStupidTheta tycon arg_tys univ_tvs + stupid_ctxt = mkDataConStupidTheta rep_tycon arg_tys univ_tvs data_con = mkDataCon src_name declared_infix arg_stricts field_lbls univ_tvs ex_tvs eq_spec ctxt - arg_tys tycon + arg_tys res_ty rep_tycon stupid_ctxt dc_ids dc_ids = mkDataConIds wrap_name work_name data_con @@ -226,14 +241,6 @@ mkDataConStupidTheta tycon arg_tys univ_tvs arg_tyvars = tyVarsOfTypes arg_tys in_arg_tys pred = not $ isEmptyVarSet $ tyVarsOfPred pred `intersectVarSet` arg_tyvars - ------------------------------------------------------- -mkTyConSelIds :: TyCon -> AlgTyConRhs -> [Id] -mkTyConSelIds tycon rhs - = [ mkRecordSelId tycon fld - | fld <- nub (concatMap dataConFieldLabels (visibleDataCons rhs)) ] - -- We'll check later that fields with the same name - -- from different constructors have the same type. \end{code} @@ -261,19 +268,11 @@ buildClass no_unf class_name tvs sc_theta fds ats sig_stuff tc_isrec let { rec_tycon = classTyCon rec_clas ; op_tys = [ty | (_,_,ty) <- sig_stuff] + ; op_names = [op | (op,_,_) <- sig_stuff] ; op_items = [ (mkDictSelId no_unf op_name rec_clas, dm_info) | (op_name, dm_info, _) <- sig_stuff ] } -- Build the selector id and default method id - ; dict_con <- buildDataCon datacon_name - False -- Not declared infix - (map (const NotMarkedStrict) op_tys) - [{- No labelled fields -}] - tvs [{- no existentials -}] - [{- No GADT equalities -}] sc_theta - op_tys - rec_tycon - ; let n_value_preds = count (not . isEqPred) sc_theta all_value_preds = n_value_preds == length sc_theta -- We only make selectors for the *value* superclasses, @@ -298,6 +297,23 @@ buildClass no_unf class_name tvs sc_theta fds ats sig_stuff tc_isrec -- i.e. exactly one operation or superclass taken together -- See note [Class newtypes and equality predicates] + -- We play a bit fast and loose by treating the superclasses + -- as ordinary arguments. That means that in the case of + -- class C a => D a + -- we don't get a newtype with no arguments! + args = sc_sel_names ++ op_names + arg_tys = map mkPredTy sc_theta ++ op_tys + + ; dict_con <- buildDataCon datacon_name + False -- Not declared infix + (map (const HsNoBang) args) + [{- No fields -}] + tvs [{- no existentials -}] + [{- No GADT equalities -}] [{- No theta -}] + arg_tys + (mkTyConApp rec_tycon (mkTyVarTys tvs)) + rec_tycon + ; rhs <- if use_newtype then mkNewTyConRhs tycon_name rec_tycon dict_con else return (mkDataTyConRhs [dict_con])