refresht-0.1.1.0: Environment Monad with automatic resource refreshment

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Refresh

Contents

Synopsis

RefreshT type and settings

data RefreshT s m a Source #

Reader monad transformer with an automatic environment refreshment.

Since 0.1.0.0

Instances

MonadIO m => MonadReader s (RefreshT s m) Source #

N.B. The refreshed result took place inside local will be reflected outside.

Since 0.1.0.0

Methods

ask :: RefreshT s m s #

local :: (s -> s) -> RefreshT s m a -> RefreshT s m a #

reader :: (s -> a) -> RefreshT s m a #

MonadTrans (RefreshT s) Source #

N.B. The lift combinator doesn't care about exceptions; this is the intended behaviour, because lift doesn't come with any atomicity meaning. If you want to trigger refresh after exceptions, use atomicLift.

Since 0.1.0.0

Methods

lift :: Monad m => m a -> RefreshT s m a #

Monad m => Monad (RefreshT s m) Source # 

Methods

(>>=) :: RefreshT s m a -> (a -> RefreshT s m b) -> RefreshT s m b #

(>>) :: RefreshT s m a -> RefreshT s m b -> RefreshT s m b #

return :: a -> RefreshT s m a #

fail :: String -> RefreshT s m a #

Functor m => Functor (RefreshT s m) Source # 

Methods

fmap :: (a -> b) -> RefreshT s m a -> RefreshT s m b #

(<$) :: a -> RefreshT s m b -> RefreshT s m a #

Monad m => Applicative (RefreshT s m) Source # 

Methods

pure :: a -> RefreshT s m a #

(<*>) :: RefreshT s m (a -> b) -> RefreshT s m a -> RefreshT s m b #

(*>) :: RefreshT s m a -> RefreshT s m b -> RefreshT s m b #

(<*) :: RefreshT s m a -> RefreshT s m b -> RefreshT s m a #

MonadIO m => MonadIO (RefreshT s m) Source #

N.B. The liftIO combinator doesn't care about exceptions; this is the intended behaviour, because liftIO doesn't come with any atomicity meaning. If you want to trigger refresh after exceptions, use atomicLiftIO.

Since 0.1.0.0

Methods

liftIO :: IO a -> RefreshT s m a #

MonadThrow m => MonadThrow (RefreshT s m) Source #

Since 0.1.1.0

Methods

throwM :: Exception e => e -> RefreshT s m a #

MonadCatch m => MonadCatch (RefreshT s m) Source #

N.B. When exception is catched, no resource refreshment will be occured. This allows users a flexible control on refreshment timing.

Methods

catch :: Exception e => RefreshT s m a -> (e -> RefreshT s m a) -> RefreshT s m a #

runRefreshT :: MonadCatch m => RefreshSetting s m -> s -> RefreshT s m a -> m (a, s) Source #

Excecute environmental computation and returns the result with the final environment.

Since 0.1.0.0

evalRefreshT :: MonadCatch m => RefreshSetting s m -> s -> RefreshT s m a -> m a Source #

Excecute environmental computation and returns the result, discarding the final environment.

Since 0.1.0.0

Settings for Refreshing

data RefreshSetting s m Source #

Settings for Refreshment

Since 0.1.0.0

Instances

Monad m => Default (RefreshSetting s m) Source #

Since 0.1.0.0

Methods

def :: RefreshSetting s m #

refresher :: forall s m. Lens' (RefreshSetting s m) (s -> m s) Source #

Environment refreshing function (default: return).

Since 0.1.0.0

Delay in microseconds before environmental refreshment (default: 100ms).

Since 0.1.0.0

shouldRefresh :: forall s m. Lens' (RefreshSetting s m) (s -> m Bool) Source #

Condition to determine if environment should be refreshed (default: const True).

Since 0.1.0.0

If this exception should occur an envionment refreshment? (default: refresh for any exception).

Since 0.1.0.0

Transaction Combinators

atomic :: (MonadIO m, MonadCatch m) => RefreshT s m a -> RefreshT s m a Source #

Try an atomic transaction and, if exceptions specified by isRefreshingError has been raised, refreshes the environment and redo the entire transaction.

Since 0.1.0.0

atomicLift :: (MonadIO m, MonadCatch m) => m a -> RefreshT s m a Source #

atomicLift = atomic . lift.

Since 0.1.0.0

atomicLiftIO :: (MonadIO m, MonadCatch m) => IO a -> RefreshT s m a Source #

atomicLiftIO = atomic . liftIO.

Since 0.1.0.0

withEnv :: (MonadIO m, MonadCatch m) => (s -> m a) -> RefreshT s m a Source #

atomicLift composed with ask.

Since 0.1.0.0

refresh :: MonadIO m => RefreshT s m () Source #

Forces environmental refreshment, regardless of shouldRefresh condition.

Since 0.1.0.0