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

Pandora.Pattern.Functor.Pointable

Documentation

class Covariant t => Pointable t where Source #

Minimal complete definition

point

Methods

point :: a :=> t Source #

pass :: t () Source #

Instances

Instances details
Pointable Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Pointable Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

point :: a :=> Maybe Source #

pass :: Maybe () Source #

Pointable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

point :: a :=> Proxy Source #

pass :: Proxy () Source #

(forall (u :: Type -> Type). Avoidable u) => Pointable (Jet t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jet

Methods

point :: a :=> Jet t Source #

pass :: Jet t () Source #

Pointable (Wedge e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wedge

Methods

point :: a :=> Wedge e Source #

pass :: Wedge e () Source #

Pointable (These e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.These

Methods

point :: a :=> These e Source #

pass :: These e () Source #

Pointable (Validation e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Validation

Pointable t => Pointable (Yoneda t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

point :: a :=> Yoneda t Source #

pass :: Yoneda t () Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

point :: a :=> Jack t Source #

pass :: Jack t () Source #

Pointable (Outline t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Outline

Methods

point :: a :=> Outline t Source #

pass :: Outline t () Source #

Avoidable t => Pointable (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

point :: a :=> Tap t Source #

pass :: Tap t () Source #

Covariant t => Pointable (Instruction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Avoidable t => Pointable (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Pointable (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

(Avoidable t, Pointable t) => Pointable (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Pointable (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

point :: a :=> State s Source #

pass :: State s () Source #

Pointable (Environment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Monoid e => Pointable (Accumulator e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Pointable (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

point :: a :=> Tagged tag Source #

pass :: Tagged tag () Source #

Pointable (Schematic Monad t u) => Pointable (t :> u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic

Methods

point :: a :=> (t :> u) Source #

pass :: (t :> u) () Source #

(Pointable t, Pointable u) => Pointable (Day t u) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Day

Methods

point :: a :=> Day t u Source #

pass :: Day t u () Source #

Pointable t => Pointable (Backwards t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Pointable t => Pointable (Reverse t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

point :: a :=> Reverse t Source #

pass :: Reverse t () Source #

Pointable (Schematic Comonad t u) => Pointable (t :< u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Comonadic

Methods

point :: a :=> (t :< u) Source #

pass :: (t :< u) () Source #

(Monoid k, Pointable t) => Pointable (Prefixed t k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Prefixed

Methods

point :: a :=> Prefixed t k Source #

pass :: Prefixed t k () Source #

Pointable ((->) e :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Function

Methods

point :: a :=> (->) e Source #

pass :: e -> () Source #

Covariant t => Pointable (Continuation r t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

(Pointable u, Adjoint t' t) => Pointable ((t <:<.>:> t') := u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

point :: a :=> ((t <:<.>:> t') := u) Source #

pass :: ((t <:<.>:> t') := u) () Source #

(Pointable t, Pointable u) => Pointable (t <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

point :: a :=> (t <.:> u) Source #

pass :: (t <.:> u) () Source #

(Pointable u, Monoid e) => Pointable ((:*:) e <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

point :: a :=> ((:*:) e <.:> u) Source #

pass :: ((:*:) e <.:> u) () Source #

(Pointable t, Pointable u) => Pointable (t <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Methods

point :: a :=> (t <:.> u) Source #

pass :: (t <:.> u) () Source #