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

Pandora.Pattern.Functor.Monad

Synopsis

Documentation

class (Pointable t, Bindable t) => Monad t where Source #

Let f :: (Pointable t, Bindable t) => a -> t a
Let g :: (Pointable t, Bindable t) => a -> t a
Let h :: (Pointable t, Bindable t) => t a
When providing a new instance, you should ensure it satisfies:
* Left identity: point a >>= f ≡ f a
* Right identity: h >>= point ≡ h
* Associativity: h >>= (f >=> g) ≡ (h >>= f) >>= g

Minimal complete definition

Nothing

Methods

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

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

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

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

Instances

Instances details
Monad Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Monad Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

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

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

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

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

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

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

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

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

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

(Avoidable t, Alternative t) => Monad (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Monad (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

(forall a. Semigroup ((t <:.> Construction t) := a), Pointable t, Avoidable t, Bindable t) => Monad (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Monad (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

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

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

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

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

Monad (Environment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Monad (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

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

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

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

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

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

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

Methods

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

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

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

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

Monad t => Monad (Continuation r t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Methods

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

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

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

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

type Schematic Monad Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

type Schematic Monad (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

type Schematic Monad (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

type Schematic Monad (State s) = ((->) s :: Type -> Type) <:<.>:> (:*:) s
type Schematic Monad (Environment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

type Schematic Monad (Environment e) = (<:.>) ((->) e :: Type -> Type)
type Schematic Monad (Accumulator e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator