module Pandora.Paradigm.Primary.Functor.Proxy where

import Pandora.Pattern.Functor.Covariant (Covariant ((<$>)), Covariant_ ((-<$>-)))
import Pandora.Pattern.Functor.Contravariant (Contravariant ((>$<)))
import Pandora.Pattern.Functor.Pointable (Pointable (point))
import Pandora.Pattern.Functor.Applicative (Applicative ((<*>)))
import Pandora.Pattern.Functor.Alternative (Alternative ((<+>)))
import Pandora.Pattern.Functor.Distributive (Distributive ((-<<)))
import Pandora.Pattern.Functor.Bindable (Bindable ((=<<)))
import Pandora.Pattern.Functor.Extendable (Extendable ((<<=)))
import Pandora.Pattern.Functor.Monad (Monad)
import Pandora.Paradigm.Primary.Algebraic.Exponential ()

data Proxy a = Proxy

instance Covariant Proxy where
	a -> b
_ <$> :: (a -> b) -> Proxy a -> Proxy b
<$> Proxy a
Proxy = Proxy b
forall k (a :: k). Proxy a
Proxy

instance Covariant_ Proxy (->) (->) where
	a -> b
_ -<$>- :: (a -> b) -> Proxy a -> Proxy b
-<$>- Proxy a
Proxy = Proxy b
forall k (a :: k). Proxy a
Proxy

instance Contravariant Proxy where
	a -> b
_ >$< :: (a -> b) -> Proxy b -> Proxy a
>$< Proxy b
_ = Proxy a
forall k (a :: k). Proxy a
Proxy

instance Pointable Proxy (->) where
	point :: a -> Proxy a
point a
_ = Proxy a
forall k (a :: k). Proxy a
Proxy

instance Applicative Proxy where
	Proxy (a -> b)
_ <*> :: Proxy (a -> b) -> Proxy a -> Proxy b
<*> Proxy a
_ = Proxy b
forall k (a :: k). Proxy a
Proxy

instance Alternative Proxy where
	Proxy a
_ <+> :: Proxy a -> Proxy a -> Proxy a
<+> Proxy a
_ = Proxy a
forall k (a :: k). Proxy a
Proxy

instance Distributive Proxy (->) (->) where
	a -> Proxy b
_ -<< :: (a -> Proxy b) -> u a -> Proxy (u b)
-<< u a
_ = Proxy (u b)
forall k (a :: k). Proxy a
Proxy

instance Bindable Proxy (->) where
	a -> Proxy b
_ =<< :: (a -> Proxy b) -> Proxy a -> Proxy b
=<< Proxy a
_ = Proxy b
forall k (a :: k). Proxy a
Proxy

instance Monad Proxy

instance Extendable Proxy (->) where
	Proxy a -> b
_ <<= :: (Proxy a -> b) -> Proxy a -> Proxy b
<<= Proxy a
_ = Proxy b
forall k (a :: k). Proxy a
Proxy