prologue-3.1.6: Better, more general Prelude exporting common utilities.

Safe HaskellNone
LanguageHaskell2010

Prologue.Data.Traversable

Documentation

type family Traversables (lst :: [* -> *]) :: Constraint where ... Source #

Equations

Traversables '[] = () 
Traversables (t ': ts) = (Traversable t, Traversables ts) 

sequence :: (Traversable t, Applicative f) => t (f a) -> f (t a) Source #

bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b) Source #

(<$>=) :: (Monad m, Traversable t1) => (a -> m b) -> t1 a -> m (t1 b) infixl 4 Source #

(<<$>>=) :: (Monad m, Traversables '[t1, t2]) => (a -> m b) -> t2 (t1 a) -> m (t2 (t1 b)) infixl 4 Source #

mapM2 :: (Monad m, Traversables '[t1, t2]) => (a -> m b) -> t2 (t1 a) -> m (t2 (t1 b)) Source #

(<<<$>>>=) :: (Monad m, Traversables '[t1, t2, t3]) => (a -> m b) -> t3 (t2 (t1 a)) -> m (t3 (t2 (t1 b))) infixl 4 Source #

mapM3 :: (Monad m, Traversables '[t1, t2, t3]) => (a -> m b) -> t3 (t2 (t1 a)) -> m (t3 (t2 (t1 b))) Source #

(<<<<$>>>>=) :: (Monad m, Traversables '[t1, t2, t3, t4]) => (a -> m b) -> t4 (t3 (t2 (t1 a))) -> m (t4 (t3 (t2 (t1 b)))) infixl 4 Source #

mapM4 :: (Monad m, Traversables '[t1, t2, t3, t4]) => (a -> m b) -> t4 (t3 (t2 (t1 a))) -> m (t4 (t3 (t2 (t1 b)))) Source #

(<<<<<$>>>>>=) :: (Monad m, Traversables '[t1, t2, t3, t4, t5]) => (a -> m b) -> t5 (t4 (t3 (t2 (t1 a)))) -> m (t5 (t4 (t3 (t2 (t1 b))))) infixl 4 Source #

mapM5 :: (Monad m, Traversables '[t1, t2, t3, t4, t5]) => (a -> m b) -> t5 (t4 (t3 (t2 (t1 a)))) -> m (t5 (t4 (t3 (t2 (t1 b))))) Source #

(<|$>=) :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t (a, b)) infixl 4 Source #

(<$|>=) :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t (b, a)) infixl 4 Source #