maam-0.3.0.0: Monadic Abstracting Abstract Machines (MAAM) built on Galois Transformers

Safe HaskellNone
LanguageHaskell2010

FP.Prelude.Monads

Documentation

class FunctorIsoFunctor t where Source

Methods

fisomap :: (m n, n m) -> t m t n Source

Instances

type Error e = ErrorT e ID Source

runError :: Error e a -> e a Source

type Reader r = ReaderT r ID Source

reader :: (r -> a) -> Reader r a Source

runReader :: Reader r a -> r -> a Source

runReaderWith :: r -> Reader r a -> a Source

readerCommute :: ReaderT r₁ (ReaderT r₂ m) ReaderT r₂ (ReaderT r₁ m) Source

type Writer o = WriterT o ID Source

writer :: (a, o) -> Writer o a Source

runWriter :: Writer o a -> (a, o) Source

writerCommute :: forall m o₁ o₂. Functor m => WriterT o₁ (WriterT o₂ m) WriterT o₂ (WriterT o₁ m) Source

type State s = StateT s ID Source

runStateWith :: s -> State s a -> (a, s) Source

evalStateWith :: s -> State s a -> a Source

execStateWith :: s -> State s a -> s Source

stateCommute :: forall m s₁ s₂. Functor m => StateT s₁ (StateT s₂ m) StateT s₂ (StateT s₁ m) Source

pluck :: [a] -> [[a]] -> Maybe ([a], [[a]]) Source

transpose :: [[a]] -> [[a]] Source

flowCommuteAppend :: forall s₁ s₂ m. (Functor m, Monoid s₁) => FlowAppendT s₁ (FlowAppendT s₂ m) FlowAppendT s₂ (FlowAppendT s₁ m) Source

flowCommuteJoin :: forall s₁ s₂ m. (Functor m, JoinLattice s₁) => FlowJoinT s₁ (FlowJoinT s₂ m) FlowJoinT s₂ (FlowJoinT s₁ m) Source

type Cont r = ContT r ID Source

cont :: ((a -> r) -> r) -> Cont r a Source

runCont :: Cont r a -> (a -> r) -> r Source

evalCont :: Cont r r -> r Source

opaqueCont :: (k r ID a -> r) -> OpaqueCont k r a Source

runOpaqueCont :: OpaqueCont k r a -> k r ID a -> r Source

metaCont :: Isomorphic3 (k r) (ContFun r) => ((a -> r) -> r) -> OpaqueCont k r a Source

runMetaCont :: Isomorphic3 (ContFun r) (k r) => OpaqueCont k r a -> (a -> r) -> r Source

class Balloon k r | k -> r where Source

Methods

inflate :: Monad m => k r m k r (OpaqueContT k r m) Source

deflate :: Monad m => k r (OpaqueContT k r m) k r m Source

errorWriterCommute :: forall e o m. Functor m => ErrorT e (WriterT o m) WriterT o (ErrorT e m) Source

writerStateCommute :: forall o s m. Functor m => WriterT o (StateT s m) StateT s (WriterT o m) Source

stateWriterCommute :: forall o s m. Functor m => StateT s (WriterT o m) WriterT o (StateT s m) Source

mergeState :: Functor m => StateT s₁ (StateT s₂ m) a -> StateT (s₁, s₂) m a Source

splitState :: Functor m => StateT (s₁, s₂) m a -> StateT s₁ (StateT s₂ m) a Source

mapState :: forall m s₁ s₂ a. Functor m => (s₁ s₂) -> StateT s₁ m a -> StateT s₂ m a Source

stateFlowAppendCommute :: forall s₁ s₂ m. (Functor m, Monoid s₁) => StateT s₁ (FlowAppendT s₂ m) FlowAppendT s₂ (StateT s₁ m) Source

flowAppendStateCommute :: forall s₁ s₂ m. (Functor m, Monoid s₁) => FlowAppendT s₁ (StateT s₂ m) StateT s₂ (FlowAppendT s₁ m) Source

stateFlowJoinCommute :: forall s₁ s₂ m. (Functor m, JoinLattice s₁) => StateT s₁ (FlowJoinT s₂ m) FlowJoinT s₂ (StateT s₁ m) Source

flowJoinStateCommute :: forall s₁ s₂ m. (Functor m, JoinLattice s₁) => FlowJoinT s₁ (StateT s₂ m) StateT s₂ (FlowJoinT s₁ m) Source

newtype RWST r o s m a Source

Constructors

RWST 

Fields

runRWST :: ReaderT r (WriterT o (StateT s m)) a
 

Instances

Functor m => MonadState s (RWST r o s m) Source 
(Functor m, Monoid o) => MonadWriter o (RWST r o s m) Source 
Functor m => MonadReader r (RWST r o s m) Source 
(Functor m, Monoid o, MonadError e m) => MonadError e (RWST r o s m) Source 
FunctorFunctor (RWST r o s) Source 
(Monad m, Monoid o) => Monad (RWST r o s m) Source 
Functor m => Functor (RWST r o s m) Source 
(Functor m, Monoid o, MonadFailure m) => MonadFailure (RWST r o s m) Source 

runRWSTWith :: forall r o s m a. Functor m => r -> s -> RWST r o s m a -> m (a, o, s) Source

type RWS r o s = RWST r o s ID Source

runRWSWith :: r -> s -> RWS r o s a -> (a, o, s) Source