X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;ds=sidebyside;f=ghc%2Fcompiler%2Ftypecheck%2FTcTyClsDecls.lhs;h=95166861ec668c6e0a09546ffc9f5e52a645de73;hb=6a4854eaa266d994ebd0d471614a52b43dd329d9;hp=2be946e252be78b27ed82c058bf9e855455fdf9c;hpb=23f40f0e9be6d4aa5cf9ea31d73f4013f8e7b4bd;p=ghc-hetmet.git diff --git a/ghc/compiler/typecheck/TcTyClsDecls.lhs b/ghc/compiler/typecheck/TcTyClsDecls.lhs index 2be946e..9516686 100644 --- a/ghc/compiler/typecheck/TcTyClsDecls.lhs +++ b/ghc/compiler/typecheck/TcTyClsDecls.lhs @@ -49,7 +49,7 @@ import Var ( TyVar, idType, idName ) import VarSet ( elemVarSet ) import Name ( Name ) import Outputable -import Util ( zipLazy, isSingleton, notNull ) +import Util ( zipLazy, isSingleton, notNull, sortLe ) import List ( partition ) import SrcLoc ( Located(..), unLoc, getLoc ) import ListSetOps ( equivClasses ) @@ -108,14 +108,15 @@ The knot-tying parameters: @rec_details_list@ is an alist mapping @Name@s to @TyThing@s. @rec_vrcs@ is a finite map from @Name@s to @ArgVrcs@s. \begin{code} -tcTyAndClassDecls :: [LTyClDecl Name] +tcTyAndClassDecls :: [Name] -> [LTyClDecl Name] -> TcM TcGblEnv -- Input env extended by types and classes -- and their implicit Ids,DataCons -tcTyAndClassDecls decls +tcTyAndClassDecls boot_names decls = do { -- First check for cyclic type synonysm or classes -- See notes with checkCycleErrs checkCycleErrs decls - + ; mod <- getModule + ; traceTc (text "tcTyAndCl" <+> ppr mod <+> ppr boot_names) ; (syn_tycons, alg_tyclss) <- fixM (\ ~(rec_syn_tycons, rec_alg_tyclss) -> do { let { -- Calculate variances and rec-flag ; (syn_decls, alg_decls) = partition (isSynDecl . unLoc) decls } @@ -133,7 +134,7 @@ tcTyAndClassDecls decls { (kc_syn_decls, kc_alg_decls) <- kcTyClDecls syn_decls alg_decls ; let { calc_vrcs = calcTyConArgVrcs (rec_syn_tycons ++ rec_alg_tyclss) - ; calc_rec = calcRecFlags rec_alg_tyclss + ; calc_rec = calcRecFlags boot_names rec_alg_tyclss ; tc_decl = addLocM (tcTyClDecl calc_vrcs calc_rec) } -- Type-check the type synonyms, and extend the envt ; syn_tycons <- tcSynDecls calc_vrcs kc_syn_decls @@ -322,8 +323,14 @@ kcTyClDeclBody decl thing_inside do { tc_ty_thing <- tcLookupLocated (tcdLName decl) ; let tc_kind = case tc_ty_thing of { AThing k -> k } ; unifyKind tc_kind (foldr (mkArrowKind . kindedTyVarKind) - liftedTypeKind kinded_tvs) + (result_kind decl) + kinded_tvs) ; thing_inside kinded_tvs } + where + result_kind (TyData { tcdKindSig = Just kind }) = kind + result_kind other = liftedTypeKind + -- On GADT-style declarations we allow a kind signature + -- data T :: *->* where { ... } kindedTyVarKind (L _ (KindedTyVar _ k)) = k \end{code} @@ -365,6 +372,9 @@ tcTyClDecl1 calc_vrcs calc_isrec ; want_generic <- doptM Opt_Generics ; tycon <- fixM (\ tycon -> do { unbox_strict <- doptM Opt_UnboxStrictFields + ; gla_exts <- doptM Opt_GlasgowExts + ; checkTc (gla_exts || h98_syntax) (badGadtDecl tc_name) + ; data_cons <- mappM (addLocM (tcConDecl unbox_strict new_or_data tycon tvs')) cons ; let tc_rhs = case new_or_data of DataType -> mkDataTyConRhs stupid_theta data_cons @@ -378,6 +388,9 @@ tcTyClDecl1 calc_vrcs calc_isrec where arg_vrcs = calc_vrcs tc_name is_rec = calc_isrec tc_name + h98_syntax = case cons of -- All constructors have same shape + L _ (GadtDecl {}) : _ -> False + other -> True tcTyClDecl1 calc_vrcs calc_isrec (ClassDecl {tcdLName = L _ class_name, tcdTyVars = tvs, @@ -413,7 +426,21 @@ tcConDecl :: Bool -- True <=> -funbox-strict_fields -> NewOrData -> TyCon -> [TyVar] -> ConDecl Name -> TcM DataCon -tcConDecl unbox_strict new_or_data tycon tc_tvs +tcConDecl unbox_strict NewType tycon tc_tvs -- Newtypes + (ConDecl name ex_tvs ex_ctxt details) + = ASSERT( null ex_tvs && null (unLoc ex_ctxt) ) + do { let tc_datacon field_lbls arg_ty + = do { arg_ty' <- tcHsKindedType arg_ty -- No bang on newtype + ; buildDataCon (unLoc name) False {- Prefix -} + True {- Vanilla -} [NotMarkedStrict] + (map unLoc field_lbls) + tc_tvs [] [arg_ty'] + tycon (mkTyVarTys tc_tvs) } + ; case details of + PrefixCon [arg_ty] -> tc_datacon [] arg_ty + RecCon [(field_lbl, arg_ty)] -> tc_datacon [field_lbl] arg_ty } + +tcConDecl unbox_strict DataType tycon tc_tvs -- Ordinary data types (ConDecl name ex_tvs ex_ctxt details) = tcTyVarBndrs ex_tvs $ \ ex_tvs' -> do { ex_ctxt' <- tcHsKindedContext ex_ctxt @@ -438,7 +465,7 @@ tcConDecl unbox_strict new_or_data tycon tc_tvs ; let { (field_names, btys) = unzip fields } ; tc_datacon False field_names btys } } -tcConDecl unbox_strict new_or_data tycon tc_tvs +tcConDecl unbox_strict DataType tycon tc_tvs -- GADTs decl@(GadtDecl name con_ty) = do { traceTc (text "tcConDecl" <+> ppr name) ; (tvs, theta, bangs, arg_tys, tc, res_tys) <- tcLHsConSig con_ty @@ -460,6 +487,7 @@ tcConDecl unbox_strict new_or_data tycon tc_tvs [{- No field labels -}] tvs' theta arg_tys' tycon res_tys' } +------------------- tcStupidTheta :: LHsContext Name -> [LConDecl Name] -> TcM (Maybe ThetaType) -- For GADTs we don't allow a context on the data declaration -- whereas for standard Haskell style data declarations, we do @@ -622,7 +650,7 @@ checkValidClass cls -- Check that for a generic method, the type of -- the method is sufficiently simple - ; checkTc (dm /= GenDefMeth || validGenericMethodType op_ty) + ; checkTc (dm /= GenDefMeth || validGenericMethodType tau) (badGenericMethodType op_name op_ty) } where @@ -674,22 +702,29 @@ genericMultiParamErr clas badGenericMethodType op op_ty = hang (ptext SLIT("Generic method type is too complex")) 4 (vcat [ppr op <+> dcolon <+> ppr op_ty, - ptext SLIT("You can only use type variables, arrows, and tuples")]) + ptext SLIT("You can only use type variables, arrows, lists, and tuples")]) recSynErr syn_decls - = setSrcSpan (getLoc (head syn_decls)) $ + = setSrcSpan (getLoc (head sorted_decls)) $ addErr (sep [ptext SLIT("Cycle in type synonym declarations:"), - nest 2 (vcat (map ppr_decl syn_decls))]) + nest 2 (vcat (map ppr_decl sorted_decls))]) where + sorted_decls = sortLocated syn_decls ppr_decl (L loc decl) = ppr loc <> colon <+> ppr decl recClsErr cls_decls - = setSrcSpan (getLoc (head cls_decls)) $ + = setSrcSpan (getLoc (head sorted_decls)) $ addErr (sep [ptext SLIT("Cycle in class declarations (via superclasses):"), - nest 2 (vcat (map ppr_decl cls_decls))]) + nest 2 (vcat (map ppr_decl sorted_decls))]) where + sorted_decls = sortLocated cls_decls ppr_decl (L loc decl) = ppr loc <> colon <+> ppr (decl { tcdSigs = [] }) +sortLocated :: [Located a] -> [Located a] +sortLocated things = sortLe le things + where + le (L l1 _) (L l2 _) = l1 <= l2 + exRecConErr name = ptext SLIT("Can't combine named fields with locally-quantified type variables or context") $$ @@ -698,4 +733,8 @@ exRecConErr name badDataConTyCon data_con = hang (ptext SLIT("Data constructor does not return its parent type:")) 2 (ppr data_con) + +badGadtDecl tc_name + = vcat [ ptext SLIT("Illegal generalised algebraic data declaration for") <+> quotes (ppr tc_name) + , nest 2 (parens $ ptext SLIT("Use -fglasgow-exts to allow GADTs")) ] \end{code}