Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data GenTickish pass
- = ProfNote {
- profNoteCC :: CostCentre
- profNoteCount :: !Bool
- profNoteScope :: !Bool
- | HpcTick {
- tickModule :: Module
- tickId :: !Int
- | Breakpoint {
- breakpointExt :: XBreakpoint pass
- breakpointId :: !Int
- breakpointFVs :: [XTickishId pass]
- | SourceNote { }
- = ProfNote {
- type CoreTickish = GenTickish 'TickishPassCore
- type StgTickish = GenTickish 'TickishPassStg
- type CmmTickish = GenTickish 'TickishPassCmm
- type family XTickishId (pass :: TickishPass)
- tickishCounts :: GenTickish pass -> Bool
- data TickishScoping
- tickishScoped :: GenTickish pass -> TickishScoping
- tickishScopesLike :: GenTickish pass -> TickishScoping -> Bool
- tickishFloatable :: GenTickish pass -> Bool
- tickishCanSplit :: GenTickish pass -> Bool
- mkNoCount :: GenTickish pass -> GenTickish pass
- mkNoScope :: GenTickish pass -> GenTickish pass
- tickishIsCode :: GenTickish pass -> Bool
- isProfTick :: GenTickish pass -> Bool
- data TickishPlacement
- tickishPlace :: GenTickish pass -> TickishPlacement
- tickishContains :: Eq (GenTickish pass) => GenTickish pass -> GenTickish pass -> Bool
Documentation
data GenTickish pass Source #
ProfNote | An |
| |
HpcTick | A "tick" used by HPC to track the execution of each subexpression in the original source code. |
| |
Breakpoint | A breakpoint for the GHCi debugger. This behaves like an HPC tick, but has a list of free variables which will be available for inspection in GHCi when the program stops at the breakpoint. NB. we must take account of these Ids when (a) counting free variables, and (b) substituting (don't substitute for them) |
| |
SourceNote | A source note. Source notes are pure annotations: Their presence should neither influence compilation nor execution. The semantics are given by causality: The presence of a source note means that a local change in the referenced source code span will possibly provoke the generated code to change. On the flip-side, the functionality of annotated code *must* be invariant against changes to all source code *except* the spans referenced in the source notes (see "Causality of optimized Haskell" paper for details). Therefore extending the scope of any given source note is always valid. Note that it is still undesirable though, as this reduces their usefulness for debugging and profiling. Therefore we will generally try only to make use of this property where it is necessary to enable optimizations. |
|
Instances
Outputable (XTickishId pass) => Outputable (GenTickish pass) Source # | |
Defined in GHC.Core.Ppr ppr :: GenTickish pass -> SDoc Source # |
type CoreTickish = GenTickish 'TickishPassCore Source #
type StgTickish = GenTickish 'TickishPassStg Source #
type CmmTickish = GenTickish 'TickishPassCmm Source #
Tickish in Cmm context (annotations only)
type family XTickishId (pass :: TickishPass) Source #
tickishCounts :: GenTickish pass -> Bool Source #
A "counting tick" (where tickishCounts is True) is one that counts evaluations in some way. We cannot discard a counting tick, and the compiler should preserve the number of counting ticks as far as possible.
However, we still allow the simplifier to increase or decrease sharing, so in practice the actual number of ticks may vary, except that we never change the value from zero to non-zero or vice versa.
data TickishScoping Source #
Specifies the scoping behaviour of ticks. This governs the behaviour of ticks that care about the covered code and the cost associated with it. Important for ticks relating to profiling.
NoScope | No scoping: The tick does not care about what code it covers. Transformations can freely move code inside as well as outside without any additional annotation obligations |
SoftScope | Soft scoping: We want all code that is covered to stay covered. Note that this scope type does not forbid transformations from happening, as long as all results of the transformations are still covered by this tick or a copy of it. For example let x = tick... (let y = foo in bar) in baz ===> let x = tick... bar; y = tick... foo in baz Is a valid transformation as far as "bar" and "foo" is concerned, because both still are scoped over by the tick. Note though that one might object to the "let" not being covered by the tick any more. However, we are generally lax with this - constant costs don't matter too much, and given that the "let" was effectively merged we can view it as having lost its identity anyway. Also note that this scoping behaviour allows floating a tick "upwards" in pretty much any situation. For example: case foo of x -> tick... bar ==> tick... case foo of x -> bar While this is always legal, we want to make a best effort to only make us of this where it exposes transformation opportunities. |
CostCentreScope | Cost centre scoping: We don't want any costs to move to other cost-centre stacks. This means we not only want no code or cost to get moved out of their cost centres, but we also object to code getting associated with new cost-centre ticks - or changing the order in which they get applied. A rule of thumb is that we don't want any code to gain new annotations. However, there are notable exceptions, for example: let f = y -> foo in tick... ... (f x) ... ==> tick... ... foo[x/y] ... In-lining lambdas like this is always legal, because inlining a function does not change the cost-centre stack when the function is called. |
Instances
Eq TickishScoping Source # | |
Defined in GHC.Types.Tickish (==) :: TickishScoping -> TickishScoping -> Bool # (/=) :: TickishScoping -> TickishScoping -> Bool # |
tickishScoped :: GenTickish pass -> TickishScoping Source #
Returns the intended scoping rule for a Tickish
tickishScopesLike :: GenTickish pass -> TickishScoping -> Bool Source #
Returns whether the tick scoping rule is at least as permissive as the given scoping rule.
tickishFloatable :: GenTickish pass -> Bool Source #
Returns True
for ticks that can be floated upwards easily even
where it might change execution counts, such as:
Just (tick... foo) ==> tick... (Just foo)
This is a combination of tickishSoftScope
and
tickishCounts
. Note that in principle splittable ticks can become
floatable using mkNoTick
-- even though there's currently no
tickish for which that is the case.
tickishCanSplit :: GenTickish pass -> Bool Source #
Returns True
for a tick that is both counting and scoping and
can be split into its (tick, scope) parts using mkNoScope
and
mkNoTick
respectively.
mkNoCount :: GenTickish pass -> GenTickish pass Source #
mkNoScope :: GenTickish pass -> GenTickish pass Source #
tickishIsCode :: GenTickish pass -> Bool Source #
Return True
if this source annotation compiles to some backend
code. Without this flag, the tickish is seen as a simple annotation
that does not have any associated evaluation code.
What this means that we are allowed to disregard the tick if doing so means that we can skip generating any code in the first place. A typical example is top-level bindings:
foo = tick... y -> ... ==> foo = y -> tick... ...
Here there is just no operational difference between the first and the second version. Therefore code generation should simply translate the code as if it found the latter.
isProfTick :: GenTickish pass -> Bool Source #
data TickishPlacement Source #
Governs the kind of expression that the tick gets placed on when
annotating for example using mkTick
. If we find that we want to
put a tickish on an expression ruled out here, we try to float it
inwards until we find a suitable expression.
PlaceRuntime | Place ticks exactly on run-time expressions. We can still
move the tick through pure compile-time constructs such as
other ticks, casts or type lambdas. This is the most
restrictive placement rule for ticks, as all tickishs have in
common that they want to track runtime processes. The only
legal placement rule for counting ticks.
NB: We generally try to move these as close to the relevant
runtime expression as possible. This means they get pushed through
tyoe arguments. E.g. we create `(tick f) |
PlaceNonLam | As |
PlaceCostCentre | In addition to floating through lambdas, cost-centre style tickishs can also be moved from constructors, non-function variables and literals. For example: let x = scc... C (scc... y) (scc... 3) in ... Neither the constructor application, the variable or the literal are likely to have any cost worth mentioning. And even if y names a thunk, the call would not care about the evaluation context. Therefore removing all annotations in the above example is safe. |
Instances
Show TickishPlacement Source # | |
Defined in GHC.Types.Tickish | |
Outputable TickishPlacement Source # | |
Defined in GHC.Types.Tickish ppr :: TickishPlacement -> SDoc Source # | |
Eq TickishPlacement Source # | |
Defined in GHC.Types.Tickish (==) :: TickishPlacement -> TickishPlacement -> Bool # (/=) :: TickishPlacement -> TickishPlacement -> Bool # |
tickishPlace :: GenTickish pass -> TickishPlacement Source #
Placement behaviour we want for the ticks
tickishContains :: Eq (GenTickish pass) => GenTickish pass -> GenTickish pass -> Bool Source #
Returns whether one tick "contains" the other one, therefore making the second tick redundant.