stacked-0.1.0: A modern indexed monad stack
Safe HaskellNone
LanguageGHC2021

Control.Monad.Indexed

Description

This module defines the main indexed monad hierarchy and some standard indexed monad combinators. This is meant to look familiar to Haskell programmers. Notice how there is no indexed functor class as, thanks to quantified constraints, this role is played by the Prelude's Functor class. Notice also how some traditional classes like MonadPlus and Alternative are synonyms thanks to the Additive type class.

Synopsis

Indexed monad hierarchy

class (forall (i :: k) (j :: k). Functor (f i j), forall (i :: k). Applicative (f i i)) => Applicative (f :: k -> k -> Type -> Type) where Source #

Minimal complete definition

pure

Methods

pure :: forall a (i :: k). a -> f i i a Source #

(<*>) :: forall (i :: k) (j :: k) a b (k1 :: k). f i j (a -> b) -> f j k1 a -> f i k1 b infixl 4 Source #

default (<*>) :: forall (i :: k) (j :: k) a b (k1 :: k). Monad f => f i j (a -> b) -> f j k1 a -> f i k1 b Source #

liftA2 :: forall a b c (i :: k) (j :: k) (k1 :: k). (a -> b -> c) -> f i j a -> f j k1 b -> f i k1 c Source #

(*>) :: forall (i :: k) (j :: k) a (k1 :: k) b. f i j a -> f j k1 b -> f i k1 b infixl 4 Source #

(<*) :: forall (i :: k) (j :: k) a (k1 :: k) b. f i j a -> f j k1 b -> f i k1 a infixl 4 Source #

Instances

Instances details
Comonad w => Applicative (ContW w :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont

Methods

pure :: a -> ContW w i i a Source #

(<*>) :: ContW w i j (a -> b) -> ContW w j k1 a -> ContW w i k1 b Source #

liftA2 :: (a -> b -> c) -> ContW w i j a -> ContW w j k1 b -> ContW w i k1 c Source #

(*>) :: ContW w i j a -> ContW w j k1 b -> ContW w i k1 b Source #

(<*) :: ContW w i j a -> ContW w j k1 b -> ContW w i k1 a Source #

Comonad w => Applicative (Cont2W w :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

pure :: a -> Cont2W w i i a Source #

(<*>) :: Cont2W w i j (a -> b) -> Cont2W w j k1 a -> Cont2W w i k1 b Source #

liftA2 :: (a -> b -> c) -> Cont2W w i j a -> Cont2W w j k1 b -> Cont2W w i k1 c Source #

(*>) :: Cont2W w i j a -> Cont2W w j k1 b -> Cont2W w i k1 b Source #

(<*) :: Cont2W w i j a -> Cont2W w j k1 b -> Cont2W w i k1 a Source #

Applicative f => Applicative (IgnoreIndices f :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

pure :: forall a (i :: k). a -> IgnoreIndices f i i a Source #

(<*>) :: forall (i :: k) (j :: k) a b (k1 :: k). IgnoreIndices f i j (a -> b) -> IgnoreIndices f j k1 a -> IgnoreIndices f i k1 b Source #

liftA2 :: forall a b c (i :: k) (j :: k) (k1 :: k). (a -> b -> c) -> IgnoreIndices f i j a -> IgnoreIndices f j k1 b -> IgnoreIndices f i k1 c Source #

(*>) :: forall (i :: k) (j :: k) a (k1 :: k) b. IgnoreIndices f i j a -> IgnoreIndices f j k1 b -> IgnoreIndices f i k1 b Source #

(<*) :: forall (i :: k) (j :: k) a (k1 :: k) b. IgnoreIndices f i j a -> IgnoreIndices f j k1 b -> IgnoreIndices f i k1 a Source #

(Applicative f, Applicative g) => Applicative (f :*: g :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

pure :: forall a (i :: k). a -> (f :*: g) i i a Source #

(<*>) :: forall (i :: k) (j :: k) a b (k1 :: k). (f :*: g) i j (a -> b) -> (f :*: g) j k1 a -> (f :*: g) i k1 b Source #

liftA2 :: forall a b c (i :: k) (j :: k) (k1 :: k). (a -> b -> c) -> (f :*: g) i j a -> (f :*: g) j k1 b -> (f :*: g) i k1 c Source #

(*>) :: forall (i :: k) (j :: k) a (k1 :: k) b. (f :*: g) i j a -> (f :*: g) j k1 b -> (f :*: g) i k1 b Source #

(<*) :: forall (i :: k) (j :: k) a (k1 :: k) b. (f :*: g) i j a -> (f :*: g) j k1 b -> (f :*: g) i k1 a Source #

class (Applicative m, forall (i :: k). Monad (m i i)) => Monad (m :: k -> k -> Type -> Type) where Source #

Methods

(>>=) :: forall (i :: k) (j :: k) a (k1 :: k) b. m i j a -> (a -> m j k1 b) -> m i k1 b Source #

Instances

Instances details
Comonad w => Monad (ContW w :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont

Methods

(>>=) :: ContW w i j a -> (a -> ContW w j k1 b) -> ContW w i k1 b Source #

Comonad w => Monad (Cont2W w :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

(>>=) :: Cont2W w i j a -> (a -> Cont2W w j k1 b) -> Cont2W w i k1 b Source #

Monad m => Monad (IgnoreIndices m :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

(>>=) :: forall (i :: k) (j :: k) a (k1 :: k) b. IgnoreIndices m i j a -> (a -> IgnoreIndices m j k1 b) -> IgnoreIndices m i k1 b Source #

(Monad f, Monad g) => Monad (f :*: g :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

(>>=) :: forall (i :: k) (j :: k) a (k1 :: k) b. (f :*: g) i j a -> (a -> (f :*: g) j k1 b) -> (f :*: g) i k1 b Source #

type Alternative (m :: k -> k -> Type -> Type) = (Applicative m, forall (r :: k) (r' :: k) a. Additive (m r r' a)) Source #

type MonadPlus (m :: k -> k -> Type -> Type) = (Monad m, forall (r :: k) (r' :: k) a. Additive (m r r' a)) Source #

guard :: forall {k} m (i :: k). Alternative m => Bool -> m i i () Source #

class Fail (m :: k -> k1 -> k2 -> Type) where Source #

This class is mainly used for the qualified `do`-notation, as described in the documentation for MonadFail. Occasionally used to fail with an error message in monads which support it, see for instance guardF below.

Methods

fail :: forall (i :: k) (j :: k1) (a :: k2). String -> m i j a Source #

Instances

Instances details
MonadFail m => Fail (IgnoreIndices m :: k1 -> k2 -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

fail :: forall (i :: k1) (j :: k2) a. String -> IgnoreIndices m i j a Source #

(Fail f, Fail g) => Fail (f :*: g :: k1 -> k2 -> k3 -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

fail :: forall (i :: k1) (j :: k2) (a :: k3). String -> (f :*: g) i j a Source #

type MonadFail (m :: k -> k -> Type -> Type) = (Monad m, Fail m) Source #

guardF :: forall {k} m (i :: k). (Applicative m, Fail m) => Bool -> String -> m i i () Source #

Deriving-via combinators

newtype FromIndexed (m :: k -> k1 -> k2 -> Type) (i :: k) (j :: k1) (a :: k2) Source #

A deriving via combinator

Constructors

FromIndexed (m i j a) 

Instances

Instances details
(Alternative m, i ~ j) => Alternative (FromIndexed m i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

empty :: FromIndexed m i j a #

(<|>) :: FromIndexed m i j a -> FromIndexed m i j a -> FromIndexed m i j a #

some :: FromIndexed m i j a -> FromIndexed m i j [a] #

many :: FromIndexed m i j a -> FromIndexed m i j [a] #

(Applicative m, i ~ j) => Applicative (FromIndexed m i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

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

(<*>) :: FromIndexed m i j (a -> b) -> FromIndexed m i j a -> FromIndexed m i j b #

liftA2 :: (a -> b -> c) -> FromIndexed m i j a -> FromIndexed m i j b -> FromIndexed m i j c #

(*>) :: FromIndexed m i j a -> FromIndexed m i j b -> FromIndexed m i j b #

(<*) :: FromIndexed m i j a -> FromIndexed m i j b -> FromIndexed m i j a #

Functor (m i j) => Functor (FromIndexed m i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

fmap :: (a -> b) -> FromIndexed m i j a -> FromIndexed m i j b #

(<$) :: a -> FromIndexed m i j b -> FromIndexed m i j a #

(Monad m, i ~ j) => Monad (FromIndexed m i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

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

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

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

(MonadPlus m, i ~ j) => MonadPlus (FromIndexed m i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

mzero :: FromIndexed m i j a #

mplus :: FromIndexed m i j a -> FromIndexed m i j a -> FromIndexed m i j a #

Index monad combinators

Product of indexed gadgets

data ((f :: k -> k1 -> k2 -> Type) :*: (g :: k -> k1 -> k2 -> Type)) (i :: k) (j :: k1) (a :: k2) Source #

Constructors

(:*:) (f i j a) (g i j a) 

Instances

Instances details
(Fail f, Fail g) => Fail (f :*: g :: k1 -> k2 -> k3 -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

fail :: forall (i :: k1) (j :: k2) (a :: k3). String -> (f :*: g) i j a Source #

(Applicative f, Applicative g) => Applicative (f :*: g :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

pure :: forall a (i :: k). a -> (f :*: g) i i a Source #

(<*>) :: forall (i :: k) (j :: k) a b (k1 :: k). (f :*: g) i j (a -> b) -> (f :*: g) j k1 a -> (f :*: g) i k1 b Source #

liftA2 :: forall a b c (i :: k) (j :: k) (k1 :: k). (a -> b -> c) -> (f :*: g) i j a -> (f :*: g) j k1 b -> (f :*: g) i k1 c Source #

(*>) :: forall (i :: k) (j :: k) a (k1 :: k) b. (f :*: g) i j a -> (f :*: g) j k1 b -> (f :*: g) i k1 b Source #

(<*) :: forall (i :: k) (j :: k) a (k1 :: k) b. (f :*: g) i j a -> (f :*: g) j k1 b -> (f :*: g) i k1 a Source #

(Monad f, Monad g) => Monad (f :*: g :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

(>>=) :: forall (i :: k) (j :: k) a (k1 :: k) b. (f :*: g) i j a -> (a -> (f :*: g) j k1 b) -> (f :*: g) i k1 b Source #

(Shifty f, Shifty g) => Shifty (f :*: g) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

shift :: ((a -> r' -> r') -> r -> (f :*: g) r k k) -> (f :*: g) r r' a Source #

(Stacked f, Stacked g) => Stacked (f :*: g) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

shift_ :: ((r' -> r') -> r -> (f :*: g) r r'' r'') -> (f :*: g) r r' () Source #

(Alternative (f i j), Alternative (g i j)) => Alternative ((f :*: g) i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

empty :: (f :*: g) i j a #

(<|>) :: (f :*: g) i j a -> (f :*: g) i j a -> (f :*: g) i j a #

some :: (f :*: g) i j a -> (f :*: g) i j [a] #

many :: (f :*: g) i j a -> (f :*: g) i j [a] #

(Applicative (f i j), Applicative (g i j)) => Applicative ((f :*: g) i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

pure :: a -> (f :*: g) i j a #

(<*>) :: (f :*: g) i j (a -> b) -> (f :*: g) i j a -> (f :*: g) i j b #

liftA2 :: (a -> b -> c) -> (f :*: g) i j a -> (f :*: g) i j b -> (f :*: g) i j c #

(*>) :: (f :*: g) i j a -> (f :*: g) i j b -> (f :*: g) i j b #

(<*) :: (f :*: g) i j a -> (f :*: g) i j b -> (f :*: g) i j a #

(Functor (f i j), Functor (g i j)) => Functor ((f :*: g) i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

fmap :: (a -> b) -> (f :*: g) i j a -> (f :*: g) i j b #

(<$) :: a -> (f :*: g) i j b -> (f :*: g) i j a #

(Monad (f i j), Monad (g i j)) => Monad ((f :*: g) i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

(>>=) :: (f :*: g) i j a -> (a -> (f :*: g) i j b) -> (f :*: g) i j b #

(>>) :: (f :*: g) i j a -> (f :*: g) i j b -> (f :*: g) i j b #

return :: a -> (f :*: g) i j a #

(MonadPlus (f i j), MonadPlus (g i j)) => MonadPlus ((f :*: g) i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

mzero :: (f :*: g) i j a #

mplus :: (f :*: g) i j a -> (f :*: g) i j a -> (f :*: g) i j a #

(Additive (f r r' a), Additive (g r r' a)) => Additive ((f :*: g) r r' a) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

empty :: (f :*: g) r r' a Source #

(<|>) :: (f :*: g) r r' a -> (f :*: g) r r' a -> (f :*: g) r r' a Source #

fst_star :: forall {k1} {k2} {k3} f (g :: k1 -> k2 -> k3 -> Type) (i :: k1) (j :: k2) (a :: k3). (f :*: g) i j a -> f i j a Source #

snd_star :: forall {k1} {k2} {k3} (f :: k1 -> k2 -> k3 -> Type) g (i :: k1) (j :: k2) (a :: k3). (f :*: g) i j a -> g i j a Source #

Lift non-indexed gadgets to indexed

newtype IgnoreIndices (m :: k -> Type) (i :: k1) (j :: k2) (a :: k) Source #

Constructors

IgnoreIndices 

Fields

Instances

Instances details
MonadFail m => Fail (IgnoreIndices m :: k1 -> k2 -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

fail :: forall (i :: k1) (j :: k2) a. String -> IgnoreIndices m i j a Source #

Applicative f => Applicative (IgnoreIndices f :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

pure :: forall a (i :: k). a -> IgnoreIndices f i i a Source #

(<*>) :: forall (i :: k) (j :: k) a b (k1 :: k). IgnoreIndices f i j (a -> b) -> IgnoreIndices f j k1 a -> IgnoreIndices f i k1 b Source #

liftA2 :: forall a b c (i :: k) (j :: k) (k1 :: k). (a -> b -> c) -> IgnoreIndices f i j a -> IgnoreIndices f j k1 b -> IgnoreIndices f i k1 c Source #

(*>) :: forall (i :: k) (j :: k) a (k1 :: k) b. IgnoreIndices f i j a -> IgnoreIndices f j k1 b -> IgnoreIndices f i k1 b Source #

(<*) :: forall (i :: k) (j :: k) a (k1 :: k) b. IgnoreIndices f i j a -> IgnoreIndices f j k1 b -> IgnoreIndices f i k1 a Source #

Monad m => Monad (IgnoreIndices m :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

(>>=) :: forall (i :: k) (j :: k) a (k1 :: k) b. IgnoreIndices m i j a -> (a -> IgnoreIndices m j k1 b) -> IgnoreIndices m i k1 b Source #

Applicative m => Stacked (IgnoreIndices m :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

shift_ :: ((r' -> r') -> r -> IgnoreIndices m r r'' r'') -> IgnoreIndices m r r' () Source #

Alternative m => Alternative (IgnoreIndices m i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

empty :: IgnoreIndices m i j a #

(<|>) :: IgnoreIndices m i j a -> IgnoreIndices m i j a -> IgnoreIndices m i j a #

some :: IgnoreIndices m i j a -> IgnoreIndices m i j [a] #

many :: IgnoreIndices m i j a -> IgnoreIndices m i j [a] #

Applicative m => Applicative (IgnoreIndices m i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

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

(<*>) :: IgnoreIndices m i j (a -> b) -> IgnoreIndices m i j a -> IgnoreIndices m i j b #

liftA2 :: (a -> b -> c) -> IgnoreIndices m i j a -> IgnoreIndices m i j b -> IgnoreIndices m i j c #

(*>) :: IgnoreIndices m i j a -> IgnoreIndices m i j b -> IgnoreIndices m i j b #

(<*) :: IgnoreIndices m i j a -> IgnoreIndices m i j b -> IgnoreIndices m i j a #

Functor m => Functor (IgnoreIndices m i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

fmap :: (a -> b) -> IgnoreIndices m i j a -> IgnoreIndices m i j b #

(<$) :: a -> IgnoreIndices m i j b -> IgnoreIndices m i j a #

Monad m => Monad (IgnoreIndices m i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

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

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

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

MonadPlus m => MonadPlus (IgnoreIndices m i j) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

mzero :: IgnoreIndices m i j a #

mplus :: IgnoreIndices m i j a -> IgnoreIndices m i j a -> IgnoreIndices m i j a #

Alternative m => Additive (IgnoreIndices m r r' a) Source # 
Instance details

Defined in Control.Monad.Indexed

Methods

empty :: IgnoreIndices m r r' a Source #

(<|>) :: IgnoreIndices m r r' a -> IgnoreIndices m r r' a -> IgnoreIndices m r r' a Source #

Additional technical definitions

(>>) :: forall {k1} m (i :: k1) (j :: k1) (k2 :: k1) a. Applicative m => m i j () -> m j k2 a -> m i k2 a Source #

Synonym of *> used for QualifiedDo notation.