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

Pandora.Pattern.Functor.Bivariant

Synopsis

Documentation

class (forall i. Covariant (v i)) => Bivariant (v :: * -> * -> *) where Source #

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

Minimal complete definition

(<->)

Methods

(<->) :: (forall i. Covariant (v i)) => (a -> b) -> (c -> d) -> v a c -> v b d infixl 4 Source #

bimap :: (forall i. Covariant (v i)) => (a -> b) -> (c -> d) -> v a c -> v b d Source #

Prefix version of <->

Instances

Instances details
Bivariant Product Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Product

Methods

(<->) :: (forall i. Covariant (Product i)) => (a -> b) -> (c -> d) -> Product a c -> Product b d Source #

bimap :: (forall i. Covariant (Product i)) => (a -> b) -> (c -> d) -> Product a c -> Product b d Source #

Bivariant Validation Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

(<->) :: (forall i. Covariant (Validation i)) => (a -> b) -> (c -> d) -> Validation a c -> Validation b d Source #

bimap :: (forall i. Covariant (Validation i)) => (a -> b) -> (c -> d) -> Validation a c -> Validation b d Source #

Bivariant Conclusion Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(<->) :: (forall i. Covariant (Conclusion i)) => (a -> b) -> (c -> d) -> Conclusion a c -> Conclusion b d Source #

bimap :: (forall i. Covariant (Conclusion i)) => (a -> b) -> (c -> d) -> Conclusion a c -> Conclusion b d Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

(<->) :: (forall i. Covariant (Tagged i)) => (a -> b) -> (c -> d) -> Tagged a c -> Tagged b d Source #

bimap :: (forall i. Covariant (Tagged i)) => (a -> b) -> (c -> d) -> Tagged a c -> Tagged b d Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Constant

Methods

(<->) :: (forall i. Covariant (Constant i)) => (a -> b) -> (c -> d) -> Constant a c -> Constant b d Source #

bimap :: (forall i. Covariant (Constant i)) => (a -> b) -> (c -> d) -> Constant a c -> Constant b d Source #

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

Methods

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

Instances

Instances details
Bivariant_ Product ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Product

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

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