2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
4 \section[GHC_Stats]{Statistics for per-module compilations}
8 -- The above warning supression flag is a temporary kludge.
9 -- While working on this module you are encouraged to remove it and fix
10 -- any warnings in the module. See
11 -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
14 module HscStats ( ppSourceStats ) where
16 #include "HsVersions.h"
20 import SrcLoc ( unLoc, Located(..) )
21 import Char ( isSpace )
22 import Bag ( bagToList )
26 %************************************************************************
28 \subsection{Statistics}
30 %************************************************************************
33 ppSourceStats short (L _ (HsModule _ exports imports ldecls _ _ _))
34 = (if short then hcat else vcat)
36 [("ExportAll ", export_all), -- 1 if no export list
37 ("ExportDecls ", export_ds),
38 ("ExportModules ", export_ms),
39 ("Imports ", import_no),
40 (" ImpQual ", import_qual),
41 (" ImpAs ", import_as),
42 (" ImpAll ", import_all),
43 (" ImpPartial ", import_partial),
44 (" ImpHiding ", import_hiding),
45 ("FixityDecls ", fixity_sigs),
46 ("DefaultDecls ", default_ds),
47 ("TypeDecls ", type_ds),
48 ("DataDecls ", data_ds),
49 ("NewTypeDecls ", newt_ds),
50 ("TypeFamilyDecls ", type_fam_ds),
51 ("FamilyInstDecls ", fam_inst_ds),
52 ("DataConstrs ", data_constrs),
53 ("DataDerivings ", data_derivs),
54 ("ClassDecls ", class_ds),
55 ("ClassMethods ", class_method_ds),
56 ("DefaultMethods ", default_method_ds),
57 ("InstDecls ", inst_ds),
58 ("InstMethods ", inst_method_ds),
59 ("InstType ", inst_type_ds),
60 ("InstData ", inst_data_ds),
61 ("TypeSigs ", bind_tys),
62 ("ValBinds ", val_bind_ds),
63 ("FunBinds ", fn_bind_ds),
64 ("InlineMeths ", method_inlines),
65 ("InlineBinds ", bind_inlines),
66 -- ("SpecialisedData ", data_specs),
67 -- ("SpecialisedInsts ", inst_specs),
68 ("SpecialisedMeths ", method_specs),
69 ("SpecialisedBinds ", bind_specs)
72 decls = map unLoc ldecls
74 pp_val (str, 0) = empty
76 | not short = hcat [text str, int n]
77 | otherwise = hcat [text (trim str), equals, int n, semi]
79 trim ls = takeWhile (not.isSpace) (dropWhile isSpace ls)
81 (fixity_sigs, bind_tys, bind_specs, bind_inlines)
82 = count_sigs [d | SigD d <- decls]
83 -- NB: this omits fixity decls on local bindings and
84 -- in class decls. ToDo
86 tycl_decls = [d | TyClD d <- decls]
87 (class_ds, type_ds, data_ds, newt_ds, type_fam_ds, fam_inst_ds) =
88 countTyClDecls tycl_decls
90 inst_decls = [d | InstD d <- decls]
91 inst_ds = length inst_decls
92 default_ds = count (\ x -> case x of { DefD{} -> True; _ -> False}) decls
93 val_decls = [d | ValD d <- decls]
95 real_exports = case exports of { Nothing -> []; Just es -> es }
96 n_exports = length real_exports
97 export_ms = count (\ e -> case unLoc e of { IEModuleContents{} -> True;_ -> False})
99 export_ds = n_exports - export_ms
100 export_all = case exports of { Nothing -> 1; other -> 0 }
102 (val_bind_ds, fn_bind_ds)
103 = foldr add2 (0,0) (map count_bind val_decls)
105 (import_no, import_qual, import_as, import_all, import_partial, import_hiding)
106 = foldr add6 (0,0,0,0,0,0) (map import_info imports)
107 (data_constrs, data_derivs)
108 = foldr add2 (0,0) (map data_info tycl_decls)
109 (class_method_ds, default_method_ds)
110 = foldr add2 (0,0) (map class_info tycl_decls)
111 (inst_method_ds, method_specs, method_inlines, inst_type_ds, inst_data_ds)
112 = foldr add5 (0,0,0,0,0) (map inst_info inst_decls)
114 count_bind (PatBind { pat_lhs = L _ (VarPat n) }) = (1,0)
115 count_bind (PatBind {}) = (0,1)
116 count_bind (FunBind {}) = (0,1)
118 count_sigs sigs = foldr add4 (0,0,0,0) (map sig_info sigs)
120 sig_info (FixSig _) = (1,0,0,0)
121 sig_info (TypeSig _ _) = (0,1,0,0)
122 sig_info (SpecSig _ _ _) = (0,0,1,0)
123 sig_info (InlineSig _ _) = (0,0,0,1)
124 sig_info _ = (0,0,0,0)
126 import_info (L _ (ImportDecl _ _ qual as spec))
127 = add6 (1, qual_info qual, as_info as, 0,0,0) (spec_info spec)
132 spec_info Nothing = (0,0,0,1,0,0)
133 spec_info (Just (False, _)) = (0,0,0,0,1,0)
134 spec_info (Just (True, _)) = (0,0,0,0,0,1)
136 data_info (TyData {tcdCons = cs, tcdDerivs = derivs})
137 = (length cs, case derivs of Nothing -> 0
138 Just ds -> length ds)
139 data_info other = (0,0)
141 class_info decl@(ClassDecl {})
142 = case count_sigs (map unLoc (tcdSigs decl)) of
144 (classops, addpr (foldr add2 (0,0) (map (count_bind.unLoc) (bagToList (tcdMeths decl)))))
145 class_info other = (0,0)
147 inst_info (InstDecl _ inst_meths inst_sigs ats)
148 = case count_sigs (map unLoc inst_sigs) of
150 case foldr add2 (0, 0) (map (countATDecl . unLoc) ats) of
152 (addpr (foldr add2 (0,0)
153 (map (count_bind.unLoc) (bagToList inst_meths))),
154 ss, is, tyDecl, dtDecl)
156 countATDecl (TyData {}) = (0, 1)
157 countATDecl (TySynonym {}) = (1, 0)
159 addpr :: (Int,Int) -> Int
160 add2 :: (Int,Int) -> (Int,Int) -> (Int, Int)
161 add3 :: (Int,Int,Int) -> (Int,Int,Int) -> (Int, Int, Int)
162 add4 :: (Int,Int,Int,Int) -> (Int,Int,Int,Int) -> (Int, Int, Int, Int)
163 add5 :: (Int,Int,Int,Int,Int) -> (Int,Int,Int,Int,Int) -> (Int, Int, Int, Int, Int)
164 add6 :: (Int,Int,Int,Int,Int,Int) -> (Int,Int,Int,Int,Int,Int) -> (Int, Int, Int, Int, Int, Int)
167 add2 (x1,x2) (y1,y2) = (x1+y1,x2+y2)
168 add3 (x1,x2,x3) (y1,y2,y3) = (x1+y1,x2+y2,x3+y3)
169 add4 (x1,x2,x3,x4) (y1,y2,y3,y4) = (x1+y1,x2+y2,x3+y3,x4+y4)
170 add5 (x1,x2,x3,x4,x5) (y1,y2,y3,y4,y5) = (x1+y1,x2+y2,x3+y3,x4+y4,x5+y5)
171 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)