Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
class Semigroupoid (s :: α -> α -> Type) where Source #
Instances
Category s => Semigroupoid (s :: α -> α -> Type) Source # | |
Defined in Control.Category.Constrained | |
Semigroupoid k => Semigroupoid (Dual k :: α -> α -> Type) Source # | |
Semigroupoid (,) Source # | |
Defined in Control.Category.Constrained | |
Semigroupoid (Const :: Type -> Type -> Type) Source # | |
Semigroupoid s => Semigroupoid (NT s :: (k -> k) -> (k -> k) -> Type) Source # | |
class Semigroupoid s => Category s where Source #
Nothing
Instances
Category (:-) Source # | |
(Category s, Valid s ~ (Unconstrained1 :: α -> Constraint)) => Category (s :: α -> α -> Type) Source # | |
Category (Coercion :: α -> α -> Type) Source # | |
Category ((:~:) :: α -> α -> Type) Source # | |
Category ((:~~:) :: α -> α -> Type) Source # | |
Category k => Category (Dual k :: α -> α -> Type) Source # | |
Category ((->) :: Type -> Type -> Type) Source # | |
Category s => Category (NT s :: (k -> k) -> (k -> k) -> Type) Source # | |
class Category s => Groupoid s where Source #
Nothing
invert :: (Valid s a, Valid s b) => s a b -> s b a Source #
invert' :: Dict (Valid s a) -> Dict (Valid s b) -> s a b -> s b a Source #
Instances
(Groupoid s, Valid s ~ (Unconstrained1 :: α -> Constraint)) => Groupoid (s :: α -> α -> Type) Source # | |
Groupoid (Coercion :: α -> α -> Type) Source # | |
Groupoid ((:~:) :: α -> α -> Type) Source # | |
Groupoid ((:~~:) :: α -> α -> Type) Source # | |
Groupoid k => Groupoid (Dual k :: α -> α -> Type) Source # | |
Groupoid s => Groupoid (NT s :: (k -> k) -> (k -> k) -> Type) Source # | |
type family Valid (s :: α -> α -> Type) :: α -> Constraint Source #
Instances
type Valid (:-) Source # | |
Defined in Control.Category.Constrained | |
type Valid (Coercion :: α -> α -> Type) Source # | |
Defined in Control.Category.Constrained | |
type Valid ((:~:) :: α -> α -> Type) Source # | |
Defined in Control.Category.Constrained | |
type Valid ((:~~:) :: α -> α -> Type) Source # | |
Defined in Control.Category.Constrained | |
type Valid (Dual k :: α -> α -> Type) Source # | |
Defined in Control.Category.Constrained | |
type Valid ((->) :: Type -> Type -> Type) Source # | |
Defined in Control.Category.Constrained | |
type Valid (NT s :: (k -> k) -> (k -> k) -> Type) Source # | |
Defined in Control.Category.Constrained |
Instances
Functor ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) Either Source # | |
Defined in Data.Functor.Constrained | |
Functor ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (,) Source # | |
Defined in Data.Functor.Constrained | |
SGM ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) Either Source # | |
SGM ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (,) Source # | |
Functor ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (Const :: Type -> Type -> Type) Source # | |
Defined in Data.Functor.Constrained | |
SGM ((->) :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (Const :: Type -> Type -> Type) Source # | |
Category s => Functor (Dual s :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (s :: Type -> Type -> Type) Source # | |
Defined in Data.Functor.Constrained | |
Semigroupoid s => SGM (Dual s :: Type -> Type -> Type) (NT ((->) :: Type -> Type -> Type)) (s :: Type -> Type -> Type) Source # | |
Groupoid s => Groupoid (NT s :: (k -> k) -> (k -> k) -> Type) Source # | |
Category s => Category (NT s :: (k -> k) -> (k -> k) -> Type) Source # | |
Semigroupoid s => Semigroupoid (NT s :: (k -> k) -> (k -> k) -> Type) Source # | |
Functor (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
Defined in Data.Functor.Constrained | |
Functor (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
Defined in Data.Functor.Constrained | |
SGM (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
SGM (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
Functor (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
Defined in Data.Functor.Constrained | |
Functor (NT ((->) :: Type -> Type -> Type)) (NT ((->) :: Type -> Type -> Type)) (Product f :: (Type -> Type) -> Type -> Type) Source # | |
Defined in Data.Functor.Constrained | |
Functor (NT ((->) :: Type -> Type -> Type)) (NT ((->) :: Type -> Type -> Type)) (Sum f :: (Type -> Type) -> Type -> Type) Source # | |
Defined in Data.Functor.Constrained | |
SGM (NT ((->) :: Type -> Type -> Type)) (NT (NT ((->) :: Type -> Type -> Type))) (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
SGM (NT ((->) :: Type -> Type -> Type)) (NT ((->) :: Type -> Type -> Type)) (Product f :: (Type -> Type) -> Type -> Type) Source # | |
SGM (NT ((->) :: Type -> Type -> Type)) (NT ((->) :: Type -> Type -> Type)) (Sum f :: (Type -> Type) -> Type -> Type) Source # | |
(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 # | |
Defined in Data.Functor.Constrained | |
(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 # | |
type Valid (NT s :: (k -> k) -> (k -> k) -> Type) Source # | |
Defined in Control.Category.Constrained |