[project @ 2004-10-11 16:16:20 by simonpj]
[ghc-hetmet.git] / ghc / compiler / typecheck / TcTyClsDecls.lhs
index e4bc357..9516686 100644 (file)
@@ -115,7 +115,8 @@ 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 }
@@ -371,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
@@ -384,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, 
@@ -419,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
@@ -444,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
@@ -466,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
@@ -628,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
@@ -680,7 +702,7 @@ 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 sorted_decls)) $
@@ -711,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}