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.Rep

Description

Hyperfunctions as an explicit nu form, but using a representable functor to describe the state space of the hyperfunction. This permits memoization but doesn't require it.

If we start with a 'function with state' (x -> a) -> x -> b we can view it as either (x -> a, x) -> b wich is a Store x Cokleisli morphism or as φ :: x -> (x -> a) -> b which given H a b x = (x -> a) -> b is a (H a b)-coalgebra: (x, φ) . Given that we can think of anamorphisms of this 'function with state' as giving us a fixed point for H a b and the morphism to the final coalgebra @(Hyper a b, ana φ) is unique (by definition).

A representable functor f is isomorphic to (->) (Rep f). ((->) x) is an obvious selection for such a representable functor, so if we switch out the functions from x in the above, for a representable functor with x as its representation we get opportunities for memoization on the internal 'state space' of our hyperfunctions.

Synopsis

Documentation

data Hyper a b where Source

Represented Hyperfunctions

arr is a faithful functor, so

arr f ≡ arr g implies f ≡ g

Constructors

Hyper :: Representable g => g (g a -> b) -> Rep g -> Hyper a b 

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

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

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

cata' :: Representable f => ((f a -> b) -> Rep f) -> Hyper a b -> Rep f Source

Memoizing catamorphism

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

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

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

Unroll a hyperfunction

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

Re-roll a hyperfunction using Lambek's lemma.

invoke :: Hyper a b -> Hyper b a -> b Source

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

run :: Hyper a a -> a Source

run f ≡ invoke f id
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 . arrid
project h a ≡ invoke h (pure a)
project (push f q) ≡ f

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

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