module Pandora.Pattern.Transformer.Hoistable (Hoistable (..)) where

import Pandora.Core.Functor (type (~>))
import Pandora.Pattern.Functor.Covariant (Covariant)

{- |
> When providing a new instance, you should ensure it satisfies one law:
> * Identity morphism: hoist identity ≡ identity
> * Interpreted of morphisms: hoist (f . g) ≡ hoist f . hoist g
-}

infixr 5 /|\

class Hoistable t where
	{-# MINIMAL (/|\) #-}
	(/|\) :: (Covariant (->) (->) u) => u ~> v -> t u ~> t v

	hoist :: (Covariant (->) (->) u) => u ~> v -> t u ~> t v
	hoist = (u ~> v) -> t u a -> t v a
forall k (t :: (* -> *) -> k -> *) (u :: * -> *) (v :: * -> *).
(Hoistable t, Covariant (->) (->) u) =>
(u ~> v) -> t u ~> t v
(/|\)