dep-t-advice-0.6.2.0: Giving good advice to functions in records-of-functions.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Dep.Advice.Basic

Description

This module contains basic examples 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.

printArgs :: forall e_ m r. (Monad m, MonadIO (DepT e_ m)) => Handle -> String -> Advice Show e_ m r Source #

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

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 Dep.SimpleAdvice.Basic

Methods

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

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

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

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

The monad m and the result type r must be known before building the advice. So, once built, this 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_ m. (Monad m, MonadUnliftIO (DepT e_ m)) => Advice ca e_ m () Source #

Makes functions that return () launch asynchronously.

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

injectFailures :: forall ca e_ m r. (Monad m, MonadIO (DepT e_ m), MonadFail (DepT e_ m)) => IORef ([IO ()], [IO ()]) -> Advice ca e_ m r Source #

Given a reference with two infinite lists of IO actions, on each invocation of the advised function, take an action from the first list and execute it before, and take one action from the second list and execute it after.

A common use for this would be to pass exception-throwing actions.

doLocally :: forall ca e_ m r. Monad m => (e_ (DepT e_ m) -> e_ (DepT e_ m)) -> 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 into dependencies.

Perhaps this is not what you want; often, it's better to tweak the environment for the current function only. For those cases, deceive might be a better fit.

>>> :{
 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

Synthetic call stacks

type StackFrame = NonEmpty (TypeRep, MethodName) Source #

The typeable representation of the record which contains the invoked function, along with the field name of the invoked function.

class HasSyntheticCallStack e where Source #

Class of environments that carry a SyntheticCallStack value that can be modified.

Methods

callStack :: forall f. Functor f => (SyntheticCallStack -> f SyntheticCallStack) -> e -> f e Source #

A lens from the environment to the call stack.

Instances

Instances details
HasSyntheticCallStack SyntheticCallStack Source #

The trivial case, useful when SyntheticCallStack is the environment type of a ReaderT.

Instance details

Defined in Dep.SimpleAdvice.Basic

HasSyntheticCallStack s => HasSyntheticCallStack (Const s x) Source # 
Instance details

Defined in Dep.SimpleAdvice.Basic

Methods

callStack :: Functor f => (SyntheticCallStack -> f SyntheticCallStack) -> Const s x -> f (Const s x) Source #

HasSyntheticCallStack s => HasSyntheticCallStack (Constant s x) Source # 
Instance details

Defined in Dep.SimpleAdvice.Basic

class MonadCallStack m where Source #

Monads that carry a SyntheticCallStack.

Instances

Instances details
MonadCallStack m => MonadCallStack (AspectT m) Source # 
Instance details

Defined in Dep.SimpleAdvice.Basic

(Monad m, HasSyntheticCallStack (e_ (DepT e_ m))) => MonadCallStack (DepT e_ m) Source # 
Instance details

Defined in Dep.SimpleAdvice.Basic

(Monad m, HasSyntheticCallStack runenv) => MonadCallStack (ReaderT runenv m) Source # 
Instance details

Defined in Dep.SimpleAdvice.Basic

Methods

askCallStack :: ReaderT runenv m SyntheticCallStack Source #

addStackFrame :: StackFrame -> ReaderT runenv m r -> ReaderT runenv m r Source #

keepCallStack Source #

Arguments

:: (Monad m, MonadUnliftIO (DepT e_ m), MonadCallStack (DepT e_ m), Exception e) 
=> (SomeException -> Maybe e)

A selector for the kinds of exceptions we want to catch. For example fromException @IOError.

-> NonEmpty (TypeRep, MethodName)

The path to the current component/method in the environment. It will be usually obtained through adviseRecord.

-> Advice ca e_ m r 

If the environment carries a SyntheticCallStack, make advised functions add themselves to the SyntheticCallStack before they start executing.

This Advice requires a reader-like base monad to work. It doesn't need to be DepT, it can be regular a ReaderT.

Caught exceptions are rethrown wrapped in SyntheticStackTraceExceptions, with the current SyntheticCallStack added.