module Pandora.Pattern.Functor.Extendable (Extendable (..)) where
import Pandora.Core.Functor (type (:.), type (:=))
import Pandora.Core.Morphism ((%))
import Pandora.Pattern.Category (identity, (.))
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
(<<=) = (%) (=>>)
extend :: (t a -> b) -> t a -> t b
extend f t = t =>> f
duplicate :: t a -> t :. t := a
duplicate t = t =>> identity
(=<=) :: (t b -> c) -> (t a -> b) -> t a -> c
f =<= g = f . extend g
(=>=) :: (t a -> b) -> (t b -> c) -> t a -> c
f =>= g = g . extend f