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

Pandora.Pattern.Category

Synopsis
  • class Category (m :: * -> * -> *) where
    • identity :: m a a
    • (.) :: m b c -> m a b -> m a c
    • ($) :: m (m a b) (m a b)
    • (#) :: m (m a b) (m a b)

Documentation

class Category (m :: * -> * -> *) where Source #

When providing a new instance, you should ensure it satisfies:
* Left identity: identity . f ≡ f
* Right identity: f . identity ≡ f
* Associativity: f . (g . h) ≡ (f . g) . h

Minimal complete definition

identity, (.)

Methods

identity :: m a a Source #

(.) :: m b c -> m a b -> m a c infixr 9 Source #

($) :: m (m a b) (m a b) infixr 0 Source #

(#) :: m (m a b) (m a b) infixl 2 Source #

Instances

Instances details
Category (Flip ((->) :: Type -> Type -> Type)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Methods

identity :: Flip (->) a a Source #

(.) :: Flip (->) b c -> Flip (->) a b -> Flip (->) a c Source #

($) :: Flip (->) (Flip (->) a b) (Flip (->) a b) Source #

(#) :: Flip (->) (Flip (->) a b) (Flip (->) a b) Source #

Category (Lens Identity) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Category (Lens Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Methods

identity :: Lens Maybe a a Source #

(.) :: Lens Maybe b c -> Lens Maybe a b -> Lens Maybe a c Source #

($) :: Lens Maybe (Lens Maybe a b) (Lens Maybe a b) Source #

(#) :: Lens Maybe (Lens Maybe a b) (Lens Maybe a b) Source #

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

Defined in Pandora.Paradigm.Primary.Algebraic.Exponential

Methods

identity :: a -> a Source #

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

($) :: (a -> b) -> (a -> b) Source #

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