yi-0.6.2.3: The Haskell-Scriptable EditorSource codeContentsIndex
Yi.Monad
Synopsis
class Ref ref where
readRef :: MonadIO m => ref a -> m a
writeRef :: MonadIO m => ref a -> a -> m ()
modifyRef :: MonadIO m => ref a -> (a -> a) -> m ()
gets :: MonadState s m => (s -> a) -> m a
getsA :: MonadState s m => Accessor s p -> (p -> a) -> m a
getsAndModify :: MonadState s m => (s -> (s, a)) -> m a
maybeM :: Monad m => (x -> m ()) -> Maybe x -> m ()
modifiesRef :: (Ref ref, MonadReader r m, MonadIO m) => (r -> ref a) -> (a -> a) -> m ()
modifiesThenReadsRef :: (MonadReader r m, MonadIO m) => (r -> IORef a) -> (a -> a) -> m a
readsRef :: (Ref ref, MonadReader r m, MonadIO m) => (r -> ref a) -> m a
repeatUntilM :: Monad m => m (Bool, a) -> m [a]
whenM :: Monad m => m Bool -> m () -> m ()
with :: (MonadReader yi m, MonadIO m) => (yi -> component) -> (component -> IO a) -> m a
writesRef :: (MonadReader r m, MonadIO m) => (r -> IORef a) -> a -> m ()
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
show/hide Instances
gets :: MonadState s m => (s -> a) -> m aSource
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
Produced by Haddock version 2.6.1