Copyright | Anthony Wang 2021 |
---|---|
License | MIT |
Maintainer | anthony.y.wang.math@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
TwoCatOfCats
is a safe version of Internal.TwoCatOfCats
.
Please refer to the documentation for that module.
This module does not export the unsafe constructors
in Internal.TwoCatOfCats
, but does export the safe versions.
For example, CompositeFunctor :: ZeroGlobelet -> [Functor] -> Functor
is not exported,
but func_compose :: [Functor] -> Maybe Functor
is.
This is because one can use CompositeFunctor
to construct invalid composite functors.
See the documentation in Internal.TwoCatOfCats
for more details.
Synopsis
- data Category = Category {
- cat_id :: !String
- cat_displayString :: !String
- data ZeroGlobelet = ZeroGlobelet {
- glob0_source :: !Category
- glob0_target :: !Category
- data Functor = Functor !String !String !ZeroGlobelet !String
- func_boundary :: Functor -> ZeroGlobelet
- func_source :: Functor -> Category
- func_target :: Functor -> Category
- identityFunctor :: Category -> Functor
- func_composable :: [Functor] -> Bool
- func_compose :: [Functor] -> Maybe Functor
- data FuncCompositionError = FuncCompositionError [Int]
- func_compose_with_error :: [Functor] -> Except FuncCompositionError Functor
- func_to_single_composition :: Functor -> Functor
- func_to_single_list :: Functor -> [Functor]
- func_reduced_length :: Functor -> Int
- is_basic_func :: Functor -> Bool
- is_identity_func :: Functor -> Bool
- data OneGlobelet
- funcs_globeletable :: Functor -> Functor -> Bool
- funcs_to_globelet :: Functor -> Functor -> Maybe OneGlobelet
- glob1_pos :: OneGlobelet -> Category
- glob1_neg :: OneGlobelet -> Category
- data NaturalTransformation = NaturalTransformation !String !String !String !OneGlobelet !String
- nat_boundary :: NaturalTransformation -> OneGlobelet
- nat_source :: NaturalTransformation -> Functor
- nat_target :: NaturalTransformation -> Functor
- identityNaturalTransformation :: Functor -> NaturalTransformation
- nat_horz_compose :: [NaturalTransformation] -> Maybe NaturalTransformation
- data NatHorzCompositionError = NatHorzCompositionError [Int]
- nat_horz_compose_with_error :: [NaturalTransformation] -> Except NatHorzCompositionError NaturalTransformation
- nat_vert_compose :: [NaturalTransformation] -> Maybe NaturalTransformation
- nat_source_length :: NaturalTransformation -> Int
- nat_target_length :: NaturalTransformation -> Int
- is_basic_nt :: NaturalTransformation -> Bool
- is_identity_nt :: NaturalTransformation -> Bool
Documentation
A representation of a category.
Category | |
|
data ZeroGlobelet Source #
A ZeroGlobelet
is the structure representing the boundary of a functor (i.e.
1-morphism).
It consists of a source Category
and a target Category
.
ZeroGlobelet | |
|
Instances
Eq ZeroGlobelet Source # | |
Defined in Internal.TwoCatOfCats (==) :: ZeroGlobelet -> ZeroGlobelet -> Bool # (/=) :: ZeroGlobelet -> ZeroGlobelet -> Bool # | |
Show ZeroGlobelet Source # | |
Defined in Internal.TwoCatOfCats showsPrec :: Int -> ZeroGlobelet -> ShowS # show :: ZeroGlobelet -> String # showList :: [ZeroGlobelet] -> ShowS # |
A representation of a functor between categories.
Functor !String !String !ZeroGlobelet !String | A data structure specifying a new functor.
We shall call |
Instances
func_boundary :: Functor -> ZeroGlobelet Source #
A boundary globelet function which works for both basic and composite functors.
func_source :: Functor -> Category Source #
func_source
gives the source category of a functor.
func_target :: Functor -> Category Source #
func_target
gives the target category of a functor.
identityFunctor :: Category -> Functor Source #
identityFunctor
takes a category C
and returns the identity functor of
that category.
The identity functor is represented by a composite functor whose underlying
cfg_functorList
is empty.
func_composable :: [Functor] -> Bool Source #
func_composable
takes a list of functors and returns True
if the list of functors can be composed (without specifying additional information),
and False
otherwise.
func_composable
will return False
on an empty list, since a source (or target) category
needs to be specified.
Function composition is left to right, so [F,G] represents a composition of F : A -> B and
G : B -> C.
func_compose :: [Functor] -> Maybe Functor Source #
func_compose
takes a list of functors and returns Just
their composite if
func_composable
is True
and Nothing
if func_composable
is False
.
data FuncCompositionError Source #
FuncCompositionError
is the type of error which can be thrown by func_compose_with_error
.
FunctorCompositionError []
is the error for an empty composition.
Otherwise, an error is given by (FuncCompositionError list)
where list
is a list of positions
where the functors do not compose.
n
is in list
if the functors in positions n
and n+1
do not compose.
(Indexing starts at 0).
func_compose_with_error :: [Functor] -> Except FuncCompositionError Functor Source #
func_compose_with_error
takes a list of functors and composes them.
It throws a FuncCompositionError
describing why composition failed if
the functors in the list could not be composed.
func_to_single_composition :: Functor -> Functor Source #
func_to_single_composition
of f
gives a functor of the form (CompositeFunctor bd fl)
which is equal to f
,
where fl
is a list of basic functors.
func_to_single_list :: Functor -> [Functor] Source #
func_to_single_list
f
returns the empty list if f
is an identity functor.
Otherwise, it returns a list of basic functors whose composition is equal to f
.
func_reduced_length :: Functor -> Int Source #
func_reduced_length
returns the length of func_to_single_list
.
For example func_reduced_length
of an identity functor is 0,
while func_reduced_length
of a basic functor is 1.
is_basic_func :: Functor -> Bool Source #
is_basic_func
of a functor is True
if the functor is a basic functor,
and False
otherwise.
is_identity_func :: Functor -> Bool Source #
is_identity_func
of a functor is True
if the functor is an identity functor
and False
otherwise.
data OneGlobelet Source #
OneGlobelet
is the structure representing the boundary of a natural transformation
(i.e. 2-morphism).
(OneGlobelet s t)
represents a globelet with source functor s
and target functor t
,
and is assumed to satisfy the following axiom:
func_boundary s == func_boundary t
See funcs_to_globelet
for safe construction of OneGlobelet
s.
Instances
Show OneGlobelet Source # | |
Defined in Internal.TwoCatOfCats showsPrec :: Int -> OneGlobelet -> ShowS # show :: OneGlobelet -> String # showList :: [OneGlobelet] -> ShowS # |
funcs_globeletable :: Functor -> Functor -> Bool Source #
(funcs_globeletable source target)
is True
if the Functor
s
source
and target
have the same boundary globelet, i.e. they have
the same source category and the same target category,
and False
otherwise.
funcs_to_globelet :: Functor -> Functor -> Maybe OneGlobelet Source #
(funcs_to_globelet source target)
is Just
the
OneGlobelet
with source source
and target target
if
(funcs_globeletable source target)=True
, and Nothing
otherwise.
glob1_pos :: OneGlobelet -> Category Source #
glob1_pos
of a OneGlobelet
is equal to the source category
of the source functor of the OneGlobelet
.
Equivalently, it is equal to the source category of the target functor
of the OneGlobelet
.
We shall refer to this category as the positive pole
of the OneGlobelet
.
glob1_neg :: OneGlobelet -> Category Source #
glob1_neg
of a OneGlobelet
is equal to the target category
of the target functor of the OneGlobelet
.
Equivalently, it is equal to the target category of the source functor
of the OneGlobelet
.
We shall refer to this category as the negative pole
of the OneGlobelet
.
data NaturalTransformation Source #
A representation of a natural transformation between functors.
NaturalTransformation !String !String !String !OneGlobelet !String | A data structure specifying a new natural transformation.
We shall call natural transformations of the form
|
Instances
Show NaturalTransformation Source # | |
Defined in Internal.TwoCatOfCats showsPrec :: Int -> NaturalTransformation -> ShowS # show :: NaturalTransformation -> String # showList :: [NaturalTransformation] -> ShowS # | |
Structure NaturalTransformation Source # | |
nat_boundary :: NaturalTransformation -> OneGlobelet Source #
nat_boundary
of a natural transformation is its boundary globelet.
nat_source :: NaturalTransformation -> Functor Source #
nat_source
of a natural transformation is its source functor.
nat_target :: NaturalTransformation -> Functor Source #
nat_target
of a natural transforamtion is its target functor.
identityNaturalTransformation :: Functor -> NaturalTransformation Source #
identityNaturalTransformation
takes a Functor
as an argument and returns
its identity natural transformation.
The identity natural transformation is represented by a vertical composition
whose nt_vert_comp_list
is empty.
nat_horz_compose :: [NaturalTransformation] -> Maybe NaturalTransformation Source #
nat_horz_compose
takes a list of natural transformations and returns
Just
their horizontal composition if they are horizontally composable,
and Nothing
otherwise.
data NatHorzCompositionError Source #
NatHorzCompositionError
is the possible error thrown by nat_horz_compose_with_error
.
(NatHorzCompositionError [])
represents an empty horizontal composition.
Otherwise, an error is given by (NatHorzCompositionError list)
where
list
is a list of positions where the natural transformations do not
horizontally compose.
n
is in list
if the negative pole of the natural transformation in position
n
is not equal to the positive pole of the natural transformation in position
n+1
.
(Indexing starts at 0).
nat_horz_compose_with_error :: [NaturalTransformation] -> Except NatHorzCompositionError NaturalTransformation Source #
nat_horz_compose_with_error
takes a list of natural transformations and returns their
horizontal composition.
It throws a NatHorzCompositionError
describing why composition failed if the
list of natural transformations cannot be horizontally composed.
Composition is from left to right.
nat_vert_compose :: [NaturalTransformation] -> Maybe NaturalTransformation Source #
nat_vert_compose
takes a list of natural transformations and returns Just
their vertical
composition if the list is vertically composable, and Nothing
otherwise.
nat_source_length :: NaturalTransformation -> Int Source #
nat_source_length
of a natural transformation is the func_reduced_length
of its source
functor.
nat_target_length :: NaturalTransformation -> Int Source #
nat_target_length
of a natural transformation is the func_reduced_length
of its target
functor.
is_basic_nt :: NaturalTransformation -> Bool Source #
is_basic_nt
of a natural transformation is True
if the natural transformation is a
basic natural transformation, and false otherwise.
is_identity_nt :: NaturalTransformation -> Bool Source #
is_identity_nt
of a natural transformation is True
if the natural transformation
is the identity of some functor, and False
otherwise.