Safe Haskell | None |
---|---|
Language | Haskell2010 |
Collect statistics.
Synopsis
- class ReadTCState m => MonadStatistics (m :: Type -> Type) where
- modifyCounter :: String -> (Integer -> Integer) -> m ()
- tick :: MonadStatistics m => String -> m ()
- tickN :: MonadStatistics m => String -> Integer -> m ()
- tickMax :: MonadStatistics m => String -> Integer -> m ()
- getStatistics :: ReadTCState m => m Statistics
- modifyStatistics :: (Statistics -> Statistics) -> TCM ()
- printStatistics :: (MonadDebug m, MonadTCEnv m, HasOptions m) => Maybe TopLevelModuleName -> Statistics -> m ()
Documentation
class ReadTCState m => MonadStatistics (m :: Type -> Type) where Source #
Nothing
modifyCounter :: String -> (Integer -> Integer) -> m () Source #
default modifyCounter :: forall (n :: Type -> Type) (t :: (Type -> Type) -> Type -> Type). (MonadStatistics n, MonadTrans t, t n ~ m) => String -> (Integer -> Integer) -> m () Source #
Instances
tick :: MonadStatistics m => String -> m () Source #
Increase specified counter by 1
.
tickN :: MonadStatistics m => String -> Integer -> m () Source #
Increase specified counter by n
.
tickMax :: MonadStatistics m => String -> Integer -> m () Source #
Set the specified counter to the maximum of its current value and n
.
getStatistics :: ReadTCState m => m Statistics Source #
Get the statistics.
modifyStatistics :: (Statistics -> Statistics) -> TCM () Source #
Modify the statistics via given function.
printStatistics :: (MonadDebug m, MonadTCEnv m, HasOptions m) => Maybe TopLevelModuleName -> Statistics -> m () Source #
Print the given statistics.