| Stability | experimental |
|---|---|
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
GHC.Eventlog.Live.Machine.Core
Description
Synopsis
- data Tick a
- batchByTick :: forall (m :: Type -> Type) a. (Monad m, Monoid a) => ProcessT m (Tick a) a
- batchToTick :: forall (f :: Type -> Type) a. Foldable f => Process (f a) (Tick a)
- batchListToTick :: forall a (m :: Type -> Type). Monad m => MachineT m (Is [a]) (Tick a)
- batchByTickList :: forall a (m :: Type -> Type). Monad m => MachineT m (Is (Tick a)) [a]
- liftTick :: forall (m :: Type -> Type) a b. Monad m => ProcessT m a b -> ProcessT m (Tick a) (Tick b)
- dropTick :: forall a (m :: Type -> Type). Monad m => MachineT m (Is (Tick a)) a
- onlyTick :: forall a (m :: Type -> Type). Monad m => MachineT m (Is (Tick a)) ()
- liftBatch :: forall (m :: Type -> Type) a b. Monad m => ProcessT m a b -> ProcessT m [a] [b]
- counterBy :: forall (m :: Type -> Type) a x. MonadIO m => Verbosity -> Text -> (a -> Word) -> ProcessT m a x
- counterByTick :: forall (m :: Type -> Type) a x. MonadIO m => Verbosity -> Text -> ProcessT m (Tick a) x
- liftRouter :: forall (m :: Type -> Type) k a b. (MonadIO m, Hashable k) => (a -> Maybe k) -> (k -> ProcessT m a b) -> ProcessT m a b
- sortByBatch :: forall (m :: Type -> Type) a. Monad m => (a -> Timestamp) -> ProcessT m [a] [a]
- sortByBatchTick :: (a -> Timestamp) -> Process (Tick a) (Tick a)
- between :: Text -> Text -> Moore Text Bool
- delimit :: forall (m :: Type -> Type). Monad m => Moore Text Bool -> ProcessT m Event Event
- validateInput :: forall (m :: Type -> Type) a x. MonadIO m => Verbosity -> Int -> ProcessT m (Tick a) x
- validateOrder :: forall (m :: Type -> Type) a x. (MonadIO m, Show a) => Verbosity -> (a -> Timestamp) -> ProcessT m a x
Ticks
The type of data on a stream of items and ticks.
The Tick type is isomorphic to Maybe modulo strictness,
but with the caveat that Tick does not represent failure.
Instances
| Foldable Tick Source # | |
Defined in GHC.Eventlog.Live.Machine.Core Methods fold :: Monoid m => Tick m -> m # foldMap :: Monoid m => (a -> m) -> Tick a -> m # foldMap' :: Monoid m => (a -> m) -> Tick a -> m # foldr :: (a -> b -> b) -> b -> Tick a -> b # foldr' :: (a -> b -> b) -> b -> Tick a -> b # foldl :: (b -> a -> b) -> b -> Tick a -> b # foldl' :: (b -> a -> b) -> b -> Tick a -> b # foldr1 :: (a -> a -> a) -> Tick a -> a # foldl1 :: (a -> a -> a) -> Tick a -> a # elem :: Eq a => a -> Tick a -> Bool # maximum :: Ord a => Tick a -> a # | |
| Traversable Tick Source # | |
| Functor Tick Source # | |
| Show a => Show (Tick a) Source # | |
| Eq a => Eq (Tick a) Source # | |
batchByTick :: forall (m :: Type -> Type) a. (Monad m, Monoid a) => ProcessT m (Tick a) a Source #
Generalised version of batchByTickList.
batchToTick :: forall (f :: Type -> Type) a. Foldable f => Process (f a) (Tick a) Source #
Generalised version of batchListToTick.
batchListToTick :: forall a (m :: Type -> Type). Monad m => MachineT m (Is [a]) (Tick a) Source #
This machine streams a list of items into a series of items separated by ticks.
batchByTickList :: forall a (m :: Type -> Type). Monad m => MachineT m (Is (Tick a)) [a] Source #
This machine batches all items between two ticks into a list.
liftTick :: forall (m :: Type -> Type) a b. Monad m => ProcessT m a b -> ProcessT m (Tick a) (Tick b) Source #
Lift a machine to a machine that passes on ticks unchanged.
Constructs the following machine:
┌─(if Tick)────────────────────┐
[ Tick a ] [ Tick b ]
└─(if Item)─( ProcessT m a b )─┘
dropTick :: forall a (m :: Type -> Type). Monad m => MachineT m (Is (Tick a)) a Source #
This machine drops all ticks.
onlyTick :: forall a (m :: Type -> Type). Monad m => MachineT m (Is (Tick a)) () Source #
This machine drops all items.
liftBatch :: forall (m :: Type -> Type) a b. Monad m => ProcessT m a b -> ProcessT m [a] [b] Source #
Lift a machine that processes as into bs to a machine that processes
batches of as into batches of bs.
Debug
counterBy :: forall (m :: Type -> Type) a x. MonadIO m => Verbosity -> Text -> (a -> Word) -> ProcessT m a x Source #
This machine counts the number of inputs it received, using the given function, and logs this value.
counterByTick :: forall (m :: Type -> Type) a x. MonadIO m => Verbosity -> Text -> ProcessT m (Tick a) x Source #
This machine counts the number of inputs it received, and logs this value on every tick.
Routers
Arguments
| :: forall (m :: Type -> Type) k a b. (MonadIO m, Hashable k) | |
| => (a -> Maybe k) | Function to measure. |
| -> (k -> ProcessT m a b) | Function to spawn child processors. |
| -> ProcessT m a b |
Spawn a copy of a machine for each "measure".
Constructs the following machine:
┌─────(if measure == k0)─( ProcessT m a b )────┐
[ a ] ──(if measure == ..)─( ProcessT m a b )─ [ b ]
└─────(if measure == kN)─( ProcessT m a b )────┘
Warning: The router does not currently garbage-collect terminated child processors.
Event sorting
sortByBatch :: forall (m :: Type -> Type) a. Monad m => (a -> Timestamp) -> ProcessT m [a] [a] Source #
Reorder events respecting ticks.
This machine caches two batches worth of events, sorts them together, and then yields only those events whose timestamp is less than or equal to the maximum of the first batch.
sortByBatchTick :: (a -> Timestamp) -> Process (Tick a) (Tick a) Source #
Variant of sortByBatch that operates on streams of items and ticks.
Delimiting
between :: Text -> Text -> Moore Text Bool Source #
A simple delimiting Moore machine,
which is opened by one constant marker and closed by the other one.
delimit :: forall (m :: Type -> Type). Monad m => Moore Text Bool -> ProcessT m Event Event Source #
Delimit the event process.
Validation
validateInput :: forall (m :: Type -> Type) a x. MonadIO m => Verbosity -> Int -> ProcessT m (Tick a) x Source #
This machine validates that there is some input.
If no input is encountered after the given number of ticks, the machine prints
a warning that directs the user to check that the -l flag was set correctly.
validateOrder :: forall (m :: Type -> Type) a x. (MonadIO m, Show a) => Verbosity -> (a -> Timestamp) -> ProcessT m a x Source #
This machine validates that the inputs are received in order.
If an out-of-order input is encountered, the machine prints an error message
that directs the user to check that the --eventlog-flush-interval and the
--batch-interval flags are set correctly.