glazier-1.0.0.0: Extensible effects using ContT, State and variants.

Safe HaskellNone
LanguageHaskell2010

Glazier.Command

Synopsis

Documentation

class Monad m => MonadCodify cmd m | m -> cmd where Source #

Converts a handler that result in monad transformer stack with a State of list of commands to a handler that result in a list of commands, using the current monad context, by running the State of comands with mempty like Writer.

Minimal complete definition

codifies

Methods

codifies :: (a -> m ()) -> m (a -> [cmd]) Source #

Instances
AsConcur cmd => MonadCodify cmd (Concur cmd) Source # 
Instance details

Defined in Glazier.Command

Methods

codifies :: (a -> Concur cmd ()) -> Concur cmd (a -> [cmd]) Source #

MonadCodify cmd m => MonadCodify cmd (MaybeT m) Source #

Passthrough instance, ignoring that the handler result might be Nothing.

Instance details

Defined in Glazier.Command

Methods

codifies :: (a -> MaybeT m ()) -> MaybeT m (a -> [cmd]) Source #

MonadCodify cmd (State (DList cmd)) Source #

Instance that does real work by running the State of commands with mempty.

Instance details

Defined in Glazier.Command

Methods

codifies :: (a -> State (DList cmd) ()) -> State (DList cmd) (a -> [cmd]) Source #

MonadCodify cmd (State (DList cmd)) Source #

Instance that does real work by running the State of commands with mempty.

Instance details

Defined in Glazier.Command

Methods

codifies :: (a -> State (DList cmd) ()) -> State (DList cmd) (a -> [cmd]) Source #

(MonadDelegate () m, MonadCodify cmd m) => MonadCodify cmd (ExceptT e m) Source #

Passthrough instance which requires the inner monad to be a MonadDelegate. This means that the Left e case can be handled by the provided delegate.

Instance details

Defined in Glazier.Command

Methods

codifies :: (a -> ExceptT e m ()) -> ExceptT e m (a -> [cmd]) Source #

MonadCodify cmd m => MonadCodify cmd (IdentityT m) Source #

Passthrough instance

Instance details

Defined in Glazier.Command

Methods

codifies :: (a -> IdentityT m ()) -> IdentityT m (a -> [cmd]) Source #

MonadCodify cmd m => MonadCodify cmd (ReaderT r m) Source #

Passthrough instance, using the Reader context

Instance details

Defined in Glazier.Command

Methods

codifies :: (a -> ReaderT r m ()) -> ReaderT r m (a -> [cmd]) Source #

MonadCodify cmd m => MonadCodify cmd (ContT () m) Source #

Passthrough instance

Instance details

Defined in Glazier.Command

Methods

codifies :: (a -> ContT () m ()) -> ContT () m (a -> [cmd]) Source #

codifies' :: MonadCodify cmd m => m () -> m [cmd] Source #

Variation of codifies to transform the monad stack instead of a handler.

codify :: (AsFacet [cmd] cmd, MonadCodify cmd m) => (a -> m ()) -> m (a -> cmd) Source #

Variation of codifies to output a handler that result in a single command

codify' :: (AsFacet [cmd] cmd, MonadCodify cmd m) => m () -> m cmd Source #

Variation of codify to transform the monad stack instead of a handler.

type MonadCommand cmd m = (MonadState (DList cmd) m, MonadDelegate () m, MonadCodify cmd m, AsFacet [cmd] cmd) Source #

command :: AsFacet c cmd => c -> cmd Source #

convert a request type to a command type. This is used for commands that doesn't have a continuation. Ie. commands that doesn't "returns" a value from running an effect. Use command' for commands that require a continuation ("returns" a value).

command' :: AsFacet (c cmd) cmd => c cmd -> cmd Source #

A variation of command for commands with a type variable cmd, which is usually commands that are containers of command, or commands that require a continuation Eg. commands that "returns" a value from running an effect.

command_ :: AsFacet [cmd] cmd => () -> cmd Source #

This helps allow executors of commands of a results only need to execute the type c cmd, ie, when the command result in the next cmd. This function is useful to fmap a command with a result of unit to to a command with a result cmd type.

commands :: AsFacet [cmd] cmd => [cmd] -> cmd Source #

Convert a list of commands to a command. This implementation avoids nesting for lists of a single command.

instruct :: MonadState (DList cmd) m => cmd -> m () Source #

Add a command to the list of commands for this MonadState. I basically want a Writer monad, but I'm using a State monad because but I also want to use it inside a ContT which only has an instance of MonadState.

instructs :: MonadState (DList cmd) m => [cmd] -> m () Source #

Adds a list of commands to the list of commands for this MonadState.

exec :: (MonadState (DList cmd) m, AsFacet c cmd) => c -> m () Source #

exec' :: (MonadState (DList cmd) m, AsFacet (c cmd) cmd) => c cmd -> m () Source #

exec_ :: (Functor c, MonadState (DList cmd) m, AsFacet [cmd] cmd, AsFacet (c cmd) cmd) => c () -> m () Source #

eval :: (MonadCommand cmd m, AsFacet [cmd] cmd, AsFacet c cmd) => ((a -> cmd) -> c) -> m a Source #

eval' :: (MonadCommand cmd m, AsFacet [cmd] cmd, AsFacet (c cmd) cmd) => ((a -> cmd) -> c cmd) -> m a Source #

sequentially :: MonadCont m => m a -> m a Source #

Adds a MonadCont constraint. It is redundant but rules out using Concur at the bottom of the transformer stack. sequentially is used for operations that MUST run sequentially, not concurrently. Eg. when the overhead of using Concur MVar is not worth it, or when data dependencies are not explicitly specified by monadic binds, Eg. A command to update mutable variable must exact before a command that reads from the mutable variable. In this case, the reference to the variable doesn't change, so the data dependency is not explicit.

dispatch :: (AsFacet (c cmd) cmd, MonadCommand cmd m, Functor c) => c a -> m a Source #

Retrieves the result of a functor command.

dispatch_ :: (AsFacet (c cmd) cmd, AsFacet [cmd] cmd, MonadState (DList cmd) m, Functor c) => c () -> m () Source #

Retrieves the result of a functor command. A simpler variation of dispatch that only requires a MonadState (DL.DList cmd) m

concurringly :: (MonadCommand cmd m, AsConcur cmd) => Concur cmd a -> m a Source #

concurringly_ :: (MonadState (DList cmd) m, AsConcur cmd) => Concur cmd () -> m () Source #

This is a monad morphism that can be used to hoist transformer stacks on Concur cmd () A simpler variation of concurringly that only requires a MonadState (DL.DList cmd) m

type AsConcur cmd = (AsFacet [cmd] cmd, AsFacet (Concur cmd cmd) cmd) Source #

newtype Concur cmd a Source #

This monad is intended to be used with ApplicativeDo to allow do notation for composing commands that can be run concurrently. The Applicative instance can merge multiple commands into the internal state of DList c. The Monad instance creates a ConcurCmd command before continuing the bind.

Constructors

Concur 

Fields

Instances
AsConcur cmd => MonadDelegate () (Concur cmd) Source #

This instance makes usages of sequel concurrent when used insdie a concurringly or concurringly_ block. Converts a command that requires a handler to a Concur monad so that the do notation can be used to compose the handler for that command. The Concur monad allows scheduling the command in concurrently with other commands.

Instance details

Defined in Glazier.Command

Methods

delegate :: ((a -> Concur cmd ()) -> Concur cmd ()) -> Concur cmd a #

AsConcur cmd => MonadCodify cmd (Concur cmd) Source # 
Instance details

Defined in Glazier.Command

Methods

codifies :: (a -> Concur cmd ()) -> Concur cmd (a -> [cmd]) Source #

AsConcur cmd => Monad (Concur cmd) Source # 
Instance details

Defined in Glazier.Command

Methods

(>>=) :: Concur cmd a -> (a -> Concur cmd b) -> Concur cmd b #

(>>) :: Concur cmd a -> Concur cmd b -> Concur cmd b #

return :: a -> Concur cmd a #

fail :: String -> Concur cmd a #

Functor (Concur cmd) Source # 
Instance details

Defined in Glazier.Command

Methods

fmap :: (a -> b) -> Concur cmd a -> Concur cmd b #

(<$) :: a -> Concur cmd b -> Concur cmd a #

Applicative (Concur cmd) Source #

Applicative instand allows building up list of commands without blocking

Instance details

Defined in Glazier.Command

Methods

pure :: a -> Concur cmd a #

(<*>) :: Concur cmd (a -> b) -> Concur cmd a -> Concur cmd b #

liftA2 :: (a -> b -> c) -> Concur cmd a -> Concur cmd b -> Concur cmd c #

(*>) :: Concur cmd a -> Concur cmd b -> Concur cmd b #

(<*) :: Concur cmd a -> Concur cmd b -> Concur cmd a #

AsConcur cmd => MonadState (DList cmd) (Concur cmd) Source # 
Instance details

Defined in Glazier.Command

Methods

get :: Concur cmd (DList cmd) #

put :: DList cmd -> Concur cmd () #

state :: (DList cmd -> (a, DList cmd)) -> Concur cmd a #

Show (Concur cmd a) Source # 
Instance details

Defined in Glazier.Command

Methods

showsPrec :: Int -> Concur cmd a -> ShowS #

show :: Concur cmd a -> String #

showList :: [Concur cmd a] -> ShowS #

Generic (Concur cmd a) Source # 
Instance details

Defined in Glazier.Command

Associated Types

type Rep (Concur cmd a) :: * -> * #

Methods

from :: Concur cmd a -> Rep (Concur cmd a) x #

to :: Rep (Concur cmd a) x -> Concur cmd a #

type Rep (Concur cmd a) Source # 
Instance details

Defined in Glazier.Command

type Rep (Concur cmd a) = D1 (MetaData "Concur" "Glazier.Command" "glazier-1.0.0.0-9X8oFuaSxEN4EAfq4DMMBj" True) (C1 (MetaCons "Concur" PrefixI True) (S1 (MetaSel (Just "runConcur") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (StateT (DList cmd) NewEmptyMVar (Either (IO a) a)))))

data NewEmptyMVar a Source #

NB. Don't export NewEmptyMVar constructor to guarantee that that it only contains non-blocking newEmptyMVar IO.

Instances
Monad NewEmptyMVar Source # 
Instance details

Defined in Glazier.Command

Functor NewEmptyMVar Source # 
Instance details

Defined in Glazier.Command

Methods

fmap :: (a -> b) -> NewEmptyMVar a -> NewEmptyMVar b #

(<$) :: a -> NewEmptyMVar b -> NewEmptyMVar a #

Applicative NewEmptyMVar Source # 
Instance details

Defined in Glazier.Command