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

Pandora.Pattern.Functor.Pointable

Documentation

class Covariant_ t source source => Pointable t source where Source #

Methods

point :: source a (t a) Source #

Instances

Instances details
Pointable Identity ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

point :: a -> Identity a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

point :: a -> Maybe a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Jet

Methods

point :: a -> Jet t a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Wedge

Methods

point :: a -> Wedge e a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.These

Methods

point :: a -> These e a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

point :: a -> Proxy a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

point :: a -> Yoneda t a 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 #

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

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

point :: a -> Validation e a Source #

Pointable (Outline t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Outline

Methods

point :: a -> Outline t a Source #

Covariant_ t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Pointable (Instruction t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Instruction

Methods

point :: a -> Instruction t a Source #

(Avoidable t, Covariant_ t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Pointable (Construction t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

point :: a -> Construction t a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

point :: a -> Conclusion e a Source #

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

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Methods

point :: a -> Comprehension t a Source #

(Avoidable t, Covariant_ t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Pointable (Tap t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

point :: a -> Tap t a Source #

Pointable (State s) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

point :: a -> State s a Source #

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

Defined in Pandora.Paradigm.Inventory.Environment

Methods

point :: a -> Environment e a Source #

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

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

point :: a -> Accumulator e a Source #

Pointable (Tagged tag) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

point :: a -> Tagged tag a Source #

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

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

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Day

Methods

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

point :: a -> Backwards t a Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

point :: a -> Reverse t a Source #

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

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

Methods

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

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

Defined in Pandora.Paradigm.Structure.Modification.Prefixed

Methods

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

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

Defined in Pandora.Paradigm.Primary.Functor.Function

Methods

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

Covariant_ t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Pointable (Continuation r t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TU

Methods

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

class Pointable_ t target where Source #

Methods

point_ :: target a (t a) Source #

Instances

Instances details
Pointable_ Identity ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

point_ :: forall (a :: k). a -> Identity a Source #

Pointable_ Maybe ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

point_ :: forall (a :: k). a -> Maybe a Source #

Pointable_ (Wedge e :: Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wedge

Methods

point_ :: forall (a :: k). a -> Wedge e a Source #

Pointable_ (These e :: Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.These

Methods

point_ :: forall (a :: k). a -> These e a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

point_ :: forall (a :: k). a -> Proxy a Source #

Pointable_ (Validation e :: Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Validation

Methods

point_ :: forall (a :: k). a -> Validation e a Source #

(Avoidable t, Covariant_ t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Pointable_ (Construction t :: Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

point_ :: forall (a :: k). a -> Construction t a Source #

Pointable_ (Conclusion e :: Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

point_ :: forall (a :: k). a -> Conclusion e a Source #

Pointable_ (Tagged tag :: Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

point_ :: forall (a :: k). a -> Tagged tag a Source #

Pointable_ t ((->) :: Type -> Type -> Type) => Pointable_ (Backwards t :: Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

point_ :: forall (a :: k). a -> Backwards t a Source #

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

Defined in Pandora.Paradigm.Primary.Functor.Function

Methods

point_ :: forall (a :: k). a -> (e -> a) Source #