computations-0.0.0.0: Advanced notions of computation

Safe HaskellNone
LanguageHaskell2010

Control.Computation

Contents

Synopsis

Arrows

Computations

class ArrowChoice p => Computation p where Source

Associated Types

type Unit p :: * Source

type Pair p :: * -> * -> * Source

type Function p :: * -> * -> * Source

type DropResult p a :: Constraint Source

Methods

(###) :: (a `p` c) -> (b `p` d) -> Pair p a b `p` Pair p c d infixr 3 Source

assocLeft :: Pair p a (Pair p b c) `p` Pair p (Pair p a b) c Source

assocRight :: Pair p (Pair p a b) c `p` Pair p a (Pair p b c) Source

padFst :: a `p` Pair p (Unit p) a Source

padSnd :: a `p` Pair p a (Unit p) Source

dropFst :: DropResult p a => Pair p (Unit p) a `p` a Source

dropSnd :: DropResult p a => Pair p a (Unit p) `p` a Source

swap :: Pair p a b `p` Pair p b a Source

curry :: (Pair p a b `p` c) -> a `p` Function p b c Source

apply :: Pair p (Function p a b) a `p` b Source

mapFst :: Computation p => (a `p` b) -> Pair p a c `p` Pair p b c Source

mapSnd :: Computation p => (b `p` c) -> Pair p a b `p` Pair p a c Source

precomp :: Computation p => (a `p` b) -> Function p b c `p` Function p a c Source

postcomp :: Computation p => (b `p` c) -> Function p a b `p` Function p a c Source

uncurry :: Computation p => (a `p` Function p b c) -> Pair p a b `p` c Source

inFst :: Computation p => (a `p` Function p b c) -> Pair p a b `p` c Source

inSnd :: Computation p => (b `p` Function p a c) -> Pair p a b `p` c Source

outFst :: Computation p => (Pair p a b `p` c) -> a `p` Function p b c Source

outSnd :: Computation p => (Pair p a b `p` c) -> b `p` Function p a c Source

Nested pairs

map1 :: Computation p => (a `p` b) -> Pair p a t `p` Pair p b t Source

map2 :: Computation p => (b `p` c) -> Pair p a (Pair p b t) `p` Pair p a (Pair p c t) Source

map3 :: Computation p => (c `p` d) -> Pair p a (Pair p b (Pair p c t)) `p` Pair p a (Pair p b (Pair p d t)) Source

map4 :: Computation p => (d `p` e) -> Pair p a (Pair p b (Pair p c (Pair p d t))) `p` Pair p a (Pair p b (Pair p c (Pair p e t))) Source

in1 :: Computation p => (a `p` Function p t r) -> Pair p a t `p` r Source

in2 :: Computation p => (b `p` Function p t (Function p a r)) -> Pair p a (Pair p b t) `p` r Source

in3 :: Computation p => (c `p` Function p t (Function p b (Function p a r))) -> Pair p a (Pair p b (Pair p c t)) `p` r Source

in4 :: Computation p => (d `p` Function p t (Function p c (Function p b (Function p a r)))) -> Pair p a (Pair p b (Pair p c (Pair p d t))) `p` r Source

out1 :: Computation p => (Pair p a t `p` r) -> a `p` Function p t r Source

out2 :: Computation p => (Pair p a (Pair p b t) `p` r) -> b `p` Function p t (Function p a r) Source

out3 :: Computation p => (Pair p a (Pair p b (Pair p c t)) `p` r) -> c `p` Function p t (Function p b (Function p a r)) Source

out4 :: Computation p => (Pair p a (Pair p b (Pair p c (Pair p d t))) `p` r) -> d `p` Function p t (Function p c (Function p b (Function p a r))) Source

construct :: Computation p => (Unit p `p` a) -> b `p` Pair p a b Source

destruct :: (Computation p, DropResult p b) => (a `p` Unit p) -> Pair p a b `p` b Source

(+:+) :: Computation p => (Unit p `p` a) -> (b `p` t) -> b `p` Pair p a t infixr 5 Source

(-:-) :: (Computation p, DropResult p t) => (a `p` Unit p) -> (t `p` b) -> Pair p a t `p` b infixr 5 Source

Pure computations

type Pure = (->) Source

Links between computation types

class (Computation (Source l), Computation (Target l)) => Link l where Source

Associated Types

type Source l :: * -> * -> * Source

type Target l :: * -> * -> * Source

Methods

linkMap :: Source l a b -> Target l (l a) (l b) Source

unitInside :: Target l (Unit (Target l)) (l (Unit (Source l))) Source

pairInside :: Target l (Pair (Target l) (l a) (l b)) (l (Pair (Source l) a b)) Source

Connected computation types

class (Link (p ==> q), Source (p ==> q) ~ p, Target (p ==> q) ~ q, Link (p <== q), Source (p <== q) ~ q, Target (p <== q) ~ p) => Connected p q where Source

Associated Types

data p ==> q :: * -> * Source

data p <== q :: * -> * Source

Methods

inject :: a `p` (p <== q) ((p ==> q) a) Source

extract :: (p ==> q) ((p <== q) b) `q` b Source

Instances

Computation p => Connected p p 
Connected Pure Resourceful 
Typeable ((* -> * -> *) -> (* -> * -> *) -> Constraint) Connected 

up :: Connected p q => (a `p` (p <== q) b) -> (p ==> q) a `q` b Source

down :: Connected p q => ((p ==> q) a `q` b) -> a `p` (p <== q) b Source