module Pandora.Paradigm.Primary.Functor.Proxy where import Pandora.Pattern.Functor.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) 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 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 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 u a _ >>- :: u a -> (a -> Proxy b) -> (Proxy :. u) := b >>- a -> Proxy b _ = (Proxy :. u) := b forall k (a :: k). Proxy a Proxy instance Bindable Proxy where Proxy a _ >>= :: Proxy a -> (a -> Proxy b) -> Proxy b >>= a -> Proxy b _ = Proxy b forall k (a :: k). Proxy a Proxy instance Monad Proxy instance Extendable Proxy where Proxy a _ =>> :: Proxy a -> (Proxy a -> b) -> Proxy b =>> Proxy a -> b _ = Proxy b forall k (a :: k). Proxy a Proxy