trek-0.0.1.0

Safe HaskellNone
LanguageHaskell2010

Trek

Contents

Synopsis

Types

newtype TrekT s m a Source #

The Trek Monad Transformer. Implements both MonadReader and MonadState.

Constructors

TrekT (LogicT (StateT s m) a) 
Instances
Monad m => MonadState s (TrekT s m) Source # 
Instance details

Defined in Trek

Methods

get :: TrekT s m s #

put :: s -> TrekT s m () #

state :: (s -> (a, s)) -> TrekT s m a #

Monad m => MonadReader s (TrekT s m) Source # 
Instance details

Defined in Trek

Methods

ask :: TrekT s m s #

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

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

MonadTrans (TrekT s) Source # 
Instance details

Defined in Trek

Methods

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

Monad (TrekT s m) Source # 
Instance details

Defined in Trek

Methods

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

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

return :: a -> TrekT s m a #

fail :: String -> TrekT s m a #

Functor (TrekT s m) Source # 
Instance details

Defined in Trek

Methods

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

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

MonadFail (TrekT s m) Source # 
Instance details

Defined in Trek

Methods

fail :: String -> TrekT s m a #

Applicative (TrekT s m) Source # 
Instance details

Defined in Trek

Methods

pure :: a -> TrekT s m a #

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

liftA2 :: (a -> b -> c) -> TrekT s m a -> TrekT s m b -> TrekT s m c #

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

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

Alternative (TrekT s m) Source # 
Instance details

Defined in Trek

Methods

empty :: TrekT s m a #

(<|>) :: TrekT s m a -> TrekT s m a -> TrekT s m a #

some :: TrekT s m a -> TrekT s m [a] #

many :: TrekT s m a -> TrekT s m [a] #

Semigroup a => Semigroup (TrekT s m a) Source # 
Instance details

Defined in Trek

Methods

(<>) :: TrekT s m a -> TrekT s m a -> TrekT s m a #

sconcat :: NonEmpty (TrekT s m a) -> TrekT s m a #

stimes :: Integral b => b -> TrekT s m a -> TrekT s m a #

Monoid a => Monoid (TrekT s m a) Source # 
Instance details

Defined in Trek

Methods

mempty :: TrekT s m a #

mappend :: TrekT s m a -> TrekT s m a -> TrekT s m a #

mconcat :: [TrekT s m a] -> TrekT s m a #

type Trek s a = TrekT s Identity a Source #

Pure Trek Monad

Combinators

select :: Monad m => (s -> a) -> TrekT s m a Source #

Get a value from your state

selectEach :: (Monad m, Foldable f) => (s -> f a) -> TrekT s m a Source #

Iterate over several values from your state. An alias for select >=> iter

iter :: Foldable f => f a -> TrekT s m a Source #

Iterate over each of the provided values one at a time.

collect :: Monad m => TrekT s m a -> TrekT s m [a] Source #

Run a full TrekT block collecting all results into a list

mount :: Monad m => (t -> s) -> TrekT s m a -> TrekT t m a Source #

Run a TrekT block over a portion of state. All state changes from the block are discarded.

mountEach :: (Monad m, Foldable f) => (t -> f s) -> TrekT s m a -> TrekT t m a Source #

Like mount but focuses each of a list of values one at a time. All state changes from the block are discarded.

with :: Monad m => s -> TrekT s m a -> TrekT t m a Source #

Run a TrekT block over a piece of state. All state changes from the block are discarded.

withEach :: (Monad m, Foldable f) => f s -> TrekT s m a -> TrekT t m a Source #

Like with but focuses each of a list of values one at a time. All state changes from the block are discarded.

Running Trek

evalTrek :: Trek s a -> s -> [a] Source #

Evaluate the results of a Trek.

evalTrekT :: Monad m => TrekT s m a -> s -> m [a] Source #

Evaluate the results of a TrekT.

execTrek :: Trek s a -> s -> s Source #

Return the altered state after running a Trek.

execTrekT :: Monad m => TrekT s m a -> s -> m s Source #

Return the altered state after running a TrekT.

runTrek :: Trek s a -> s -> ([a], s) Source #

Run a Trek

runTrekT :: Monad m => TrekT s m a -> s -> m ([a], s) Source #

Run a TrekT

Re-Exports

get :: MonadState s m => m s #

Return the state from the internals of the monad.

gets :: MonadState s m => (s -> a) -> m a #

Gets specific component of the state, using a projection function supplied.

put :: MonadState s m => s -> m () #

Replace the state inside the monad.

modify :: MonadState s m => (s -> s) -> m () #

Monadic state transformer.

Maps an old state to a new state inside a state monad. The old state is thrown away.

     Main> :t modify ((+1) :: Int -> Int)
     modify (...) :: (MonadState Int a) => a ()

This says that modify (+1) acts over any Monad that is a member of the MonadState class, with an Int state.

ask :: MonadReader r m => m r #

Retrieves the monad environment.

asks #

Arguments

:: MonadReader r m 
=> (r -> a)

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.