data-aviary-0.4.0: Combinator birds.

Portabilityto be determined
Stabilityexperimental
Maintainerstephen.tetley@gmail.com
Safe HaskellSafe-Inferred

Data.Aviary.Functional

Contents

Description

Functor, Applicative, Monad operations specialized to the functional type.

This catalogue is for reference and is not intended for use.

Synopsis

Functor

fmap :: (a -> b) -> (r -> a) -> r -> bSource

fmap for the function instance of Functor is compose (.) which in turn is bluebird.

Applicative

(<$>) :: (a -> b) -> (r -> a) -> r -> bSource

The Applicative combinator (<$>) is a synonym for fmap, so for the function instance of of Applicative it is compose (.) which is bluebird.

(<$) :: a -> (r -> b) -> r -> aSource

Applicative (<$).

pure :: a -> r -> aSource

The function instance of Applicative pure is const which is kestrel.

(<*>) :: (r -> a -> b) -> (r -> a) -> r -> bSource

The combinator (<*>) for the function instance of Applicative is the S combinator aka starling.

(*>) :: (r -> a) -> (r -> b) -> r -> bSource

(<*) :: (r -> a) -> (r -> b) -> r -> aSource

(<**>) :: (r -> a) -> (r -> a -> b) -> r -> bSource

liftA :: (a -> b) -> (r -> a) -> r -> bSource

The Applicative function liftA is a synonym for fmap, so for the function instance of of Applicative it is compose (.) which is bluebird.

liftA2 :: (a -> b -> c) -> (r -> a) -> (r -> b) -> r -> cSource

liftA2 for the function instance of Applicative is the phoenix combinator, also called big Phi and starling-prime.

liftA3 :: (a -> b -> c -> d) -> (r -> a) -> (r -> b) -> (r -> c) -> r -> dSource

Category

id :: a -> aSource

For the function instance of Category id is just the identity function (Haskell's id).

(.) :: (b -> c) -> (a -> b) -> a -> cSource

For the function instance of Category composition is just regular function composition aka bluebird.

(<<<) :: (b -> c) -> (a -> b) -> a -> cSource

For the function instance of Category right-to-left composition is just regular function composition aka bluebird.

(>>>) :: (a -> b) -> (b -> c) -> a -> cSource

For the function instance of Category left-to-right composition is the queer bird.

Monad

(>>=) :: (r -> a) -> (a -> r -> b) -> r -> bSource

(>>) :: (r -> a) -> (r -> b) -> r -> bSource

return :: a -> r -> aSource

The function instance of Monadic return is equal to the constant function (const) aka kestrel.

fail :: String -> r -> aSource

mapM :: (a -> r -> b) -> [a] -> r -> [b]Source

mapM_ :: (a -> r -> b) -> [a] -> r -> ()Source

forM :: [a] -> (a -> r -> b) -> r -> [b]Source

forM_ :: [a] -> (a -> r -> b) -> r -> ()Source

sequence :: [r -> a] -> r -> [a]Source

sequence_ :: [r -> a] -> r -> ()Source

(=<<) :: (a -> r -> b) -> (r -> a) -> r -> bSource

(>=>) :: (a -> r -> b) -> (b -> r -> c) -> a -> r -> cSource

(<=<) :: (b -> r -> c) -> (a -> r -> b) -> a -> r -> cSource

forever :: (r -> a) -> r -> bSource

join :: (r -> r -> a) -> r -> aSource

filterM :: (a -> r -> Bool) -> [a] -> r -> [a]Source

mapAndUnzipM :: (a -> r -> (b, c)) -> [a] -> r -> ([b], [c])Source

zipWithM :: (a -> b -> r -> c) -> [a] -> [b] -> r -> [c]Source

zipWithM_ :: (a -> b -> r -> c) -> [a] -> [b] -> r -> ()Source

foldM :: (a -> b -> r -> a) -> a -> [b] -> r -> aSource

foldM_ :: (a -> b -> r -> a) -> a -> [b] -> r -> ()Source

replicateM :: Int -> (r -> a) -> r -> [a]Source

replicateM_ :: Int -> (r -> a) -> r -> ()Source

when :: Bool -> (r -> ()) -> r -> ()Source

unless :: Bool -> (r -> ()) -> r -> ()Source

liftM :: (a -> b) -> (r -> a) -> r -> bSource

The Monadic function liftM would ideally be a synonym for fmap, so for the function instance of of Monad it corresponds to composition - Haskell's (.) and the bluebird combinator.

liftM2 :: (a -> b -> c) -> (r -> a) -> (r -> b) -> r -> cSource

liftM2 for the function instance of Monad is the phoenix combinator, also called big Phi and starling-prime.

liftM3 :: (a -> b -> c -> d) -> (r -> a) -> (r -> b) -> (r -> c) -> r -> dSource

liftM4 :: (a -> b -> c -> d -> e) -> (r -> a) -> (r -> b) -> (r -> c) -> (r -> d) -> r -> eSource

liftM5 :: (a -> b -> c -> d -> e -> f) -> (r -> a) -> (r -> b) -> (r -> c) -> (r -> d) -> (r -> e) -> r -> fSource

ap :: (r -> a -> b) -> (r -> a) -> r -> bSource

ap is the Monadic equivalent of the Applicative operator (<*>). So for the function instance of Monad it corresponds to the S combinator aka starling.

Arrow

arr :: (b -> c) -> b -> cSource

The Arrow operation arr corresponds to function application for the function instance of Arrow - i.e. Haskell's ($) operator.

This is the applicator combinator in Data.Aviary.

first :: (b -> c) -> (b, d) -> (c, d)Source

second :: (b -> c) -> (d, b) -> (d, c)Source

(***) :: (b -> c) -> (b' -> c') -> (b, b') -> (c, c')Source

(&&&) :: (b -> c) -> (b -> c') -> b -> (c, c')Source

returnA :: b -> bSource

For the function instance of Arrow, returnA is the identity function aka idiot.

(^>>) :: (b -> c) -> (c -> d) -> b -> dSource

The Arrow operation precomposition with a pure function (left-to-right) is equal to the left-to-right composition operator (>>>) for function Arrows.

This corresponds to queer.

(>>^) :: (b -> c) -> (c -> d) -> b -> dSource

The Arrow operation postcomposition with a pure function (left-to-right) is equal to the left-to-right composition operator (>>>) for function Arrows.

This corresponds to queer.

(<<^) :: (c -> d) -> (b -> c) -> b -> dSource

The Arrow operation precomposition with a pure function (right-to-left) is equal to the right-to-left composition operator (<<<) for function Arrows, which in turn is equal to regular function composition.

This corresponds to bluebird.

(^<<) :: (c -> d) -> (b -> c) -> b -> dSource

The Arrow operation postcomposition with a pure function (right-to-left) is equal to the right-to-left composition operator (<<<) for function Arrows, which in turn is equal to regular function composition.

This corresponds to bluebird.

left :: (b -> c) -> Either b d -> Either c dSource

right :: (b -> c) -> Either d b -> Either d cSource

(+++) :: (b -> c) -> (b' -> c') -> Either b b' -> Either c c'Source

(|||) :: (b -> d) -> (c -> d) -> Either b c -> dSource

app :: (b -> c, b) -> cSource

leftApp :: (b -> c) -> Either b d -> Either c dSource

loop :: ((b, d) -> (c, d)) -> b -> cSource

Comonad

extract :: Monoid m => (m -> a) -> aSource

duplicate :: Monoid m => (m -> a) -> m -> m -> aSource

extend :: Monoid m => ((m -> a) -> b) -> (m -> a) -> m -> bSource

liftW :: Monoid m => (a -> b) -> (m -> a) -> m -> bSource

(=>>) :: Monoid m => (m -> a) -> ((m -> a) -> b) -> m -> bSource

(.>>) :: Monoid m => (m -> a) -> b -> m -> bSource

liftCtx :: Monoid m => (a -> b) -> (m -> a) -> bSource

mapW :: Monoid m => ((m -> a) -> b) -> (m -> [a]) -> [b]Source

parallelW :: Monoid m => (m -> [a]) -> [m -> a]Source

unfoldW :: Monoid m => ((m -> b) -> (a, b)) -> (m -> b) -> [a]Source

sequenceW :: Monoid m => [(m -> a) -> b] -> (m -> a) -> [b]Source