X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FHscStats.lhs;h=750744af441abaa621f68231a06b6b46079b5ff5;hb=3c96346b3685f83885cea7906b0dbc536d7695f6;hp=8c8fee439d03ab32bd781226aedb3e5a65bb21af;hpb=9af77fa423926fbda946b31e174173d0ec5ebac8;p=ghc-hetmet.git diff --git a/ghc/compiler/main/HscStats.lhs b/ghc/compiler/main/HscStats.lhs index 8c8fee4..750744a 100644 --- a/ghc/compiler/main/HscStats.lhs +++ b/ghc/compiler/main/HscStats.lhs @@ -9,9 +9,10 @@ module HscStats ( ppSourceStats ) where #include "HsVersions.h" import HsSyn -import TyCon ( DataConDetails(..) ) import Outputable +import SrcLoc ( unLoc, Located(..) ) import Char ( isSpace ) +import Bag ( bagToList ) import Util ( count ) \end{code} @@ -22,7 +23,7 @@ import Util ( count ) %************************************************************************ \begin{code} -ppSourceStats short (HsModule name version exports imports decls _ src_loc) +ppSourceStats short (L _ (HsModule _ exports imports ldecls _)) = (if short then hcat else vcat) (map pp_val [("ExportAll ", export_all), -- 1 if no export list @@ -34,7 +35,7 @@ ppSourceStats short (HsModule name version exports imports decls _ src_loc) (" ImpAll ", import_all), (" ImpPartial ", import_partial), (" ImpHiding ", import_hiding), - ("FixityDecls ", fixity_ds), + ("FixityDecls ", fixity_sigs), ("DefaultDecls ", default_ds), ("TypeDecls ", type_ds), ("DataDecls ", data_ds), @@ -57,6 +58,8 @@ ppSourceStats short (HsModule name version exports imports decls _ src_loc) ("SpecialisedBinds ", bind_specs) ]) where + decls = map unLoc ldecls + pp_val (str, 0) = empty pp_val (str, n) | not short = hcat [text str, int n] @@ -64,12 +67,13 @@ ppSourceStats short (HsModule name version exports imports decls _ src_loc) trim ls = takeWhile (not.isSpace) (dropWhile isSpace ls) - fixity_ds = count (\ x -> case x of { FixD{} -> True; _ -> False}) decls + (fixity_sigs, bind_tys, bind_specs, bind_inlines) + = count_sigs [d | SigD d <- 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, type_ds, data_ds, newt_ds) = countTyClDecls tycl_decls inst_decls = [d | InstD d <- decls] inst_ds = length inst_decls @@ -78,13 +82,13 @@ ppSourceStats short (HsModule name version exports imports decls _ src_loc) real_exports = case exports of { Nothing -> []; Just es -> es } n_exports = length real_exports - export_ms = count (\ e -> case e of { IEModuleContents{} -> True;_ -> False}) + export_ms = count (\ e -> case unLoc e of { IEModuleContents{} -> True;_ -> False}) real_exports export_ds = n_exports - export_ms export_all = case exports of { Nothing -> 1; other -> 0 } - (val_bind_ds, fn_bind_ds, bind_tys, bind_specs, bind_inlines) - = count_binds (foldr ThenBinds EmptyBinds val_decls) + (val_bind_ds, fn_bind_ds) + = foldr add2 (0,0) (map count_bind val_decls) (import_no, import_qual, import_as, import_all, import_partial, import_hiding) = foldr add6 (0,0,0,0,0,0) (map import_info imports) @@ -95,30 +99,19 @@ ppSourceStats short (HsModule name version exports imports decls _ src_loc) (inst_method_ds, method_specs, method_inlines) = foldr add3 (0,0,0) (map inst_info inst_decls) - - count_binds EmptyBinds = (0,0,0,0,0) - count_binds (ThenBinds b1 b2) = count_binds b1 `add5` count_binds b2 - count_binds (MonoBind b sigs _) = case (count_monobinds b, count_sigs sigs) of - ((vs,fs),(ts,_,ss,is)) -> (vs,fs,ts,ss,is) - - count_monobinds EmptyMonoBinds = (0,0) - count_monobinds (AndMonoBinds b1 b2) = count_monobinds b1 `add2` count_monobinds b2 - count_monobinds (PatMonoBind (VarPat n) r _) = (1,0) - 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_bind (PatBind { pat_lhs = L _ (VarPat n) }) = (1,0) + count_bind (PatBind {}) = (0,1) + count_bind (FunBind {}) = (0,1) 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 _ = (0,0,0,0) + 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) - import_info (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 @@ -128,35 +121,32 @@ 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 {tcdCons = DataCons cs, tcdDerivs = derivs}) - = (length cs, case derivs of {Nothing -> 0; Just ds -> length ds}) + data_info (TyData {tcdCons = cs, tcdDerivs = derivs}) + = (length cs, case derivs of Nothing -> 0 + Just ds -> length ds) data_info other = (0,0) class_info decl@(ClassDecl {}) - = case count_sigs (tcdSigs decl) of + = case count_sigs (map unLoc (tcdSigs decl)) of (_,classops,_,_) -> - (classops, addpr (count_mb_monobinds (tcdMeths decl))) + (classops, addpr (foldr add2 (0,0) (map (count_bind.unLoc) (bagToList (tcdMeths decl))))) class_info other = (0,0) - inst_info (InstDecl _ inst_meths inst_sigs _ _) - = case count_sigs inst_sigs of + inst_info (InstDecl _ inst_meths inst_sigs) + = case count_sigs (map unLoc inst_sigs) of (_,_,ss,is) -> - (addpr (count_monobinds inst_meths), ss, is) + (addpr (foldr add2 (0,0) (map (count_bind.unLoc) (bagToList inst_meths))), ss, is) addpr :: (Int,Int) -> Int - add1 :: Int -> Int -> Int add2 :: (Int,Int) -> (Int,Int) -> (Int, Int) add3 :: (Int,Int,Int) -> (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 - add1 x1 y1 = x1+y1 add2 (x1,x2) (y1,y2) = (x1+y1,x2+y2) add3 (x1,x2,x3) (y1,y2,y3) = (x1+y1,x2+y2,x3+y3) 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}