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

Pandora.Paradigm.Primary.Transformer.Jack

Documentation

data Jack t a Source #

Constructors

It a 
Other (t a) 

Instances

Instances details
Liftable Jack Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

lift :: forall (u :: Type -> Type). Covariant u (->) (->) => u ~> Jack u Source #

Hoistable Jack Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

(/|\) :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant u (->) (->) => (u ~> v) -> Jack u ~> Jack v Source #

hoist :: forall (u :: Type -> Type) (v :: Type -> Type). Covariant u (->) (->) => (u ~> v) -> Jack u ~> Jack v Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Pointable (Jack t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

point :: a -> Jack t a Source #

Extractable t ((->) :: Type -> Type -> Type) => Extractable (Jack t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

extract :: Jack t a -> a Source #

Extendable t ((->) :: Type -> Type -> Type) => Extendable (Jack t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

(<<=) :: (Jack t a -> b) -> Jack t a -> Jack t b Source #

(Pointable t ((->) :: Type -> Type -> Type), Bindable t ((->) :: Type -> Type -> Type)) => Bindable (Jack t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

(=<<) :: (a -> Jack t b) -> Jack t a -> Jack t b Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Jack t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

(-<$>-) :: (a -> b) -> Jack t a -> Jack t b Source #

Traversable t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Traversable (Jack t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

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

(Setoid a, Setoid (t a)) => Setoid (Jack t a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

(==) :: Jack t a -> Jack t a -> Boolean Source #

(!=) :: Jack t a -> Jack t a -> Boolean Source #

(Chain a, Chain (t a)) => Chain (Jack t a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

(<=>) :: Jack t a -> Jack t a -> Ordering Source #

(<) :: Jack t a -> Jack t a -> Boolean Source #

(<=) :: Jack t a -> Jack t a -> Boolean Source #

(>) :: Jack t a -> Jack t a -> Boolean Source #

(>=) :: Jack t a -> Jack t a -> Boolean Source #

jack :: (a -> r) -> (t a -> r) -> Jack t a -> r Source #