do-notation-0.1.0.1: Generalize do-notation to work on monads and indexed monads simultaneously.

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.DoNotation

Description

This module provides new implementations for '(>>=)', '(>>)', pure and return so that they will work simultaneously with both regular and indexed monads.

Intended usage:

@@ {--}

import Language.Haskell.DoNotation import Prelude hiding (Monad (..), pure) @@

Synopsis

Documentation

class BindSyntax (x :: Type -> Type) (y :: Type -> Type) (z :: Type -> Type) | x y -> z, x z -> y, y z -> x where Source #

Typeclass that provides '(>>=)' and '(>>)'.

Minimal complete definition

(>>=)

Methods

(>>=) :: x a -> (a -> y b) -> z b Source #

(>>) :: x a -> y b -> z b Source #

Instances
(IxMonad m, x ~ m i j, y ~ m j k2, z ~ m i k2) => BindSyntax x y z Source # 
Instance details

Defined in Language.Haskell.DoNotation

Methods

(>>=) :: x a -> (a -> y b) -> z b Source #

(>>) :: x a -> y b -> z b Source #

(Monad m, x ~ m) => BindSyntax m x m Source # 
Instance details

Defined in Language.Haskell.DoNotation

Methods

(>>=) :: m a -> (a -> x b) -> m b Source #

(>>) :: m a -> x b -> m b Source #

class PureSyntax (x :: Type -> Type) where Source #

Typeclass that provides pure and return.

Methods

pure :: a -> x a Source #

return :: a -> x a Source #

Instances
Monad m => PureSyntax m Source # 
Instance details

Defined in Language.Haskell.DoNotation

Methods

pure :: a -> m a Source #

return :: a -> m a Source #

(IxMonad m, j ~ i) => PureSyntax (m i j) Source # 
Instance details

Defined in Language.Haskell.DoNotation

Methods

pure :: a -> m i j a Source #

return :: a -> m i j a Source #

class Applicative m => Monad (m :: * -> *) #

The Monad class defines the basic operations over a monad, a concept from a branch of mathematics known as category theory. From the perspective of a Haskell programmer, however, it is best to think of a monad as an abstract datatype of actions. Haskell's do expressions provide a convenient syntax for writing monadic expressions.

Instances of Monad should satisfy the following laws:

Furthermore, the Monad and Applicative operations should relate as follows:

The above laws imply:

and that pure and (<*>) satisfy the applicative functor laws.

The instances of Monad for lists, Maybe and IO defined in the Prelude satisfy these laws.

Minimal complete definition

(>>=)

Instances
Monad []

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

(>>=) :: [a] -> (a -> [b]) -> [b] #

(>>) :: [a] -> [b] -> [b] #

return :: a -> [a] #

fail :: String -> [a] #

Monad Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

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

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

return :: a -> Maybe a #

fail :: String -> Maybe a #

Monad IO

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

(>>=) :: IO a -> (a -> IO b) -> IO b #

(>>) :: IO a -> IO b -> IO b #

return :: a -> IO a #

fail :: String -> IO a #

Monad ReadP

Since: base-2.1

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

(>>=) :: ReadP a -> (a -> ReadP b) -> ReadP b #

(>>) :: ReadP a -> ReadP b -> ReadP b #

return :: a -> ReadP a #

fail :: String -> ReadP a #

Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

fail :: String -> NonEmpty a #

Monad P

Since: base-2.1

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

(>>=) :: P a -> (a -> P b) -> P b #

(>>) :: P a -> P b -> P b #

return :: a -> P a #

fail :: String -> P a #

Monad (Either e)

Since: base-4.4.0.0

Instance details

Defined in Data.Either

Methods

(>>=) :: Either e a -> (a -> Either e b) -> Either e b #

(>>) :: Either e a -> Either e b -> Either e b #

return :: a -> Either e a #

fail :: String -> Either e a #

Monoid a => Monad ((,) a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: (a, a0) -> (a0 -> (a, b)) -> (a, b) #

(>>) :: (a, a0) -> (a, b) -> (a, b) #

return :: a0 -> (a, a0) #

fail :: String -> (a, a0) #

Monad ((->) r :: * -> *)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

(>>=) :: (r -> a) -> (a -> r -> b) -> r -> b #

(>>) :: (r -> a) -> (r -> b) -> r -> b #

return :: a -> r -> a #

fail :: String -> r -> a #

Monad m => Monad (Ix m i j) # 
Instance details

Defined in Control.Monad.Trans.Ix

Methods

(>>=) :: Ix m i j a -> (a -> Ix m i j b) -> Ix m i j b #

(>>) :: Ix m i j a -> Ix m i j b -> Ix m i j b #

return :: a -> Ix m i j a #

fail :: String -> Ix m i j a #

class IxApplicative m => IxMonad (m :: k -> k -> * -> *) #

Minimal complete definition

ibind

Instances
Monad m => IxMonad (Ix m :: k -> k -> Type -> *) # 
Instance details

Defined in Control.Monad.Trans.Ix

Methods

ibind :: (a -> Ix m j k1 b) -> Ix m i j a -> Ix m i k1 b #