constraint-0.1.4.0: Reified constraints

Safe HaskellNone
LanguageHaskell2010

Data.Constraint.Lifting

Documentation

class Lifting c d f where Source #

Methods

lift :: c a :- d (f a) Source #

Instances
Lifting (c :: k2 -> Constraint) (Unconstrained1 :: k1 -> Constraint) (f :: k2 -> k1) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lift :: c a :- Unconstrained1 (f a) Source #

(forall a. Show a => c (f a)) => Lifting Show (c :: k -> Constraint) (f :: Type -> k) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lift :: Show a :- c (f a) Source #

(forall a. Read a => c (f a)) => Lifting Read (c :: k -> Constraint) (f :: Type -> k) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lift :: Read a :- c (f a) Source #

(forall a. Monoid a => c (f a)) => Lifting Monoid (c :: k -> Constraint) (f :: Type -> k) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lift :: Monoid a :- c (f a) Source #

(forall a. Semigroup a => c (f a)) => Lifting Semigroup (c :: k -> Constraint) (f :: Type -> k) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lift :: Semigroup a :- c (f a) Source #

(forall a. Bounded a => c (f a)) => Lifting Bounded (c :: k -> Constraint) (f :: Type -> k) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lift :: Bounded a :- c (f a) Source #

(forall a. Ord a => c (f a)) => Lifting Ord (c :: k -> Constraint) (f :: Type -> k) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lift :: Ord a :- c (f a) Source #

(forall a. Eq a => c (f a)) => Lifting Eq (c :: k -> Constraint) (f :: Type -> k) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lift :: Eq a :- c (f a) Source #

Lifting (Category :: (k -> k -> Type) -> Constraint) (Groupoid :: (k -> k -> Type) -> Constraint) (Iso :: (k -> k -> Type) -> k -> k -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lift :: Category a :- Groupoid (Iso a) Source #

Lifting (Functor s ((->) :: Type -> Type -> Type) :: (k2 -> Type) -> Constraint) (Functor (NT s :: (k1 -> k2) -> (k1 -> k2) -> Type) (NT ((->) :: Type -> Type -> Type) :: (k1 -> Type) -> (k1 -> Type) -> Type) :: ((k1 -> k2) -> k1 -> Type) -> Constraint) (Compose :: (k2 -> Type) -> (k1 -> k2) -> k1 -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lift :: Functor s (->) a :- Functor (NT s) (NT (->)) (Compose a) Source #