FiniteCategories-0.6.4.0: Finite categories and usual categorical constructions on them.
CopyrightGuillaume Sabbagh 2022
LicenseGPL-3
Maintainerguillaumesabbagh@protonmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Math.Categories.Opposite

Description

Each Category has an opposite one where morphisms are reversed.

Synopsis

Documentation

data OpMorphism m Source #

An OpMorphism is a morphism where source and target are reversed.

Constructors

OpMorphism m 

Instances

Instances details
PrettyPrint m => PrettyPrint (OpMorphism m) Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

pprint :: Int -> OpMorphism m -> String Source #

pprintWithIndentations :: Int -> Int -> String -> OpMorphism m -> String Source #

pprintIndent :: Int -> OpMorphism m -> String Source #

Simplifiable m => Simplifiable (OpMorphism m) Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

simplify :: OpMorphism m -> OpMorphism m #

Generic (OpMorphism m) Source # 
Instance details

Defined in Math.Categories.Opposite

Associated Types

type Rep (OpMorphism m) :: Type -> Type

Methods

from :: OpMorphism m -> Rep (OpMorphism m) x

to :: Rep (OpMorphism m) x -> OpMorphism m

Show m => Show (OpMorphism m) Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

showsPrec :: Int -> OpMorphism m -> ShowS

show :: OpMorphism m -> String

showList :: [OpMorphism m] -> ShowS

Eq m => Eq (OpMorphism m) Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

(==) :: OpMorphism m -> OpMorphism m -> Bool

(/=) :: OpMorphism m -> OpMorphism m -> Bool

Morphism m o => Morphism (OpMorphism m) o Source # 
Instance details

Defined in Math.Categories.Opposite

(Category c m o, Morphism m o) => Category (Op c) (OpMorphism m) o Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

identity :: Op c -> o -> OpMorphism m Source #

ar :: Op c -> o -> o -> Set (OpMorphism m) Source #

genAr :: Op c -> o -> o -> Set (OpMorphism m) Source #

decompose :: Op c -> OpMorphism m -> [OpMorphism m] Source #

(FiniteCategory c m o, Morphism m o) => FiniteCategory (Op c) (OpMorphism m) o Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

ob :: Op c -> Set o Source #

type Rep (OpMorphism m) Source # 
Instance details

Defined in Math.Categories.Opposite

type Rep (OpMorphism m) = D1 ('MetaData "OpMorphism" "Math.Categories.Opposite" "FiniteCategories-0.6.4.0-inplace" 'False) (C1 ('MetaCons "OpMorphism" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m)))

opOpMorphism :: OpMorphism m -> m Source #

Return the original morphism given an OpMorphism.

data Op c Source #

The Op operator gives the opposite of a Category.

Constructors

Op c 

Instances

Instances details
PrettyPrint c => PrettyPrint (Op c) Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

pprint :: Int -> Op c -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Op c -> String Source #

pprintIndent :: Int -> Op c -> String Source #

Simplifiable c => Simplifiable (Op c) Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

simplify :: Op c -> Op c #

Generic (Op c) Source # 
Instance details

Defined in Math.Categories.Opposite

Associated Types

type Rep (Op c) :: Type -> Type

Methods

from :: Op c -> Rep (Op c) x

to :: Rep (Op c) x -> Op c

Show c => Show (Op c) Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

showsPrec :: Int -> Op c -> ShowS

show :: Op c -> String

showList :: [Op c] -> ShowS

Eq c => Eq (Op c) Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

(==) :: Op c -> Op c -> Bool

(/=) :: Op c -> Op c -> Bool

(Category c m o, Morphism m o) => Category (Op c) (OpMorphism m) o Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

identity :: Op c -> o -> OpMorphism m Source #

ar :: Op c -> o -> o -> Set (OpMorphism m) Source #

genAr :: Op c -> o -> o -> Set (OpMorphism m) Source #

decompose :: Op c -> OpMorphism m -> [OpMorphism m] Source #

(FiniteCategory c m o, Morphism m o) => FiniteCategory (Op c) (OpMorphism m) o Source # 
Instance details

Defined in Math.Categories.Opposite

Methods

ob :: Op c -> Set o Source #

type Rep (Op c) Source # 
Instance details

Defined in Math.Categories.Opposite

type Rep (Op c) = D1 ('MetaData "Op" "Math.Categories.Opposite" "FiniteCategories-0.6.4.0-inplace" 'False) (C1 ('MetaCons "Op" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c)))

opOp :: Op c -> c Source #

Return the original category given an Op category.