pandora-0.2.8: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Pattern.Functor.Pointable

Documentation

class Covariant t => Pointable t where Source #

Methods

point :: a |-> t Source #

Instances
Pointable Delta Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Delta

Methods

point :: a |-> Delta Source #

Pointable Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

point :: a |-> Identity Source #

Pointable Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

point :: a |-> Maybe Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

point :: a |-> Proxy Source #

Pointable (Wedge e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wedge

Methods

point :: a |-> Wedge e Source #

Pointable (These e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.These

Methods

point :: a |-> These e 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 #

Pointable (Validation e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

point :: a |-> Validation e Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

point :: a |-> Yoneda t Source #

Pointable (Outline t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Outline

Methods

point :: a |-> Outline t Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

point :: a |-> Jack t Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

point :: a |-> Instruction t Source #

Pointable (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

point :: a |-> Conclusion e Source #

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

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

point :: a |-> Accumulator e Source #

Pointable (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

point :: a |-> State s Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

point :: a |-> Construction t Source #

Pointable (Environment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Methods

point :: a |-> Environment e Source #

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

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

Methods

point :: a |-> (t :> u) Source #

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

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

Methods

point :: a |-> (t :< u) Source #

Pointable (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

point :: a |-> Tagged tag Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

point :: a |-> Backwards t Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

point :: a |-> Reverse t Source #

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

Defined in Pandora.Pattern.Functor.Pointable

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Methods

point :: a |-> Continuation r t Source #

(Pointable u, Monoid e) => Pointable (UT Covariant Covariant ((:*:) e) u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Pointable u => Pointable (UT Covariant Covariant Maybe u) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Pointable u => Pointable (UT Covariant Covariant (Conclusion e) u) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

(Covariant u, Pointable u) => Pointable (TU Covariant Covariant ((->) e :: Type -> Type) u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Methods

point :: a |-> TU Covariant Covariant ((->) e) u Source #

(Avoidable t, Pointable u) => Pointable (TU Covariant Covariant u (Construction t)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Pointable u => Pointable (TUT Covariant Covariant Covariant ((->) s :: Type -> Type) ((:*:) s) u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

point :: a |-> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u Source #