dep-t-advice-0.2.0.1: Giving good advice to functions in a DepT environment.
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Dep.Advice.Basic

Description

This module contains examples of simple advices.

BEWARE! These are provided for illustrative purposes only, they strive for simplicity and not robustness or efficiency.

Synopsis

Basic advices

returnMempty :: forall ca e m r. (Monad m, Monoid r) => Advice ca e m r Source #

Makes functions discard their result and always return mempty.

Because it doesn't touch the arguments or require some effect from the environment, this Advice is polymorphic on ca and cem.

printArgs :: forall e m r. MonadIO m => Handle -> String -> Advice Show e m r Source #

Given a Handle and a prefix string, makes functions print their arguments to the Handle.

This advice uses MonadConstraint to lift the MonadIO constraint that applies only to the monad.

Because it doesn't touch the return value of the advised function, this Advice is polymorphic on cr.

doLocally :: forall ca e m r. Monad m => (forall n. e n -> e n) -> Advice ca e m r Source #

Use local on the final DepT action of a function.

Allows tweaking the environment that will be seen by the function and all of its sub-calls.

>>> :{
 type HasLogger :: Type -> (Type -> Type) -> Constraint
 class HasLogger em m | em -> m where
   logger :: em -> String -> m ()
 type Env :: (Type -> Type) -> Type
 data Env m = Env
   { _logger1 :: String -> m (),
     _logger2 :: String -> m (),
     _controllerA :: Int -> m (),
     _controllerB :: Int -> m ()
   }
 instance HasLogger (Env m) m where
   logger = _logger1
 envIO :: Env (DepT Env IO)
 envIO = Env 
   {
     _logger1 = \_ -> liftIO $ putStrLn "logger1 ran",
     _logger2 = \_ -> liftIO $ putStrLn "logger2 ran",
     _controllerA = \_ -> do e <- ask; logger e "foo",
     _controllerB = advise @Top 
                    (doLocally \e@Env{_logger2} -> e {_logger1 = _logger2}) 
                    \_ -> do e <- ask; logger e "foo" 
   }
:}
>>> runFromEnv (pure envIO) _controllerA 0
logger1 ran
>>> runFromEnv (pure envIO) _controllerB 0
logger2 ran

data AnyEq where Source #

A helper datatype for universal equality comparisons of existentialized values, used by doCachingBadly.

For a more complete elaboration of this idea, see the the "exinst" package.

Constructors

AnyEq :: forall a. (Typeable a, Eq a) => a -> AnyEq 

Instances

Instances details
Eq AnyEq Source # 
Instance details

Defined in Control.Monad.Dep.Advice.Basic

Methods

(==) :: AnyEq -> AnyEq -> Bool #

(/=) :: AnyEq -> AnyEq -> Bool #

doCachingBadly :: forall e m r. Monad m => (AnyEq -> m (Maybe r)) -> (AnyEq -> r -> m ()) -> Advice (Eq `And` Typeable) e m r Source #

Given the means for looking up and storing values in the underlying monad m, makes functions (inefficiently) cache their results.

Notice the equality constraints on the Advice. This means that the monad m and the result type r are known and fixed before building the advice. Once built, the Advice won't be polymorphic over them.

The implementation of this function makes use of the existential type parameter u of makeAdvice, because the phase that processes the function arguments needs to communicate the calculated AnyEq cache key to the phase that processes the function result.

A better implementation of this advice would likely use an AnyHashable helper datatype for the keys.

doAsyncBadly :: forall ca e. Advice ca e IO () Source #

Makes functions that return () launch asynchronously.

A better implementation of this advice would likely use the "async" package instead of bare forkIO.

And the MustBe IO constraint could be relaxed to MonadUnliftIO.