pandora-0.4.6: A box of patterns and paradigms
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pandora.Pattern.Functor.Bivariant

Synopsis
  • class (forall i. Covariant left target (v i), forall i. Covariant right target (Flip v i)) => Bivariant left right target v where
    • (<->) :: left a b -> right c d -> target (v a c) (v b d)

Documentation

class (forall i. Covariant left target (v i), forall i. Covariant right target (Flip v i)) => Bivariant left right target v where Source #

When providing a new instance, you should ensure it satisfies:
* Identity: identity <-> identity ≡ identity
* Parametricity: (f . g) <-> (h . i) ≡ f <-> h . g <-> i

Methods

(<->) :: left a b -> right c d -> target (v a c) (v b d) infixl 4 Source #

Instances

Instances details
Bivariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:+:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Sum

Methods

(<->) :: (a -> b) -> (c -> d) -> (a :+: c) -> (b :+: d) Source #

Bivariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

(<->) :: (a -> b) -> (c -> d) -> (a :*: c) -> (b :*: d) Source #

Bivariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Validation Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

(<->) :: (a -> b) -> (c -> d) -> Validation a c -> Validation b d Source #

Bivariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Conclusion Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(<->) :: (a -> b) -> (c -> d) -> Conclusion a c -> Conclusion b d Source #

Bivariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Constant :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Constant

Methods

(<->) :: (a -> b) -> (c -> d) -> Constant a c -> Constant b d Source #

Bivariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

(<->) :: (a -> b) -> (c -> d) -> Tagged a c -> Tagged b d Source #