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

Pandora.Paradigm.Primary.Algebraic

Documentation

(!>-) :: Covariant (->) (->) t => t a -> b -> t b Source #

(!!>-) :: (Covariant (->) (->) t, Covariant (->) (->) u) => t (u a) -> b -> t (u b) Source #

(!!!>-) :: (Covariant (->) (->) t, Covariant (->) (->) u, Covariant (->) (->) v) => t (u (v a)) -> b -> t (u (v b)) Source #

(<-*-) :: (Covariant (->) (->) t, Semimonoidal (-->) (:*:) (:*:) t) => t (a -> b) -> t a -> t b infixl 4 Source #

(.-*-) :: (Covariant (->) (->) t, Semimonoidal (-->) (:*:) (:*:) t) => t b -> t a -> t b infixl 4 Source #

(<-*-*-) :: (Covariant (->) (->) t, Covariant (->) (->) u, Semimonoidal (-->) (:*:) (:*:) t, Semimonoidal (-->) (:*:) (:*:) u) => t (u (a -> b)) -> t (u a) -> t (u b) infixl 3 Source #

(.-*-*-) :: (Covariant (->) (->) t, Covariant (->) (->) u, Semimonoidal (-->) (:*:) (:*:) t, Semimonoidal (-->) (:*:) (:*:) u) => t (u b) -> t (u a) -> t (u b) infixl 3 Source #

forever_ :: (Covariant (->) (->) t, Semimonoidal (-->) (:*:) (:*:) t) => t a -> t b Source #

(<-+-) :: (Covariant (->) (->) t, Semimonoidal (-->) (:*:) (:+:) t) => t b -> t a -> ((a :+: b) -> r) -> t r infixl 3 Source #

(-+-) :: (Covariant (->) (->) t, Semimonoidal (-->) (:*:) (:+:) t) => t a -> t a -> t a infixl 3 Source #

void :: Covariant (->) (->) t => t a -> t () Source #

empty :: Emptiable t => t a Source #

point :: Pointable t => a -> t a Source #

pass :: Pointable t => t () Source #

extract :: Extractable t => t a -> a Source #

Orphan instances

Monoidal (-->) (-->) (:*:) (:*:) ((:+:) e) Source # 
Instance details

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) --> (e :+: a) Source #

Monoidal (<--) (-->) (:*:) (:*:) ((:*:) s) Source # 
Instance details

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) <-- (s :*: a) Source #

Monoidal (<--) (-->) (:*:) (:*:) (Flip (:*:) a) Source # 
Instance details

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a0) <-- Flip (:*:) a a0 Source #

Monoidal (-->) (-->) (:*:) (:*:) ((->) e :: Type -> Type) Source # 
Instance details

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) --> (e -> a) Source #

Semimonoidal (-->) (:*:) (:+:) ((:+:) e :: Type -> Type) Source # 
Instance details

Methods

mult :: forall (a :: k) (b :: k). ((e :+: a) :*: (e :+: b)) --> (e :+: (a :+: b)) Source #

Semimonoidal (-->) (:*:) (:*:) ((:+:) e :: Type -> Type) Source # 
Instance details

Methods

mult :: forall (a :: k) (b :: k). ((e :+: a) :*: (e :+: b)) --> (e :+: (a :*: b)) Source #

Semimonoidal (<--) (:*:) (:*:) ((:*:) s :: Type -> Type) Source # 
Instance details

Methods

mult :: forall (a :: k) (b :: k). ((s :*: a) :*: (s :*: b)) <-- (s :*: (a :*: b)) Source #

Semimonoidal (<--) (:*:) (:*:) (Flip (:*:) a :: Type -> Type) Source # 
Instance details

Methods

mult :: forall (a0 :: k) (b :: k). (Flip (:*:) a a0 :*: Flip (:*:) a b) <-- Flip (:*:) a (a0 :*: b) Source #

Semimonoidal (-->) (:*:) (:*:) ((->) e :: Type -> Type) Source # 
Instance details

Methods

mult :: forall (a :: k) (b :: k). ((e -> a) :*: (e -> b)) --> (e -> (a :*: b)) Source #

Semimonoidal (<--) (:*:) (:*:) ((->) e :: Type -> Type) Source # 
Instance details

Methods

mult :: forall (a :: k) (b :: k). ((e -> a) :*: (e -> b)) <-- (e -> (a :*: b)) Source #

Comonad ((->) :: Type -> Type -> Type) ((:*:) s) Source # 
Instance details

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((:*:) s) Source # 
Instance details

Methods

(<<-) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> (s :*: a) -> u (s :*: b) Source #

Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((:*:) s) ((->) s :: Type -> Type) Source # 
Instance details

Methods

(-|) :: ((s :*: a) -> b) -> a -> (s -> b) Source #

(|-) :: (a -> (s -> b)) -> (s :*: a) -> b Source #