Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Pandora.Pattern.Functor.Bindable
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 # | |
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 # | |
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 (Proxy :: Type -> Type) Source # | |
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 # | |
Bindable (Environment e) Source # | |
Defined in Pandora.Paradigm.Inventory.Environment Methods (>>=) :: Environment e a -> (a -> Environment e b) -> Environment e b Source # (=<<) :: (a -> Environment e b) -> Environment e a -> Environment e b Source # bind :: (a -> Environment e b) -> Environment e a -> Environment e b Source # join :: ((Environment e :. Environment e) := a) -> Environment e a Source # (>=>) :: (a -> Environment e b) -> (b -> Environment e c) -> a -> Environment e c Source # (<=<) :: (b -> Environment e c) -> (a -> Environment e b) -> a -> Environment e c Source # | |
Covariant t => Bindable (Free t) Source # | |
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 # | |
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 # | |
Semigroup e => Bindable (Accumulator e) Source # | |
Defined in Pandora.Paradigm.Inventory.Accumulator Methods (>>=) :: Accumulator e a -> (a -> Accumulator e b) -> Accumulator e b Source # (=<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # bind :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source # join :: ((Accumulator e :. Accumulator e) := a) -> Accumulator e a Source # (>=>) :: (a -> Accumulator e b) -> (b -> Accumulator e c) -> a -> Accumulator e c Source # (<=<) :: (b -> Accumulator e c) -> (a -> Accumulator e b) -> a -> Accumulator e c Source # | |
Bindable (State s) Source # | |
Defined in Pandora.Paradigm.Inventory.State Methods (>>=) :: State s a -> (a -> State s b) -> State s b Source # (=<<) :: (a -> State s b) -> State s a -> State s b Source # bind :: (a -> State s b) -> State s a -> State s b Source # join :: ((State s :. State s) := a) -> State s a Source # (>=>) :: (a -> State s b) -> (b -> State s c) -> a -> State s c Source # (<=<) :: (b -> State s c) -> (a -> State s b) -> a -> State s c Source # | |
Bindable (Conclusion e) Source # | |
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 (Schema t u) => Bindable (t :> u) Source # | |
Defined in Pandora.Paradigm.Controlflow.Joint.Transformer Methods (>>=) :: (t :> u) a -> (a -> (t :> u) b) -> (t :> u) b Source # (=<<) :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # bind :: (a -> (t :> u) b) -> (t :> u) a -> (t :> u) b Source # join :: (((t :> u) :. (t :> u)) := a) -> (t :> u) a Source # (>=>) :: (a -> (t :> u) b) -> (b -> (t :> u) c) -> a -> (t :> u) c Source # (<=<) :: (b -> (t :> u) c) -> (a -> (t :> u) b) -> a -> (t :> u) c Source # | |
Bindable (Tagged tag) Source # | |
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 # | |
Bindable ((->) e :: Type -> Type) Source # | |
Defined in Pandora.Pattern.Functor.Bindable Methods (>>=) :: (e -> a) -> (a -> e -> b) -> e -> b Source # (=<<) :: (a -> e -> b) -> (e -> a) -> e -> b Source # bind :: (a -> e -> b) -> (e -> a) -> e -> b Source # join :: (((->) e :. (->) e) := a) -> e -> a Source # (>=>) :: (a -> e -> b) -> (b -> e -> c) -> a -> e -> c Source # (<=<) :: (b -> e -> c) -> (a -> e -> b) -> a -> e -> c Source # | |
Covariant t => Bindable (Continuation r t) Source # | |
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 # | |
Bindable u => Bindable (TU Co Co ((->) e :: Type -> Type) u) Source # | |
Defined in Pandora.Paradigm.Inventory.Environment Methods (>>=) :: TU Co Co ((->) e) u a -> (a -> TU Co Co ((->) e) u b) -> TU Co Co ((->) e) u b Source # (=<<) :: (a -> TU Co Co ((->) e) u b) -> TU Co Co ((->) e) u a -> TU Co Co ((->) e) u b Source # bind :: (a -> TU Co Co ((->) e) u b) -> TU Co Co ((->) e) u a -> TU Co Co ((->) e) u b Source # join :: ((TU Co Co ((->) e) u :. TU Co Co ((->) e) u) := a) -> TU Co Co ((->) e) u a Source # (>=>) :: (a -> TU Co Co ((->) e) u b) -> (b -> TU Co Co ((->) e) u c) -> a -> TU Co Co ((->) e) u c Source # (<=<) :: (b -> TU Co Co ((->) e) u c) -> (a -> TU Co Co ((->) e) u b) -> a -> TU Co Co ((->) e) u c Source # | |
(Semigroup e, Pointable u, Bindable u) => Bindable (UT Co Co ((:*:) e) u) Source # | |
Defined in Pandora.Paradigm.Inventory.Accumulator Methods (>>=) :: UT Co Co ((:*:) e) u a -> (a -> UT Co Co ((:*:) e) u b) -> UT Co Co ((:*:) e) u b Source # (=<<) :: (a -> UT Co Co ((:*:) e) u b) -> UT Co Co ((:*:) e) u a -> UT Co Co ((:*:) e) u b Source # bind :: (a -> UT Co Co ((:*:) e) u b) -> UT Co Co ((:*:) e) u a -> UT Co Co ((:*:) e) u b Source # join :: ((UT Co Co ((:*:) e) u :. UT Co Co ((:*:) e) u) := a) -> UT Co Co ((:*:) e) u a Source # (>=>) :: (a -> UT Co Co ((:*:) e) u b) -> (b -> UT Co Co ((:*:) e) u c) -> a -> UT Co Co ((:*:) e) u c Source # (<=<) :: (b -> UT Co Co ((:*:) e) u c) -> (a -> UT Co Co ((:*:) e) u b) -> a -> UT Co Co ((:*:) e) u c Source # | |
(Pointable u, Bindable u) => Bindable (UT Co Co Maybe u) Source # | |
Defined in Pandora.Paradigm.Basis.Maybe Methods (>>=) :: UT Co Co Maybe u a -> (a -> UT Co Co Maybe u b) -> UT Co Co Maybe u b Source # (=<<) :: (a -> UT Co Co Maybe u b) -> UT Co Co Maybe u a -> UT Co Co Maybe u b Source # bind :: (a -> UT Co Co Maybe u b) -> UT Co Co Maybe u a -> UT Co Co Maybe u b Source # join :: ((UT Co Co Maybe u :. UT Co Co Maybe u) := a) -> UT Co Co Maybe u a Source # (>=>) :: (a -> UT Co Co Maybe u b) -> (b -> UT Co Co Maybe u c) -> a -> UT Co Co Maybe u c Source # (<=<) :: (b -> UT Co Co Maybe u c) -> (a -> UT Co Co Maybe u b) -> a -> UT Co Co Maybe u c Source # | |
(Pointable u, Bindable u) => Bindable (UT Co Co (Conclusion e) u) Source # | |
Defined in Pandora.Paradigm.Basis.Conclusion Methods (>>=) :: UT Co Co (Conclusion e) u a -> (a -> UT Co Co (Conclusion e) u b) -> UT Co Co (Conclusion e) u b Source # (=<<) :: (a -> UT Co Co (Conclusion e) u b) -> UT Co Co (Conclusion e) u a -> UT Co Co (Conclusion e) u b Source # bind :: (a -> UT Co Co (Conclusion e) u b) -> UT Co Co (Conclusion e) u a -> UT Co Co (Conclusion e) u b Source # join :: ((UT Co Co (Conclusion e) u :. UT Co Co (Conclusion e) u) := a) -> UT Co Co (Conclusion e) u a Source # (>=>) :: (a -> UT Co Co (Conclusion e) u b) -> (b -> UT Co Co (Conclusion e) u c) -> a -> UT Co Co (Conclusion e) u c Source # (<=<) :: (b -> UT Co Co (Conclusion e) u c) -> (a -> UT Co Co (Conclusion e) u b) -> a -> UT Co Co (Conclusion e) u c Source # | |
Bindable u => Bindable (TUV Co Co Co ((->) s :: Type -> Type) u ((:*:) s)) Source # | |
Defined in Pandora.Paradigm.Inventory.State Methods (>>=) :: TUV Co Co Co ((->) s) u ((:*:) s) a -> (a -> TUV Co Co Co ((->) s) u ((:*:) s) b) -> TUV Co Co Co ((->) s) u ((:*:) s) b Source # (=<<) :: (a -> TUV Co Co Co ((->) s) u ((:*:) s) b) -> TUV Co Co Co ((->) s) u ((:*:) s) a -> TUV Co Co Co ((->) s) u ((:*:) s) b Source # bind :: (a -> TUV Co Co Co ((->) s) u ((:*:) s) b) -> TUV Co Co Co ((->) s) u ((:*:) s) a -> TUV Co Co Co ((->) s) u ((:*:) s) b Source # join :: ((TUV Co Co Co ((->) s) u ((:*:) s) :. TUV Co Co Co ((->) s) u ((:*:) s)) := a) -> TUV Co Co Co ((->) s) u ((:*:) s) a Source # (>=>) :: (a -> TUV Co Co Co ((->) s) u ((:*:) s) b) -> (b -> TUV Co Co Co ((->) s) u ((:*:) s) c) -> a -> TUV Co Co Co ((->) s) u ((:*:) s) c Source # (<=<) :: (b -> TUV Co Co Co ((->) s) u ((:*:) s) c) -> (a -> TUV Co Co Co ((->) s) u ((:*:) s) b) -> a -> TUV Co Co Co ((->) s) u ((:*:) s) c Source # |