hyperfunctions-0: Hyperfunctions

Copyright(C) 2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell98

Control.Monad.Hyper

Description

 

Synopsis

Documentation

newtype Hyper a b Source

invoke f g ≡ run (f . g)
arr f ≡ push f (arr f)
invoke id id ≡ _|_

arr is a faithful functor, so arr f ≡ arr g implies f ≡ g

Constructors

Hyper 

Fields

invoke :: Hyper b a -> b
 

unroll :: Hyper a b -> (Hyper a b -> a) -> b Source

roll :: ((Hyper a b -> a) -> b) -> Hyper a b Source

ana :: (x -> (x -> a) -> b) -> x -> Hyper a b Source

cata :: (((x -> a) -> b) -> x) -> Hyper a b -> x Source

From "Generalizing the augment combinator" by Ghani, Uustali and Vene.

cata phi (push f h) ≡ phi $ \g -> f $ g (cata phi h)

push :: (a -> b) -> Hyper a b -> Hyper a b Source

push f p . push g q ≡ push (f . g) (p . q)
invoke (push f p) q ≡ f (invoke q p)

run :: Hyper a a -> a Source

run (arr f) ≡ fix f
run (push f q) ≡ f (run q)
run (push f p . q) ≡ f (run (q . p)) = f (invoke q p)

project :: Hyper a b -> a -> b Source

project (push f q) ≡ f

project is a left inverse for arr:

project . arrid

fold :: [a] -> (a -> b -> c) -> c -> Hyper b c Source

build :: (forall b c. (a -> b -> c) -> c -> Hyper b c) -> [a] Source