| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Capataz
Description
Convinience module that re-exports modules:
Since: 0.2.0.0
Synopsis
- buildLogWorkerSpec1 :: (MonadUnliftIO m, MonadIO m0) => LogOptions -> WorkerName -> Natural -> (WorkerOptions m -> WorkerOptions m) -> m0 (ProcessSpec m, LogFunc)
- buildLogWorkerSpec :: (MonadUnliftIO m, MonadIO m0) => LogOptions -> WorkerName -> Int -> (WorkerOptions m -> WorkerOptions m) -> m0 (ProcessSpec m, LogFunc)
- buildLogWorkerOptions1 :: (MonadUnliftIO m, MonadIO m0) => LogOptions -> WorkerName -> Natural -> (WorkerOptions m -> WorkerOptions m) -> m0 (WorkerOptions m, LogFunc)
- buildLogWorkerOptions :: (MonadUnliftIO m, MonadIO m0) => LogOptions -> WorkerName -> Int -> (WorkerOptions m -> WorkerOptions m) -> m0 (WorkerOptions m, LogFunc)
- module Control.Concurrent.Capataz
Documentation
Arguments
| :: (MonadUnliftIO m, MonadIO m0) | |
| => LogOptions | options for the |
| -> WorkerName | name of the logger worker process |
| -> Natural | how many log messages can be in-flight when writer is slow? |
| -> (WorkerOptions m -> WorkerOptions m) | worker process modifier |
| -> m0 (ProcessSpec m, LogFunc) |
Builds a ProcessSpec that spawns a thread that logs messages written with
the returned LogFunc. Use this function when your want your logger to be
part of a static supervision tree.
IMPORTANT If you use the returned LogFunc to log functions and the
ProcessSpec is not used in a supervision tree, your logging won't work and
your application will eventually block the current thread when logging.
A minimal example:
{--}
{--}
import RIO
import Capataz
main :: IO ()
main = do
logOptions <- logOptionsHandle stdout True
(loggerSpec, logFunc) <- buildLogWorkerSpec logOptions "app-logger" 100 id
runRIO logFunc $ do
bracket (forkCapataz "application" (set supervisorProcessSpecListL [loggerSpec]))
terminateCapataz_ $ _capataz -> do
logInfo "this log message is written by a dedicated supervised thread"
threadDelay 1000100
Since: 0.2.1.0
Arguments
| :: (MonadUnliftIO m, MonadIO m0) | |
| => LogOptions | options for the |
| -> WorkerName | name of the logger worker process |
| -> Int | how many log messages can be in-flight when writer is slow? |
| -> (WorkerOptions m -> WorkerOptions m) | worker process modifier |
| -> m0 (ProcessSpec m, LogFunc) |
Deprecated: Use buildLogWorkerSpec1 instead
Deprecated in favour of buildLogWorkerSpec1.
IMPORTANT Since 0.2.1.0 this function throws a runtime error if
the argumet of the type Int is negative.
Since: 0.2.0.0
buildLogWorkerOptions1 :: (MonadUnliftIO m, MonadIO m0) => LogOptions -> WorkerName -> Natural -> (WorkerOptions m -> WorkerOptions m) -> m0 (WorkerOptions m, LogFunc) Source #
Builds a WorkerOptions record that spawns a thread that logs messages
written with the returned LogFunc. Use this function if you want to build a
logger thread dynamically via forkWorker.
IMPORTANT If you use the returned LogFunc to log functions and the
WorkerOptions is not used in a forkWorker call, your logging won't work
and your application will eventually block the current thread when logging.
A minimal example:
{--}
{--}
import RIO
import Capataz
main :: IO ()
main = do
logOptions <- logOptionsHandle stdout True
(loggerOptions, logFunc) <- buildLogWorkerOptions logOptions "app-logger" 100 id
runRIO logFunc $ do
bracket (forkCapataz "application" id)
terminateCapataz_ $ capataz -> do
_workerId <- forkWorker loggerOptions capataz
logInfo "this log message is written by a dedicated supervised thread"
threadDelay 1000100
Since: 0.2.1.0
buildLogWorkerOptions :: (MonadUnliftIO m, MonadIO m0) => LogOptions -> WorkerName -> Int -> (WorkerOptions m -> WorkerOptions m) -> m0 (WorkerOptions m, LogFunc) Source #
Deprecated: Use buildLogWorkerOptions1 instead
Deprecated in favour of buildLogWorkerOptions1.
IMPORTANT Since 0.2.1.0 this function throws a runtime error if
the argumet of the type Int is negative.
Since: 0.2.0.0
module Control.Concurrent.Capataz