| Copyright | 2019 Daniel YU |
|---|---|
| License | BSD3 |
| Maintainer | leptonyu@gmail.com |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Boots
Description
Boot application by using plugins.
>>>booting (pluginSimple "application") (logInfo "hello")2019-07-27 19:35:30 INFO [application] Ghci1 - hello>>>booting (pluginSimple "application") (require "user" >>= logInfo)2019-07-27 19:37:45 INFO [application] Ghci2 - daniel
Synopsis
- booting :: Plugin () m cxt -> AppT cxt m () -> m ()
- data AppT cxt m a
- runAppT :: cxt -> AppT cxt m a -> m a
- liftIO :: MonadIO m => IO a -> m a
- ask :: MonadReader r m => m r
- lift :: (MonadTrans t, Monad m) => m a -> t m a
- throwM :: (MonadThrow m, Exception e) => e -> m a
- data Plugin i m u
- runPlugin :: i -> Plugin i m u -> (u -> m ()) -> m ()
- promote :: i -> Plugin i m u -> Plugin x m u
- withPlugin :: (i -> j) -> Plugin j m u -> Plugin i m u
- mapPlugin :: (m () -> m ()) -> Plugin i m u -> Plugin i m u
- bracketP :: MonadCatch m => m u -> (u -> m ()) -> Plugin i m u
- module Boots.Plugin
Main function
booting :: Plugin () m cxt -> AppT cxt m () -> m () Source #
Run application using a plugin. Context cxt can't escape from m.
Application
Application monad transformation.
Instances
ask :: MonadReader r m => m r #
Retrieves the monad environment.
lift :: (MonadTrans t, Monad m) => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
throwM :: (MonadThrow m, Exception e) => e -> m a #
Throw an exception. Note that this throws when this action is run in
the monad m, not when it is applied. It is a generalization of
Control.Exception's throwIO.
Should satisfy the law:
throwM e >> f = throwM e
Application plugin
Plugin generates component u with the context of component i running in monad m.
Instances
| MonadReader i (Plugin i m) Source # | |
| MonadTrans (Plugin i) Source # | |
Defined in Boots.Internal.Plugin | |
| Monad (Plugin i m) Source # | |
| Functor (Plugin i m) Source # | |
| Applicative (Plugin i m) Source # | |
Defined in Boots.Internal.Plugin | |
| MonadIO m => MonadIO (Plugin i m) Source # | |
Defined in Boots.Internal.Plugin | |
| MonadThrow m => MonadThrow (Plugin i m) Source # | |
Defined in Boots.Internal.Plugin | |
| (MonadIO m, HasLogger cxt) => MonadLogger (Plugin cxt m) Source # | |
Defined in Boots.Plugin.Logger | |
| Monad m => MonadCont (Plugin i m) Source # | |
| HasSalak cxt => MonadSalak (Plugin cxt m) Source # | |
Defined in Boots.Plugin.Salak | |
withPlugin :: (i -> j) -> Plugin j m u -> Plugin i m u Source #
Convert a plugin into another.
mapPlugin :: (m () -> m ()) -> Plugin i m u -> Plugin i m u Source #
Apply a function to transform the result of a continuation-passing computation.
Arguments
| :: MonadCatch m | |
| => m u | Open resource. |
| -> (u -> m ()) | Close resource. |
| -> Plugin i m u | Resource plugin. |
Create bracket style plugin, used for manage resources, which need to open and close.
A simple example:
>>>res = bracketP (putStrLn "open") (const $ putStrLn "close")>>>runPlugin () res (const $ putStrLn "using")open using close
module Boots.Plugin