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.FiniteCategories.Square

Description

The Square category contains 4 generating arrows forming a square. It has 6 non identity arrows.

Synopsis

Documentation

data SquareOb Source #

Objects of the Square category.

Constructors

SquareA 
SquareB 
SquareC 
SquareD 

Instances

Instances details
PrettyPrint SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

pprint :: Int -> SquareOb -> String Source #

pprintWithIndentations :: Int -> Int -> String -> SquareOb -> String Source #

pprintIndent :: Int -> SquareOb -> String Source #

Simplifiable SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

Generic SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

Associated Types

type Rep SquareOb :: Type -> Type

Methods

from :: SquareOb -> Rep SquareOb x

to :: Rep SquareOb x -> SquareOb

Show SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

showsPrec :: Int -> SquareOb -> ShowS

show :: SquareOb -> String

showList :: [SquareOb] -> ShowS

Eq SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

(==) :: SquareOb -> SquareOb -> Bool

(/=) :: SquareOb -> SquareOb -> Bool

Morphism SquareAr SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

Category Square SquareAr SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

FiniteCategory Square SquareAr SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

ob :: Square -> Set SquareOb Source #

type Rep SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

type Rep SquareOb = D1 ('MetaData "SquareOb" "Math.FiniteCategories.Square" "FiniteCategories-0.6.4.0-inplace" 'False) ((C1 ('MetaCons "SquareA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SquareB" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SquareC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SquareD" 'PrefixI 'False) (U1 :: Type -> Type)))

data SquareAr Source #

Morphisms of the Square category.

Instances

Instances details
PrettyPrint SquareAr Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

pprint :: Int -> SquareAr -> String Source #

pprintWithIndentations :: Int -> Int -> String -> SquareAr -> String Source #

pprintIndent :: Int -> SquareAr -> String Source #

Simplifiable SquareAr Source # 
Instance details

Defined in Math.FiniteCategories.Square

Generic SquareAr Source # 
Instance details

Defined in Math.FiniteCategories.Square

Associated Types

type Rep SquareAr :: Type -> Type

Methods

from :: SquareAr -> Rep SquareAr x

to :: Rep SquareAr x -> SquareAr

Show SquareAr Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

showsPrec :: Int -> SquareAr -> ShowS

show :: SquareAr -> String

showList :: [SquareAr] -> ShowS

Eq SquareAr Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

(==) :: SquareAr -> SquareAr -> Bool

(/=) :: SquareAr -> SquareAr -> Bool

Morphism SquareAr SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

Category Square SquareAr SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

FiniteCategory Square SquareAr SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

ob :: Square -> Set SquareOb Source #

type Rep SquareAr Source # 
Instance details

Defined in Math.FiniteCategories.Square

type Rep SquareAr = D1 ('MetaData "SquareAr" "Math.FiniteCategories.Square" "FiniteCategories-0.6.4.0-inplace" 'False) (((C1 ('MetaCons "SquareIdA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SquareIdB" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SquareIdC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SquareIdD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SquareF" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "SquareG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SquareH" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SquareI" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SquareFH" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SquareGI" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Square Source #

The Square category.

Constructors

Square 

Instances

Instances details
PrettyPrint Square Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

pprint :: Int -> Square -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Square -> String Source #

pprintIndent :: Int -> Square -> String Source #

Simplifiable Square Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

simplify :: Square -> Square #

Generic Square Source # 
Instance details

Defined in Math.FiniteCategories.Square

Associated Types

type Rep Square :: Type -> Type

Methods

from :: Square -> Rep Square x

to :: Rep Square x -> Square

Show Square Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

showsPrec :: Int -> Square -> ShowS

show :: Square -> String

showList :: [Square] -> ShowS

Eq Square Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

(==) :: Square -> Square -> Bool

(/=) :: Square -> Square -> Bool

Category Square SquareAr SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

FiniteCategory Square SquareAr SquareOb Source # 
Instance details

Defined in Math.FiniteCategories.Square

Methods

ob :: Square -> Set SquareOb Source #

type Rep Square Source # 
Instance details

Defined in Math.FiniteCategories.Square

type Rep Square = D1 ('MetaData "Square" "Math.FiniteCategories.Square" "FiniteCategories-0.6.4.0-inplace" 'False) (C1 ('MetaCons "Square" 'PrefixI 'False) (U1 :: Type -> Type))