Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Helper functions for functors.
These operators are designed to make the interoperation between monadic and pure computations more convenient by allowing them to be chained together without peppering the program with superflouos return statements.
Each function is a pure analogue of a monadic one. The correspondences are as follows:
>$> ~ >>=
(bind)$> ~ >>
(throw away left argument)<$ ~ <<
(re-exported from Data.Functor)<$< ~ =<<
(same as<$>
, but with the precedence of>>=
)>=$> ~ >=>
(Kleisli composition)<$=< ~ <=<
(flipped Kleisli composition)
Lastly, |>
is left-to-right function composition (flipped version of $
).
Documentation
module Data.Functor
(>$>) :: Functor f => f a -> (a -> b) -> f b infixl 1 Source
Flipped fmap
for chaining plain functions after a functor in the following
way:
readFile '1.txt' >$> lines >$> map length >>= print
lines
and map length
are non-monadic functions, but peppering
them with returns, as pure >>=
necessitates, is quite tedious.
In general:
m >>= return . f is the same as m >$> f
(<$<) :: Functor f => (a -> b) -> f a -> f b infixr 1 Source
Right-associative infix synonym for fmap
.