| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.HsToCore.Ticks
Synopsis
- data TicksConfig = TicksConfig {
- ticks_passes :: ![TickishType]
 - ticks_profAuto :: !ProfAuto
 - ticks_countEntries :: !Bool
 
 - data Tick = Tick {}
 - data TickishType
 - addTicksToBinds :: Logger -> TicksConfig -> Module -> ModLocation -> NameSet -> [TyCon] -> LHsBinds GhcTc -> IO (LHsBinds GhcTc, Maybe (FilePath, SizedSeq Tick))
 - isGoodSrcSpan' :: SrcSpan -> Bool
 - stripTicksTopHsExpr :: HsExpr GhcTc -> ([CoreTickish], HsExpr GhcTc)
 
Documentation
data TicksConfig Source #
Configuration for compilation pass to add tick for instrumentation to binding sites.
Constructors
| TicksConfig | |
Fields 
  | |
data TickishType Source #
Reasons why we need ticks,
Constructors
| ProfNotes | For profiling  | 
| HpcTicks | For Haskell Program Coverage  | 
| Breakpoints | For ByteCode interpreter break points  | 
| SourceNotes | For source notes  | 
Instances
| Eq TickishType Source # | |
Defined in GHC.HsToCore.Ticks  | |
Arguments
| :: Logger | |
| -> TicksConfig | |
| -> Module | |
| -> ModLocation | location of the current module  | 
| -> NameSet | Exported Ids. When we call addTicksToBinds, isExportedId doesn't work yet (the desugarer hasn't set it), so we have to work from this set.  | 
| -> [TyCon] | Type constructors in this module  | 
| -> LHsBinds GhcTc | |
| -> IO (LHsBinds GhcTc, Maybe (FilePath, SizedSeq Tick)) | 
isGoodSrcSpan' :: SrcSpan -> Bool Source #
stripTicksTopHsExpr :: HsExpr GhcTc -> ([CoreTickish], HsExpr GhcTc) Source #
Strip CoreTicks from an HsExpr