pandora-0.1.9: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Pattern.Functor.Bindable

Synopsis
  • class Covariant t => Bindable t where
    • (>>=) :: t a -> (a -> t b) -> t b
    • (=<<) :: (a -> t b) -> t a -> t b
    • bind :: (a -> t b) -> t a -> t b
    • join :: ((t :.: t) >< a) -> t a
    • (>=>) :: (a -> t b) -> (b -> t c) -> a -> t c
    • (<=<) :: (b -> t c) -> (a -> t b) -> a -> t c

Documentation

class Covariant t => Bindable t where Source #

When providing a new instance, you should ensure it satisfies the one law:
* Interchange: t >>= f = join (f <$> t)

Minimal complete definition

(>>=)

Methods

(>>=) :: t a -> (a -> t b) -> t b infixl 1 Source #

Infix and flipped version of bind, the dual of =>>

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

Flipped version of >>=, the dual of <<=

bind :: (a -> t b) -> t a -> t b Source #

Prefix and flipped version of >>=, the dual of extend

join :: ((t :.: t) >< a) -> t a Source #

Merge effects/contexts, the dual of duplicate

(>=>) :: (a -> t b) -> (b -> t c) -> a -> t c infixr 1 Source #

Left-to-right Kleisli composition

(<=<) :: (b -> t c) -> (a -> t b) -> a -> t c infixr 1 Source #

Right-to-left Kleisli composition

Instances
Bindable Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Maybe

Methods

(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b Source #

(=<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source #

bind :: (a -> Maybe b) -> Maybe a -> Maybe b Source #

join :: ((Maybe :.: Maybe) >< a) -> Maybe a Source #

(>=>) :: (a -> Maybe b) -> (b -> Maybe c) -> a -> Maybe c Source #

(<=<) :: (b -> Maybe c) -> (a -> Maybe b) -> a -> Maybe c Source #

Bindable Identity Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Identity

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b Source #

(=<<) :: (a -> Identity b) -> Identity a -> Identity b Source #

bind :: (a -> Identity b) -> Identity a -> Identity b Source #

join :: ((Identity :.: Identity) >< a) -> Identity a Source #

(>=>) :: (a -> Identity b) -> (b -> Identity c) -> a -> Identity c Source #

(<=<) :: (b -> Identity c) -> (a -> Identity b) -> a -> Identity c Source #

Bindable (Environmental e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environmental

Methods

(>>=) :: Environmental e a -> (a -> Environmental e b) -> Environmental e b Source #

(=<<) :: (a -> Environmental e b) -> Environmental e a -> Environmental e b Source #

bind :: (a -> Environmental e b) -> Environmental e a -> Environmental e b Source #

join :: ((Environmental e :.: Environmental e) >< a) -> Environmental e a Source #

(>=>) :: (a -> Environmental e b) -> (b -> Environmental e c) -> a -> Environmental e c Source #

(<=<) :: (b -> Environmental e c) -> (a -> Environmental e b) -> a -> Environmental e c Source #

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

Defined in Pandora.Paradigm.Basis.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b Source #

(=<<) :: (a -> Proxy b) -> Proxy a -> Proxy b Source #

bind :: (a -> Proxy b) -> Proxy a -> Proxy b Source #

join :: ((Proxy :.: Proxy) >< a) -> Proxy a Source #

(>=>) :: (a -> Proxy b) -> (b -> Proxy c) -> a -> Proxy c Source #

(<=<) :: (b -> Proxy c) -> (a -> Proxy b) -> a -> Proxy c Source #

Covariant t => Bindable (Free t) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Free

Methods

(>>=) :: Free t a -> (a -> Free t b) -> Free t b Source #

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

bind :: (a -> Free t b) -> Free t a -> Free t b Source #

join :: ((Free t :.: Free t) >< a) -> Free t a Source #

(>=>) :: (a -> Free t b) -> (b -> Free t c) -> a -> Free t c Source #

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

Alternative t => Bindable (Twister t) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Twister

Methods

(>>=) :: Twister t a -> (a -> Twister t b) -> Twister t b Source #

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

bind :: (a -> Twister t b) -> Twister t a -> Twister t b Source #

join :: ((Twister t :.: Twister t) >< a) -> Twister t a Source #

(>=>) :: (a -> Twister t b) -> (b -> Twister t c) -> a -> Twister t c Source #

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

Bindable (Stateful s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Stateful

Methods

(>>=) :: Stateful s a -> (a -> Stateful s b) -> Stateful s b Source #

(=<<) :: (a -> Stateful s b) -> Stateful s a -> Stateful s b Source #

bind :: (a -> Stateful s b) -> Stateful s a -> Stateful s b Source #

join :: ((Stateful s :.: Stateful s) >< a) -> Stateful s a Source #

(>=>) :: (a -> Stateful s b) -> (b -> Stateful s c) -> a -> Stateful s c Source #

(<=<) :: (b -> Stateful s c) -> (a -> Stateful s b) -> a -> Stateful s c Source #

Bindable (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Conclusion

Methods

(>>=) :: Conclusion e a -> (a -> Conclusion e b) -> Conclusion e b Source #

(=<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source #

bind :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source #

join :: ((Conclusion e :.: Conclusion e) >< a) -> Conclusion e a Source #

(>=>) :: (a -> Conclusion e b) -> (b -> Conclusion e c) -> a -> Conclusion e c Source #

(<=<) :: (b -> Conclusion e c) -> (a -> Conclusion e b) -> a -> Conclusion e c Source #

Bindable (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Basis.Tagged

Methods

(>>=) :: Tagged tag a -> (a -> Tagged tag b) -> Tagged tag b Source #

(=<<) :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source #

bind :: (a -> Tagged tag b) -> Tagged tag a -> Tagged tag b Source #

join :: ((Tagged tag :.: Tagged tag) >< a) -> Tagged tag a Source #

(>=>) :: (a -> Tagged tag b) -> (b -> Tagged tag c) -> a -> Tagged tag c Source #

(<=<) :: (b -> Tagged tag c) -> (a -> Tagged tag b) -> a -> Tagged tag c Source #

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

Defined in Pandora.Paradigm.Basis.Continuation

Methods

(>>=) :: Continuation r t a -> (a -> Continuation r t b) -> Continuation r t b Source #

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

bind :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source #

join :: ((Continuation r t :.: Continuation r t) >< a) -> Continuation r t a Source #

(>=>) :: (a -> Continuation r t b) -> (b -> Continuation r t c) -> a -> Continuation r t c Source #

(<=<) :: (b -> Continuation r t c) -> (a -> Continuation r t b) -> a -> Continuation r t c Source #

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

Defined in Pandora.Paradigm.Basis.Maybe

Methods

(>>=) :: UT Maybe () Maybe u a -> (a -> UT Maybe () Maybe u b) -> UT Maybe () Maybe u b Source #

(=<<) :: (a -> UT Maybe () Maybe u b) -> UT Maybe () Maybe u a -> UT Maybe () Maybe u b Source #

bind :: (a -> UT Maybe () Maybe u b) -> UT Maybe () Maybe u a -> UT Maybe () Maybe u b Source #

join :: ((UT Maybe () Maybe u :.: UT Maybe () Maybe u) >< a) -> UT Maybe () Maybe u a Source #

(>=>) :: (a -> UT Maybe () Maybe u b) -> (b -> UT Maybe () Maybe u c) -> a -> UT Maybe () Maybe u c Source #

(<=<) :: (b -> UT Maybe () Maybe u c) -> (a -> UT Maybe () Maybe u b) -> a -> UT Maybe () Maybe u c Source #

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

Defined in Pandora.Paradigm.Basis.Conclusion

Methods

(>>=) :: UT (Conclusion e) () (Conclusion e) u a -> (a -> UT (Conclusion e) () (Conclusion e) u b) -> UT (Conclusion e) () (Conclusion e) u b Source #

(=<<) :: (a -> UT (Conclusion e) () (Conclusion e) u b) -> UT (Conclusion e) () (Conclusion e) u a -> UT (Conclusion e) () (Conclusion e) u b Source #

bind :: (a -> UT (Conclusion e) () (Conclusion e) u b) -> UT (Conclusion e) () (Conclusion e) u a -> UT (Conclusion e) () (Conclusion e) u b Source #

join :: ((UT (Conclusion e) () (Conclusion e) u :.: UT (Conclusion e) () (Conclusion e) u) >< a) -> UT (Conclusion e) () (Conclusion e) u a Source #

(>=>) :: (a -> UT (Conclusion e) () (Conclusion e) u b) -> (b -> UT (Conclusion e) () (Conclusion e) u c) -> a -> UT (Conclusion e) () (Conclusion e) u c Source #

(<=<) :: (b -> UT (Conclusion e) () (Conclusion e) u c) -> (a -> UT (Conclusion e) () (Conclusion e) u b) -> a -> UT (Conclusion e) () (Conclusion e) u c Source #

Bindable u => Bindable (TUV Stateful () Stateful ((->) s :: Type -> Type) u ((:*:) s)) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Stateful

Methods

(>>=) :: TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> (a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b) -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

(=<<) :: (a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b) -> TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

bind :: (a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b) -> TUV Stateful () Stateful ((->) s) u ((:*:) s) a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b Source #

join :: ((TUV Stateful () Stateful ((->) s) u ((:*:) s) :.: TUV Stateful () Stateful ((->) s) u ((:*:) s)) >< a) -> TUV Stateful () Stateful ((->) s) u ((:*:) s) a Source #

(>=>) :: (a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b) -> (b -> TUV Stateful () Stateful ((->) s) u ((:*:) s) c) -> a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) c Source #

(<=<) :: (b -> TUV Stateful () Stateful ((->) s) u ((:*:) s) c) -> (a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) b) -> a -> TUV Stateful () Stateful ((->) s) u ((:*:) s) c Source #