summaryrefslogtreecommitdiff
path: root/compiler/simplStg/StgStats.hs
blob: 3f75ae23facbf1f28e66ce7180f8836cb1558f7d (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
{-
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998

\section[StgStats]{Gathers statistical information about programs}


The program gather statistics about
\begin{enumerate}
\item number of boxed cases
\item number of unboxed cases
\item number of let-no-escapes
\item number of non-updatable lets
\item number of updatable lets
\item number of applications
\item number of primitive applications
\item number of closures (does not include lets bound to constructors)
\item number of free variables in closures
%\item number of top-level functions
%\item number of top-level CAFs
\item number of constructors
\end{enumerate}
-}

{-# LANGUAGE CPP #-}

module StgStats ( showStgStats ) where

#include "HsVersions.h"

import StgSyn

import Id (Id)
import Panic

import Data.Map (Map)
import qualified Data.Map as Map

data CounterType
  = Literals
  | Applications
  | ConstructorApps
  | PrimitiveApps
  | LetNoEscapes
  | StgCases
  | FreeVariables
  | ConstructorBinds Bool{-True<=>top-level-}
  | ReEntrantBinds   Bool{-ditto-}
  | SingleEntryBinds Bool{-ditto-}
  | UpdatableBinds   Bool{-ditto-}
  deriving (Eq, Ord)

type Count      = Int
type StatEnv    = Map CounterType Count

emptySE :: StatEnv
emptySE = Map.empty

combineSE :: StatEnv -> StatEnv -> StatEnv
combineSE = Map.unionWith (+)

combineSEs :: [StatEnv] -> StatEnv
combineSEs = foldr combineSE emptySE

countOne :: CounterType -> StatEnv
countOne c = Map.singleton c 1

countN :: CounterType -> Int -> StatEnv
countN = Map.singleton

{-
************************************************************************
*                                                                      *
\subsection{Top-level list of bindings (a ``program'')}
*                                                                      *
************************************************************************
-}

showStgStats :: [StgTopBinding] -> String

showStgStats prog
  = "STG Statistics:\n\n"
    ++ concat (map showc (Map.toList (gatherStgStats prog)))
  where
    showc (x,n) = (showString (s x) . shows n) "\n"

    s Literals                = "Literals                   "
    s Applications            = "Applications               "
    s ConstructorApps         = "ConstructorApps            "
    s PrimitiveApps           = "PrimitiveApps              "
    s LetNoEscapes            = "LetNoEscapes               "
    s StgCases                = "StgCases                   "
    s FreeVariables           = "FreeVariables              "
    s (ConstructorBinds True) = "ConstructorBinds_Top       "
    s (ReEntrantBinds True)   = "ReEntrantBinds_Top         "
    s (SingleEntryBinds True) = "SingleEntryBinds_Top       "
    s (UpdatableBinds True)   = "UpdatableBinds_Top         "
    s (ConstructorBinds _)    = "ConstructorBinds_Nested    "
    s (ReEntrantBinds _)      = "ReEntrantBindsBinds_Nested "
    s (SingleEntryBinds _)    = "SingleEntryBinds_Nested    "
    s (UpdatableBinds _)      = "UpdatableBinds_Nested      "

gatherStgStats :: [StgTopBinding] -> StatEnv
gatherStgStats binds = combineSEs (map statTopBinding binds)

{-
************************************************************************
*                                                                      *
\subsection{Bindings}
*                                                                      *
************************************************************************
-}

statTopBinding :: StgTopBinding -> StatEnv
statTopBinding (StgTopStringLit _ _) = countOne Literals
statTopBinding (StgTopLifted bind) = statBinding True bind

statBinding :: Bool -- True <=> top-level; False <=> nested
            -> StgBinding
            -> StatEnv

statBinding top (StgNonRec b rhs)
  = statRhs top (b, rhs)

statBinding top (StgRec pairs)
  = combineSEs (map (statRhs top) pairs)

statRhs :: Bool -> (Id, StgRhs) -> StatEnv

statRhs top (_, StgRhsCon _ _ _)
  = countOne (ConstructorBinds top)

statRhs top (_, StgRhsClosure _ _ fv u _ body)
  = statExpr body                       `combineSE`
    countN FreeVariables (length fv)    `combineSE`
    countOne (
      case u of
        ReEntrant   -> ReEntrantBinds   top
        Updatable   -> UpdatableBinds   top
        SingleEntry -> SingleEntryBinds top
    )

{-
************************************************************************
*                                                                      *
\subsection{Expressions}
*                                                                      *
************************************************************************
-}

statExpr :: StgExpr -> StatEnv

statExpr (StgApp _ _)     = countOne Applications
statExpr (StgLit _)       = countOne Literals
statExpr (StgConApp _ _ _)= countOne ConstructorApps
statExpr (StgOpApp _ _ _) = countOne PrimitiveApps
statExpr (StgTick _ e)    = statExpr e

statExpr (StgLetNoEscape binds body)
  = statBinding False{-not top-level-} binds    `combineSE`
    statExpr body                               `combineSE`
    countOne LetNoEscapes

statExpr (StgLet binds body)
  = statBinding False{-not top-level-} binds    `combineSE`
    statExpr body

statExpr (StgCase expr _ _ alts)
  = statExpr expr       `combineSE`
    stat_alts alts      `combineSE`
    countOne StgCases
  where
    stat_alts alts
        = combineSEs (map statExpr [ e | (_,_,e) <- alts ])

statExpr (StgLam {}) = panic "statExpr StgLam"