Use OPTIONS rather than OPTIONS_GHC for pragmas
[ghc-hetmet.git] / compiler / iface / BuildTyCl.lhs
index 707de1c..242772f 100644 (file)
@@ -4,10 +4,17 @@
 %
 
 \begin{code}
+{-# OPTIONS -w #-}
+-- The above warning supression flag is a temporary kludge.
+-- While working on this module you are encouraged to remove it and fix
+-- any warnings in the module. See
+--     http://hackage.haskell.org/trac/ghc/wiki/CodingStyle#Warnings
+-- for details
+
 module BuildTyCl (
        buildSynTyCon, buildAlgTyCon, buildDataCon,
        buildClass,
-       mkAbstractTyConRhs, mkOpenDataTyConRhs, mkOpenNewTyConRhs,
+       mkAbstractTyConRhs, mkOpenDataTyConRhs, 
        mkNewTyConRhs, mkDataTyConRhs 
     ) where
 
@@ -29,6 +36,9 @@ import TyCon
 import Type
 import Coercion
 
+import TcRnMonad
+import Outputable
+
 import Data.List
 \end{code}
        
@@ -115,10 +125,7 @@ mkAbstractTyConRhs :: AlgTyConRhs
 mkAbstractTyConRhs = AbstractTyCon
 
 mkOpenDataTyConRhs :: AlgTyConRhs
-mkOpenDataTyConRhs = OpenTyCon Nothing False
-
-mkOpenNewTyConRhs :: AlgTyConRhs
-mkOpenNewTyConRhs = OpenTyCon Nothing True
+mkOpenDataTyConRhs = OpenTyCon Nothing
 
 mkDataTyConRhs :: [DataCon] -> AlgTyConRhs
 mkDataTyConRhs cons
@@ -135,6 +142,7 @@ mkNewTyConRhs tycon_name tycon con
                          = Just co_tycon
                          | otherwise              
                          = Nothing
+       ; traceIf (text "mkNewTyConRhs" <+> ppr cocon_maybe)
        ; return (NewTyCon { data_con    = con, 
                             nt_rhs      = rhs_ty,
                             nt_etad_rhs = (etad_tvs, etad_rhs),
@@ -148,9 +156,13 @@ mkNewTyConRhs tycon_name tycon con
         -- non-recursive newtypes
     all_coercions = True
     tvs    = tyConTyVars tycon
-    rhs_ty = head (dataConInstOrigArgTys con (mkTyVarTys tvs))
+    rhs_ty = ASSERT(not (null (dataConInstOrigDictsAndArgTys con (mkTyVarTys tvs)))) 
+            -- head (dataConInstOrigArgTys con (mkTyVarTys tvs))
+            head (dataConInstOrigDictsAndArgTys con (mkTyVarTys tvs))
        -- Instantiate the data con with the 
        -- type variables from the tycon
+       -- NB: a newtype DataCon has no existentials; hence the
+       --     call to dataConInstOrigArgTys has the right type args
 
     etad_tvs :: [TyVar]        -- Matched lazily, so that mkNewTypeCoercion can
     etad_rhs :: Type   -- return a TyCon without pulling on rhs_ty
@@ -275,44 +287,48 @@ buildClass :: Name -> [TyVar] -> ThetaType
           -> TcRnIf m n Class
 
 buildClass class_name tvs sc_theta fds ats sig_stuff tc_isrec
-  = do { tycon_name <- newImplicitBinder class_name mkClassTyConOcc
+  = do { traceIf (text "buildClass")
+       ; tycon_name <- newImplicitBinder class_name mkClassTyConOcc
        ; datacon_name <- newImplicitBinder class_name mkClassDataConOcc
                -- The class name is the 'parent' for this datacon, not its tycon,
                -- because one should import the class to get the binding for 
                -- the datacon
-       ; sc_sel_names <- mapM (newImplicitBinder class_name . mkSuperDictSelOcc) 
-                               [1..length sc_theta]
-             -- We number off the superclass selectors, 1, 2, 3 etc so that we 
-             -- can construct names for the selectors.  Thus
-             --      class (C a, C b) => D a b where ...
-             -- gives superclass selectors
-             --      D_sc1, D_sc2
-             -- (We used to call them D_C, but now we can have two different
-             --  superclasses both called C!)
 
        ; fixM (\ rec_clas -> do {      -- Only name generation inside loop
 
-         let { rec_tycon          = classTyCon rec_clas
-             ; op_tys             = [ty | (_,_,ty) <- sig_stuff]
-             ; sc_tys             = mkPredTys sc_theta
-             ; dict_component_tys = sc_tys ++ op_tys
-             ; sc_sel_ids         = [mkDictSelId sc_name rec_clas | sc_name <- sc_sel_names]
-             ; op_items = [ (mkDictSelId op_name rec_clas, dm_info)
-                          | (op_name, dm_info, _) <- sig_stuff ] }
+         let { rec_tycon  = classTyCon rec_clas
+             ; op_tys     = [ty | (_,_,ty) <- sig_stuff]
+             ; op_items   = [ (mkDictSelId 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) dict_component_tys)
+                                  (map (const NotMarkedStrict) op_tys)
                                   [{- No labelled fields -}]
                                   tvs [{- no existentials -}]
-                                   [{- No equalities -}] [{-No context-}] 
-                                   dict_component_tys 
+                                   [{- No GADT equalities -}] sc_theta 
+                                   op_tys
                                   rec_tycon
 
-       ; rhs <- case dict_component_tys of
-                           [rep_ty] -> mkNewTyConRhs tycon_name rec_tycon dict_con
-                           other    -> return (mkDataTyConRhs [dict_con])
+       ; sc_sel_names <- mapM (newImplicitBinder class_name . mkSuperDictSelOcc) 
+                               [1..length (dataConDictTheta dict_con)]
+             -- We number off the Dict superclass selectors, 1, 2, 3 etc so that we 
+             -- can construct names for the selectors.  Thus
+             --      class (C a, C b) => D a b where ...
+             -- gives superclass selectors
+             --      D_sc1, D_sc2
+             -- (We used to call them D_C, but now we can have two different
+             --  superclasses both called C!)
+        ; let sc_sel_ids = [mkDictSelId sc_name rec_clas | sc_name <- sc_sel_names]
+
+               -- Use a newtype if the class constructor has exactly one field:
+               -- i.e. exactly one operation or superclass taken together
+               -- Watch out: the sc_theta includes equality predicates,
+               --            which don't count for this purpose; hence dataConDictTheta
+       ; rhs <- if ((length $ dataConDictTheta dict_con) + length sig_stuff) == 1
+                then mkNewTyConRhs tycon_name rec_tycon dict_con
+                else return (mkDataTyConRhs [dict_con])
 
        ; let { clas_kind = mkArrowKinds (map tyVarKind tvs) liftedTypeKind
 
@@ -327,10 +343,13 @@ buildClass class_name tvs sc_theta fds ats sig_stuff tc_isrec
                -- newtype like a synonym, but that will lead to an infinite
                -- type]
              ; atTyCons = [tycon | ATyCon tycon <- ats]
+
+             ; result = mkClass class_name tvs fds 
+                                sc_theta sc_sel_ids atTyCons
+                                op_items tycon
              }
-       ; return (mkClass class_name tvs fds 
-                      sc_theta sc_sel_ids atTyCons op_items
-                      tycon)
+       ; traceIf (text "buildClass" <+> ppr tycon) 
+       ; return result
        })}
 \end{code}