supermonad-0.2.1.1: Plugin and base library to support supermonads in Haskell

Safe HaskellNone
LanguageHaskell2010

Control.Super.Monad.Constrained.Alternative

Description

WARNING: This module is an experiment to see how Alternative may be encoded. The authors are not aware of any generalized applicatives that make use of Alternative. Hence, we do not know if this encoding of it is sufficient. Therefore, the encoding is not in its final form and may change in the future.

Synopsis

Documentation

class Functor f => AlternativeEmpty f where Source #

The encoding of the empty operation.

Return is not a superclass, because the indices or constraints involved in an AlternativeEmpty instance may differ from those involved with the Return instance.

WARNING: This module is an experiment to see how Alternative may be encoded. The authors are not aware of any generalized applicatives that make use of Alternative. Hence, we do not know if this encoding of it is sufficient. Therefore, the encoding is not in its final form and may change in the future.

Minimal complete definition

empty

Associated Types

type AlternativeEmptyCts f a :: Constraint Source #

Methods

empty :: AlternativeEmptyCts f a => f a Source #

Instances

AlternativeEmpty [] Source # 

Associated Types

type AlternativeEmptyCts ([] :: * -> *) a :: Constraint Source #

Methods

empty :: AlternativeEmptyCts [] a => [a] Source #

AlternativeEmpty Maybe Source # 

Associated Types

type AlternativeEmptyCts (Maybe :: * -> *) a :: Constraint Source #

AlternativeEmpty IO Source # 

Associated Types

type AlternativeEmptyCts (IO :: * -> *) a :: Constraint Source #

AlternativeEmpty Option Source # 

Associated Types

type AlternativeEmptyCts (Option :: * -> *) a :: Constraint Source #

AlternativeEmpty STM Source # 

Associated Types

type AlternativeEmptyCts (STM :: * -> *) a :: Constraint Source #

AlternativeEmpty ReadPrec Source # 

Associated Types

type AlternativeEmptyCts (ReadPrec :: * -> *) a :: Constraint Source #

AlternativeEmpty ReadP Source # 

Associated Types

type AlternativeEmptyCts (ReadP :: * -> *) a :: Constraint Source #

AlternativeEmpty (U1 *) Source # 

Associated Types

type AlternativeEmptyCts (U1 * :: * -> *) a :: Constraint Source #

Methods

empty :: AlternativeEmptyCts (U1 *) a => U1 * a Source #

AlternativeEmpty (Proxy *) Source # 

Associated Types

type AlternativeEmptyCts (Proxy * :: * -> *) a :: Constraint Source #

AlternativeEmpty f => AlternativeEmpty (Rec1 * f) Source # 

Associated Types

type AlternativeEmptyCts (Rec1 * f :: * -> *) a :: Constraint Source #

Methods

empty :: AlternativeEmptyCts (Rec1 * f) a => Rec1 * f a Source #

AlternativeEmpty f => AlternativeEmpty (Alt * f) Source # 

Associated Types

type AlternativeEmptyCts (Alt * f :: * -> *) a :: Constraint Source #

Methods

empty :: AlternativeEmptyCts (Alt * f) a => Alt * f a Source #

(AlternativeEmpty f, AlternativeEmpty g) => AlternativeEmpty ((:*:) * f g) Source # 

Associated Types

type AlternativeEmptyCts ((* :*: f) g :: * -> *) a :: Constraint Source #

Methods

empty :: AlternativeEmptyCts ((* :*: f) g) a => (* :*: f) g a Source #

(AlternativeEmpty f, AlternativeEmpty f') => AlternativeEmpty (Product * f f') Source # 

Associated Types

type AlternativeEmptyCts (Product * f f' :: * -> *) a :: Constraint Source #

Methods

empty :: AlternativeEmptyCts (Product * f f') a => Product * f f' a Source #

AlternativeEmpty f => AlternativeEmpty (M1 * i c f) Source # 

Associated Types

type AlternativeEmptyCts (M1 * i c f :: * -> *) a :: Constraint Source #

Methods

empty :: AlternativeEmptyCts (M1 * i c f) a => M1 * i c f a Source #

(AlternativeEmpty f, AlternativeEmpty g) => AlternativeEmpty ((:.:) * * f g) Source # 

Associated Types

type AlternativeEmptyCts ((* :.: *) f g :: * -> *) a :: Constraint Source #

Methods

empty :: AlternativeEmptyCts ((* :.: *) f g) a => (* :.: *) f g a Source #

(AlternativeEmpty f, AlternativeEmpty f') => AlternativeEmpty (Compose * * f f') Source # 

Associated Types

type AlternativeEmptyCts (Compose * * f f' :: * -> *) a :: Constraint Source #

Methods

empty :: AlternativeEmptyCts (Compose * * f f') a => Compose * * f f' a Source #

class (Functor f, Functor g, Functor h) => AlternativeAlt f g h where Source #

The encoding of the <|> operation.

Applicative is not a superclass, because the indices or constraints involved in an Alternative instance may differ from those involved with the Applicative instance.

WARNING: This module is an experiment to see how Alternative may be encoded. The authors are not aware of any generalized applicatives that make use of Alternative. Hence, we do not know if this encoding of it is sufficient. Therefore, the encoding is not in its final form and may change in the future.

Minimal complete definition

(<|>)

Associated Types

type AlternativeAltCts f g h a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts f g h a => f a -> g a -> h a Source #

Instances

AlternativeAlt [] [] [] Source # 

Associated Types

type AlternativeAltCts ([] :: * -> *) ([] :: * -> *) ([] :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts [] [] [] a => [a] -> [a] -> [a] Source #

AlternativeAlt Maybe Maybe Maybe Source # 

Associated Types

type AlternativeAltCts (Maybe :: * -> *) (Maybe :: * -> *) (Maybe :: * -> *) a :: Constraint Source #

AlternativeAlt IO IO IO Source # 

Associated Types

type AlternativeAltCts (IO :: * -> *) (IO :: * -> *) (IO :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts IO IO IO a => IO a -> IO a -> IO a Source #

AlternativeAlt Option Option Option Source # 

Associated Types

type AlternativeAltCts (Option :: * -> *) (Option :: * -> *) (Option :: * -> *) a :: Constraint Source #

AlternativeAlt STM STM STM Source # 

Associated Types

type AlternativeAltCts (STM :: * -> *) (STM :: * -> *) (STM :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts STM STM STM a => STM a -> STM a -> STM a Source #

AlternativeAlt ReadPrec ReadPrec ReadPrec Source # 

Associated Types

type AlternativeAltCts (ReadPrec :: * -> *) (ReadPrec :: * -> *) (ReadPrec :: * -> *) a :: Constraint Source #

AlternativeAlt ReadP ReadP ReadP Source # 

Associated Types

type AlternativeAltCts (ReadP :: * -> *) (ReadP :: * -> *) (ReadP :: * -> *) a :: Constraint Source #

AlternativeAlt (U1 *) (U1 *) (U1 *) Source # 

Associated Types

type AlternativeAltCts (U1 * :: * -> *) (U1 * :: * -> *) (U1 * :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts (U1 *) (U1 *) (U1 *) a => U1 * a -> U1 * a -> U1 * a Source #

AlternativeAlt (Proxy *) (Proxy *) (Proxy *) Source # 

Associated Types

type AlternativeAltCts (Proxy * :: * -> *) (Proxy * :: * -> *) (Proxy * :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts (Proxy *) (Proxy *) (Proxy *) a => Proxy * a -> Proxy * a -> Proxy * a Source #

AlternativeAlt f g h => AlternativeAlt (Rec1 * f) (Rec1 * g) (Rec1 * h) Source # 

Associated Types

type AlternativeAltCts (Rec1 * f :: * -> *) (Rec1 * g :: * -> *) (Rec1 * h :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts (Rec1 * f) (Rec1 * g) (Rec1 * h) a => Rec1 * f a -> Rec1 * g a -> Rec1 * h a Source #

AlternativeAlt f g h => AlternativeAlt (Alt * f) (Alt * g) (Alt * h) Source # 

Associated Types

type AlternativeAltCts (Alt * f :: * -> *) (Alt * g :: * -> *) (Alt * h :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts (Alt * f) (Alt * g) (Alt * h) a => Alt * f a -> Alt * g a -> Alt * h a Source #

(AlternativeAlt f g h, AlternativeAlt f' g' h') => AlternativeAlt ((:*:) * f f') ((:*:) * g g') ((:*:) * h h') Source # 

Associated Types

type AlternativeAltCts ((* :*: f) f' :: * -> *) ((* :*: g) g' :: * -> *) ((* :*: h) h' :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts ((* :*: f) f') ((* :*: g) g') ((* :*: h) h') a => (* :*: f) f' a -> (* :*: g) g' a -> (* :*: h) h' a Source #

(AlternativeAlt f g h, AlternativeAlt f' g' h') => AlternativeAlt (Product * f f') (Product * g g') (Product * h h') Source # 

Associated Types

type AlternativeAltCts (Product * f f' :: * -> *) (Product * g g' :: * -> *) (Product * h h' :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts (Product * f f') (Product * g g') (Product * h h') a => Product * f f' a -> Product * g g' a -> Product * h h' a Source #

AlternativeAlt f g h => AlternativeAlt (M1 * i c f) (M1 * i c g) (M1 * i c h) Source # 

Associated Types

type AlternativeAltCts (M1 * i c f :: * -> *) (M1 * i c g :: * -> *) (M1 * i c h :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts (M1 * i c f) (M1 * i c g) (M1 * i c h) a => M1 * i c f a -> M1 * i c g a -> M1 * i c h a Source #

(Applicative f g h, AlternativeAlt f' g' h') => AlternativeAlt ((:.:) * * f f') ((:.:) * * g g') ((:.:) * * h h') Source # 

Associated Types

type AlternativeAltCts ((* :.: *) f f' :: * -> *) ((* :.: *) g g' :: * -> *) ((* :.: *) h h' :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts ((* :.: *) f f') ((* :.: *) g g') ((* :.: *) h h') a => (* :.: *) f f' a -> (* :.: *) g g' a -> (* :.: *) h h' a Source #

(Applicative f g h, AlternativeAlt f' g' h') => AlternativeAlt (Compose * * f f') (Compose * * g g') (Compose * * h h') Source # 

Associated Types

type AlternativeAltCts (Compose * * f f' :: * -> *) (Compose * * g g' :: * -> *) (Compose * * h h' :: * -> *) a :: Constraint Source #

Methods

(<|>) :: AlternativeAltCts (Compose * * f f') (Compose * * g g') (Compose * * h h') a => Compose * * f f' a -> Compose * * g g' a -> Compose * * h h' a Source #