1-------------------------------------------------------------------
2---
3--- FriCAS FormatLaTeX
4--- Copyright (C) 2014-2015, 2019-2020  Ralf Hemmecke <ralf@hemmecke.org>
5---
6-------------------------------------------------------------------
7-- Redistribution and use in source and binary forms, with or without
8-- modification, are permitted provided that the following conditions
9-- are met:
10--
11-- 1. Redistributions of source code must retain the above copyright
12-- notice, this list of conditions and the following disclaimer.
13--
14-- 2. Redistributions in binary form must reproduce the above
15-- copyright notice, this list of conditions and the following
16-- disclaimer in the documentation and/or other materials provided
17-- with the distribution.
18--
19-- 3. Neither the name of the copyright holder nor the names of its
20-- contributors may be used to endorse or promote products derived
21-- from this software without specific prior written permission.
22--
23-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
24-- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
25-- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
26-- FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
27-- COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT,
28-- INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
29-- (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
30-- SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
31-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
32-- STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
33-- ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED
34-- OF THE POSSIBILITY OF SUCH DAMAGE.
35-------------------------------------------------------------------
36)if LiterateDoc
37%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
38%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
39\documentclass{article}
40\usepackage{literatedoc}
41\usepackage{fricasmath}
42\begin{document}
43%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
44%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
45\title{A \LaTeX{} formatter}
46\author{Ralf Hemmecke}
47\date{14-Jul-2014}
48%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
49%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
50\maketitle
51
52\begin{abstract}
53  The formatter \spadtype{FormatLaTeX} is part of the \SYSTEM{}
54  formatting framework and transforms elements of
55  \spadtype{OutputForm} to \
56  spadtype{OutputBox} such that they can be
57  included into a \LaTeX{} document when the package
58  \url{fricasmath.sty} is used.
59\end{abstract}
60
61\tableofcontents
62
63%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
64%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
65%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
66\section{Overview}
67%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
68%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
69%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
70
71For an overview of the formatting framework in \SYSTEM{} look into the
72\url{fmt.spad} document.
73
74%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
75%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
76%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
77\section{Introduction}
78%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
79%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
80%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
81
82Unfortunately, there is no document that clearly describes the meaning
83of the primitives in \spadtype{OutputForm}. The following code of the
84domain \spadtype{FormatLaTeX} is a complete reimplementation, but with
85similar intend as the domain \spadtype{TexFormat} (by R. S. Sutor).
86
87The domain \spadtype{OutputForm} as well as the former implementation
88of \spadtype{TexFormat} has been analyzed and a new structure of the
89code has been designed.
90
91%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
92%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
93%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
94\section{The Implementation of \spadtype{FormatLaTeX}}
95%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
96%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
97%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
98)endif
99
100)abbrev domain FMTLATEX FormatLaTeX
101++ \spadtype{FormatLaTeX} provides a coercion from
102++ \spadtype{OutputForm} to \LaTeX{} format. The particular dialect of
103++ \TeX{} used is \LaTeX{}, but for flexibility reasons
104++ \spadtype{FormatLaTeX} outputs everything into a fricasmath
105++ environment in which certain additional commands are available.
106++ These commands are defined in a .sty file that is distributed with
107++ the source code of FriCAS.
108FormatLaTeX: Exports == Implementation where
109  E   ==> OutputForm
110  Z   ==> Integer
111  S   ==> String
112  LE  ==> List E
113  BOX ==> OutputBox
114  LBOX ==> S -> BOX -- Label box for prologue and epilogue
115  HANDLER ==> (Z, LE) -> OutputBox -- (precedence, arguments) +-> resulting box
116  H ==> HANDLER
117
118  Exports ==> FormatterCategory with
119    environment: (S, S, S, H) -> H
120      ++ \spad{environmnt(env, x, sep)} returns a handler that typesets
121      ++ its arguments (without parentheses) in a \LaTeX{} environment
122      ++ with name \spad{env}. The string \spad{x} is put right after
123      ++ the start of the environment.
124      ++ The arguments are separated by the string \spad{sep}.
125
126  Implementation ==> add
127    Rep ==> Record(prolog: BOX, fmt: BOX, epilog: BOX)
128    import from Rep
129    rep x ==> (x@%) pretend Rep
130    per x ==> (x@Rep) pretend %
131
132    FE ==> formatExpression
133    MIN ==> minPrecedence()
134    MAX ==> maxPrecedence()
135
136    coerce(x: %): OutputForm == rep(x)::OutputForm
137
138)if LiterateDoc
139%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
140By default the \LaTeX{} part is introduced by
141\verb'\begin{fricasmath}{STEPNUMBER}' and ended by
142\verb'\end{fricasmath}'.
143%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
144)endif
145
146    defaultPrologue(label: S): BOX ==
147        box concat ["\begin{fricasmath}{", label, "}"]
148    defaultEpilogue(label: S): BOX == box "\end{fricasmath}"
149
150    -- Functions from FormatterCategory
151    parenthesize(left: S, right: S, b: BOX): BOX ==
152        if left = "(" and right = ")" then (left := "\PAREN{"; right := "}")
153        hconcat [box left, b, box right]
154
155)if LiterateDoc
156%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
157\spad{texEscapeString(s)} escapes all \TeX{} special characters.
158These characters are: \verb|\ { } $ ^ _ % ~ # &|.
159We prepend these characters with a backslash in front of them.
160Of course, this requires at least for \verb'\\' and \verb'\^' to define
161them appropriately in the style file
162
163In order to keep spaces, we also escape spaces by a backslash.
164%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
165)endif
166
167    -- local functions: texEscape, tex1, tex1Escape, tex2
168    texEscapeString(s: S): S == -- local function
169        cc: CharacterClass := charClass " \{}$^_%~#&" --$
170        p: Integer := position(cc, s, 1)
171        zero? p => s
172        str: S := ""
173        n: Integer := 1
174        while (p := position(cc, s, n)) > 0 repeat
175            str := concat(str, s(n..p-1))
176            n := p+1
177            str := concat(str, concat("\", s.p))
178        concat(str, s(n..#s))
179
180    braceBox(b: BOX): BOX == parenthesize("{", "}", b)
181    tex1(cmd: S, b: BOX): BOX == hconcat [box cmd, braceBox b]
182    tex1Escape(cmd: S, s: S): BOX == tex1(cmd, box texEscapeString s)
183    tex2(cmd: S, b1: BOX, b2: BOX): BOX == hconcat [tex1(cmd, b1), braceBox b2]
184
185    -- Take category default for formatInteger
186    formatFloat(s: S): BOX == box remove(char "__", s)
187    formatString(s: S): BOX == tex1Escape("\STRING", s)
188    formatSymbol(s: S): BOX == tex1Escape("\SYMBOL", s)
189    formatFunctionSymbol(s: S): BOX == tex1Escape("\FUN", s)
190
191    -- If a is of the form (* x (CONCAT d y)) then replace it
192    -- by (INTSEP x (CONCAT d y)).
193    integralArgument(a: E): E ==
194        import from OutputFormTools
195        atom? a => a
196        op: E := operator a
197        not is_symbol?(op, "*"::Symbol) => a
198        args: LE := arguments a
199        #args ~= 2 => a
200        op2: E := operator(args.2)
201        not is_symbol?(op2, "CONCAT"::Symbol) => a
202        op3: E := first arguments(args.2)
203        not is_symbol?(op3, "d"::Symbol) => a
204        elt("INTSEP"::Symbol::E, [args.1, args.2])
205        -- create a (INTSEP x (CONCAT d y)) form
206
207    integral(p: Z): H == (prec: Z, args: LE): BOX +->
208        -- We can assume #args=3.
209        bl: BOX := formatExpression(args.1, MIN) -- lower limit
210        bu: BOX := formatExpression(args.2, MIN) -- upper limit
211        a: E := integralArgument(args.3)
212        ba: BOX := formatExpression(a, MIN)
213        if not empty? bl then bl := parenthesize("__{", "}", bl)
214        if not empty? bu then bu := parenthesize("^{",  "}", bu)
215        parenthesizeIf(p < prec, hconcat [box "\int", bl, bu, braceBox ba])
216
217    -- local
218    operatorWithLimits(s: String, p: Z): H == (prec: Z, args: LE): BOX +->
219        -- We can assume #args>=2.
220        bl: BOX := formatExpression(args.1, MIN) -- lower limit
221        bu: BOX := empty() -- upper limit
222        ba: BOX := formatExpression(args.2, MIN) -- upper limit or arg
223        if #args = 3 then
224            bu := ba                                  -- upper limit
225            ba := formatExpression(args.3, MIN) -- arg
226        if not empty? bl then bl := parenthesize("__{", "}", bl)
227        if not empty? bu then bu := parenthesize("^{",  "}", bu)
228        parenthesizeIf(p < prec, hconcat [box s, bl, bu, braceBox ba])
229
230    sum(p: Z): H == operatorWithLimits("\sum", p)
231    product(p: Z): H == operatorWithLimits("\prod", p)
232
233    theMap(prec: Z, args: LE): BOX ==
234        import from OutputFormTools
235        a: E := first args
236        s: S :=
237            atom? a and not string? a and not symbol? a => ";?;"
238            b: BOX := formatExpression(a, MIN) -- assume only one line!!!
239            first lines b -- strings are already run through texEscape
240        p1 := position(char ";", s)
241        p2 := position(char ";", s, p1+1)
242        tex1("\theMap", box s(p1+1..p2-1)) -- \theMap{FUNNAME}
243
244    overbar(p: Z, hh: H): H == (prec: Z, args: LE): BOX +->
245        parenthesizeIf(p < prec, tex1("\overline", hh(p, args)))
246
247    box(hh: H): H == (prec: Z, args: LE): BOX +->
248        tex1("\BOX", hh(prec, [args.1]))
249
250    -- \sqrt[n]{x}
251    nthRoot(p: Z, h1: H, h2: H): H == (prec: Z, args: LE): BOX +->
252        bx: BOX := bracket("{", "}", h1)(p, [args.1])
253        bn: BOX := empty()
254        if #args > 1 then bn := bracket("[", "]", h2)(p, [args.2])
255        parenthesizeIf(p < prec, hconcat [box "\sqrt", bn, bx])
256
257    -- This handles multi-dots super(x,"....").
258    -- scripts(f, [sub, super, presuper, presub]) -->
259    -- \SCRIPTS{f}{d}{u}{pu}{pd}
260    -- can assume #args>2
261    scripts(p: Z): H == (prec: Z, args: LE): BOX +->
262        import from OutputFormTools
263        b: BOX := tex1("\SCRIPTS", formatExpression(first args, p))
264        args := rest args
265        for i in 1..4 repeat
266            empty? args => b := hconcat [b, box "{}"]
267            a := first args
268            args := rest args
269            string? a and string a = " " => b := hconcat [b, box "{}"]
270            b := hconcat [b, box "{", formatExpression(a, MIN), box "}"]
271        parenthesizeIf(p < prec, b)
272
273    subscript(p: Z): H == (prec: Z, args: LE): BOX +->
274        b1: BOX := formatExpression(args.1, p+1)
275        b2: BOX := formatExpression(args.2, MIN)
276        parenthesizeIf(p < prec, tex2("\SUB", b1, b2))
277
278
279)if LiterateDoc
280%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
281The handler \spad{altsupersub} treats an expression that is generated by
282\begin{verbcode}
283supersub(a, [sub1, super1, sub2, super2, ...])
284\end{verbcode}
285from \spadtype{OutputForm}.
286We basically turn it into something like
287\begin{verbcode}
288\ALTSUPERSUB{a}{_{sub1}^{super1}_{sub2}^{super2}...}
289\end{verbcode}
290and let an appropriate \LaTeX{} package deal with the actual formatting,
291for example, the \href{http://www.ctan.org/pkg/tensor}{tensor package}.
292
293For example, for
294\begin{verbcode}
295supersub(x, [a, b, 1, 2+b, 1/3, 4])
296\end{verbcode}
297the above code then looks like this
298\begin{verbcode}
299\ALTSUPERSUB{\SYMBOL{x}}{_{\SYMBOL{a}}^{\SYMBOL{b}}_{1}^{2+\SYMBOL{b}}_{\frac{1}{3}}^{4}}
300\end{verbcode}
301and is printed like this.
302\begin{fricasmath}{}
303\ALTSUPERSUB{\SYMBOL{x}}{_{\SYMBOL{a}}^{\SYMBOL{b}}_{1}^{2+\SYMBOL{b}}_{\frac{1}{3}}^{4}}
304\end{fricasmath}
305%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
306)endif
307
308    altsupersub(p: Z): H == (prec: Z, args: LE): BOX +->
309        b1: BOX := formatExpression(first args, p)
310        lb: List BOX := empty()
311        for a in rest args for i in 1.. repeat
312            -- add "_{a}" or "^{a}"
313            o: S := if odd? i then "__" else "^"
314            lb := cons(tex1(o, formatExpression(a, MIN)), lb)
315        b2: BOX := hconcat reverse! lb
316        parenthesizeIf(p < prec, tex2("\ALTSUPERSUB", b1, b2))
317
318    -- we must treat the special format of a prime expression
319    prime(p: Z): H == (prec: Z, args: LE): BOX +->
320        b1: BOX := formatExpression(args.1, p+1)
321        b2: BOX := formatExpression(args.2, MIN)
322        parenthesizeIf(p < prec, tex2("\PRIME", b1, b2))
323
324    -- local
325    aux2(s: S, p: Z, h1: H, h2: H): H == (prec: Z, args: LE): BOX +->
326        parenthesizeIf(p < prec, tex2(s, h1(p, [args.1]), h2(p, [args.2])))
327
328    power(p: Z, h1: H, h2: H): H == aux2("\SUPER", p, h1, h2)
329    fraction(p: Z, h1: H, h2: H): H == aux2("\frac", p, h1, h2)
330    slash(p: Z, h1: H, h2: H): H == aux2("\SLASH", p, h1, h2)
331
332    binomial(prec: Z, args: LE): BOX ==
333        b1: BOX := formatExpression(args.1, MIN)
334        b2: BOX := formatExpression(args.2, MIN)
335        tex2("\binom", b1, b2)
336
337    -- \def\ZAG##1##2{\frac{\left.{##1}\right|}{\left|{##2}\right.}}%
338    zag(prec: Z, args: LE): BOX ==
339        b1: BOX := formatExpression(args.1, MIN)
340        b2: BOX := formatExpression(args.2, MIN)
341        tex2("\ZAG", b1, b2)
342
343)if LiterateDoc
344%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
345The function \spad{environment} is a general handler to create a
346\LaTeX{} environment.
347%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
348)endif
349
350    environment(env: S, x: S, sep: S, h: H): H == (prec: Z, args: LE): BOX +->
351        -- We must return a box with just one line, but we want to see
352        -- newlines in the actual tex-output. Therefore, we introduce
353        -- explicit newlines.
354        empty? args => empty()
355        b: BOX := box concat ["\begin{", env, "}", x]
356        e: BOX := box concat ["\end{", env, "}"]
357        entries: BOX := nary(sep, MIN, h)(MIN, args)
358        hconcat [b, entries, e]
359
360    vconcat(h: H): H == environment("VCONCAT", "", "\\", h)
361    pile(h: H): H == environment("PILE", "", "\\", h)
362
363    matrix(left: S, right: S): H == (prec: Z, args: LE): BOX +->
364        -- We ignore the left and right parameters and rather use
365        -- LaTeX definitions to do the formatting. We also rely on an
366        -- entry for the ROW operator to be present in the
367        -- operatorHandlers table.
368
369        -- format for args is [[], [ROW ...], [ROW ...], [ROW ...]]
370        import from OutputFormTools
371        n: S := concat ["{", convert(# arguments first rest args), "}"]
372        environment("MATRIX", n, "\\", FE MIN)(MIN, rest args)
373
374
375)if LiterateDoc
376%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
377Now all function are defined and we can fill the \spad{oh}
378data structure.
379The operators have been mainly extracted from the definitions of
380\spadtype{OutputForm} and the original implementation of
381\spadtype{TexFormat} by R. S. Sutor
382%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
383)endif
384
385    setOperatorHandlers!(oh: OperatorHandlers H): OperatorHandlers H ==
386        NARY ==> -1 -- means n-ary.
387        PAREN p ==> bracket("\PAREN{", "}", FE p)
388        BRACE p ==> bracket("{", "}", FE p)
389        BRACE2(p1, p2) ==> binary(BRACE p1, BRACE p2)
390
391        o(n, op, hdl) ==> setHandler!(oh, n, op, hdl)
392
393        o(0, "NOTHING",     nothing())
394        o(0, "%pi",         formatConstant "\pi ")
395        o(0, "%e",          formatConstant "\EulerE ")
396        o(0, "%i",          formatConstant "\ImaginaryI ")
397        o(0, "%Infinity",   formatConstant "\infty ")
398        o(0, "infinity",    formatConstant "\infty ") -- for %minusInfinity
399        o(0, "...",         formatConstant "\ldots ")
400
401        o(1, "cos",         prefix("\cos",    900, PAREN MIN))
402        o(1, "cot",         prefix("\cot",    900, PAREN MIN))
403        o(1, "csc",         prefix("\csc",    900, PAREN MIN))
404        o(1, "log",         prefix("\log",    900, PAREN MIN))
405        o(1, "sec",         prefix("\sin",    900, PAREN MIN))
406        o(1, "sin",         prefix("\sin",    900, PAREN MIN))
407        o(1, "tan",         prefix("\tan",    900, PAREN MIN))
408        o(1, "cosh",        prefix("\cosh",   900, PAREN MIN))
409        o(1, "coth",        prefix("\coth",   900, PAREN MIN))
410        o(1, "csch",        prefix("\csch",   900, PAREN MIN))
411        o(1, "sech",        prefix("\sech",   900, PAREN MIN))
412        o(1, "sinh",        prefix("\sinh",   900, PAREN MIN))
413        o(1, "tanh",        prefix("\tanh",   900, PAREN MIN))
414        o(1, "acos",        prefix("\arccos", 900, PAREN MIN))
415        o(1, "asin",        prefix("\arcsin", 900, PAREN MIN))
416        o(1, "atan",        prefix("\arctan", 900, PAREN MIN))
417        o(1, "erf",         prefix("\erf",    900, PAREN MIN))
418
419        o(1, "-",           prefix("-",       710, FE 715))
420        o(1, "not",         prefix("\lnot ",  710, FE 715))
421
422        o(1, "QUOTE",       bracket("\QUOTE{", "}",  FE 990))
423        o(1, "OVERBAR",     overbar(MAX, FE MIN))
424        o(1, "BOX",         box FE MIN)
425        o(1, "Aleph",       bracket("\SUB{\aleph}{", "}", FE MIN))
426        o(1, "BRACE",       bracket("\BRACE{", "}", FE MIN))
427        o(1, "BRACKET",     bracket("\BRACKET{", "}", FE MIN))
428        o(1, "PAREN",       bracket("\PAREN{", "}", FE MIN))
429        o(1, "Gamma",       bracket("\Gamma\PAREN{", "}", FE MIN))
430        o(1, "ROOT",        bracket("\sqrt{", "}", FE MIN))
431        o(1, "SEGMENT",     bracket("\SEGMENTi{", "}", FE MIN))
432        o(1, "STRING",      bracket("\STRING{", "}", FE MIN))
433
434        o(2, "rem",  infix("", 810, bracket("\REM{",   "}", FE 811), BRACE 811))
435        o(2, "quo",  infix("", 810, bracket("\QUO{",   "}", FE 811), BRACE 811))
436        o(2, "exquo",infix("", 810, bracket("\EXQUO{", "}", FE 811), BRACE 811))
437
438        o(2, "^",           power(950, FE 960, FE MIN))
439        o(2, "/",           fraction(910, FE MIN, FE MIN))
440        o(2, "OVER",        fraction(910, FE MIN, FE MIN))
441        o(2, "SLASH",       slash(880, FE 881, FE 882))
442        o(2, "ZAG",         zag)
443        o(2, "BINOMIAL",    binomial)
444        o(2, "PRIME",       prime 950)
445
446        o(2, "ROOT",        nthRoot(970, FE MIN, FE MIN))
447        o(2, "SUB",         subscript 950)
448
449        o(2, "SEGMENT",     prefix("\SEGMENTii", 100, BRACE2(100, 100)))
450
451        o(2, "TENSOR",      infix("\otimes ",    850, FE 850, FE 850))
452
453        o(2, "EQUATNUM",    prefix("\EQUATNUM",  MAX, BRACE2(MIN, MIN)))
454        o(2, "OVERLABEL",   prefix("\OVERLABEL", MAX, BRACE2(MIN, MIN)))
455
456        o(2, "==",          nary("==",         400, FE 401))
457
458        o(2, "=",           nary("=",          400, FE 400))
459        o(2, "~=",          nary("\ne ",       400, FE 400))
460        o(2, "<",           nary("<",          400, FE 400))
461        o(2, ">",           nary(">",          400, FE 400))
462        o(2, "<=",          nary("\leq ",      400, FE 400))
463        o(2, ">=",          nary("\geq ",      400, FE 400))
464        o(2, "and",         nary("\land ",     300, FE 300))
465        o(2, "or",          nary("\lor ",      200, FE 200))
466        o(2, "LET",         nary("\coloneqq ", 125, FE 125))
467        o(2, "TAG",         nary("\to ",       100, FE 100))
468        o(2, "+->",         nary("\mapsto ",   100, FE 100))
469        o(2, "|",           nary("\mid ",      100, FE 100))
470
471        o(2, "SIGMA",       sum 750)
472        o(2, "PI",          product 750)
473
474        o(3, "SIGMA2",      sum 750)
475        o(3, "PI2",         product 750)
476        o(3, "INTSIGN",     integral 700)
477        o(2, "INTSEP",      infix("\, ", MAX, FE MIN, FE MIN)) -- non-OutputForm
478
479        o(NARY, "+",           naryPlus("+", "-",  700, FE 700))
480        -- Does n-ary minus ever appear in OutputForm???
481        o(NARY, "-",           naryPlus("+", "-",  700, FE 700))
482
483        o(NARY, "*",           nary("\TIMES ",     800, FE 800))
484
485        o(NARY, "AGGLST",      nary("\COMMA ",     MAX, FE MIN))
486        o(NARY, "AGGSET",      nary("\SEMICOLON ", MAX, FE MIN))
487        o(NARY, "CONCAT",      nary("",            MAX, FE MIN))
488        o(NARY, "CONCATB",     nary("\ ",          MAX, FE MIN))
489
490        o(NARY, "ALTSUPERSUB", altsupersub 900)
491        o(NARY, "SUPERSUB",    scripts 900)
492        o(NARY, "SC",          pile FE MIN) -- pile notation
493        o(NARY, "VCONCAT",     vconcat FE MIN)
494
495        o(NARY, "ROW",         nary("&", MAX, FE MIN))
496        o(NARY, "MATRIX",      matrix("[", "]"))
497        o(NARY, "theMap",      theMap) -- one or two arguments
498
499        return oh
500
501    -- local variable declarations and definitions
502    operatorData: OperatorHandlers(H) := setOperatorHandlers! new()
503    operatorHandlers(): OperatorHandlers(HANDLER) == operatorData
504
505)if LiterateDoc
506%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
507%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
508%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
509\section{A style file for use with output of \spadtype{FormatLaTeX}}
510%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
511%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
512%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
513
514%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
515\begin{verbcode}
516%% fricasmath.sty
517%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
518%% Copyright (c) 2014, 2020  Ralf Hemmecke <ralf@hemmecke.org>
519%% All rights reserved.
520%%
521%% Redistribution and use in source and binary forms, with or without
522%% modification, are permitted provided that the following conditions are
523%% met:
524%%
525%% 1. Redistributions of source code must retain the above copyright
526%% notice, this list of conditions and the following disclaimer.
527%%
528%% 2. Redistributions in binary form must reproduce the above
529%% copyright notice, this list of conditions and the following
530%% disclaimer in the documentation and/or other materials provided
531%% with the distribution.
532%%
533%% 3. Neither the name of the copyright holder nor the names of its
534%% contributors may be used to endorse or promote products derived
535%% from this software without specific prior written permission.
536%%
537%% THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
538%% "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
539%% LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
540%% FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
541%% COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT,
542%% INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
543%% (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
544%% SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
545%% HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
546%% STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
547%% ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED
548%% OF THE POSSIBILITY OF SUCH DAMAGE.
549%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
550
551\usepackage{amsmath}
552\usepackage[mathstyleoff]{breqn}
553\usepackage{tensor}
554\usepackage{mleftright}
555%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
556\newenvironment{fricasmath}[1]%
557  {\def\arg{#1}%
558   \ifx\arg\empty \def\BEGIN{\begin{dmath*}[compact]}%
559                  \def\END{\end{dmath*}}%
560            \else \def\BEGIN{\begin{dmath}[compact,number={#1}]}%
561                  \def\END{\end{dmath}}%
562
563   \fi
564   \def\EulerE{e}% %e
565   \def\ImaginaryI{i}% %i
566   \def\csch{\operatorname{csch}}%
567   \def\erf{\operatorname{erf}}%
568   \def\coloneqq{\mathrel{:\mkern-1.2mu=}}%
569   \def\embrace##1##2##3{\left##1\relax##3\right##2\relax}%
570   \def\BRACE{\embrace{\{}{\}}}%
571   \def\BRACKET{\embrace{[}{]}}%
572   \def\PAREN##1{\mleft(##1\mright)}%
573   \def\ZAG##1##2{\frac{\left.{##1}\right|}{\left|{##2}\right.}}%
574   \def\QUOTE##1{\texttt{'}##1}%
575   \def\BOX##1{\boxed{##1}}%
576   \def\SEGMENTi##1{{##1}\operatorname{..}}%
577   \def\SEGMENTii##1##2{{##1}\operatorname{..}{##2}}%
578   \def\SUB##1##2{{{##1}_{##2}}}%
579   \def\SUPER##1##2{{{##1}^{##2}}}%
580   \def\SLASH##1##2{\left.##1\vphantom{{##1}{##2}}\right/ ##2}%
581   \def\PRIMEx##1{{##1}\endgroup}%
582   % Translate comma into \prime.
583   \def\PRIME##1{\begingroup% redefinitions are only local
584     {##1}%
585     % for the second parameter redefine \STRING and \PAREN
586     \def\PAREN{\def\STRING{\embrace{(}{)}}}%
587     \def\STRING{\begingroup\lccode`\~=`\,\lowercase{\endgroup\def~{\prime}}}%
588     ^\PRIMEx}%
589   \def\OVERLABEL##1{\FUN{OVERLABEL}(##1)}%
590   \def\REM##1##2{{##1}\mathbin{\mathrm{rem}}{##2}}%
591   \def\QUO##1##2{{##1}\mathbin{\mathrm{quo}}{##2}}%
592   \def\EXQUO##1##2{{##1}\mathbin{\mathrm{exquo}}{##2}}%
593   \def\EQUATNUM##1##2{(##1)\qquad ##2}%
594   \def\COMMA{,\linebreak[2]\:}% allow breaks in lists and sets
595   \def\SEMICOLON{;\:}%
596   \def\TIMES{\,}%
597   \def\theMap##1{\FUN{theMap}(\FUN{##1})}%
598   \def\ALTSUPERSUB##1##2{\tensor*{##1}{*##2}}%
599   \def\SCRIPTS##1##2##3##4##5{\tensor*[^{##4}_{##5}]{##1}{_{##2}^{##3}}}%
600   \newenvironment{MATRIX}[1]%
601     {\setcounter{MaxMatrixCols}{##1}\begin{bmatrix}}{\end{bmatrix}}%
602   \newenvironment{PILE}{\begin{array}[t]{l}}{\end{array}}%
603   \newenvironment{VCONCAT}{\begin{array}{c}}{\end{array}}%
604   \def\DefSpecialChars{%
605     \def\^{{\tiny\ensuremath{^{\wedge}}}}%
606     \def\\{\ensuremath{\backslash}}%
607     \def\~{\char`~}%
608   }%
609   % If there is only one letter in the argument of \FUN, then
610   % do not typeset it with \operatorname.
611   \def\FUN##1{{\DefSpecialChars\DEFOPNAME##1\ENDDEFOPNAME\OPNAME{##1}}}%
612   \def\DEFOPNAME##1##2\ENDDEFOPNAME{\def\arg{##2}%
613     \ifx\arg\empty\def\OPNAME{}\else\def\OPNAME{\operatorname}\fi}%
614   \def\STRING##1{\texttt{\DefSpecialChars ##1}}%
615   \def\SYMBOL##1{{\DefSpecialChars ##1}}%
616   \BEGIN{}}%
617  {\END{}}
618\end{verbcode}
619%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
620
621%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
622%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
623%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
624\section{Customization}
625%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
626%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
627%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
628
629The visual appearance of expressions in a \LaTeX{} document can be
630customized in two places. The definitions of the \TeX{} commands in
631the style file \url{fricasmath.sty} can be changed. Furthermore also
632the internal data structure of the handlers can be modified, see
633documentation of the formatting framework in \SYSTEM{}.
634
635\end{document}
636%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
637)endif
638