Trace output
[ghc-hetmet.git] / compiler / iface / BuildTyCl.lhs
index ba383d8..8a3dfd7 100644 (file)
@@ -6,7 +6,7 @@
 \begin{code}
 module BuildTyCl (
        buildSynTyCon, buildAlgTyCon, buildDataCon,
-       buildClass,
+       TcMethInfo, buildClass,
        mkAbstractTyConRhs, mkOpenDataTyConRhs, 
        mkNewTyConRhs, mkDataTyConRhs, setAssocFamilyPermutation
     ) where
@@ -36,8 +36,8 @@ import Outputable
 ------------------------------------------------------
 buildSynTyCon :: Name -> [TyVar] 
               -> SynTyConRhs 
-             -> Kind                   -- Kind of the RHS
-             -> Maybe (TyCon, [Type])  -- family instance if applicable
+             -> Kind                   -- ^ Kind of the RHS
+             -> Maybe (TyCon, [Type])  -- ^ family instance if applicable
               -> TcRnIf m n TyCon
 
 buildSynTyCon tc_name tvs rhs@(OpenSynTyCon {}) rhs_kind _
@@ -61,12 +61,12 @@ buildSynTyCon tc_name tvs rhs@(SynonymTyCon {}) rhs_kind mb_family
 
 ------------------------------------------------------
 buildAlgTyCon :: Name -> [TyVar] 
-             -> ThetaType              -- Stupid theta
+             -> ThetaType              -- ^ Stupid theta
              -> AlgTyConRhs
              -> RecFlag
-             -> Bool                   -- True <=> want generics functions
-             -> Bool                   -- True <=> was declared in GADT syntax
-             -> Maybe (TyCon, [Type])  -- family instance if applicable
+             -> Bool                   -- ^ True <=> want generics functions
+             -> Bool                   -- ^ True <=> was declared in GADT syntax
+             -> Maybe (TyCon, [Type])  -- ^ family instance if applicable
              -> TcRnIf m n TyCon
 
 buildAlgTyCon tc_name tvs stupid_theta rhs is_rec want_generics gadt_syn
@@ -84,7 +84,7 @@ buildAlgTyCon tc_name tvs stupid_theta rhs is_rec want_generics gadt_syn
        ; return tycon 
        }
 
--- If a family tycon with instance types is given, the current tycon is an
+-- | If a family tycon with instance types is given, the current tycon is an
 -- instance of that family and we need to
 --
 -- (1) create a coercion that identifies the family instance type and the
@@ -118,12 +118,23 @@ 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
+                  --   <mod>_<type>_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
--- We pass the Name of the parent TyCon, as well as the TyCon itself,
--- because the latter is part of a knot, whereas the former is not.
+-- ^ Monadic because it makes a Name for the coercion TyCon
+--   We pass the Name of the parent TyCon, as well as the TyCon itself,
+--   because the latter is part of a knot, whereas the former is not.
 mkNewTyConRhs tycon_name tycon con 
   = do { co_tycon_name <- newImplicitBinder tycon_name mkNewTyCoOcc
        ; let co_tycon = mkNewTypeCoercion co_tycon_name tycon etad_tvs etad_rhs
@@ -180,7 +191,7 @@ setAssocFamilyPermutation _clas_tvs other
 
 ------------------------------------------------------
 buildDataCon :: Name -> Bool
-           -> [StrictnessMark] 
+           -> [HsBang] 
            -> [Name]                   -- Field labels
            -> [TyVar] -> [TyVar]       -- Univ and ext 
             -> [(TyVar,Type)]           -- Equality spec
@@ -235,14 +246,17 @@ mkDataConStupidTheta tycon arg_tys univ_tvs
 
 ------------------------------------------------------
 \begin{code}
+type TcMethInfo = (Name, DefMethSpec, Type)  -- A temporary intermediate, to communicate 
+                                            -- between tcClassSigs and buildClass
+
 buildClass :: Bool                     -- True <=> do not include unfoldings 
                                        --          on dict selectors
                                        -- Used when importing a class without -O
           -> Name -> [TyVar] -> ThetaType
-          -> [FunDep TyVar]            -- Functional dependencies
-          -> [TyThing]                 -- Associated types
-          -> [(Name, DefMeth, Type)]   -- Method info
-          -> RecFlag                   -- Info for type constructor
+          -> [FunDep TyVar]               -- Functional dependencies
+          -> [TyThing]                    -- Associated types
+          -> [TcMethInfo]                 -- Method info
+          -> RecFlag                      -- Info for type constructor
           -> TcRnIf m n Class
 
 buildClass no_unf class_name tvs sc_theta fds ats sig_stuff tc_isrec
@@ -255,11 +269,7 @@ buildClass no_unf class_name tvs sc_theta fds ats sig_stuff tc_isrec
 
        ; fixM (\ rec_clas -> do {      -- Only name generation inside loop
 
-         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 ] }
+       ; op_items <- mapM (mk_op_item rec_clas) sig_stuff
                        -- Build the selector id and default method id
 
        ; let n_value_preds   = count (not . isEqPred) sc_theta
@@ -290,12 +300,15 @@ buildClass no_unf class_name tvs sc_theta fds ats sig_stuff tc_isrec
                -- 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
-
+             args      = sc_sel_names ++ op_names
+             arg_tys   = map mkPredTy sc_theta ++ op_tys
+             op_tys    = [ty | (_,_,ty) <- sig_stuff]
+             op_names  = [op | (op,_,_) <- sig_stuff]
+              rec_tycon = classTyCon rec_clas
+               
        ; dict_con <- buildDataCon datacon_name
                                   False        -- Not declared infix
-                                  (map (const NotMarkedStrict) args)
+                                  (map (const HsNoBang) args)
                                   [{- No fields -}]
                                   tvs [{- no existentials -}]
                                    [{- No GADT equalities -}] [{- No theta -}]
@@ -328,6 +341,15 @@ buildClass no_unf class_name tvs sc_theta fds ats sig_stuff tc_isrec
        ; traceIf (text "buildClass" <+> ppr tycon) 
        ; return result
        })}
+  where
+    mk_op_item :: Class -> TcMethInfo -> TcRnIf n m ClassOpItem
+    mk_op_item rec_clas (op_name, dm_spec, _) 
+      = do { dm_info <- case dm_spec of
+                          NoDM      -> return NoDefMeth
+                          GenericDM -> return GenDefMeth
+                          VanillaDM -> do { dm_name <- newImplicitBinder op_name mkDefaultMethodOcc
+                                         ; return (DefMeth dm_name) }
+           ; return (mkDictSelId no_unf op_name rec_clas, dm_info) }
 \end{code}
 
 Note [Class newtypes and equality predicates]