{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2009-2022 John MacFarlane <jgm@berkeley.edu>

This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation; either version 2 of the License, or
(at your option) any later version.

This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
GNU General Public License for more details.

You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
-}

{- | Lookup tables for TeX commands.
-}

module Text.TeXMath.Readers.TeX.Commands
  ( styleOps
  , textOps
  , enclosures
  , operators
  , symbols
  , siUnitMap
  )
where

import qualified Data.Map as M
import Text.TeXMath.Types
import Text.TeXMath.Unicode.ToTeX (symbolMap)
import Data.Text (Text)
import Data.Ratio ((%))

-- Note: cal and scr are treated the same way, as unicode is lacking such two different sets for those.
styleOps :: M.Map Text ([Exp] -> Exp)
styleOps :: Map Text ([Exp] -> Exp)
styleOps = [(Text, [Exp] -> Exp)] -> Map Text ([Exp] -> Exp)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
          [ (Text
"\\mathrm",     TextType -> [Exp] -> Exp
EStyled TextType
TextNormal)
          , (Text
"\\mathup",     TextType -> [Exp] -> Exp
EStyled TextType
TextNormal)
          , (Text
"\\mathbf",     TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
          , (Text
"\\boldsymbol", TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
          , (Text
"\\bm",         TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
          , (Text
"\\symbf",      TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
          , (Text
"\\mathbold",   TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
          , (Text
"\\pmb",        TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
          , (Text
"\\mathbfup",   TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
          , (Text
"\\mathit",     TextType -> [Exp] -> Exp
EStyled TextType
TextItalic)
          , (Text
"\\mathtt",     TextType -> [Exp] -> Exp
EStyled TextType
TextMonospace)
          , (Text
"\\texttt",     TextType -> [Exp] -> Exp
EStyled TextType
TextMonospace)
          , (Text
"\\mathsf",     TextType -> [Exp] -> Exp
EStyled TextType
TextSansSerif)
          , (Text
"\\mathsfup",   TextType -> [Exp] -> Exp
EStyled TextType
TextSansSerif)
          , (Text
"\\mathbb",     TextType -> [Exp] -> Exp
EStyled TextType
TextDoubleStruck)
          , (Text
"\\mathds",     TextType -> [Exp] -> Exp
EStyled TextType
TextDoubleStruck) -- mathds package
          , (Text
"\\mathcal",    TextType -> [Exp] -> Exp
EStyled TextType
TextScript)
          , (Text
"\\mathscr",    TextType -> [Exp] -> Exp
EStyled TextType
TextScript)
          , (Text
"\\mathfrak",   TextType -> [Exp] -> Exp
EStyled TextType
TextFraktur)
          , (Text
"\\mathbfit",   TextType -> [Exp] -> Exp
EStyled TextType
TextBoldItalic)
          , (Text
"\\mathbfsfup", TextType -> [Exp] -> Exp
EStyled TextType
TextSansSerifBold)
          , (Text
"\\mathbfsfit", TextType -> [Exp] -> Exp
EStyled TextType
TextSansSerifBoldItalic)
          , (Text
"\\mathbfscr",  TextType -> [Exp] -> Exp
EStyled TextType
TextBoldScript)
          , (Text
"\\mathbffrak", TextType -> [Exp] -> Exp
EStyled TextType
TextBoldFraktur)
          , (Text
"\\mathbfcal",  TextType -> [Exp] -> Exp
EStyled TextType
TextBoldScript)
          , (Text
"\\mathsfit",   TextType -> [Exp] -> Exp
EStyled TextType
TextSansSerifItalic)
          ]

textOps :: M.Map Text (Text -> Exp)
textOps :: Map Text (Text -> Exp)
textOps = [(Text, Text -> Exp)] -> Map Text (Text -> Exp)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
          [ (Text
"\\textrm", (TextType -> Text -> Exp
EText TextType
TextNormal))
          , (Text
"\\text",   (TextType -> Text -> Exp
EText TextType
TextNormal))
          , (Text
"\\textbf", (TextType -> Text -> Exp
EText TextType
TextBold))
          , (Text
"\\textit", (TextType -> Text -> Exp
EText TextType
TextItalic))
          , (Text
"\\texttt", (TextType -> Text -> Exp
EText TextType
TextMonospace))
          , (Text
"\\textsf", (TextType -> Text -> Exp
EText TextType
TextSansSerif))
          , (Text
"\\mbox",   (TextType -> Text -> Exp
EText TextType
TextNormal))
          ]

enclosures :: M.Map Text Exp
enclosures :: Map Text Exp
enclosures = [(Text, Exp)] -> Map Text Exp
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
  [ (Text
"(", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"(")
  , (Text
")", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
")")
  , (Text
"[", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"[")
  , (Text
"]", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"]")
  , (Text
"\\{", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"{")
  , (Text
"\\}", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"}")
  , (Text
"\\lbrack", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"[")
  , (Text
"\\lbrace", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"{")
  , (Text
"\\rbrack", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"]")
  , (Text
"\\rbrace", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"}")
  , (Text
"\\llbracket", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x27E6")
  , (Text
"\\rrbracket", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x27E7")
  , (Text
"\\langle", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x27E8")
  , (Text
"\\rangle", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x27E9")
  , (Text
"\\lfloor", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x230A")
  , (Text
"\\rfloor", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x230B")
  , (Text
"\\lceil", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x2308")
  , (Text
"\\rceil", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x2309")
  , (Text
"|", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"|")
  , (Text
"|", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"|")
  , (Text
"\\|", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x2225")
  , (Text
"\\|", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x2225")
  , (Text
"\\lvert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x7C")
  , (Text
"\\rvert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x7C")
  , (Text
"\\vert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x7C")
  , (Text
"\\lVert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x2225")
  , (Text
"\\rVert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x2225")
  , (Text
"\\Vert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x2016")
  , (Text
"\\ulcorner", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x231C")
  , (Text
"\\urcorner", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x231D")
  ]

operators :: M.Map Text Exp
operators :: Map Text Exp
operators = [(Text, Exp)] -> Map Text Exp
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [
             (Text
"+", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"+")
           , (Text
"-", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\x2212")
           , (Text
"*", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"*")
           , (Text
"@", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"@")
           , (Text
",", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
",")
           , (Text
".", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
".")
           , (Text
";", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
";")
           , (Text
":", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
":")
           , (Text
"?", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"?")
           , (Text
">", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
">")
           , (Text
"<", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"<")
           , (Text
"!", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"!")
           , (Text
"'", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\x2032")
           , (Text
"''", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\x2033")
           , (Text
"'''", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\x2034")
           , (Text
"''''", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\x2057")
           , (Text
"=", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"=")
           , (Text
":=", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
":=")
           , (Text
"/", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"/")
           , (Text
"~", Rational -> Exp
ESpace (Rational
4Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
18)) ]

symbols :: M.Map Text Exp
symbols :: Map Text Exp
symbols = Map Text Exp
symbolMapOverrides Map Text Exp -> Map Text Exp -> Map Text Exp
forall a. Semigroup a => a -> a -> a
<> Map Text Exp
symbolMap

-- These are the cases where texmath historically diverged
-- from symbolMap.  We may want to remove some of these overrides,
-- but for now we keep them so behavior doesn't change.
symbolMapOverrides ::  M.Map Text Exp
symbolMapOverrides :: Map Text Exp
symbolMapOverrides = [(Text, Exp)] -> Map Text Exp
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
  [ (Text
"\\\n",Rational -> Exp
ESpace (Integer
2 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
9))
  , (Text
"\\ ",Rational -> Exp
ESpace (Integer
2 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
9))
  , (Text
"\\!",Rational -> Exp
ESpace ((-Integer
1) Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
6))
  , (Text
"\\,",Rational -> Exp
ESpace (Integer
1 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
6))
  , (Text
"\\:",Rational -> Exp
ESpace (Integer
2 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
9))
  , (Text
"\\;",Rational -> Exp
ESpace (Integer
5 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
18))
  , (Text
"\\>",Rational -> Exp
ESpace (Integer
2 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
9))
  , (Text
"\\AC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9190")
  , (Text
"\\Box",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\9633")
  , (Text
"\\Delta",Text -> Exp
EIdentifier Text
"\916")
  , (Text
"\\Diamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\9671")
  , (Text
"\\Gamma",Text -> Exp
EIdentifier Text
"\915")
  , (Text
"\\Im",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8465")
  , (Text
"\\Join",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8904")
  , (Text
"\\Lambda",Text -> Exp
EIdentifier Text
"\923")
  , (Text
"\\Lbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\12312")
  , (Text
"\\Longleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8656")
  , (Text
"\\Longleftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8660")
  , (Text
"\\Longrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8658")
  , (Text
"\\Omega",Text -> Exp
EIdentifier Text
"\937")
  , (Text
"\\Phi",Text -> Exp
EIdentifier Text
"\934")
  , (Text
"\\Pi",Text -> Exp
EIdentifier Text
"\928")
  , (Text
"\\Pr",Text -> Exp
EMathOperator Text
"Pr")
  , (Text
"\\Psi",Text -> Exp
EIdentifier Text
"\936")
  , (Text
"\\Rbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\12313")
  , (Text
"\\Re",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8476")
  , (Text
"\\Sigma",Text -> Exp
EIdentifier Text
"\931")
  , (Text
"\\Theta",Text -> Exp
EIdentifier Text
"\920")
  , (Text
"\\Upsilon",Text -> Exp
EIdentifier Text
"\933")
  , (Text
"\\Xi",Text -> Exp
EIdentifier Text
"\926")
  , (Text
"\\^",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"^")
  , (Text
"\\alpha",Text -> Exp
EIdentifier Text
"\945")
  , (Text
"\\amalg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8720")
  , (Text
"\\arccos",Text -> Exp
EMathOperator Text
"arccos")
  , (Text
"\\arcsin",Text -> Exp
EMathOperator Text
"arcsin")
  , (Text
"\\arctan",Text -> Exp
EMathOperator Text
"arctan")
  , (Text
"\\arg",Text -> Exp
EMathOperator Text
"arg")
  , (Text
"\\ast",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"*")
  , (Text
"\\backslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8726")
  , (Text
"\\bar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8254")
  , (Text
"\\barwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8965")
  , (Text
"\\beta",Text -> Exp
EIdentifier Text
"\946")
  , (Text
"\\bigcirc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9675")
  , (Text
"\\blacklozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11047")
  , (Text
"\\blacksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9724")
  , (Text
"\\blacktriangleleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9666")
  , (Text
"\\blacktriangleright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9656")
  , (Text
"\\cdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8901")
  , (Text
"\\chi",Text -> Exp
EIdentifier Text
"\967")
  , (Text
"\\cos",Text -> Exp
EMathOperator Text
"cos")
  , (Text
"\\cosh",Text -> Exp
EMathOperator Text
"cosh")
  , (Text
"\\cot",Text -> Exp
EMathOperator Text
"cot")
  , (Text
"\\coth",Text -> Exp
EMathOperator Text
"coth")
  , (Text
"\\csc",Text -> Exp
EMathOperator Text
"csc")
  , (Text
"\\dag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8224")
  , (Text
"\\ddag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8225")
  , (Text
"\\deg",Text -> Exp
EMathOperator Text
"deg")
  , (Text
"\\delta",Text -> Exp
EIdentifier Text
"\948")
  , (Text
"\\det",Text -> Exp
EMathOperator Text
"det")
  , (Text
"\\diamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8900")
  , (Text
"\\digamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\989")
  , (Text
"\\dim",Text -> Exp
EMathOperator Text
"dim")
  , (Text
"\\dots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8230")
  , (Text
"\\dotsb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8943")
  , (Text
"\\dotsc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8230")
  , (Text
"\\dotsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8943")
  , (Text
"\\dotsm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8943")
  , (Text
"\\dotso",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8230")
  , (Text
"\\emptyset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8709")
  , (Text
"\\epsilon",Text -> Exp
EIdentifier Text
"\1013")
  , (Text
"\\eqcolon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8789")
  , (Text
"\\eta",Text -> Exp
EIdentifier Text
"\951")
  , (Text
"\\exists",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8707")
  , (Text
"\\exp",Text -> Exp
EMathOperator Text
"exp")
  , (Text
"\\forall",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8704")
  , (Text
"\\gamma",Text -> Exp
EIdentifier Text
"\947")
  , (Text
"\\gcd",Text -> Exp
EMathOperator Text
"gcd")
  , (Text
"\\geqslant",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8805")
  , (Text
"\\gt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
">")
  , (Text
"\\hbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8463")
  , (Text
"\\hdots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8230")
  , (Text
"\\hom",Text -> Exp
EMathOperator Text
"hom")
  , (Text
"\\iff",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8660")
  , (Text
"\\inf",Text -> Exp
EMathOperator Text
"inf")
  , (Text
"\\iota",Text -> Exp
EIdentifier Text
"\953")
  , (Text
"\\kappa",Text -> Exp
EIdentifier Text
"\954")
  , (Text
"\\ker",Text -> Exp
EMathOperator Text
"ker")
  , (Text
"\\lambda",Text -> Exp
EIdentifier Text
"\955")
  , (Text
"\\lbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\12308")
  , (Text
"\\leqslant",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8804")
  , (Text
"\\lg",Text -> Exp
EMathOperator Text
"lg")
  , (Text
"\\lhd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8882")
  , (Text
"\\lim",Text -> Exp
EMathOperator Text
"lim")
  , (Text
"\\liminf",Text -> Exp
EMathOperator Text
"liminf")
  , (Text
"\\limsup",Text -> Exp
EMathOperator Text
"limsup")
  , (Text
"\\llbracket",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\12314")
  , (Text
"\\ln",Text -> Exp
EMathOperator Text
"ln")
  , (Text
"\\log",Text -> Exp
EMathOperator Text
"log")
  , (Text
"\\longleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8592")
  , (Text
"\\longleftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8596")
  , (Text
"\\longmapsto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8614")
  , (Text
"\\longrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8594")
  , (Text
"\\lozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\9674")
  , (Text
"\\lt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"<")
  , (Text
"\\max",Text -> Exp
EMathOperator Text
"max")
  , (Text
"\\mid",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8739")
  , (Text
"\\min",Text -> Exp
EMathOperator Text
"min")
  , (Text
"\\models",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8872")
  , (Text
"\\mu",Text -> Exp
EIdentifier Text
"\956")
  , (Text
"\\neg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\172")
  , (Text
"\\nu",Text -> Exp
EIdentifier Text
"\957")
  , (Text
"\\omega",Text -> Exp
EIdentifier Text
"\969")
  , (Text
"\\overbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\175")
  , (Text
"\\overline",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TOver Text
"\175")
  , (Text
"\\overrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8407")
  , (Text
"\\perp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8869")
  , (Text
"\\phi",Text -> Exp
EIdentifier Text
"\981")
  , (Text
"\\pi",Text -> Exp
EIdentifier Text
"\960")
  , (Text
"\\preceq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8828")
  , (Text
"\\psi",Text -> Exp
EIdentifier Text
"\968")
  , (Text
"\\qquad",Rational -> Exp
ESpace (Integer
2 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
1))
  , (Text
"\\quad",Rational -> Exp
ESpace (Integer
1 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
1))
  , (Text
"\\rbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\12309")
  , (Text
"\\rhd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8883")
  , (Text
"\\rho",Text -> Exp
EIdentifier Text
"\961")
  , (Text
"\\rrbracket",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\12315")
  , (Text
"\\sec",Text -> Exp
EMathOperator Text
"sec")
  , (Text
"\\setminus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\\")
  , (Text
"\\sigma",Text -> Exp
EIdentifier Text
"\963")
  , (Text
"\\sim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8764")
  , (Text
"\\sin",Text -> Exp
EMathOperator Text
"sin")
  , (Text
"\\sinh",Text -> Exp
EMathOperator Text
"sinh")
  , (Text
"\\square",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9643")
  , (Text
"\\succeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8829")
  , (Text
"\\sup",Text -> Exp
EMathOperator Text
"sup")
  , (Text
"\\tan",Text -> Exp
EMathOperator Text
"tan")
  , (Text
"\\tanh",Text -> Exp
EMathOperator Text
"tanh")
  , (Text
"\\tau",Text -> Exp
EIdentifier Text
"\964")
  , (Text
"\\therefore",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
"\8756")
  , (Text
"\\theta",Text -> Exp
EIdentifier Text
"\952")
  , (Text
"\\triangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9651")
  , (Text
"\\triangleleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8882")
  , (Text
"\\triangleright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8883")
  , (Text
"\\underbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TUnder Text
"\817")
  , (Text
"\\underline",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TUnder Text
"_")
  , (Text
"\\unlhd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8884")
  , (Text
"\\unrhd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8885")
  , (Text
"\\upUpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\978")
  , (Text
"\\upsilon",Text -> Exp
EIdentifier Text
"\965")
  , (Text
"\\varDelta",Text -> Exp
EIdentifier Text
"\120549")
  , (Text
"\\varGamma",Text -> Exp
EIdentifier Text
"\120548")
  , (Text
"\\varLambda",Text -> Exp
EIdentifier Text
"\120556")
  , (Text
"\\varOmega",Text -> Exp
EIdentifier Text
"\120570")
  , (Text
"\\varPhi",Text -> Exp
EIdentifier Text
"\120567")
  , (Text
"\\varPi",Text -> Exp
EIdentifier Text
"\120561")
  , (Text
"\\varPsi",Text -> Exp
EIdentifier Text
"\120569")
  , (Text
"\\varSigma",Text -> Exp
EIdentifier Text
"\120564")
  , (Text
"\\varTheta",Text -> Exp
EIdentifier Text
"\120553")
  , (Text
"\\varUpsilon",Text -> Exp
EIdentifier Text
"\120566")
  , (Text
"\\varXi",Text -> Exp
EIdentifier Text
"\120559")
  , (Text
"\\varepsilon",Text -> Exp
EIdentifier Text
"\949")
  , (Text
"\\varnothing",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8960")
  , (Text
"\\varphi",Text -> Exp
EIdentifier Text
"\966")
  , (Text
"\\varrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120602")
  , (Text
"\\varsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120589")
  , (Text
"\\vartheta",Text -> Exp
EIdentifier Text
"\977")
  , (Text
"\\vdots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8942")
  , (Text
"\\vec",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8407")
  , (Text
"\\wp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8472")
  , (Text
"\\wr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8768")
  , (Text
"\\xi",Text -> Exp
EIdentifier Text
"\958")
  , (Text
"\\zeta",Text -> Exp
EIdentifier Text
"\950")
  ]

siUnitMap :: M.Map Text Exp
siUnitMap :: Map Text Exp
siUnitMap = [(Text, Exp)] -> Map Text Exp
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
  [ (Text
"fg", Text -> Exp
str Text
"fg")
  , (Text
"pg", Text -> Exp
str Text
"pg")
  , (Text
"ng", Text -> Exp
str Text
"ng")
  , (Text
"ug", Text -> Exp
str Text
"μg")
  , (Text
"mg", Text -> Exp
str Text
"mg")
  , (Text
"g", Text -> Exp
str Text
"g")
  , (Text
"kg", Text -> Exp
str Text
"kg")
  , (Text
"amu", Text -> Exp
str Text
"u")
  , (Text
"pm", Text -> Exp
str Text
"pm")
  , (Text
"nm", Text -> Exp
str Text
"nm")
  , (Text
"um", Text -> Exp
str Text
"μm")
  , (Text
"mm", Text -> Exp
str Text
"mm")
  , (Text
"cm", Text -> Exp
str Text
"cm")
  , (Text
"dm", Text -> Exp
str Text
"dm")
  , (Text
"m", Text -> Exp
str Text
"m")
  , (Text
"km", Text -> Exp
str Text
"km")
  , (Text
"as", Text -> Exp
str Text
"as")
  , (Text
"fs", Text -> Exp
str Text
"fs")
  , (Text
"ps", Text -> Exp
str Text
"ps")
  , (Text
"ns", Text -> Exp
str Text
"ns")
  , (Text
"us", Text -> Exp
str Text
"μs")
  , (Text
"ms", Text -> Exp
str Text
"ms")
  , (Text
"s", Text -> Exp
str Text
"s")
  , (Text
"fmol", Text -> Exp
str Text
"fmol")
  , (Text
"pmol", Text -> Exp
str Text
"pmol")
  , (Text
"nmol", Text -> Exp
str Text
"nmol")
  , (Text
"umol", Text -> Exp
str Text
"μmol")
  , (Text
"mmol", Text -> Exp
str Text
"mmol")
  , (Text
"mol", Text -> Exp
str Text
"mol")
  , (Text
"kmol", Text -> Exp
str Text
"kmol")
  , (Text
"pA", Text -> Exp
str Text
"pA")
  , (Text
"nA", Text -> Exp
str Text
"nA")
  , (Text
"uA", Text -> Exp
str Text
"μA")
  , (Text
"mA", Text -> Exp
str Text
"mA")
  , (Text
"A", Text -> Exp
str Text
"A")
  , (Text
"kA", Text -> Exp
str Text
"kA")
  , (Text
"ul", Text -> Exp
str Text
"μl")
  , (Text
"ml", Text -> Exp
str Text
"ml")
  , (Text
"l", Text -> Exp
str Text
"l")
  , (Text
"hl", Text -> Exp
str Text
"hl")
  , (Text
"uL", Text -> Exp
str Text
"μL")
  , (Text
"mL", Text -> Exp
str Text
"mL")
  , (Text
"L", Text -> Exp
str Text
"L")
  , (Text
"hL", Text -> Exp
str Text
"hL")
  , (Text
"mHz", Text -> Exp
str Text
"mHz")
  , (Text
"Hz", Text -> Exp
str Text
"Hz")
  , (Text
"kHz", Text -> Exp
str Text
"kHz")
  , (Text
"MHz", Text -> Exp
str Text
"MHz")
  , (Text
"GHz", Text -> Exp
str Text
"GHz")
  , (Text
"THz", Text -> Exp
str Text
"THz")
  , (Text
"mN", Text -> Exp
str Text
"mN")
  , (Text
"N", Text -> Exp
str Text
"N")
  , (Text
"kN", Text -> Exp
str Text
"kN")
  , (Text
"MN", Text -> Exp
str Text
"MN")
  , (Text
"Pa", Text -> Exp
str Text
"Pa")
  , (Text
"kPa", Text -> Exp
str Text
"kPa")
  , (Text
"MPa", Text -> Exp
str Text
"MPa")
  , (Text
"GPa", Text -> Exp
str Text
"GPa")
  , (Text
"mohm", Text -> Exp
str Text
"mΩ")
  , (Text
"kohm", Text -> Exp
str Text
"kΩ")
  , (Text
"Mohm", Text -> Exp
str Text
"MΩ")
  , (Text
"pV", Text -> Exp
str Text
"pV")
  , (Text
"nV", Text -> Exp
str Text
"nV")
  , (Text
"uV", Text -> Exp
str Text
"μV")
  , (Text
"mV", Text -> Exp
str Text
"mV")
  , (Text
"V", Text -> Exp
str Text
"V")
  , (Text
"kV", Text -> Exp
str Text
"kV")
  , (Text
"W", Text -> Exp
str Text
"W")
  , (Text
"uW", Text -> Exp
str Text
"μW")
  , (Text
"mW", Text -> Exp
str Text
"mW")
  , (Text
"kW", Text -> Exp
str Text
"kW")
  , (Text
"MW", Text -> Exp
str Text
"MW")
  , (Text
"GW", Text -> Exp
str Text
"GW")
  , (Text
"J", Text -> Exp
str Text
"J")
  , (Text
"uJ", Text -> Exp
str Text
"μJ")
  , (Text
"mJ", Text -> Exp
str Text
"mJ")
  , (Text
"kJ", Text -> Exp
str Text
"kJ")
  , (Text
"eV", Text -> Exp
str Text
"eV")
  , (Text
"meV", Text -> Exp
str Text
"meV")
  , (Text
"keV", Text -> Exp
str Text
"keV")
  , (Text
"MeV", Text -> Exp
str Text
"MeV")
  , (Text
"GeV", Text -> Exp
str Text
"GeV")
  , (Text
"TeV", Text -> Exp
str Text
"TeV")
  , (Text
"kWh", Text -> Exp
str Text
"kWh")
  , (Text
"F", Text -> Exp
str Text
"F")
  , (Text
"fF", Text -> Exp
str Text
"fF")
  , (Text
"pF", Text -> Exp
str Text
"pF")
  , (Text
"K", Text -> Exp
str Text
"K")
  , (Text
"dB", Text -> Exp
str Text
"dB")
  , (Text
"ampere", Text -> Exp
str Text
"A")
  , (Text
"angstrom", Text -> Exp
str Text
"Å")
  , (Text
"arcmin", Text -> Exp
str Text
"′")
  , (Text
"arcminute", Text -> Exp
str Text
"′")
  , (Text
"arcsecond", Text -> Exp
str Text
"″")
  , (Text
"astronomicalunit", Text -> Exp
str Text
"ua")
  , (Text
"atomicmassunit", Text -> Exp
str Text
"u")
  , (Text
"atto", Text -> Exp
str Text
"a")
  , (Text
"bar", Text -> Exp
str Text
"bar")
  , (Text
"barn", Text -> Exp
str Text
"b")
  , (Text
"becquerel", Text -> Exp
str Text
"Bq")
  , (Text
"bel", Text -> Exp
str Text
"B")
  , (Text
"bohr", Exp -> Exp -> Exp
ESuper (TextType -> Text -> Exp
EText TextType
TextItalic Text
"a") (Text -> Exp
ENumber Text
"0"))
  , (Text
"candela", Text -> Exp
str Text
"cd")
  , (Text
"celsius", Text -> Exp
str Text
"°C")
  , (Text
"centi", Text -> Exp
str Text
"c")
  , (Text
"clight", Exp -> Exp -> Exp
ESuper (TextType -> Text -> Exp
EText TextType
TextItalic Text
"c") (Text -> Exp
ENumber Text
"0"))
  , (Text
"coulomb", Text -> Exp
str Text
"C")
  , (Text
"dalton", Text -> Exp
str Text
"Da")
  , (Text
"day", Text -> Exp
str Text
"d")
  , (Text
"deca", Text -> Exp
str Text
"d")
  , (Text
"deci", Text -> Exp
str Text
"d")
  , (Text
"decibel", Text -> Exp
str Text
"db")
  , (Text
"degreeCelsius",Text -> Exp
str Text
"°C")
  , (Text
"degree", Text -> Exp
str Text
"°")
  , (Text
"deka", Text -> Exp
str Text
"d")
  , (Text
"electronmass", Exp -> Exp -> Exp
ESuper (TextType -> Text -> Exp
EText TextType
TextItalic Text
"m") (TextType -> Text -> Exp
EText TextType
TextItalic Text
"e"))
  , (Text
"electronvolt", Text -> Exp
str Text
"eV")
  , (Text
"elementarycharge", TextType -> Text -> Exp
EText TextType
TextItalic Text
"e")
  , (Text
"exa", Text -> Exp
str Text
"E")
  , (Text
"farad", Text -> Exp
str Text
"F")
  , (Text
"femto", Text -> Exp
str Text
"f")
  , (Text
"giga", Text -> Exp
str Text
"G")
  , (Text
"gram", Text -> Exp
str Text
"g")
  , (Text
"gray", Text -> Exp
str Text
"Gy")
  , (Text
"hartree", Exp -> Exp -> Exp
ESuper (TextType -> Text -> Exp
EText TextType
TextItalic Text
"E") (TextType -> Text -> Exp
EText TextType
TextItalic Text
"h"))
  , (Text
"hectare", Text -> Exp
str Text
"ha")
  , (Text
"hecto", Text -> Exp
str Text
"h")
  , (Text
"henry", Text -> Exp
str Text
"H")
  , (Text
"hertz", Text -> Exp
str Text
"Hz")
  , (Text
"hour", Text -> Exp
str Text
"h")
  , (Text
"joule", Text -> Exp
str Text
"J")
  , (Text
"katal", Text -> Exp
str Text
"kat")
  , (Text
"kelvin", Text -> Exp
str Text
"K")
  , (Text
"kilo", Text -> Exp
str Text
"k")
  , (Text
"kilogram", Text -> Exp
str Text
"kg")
  , (Text
"knot", Text -> Exp
str Text
"kn")
  , (Text
"liter", Text -> Exp
str Text
"L")
  , (Text
"litre", Text -> Exp
str Text
"l")
  , (Text
"lumen", Text -> Exp
str Text
"lm")
  , (Text
"lux", Text -> Exp
str Text
"lx")
  , (Text
"mega", Text -> Exp
str Text
"M")
  , (Text
"meter", Text -> Exp
str Text
"m")
  , (Text
"metre", Text -> Exp
str Text
"m")
  , (Text
"micro", Text -> Exp
str Text
"μ")
  , (Text
"milli", Text -> Exp
str Text
"m")
  , (Text
"minute", Text -> Exp
str Text
"min")
  , (Text
"mmHg", Text -> Exp
str Text
"mmHg")
  , (Text
"mole", Text -> Exp
str Text
"mol")
  , (Text
"nano", Text -> Exp
str Text
"n")
  , (Text
"nauticalmile", Text -> Exp
str Text
"M")
  , (Text
"neper", Text -> Exp
str Text
"Np")
  , (Text
"newton", Text -> Exp
str Text
"N")
  , (Text
"ohm", Text -> Exp
str Text
"Ω")
  , (Text
"Pa", Text -> Exp
str Text
"Pa")
  , (Text
"pascal", Text -> Exp
str Text
"Pa")
  , (Text
"percent", Text -> Exp
str Text
"%")
  , (Text
"per", Text -> Exp
str Text
"/")
  , (Text
"peta", Text -> Exp
str Text
"P")
  , (Text
"pico", Text -> Exp
str Text
"p")
  , (Text
"planckbar", TextType -> Text -> Exp
EText TextType
TextItalic Text
"\x210f")
  , (Text
"radian", Text -> Exp
str Text
"rad")
  , (Text
"second", Text -> Exp
str Text
"s")
  , (Text
"siemens", Text -> Exp
str Text
"S")
  , (Text
"sievert", Text -> Exp
str Text
"Sv")
  , (Text
"steradian", Text -> Exp
str Text
"sr")
  , (Text
"tera", Text -> Exp
str Text
"T")
  , (Text
"tesla", Text -> Exp
str Text
"T")
  , (Text
"tonne", Text -> Exp
str Text
"t")
  , (Text
"volt", Text -> Exp
str Text
"V")
  , (Text
"watt", Text -> Exp
str Text
"W")
  , (Text
"weber", Text -> Exp
str Text
"Wb")
  , (Text
"yocto", Text -> Exp
str Text
"y")
  , (Text
"yotta", Text -> Exp
str Text
"Y")
  , (Text
"zepto", Text -> Exp
str Text
"z")
  , (Text
"zetta", Text -> Exp
str Text
"Z")
  ]
 where
  str :: Text -> Exp
str = TextType -> Text -> Exp
EText TextType
TextNormal