module Pandora.Pattern.Functor.Extendable where
import Pandora.Core.Functor (type (:.), type (:=))
import Pandora.Pattern.Functor.Covariant (Covariant ((<$>)))
infixl 1 =>>
infixr 1 <<=, =<=, =>=
class Covariant t => Extendable t where
{-# MINIMAL (=>>) #-}
(=>>) :: t a -> (t a -> b) -> t b
(<<=) :: (t a -> b) -> t a -> t b
t a -> b
f <<= t a
x = t a
x t a -> (t a -> b) -> t b
forall (t :: * -> *) a b. Extendable t => t a -> (t a -> b) -> t b
=>> t a -> b
f
extend :: (t a -> b) -> t a -> t b
extend t a -> b
f t a
t = t a
t t a -> (t a -> b) -> t b
forall (t :: * -> *) a b. Extendable t => t a -> (t a -> b) -> t b
=>> t a -> b
f
duplicate :: t a -> t :. t := a
duplicate t a
t = t a
t t a -> (t a -> t a) -> (t :. t) := a
forall (t :: * -> *) a b. Extendable t => t a -> (t a -> b) -> t b
=>> (\t a
x -> t a
x)
(=<=) :: (t b -> c) -> (t a -> b) -> t a -> c
t b -> c
f =<= t a -> b
g = \t a
x -> t b -> c
f ((t a -> b) -> t a -> t b
forall (t :: * -> *) a b. Extendable t => (t a -> b) -> t a -> t b
extend t a -> b
g t a
x)
(=>=) :: (t a -> b) -> (t b -> c) -> t a -> c
t a -> b
f =>= t b -> c
g = \t a
x -> t b -> c
g ((t a -> b) -> t a -> t b
forall (t :: * -> *) a b. Extendable t => (t a -> b) -> t a -> t b
extend t a -> b
f t a
x)
($=>>) :: Covariant u => u :. t := a -> (t a -> b) -> u :. t := b
(u :. t) := a
x $=>> t a -> b
f = (t a -> (t a -> b) -> t b
forall (t :: * -> *) a b. Extendable t => t a -> (t a -> b) -> t b
=>> t a -> b
f) (t a -> t b) -> ((u :. t) := a) -> (u :. t) := b
forall (t :: * -> *) a b. Covariant t => (a -> b) -> t a -> t b
<$> (u :. t) := a
x
(<<=$) :: Covariant u => u :. t := a -> (t a -> b) -> u :. t := b
(u :. t) := a
x <<=$ t a -> b
f = (t a -> (t a -> b) -> t b
forall (t :: * -> *) a b. Extendable t => t a -> (t a -> b) -> t b
=>> t a -> b
f) (t a -> t b) -> ((u :. t) := a) -> (u :. t) := b
forall (t :: * -> *) a b. Covariant t => (a -> b) -> t a -> t b
<$> (u :. t) := a
x