1{-# LANGUAGE DataKinds #-}
2{-# LANGUAGE DeriveDataTypeable #-}
3{-# LANGUAGE TypeFamilies #-}
4{-# LANGUAGE StandaloneDeriving #-}
5{-# LANGUAGE FlexibleContexts #-}
6{-# LANGUAGE FlexibleInstances #-}
7
8module GHC.Types.Tickish (
9  GenTickish(..),
10  CoreTickish, StgTickish, CmmTickish,
11  XTickishId,
12  tickishCounts,
13  TickishScoping(..),
14  tickishScoped,
15  tickishScopesLike,
16  tickishFloatable,
17  tickishCanSplit,
18  mkNoCount,
19  mkNoScope,
20  tickishIsCode,
21  TickishPlacement(..),
22  tickishPlace,
23  tickishContains
24) where
25
26import GHC.Prelude
27
28import GHC.Core.Type
29
30import GHC.Unit.Module
31
32import GHC.Types.CostCentre
33import GHC.Types.SrcLoc ( RealSrcSpan, containsSpan )
34import GHC.Types.Var
35
36import GHC.Utils.Panic
37
38import Language.Haskell.Syntax.Extension ( NoExtField )
39
40import Data.Data
41
42{- *********************************************************************
43*                                                                      *
44              Ticks
45*                                                                      *
46************************************************************************
47-}
48
49-- | Allows attaching extra information to points in expressions
50
51{- | Used as a data type index for the GenTickish annotations.
52     See Note [Tickish passes]
53 -}
54data TickishPass
55  = TickishPassCore
56  | TickishPassStg
57  | TickishPassCmm
58
59{-
60   Note [Tickish passes]
61
62   Tickish annotations store different information depending on
63   where they are used. Here's a summary of the differences
64   between the passes.
65
66   - CoreTickish: Haskell and Core
67         The tickish annotations store the free variables of
68         breakpoints.
69
70   - StgTickish: Stg
71         The GHCi bytecode generator (GHC.StgToByteCode) needs
72         to know the type of each breakpoint in addition to its
73         free variables. Since we cannot compute the type from
74         an STG expression, the tickish annotations store the
75         type of breakpoints in addition to the free variables.
76
77   - CmmTickish: Cmm
78         Breakpoints are unsupported and no free variables or
79         type are stored.
80 -}
81
82type family XBreakpoint (pass :: TickishPass)
83type instance XBreakpoint 'TickishPassCore = NoExtField
84-- | Keep track of the type of breakpoints in STG, for GHCi
85type instance XBreakpoint 'TickishPassStg  = Type
86type instance XBreakpoint 'TickishPassCmm  = NoExtField
87
88type family XTickishId (pass :: TickishPass)
89type instance XTickishId 'TickishPassCore = Id
90type instance XTickishId 'TickishPassStg = Id
91type instance XTickishId 'TickishPassCmm = NoExtField
92
93type CoreTickish = GenTickish 'TickishPassCore
94type StgTickish = GenTickish 'TickishPassStg
95-- | Tickish in Cmm context (annotations only)
96type CmmTickish = GenTickish 'TickishPassCmm
97
98-- If you edit this type, you may need to update the GHC formalism
99-- See Note [GHC Formalism] in GHC.Core.Lint
100data GenTickish pass =
101    -- | An @{-# SCC #-}@ profiling annotation, either automatically
102    -- added by the desugarer as a result of -auto-all, or added by
103    -- the user.
104    ProfNote {
105      profNoteCC    :: CostCentre, -- ^ the cost centre
106      profNoteCount :: !Bool,      -- ^ bump the entry count?
107      profNoteScope :: !Bool       -- ^ scopes over the enclosed expression
108                                   -- (i.e. not just a tick)
109    }
110
111  -- | A "tick" used by HPC to track the execution of each
112  -- subexpression in the original source code.
113  | HpcTick {
114      tickModule :: Module,
115      tickId     :: !Int
116    }
117
118  -- | A breakpoint for the GHCi debugger.  This behaves like an HPC
119  -- tick, but has a list of free variables which will be available
120  -- for inspection in GHCi when the program stops at the breakpoint.
121  --
122  -- NB. we must take account of these Ids when (a) counting free variables,
123  -- and (b) substituting (don't substitute for them)
124  | Breakpoint
125    { breakpointExt    :: XBreakpoint pass
126    , breakpointId     :: !Int
127    , breakpointFVs    :: [XTickishId pass]
128                                -- ^ the order of this list is important:
129                                -- it matches the order of the lists in the
130                                -- appropriate entry in 'GHC.ByteCode.Types.ModBreaks'.
131                                --
132                                -- Careful about substitution!  See
133                                -- Note [substTickish] in "GHC.Core.Subst".
134    }
135
136  -- | A source note.
137  --
138  -- Source notes are pure annotations: Their presence should neither
139  -- influence compilation nor execution. The semantics are given by
140  -- causality: The presence of a source note means that a local
141  -- change in the referenced source code span will possibly provoke
142  -- the generated code to change. On the flip-side, the functionality
143  -- of annotated code *must* be invariant against changes to all
144  -- source code *except* the spans referenced in the source notes
145  -- (see "Causality of optimized Haskell" paper for details).
146  --
147  -- Therefore extending the scope of any given source note is always
148  -- valid. Note that it is still undesirable though, as this reduces
149  -- their usefulness for debugging and profiling. Therefore we will
150  -- generally try only to make use of this property where it is
151  -- necessary to enable optimizations.
152  | SourceNote
153    { sourceSpan :: RealSrcSpan -- ^ Source covered
154    , sourceName :: String      -- ^ Name for source location
155                                --   (uses same names as CCs)
156    }
157
158deriving instance Eq (GenTickish 'TickishPassCore)
159deriving instance Ord (GenTickish 'TickishPassCore)
160deriving instance Data (GenTickish 'TickishPassCore)
161
162deriving instance Data (GenTickish 'TickishPassStg)
163
164deriving instance Eq (GenTickish 'TickishPassCmm)
165deriving instance Ord (GenTickish 'TickishPassCmm)
166deriving instance Data (GenTickish 'TickishPassCmm)
167
168
169-- | A "counting tick" (where tickishCounts is True) is one that
170-- counts evaluations in some way.  We cannot discard a counting tick,
171-- and the compiler should preserve the number of counting ticks as
172-- far as possible.
173--
174-- However, we still allow the simplifier to increase or decrease
175-- sharing, so in practice the actual number of ticks may vary, except
176-- that we never change the value from zero to non-zero or vice versa.
177tickishCounts :: GenTickish pass -> Bool
178tickishCounts n@ProfNote{} = profNoteCount n
179tickishCounts HpcTick{}    = True
180tickishCounts Breakpoint{} = True
181tickishCounts _            = False
182
183
184-- | Specifies the scoping behaviour of ticks. This governs the
185-- behaviour of ticks that care about the covered code and the cost
186-- associated with it. Important for ticks relating to profiling.
187data TickishScoping =
188    -- | No scoping: The tick does not care about what code it
189    -- covers. Transformations can freely move code inside as well as
190    -- outside without any additional annotation obligations
191    NoScope
192
193    -- | Soft scoping: We want all code that is covered to stay
194    -- covered.  Note that this scope type does not forbid
195    -- transformations from happening, as long as all results of
196    -- the transformations are still covered by this tick or a copy of
197    -- it. For example
198    --
199    --   let x = tick<...> (let y = foo in bar) in baz
200    --     ===>
201    --   let x = tick<...> bar; y = tick<...> foo in baz
202    --
203    -- Is a valid transformation as far as "bar" and "foo" is
204    -- concerned, because both still are scoped over by the tick.
205    --
206    -- Note though that one might object to the "let" not being
207    -- covered by the tick any more. However, we are generally lax
208    -- with this - constant costs don't matter too much, and given
209    -- that the "let" was effectively merged we can view it as having
210    -- lost its identity anyway.
211    --
212    -- Also note that this scoping behaviour allows floating a tick
213    -- "upwards" in pretty much any situation. For example:
214    --
215    --   case foo of x -> tick<...> bar
216    --     ==>
217    --   tick<...> case foo of x -> bar
218    --
219    -- While this is always legal, we want to make a best effort to
220    -- only make us of this where it exposes transformation
221    -- opportunities.
222  | SoftScope
223
224    -- | Cost centre scoping: We don't want any costs to move to other
225    -- cost-centre stacks. This means we not only want no code or cost
226    -- to get moved out of their cost centres, but we also object to
227    -- code getting associated with new cost-centre ticks - or
228    -- changing the order in which they get applied.
229    --
230    -- A rule of thumb is that we don't want any code to gain new
231    -- annotations. However, there are notable exceptions, for
232    -- example:
233    --
234    --   let f = \y -> foo in tick<...> ... (f x) ...
235    --     ==>
236    --   tick<...> ... foo[x/y] ...
237    --
238    -- In-lining lambdas like this is always legal, because inlining a
239    -- function does not change the cost-centre stack when the
240    -- function is called.
241  | CostCentreScope
242
243  deriving (Eq)
244
245-- | Returns the intended scoping rule for a Tickish
246tickishScoped :: GenTickish pass -> TickishScoping
247tickishScoped n@ProfNote{}
248  | profNoteScope n        = CostCentreScope
249  | otherwise              = NoScope
250tickishScoped HpcTick{}    = NoScope
251tickishScoped Breakpoint{} = CostCentreScope
252   -- Breakpoints are scoped: eventually we're going to do call
253   -- stacks, but also this helps prevent the simplifier from moving
254   -- breakpoints around and changing their result type (see #1531).
255tickishScoped SourceNote{} = SoftScope
256
257-- | Returns whether the tick scoping rule is at least as permissive
258-- as the given scoping rule.
259tickishScopesLike :: GenTickish pass -> TickishScoping -> Bool
260tickishScopesLike t scope = tickishScoped t `like` scope
261  where NoScope         `like` _               = True
262        _               `like` NoScope         = False
263        SoftScope       `like` _               = True
264        _               `like` SoftScope       = False
265        CostCentreScope `like` _               = True
266
267-- | Returns @True@ for ticks that can be floated upwards easily even
268-- where it might change execution counts, such as:
269--
270--   Just (tick<...> foo)
271--     ==>
272--   tick<...> (Just foo)
273--
274-- This is a combination of @tickishSoftScope@ and
275-- @tickishCounts@. Note that in principle splittable ticks can become
276-- floatable using @mkNoTick@ -- even though there's currently no
277-- tickish for which that is the case.
278tickishFloatable :: GenTickish pass -> Bool
279tickishFloatable t = t `tickishScopesLike` SoftScope && not (tickishCounts t)
280
281-- | Returns @True@ for a tick that is both counting /and/ scoping and
282-- can be split into its (tick, scope) parts using 'mkNoScope' and
283-- 'mkNoTick' respectively.
284tickishCanSplit :: GenTickish pass -> Bool
285tickishCanSplit ProfNote{profNoteScope = True, profNoteCount = True}
286                   = True
287tickishCanSplit _  = False
288
289mkNoCount :: GenTickish pass -> GenTickish pass
290mkNoCount n | not (tickishCounts n)   = n
291            | not (tickishCanSplit n) = panic "mkNoCount: Cannot split!"
292mkNoCount n@ProfNote{}                = n {profNoteCount = False}
293mkNoCount _                           = panic "mkNoCount: Undefined split!"
294
295mkNoScope :: GenTickish pass -> GenTickish pass
296mkNoScope n | tickishScoped n == NoScope  = n
297            | not (tickishCanSplit n)     = panic "mkNoScope: Cannot split!"
298mkNoScope n@ProfNote{}                    = n {profNoteScope = False}
299mkNoScope _                               = panic "mkNoScope: Undefined split!"
300
301-- | Return @True@ if this source annotation compiles to some backend
302-- code. Without this flag, the tickish is seen as a simple annotation
303-- that does not have any associated evaluation code.
304--
305-- What this means that we are allowed to disregard the tick if doing
306-- so means that we can skip generating any code in the first place. A
307-- typical example is top-level bindings:
308--
309--   foo = tick<...> \y -> ...
310--     ==>
311--   foo = \y -> tick<...> ...
312--
313-- Here there is just no operational difference between the first and
314-- the second version. Therefore code generation should simply
315-- translate the code as if it found the latter.
316tickishIsCode :: GenTickish pass -> Bool
317tickishIsCode SourceNote{} = False
318tickishIsCode _tickish     = True  -- all the rest for now
319
320
321-- | Governs the kind of expression that the tick gets placed on when
322-- annotating for example using @mkTick@. If we find that we want to
323-- put a tickish on an expression ruled out here, we try to float it
324-- inwards until we find a suitable expression.
325data TickishPlacement =
326
327    -- | Place ticks exactly on run-time expressions. We can still
328    -- move the tick through pure compile-time constructs such as
329    -- other ticks, casts or type lambdas. This is the most
330    -- restrictive placement rule for ticks, as all tickishs have in
331    -- common that they want to track runtime processes. The only
332    -- legal placement rule for counting ticks.
333    PlaceRuntime
334
335    -- | As @PlaceRuntime@, but we float the tick through all
336    -- lambdas. This makes sense where there is little difference
337    -- between annotating the lambda and annotating the lambda's code.
338  | PlaceNonLam
339
340    -- | In addition to floating through lambdas, cost-centre style
341    -- tickishs can also be moved from constructors, non-function
342    -- variables and literals. For example:
343    --
344    --   let x = scc<...> C (scc<...> y) (scc<...> 3) in ...
345    --
346    -- Neither the constructor application, the variable or the
347    -- literal are likely to have any cost worth mentioning. And even
348    -- if y names a thunk, the call would not care about the
349    -- evaluation context. Therefore removing all annotations in the
350    -- above example is safe.
351  | PlaceCostCentre
352
353  deriving (Eq)
354
355-- | Placement behaviour we want for the ticks
356tickishPlace :: GenTickish pass -> TickishPlacement
357tickishPlace n@ProfNote{}
358  | profNoteCount n        = PlaceRuntime
359  | otherwise              = PlaceCostCentre
360tickishPlace HpcTick{}     = PlaceRuntime
361tickishPlace Breakpoint{}  = PlaceRuntime
362tickishPlace SourceNote{}  = PlaceNonLam
363
364-- | Returns whether one tick "contains" the other one, therefore
365-- making the second tick redundant.
366tickishContains :: Eq (GenTickish pass)
367                => GenTickish pass -> GenTickish pass -> Bool
368tickishContains (SourceNote sp1 n1) (SourceNote sp2 n2)
369  = containsSpan sp1 sp2 && n1 == n2
370    -- compare the String last
371tickishContains t1 t2
372  = t1 == t2
373