Reject newtypes with strictness annotations; fixes read008
[ghc-hetmet.git] / compiler / typecheck / TcDeriv.lhs
index f86dd64..4e1a065 100644 (file)
@@ -47,6 +47,8 @@ import Util
 import ListSetOps
 import Outputable
 import Bag
+
+import Monad (unless)
 \end{code}
 
 %************************************************************************
@@ -381,6 +383,8 @@ deriveTyData (deriv_pred, L loc decl@(TyData { tcdLName = L _ tycon_name,
                -- The "deriv_pred" is a LHsType to take account of the fact that for
                -- newtype deriving we allow deriving (forall a. C [a]).
        ; mkEqnHelp DerivOrigin (tvs++deriv_tvs) cls cls_tys tc_app } }
+deriveTyData (deriv_pred, other_decl)
+  = panic "derivTyData"        -- Caller ensures that only TyData can happen
 
 ------------------------------------------------------------------
 mkEqnHelp orig tvs cls cls_tys tc_app
@@ -393,11 +397,14 @@ mkEqnHelp orig tvs cls cls_tys tc_app
              full_tc_args = tc_args ++ mkTyVarTys extra_tvs
              full_tvs = tvs ++ extra_tvs
                
-       ; (rep_tc, rep_tc_args) <- tcLookupFamInst tycon full_tc_args
+       ; (rep_tc, rep_tc_args) <- tcLookupFamInstExact tycon full_tc_args
 
        ; gla_exts <- doptM Opt_GlasgowExts
        ; overlap_flag <- getOverlapFlag
-       ; if isDataTyCon tycon then
+
+          -- Be careful to test rep_tc here: in the case of families, we want
+          -- to check the instance tycon, not the family tycon
+       ; if isDataTyCon rep_tc then
                mkDataTypeEqn orig gla_exts full_tvs cls cls_tys 
                              tycon full_tc_args rep_tc rep_tc_args
          else
@@ -410,6 +417,27 @@ mkEqnHelp orig tvs cls cls_tys tc_app
 baleOut err = addErrTc err >> returnM (Nothing, Nothing) 
 \end{code}
 
+Auxiliary lookup wrapper which requires that looked up family instances are
+not type instances.
+
+\begin{code}
+tcLookupFamInstExact :: TyCon -> [Type] -> TcM (TyCon, [Type])
+tcLookupFamInstExact tycon tys
+  = do { result@(rep_tycon, rep_tys) <- tcLookupFamInst tycon tys
+       ; let { tvs                   = map (Type.getTyVar 
+                                               "TcDeriv.tcLookupFamInstExact") 
+                                           tys
+            ; variable_only_subst = all Type.isTyVarTy rep_tys &&
+                                    sizeVarSet (mkVarSet tvs) == length tvs
+                                       -- renaming may have no repetitions
+             }
+       ; unless variable_only_subst $
+           famInstNotFound tycon tys [result]
+       ; return result
+       }
+       
+\end{code}
+
 
 %************************************************************************
 %*                                                                     *
@@ -541,7 +569,7 @@ cond_isProduct (gla_exts, rep_tc)
   | isProductTyCon rep_tc = Nothing
   | otherwise            = Just why
   where
-    why = (pprSourceTyCon rep_tc) <+> 
+    why = quotes (pprSourceTyCon rep_tc) <+> 
          ptext SLIT("has more than one constructor")
 
 cond_typeableOK :: Condition
@@ -568,12 +596,6 @@ cond_glaExts (gla_exts, _rep_tc) | gla_exts  = Nothing
   where
     why  = ptext SLIT("You need -fglasgow-exts to derive an instance for this class")
 
-std_class gla_exts clas 
-  =  key `elem` derivableClassKeys
-  || (gla_exts && (key == typeableClassKey || key == dataClassKey))
-  where
-     key = classKey clas
-    
 std_class_via_iso clas -- These standard classes can be derived for a newtype
                        -- using the isomorphism trick *even if no -fglasgow-exts*
   = classKey clas `elem`  [eqClassKey, ordClassKey, ixClassKey, boundedClassKey]
@@ -582,7 +604,7 @@ std_class_via_iso clas      -- These standard classes can be derived for a newtype
 
 
 new_dfun_name clas tycon       -- Just a simple wrapper
-  = newDFunName clas [mkTyConApp tycon []] (getSrcLoc tycon)
+  = newDFunName clas [mkTyConApp tycon []] (getSrcSpan tycon)
        -- The type passed to newDFunName is only used to generate
        -- a suitable string; hence the empty type arg list
 \end{code}
@@ -599,18 +621,26 @@ mkNewTypeEqn orig gla_exts overlap_flag tvs cls cls_tys
             tycon tc_args 
             rep_tycon rep_tc_args
   | can_derive_via_isomorphism && (gla_exts || std_class_via_iso cls)
-  =    do { traceTc (text "newtype deriving:" <+> ppr tycon <+> ppr rep_tys)
-          ;    -- Go ahead and use the isomorphism
-            dfun_name <- new_dfun_name cls tycon
-          ; return (Nothing, Just (InstInfo { iSpec  = mk_inst_spec dfun_name,
-                                              iBinds = NewTypeDerived ntd_info })) }
-  | std_class gla_exts cls
-  = mkDataTypeEqn orig gla_exts tvs cls cls_tys tycon tc_args rep_tycon rep_tc_args    -- Go via bale-out route
-
-       -- Otherwise its a non-standard instance
+  = do { traceTc (text "newtype deriving:" <+> ppr tycon <+> ppr rep_tys)
+       ;       -- Go ahead and use the isomorphism
+          dfun_name <- new_dfun_name cls tycon
+       ; return (Nothing, Just (InstInfo { iSpec  = mk_inst_spec dfun_name,
+                                           iBinds = NewTypeDerived ntd_info })) }
+
+  | isNothing mb_std_err       -- Use the standard H98 method
+  = do { loc <- getSrcSpanM
+       ; eqn <- mk_data_eqn loc orig tvs cls tycon tc_args rep_tycon rep_tc_args
+       ; return (Just eqn, Nothing) }
+
+       -- Otherwise we can't derive
   | gla_exts  = baleOut cant_derive_err        -- Too hard
-  | otherwise = baleOut non_std_err    -- Just complain about being a non-std instance
+  | otherwise = baleOut std_err                -- Just complain about being a non-std instance
   where
+       mb_std_err = checkSideConditions gla_exts cls cls_tys rep_tycon
+       std_err = derivingThingErr cls cls_tys tc_app $
+                 vcat [fromJust mb_std_err,
+                       ptext SLIT("Try -fglasgow-exts for GHC's newtype-deriving extension")]
+
        -- Here is the plan for newtype derivings.  We see
        --        newtype T a1...an = MkT (t ak+1...an) deriving (.., C s1 .. sm, ...)
        -- where t is a type,
@@ -752,7 +782,7 @@ mkNewTypeEqn orig gla_exts overlap_flag tvs cls cls_tys
        cant_derive_err = derivingThingErr cls cls_tys tc_app
                                (vcat [ptext SLIT("even with cunning newtype deriving:"),
                                        if isRecursiveTyCon tycon then
-                                         ptext SLIT("the newtype is recursive")
+                                         ptext SLIT("the newtype may be recursive")
                                        else empty,
                                        if not right_arity then 
                                          quotes (ppr (mkClassPred cls cls_tys)) <+> ptext SLIT("does not have arity 1")
@@ -765,10 +795,6 @@ mkNewTypeEqn orig gla_exts overlap_flag tvs cls cls_tys
                                          ptext SLIT("the eta-reduction property does not hold")
                                        else empty
                                      ])
-
-       non_std_err = derivingThingErr cls cls_tys tc_app
-                               (vcat [non_std_why cls,
-                                      ptext SLIT("Try -fglasgow-exts for GHC's newtype-deriving extension")])
 \end{code}
 
 
@@ -977,7 +1003,7 @@ genInst spec
 
           -- In case of a family instance, we need to use the representation
           -- tycon (after all, it has the data constructors)
-        ; (tycon, _) <- tcLookupFamInst visible_tycon tyArgs
+        ; (tycon, _) <- tcLookupFamInstExact visible_tycon tyArgs
        ; let (meth_binds, aux_binds) = genDerivBinds clas fix_env tycon
 
        -- Bring the right type variables into 
@@ -1122,3 +1148,4 @@ badDerivedPred pred
          nest 2 (ptext SLIT("Offending constraint:") <+> ppr pred)]
 \end{code}