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

Pandora.Pattern.Functor.Divariant

Synopsis

Documentation

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

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

Minimal complete definition

(>->)

Methods

(>->) :: (a -> b) -> (c -> d) -> v b c -> v a d infixl 4 Source #

dimap :: (a -> b) -> (c -> d) -> v b c -> v a d Source #

Prefix version of >->

Instances

Instances details
Divariant Imprint Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(>->) :: (a -> b) -> (c -> d) -> Imprint b c -> Imprint a d Source #

dimap :: (a -> b) -> (c -> d) -> Imprint b c -> Imprint a d Source #

Divariant Environment Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Methods

(>->) :: (a -> b) -> (c -> d) -> Environment b c -> Environment a d Source #

dimap :: (a -> b) -> (c -> d) -> Environment b c -> Environment a d Source #

Divariant ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Function

Methods

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

dimap :: (a -> b) -> (c -> d) -> (b -> c) -> a -> d Source #

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

Methods

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

Instances

Instances details
Divariant_ ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Function

Methods

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