deepcontrol-0.1.0.0: Enable deeper level style of programming than the usual control provides

CopyrightKONISHI Yohuske 2015
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerocean0yohsuke@gmail.com
Stabilityexperimental
Portability---
Safe HaskellSafe
LanguageHaskell2010

DeepControl.Applicative

Contents

Description

This module enables you to program in applicative style for more deeper level than the usual Applicative module expresses. You would soon realize exactly what more deeper level means by reading the example codes in order, which are attached on the functions below. Note: all braket-cover notation for Level-4 and Level-5 is not written yet.

Synopsis

Documentation

Level-0

bra-ket notation

(|>) :: (a -> b) -> a -> b infixl 4 Source

Alias for $.

>>> (1+) |> 2
3

(<|) :: a -> (a -> b) -> b infixl 4 Source

The auguments-flipped function for |>.

>>> 1 <| (+2)
3 
>>> 1 <|(+)|> 2
3 
>>> 1 <|(+)|> 2 <|(*)|> 3
9
>>> 1 <|(,)|> 2
(1,2)

Level-1

cover notation

(*:) :: Applicative f => a -> f a infixl 5 Source

Alias for pure.

bra-ket notation

(|$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 Source

Alias for <$>.

>>> (1+) |$> [2]
[3]

(<$|) :: Functor f => f a -> (a -> b) -> f b infixl 3 Source

The auguments-flipped function for |$>.

>>> [1] <$| (+2)
[3]
>>> ("<"++)|$> ["a","b"] <$|(++">")
["<a>","<b>"]

(|*>) :: Applicative f => f (a -> b) -> f a -> f b infixl 3 Source

Alias for <*>.

>>> [(1+)] |*> [2]
[3]
>>> [1] <$|(+)|*> [2]
[3]
>>> [1] <$|(+)|*> [0,1,2]
[1,2,3]
>>> [0,1] <$|(+)|*> [2,3] <$|(^)|*> [4,5]
[16,32,81,243,81,243,256,1024]
>>> foldr (\x acc -> x <$|(:)|*> acc) ((*:) []) [Just 1, Just 2,  Just 3]
Just [1,2,3]
>>> foldr (\x acc -> x <$|(:)|*> acc) ((*:) []) [Just 1, Nothing, Just 3]
Nothing
>>> filter (even <$|(&&)|*> (10 >)) [1..100]
[2,4,6,8]
>>> filter (even <$|(&&)|*> (10 >) <$|(&&)|*> (5 <)) [1..100]
[6,8]

(<*|) :: Applicative f => f a -> f (a -> b) -> f b infixl 3 Source

The auguments-flipped function for |*>.

braket-cover notation

(|*) :: Applicative f => f (a -> b) -> a -> f b infixl 3 Source

Combination consisted of ket |*> and cover *:, defined as f |* x = f |*> ((*:) x).

>>> [(1+)] |* 2
[3]
>>> [1] <$|(+)|* 2
[3]
>>> [1] <$|(+)|* 2 <$|(*)|* 3
[9]
>>> Just 1 <$|(,)|* 2
Just (1,2)

(*|) :: Applicative f => a -> f (a -> b) -> f b infixl 3 Source

The auguments-flipped function for |*.

>>> 1 *| [(+2)]
[3]
>>> 1 *| [(+)] |* 2
[3]
>>> 1 *|[(+),(-),(*),(^)]|* 2
[3,-1,2,1]
>>> 1 *|Just (,)|* 2
Just (1,2)

Level-2

cover notation

(**:) :: (Applicative f1, Applicative f2) => a -> f1 (f2 a) infixl 5 Source

Combination consisted of cover *: twice, defined as (**:) = (*:) . (*:).

(*-) :: (Applicative f1, Applicative f2) => f2 a -> f1 (f2 a) infixl 5 Source

Alias for *:.

(-*) :: (Applicative f1, Applicative f2) => f1 a -> f1 (f2 a) infixl 5 Source

Combination consisted of cover *: and ket |$>, defined as (-*) = ((*:)|$>).

bra-ket notation

(|$>>) :: (Functor f1, Functor f2) => (a -> b) -> f1 (f2 a) -> f1 (f2 b) infixl 4 Source

Combination consisted of cover |$> twice, defined as (|$>>) = (|$>) . (|$>).

>>> (+1) |$>> [[2]]
[[3]]

(<<$|) :: (Functor f1, Functor f2) => f1 (f2 a) -> (a -> b) -> f1 (f2 b) infixl 3 Source

The auguments-flipped function for |$>>

>>> [[2]] <<$| (+1)
[[3]]

(|*>>) :: (Applicative f1, Applicative f2) => f1 (f2 (a -> b)) -> f1 (f2 a) -> f1 (f2 b) infixl 3 Source

The lifted function of |*>, defined as (|*>>) = liftA2 (|*>).

>>> [Just 1] <<$|(+)|*>> [Just 2]
[Just 3]
>>> [Just 1] <<$|(,)|*>> [Just 2]
[Just (1,2)]
>>> [[1]] <<$|(+)|*>> [[2]] <<$|(-)|*>> [[3]]
[[0]]
>>> foldr (\n acc -> n <<$|(+)|*>> acc) ((**:) 0) ([Right (Just 1), Right (Just 2), Right (Just 3)]) :: Either () (Maybe Int)
Right (Just 6)
>>> foldr (\n acc -> n <<$|(+)|*>> acc) ((**:) 0) ([Right (Just 1), Right Nothing, Right (Just 3)]) :: Either () (Maybe Int)
Right Nothing
>>> foldr (\n acc -> n <<$|(+)|*>> acc) ((**:) 0) ([Right (Just 1), Right Nothing, Left ()])
Left ()

(<<*|) :: (Applicative f1, Applicative f2) => f1 (f2 a) -> f1 (f2 (a -> b)) -> f1 (f2 b) infixl 3 Source

The auguments-flipped function for |*>>.

braket-cover notation

(|**) :: (Applicative f1, Applicative f2) => f1 (f2 (a -> b)) -> a -> f1 (f2 b) infixl 3 Source

Combination consisted of ket |*>> and cover **:, defined as f |** x = f |*>> ((**:) x).

>>> [Just 1] <<$|(+)|** 2
[Just 3]

(**|) :: (Applicative f1, Applicative f2) => a -> f1 (f2 (a -> b)) -> f1 (f2 b) infixl 3 Source

The auguments-flipped function for |**.

>>> 1 **|(+)|$>> [Just 2]
[Just 3]
>>> 1 **|[Just (+)]|**  2
[Just 3]
>>> 1 **|[Just (+), Just (-), Just (*), Nothing]|** 2
[Just 3,Just (-1),Just 2,Nothing]

(|-*) :: (Applicative f1, Applicative f2) => f1 (f2 (a -> b)) -> f1 a -> f1 (f2 b) infixl 3 Source

Combination consisted of ket |*>> and cover -*, defined as f |-* x = f |*>> ((-*) x).

>>> [Just 1] <<$|(+)|-* [2]
[Just 3]

(|*-) :: (Applicative f1, Applicative f2) => f1 (f2 (a -> b)) -> f2 a -> f1 (f2 b) infixl 3 Source

Combination consisted of ket |*>> and cover *-, defined as f |-* x = f |*>> ((*-) x).

>>> [Just 1] <<$|(+)|*- Just 2
[Just 3]

(-*|) :: (Applicative f1, Applicative f2) => f1 a -> f1 (f2 (a -> b)) -> f1 (f2 b) infixl 3 Source

The auguments-flipped function for |-*.

>>> [1] -*|(+)|$>> [Just 2]
[Just 3]

(*-|) :: (Applicative f1, Applicative f2) => f2 a -> f1 (f2 (a -> b)) -> f1 (f2 b) infixl 3 Source

The auguments-flipped function for |*-.

>>> Just 1 *-|(+)|$>> [Just 2]
[Just 3]
>>> Just 1 *-|[Just (+)]|** 2
[Just 3]
>>> Just 1 *-|[Just (+)]|*- Just 2
[Just 3]
>>> [1] -*|[Just (+)]|*- Just 2
[Just 3]
>>> [1] -*|[Just (+), Just (-), Just (*), Nothing]|*- Just 2
[Just 3,Just (-1),Just 2,Nothing]
>>> [0,1] -*|[Just (+), Just (-), Just (*), Nothing]|*- Just 2
[Just 2,Just 3,Just (-2),Just (-1),Just 0,Just 2,Nothing,Nothing]

Level-3

cover notation

(***:) :: (Applicative f1, Applicative f2, Applicative f3) => a -> f1 (f2 (f3 a)) infixl 5 Source

(**-) :: (Applicative f1, Applicative f2, Applicative f3) => f3 a -> f1 (f2 (f3 a)) infixl 5 Source

(*-*) :: (Applicative f1, Applicative f2, Applicative f3) => f2 a -> f1 (f2 (f3 a)) infixl 5 Source

(-**) :: (Applicative f1, Applicative f2, Applicative f3) => f1 a -> f1 (f2 (f3 a)) infixl 5 Source

(--*) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f2 a) -> f1 (f2 (f3 a)) infixl 5 Source

(-*-) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f3 a) -> f1 (f2 (f3 a)) infixl 5 Source

(*--) :: (Applicative f1, Applicative f2, Applicative f3) => f2 (f3 a) -> f1 (f2 (f3 a)) infixl 5 Source

bra-ket notation

(|$>>>) :: (Functor f1, Functor f2, Functor f3) => (a -> b) -> f1 (f2 (f3 a)) -> f1 (f2 (f3 b)) infixl 4 Source

(<<<$|) :: (Functor f1, Functor f2, Functor f3) => f1 (f2 (f3 a)) -> (a -> b) -> f1 (f2 (f3 b)) infixl 3 Source

(|*>>>) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f2 (f3 (a -> b))) -> f1 (f2 (f3 a)) -> f1 (f2 (f3 b)) infixl 3 Source

(<<<*|) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f2 (f3 a)) -> f1 (f2 (f3 (a -> b))) -> f1 (f2 (f3 b)) infixl 3 Source

braket-cover notation

(|***) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f2 (f3 (a -> b))) -> a -> f1 (f2 (f3 b)) infixl 3 Source

(***|) :: (Applicative f1, Applicative f2, Applicative f3) => a -> f1 (f2 (f3 (a -> b))) -> f1 (f2 (f3 b)) infixl 3 Source

(|-**) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f2 (f3 (a -> b))) -> f1 a -> f1 (f2 (f3 b)) infixl 3 Source

(|*-*) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f2 (f3 (a -> b))) -> f2 a -> f1 (f2 (f3 b)) infixl 3 Source

(|**-) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f2 (f3 (a -> b))) -> f3 a -> f1 (f2 (f3 b)) infixl 3 Source

(|--*) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f2 (f3 (a -> b))) -> f1 (f2 a) -> f1 (f2 (f3 b)) infixl 3 Source

(|-*-) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f2 (f3 (a -> b))) -> f1 (f3 a) -> f1 (f2 (f3 b)) infixl 3 Source

(|*--) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f2 (f3 (a -> b))) -> f2 (f3 a) -> f1 (f2 (f3 b)) infixl 3 Source

(-**|) :: (Applicative f1, Applicative f2, Applicative f3) => f1 a -> f1 (f2 (f3 (a -> b))) -> f1 (f2 (f3 b)) infixl 3 Source

(*-*|) :: (Applicative f1, Applicative f2, Applicative f3) => f2 a -> f1 (f2 (f3 (a -> b))) -> f1 (f2 (f3 b)) infixl 3 Source

(**-|) :: (Applicative f1, Applicative f2, Applicative f3) => f3 a -> f1 (f2 (f3 (a -> b))) -> f1 (f2 (f3 b)) infixl 3 Source

(--*|) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f2 a) -> f1 (f2 (f3 (a -> b))) -> f1 (f2 (f3 b)) infixl 3 Source

(-*-|) :: (Applicative f1, Applicative f2, Applicative f3) => f1 (f3 a) -> f1 (f2 (f3 (a -> b))) -> f1 (f2 (f3 b)) infixl 3 Source

(*--|) :: (Applicative f1, Applicative f2, Applicative f3) => f2 (f3 a) -> f1 (f2 (f3 (a -> b))) -> f1 (f2 (f3 b)) infixl 3 Source

Level-4

cover notation

(****:) :: (Applicative f1, Applicative f2, Applicative f3, Applicative f4) => a -> f1 (f2 (f3 (f4 a))) infixl 5 Source

bra-ket notation

(|$>>>>) :: (Functor f1, Functor f2, Functor f3, Functor f4) => (a -> b) -> f1 (f2 (f3 (f4 a))) -> f1 (f2 (f3 (f4 b))) infixl 4 Source

(<<<<$|) :: (Functor f1, Functor f2, Functor f3, Functor f4) => f1 (f2 (f3 (f4 a))) -> (a -> b) -> f1 (f2 (f3 (f4 b))) infixl 3 Source

(|*>>>>) :: (Applicative f1, Applicative f2, Applicative f3, Applicative f4) => f1 (f2 (f3 (f4 (a -> b)))) -> f1 (f2 (f3 (f4 a))) -> f1 (f2 (f3 (f4 b))) infixl 3 Source

(<<<<*|) :: (Applicative f1, Applicative f2, Applicative f3, Applicative f4) => f1 (f2 (f3 (f4 a))) -> f1 (f2 (f3 (f4 (a -> b)))) -> f1 (f2 (f3 (f4 b))) infixl 3 Source

Level-5

cover notation

(*****:) :: (Applicative f1, Applicative f2, Applicative f3, Applicative f4, Applicative f5) => a -> f1 (f2 (f3 (f4 (f5 a)))) infixl 5 Source

bra-ket notation

(|$>>>>>) :: (Functor f1, Functor f2, Functor f3, Functor f4, Functor f5) => (a -> b) -> f1 (f2 (f3 (f4 (f5 a)))) -> f1 (f2 (f3 (f4 (f5 b)))) infixl 4 Source

(<<<<<$|) :: (Functor f1, Functor f2, Functor f3, Functor f4, Functor f5) => f1 (f2 (f3 (f4 (f5 a)))) -> (a -> b) -> f1 (f2 (f3 (f4 (f5 b)))) infixl 3 Source

(|*>>>>>) :: (Applicative f1, Applicative f2, Applicative f3, Applicative f4, Applicative f5) => f1 (f2 (f3 (f4 (f5 (a -> b))))) -> f1 (f2 (f3 (f4 (f5 a)))) -> f1 (f2 (f3 (f4 (f5 b)))) infixl 3 Source

(<<<<<*|) :: (Applicative f1, Applicative f2, Applicative f3, Applicative f4, Applicative f5) => f1 (f2 (f3 (f4 (f5 a)))) -> f1 (f2 (f3 (f4 (f5 (a -> b))))) -> f1 (f2 (f3 (f4 (f5 b)))) infixl 3 Source