[project @ 2002-07-16 14:56:08 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / HscStats.lhs
index bb75ae1..f20d796 100644 (file)
@@ -9,8 +9,10 @@ module HscStats ( ppSourceStats ) where
 #include "HsVersions.h"
 
 import HsSyn
+import TyCon           ( DataConDetails(..) )
 import Outputable
 import Char            ( isSpace )
+import Util             ( count )
 \end{code}
 
 %************************************************************************
@@ -62,21 +64,22 @@ ppSourceStats short (HsModule name version exports imports decls _ src_loc)
     
     trim ls     = takeWhile (not.isSpace) (dropWhile isSpace ls)
 
-    fixity_ds   = length [() | FixD d <- decls]
+    fixity_ds   = count (\ x -> case x of { FixD{} -> True; _ -> False}) decls
                -- NB: this omits fixity decls on local bindings and
                -- in class decls.  ToDo
 
     tycl_decls  = [d | TyClD d <- decls]
-    (class_ds, data_ds, newt_ds, type_ds) = countTyClDecls tycl_decls
+    (class_ds, data_ds, newt_ds, type_ds, _) = countTyClDecls tycl_decls
 
     inst_decls  = [d | InstD d <- decls]
     inst_ds     = length inst_decls
-    default_ds  = length [() | DefD _ <- decls]
+    default_ds  = count (\ x -> case x of { DefD{} -> True; _ -> False}) decls
     val_decls   = [d | ValD d <- decls]
 
     real_exports = case exports of { Nothing -> []; Just es -> es }
     n_exports           = length real_exports
-    export_ms           = length [() | IEModuleContents _ <- real_exports]
+    export_ms           = count (\ e -> case e of { IEModuleContents{} -> True;_ -> False})
+                         real_exports
     export_ds           = n_exports - export_ms
     export_all          = case exports of { Nothing -> 1; other -> 0 }
 
@@ -104,13 +107,15 @@ ppSourceStats short (HsModule name version exports imports decls _ src_loc)
     count_monobinds (PatMonoBind p r _)            = (0,1)
     count_monobinds (FunMonoBind f _ m _)          = (0,1)
 
+    count_mb_monobinds (Just mbs) = count_monobinds mbs
+    count_mb_monobinds Nothing   = (0,0)
+
     count_sigs sigs = foldr add4 (0,0,0,0) (map sig_info sigs)
 
     sig_info (Sig _ _ _)            = (1,0,0,0)
     sig_info (ClassOpSig _ _ _ _)   = (0,1,0,0)
     sig_info (SpecSig _ _ _)        = (0,0,1,0)
-    sig_info (InlineSig _ _ _)      = (0,0,0,1)
-    sig_info (NoInlineSig _ _ _)    = (0,0,0,1)
+    sig_info (InlineSig _ _ _ _)    = (0,0,0,1)
     sig_info _                      = (0,0,0,0)
 
     import_info (ImportDecl _ _ qual as spec _)
@@ -123,14 +128,14 @@ ppSourceStats short (HsModule name version exports imports decls _ src_loc)
     spec_info (Just (False, _)) = (0,0,0,0,1,0)
     spec_info (Just (True, _))  = (0,0,0,0,0,1)
 
-    data_info (TyData _ _ _ _ _ nconstrs derivs _ _ _)
-       = (nconstrs, case derivs of {Nothing -> 0; Just ds -> length ds})
+    data_info (TyData {tcdCons = DataCons cs, tcdDerivs = derivs})
+       = (length cs, case derivs of {Nothing -> 0; Just ds -> length ds})
     data_info other = (0,0)
 
-    class_info (ClassDecl _ _ _ _ meth_sigs def_meths _ _ )
-       = case count_sigs meth_sigs of
+    class_info decl@(ClassDecl {})
+       = case count_sigs (tcdSigs decl) of
            (_,classops,_,_) ->
-              (classops, addpr (count_monobinds def_meths))
+              (classops, addpr (count_mb_monobinds (tcdMeths decl)))
     class_info other = (0,0)
 
     inst_info (InstDecl _ inst_meths inst_sigs _ _)