Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype UnfoldlM m a = UnfoldlM (forall x. (x -> a -> m x) -> x -> m x)
- null :: Monad m => UnfoldlM m input -> m Bool
- foldlM' :: Monad m => (output -> input -> m output) -> output -> UnfoldlM m input -> m output
- mapM_ :: Monad m => (input -> m ()) -> UnfoldlM m input -> m ()
- forM_ :: Monad m => UnfoldlM m input -> (input -> m ()) -> m ()
- fold :: Fold input output -> UnfoldlM Identity input -> output
- foldM :: Monad m => FoldM m input output -> UnfoldlM m input -> m output
- mapFoldMInput :: Monad m => (forall x. FoldM m b x -> FoldM m a x) -> UnfoldlM m a -> UnfoldlM m b
- foldable :: (Monad m, Foldable foldable) => foldable a -> UnfoldlM m a
- foldlRunner :: Monad m => (forall x. (x -> a -> x) -> x -> x) -> UnfoldlM m a
- foldrRunner :: Monad m => (forall x. (a -> x -> x) -> x -> x) -> UnfoldlM m a
- unfoldr :: Monad m => Unfoldr a -> UnfoldlM m a
- filter :: Monad m => (a -> m Bool) -> UnfoldlM m a -> UnfoldlM m a
- intsInRange :: Monad m => Int -> Int -> UnfoldlM m Int
- tVarValue :: TVar a -> UnfoldlM STM a
- hoist :: (forall a. m a -> n a) -> (forall a. n a -> m a) -> UnfoldlM m a -> UnfoldlM n a
- byteStringBytes :: ByteString -> UnfoldlM IO Word8
- shortByteStringBytes :: Monad m => ShortByteString -> UnfoldlM m Word8
- primArray :: (Monad m, Prim prim) => PrimArray prim -> UnfoldlM m prim
- primArrayWithIndices :: (Monad m, Prim prim) => PrimArray prim -> UnfoldlM m (Int, prim)
Documentation
A monadic variation of DeferredFolds.Unfoldl
UnfoldlM (forall x. (x -> a -> m x) -> x -> m x) |
Instances
foldlM' :: Monad m => (output -> input -> m output) -> output -> UnfoldlM m input -> m output Source #
Perform a monadic strict left fold
mapM_ :: Monad m => (input -> m ()) -> UnfoldlM m input -> m () Source #
A more efficient implementation of mapM_
forM_ :: Monad m => UnfoldlM m input -> (input -> m ()) -> m () Source #
Same as mapM_
with arguments flipped
foldM :: Monad m => FoldM m input output -> UnfoldlM m input -> m output Source #
Apply a monadic Gonzalez fold
mapFoldMInput :: Monad m => (forall x. FoldM m b x -> FoldM m a x) -> UnfoldlM m a -> UnfoldlM m b Source #
Lift a fold input mapping function into a mapping of unfolds
foldable :: (Monad m, Foldable foldable) => foldable a -> UnfoldlM m a Source #
Construct from any foldable
foldlRunner :: Monad m => (forall x. (x -> a -> x) -> x -> x) -> UnfoldlM m a Source #
Construct from a specification of how to execute a left-fold
foldrRunner :: Monad m => (forall x. (a -> x -> x) -> x -> x) -> UnfoldlM m a Source #
Construct from a specification of how to execute a right-fold
filter :: Monad m => (a -> m Bool) -> UnfoldlM m a -> UnfoldlM m a Source #
Filter the values given a predicate
intsInRange :: Monad m => Int -> Int -> UnfoldlM m Int Source #
Ints in the specified inclusive range
hoist :: (forall a. m a -> n a) -> (forall a. n a -> m a) -> UnfoldlM m a -> UnfoldlM n a Source #
Change the base monad using invariant natural transformations
byteStringBytes :: ByteString -> UnfoldlM IO Word8 Source #
Bytes of a bytestring
shortByteStringBytes :: Monad m => ShortByteString -> UnfoldlM m Word8 Source #
Bytes of a short bytestring