f20d7965ecc6caef38b5155a85689519be611b90
[ghc-hetmet.git] / ghc / compiler / main / HscStats.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
3 %
4 \section[GHC_Stats]{Statistics for per-module compilations}
5
6 \begin{code}
7 module HscStats ( ppSourceStats ) where
8
9 #include "HsVersions.h"
10
11 import HsSyn
12 import TyCon            ( DataConDetails(..) )
13 import Outputable
14 import Char             ( isSpace )
15 import Util             ( count )
16 \end{code}
17
18 %************************************************************************
19 %*                                                                      *
20 \subsection{Statistics}
21 %*                                                                      *
22 %************************************************************************
23
24 \begin{code}
25 ppSourceStats short (HsModule name version exports imports decls _ src_loc)
26  = (if short then hcat else vcat)
27         (map pp_val
28                [("ExportAll        ", export_all), -- 1 if no export list
29                 ("ExportDecls      ", export_ds),
30                 ("ExportModules    ", export_ms),
31                 ("Imports          ", import_no),
32                 ("  ImpQual        ", import_qual),
33                 ("  ImpAs          ", import_as),
34                 ("  ImpAll         ", import_all),
35                 ("  ImpPartial     ", import_partial),
36                 ("  ImpHiding      ", import_hiding),
37                 ("FixityDecls      ", fixity_ds),
38                 ("DefaultDecls     ", default_ds),
39                 ("TypeDecls        ", type_ds),
40                 ("DataDecls        ", data_ds),
41                 ("NewTypeDecls     ", newt_ds),
42                 ("DataConstrs      ", data_constrs),
43                 ("DataDerivings    ", data_derivs),
44                 ("ClassDecls       ", class_ds),
45                 ("ClassMethods     ", class_method_ds),
46                 ("DefaultMethods   ", default_method_ds),
47                 ("InstDecls        ", inst_ds),
48                 ("InstMethods      ", inst_method_ds),
49                 ("TypeSigs         ", bind_tys),
50                 ("ValBinds         ", val_bind_ds),
51                 ("FunBinds         ", fn_bind_ds),
52                 ("InlineMeths      ", method_inlines),
53                 ("InlineBinds      ", bind_inlines),
54 --              ("SpecialisedData  ", data_specs),
55 --              ("SpecialisedInsts ", inst_specs),
56                 ("SpecialisedMeths ", method_specs),
57                 ("SpecialisedBinds ", bind_specs)
58                ])
59   where
60     pp_val (str, 0) = empty
61     pp_val (str, n) 
62       | not short   = hcat [text str, int n]
63       | otherwise   = hcat [text (trim str), equals, int n, semi]
64     
65     trim ls     = takeWhile (not.isSpace) (dropWhile isSpace ls)
66
67     fixity_ds   = count (\ x -> case x of { FixD{} -> True; _ -> False}) decls
68                 -- NB: this omits fixity decls on local bindings and
69                 -- in class decls.  ToDo
70
71     tycl_decls  = [d | TyClD d <- decls]
72     (class_ds, data_ds, newt_ds, type_ds, _) = countTyClDecls tycl_decls
73
74     inst_decls  = [d | InstD d <- decls]
75     inst_ds     = length inst_decls
76     default_ds  = count (\ x -> case x of { DefD{} -> True; _ -> False}) decls
77     val_decls   = [d | ValD d <- decls]
78
79     real_exports = case exports of { Nothing -> []; Just es -> es }
80     n_exports    = length real_exports
81     export_ms    = count (\ e -> case e of { IEModuleContents{} -> True;_ -> False})
82                          real_exports
83     export_ds    = n_exports - export_ms
84     export_all   = case exports of { Nothing -> 1; other -> 0 }
85
86     (val_bind_ds, fn_bind_ds, bind_tys, bind_specs, bind_inlines)
87         = count_binds (foldr ThenBinds EmptyBinds val_decls)
88
89     (import_no, import_qual, import_as, import_all, import_partial, import_hiding)
90         = foldr add6 (0,0,0,0,0,0) (map import_info imports)
91     (data_constrs, data_derivs)
92         = foldr add2 (0,0) (map data_info tycl_decls)
93     (class_method_ds, default_method_ds)
94         = foldr add2 (0,0) (map class_info tycl_decls)
95     (inst_method_ds, method_specs, method_inlines)
96         = foldr add3 (0,0,0) (map inst_info inst_decls)
97
98
99     count_binds EmptyBinds        = (0,0,0,0,0)
100     count_binds (ThenBinds b1 b2) = count_binds b1 `add5` count_binds b2
101     count_binds (MonoBind b sigs _) = case (count_monobinds b, count_sigs sigs) of
102                                         ((vs,fs),(ts,_,ss,is)) -> (vs,fs,ts,ss,is)
103
104     count_monobinds EmptyMonoBinds                 = (0,0)
105     count_monobinds (AndMonoBinds b1 b2)           = count_monobinds b1 `add2` count_monobinds b2
106     count_monobinds (PatMonoBind (VarPatIn n) r _) = (1,0)
107     count_monobinds (PatMonoBind p r _)            = (0,1)
108     count_monobinds (FunMonoBind f _ m _)          = (0,1)
109
110     count_mb_monobinds (Just mbs) = count_monobinds mbs
111     count_mb_monobinds Nothing    = (0,0)
112
113     count_sigs sigs = foldr add4 (0,0,0,0) (map sig_info sigs)
114
115     sig_info (Sig _ _ _)            = (1,0,0,0)
116     sig_info (ClassOpSig _ _ _ _)   = (0,1,0,0)
117     sig_info (SpecSig _ _ _)        = (0,0,1,0)
118     sig_info (InlineSig _ _ _ _)    = (0,0,0,1)
119     sig_info _                      = (0,0,0,0)
120
121     import_info (ImportDecl _ _ qual as spec _)
122         = add6 (1, qual_info qual, as_info as, 0,0,0) (spec_info spec)
123     qual_info False  = 0
124     qual_info True   = 1
125     as_info Nothing  = 0
126     as_info (Just _) = 1
127     spec_info Nothing           = (0,0,0,1,0,0)
128     spec_info (Just (False, _)) = (0,0,0,0,1,0)
129     spec_info (Just (True, _))  = (0,0,0,0,0,1)
130
131     data_info (TyData {tcdCons = DataCons cs, tcdDerivs = derivs})
132         = (length cs, case derivs of {Nothing -> 0; Just ds -> length ds})
133     data_info other = (0,0)
134
135     class_info decl@(ClassDecl {})
136         = case count_sigs (tcdSigs decl) of
137             (_,classops,_,_) ->
138                (classops, addpr (count_mb_monobinds (tcdMeths decl)))
139     class_info other = (0,0)
140
141     inst_info (InstDecl _ inst_meths inst_sigs _ _)
142         = case count_sigs inst_sigs of
143             (_,_,ss,is) ->
144                (addpr (count_monobinds inst_meths), ss, is)
145
146     addpr :: (Int,Int) -> Int
147     add1  :: Int -> Int -> Int
148     add2  :: (Int,Int) -> (Int,Int) -> (Int, Int)
149     add3  :: (Int,Int,Int) -> (Int,Int,Int) -> (Int, Int, Int)
150     add4  :: (Int,Int,Int,Int) -> (Int,Int,Int,Int) -> (Int, Int, Int, Int)
151     add5  :: (Int,Int,Int,Int,Int) -> (Int,Int,Int,Int,Int) -> (Int, Int, Int, Int, Int)
152     add6  :: (Int,Int,Int,Int,Int,Int) -> (Int,Int,Int,Int,Int,Int) -> (Int, Int, Int, Int, Int, Int)
153
154     addpr (x,y) = x+y
155     add1 x1 y1  = x1+y1
156     add2 (x1,x2) (y1,y2) = (x1+y1,x2+y2)
157     add3 (x1,x2,x3) (y1,y2,y3) = (x1+y1,x2+y2,x3+y3)
158     add4 (x1,x2,x3,x4) (y1,y2,y3,y4) = (x1+y1,x2+y2,x3+y3,x4+y4)
159     add5 (x1,x2,x3,x4,x5) (y1,y2,y3,y4,y5) = (x1+y1,x2+y2,x3+y3,x4+y4,x5+y5)
160     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)
161 \end{code}
162
163
164
165
166
167
168
169
170