yi-0.7.1: The Haskell-Scriptable Editor

Safe HaskellSafe-Inferred

Yi.Monad

Synopsis

Documentation

class Ref ref whereSource

Methods

readRef :: MonadIO m => ref a -> m aSource

writeRef :: MonadIO m => ref a -> a -> m ()Source

modifyRef :: MonadIO m => ref a -> (a -> a) -> m ()Source

Instances

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

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

getsA :: MonadState s m => Accessor s p -> (p -> a) -> m aSource

getsAndModify :: MonadState s m => (s -> (s, a)) -> m aSource

Combination of the Control.Monad.State modify and gets

maybeM :: Monad m => (x -> m ()) -> Maybe x -> m ()Source

modifiesRef :: (Ref ref, MonadReader r m, MonadIO m) => (r -> ref a) -> (a -> a) -> m ()Source

modifiesThenReadsRef :: (MonadReader r m, MonadIO m) => (r -> IORef a) -> (a -> a) -> m aSource

readsRef :: (Ref ref, MonadReader r m, MonadIO m) => (r -> ref a) -> m aSource

repeatUntilM :: Monad m => m (Bool, a) -> m [a]Source

Rerun the monad until the boolean result is false, collecting list of results.

whenM :: Monad m => m Bool -> m () -> m ()Source

with :: (MonadReader yi m, MonadIO m) => (yi -> component) -> (component -> IO a) -> m aSource

writesRef :: (MonadReader r m, MonadIO m) => (r -> IORef a) -> a -> m ()Source