subcategories-0.1.1.0: Subcategories induced by class constraints
Safe HaskellNone
LanguageHaskell2010

Control.Subcategory.Alternative

Documentation

class CChoice f => CAlternative f where Source #

Minimal complete definition

Nothing

Methods

cempty :: Dom f a => f a Source #

default cempty :: Alternative f => f a Source #

Instances

Instances details
CAlternative [] Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom [] a => [a] Source #

CAlternative Maybe Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom Maybe a => Maybe a Source #

CAlternative Option Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom Option a => Option a Source #

CAlternative ReadPrec Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom ReadPrec a => ReadPrec a Source #

CAlternative ReadP Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom ReadP a => ReadP a Source #

CAlternative IntMap Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom IntMap a => IntMap a Source #

CAlternative Seq Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom Seq a => Seq a Source #

CAlternative Set Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom Set a => Set a Source #

CAlternative PrimArray Source # 
Instance details

Defined in Control.Subcategory.Alternative

CAlternative SmallArray Source # 
Instance details

Defined in Control.Subcategory.Alternative

CAlternative Array Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom Array a => Array a Source #

CAlternative HashSet Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom HashSet a => HashSet a Source #

CAlternative Vector Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom Vector a => Vector a Source #

CAlternative Vector Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom Vector a => Vector a Source #

CAlternative Vector Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom Vector a => Vector a Source #

CAlternative Vector Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom Vector a => Vector a Source #

Ord k => CAlternative (Map k) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom (Map k) a => Map k a Source #

(Eq k, Hashable k) => CAlternative (HashMap k) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom (HashMap k) a => HashMap k a Source #

(MonoFunctor mono, Monoid mono, GrowingAppend mono) => CAlternative (WrapMono mono :: Type -> Type) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom (WrapMono mono) a => WrapMono mono a Source #

CAlternative f => CAlternative (CApp f) Source # 
Instance details

Defined in Control.Subcategory.Applicative

Methods

cempty :: Dom (CApp f) a => CApp f a Source #

CAlternative f => CAlternative (CAlt f) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom (CAlt f) a => CAlt f a Source #

(CAlternative f, CAlternative g) => CAlternative (Product f g) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom (Product f g) a => Product f g a Source #

(CAlternative f, CFunctor g) => CAlternative (Compose f g) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom (Compose f g) a => Compose f g a Source #

class CFunctor f => CChoice f where Source #

Minimal complete definition

Nothing

Methods

(<!>) :: Dom f a => f a -> f a -> f a infixl 3 Source #

default (<!>) :: Alternative f => f a -> f a -> f a Source #

Instances

Instances details
CChoice [] Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom [] a => [a] -> [a] -> [a] Source #

CChoice Maybe Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom Maybe a => Maybe a -> Maybe a -> Maybe a Source #

CChoice Option Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom Option a => Option a -> Option a -> Option a Source #

CChoice ReadPrec Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom ReadPrec a => ReadPrec a -> ReadPrec a -> ReadPrec a Source #

CChoice ReadP Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom ReadP a => ReadP a -> ReadP a -> ReadP a Source #

CChoice NonEmpty Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom NonEmpty a => NonEmpty a -> NonEmpty a -> NonEmpty a Source #

CChoice IntMap Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom IntMap a => IntMap a -> IntMap a -> IntMap a Source #

CChoice Seq Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom Seq a => Seq a -> Seq a -> Seq a Source #

CChoice Set Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom Set a => Set a -> Set a -> Set a Source #

CChoice PrimArray Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom PrimArray a => PrimArray a -> PrimArray a -> PrimArray a Source #

CChoice SmallArray Source # 
Instance details

Defined in Control.Subcategory.Alternative

CChoice Array Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom Array a => Array a -> Array a -> Array a Source #

CChoice HashSet Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom HashSet a => HashSet a -> HashSet a -> HashSet a Source #

CChoice Vector Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom Vector a => Vector a -> Vector a -> Vector a Source #

CChoice Vector Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom Vector a => Vector a -> Vector a -> Vector a Source #

CChoice Vector Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom Vector a => Vector a -> Vector a -> Vector a Source #

CChoice Vector Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom Vector a => Vector a -> Vector a -> Vector a Source #

CChoice (Either a) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom (Either a) a0 => Either a a0 -> Either a a0 -> Either a a0 Source #

Ord k => CChoice (Map k) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom (Map k) a => Map k a -> Map k a -> Map k a Source #

(Eq k, Hashable k) => CChoice (HashMap k) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom (HashMap k) a => HashMap k a -> HashMap k a -> HashMap k a Source #

(MonoFunctor mono, GrowingAppend mono, Semigroup mono) => CChoice (WrapMono mono :: Type -> Type) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom (WrapMono mono) a => WrapMono mono a -> WrapMono mono a -> WrapMono mono a Source #

CChoice f => CChoice (CApp f) Source # 
Instance details

Defined in Control.Subcategory.Applicative

Methods

(<!>) :: Dom (CApp f) a => CApp f a -> CApp f a -> CApp f a Source #

CChoice f => CChoice (CAlt f) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom (CAlt f) a => CAlt f a -> CAlt f a -> CAlt f a Source #

(CChoice f, CChoice g) => CChoice (Product f g) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom (Product f g) a => Product f g a -> Product f g a -> Product f g a Source #

(CChoice f, CFunctor g) => CChoice (Compose f g) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom (Compose f g) a => Compose f g a -> Compose f g a -> Compose f g a Source #

newtype CAlt f a Source #

Constructors

CAlt 

Fields

Instances

Instances details
Functor f => Functor (CAlt f) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

fmap :: (a -> b) -> CAlt f a -> CAlt f b #

(<$) :: a -> CAlt f b -> CAlt f a #

Applicative f => Applicative (CAlt f) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

pure :: a -> CAlt f a #

(<*>) :: CAlt f (a -> b) -> CAlt f a -> CAlt f b #

liftA2 :: (a -> b -> c) -> CAlt f a -> CAlt f b -> CAlt f c #

(*>) :: CAlt f a -> CAlt f b -> CAlt f b #

(<*) :: CAlt f a -> CAlt f b -> CAlt f a #

Alternative f => Alternative (CAlt f) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

empty :: CAlt f a #

(<|>) :: CAlt f a -> CAlt f a -> CAlt f a #

some :: CAlt f a -> CAlt f [a] #

many :: CAlt f a -> CAlt f [a] #

CFunctor f => CFunctor (CAlt f) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cmap :: (Dom (CAlt f) a, Dom (CAlt f) b) => (a -> b) -> CAlt f a -> CAlt f b Source #

(<$:) :: (Dom (CAlt f) a, Dom (CAlt f) b) => a -> CAlt f b -> CAlt f a Source #

Constrained (CAlt f) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Associated Types

type Dom (CAlt f) a Source #

CPointed f => CPointed (CAlt f) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cpure :: Dom (CAlt f) a => a -> CAlt f a Source #

CApplicative f => CApplicative (CAlt f) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

pair :: (Dom (CAlt f) a, Dom (CAlt f) b, Dom (CAlt f) (a, b)) => CAlt f a -> CAlt f b -> CAlt f (a, b) Source #

(<.>) :: (Dom (CAlt f) a, Dom (CAlt f) b, Dom (CAlt f) (a -> b)) => CAlt f (a -> b) -> CAlt f a -> CAlt f b Source #

(.>) :: (Dom (CAlt f) a, Dom (CAlt f) b) => CAlt f a -> CAlt f b -> CAlt f b Source #

(<.) :: (Dom (CAlt f) a, Dom (CAlt f) b) => CAlt f a -> CAlt f b -> CAlt f a Source #

CAlternative f => CAlternative (CAlt f) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

cempty :: Dom (CAlt f) a => CAlt f a Source #

CChoice f => CChoice (CAlt f) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<!>) :: Dom (CAlt f) a => CAlt f a -> CAlt f a -> CAlt f a Source #

(Dom f a, CChoice f) => Semigroup (CAlt f a) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

(<>) :: CAlt f a -> CAlt f a -> CAlt f a #

sconcat :: NonEmpty (CAlt f a) -> CAlt f a #

stimes :: Integral b => b -> CAlt f a -> CAlt f a #

(Dom f a, CAlternative f) => Monoid (CAlt f a) Source # 
Instance details

Defined in Control.Subcategory.Alternative

Methods

mempty :: CAlt f a #

mappend :: CAlt f a -> CAlt f a -> CAlt f a #

mconcat :: [CAlt f a] -> CAlt f a #

type Dom (CAlt f) a Source # 
Instance details

Defined in Control.Subcategory.Alternative

type Dom (CAlt f) a = Dom f a

Orphan instances

CAlternative [] Source # 
Instance details

Methods

cempty :: Dom [] a => [a] Source #

CAlternative Maybe Source # 
Instance details

Methods

cempty :: Dom Maybe a => Maybe a Source #

CAlternative Option Source # 
Instance details

Methods

cempty :: Dom Option a => Option a Source #

CAlternative ReadPrec Source # 
Instance details

Methods

cempty :: Dom ReadPrec a => ReadPrec a Source #

CAlternative ReadP Source # 
Instance details

Methods

cempty :: Dom ReadP a => ReadP a Source #

CAlternative IntMap Source # 
Instance details

Methods

cempty :: Dom IntMap a => IntMap a Source #

CAlternative Seq Source # 
Instance details

Methods

cempty :: Dom Seq a => Seq a Source #

CAlternative Set Source # 
Instance details

Methods

cempty :: Dom Set a => Set a Source #

CAlternative PrimArray Source # 
Instance details

CAlternative SmallArray Source # 
Instance details

CAlternative Array Source # 
Instance details

Methods

cempty :: Dom Array a => Array a Source #

CAlternative HashSet Source # 
Instance details

Methods

cempty :: Dom HashSet a => HashSet a Source #

CAlternative Vector Source # 
Instance details

Methods

cempty :: Dom Vector a => Vector a Source #

CAlternative Vector Source # 
Instance details

Methods

cempty :: Dom Vector a => Vector a Source #

CAlternative Vector Source # 
Instance details

Methods

cempty :: Dom Vector a => Vector a Source #

CAlternative Vector Source # 
Instance details

Methods

cempty :: Dom Vector a => Vector a Source #

CChoice [] Source # 
Instance details

Methods

(<!>) :: Dom [] a => [a] -> [a] -> [a] Source #

CChoice Maybe Source # 
Instance details

Methods

(<!>) :: Dom Maybe a => Maybe a -> Maybe a -> Maybe a Source #

CChoice Option Source # 
Instance details

Methods

(<!>) :: Dom Option a => Option a -> Option a -> Option a Source #

CChoice ReadPrec Source # 
Instance details

Methods

(<!>) :: Dom ReadPrec a => ReadPrec a -> ReadPrec a -> ReadPrec a Source #

CChoice ReadP Source # 
Instance details

Methods

(<!>) :: Dom ReadP a => ReadP a -> ReadP a -> ReadP a Source #

CChoice NonEmpty Source # 
Instance details

Methods

(<!>) :: Dom NonEmpty a => NonEmpty a -> NonEmpty a -> NonEmpty a Source #

CChoice IntMap Source # 
Instance details

Methods

(<!>) :: Dom IntMap a => IntMap a -> IntMap a -> IntMap a Source #

CChoice Seq Source # 
Instance details

Methods

(<!>) :: Dom Seq a => Seq a -> Seq a -> Seq a Source #

CChoice Set Source # 
Instance details

Methods

(<!>) :: Dom Set a => Set a -> Set a -> Set a Source #

CChoice PrimArray Source # 
Instance details

Methods

(<!>) :: Dom PrimArray a => PrimArray a -> PrimArray a -> PrimArray a Source #

CChoice SmallArray Source # 
Instance details

CChoice Array Source # 
Instance details

Methods

(<!>) :: Dom Array a => Array a -> Array a -> Array a Source #

CChoice HashSet Source # 
Instance details

Methods

(<!>) :: Dom HashSet a => HashSet a -> HashSet a -> HashSet a Source #

CChoice Vector Source # 
Instance details

Methods

(<!>) :: Dom Vector a => Vector a -> Vector a -> Vector a Source #

CChoice Vector Source # 
Instance details

Methods

(<!>) :: Dom Vector a => Vector a -> Vector a -> Vector a Source #

CChoice Vector Source # 
Instance details

Methods

(<!>) :: Dom Vector a => Vector a -> Vector a -> Vector a Source #

CChoice Vector Source # 
Instance details

Methods

(<!>) :: Dom Vector a => Vector a -> Vector a -> Vector a Source #

Ord k => CAlternative (Map k) Source # 
Instance details

Methods

cempty :: Dom (Map k) a => Map k a Source #

(Eq k, Hashable k) => CAlternative (HashMap k) Source # 
Instance details

Methods

cempty :: Dom (HashMap k) a => HashMap k a Source #

CChoice (Either a) Source # 
Instance details

Methods

(<!>) :: Dom (Either a) a0 => Either a a0 -> Either a a0 -> Either a a0 Source #

Ord k => CChoice (Map k) Source # 
Instance details

Methods

(<!>) :: Dom (Map k) a => Map k a -> Map k a -> Map k a Source #

(Eq k, Hashable k) => CChoice (HashMap k) Source # 
Instance details

Methods

(<!>) :: Dom (HashMap k) a => HashMap k a -> HashMap k a -> HashMap k a Source #

(MonoFunctor mono, Monoid mono, GrowingAppend mono) => CAlternative (WrapMono mono :: Type -> Type) Source # 
Instance details

Methods

cempty :: Dom (WrapMono mono) a => WrapMono mono a Source #

(MonoFunctor mono, GrowingAppend mono, Semigroup mono) => CChoice (WrapMono mono :: Type -> Type) Source # 
Instance details

Methods

(<!>) :: Dom (WrapMono mono) a => WrapMono mono a -> WrapMono mono a -> WrapMono mono a Source #

(CAlternative f, CAlternative g) => CAlternative (Product f g) Source # 
Instance details

Methods

cempty :: Dom (Product f g) a => Product f g a Source #

(CChoice f, CChoice g) => CChoice (Product f g) Source # 
Instance details

Methods

(<!>) :: Dom (Product f g) a => Product f g a -> Product f g a -> Product f g a Source #

(CAlternative f, CFunctor g) => CAlternative (Compose f g) Source # 
Instance details

Methods

cempty :: Dom (Compose f g) a => Compose f g a Source #

(CChoice f, CFunctor g) => CChoice (Compose f g) Source # 
Instance details

Methods

(<!>) :: Dom (Compose f g) a => Compose f g a -> Compose f g a -> Compose f g a Source #