Safe Haskell | None |
---|---|
Language | Haskell2010 |
- newtype LoopT m a = LoopT {
- runLoopT :: forall r. (a -> m r -> m r -> m r) -> m r -> m r -> m r
- type Loop = LoopT Identity
- loop :: Loop a -> Loop a
- cons :: a -> LoopT m a -> LoopT m a
- continue :: a -> LoopT m a
- continue_ :: LoopT m a
- break_ :: LoopT m a
- exec_ :: Applicative m => LoopT m a -> m ()
- class ForEach m c where
- type ForEachValue c
- type ForEachIx c
- iterate :: a -> (a -> a) -> LoopT m a
- forever :: LoopT m ()
- for :: a -> (a -> Bool) -> (a -> a) -> LoopT m a
- unfoldl :: (i -> Maybe (i, a)) -> i -> LoopT m a
- while :: Monad m => m Bool -> LoopT m ()
- forEach :: ForEach m c => c -> m (ForEachValue c)
- iforEach :: ForEach m c => c -> m (ForEachIx c, ForEachValue c)
Documentation
LoopT m a
represents a loop over a base type m
that yields a value
a
at each iteration. It can be used as a monad transformer, but there
are actually no restrictions on the type m
. However, this library only
provides functions to execute the loop if m
is at least Applicative
(for exec_
). If m
is also Foldable
, so is LoopT m
. For any other
type, you may use runLoopT
.
MonadTrans (LoopT *) | |
Monad (LoopT k m) | |
Functor (LoopT k m) | |
Applicative (LoopT k m) | |
(Applicative m, Foldable m) => Foldable (LoopT * m) | |
(Applicative m, Foldable m) => Traversable (LoopT * m) | |
MonadIO m => MonadIO (LoopT * m) | |
(Monad m, Storable a) => ForEach (LoopT * m) (Vector a) | |
(Monad m, Prim a) => ForEach (LoopT * m) (Vector a) | |
(Monad m, Unbox a) => ForEach (LoopT * m) (Vector a) | |
Monad m => ForEach (LoopT * m) (Vector a) | |
Monad m => ForEach (LoopT * m) [a] | |
(Storable a, PrimMonad m, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) | |
(PrimMonad m, Prim a, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) | |
(PrimMonad m, Unbox a, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) | |
(PrimMonad m, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) |
loop :: Loop a -> Loop a Source
loop
is just an aid to type inference. For loops over a base monad,
there are usually other constraints that fix the type, but for pure
loops, the compiler often has trouble inferring Identity
.
continue :: a -> LoopT m a Source
Yield a value for this iteration of the loop and skip immediately to the next iteration.
Skip immediately to the next iteration of the loop without yielding a value.
exec_ :: Applicative m => LoopT m a -> m () Source
Execute a loop, sequencing the effects and discarding the values.
Class of containers that can be iterated over. The class is parameterized over a base monad where the values of the container can be read to allow iterating over mutable structures. The associated type families parameterize the value and index types of the container, allowing the class to be instantiated for container types (unboxed or storable vectors, for example) which do not admit all types as values.
type ForEachValue c Source
(Monad m, Storable a) => ForEach (LoopT * m) (Vector a) | |
(Monad m, Prim a) => ForEach (LoopT * m) (Vector a) | |
(Monad m, Unbox a) => ForEach (LoopT * m) (Vector a) | |
Monad m => ForEach (LoopT * m) (Vector a) | |
Monad m => ForEach (LoopT * m) [a] | |
(Storable a, PrimMonad m, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) | |
(PrimMonad m, Prim a, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) | |
(PrimMonad m, Unbox a, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) | |
(PrimMonad m, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) |
forEach :: ForEach m c => c -> m (ForEachValue c) Source
Iterate over the values in the container.
iforEach :: ForEach m c => c -> m (ForEachIx c, ForEachValue c) Source
Iterate over the indices and the value at each index.