constrained-category-0.1.0.0: Constrained Categories

Safe HaskellNone
LanguageHaskell2010

Data.Functor.Constrained

Synopsis

Documentation

class (Semigroupoid s, Semigroupoid t) => SGM (s :: α -> α -> *) (t :: β -> β -> *) (f :: α -> β) where Source #

Laws:

map (f  g) = map f  map g

Methods

map :: s a b -> t (f a) (f b) Source #

Instances
SGM (:-) ((->) :: Type -> Type -> Type) Dict Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: (a :- b) -> Dict a -> Dict b Source #

Semigroupoid s => SGM (s :: α -> α -> Type) ((->) :: Type -> Type -> Type) (s a :: α -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: s a0 b -> s a a0 -> s a b Source #

Semigroupoid s => SGM (s :: α -> α -> Type) ((->) :: Type -> Type -> Type) (Proxy :: α -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: s a b -> Proxy a -> Proxy b Source #

Semigroupoid s => SGM (s :: α -> α -> Type) ((->) :: Type -> Type -> Type) (Const a :: α -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: s a0 b -> Const a a0 -> Const a b Source #

(SGM s ((->) :: Type -> Type -> Type) f, SGM s ((->) :: Type -> Type -> Type) g) => SGM (s :: k -> k -> Type) ((->) :: Type -> Type -> Type) (Product f g :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: s a b -> Product f g a -> Product f g b Source #

(SGM s ((->) :: Type -> Type -> Type) f, SGM s ((->) :: Type -> Type -> Type) g) => SGM (s :: k -> k -> Type) ((->) :: Type -> Type -> Type) (Sum f g :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: s a b -> Sum f g a -> Sum f g b Source #

Functor f => SGM ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (f :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: (a -> b) -> f a -> f b Source #

SGM ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: (a -> b) -> Identity a -> Identity b Source #

SGM ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Either a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: (a0 -> b) -> Either a a0 -> Either a b Source #

SGM ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: (a0 -> b) -> (a, a0) -> (a, b) Source #

SGM ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) Either Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: (a -> b) -> NT (->) (Either a) (Either b) Source #

SGM ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (,) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: (a -> b) -> NT (->) ((,) a) ((,) b) Source #

SGM ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: (a -> b) -> NT (->) (Const a) (Const b) Source #

Semigroupoid s => SGM (Dual s :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (s :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: Dual s a b -> NT (->) (s a) (s b) Source #

SGM (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: NT (->) a b -> NT (NT (->)) (Product a) (Product b) Source #

SGM (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: NT (->) a b -> NT (NT (->)) (Sum a) (Sum b) Source #

SGM (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: NT (->) a b -> NT (NT (->)) (Compose a) (Compose b) Source #

SGM (NT ((->) :: Type -> Type -> Type)) (NT ((->) :: Type -> Type -> Type)) (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: NT (->) a b -> NT (->) (Product f a) (Product f b) Source #

SGM (NT ((->) :: Type -> Type -> Type)) (NT ((->) :: Type -> Type -> Type)) (Sum f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: NT (->) a b -> NT (->) (Sum f a) (Sum f b) Source #

(SGM s ((->) :: Type -> Type -> Type) f, Valid s ~ (Unconstrained1 :: Type -> Constraint)) => SGM (NT s :: (Type -> Type) -> (Type -> Type) -> Type) (NT ((->) :: Type -> Type -> Type)) (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

map :: NT s a b -> NT (->) (Compose f a) (Compose f b) Source #

class (SGM s t f, Category s, Category t) => Functor s t f Source #

Laws:

map id = id
Instances
Functor (:-) ((->) :: Type -> Type -> Type) Dict Source # 
Instance details

Defined in Data.Functor.Constrained

Category s => Functor (s :: α -> α -> Type) ((->) :: Type -> Type -> Type) (s a :: α -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Category s => Functor (s :: α -> α -> Type) ((->) :: Type -> Type -> Type) (Proxy :: α -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Category s => Functor (s :: α -> α -> Type) ((->) :: Type -> Type -> Type) (Const a :: α -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

(Functor s ((->) :: Type -> Type -> Type) f, Functor s ((->) :: Type -> Type -> Type) g) => Functor (s :: k -> k -> Type) ((->) :: Type -> Type -> Type) (Product f g :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

(Functor s ((->) :: Type -> Type -> Type) f, Functor s ((->) :: Type -> Type -> Type) g) => Functor (s :: k -> k -> Type) ((->) :: Type -> Type -> Type) (Sum f g :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Functor f => Functor ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (f :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Functor ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Data.Functor.Constrained

Functor ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Either a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Functor ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Functor ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) Either Source # 
Instance details

Defined in Data.Functor.Constrained

Functor ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (,) Source # 
Instance details

Defined in Data.Functor.Constrained

Functor ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Category s => Functor (Dual s :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (s :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Functor (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Functor (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Functor (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Functor (NT ((->) :: Type -> Type -> Type)) (NT ((->) :: Type -> Type -> Type)) (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Functor (NT ((->) :: Type -> Type -> Type)) (NT ((->) :: Type -> Type -> Type)) (Sum f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

(Functor s ((->) :: Type -> Type -> Type) f, Valid s ~ (Unconstrained1 :: Type -> Constraint)) => Functor (NT s :: (Type -> Type) -> (Type -> Type) -> Type) (NT ((->) :: Type -> Type -> Type)) (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

(<$>) :: SGM s (->) f => s a b -> f a -> f b infixl 4 Source #