Small fixes to the generics branch to get rid of warnings,
[ghc-hetmet.git] / compiler / main / HscStats.lhs
index d12831e..d902626 100644 (file)
@@ -6,18 +6,16 @@
 \begin{code}
 module HscStats ( ppSourceStats ) where
 
--- XXX This define is a bit of a hack, and should be done more nicely
-#define FAST_STRING_NOT_NEEDED 1
 #include "HsVersions.h"
 
 import HsSyn
 import Outputable
 import SrcLoc
-import Char
 import Bag
 import Util
-import Pretty ( Doc )
 import RdrName
+
+import Data.Char
 \end{code}
 
 %************************************************************************
@@ -27,8 +25,8 @@ import RdrName
 %************************************************************************
 
 \begin{code}
-ppSourceStats :: Bool -> Located (HsModule RdrName) -> PprStyle -> Doc
-ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _ _))
+ppSourceStats :: Bool -> Located (HsModule RdrName) -> SDoc
+ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _))
  = (if short then hcat else vcat)
         (map pp_val
               [("ExportAll        ", export_all), -- 1 if no export list
@@ -57,6 +55,7 @@ ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _ _))
                ("InstType         ", inst_type_ds),
                ("InstData         ", inst_data_ds),
                ("TypeSigs         ", bind_tys),
+               ("GenericSigs      ", generic_sigs),
                ("ValBinds         ", val_bind_ds),
                ("FunBinds         ", fn_bind_ds),
                ("InlineMeths      ", method_inlines),
@@ -76,7 +75,7 @@ ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _ _))
     
     trim ls     = takeWhile (not.isSpace) (dropWhile isSpace ls)
 
-    (fixity_sigs, bind_tys, bind_specs, bind_inlines) 
+    (fixity_sigs, bind_tys, bind_specs, bind_inlines, generic_sigs) 
        = count_sigs [d | SigD d <- decls]
                -- NB: this omits fixity decls on local bindings and
                -- in class decls.  ToDo
@@ -114,15 +113,16 @@ ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _ _))
     count_bind (FunBind {})                           = (0,1)
     count_bind b = pprPanic "count_bind: Unhandled binder" (ppr b)
 
-    count_sigs sigs = foldr add4 (0,0,0,0) (map sig_info sigs)
+    count_sigs sigs = foldr add5 (0,0,0,0,0) (map sig_info sigs)
 
-    sig_info (FixSig _)                = (1,0,0,0)
-    sig_info (TypeSig _ _)      = (0,1,0,0)
-    sig_info (SpecSig _ _ _)    = (0,0,1,0)
-    sig_info (InlineSig _ _)    = (0,0,0,1)
-    sig_info _                  = (0,0,0,0)
+    sig_info (FixSig _)                = (1,0,0,0,0)
+    sig_info (TypeSig _ _)      = (0,1,0,0,0)
+    sig_info (SpecSig _ _ _)    = (0,0,1,0,0)
+    sig_info (InlineSig _ _)    = (0,0,0,1,0)
+    sig_info (GenericSig _ _)   = (0,0,0,0,1)
+    sig_info _                  = (0,0,0,0,0)
 
-    import_info (L _ (ImportDecl _ _ qual as spec))
+    import_info (L _ (ImportDecl _ _ _ qual as spec))
        = add6 (1, qual_info qual, as_info as, 0,0,0) (spec_info spec)
     qual_info False  = 0
     qual_info True   = 1
@@ -139,13 +139,13 @@ ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _ _))
 
     class_info decl@(ClassDecl {})
        = case count_sigs (map unLoc (tcdSigs decl)) of
-           (_,classops,_,_) ->
+           (_,classops,_,_,_) ->
               (classops, addpr (foldr add2 (0,0) (map (count_bind.unLoc) (bagToList (tcdMeths decl)))))
     class_info _ = (0,0)
 
     inst_info (InstDecl _ inst_meths inst_sigs ats)
        = case count_sigs (map unLoc inst_sigs) of
-           (_,_,ss,is) ->
+           (_,_,ss,is,_) ->
              case foldr add2 (0, 0) (map (countATDecl . unLoc) ats) of
                (tyDecl, dtDecl) ->
                  (addpr (foldr add2 (0,0) 
@@ -159,13 +159,11 @@ ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _ _))
 
     addpr :: (Int,Int) -> Int
     add2  :: (Int,Int) -> (Int,Int) -> (Int, Int)
-    add4  :: (Int,Int,Int,Int) -> (Int,Int,Int,Int) -> (Int, Int, Int, Int)
     add5  :: (Int,Int,Int,Int,Int) -> (Int,Int,Int,Int,Int) -> (Int, Int, Int, Int, Int)
     add6  :: (Int,Int,Int,Int,Int,Int) -> (Int,Int,Int,Int,Int,Int) -> (Int, Int, Int, Int, Int, Int)
 
     addpr (x,y) = x+y
     add2 (x1,x2) (y1,y2) = (x1+y1,x2+y2)
-    add4 (x1,x2,x3,x4) (y1,y2,y3,y4) = (x1+y1,x2+y2,x3+y3,x4+y4)
     add5 (x1,x2,x3,x4,x5) (y1,y2,y3,y4,y5) = (x1+y1,x2+y2,x3+y3,x4+y4,x5+y5)
     add6 (x1,x2,x3,x4,x5,x6) (y1,y2,y3,y4,y5,y6) = (x1+y1,x2+y2,x3+y3,x4+y4,x5+y5,x6+y6)
 \end{code}