constraint-classes-0.5.1: Various typeclasses using ConstraintKinds

Safe HaskellNone
LanguageHaskell2010

Control.ConstraintClasses

Contents

Synopsis

Constraint

type family Dom (f :: * -> *) a :: Constraint Source #

The Dom type family gives the domain of a given type constructor of kind * -> *. This is meant to represent that f is a function from a subset of the the objects in Hask to the objects of Hask.

Instances

type Dom Identity a Source # 
type Dom Identity a
type Dom (Constant * a) b Source # 
type Dom (Constant * a) b
type Dom (Sum * f g) a Source # 
type Dom (Sum * f g) a = (Dom f a, Dom g a)
type Dom (Product * f g) a Source # 
type Dom (Product * f g) a = (Dom f a, Dom g a)
type Dom (Compose * * f g) a Source # 
type Dom (Compose * * f g) a = (Dom g a, Dom f (g a))

class DomCartesian f where Source #

Minimal complete definition

domCartesian

Methods

domCartesian :: (Dom f a, Dom f b) :- Dom f (a, b) Source #

class DomCartesian f => DomClosed f where Source #

Minimal complete definition

domClosed

Methods

domClosed :: (Dom f a, Dom f b) :- Dom f (a -> b) Source #

Base classes

class CFunctor f where Source #

Equivalent to the Functor class.

Methods

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

Instances

CFunctor Identity Source # 

Methods

_fmap :: (Dom Identity a, Dom Identity b) => (a -> b) -> Identity a -> Identity b Source #

CFunctor (Constant * a) Source # 

Methods

_fmap :: (Dom (Constant * a) a, Dom (Constant * a) b) => (a -> b) -> Constant * a a -> Constant * a b Source #

(CFunctor f, CFunctor g) => CFunctor (Sum * f g) Source # 

Methods

_fmap :: (Dom (Sum * f g) a, Dom (Sum * f g) b) => (a -> b) -> Sum * f g a -> Sum * f g b Source #

(CFunctor f, CFunctor g) => CFunctor (Product * f g) Source # 

Methods

_fmap :: (Dom (Product * f g) a, Dom (Product * f g) b) => (a -> b) -> Product * f g a -> Product * f g b Source #

(CFunctor f, CFunctor g) => CFunctor (Compose * * f g) Source # 

Methods

_fmap :: (Dom (Compose * * f g) a, Dom (Compose * * f g) b) => (a -> b) -> Compose * * f g a -> Compose * * f g b Source #

(<$>:) :: (CFunctor f, Dom f a, Dom f b) => (a -> b) -> f a -> f b infixl 4 Source #

class CFunctor f => CApply f where Source #

Equivalent to the Applicative class.

Methods

_zipA :: forall a b. (DomCartesian f, Dom f a, Dom f b) => f a -> f b -> f (a, b) Source #

_liftA2 :: (Dom f a, Dom f b, Dom f c) => (a -> b -> c) -> f a -> f b -> f c Source #

_liftA3 :: (Dom f a, Dom f b, Dom f c, Dom f d) => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source #

_liftA4 :: (Dom f a, Dom f b, Dom f c, Dom f d, Dom f e) => (a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f e Source #

_ap :: (DomClosed f, Dom f a, Dom f b) => f (a -> b) -> f a -> f b Source #

(<*>:) :: (CApply f, DomClosed f, Dom f a, Dom f b) => f (a -> b) -> f a -> f b infixl 4 Source #

class CApply f => CApplicative f where Source #

Methods

_pure :: Dom f a => a -> f a Source #

class CApplicative f => CMonad f where Source #

Equivalent to the @Monad$ class.

Methods

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

(>>=:) :: (CMonad f, Dom f a, Dom f b) => f a -> (a -> f b) -> f b infixl 1 Source #

(=<<:) :: (CMonad f, Dom f a, Dom f b) => (a -> f b) -> f a -> f b infixr 1 Source #

class CApplicative f => CAlt f where Source #

Equivalent to the Applicative class.

Methods

_concat :: Dom f a => f a -> f a -> f a Source #

(<|>:) :: (CAlt f, Dom f a) => f a -> f a -> f a infixl 3 Source #

class CAlt f => CAlternative f where Source #

Methods

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

class CFoldable f where Source #

Equivalent to the Foldable class.

Minimal complete definition

_foldMap | _foldr

Methods

_foldr :: Dom f a => (a -> b -> b) -> b -> f a -> b Source #

_foldr' :: Dom f a => (a -> b -> b) -> b -> f a -> b Source #

_foldl :: Dom f b => (a -> b -> a) -> a -> f b -> a Source #

_foldl' :: Dom f b => (a -> b -> a) -> a -> f b -> a Source #

_fold :: (Dom f m, Monoid m) => f m -> m Source #

_foldMap :: (Dom f a, Monoid m) => (a -> m) -> f a -> m Source #

_toList :: Dom f a => f a -> [a] Source #

_length :: Dom f a => f a -> Int Source #

_mapM_ :: (Monad m, Dom f a) => (a -> m b) -> f a -> m () Source #

_forM_ :: (Monad m, Dom f a) => f a -> (a -> m b) -> m () Source #

class (CFunctor t, CFoldable t) => CTraversable t where Source #

Equivalent to the Traversable class.

Methods

_traverse :: (Dom t a, Dom t b, Monad f) => (a -> f b) -> t a -> f (t b) Source #

_sequence :: (Monad f, Dom t a, Dom t (f a)) => t (f a) -> f (t a) Source #

Key classes

type family CKey (f :: * -> *) Source #

Equivalent to the Key type family.

class CLookup f where Source #

Equivalent to the Lookup class.

Methods

_lookup :: Dom f a => CKey f -> f a -> Maybe a Source #

(!?) :: (CLookup f, Dom f a) => CKey f -> f a -> Maybe a Source #

class CLookup f => CIndexable f where Source #

Equivalent to the Indexable class.

Methods

_index :: Dom f a => f a -> CKey f -> a Source #

(!) :: (CIndexable f, Dom f a) => f a -> CKey f -> a Source #

class CFunctor f => CKeyed f where Source #

Equivalent to the Keyed class.

Methods

_imap :: (Dom f a, Dom f b) => (CKey f -> a -> b) -> f a -> f b Source #

class CFunctor f => CZip f where Source #

Equivalent to the Zip class.

Methods

_zip :: (DomCartesian f, Dom f a, Dom f b) => f a -> f b -> f (a, b) Source #

_zipWith :: (Dom f a, Dom f b, Dom f c) => (a -> b -> c) -> f a -> f b -> f c Source #

_zipWith3 :: (Dom f a, Dom f b, Dom f c, Dom f d) => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source #

_zipWith4 :: (Dom f a, Dom f b, Dom f c, Dom f d, Dom f e) => (a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f e Source #

_zipAp :: (DomClosed f, Dom f a, Dom f b) => f (a -> b) -> f a -> f b Source #

class (CKeyed f, CZip f) => CZipWithKey f where Source #

Equivalent to the Zip class.

Methods

_izipWith :: (Dom f a, Dom f b, Dom f c) => (CKey f -> a -> b -> c) -> f a -> f b -> f c Source #

_izipWith3 :: (Dom f a, Dom f b, Dom f c, Dom f d) => (CKey f -> a -> b -> c -> d) -> f a -> f b -> f c -> f d Source #

_izipWith4 :: (Dom f a, Dom f b, Dom f c, Dom f d, Dom f e) => (CKey f -> a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f e Source #

class CFoldable f => CFoldableWithKey f where Source #

Equivalent to the FoldableWithKey class.

Methods

_itoList :: Dom f a => f a -> [(CKey f, a)] Source #

_ifoldMap :: (Monoid m, Dom f a) => (CKey f -> a -> m) -> f a -> m Source #

_ifoldr :: Dom f a => (CKey f -> a -> b -> b) -> b -> f a -> b Source #

_ifoldr' :: Dom f a => (CKey f -> a -> b -> b) -> b -> f a -> b Source #

_ifoldl :: Dom f b => (a -> CKey f -> b -> a) -> a -> f b -> a Source #

_ifoldl' :: Dom f b => (a -> CKey f -> b -> a) -> a -> f b -> a Source #

class (CKeyed t, CFoldableWithKey t, CTraversable t) => CTraversableWithKey t where Source #

Equivalent to the Traversable class.

Methods

_itraverse :: (Dom t a, Dom t b, Monad f) => (CKey t -> a -> f b) -> t a -> f (t b) Source #

class CFunctor f => CAdjustable f where Source #

Equivalent to the Adjustable class.

Methods

_update :: Dom f a => (a -> b -> a) -> f a -> [(CKey f, b)] -> f a Source #

_adjust :: Dom f a => (a -> a) -> CKey f -> f a -> f a Source #

_replace :: Dom f a => CKey f -> a -> f a -> f a Source #