| Copyright | Anthony Wang 2021 |
|---|---|
| License | MIT |
| Maintainer | anthony.y.wang.math@gmail.com |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Internal.FormattingData
Description
Internal.FormattingData defines data structures relating to the placement
of functors on a TikZ canvas when drawing a string diagram.
Synopsis
- data FunctorFormatting = FunctorFormatting {
- ff_length :: !Int
- ff_positions_list :: ![Int]
- ff_num_positions :: FunctorFormatting -> Int
- ff_operad_compose :: FunctorFormatting -> [FunctorFormatting] -> Maybe FunctorFormatting
- default_ff :: Functor -> FunctorFormatting
- type NatFormatting = [FunctorFormatting]
- nf_max_horz_position :: NatFormatting -> Int
- nf_pos_to_coord :: NatFormatting -> (Int, Int) -> Maybe (Float, Float)
- nf_pos_to_tikz_coord :: NatFormatting -> (Int, Int) -> Maybe TikzPathOperation
- pos_to_internal_name :: (Int, Int) -> String
- pos_to_named_coord :: (Int, Int) -> TikzCoordinate
- array_of_tikz_coords :: NatFormatting -> Array (Int, Int) (Maybe TikzPathOperation)
- get_nt_in_pos :: NaturalTransformation -> (Int, Int) -> Maybe NaturalTransformation
- nt_nf_pos_to_coord :: NaturalTransformation -> NatFormatting -> (Int, Int) -> Maybe (Float, Float)
- nt_nf_pos_to_nt_node :: NaturalTransformation -> NatFormatting -> (Int, Int) -> Maybe TikzPathOperation
- nt_pos_to_internal_name :: (Int, Int) -> String
- nt_pos_to_named_coord :: (Int, Int) -> TikzCoordinate
- nt_max_pos_dimensions :: NaturalTransformation -> (Int, Int)
- array_of_tikz_nt_nodes :: NaturalTransformation -> NatFormatting -> Array (Int, Int) (Maybe TikzPathOperation)
- data FunctorStringElement
- = FunctorElement (Int, Int)
- | NatElement (Int, Int)
- data FunctorStringData = FunctorStringData {}
- fse_get_named_coord :: FunctorStringElement -> TikzCoordinate
- fse_is_nat_elem :: FunctorStringElement -> Bool
- fsd_head_position :: FunctorStringData -> Maybe (Int, Int)
- fsd_tail_position :: FunctorStringData -> Maybe (Int, Int)
- fsd_combinable :: FunctorStringData -> FunctorStringData -> Bool
- fsd_combine :: FunctorStringData -> FunctorStringData -> FunctorStringData
- fsd_append :: FunctorStringData -> FunctorStringElement -> FunctorStringData
- fsd_prepend :: FunctorStringElement -> FunctorStringData -> FunctorStringData
- basic_func_to_fsd :: Functor -> (Int, Int) -> FunctorStringData
- type OrderedFSDList = [FunctorStringData]
- func_to_fsds :: Functor -> Int -> Int -> OrderedFSDList
- fsds_amalg :: OrderedFSDList -> OrderedFSDList -> OrderedFSDList
- nt_to_functor_strings :: NaturalTransformation -> OrderedFSDList
- nt_to_functor_strings_helper :: NaturalTransformation -> Int -> Int -> Int -> Int -> [FunctorStringData]
- fsd_get_mid :: [FunctorStringElement] -> (Int, Float)
- fsd_lengths :: [FunctorStringElement] -> [Int]
- seg_length :: FunctorStringElement -> FunctorStringElement -> Int
- fe_from_top_offset :: NatFormatting -> (Int, Int) -> Maybe TikzCoordinate
- fe_from_bot_offset :: NatFormatting -> (Int, Int) -> Maybe TikzCoordinate
- fse_fse_to_curve_op :: NatFormatting -> FunctorStringElement -> FunctorStringElement -> Maybe TikzPathOperation
- fsd_to_tikz_path :: NatFormatting -> FunctorStringData -> TikzPath
- fsd_to_tikz_path_helper :: (Int, Float) -> NatFormatting -> [FunctorStringElement] -> String -> String -> [Maybe TikzPathOperation]
Documentation
data FunctorFormatting Source #
FunctorFormatting is a data structure that specifies the spacing
for a composite of basic functors on a horizontal line.
The ff_length is the total length of the line.
The ff_positions_list is the collection of indices where a functor is placed.
The ff_positions_list is indexed starting at 0.
For example, if we use (FunctorFormatting 5 [1,2,4]) to
format a composition F G H (composing from left to right as is our convention),
we would get the spacing
& F & G & & H,
while using (FunctorFormatting 4 [0,1,3]) to format the same list would give the spacing
F & G & & H.
The notation for the spacing above is similar to how spacing is defined in LaTeX, i.e. in tables, arrays, etc.
Assumptions on the data: ff_positions_list is an increasing list of nonnegative integers.
The largest element in ff_positions_list, if it exists, is at most ff_length - 1.
Constructors
| FunctorFormatting | |
Fields
| |
Instances
| Eq FunctorFormatting Source # | |
Defined in Internal.FormattingData Methods (==) :: FunctorFormatting -> FunctorFormatting -> Bool # (/=) :: FunctorFormatting -> FunctorFormatting -> Bool # | |
| Show FunctorFormatting Source # | A show function which is easier to understand than the default one. If the If the For example |
Defined in Internal.FormattingData Methods showsPrec :: Int -> FunctorFormatting -> ShowS # show :: FunctorFormatting -> String # showList :: [FunctorFormatting] -> ShowS # | |
ff_num_positions :: FunctorFormatting -> Int Source #
ff_num_positions of a FunctorFormatting is equal to the func_reduced_length
of a functor which it can format, i.e. it is the length of func_positions_list.
ff_operad_compose :: FunctorFormatting -> [FunctorFormatting] -> Maybe FunctorFormatting Source #
Data of type FunctorFormatting naturally form an operad, with each FunctorFormatting
giving an n-ary operation where n is equal to the number of positions given by
ff_num_positions.
If ff is a FunctorFormatting with n=(ff_num_positions ff), and
[ff1, ..., ffn] is a list of n FunctorFormattings, then
we can get a composite FunctorFormatting by putting ff1 at the first position
in ff,..., and ffn at the nth position in ff.
For example:
If ff is the formatting "*&*&*&*"
and ff1,...,ff4 are all empty, then ff_operad_compose ff [ff1,ff2,ff3,ff4]
is empty.
If ff is the formatting represented by "*& &*& ", ff1 is the formatting "*& &*" and
ff2 is the formatting "*&*&*& ", then
ff_operad_compose ff [ff1,ff2] is "*& &*& &*&*&*& & ".
(ff_operad_compose ff ffs) is equal to Nothing if the length of ffs is not equal to
(ff_num_positions ff).
Otherwise, it returns Just the above composition.
default_ff :: Functor -> FunctorFormatting Source #
If f is a Functor with func_reduced_length f equal to n,
then default_ff f is the formatting "*&*&...&*" where there are n total positions.
type NatFormatting = [FunctorFormatting] Source #
A data structure to specify the location of functors when creating a string diagram from a natural transformation.
We will not attempt to format every possible NaturalTransformation,
but will only format a certain subcollection.
Roughly speaking, we can format natural transformations that can be thought of as vertical
compositions of horizontal compositions of basic natural transformations.
We will only format the following types of NaturalTransformation
(NaturalTransformation n d s b o)can be formatted with a length 2 list[ff1, ff2]ofFunctorFormattingwhere(ff_num_positions ff1)is equal tofunc_reduced_lengthof the source functor,(ff_num_positions ff2)is equal tofunc_reduced_lengthof the target functor, and at least one of(ff_num_positions ff1)or(ff_num_positions ff2)is nonzero.- Identity natural transformations of an identity functor of a category
c, i.e.(NatTransVerticalComposite (OneGlobelet (CompositeFunctor (ZeroGlobelet c c) []) (CompositeFunctor (ZeroGlobelet c c) [])) [])can be formatted with a length 2 list[ff1,ff2]of FunctorFormatting with(ff_num_positions ff1)and(ff_num_positions ff2)both equal to 0 - Identity natural transformations of a functor
i.e.
(NatTransVerticalComposite (OneGlobelet (Functor i d b o) (Functor i d b o)) [])can be formatted with a length 2 list[ff1,ff2]of FunctorFormatting with(ff_num_positions ff1)and(ff_num_positions ff2)both equal to 1 - Horizontal composites of natural transformations of type 1,2,3 above
i.e.
(NatTransHorizontalComposite g list)where list is a list of natural transformations of types 1,2,3 above, can be formatted with a length 2 list[ff1, ff2]of FunctorFormatting, whereff_num_positions ff1is equal tofunc_reduced_lengthof the source functor, andff_num_positions ff2is equal tofunc_reduced_lengthof the target functor. - Vertical composites of natural transformations of type 1,2,3,4,
i.e.
(NatTransVerticalComposite g list)where list is a nonempty list of natural transformations of types 1,2,3,4 above, can be formatted with a lengthl+1list[ff_0, ... , ff_l]ofFunctorFormatting, wherelis the length oflist, whereff_num_positionsofff_iis equal tofunc_reduced_lengthof the source oflist!!ior thefunc_reduced_lengthof the target oflist!!(i-1), whichever is defined (these two are equal when both are defined by our assumptions onNatTransVerticalComposite).
nf_max_horz_position :: NatFormatting -> Int Source #
nf_max_horz_position of a NatFormatting gives the largest ff_num_positions
among the FunctorFormatting in the list.
nf_pos_to_coord :: NatFormatting -> (Int, Int) -> Maybe (Float, Float) Source #
nf_pos_to_coord takes a NatFormatting nt and a pair (x,y) representing
the position of a basic natural transformation in a natural transformation
which can be formatted by nt, and returns Just the associated coordinate on a TikZ canvas,
if possible.
It returns Nothing if (x,y) does not specify a valid position in a natural transformation
which can be formatted by nt.
Here, x represents the row and y represents the position in the row, with indexing starting
at 0.
nf_pos_to_coord will return Nothing unless the following are satisfied:
xis between0and(length nf)-1, inclusiveyis between0and(ff_num_positions (nf!!x))-1, inclusive.
nf_pos_to_tikz_coord :: NatFormatting -> (Int, Int) -> Maybe TikzPathOperation Source #
nf_pos_to_tikz_coord returns Just the TikZ coordinate path
operation at nf_pos_to_coord, with the coordinate named by
pos_to_internal_name.
It returns Nothing if nf_pos_to_coord returns Nothing.
pos_to_internal_name :: (Int, Int) -> String Source #
pos_to_internal_name converts a position (x,y) described by the documentation
for nf_pos_to_coord and converts it into a String for referencing purposes inside a TikZ
picture.
pos_to_named_coord :: (Int, Int) -> TikzCoordinate Source #
pos_to_named_coord gives the named TikzCoordinate with name given by
pos_to_internal_name.
This named coordinate can be used to refer to the TikzPathOp
coordinate given by nf_pos_to_coord.
array_of_tikz_coords :: NatFormatting -> Array (Int, Int) (Maybe TikzPathOperation) Source #
array_of_tikz_coords takes a NatFormatting nf and returns the array
which maps (x,y) to nf_pos_to_tikz_coord nf (x,y).
The bounds of the array are from (0,0) to ((length nf)-1,(nf_max_horz_position nf)-1).
get_nt_in_pos :: NaturalTransformation -> (Int, Int) -> Maybe NaturalTransformation Source #
(get_nt_in_pos nt (x,y)) will return Just the yth basic natural transformation
in the xth row.
It returns Nothing if x does not specify a row of the natural transformation or y<0 or y>= the number of
basic natural transformations in the xth row.
We assume nt is assumed to be one of the 5 types of natural transformations which we can format,
described in the documentation for NatFormatting.
It makes sense to think of such nt as vertical composites of horizontal composites of natural
transformations.
x specifies the index in the vertical composite, while y specifies the index in the
horizontal composite, with indexing starting at 0.
nt_nf_pos_to_coord :: NaturalTransformation -> NatFormatting -> (Int, Int) -> Maybe (Float, Float) Source #
(get_nt_pos_to_coord nt nf (x,y)) will calculate the TikZ coordinates the basic natural
tranformation (get_nt_in_pos nt (x,y)) should be placed at.
It returns
Just the coordinates if (get_nt_in_pos nt (x,y) is not Nothing,
and Nothing otherwise.
nt is assumed to be one of the natural transformations we can format,
and nf is assumed to be a NatFormatting which can be used to format nt.
The TikZ coordinates of the basic natural transformation (get_nt_in_pos nt (x,y))
is based on the TikZ coordinates of the basic functors in its source and target.
nt_nf_pos_to_nt_node :: NaturalTransformation -> NatFormatting -> (Int, Int) -> Maybe TikzPathOperation Source #
nt_nf_pos_to_nt_node gives Just the TikZ node path operation with a node created at
nt_nf_pos_to_coord with name given by nt_pos_to_internal_name.
It returns Nothing if nt_nf_pos_to_coord returns Nothing.
nt_pos_to_internal_name :: (Int, Int) -> String Source #
nt_pos_to_internal_name converts a position (x,y) as described by get_nt_in_pos
and creates a String for referencing purposes inside a TikZ picture.
nt_pos_to_named_coord :: (Int, Int) -> TikzCoordinate Source #
nt_pos_to_named_coord gives the named TikzCoordinate with name given by
nf_pos_to_internal_name.
This named coordinate can be used to refer to the TikzPathOp node given by
nt_nf_pos_to_nt_node.
nt_max_pos_dimensions :: NaturalTransformation -> (Int, Int) Source #
nt_max_pos_dimensions takes one of the 5 types of NaturalTransformation
we can format (described by the documentation for NatFormatting) and returns
(x,y).
If our natural transformation is viewed as a vertical composite of horizontal composites
of basic natural transformations, x will equal the number of horizontal composites which
are being composed vertically, and y will be the maximum number of basic natural
transformations in a horizontal composite.
array_of_tikz_nt_nodes :: NaturalTransformation -> NatFormatting -> Array (Int, Int) (Maybe TikzPathOperation) Source #
(array_of_tikz_nt_nodes nt nf) is the array mapping pairs (x,y)
to the TikZ node path operation (nt_nf_pos_to_nt_node nt nf (x,y)).
If (nt_max_pos_dimensions nt) is equal to (a,b), then the bounds of the array
are (0,0) to (a-1,b-1).
data FunctorStringElement Source #
A FunctorStringElement is either
a (FunctorElement (x,y)), where (x,y) can be converted to coordinates on a TikZ picture
using nf_pos_to_coord (after specifying a NatFormatting)
or a (NatElement (x,y)), where (x,y) can be converted to coordinates in a TikZ picture
using nt_nf_pos_to_coord (after specifying a NaturalTransformation and NatFormatting
which can be used to format the NaturalTransformation).
Constructors
| FunctorElement (Int, Int) | |
| NatElement (Int, Int) |
Instances
| Show FunctorStringElement Source # | |
Defined in Internal.FormattingData Methods showsPrec :: Int -> FunctorStringElement -> ShowS # show :: FunctorStringElement -> String # showList :: [FunctorStringElement] -> ShowS # | |
data FunctorStringData Source #
A FunctorStringData represents a string in a string diagram.
It consists of a list fsd_list_of_elements, which is a list of FunctorStringElement
which the string goes between, fsd_display_string which is LaTeX code for labeling the string,
and fsd_options which is LaTeX code for options when labeling the string.
If the first element of the fsd_list_of_elements is of the form (FunctorElement (x,y)),
the string in the string diagram starts from the top of the diagram, at the position specified by
the FunctorElement.
If the first element of the list is of the form (NatElement (x,y)),
the string starts at a basic natural transformation at the position
specified by the NatElement.
A similar statement holds for lists ending with FunctorElement or NatElement.
All other positions on the list (i.e. not the first and not the last)
are occupied by a (FunctorElement (x,y)) representing positions where the string will pass
through.
The following assumptions on fsd_list_of_elements are assumed to hold:
- All but possibly the first and the last element on the list are of the form
(FunctorElement (x,y)). - The list contains at least one element of the form
(FunctorElement (x,y)). - If
(FunctorElement (x,y))and(FunctorElement (z,w))are consecutive elements of the list, thenzis equal tox+1. - If
(NatElement (x,y))is the first element of the list and is followed by(FunctorElement (z,w))thenzis equal tox+1. - If
(NatElement (x,y))is the last element of the list and is preceded by(FunctorElement (z,w))thenxis equal toz.
Constructors
| FunctorStringData | |
Fields | |
Instances
| Show FunctorStringData Source # | |
Defined in Internal.FormattingData Methods showsPrec :: Int -> FunctorStringData -> ShowS # show :: FunctorStringData -> String # showList :: [FunctorStringData] -> ShowS # | |
fse_get_named_coord :: FunctorStringElement -> TikzCoordinate Source #
fse_get_named_coord gives the named coordinate associated to
a FunctorStringelement.
It either calls pos_to_named_coord in the case of FunctorElement,
or it calls nt_pos_to_named_coord in the case of NatElement.
fse_is_nat_elem :: FunctorStringElement -> Bool Source #
fse_is_nat_elem returns True if the FunctorStringElement
is of the form (NatElement (x,y)) and False otherwise.
fsd_head_position :: FunctorStringData -> Maybe (Int, Int) Source #
fsd_head_position is Just (x,y) when the first element in
the fsd_list_of_elements of the given
FunctorStringData is (FunctorElement (x,y)), otherwise it is
Nothing.
fsd_tail_position :: FunctorStringData -> Maybe (Int, Int) Source #
fsd_tail_position is Just (x,y) when the last element in
the fsd_list_of_elements of the given
FunctorStringData is (FunctorElement (x,y)), otherwise it is
Nothing.
fsd_combinable :: FunctorStringData -> FunctorStringData -> Bool Source #
fsd_combinable is a Boolean value which tells whether two
FunctorStringData
can be combined together to form a longer FunctorStringData.
Explicitly, it returns True if the last element in
fsd_list_of_elements of the first FunctorStringData is of the form
(FunctorElement (x,y)) and is equal to the first
elementin fsd_list_of_elements of the second FunctorStringData.
fsd_combine :: FunctorStringData -> FunctorStringData -> FunctorStringData Source #
If (fsd_combinable fsd1 fsd2) is True, (fsd_combine fsd1 fsd2)
is the FunctorStringData gotten by combining the fsd_list_of_elements of fsd1 and fsd2,
which is done by identifying the common last element of of the first list with the first
element of the second.
The display string and options are taken from fsd1.
fsd_append :: FunctorStringData -> FunctorStringElement -> FunctorStringData Source #
(fsd_append fsd fse) appends the FunctorStringElement fse
to the end of the fsd_list_of_elements of fsd.
No check is done that the resulting fsd_list_of_elements satisfies the
assumptions given in the documentation for FunctorStringData.
fsd_prepend :: FunctorStringElement -> FunctorStringData -> FunctorStringData Source #
(fsd_prepend fse fsd) adds the FunctorStringElement fse
to the start of the fsd_list_of_elements of fsd.
No check is done that the resulting fsd_list_of_elements satisfies the
assumptions given in the documentation for FunctorStringData.
basic_func_to_fsd :: Functor -> (Int, Int) -> FunctorStringData Source #
basic_func_to_fsd takes a basic functor along with a position (x,y)
and gives the associated FunctorStringData whose
fsd_list_of_elements is the singleton list containing (FunctorElement (x,y)).
type OrderedFSDList = [FunctorStringData] Source #
An OrderedFSDList is a list of FunctorStringData
assumed to satisfy the following axioms on the order of its elements:
filter (x-> x/=Nothing) (map fsd_head_position fsds)is equal to[Just (r,0), ..., Just (r,n)]for somerandnfilter (x-> x/=Nothing) (map fsd_tail_position fsds)is equal to[Just (s,0), ..., Just (s,m)]for somesandmr<=swhen bothrandsare uniquely determined (i.e. the above lists are nonempty).
func_to_fsds :: Functor -> Int -> Int -> OrderedFSDList Source #
func_to_fsds takes a Functor,
an Int representing a row and an Int representing an offset
and returns an OrderedFSDList.
Decomposing the Functor into a composition of basic functors, each
basic functor corresponds to one element of the OrderedFSDList.
The FunctorStringData in this list are created with
basic_func_to_fsd, with the basic functors placed at
(r,o),(r,o+1),...,(r,o+n-1) where r is the given row,
o is the given offset, and n is equal to func_reduced_length
of the given functor.
fsds_amalg :: OrderedFSDList -> OrderedFSDList -> OrderedFSDList Source #
If fsds1 and fsds2 are two OrderedFSDList for which
there exists a pair (x,y) of nonnegative integers such that
filter (x-> x/=Nothing) (map fsd_tail_position fsds1)is equal tofilter (x-> x/=Nothing) (map fsd_head_position fsds2)which is equal to[Just (x,0), ..., Just (x,y)],
then (fsds_amalg fsds1 fsds2) is an OrderedFSDList which contains
- the
fsdinfsds1for which(fsd_tail_position fsd)is equal toNothing - the
fsdinfsds2for which(fsd_head_position fsd)is equal toNothing (fsd_combine fsd1 fsd2)wherefsd1is infsds1andfsd2is infsds2and(fsd_combinable fsd1 fsd2)isTrue.
nt_to_functor_strings :: NaturalTransformation -> OrderedFSDList Source #
nt_to_functor_strings takes a NaturalTransformation of one of the 5 types
of the NaturalTransformation which we can format (see NatFormatting) and returns
and OrderedFSDList containing a list of FunctorStringData representing all the
strings in the string diagram for the given natural transformation.
nt_to_functor_strings_helper :: NaturalTransformation -> Int -> Int -> Int -> Int -> [FunctorStringData] Source #
A helper function for nt_to_functor_strings.
fsd_get_mid :: [FunctorStringElement] -> (Int, Float) Source #
fsd_get_mid returns the placement of the midpoint of a list of FunctorStringElements.
Here the length between two consecutive FunctorStringElement in the list is gotten using
fsd_lengths.
It returns (n,f) where n is the index of the segment where the midpoint is located
(with the first segment being indexed by 0) and
f is on the interval [0,1) and specifies how far into this segment the midpoint is located.
fsd_lengths :: [FunctorStringElement] -> [Int] Source #
fsd_lengths gives the lengths of the segments, and is used in fsd_get_mid.
Segments of the form NatElement -- FunctorStringElement
or FunctorStringElement -- NatElement have length 2, while
segments of the form FunctorStringElement -- FunctorStringElement have length 4.
seg_length :: FunctorStringElement -> FunctorStringElement -> Int Source #
seg_length gives the length between two FunctorStringElements, as described
in fsd_lengths.
fe_from_top_offset :: NatFormatting -> (Int, Int) -> Maybe TikzCoordinate Source #
A helper function computing the coordinates of a control point under
the position described by a FunctorElement.
fe_from_bot_offset :: NatFormatting -> (Int, Int) -> Maybe TikzCoordinate Source #
A helper function computing the coordinates of a control point over
the position described by a FunctorElement.
fse_fse_to_curve_op :: NatFormatting -> FunctorStringElement -> FunctorStringElement -> Maybe TikzPathOperation Source #
fse_fse_to_curve_op takes a NatFormatting and two consecutive FunctorStringElements
in the fsd_list_of_elements of a FunctorStringData and creates a TikzPathOperation
drawing the part of the string between the two points described by the
two FunctorStringElements.
fsd_to_tikz_path :: NatFormatting -> FunctorStringData -> TikzPath Source #
fsd_to_tikz_path takes a NatFormatting and a FunctorStringData
and gives the TikzPath which draws the string in the string diagram
represented by the FunctorStringData.
fsd_to_tikz_path_helper :: (Int, Float) -> NatFormatting -> [FunctorStringElement] -> String -> String -> [Maybe TikzPathOperation] Source #
A helper function for fsd_to_tikz_path.