module Control.Functor.Composition.Extendable (Extendable (..)) where

import "morphisms" Control.Morphism (flip, identity)

import Control.Functor.Composition ((:.:))
import Control.Functor.Covariant (Covariant)

infixl 1 =>>
infixr 1 <<=

{- |
> When providing a new instance, you should ensure it satisfies the three laws:
> * Duplication interchange: comap (comap f) . duplicate ≡ duplicate . comap f
> * Extension interchange: extend f ≡ comap f . duplicate
-}

class Covariant t => Extendable t where
        {-# MINIMAL (=>>) #-}
        -- | Infix and flipped version of 'extend', the dual of '>>='
        (=>>) :: t a -> (t a -> b) -> t b

        -- | Flipped version of '>>=', the dual of '=<<'
        (<<=) :: (t a -> b) -> t a -> t b
        (<<=) = flip (=>>)
        -- | Prefix and flipped version of '=>>', the dual of 'bind'
        extend :: (t a -> b) -> t a -> t b
        extend f t = t =>> f
        -- | Clone existing structure, the dual of 'join'
        duplicate :: t a -> (t :.: t) a
        duplicate t = t =>> identity