Script 'mail_helper' called by obssrc Hello community, here is the log from the commit of package texmath for openSUSE:Factory checked in at 2021-02-16 22:39:23 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Comparing /work/SRC/openSUSE:Factory/texmath (Old) and /work/SRC/openSUSE:Factory/.texmath.new.28504 (New) ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "texmath" Tue Feb 16 22:39:23 2021 rev:41 rq:870888 version:0.12.1.1 Changes: -------- --- /work/SRC/openSUSE:Factory/texmath/texmath.changes 2021-01-08 17:40:08.781010591 +0100 +++ /work/SRC/openSUSE:Factory/.texmath.new.28504/texmath.changes 2021-02-16 22:48:56.898580273 +0100 @@ -1,0 +2,13 @@ +Mon Feb 8 05:04:15 UTC 2021 - psim...@suse.com + +- Update texmath to version 0.12.1.1. + texmath (0.12.1.1) + + * Fix compilation with GHC-9.0.1 (#169, Simon Jakobi). + Background: + https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.0#simplified-subsumption + * Add eqn to online demo. + * Improve error messages for unknown control sequences, and restructure + tex parser to be more efficient (#167). + +------------------------------------------------------------------- Old: ---- texmath-0.12.1.tar.gz New: ---- texmath-0.12.1.1.tar.gz ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Other differences: ------------------ ++++++ texmath.spec ++++++ --- /var/tmp/diff_new_pack.wUMhQG/_old 2021-02-16 22:48:57.770580955 +0100 +++ /var/tmp/diff_new_pack.wUMhQG/_new 2021-02-16 22:48:57.774580957 +0100 @@ -1,7 +1,7 @@ # # spec file for package texmath # -# Copyright (c) 2020 SUSE LLC +# Copyright (c) 2021 SUSE LLC # # All modifications and additions to the file contributed by third parties # remain the property of their copyright owners, unless otherwise agreed @@ -19,7 +19,7 @@ %global pkg_name texmath %bcond_with tests Name: %{pkg_name} -Version: 0.12.1 +Version: 0.12.1.1 Release: 0 Summary: Conversion between formats used to represent mathematics License: GPL-2.0-or-later ++++++ texmath-0.12.1.tar.gz -> texmath-0.12.1.1.tar.gz ++++++ diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.12.1/cgi/texmath.html new/texmath-0.12.1.1/cgi/texmath.html --- old/texmath-0.12.1/cgi/texmath.html 2017-06-19 11:07:56.000000000 +0200 +++ new/texmath-0.12.1.1/cgi/texmath.html 2021-01-26 18:17:59.000000000 +0100 @@ -67,6 +67,23 @@ MathJax.Hub.Queue(["Typeset",MathJax.Hub,"preview"]); }, 'json') }); + $('#convert-latex2eqn').click(function() { + $.post("/cgi-bin/texmath-cgi", + { 'input' : $('#latex-input').val(), + 'from': 'tex', + 'to': 'eqn' }, + function(result){ + if (result.success) { + var res = result.success; + $('#eqn-result').text(res); + $('#preview').html(removeSelfClosingTags(res)); + } else { + $('#eqn-result').text(result.error); + $('#preview').html(''); + }; + MathJax.Hub.Queue(["Typeset",MathJax.Hub,"preview"]); + }, 'json') + }); $('a[data-toggle="tab"]').click(function (e) { $('#preview').text(''); // clear preview MathJax.Hub.Queue(["Typeset",MathJax.Hub,"preview"]); @@ -87,6 +104,7 @@ <div class="col-md-12"> <ul class="nav nav-tabs" role="tablist"> <li class="active"><a href="#tex2mathml" role="tab" data-toggle="tab">LaTeX ⇒ MathML</a></li> + <li><a href="#tex2eqn" role="tab" data-toggle="tab">LaTeX ⇒ eqn</a></li> <li><a href="#mathml2tex" role="tab" data-toggle="tab">MathML ⇒ LaTeX</a></li> <li><a href="#installing" role="tab" data-toggle="tab">Installing</a></li> </ul> @@ -104,6 +122,17 @@ <pre id="mathml-result"></pre> </div> </div> + <div id="tex2eqn" class="tab-pane active"> + <div class="col-md-6"> + <label for="latex-input">Enter a LaTeX formula here. (You may precede it with macro definitions.)</label><br/> + <textarea name="latex-input" rows="10" id="latex-input">\iiint_{0}^{1}f\left( x \right)\mathbb{d}x</textarea> + <br/> + <input type="submit" id="convert-latex2eqn" value="Convert to eqn" /> + </div> + <div class="col-md-6"> + <pre id="eqn-result"></pre> + </div> + </div> <div id="mathml2tex" class="tab-pane"> <div class="col-md-6"> <label for="mathml-input">Enter a MathML formula here.</label><br/> diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.12.1/changelog new/texmath-0.12.1.1/changelog --- old/texmath-0.12.1/changelog 2020-12-28 06:43:23.000000000 +0100 +++ new/texmath-0.12.1.1/changelog 2021-02-07 07:06:24.000000000 +0100 @@ -1,3 +1,12 @@ +texmath (0.12.1.1) + + * Fix compilation with GHC-9.0.1 (#169, Simon Jakobi). + Background: + https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.0#simplified-subsumption + * Add eqn to online demo. + * Improve error messages for unknown control sequences, and restructure + tex parser to be more efficient (#167). + texmath (0.12.1) * OMML writer: explicitly mark symbols as non-italic (#109). diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.12.1/src/Text/TeXMath/Readers/TeX/Macros.hs new/texmath-0.12.1.1/src/Text/TeXMath/Readers/TeX/Macros.hs --- old/texmath-0.12.1/src/Text/TeXMath/Readers/TeX/Macros.hs 2019-11-12 20:07:47.000000000 +0100 +++ new/texmath-0.12.1.1/src/Text/TeXMath/Readers/TeX/Macros.hs 2021-02-07 07:04:44.000000000 +0100 @@ -103,7 +103,7 @@ Left _ -> Nothing where tok = try $ do skipComment - choice [ choice (map macroParser ms) + choice [ choice (map (\m -> macroParser m) ms) , T.pack <$> ctrlseq , T.pack <$> count 1 anyChar ] diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.12.1/src/Text/TeXMath/Readers/TeX.hs new/texmath-0.12.1.1/src/Text/TeXMath/Readers/TeX.hs --- old/texmath-0.12.1/src/Text/TeXMath/Readers/TeX.hs 2020-12-28 03:52:01.000000000 +0100 +++ new/texmath-0.12.1.1/src/Text/TeXMath/Readers/TeX.hs 2021-01-09 20:45:54.000000000 +0100 @@ -31,6 +31,7 @@ import Data.Char (isDigit, isAscii, isLetter) import qualified Data.Map as M import qualified Data.Text as T +import Data.Text (Text) import Data.Maybe (mapMaybe, catMaybes) import Data.Semigroup ((<>)) import Text.Parsec hiding (label) @@ -55,36 +56,21 @@ [ inbraces , variable , number - , text - , styled - , root - , mspace - , hspace - , mathop - , phantom - , boxed - , binary - , genfrac - , substack - , bareSubSup - , environment , unicode - , ensuremath - , scaled + , operator + , bareSubSup , enclosure - , negated - , siunitx - , texSymbol + , command ] <* ignorable -- | Parse a formula, returning a list of 'Exp'. -readTeX :: T.Text -> Either T.Text [Exp] +readTeX :: Text -> Either Text [Exp] readTeX inp = let (ms, rest) = parseMacroDefinitions inp in either (Left . showParseError inp) (Right . id) $ parse formula "formula" $ applyMacros ms rest -showParseError :: T.Text -> ParseError -> T.Text +showParseError :: Text -> ParseError -> Text showParseError inp pe = snippet <> "\n" <> caretline <> T.pack (showErrorMessages "or" "unknown" "expecting" "unexpected" "eof" @@ -99,7 +85,7 @@ snippet = T.take 40 $ T.drop snipoffset ln caretline = T.replicate (errcol - snipoffset - 1) " " <> "^" -anyCtrlSeq :: TP T.Text +anyCtrlSeq :: TP Text anyCtrlSeq = lexeme $ try $ do char '\\' res <- count 1 (satisfy (not . isLetter)) <|> many1 (satisfy isLetter) @@ -142,11 +128,36 @@ optional (ctrlseq "displaystyle" <|> ctrlseq "textstyle" <|> ctrlseq "scriptstyle" <|> ctrlseq "scriptscriptstyle") (a, convertible) <- try (braces operatorname) -- needed because macros add {} - <|> ((,False) <$> expr1) <|> operatorname + <|> ((,False) <$> expr1) limits <- limitsIndicator subSup limits convertible a <|> superOrSubscripted limits convertible a <|> return a +command :: TP Exp +command = try $ do + c <- anyCtrlSeq + guard $ c /= "\\end" -- handled in environment + && c /= "\\operatorname" -- handled in expr + choice + [ text c + , styled c + , root c + , xspace c + , mathop c + , phantom c + , boxed c + , binary c + , genfrac c + , substack c + , environment c + , ensuremath c + , scaled c + , negated c + , siunitx c + , tSymbol c + ] <|> unexpected ("control sequence " <> T.unpack c) + + -- | Parser for \operatorname command. -- Returns a tuple of EMathOperator name and Bool depending on the flavor -- of the command: @@ -164,7 +175,7 @@ -- | Converts identifiers, symbols and numbers to a flat string. -- Returns Nothing if the expression contains anything else. -expToOperatorName :: Exp -> Maybe T.Text +expToOperatorName :: Exp -> Maybe Text expToOperatorName e = case e of EGrouped xs -> T.concat <$> mapM fl xs _ -> fl e @@ -201,10 +212,10 @@ <|> (ctrlseq "nolimits" >> return (Just False)) <|> return Nothing -binomCmd :: TP T.Text +binomCmd :: TP Text binomCmd = oneOfCommands (M.keys binomCmds) -binomCmds :: M.Map T.Text (Exp -> Exp -> Exp) +binomCmds :: M.Map Text (Exp -> Exp -> Exp) binomCmds = M.fromList [ ("\\choose", \x y -> EDelimited "(" ")" [Right (EFraction NoLineFrac x y)]) @@ -216,9 +227,8 @@ EDelimited "\x27E8" "\x27E9" [Right (EFraction NoLineFrac x y)]) ] -genfrac :: TP Exp -genfrac = do - ctrlseq "genfrac" +genfrac :: Text -> TP Exp +genfrac "\\genfrac" = do let opener = option "" $ T.singleton <$> ((char '\\' >> anyChar) <|> anyChar) let closer = option "" $ @@ -235,12 +245,13 @@ _ -> NormalFrac return $ EDelimited openDelim closeDelim [Right (EFraction fracType x y)] +genfrac _ = mzero -substack :: TP Exp -substack = do - ctrlseq "substack" +substack :: Text -> TP Exp +substack "\\substack" = do formulas <- braces $ ignorable >> (manyExp expr) `sepEndBy` endLine return $ EArray [AlignCenter] $ map (\x -> [[x]]) formulas +substack _ = mzero asGroup :: [Exp] -> Exp asGroup [x] = x @@ -252,7 +263,7 @@ initial <- if requireNonempty then many1 (notFollowedBy binomCmd >> p) else many (notFollowedBy binomCmd >> p) - let withCmd :: T.Text -> TP Exp + let withCmd :: Text -> TP Exp withCmd cmd = case M.lookup cmd binomCmds of Just f -> f <$> (asGroup <$> pure initial) @@ -305,7 +316,7 @@ Just x -> return x Nothing -> mzero -fence :: String -> TP T.Text +fence :: String -> TP Text fence cmd = do symbol cmd enc <- basicEnclosure <|> (try (symbol ".") >> return (ESymbol Open "")) @@ -314,10 +325,10 @@ ESymbol Close x -> return x _ -> mzero -middle :: TP T.Text +middle :: TP Text middle = fence "\\middle" -right :: TP T.Text +right :: TP Text right = fence "\\right" delimited :: TP Exp @@ -330,9 +341,8 @@ closec <- right <|> return "" return $ EDelimited openc closec contents -scaled :: TP Exp -scaled = do - cmd <- oneOfCommands (map fst S.scalers) +scaled :: Text -> TP Exp +scaled cmd = do case S.getScalerValue cmd of Just r -> EScaled r <$> (basicEnclosure <|> operator) Nothing -> mzero @@ -371,9 +381,8 @@ letterToAlignment _ = AlignCenter return $ map letterToAlignment $ filter (/= '|') as -environment :: TP Exp -environment = do - ctrlseq "begin" +environment :: Text -> TP Exp +environment "\\begin" = do name <- braces (oneOfStrings (M.keys environments) <* optional (char '*')) spaces case M.lookup name environments of @@ -385,8 +394,9 @@ spaces return result Nothing -> mzero -- should not happen +environment _ = mzero -environments :: M.Map T.Text (TP Exp) +environments :: M.Map Text (TP Exp) environments = M.fromList [ ("array", stdarray) , ("eqnarray", eqnarray) @@ -415,7 +425,7 @@ alignsFromRows _ [] = [] alignsFromRows defaultAlignment (r:_) = replicate (length r) defaultAlignment -matrixWith :: T.Text -> T.Text -> TP Exp +matrixWith :: Text -> Text -> TP Exp matrixWith opendelim closedelim = do lines' <- sepEndBy1 arrayLine endLineAMS let aligns = alignsFromRows AlignCenter lines' @@ -530,11 +540,12 @@ c <- satisfy (not . isAscii) return (ESymbol (getSymbolType c) $ T.singleton c) -ensuremath :: TP Exp -ensuremath = ctrlseq "ensuremath" *> inbraces +ensuremath :: Text -> TP Exp +ensuremath "\\ensuremath" = inbraces +ensuremath _ = mzero -- Note: cal and scr are treated the same way, as unicode is lacking such two different sets for those. -styleOps :: M.Map T.Text ([Exp] -> Exp) +styleOps :: M.Map Text ([Exp] -> Exp) styleOps = M.fromList [ ("\\mathrm", EStyled TextNormal) , ("\\mathup", EStyled TextNormal) @@ -564,15 +575,16 @@ , ("\\mathsfit", EStyled TextSansSerifItalic) ] -phantom :: TP Exp -phantom = EPhantom <$> (ctrlseq "phantom" *> texToken) - -boxed :: TP Exp -boxed = EBoxed <$> (ctrlseq "boxed" *> texToken) +phantom :: Text -> TP Exp +phantom "\\phantom" = EPhantom <$> texToken +phantom _ = mzero + +boxed :: Text -> TP Exp +boxed "\\boxed" = EBoxed <$> texToken +boxed _ = mzero -text :: TP Exp -text = do - c <- oneOfCommands (M.keys textOps) +text :: Text -> TP Exp +text c = do op <- maybe mzero return $ M.lookup c textOps char '{' let chunk = ((op . T.concat) <$> many1 textual) @@ -596,7 +608,7 @@ string closer return e -textOps :: M.Map T.Text (T.Text -> Exp) +textOps :: M.Map Text (Text -> Exp) textOps = M.fromList [ ("\\textrm", (EText TextNormal)) , ("\\text", (EText TextNormal)) @@ -607,9 +619,8 @@ , ("\\mbox", (EText TextNormal)) ] -styled :: TP Exp -styled = do - c <- oneOfCommands (M.keys styleOps) +styled :: Text -> TP Exp +styled c = do case M.lookup c styleOps of Just f -> do x <- texSymbol <|> inbraces <|> texChar @@ -619,13 +630,13 @@ Nothing -> mzero -- note: sqrt can be unary, \sqrt{2}, or binary, \sqrt[3]{2} -root :: TP Exp -root = do - ctrlseq "sqrt" <|> ctrlseq "surd" +root :: Text -> TP Exp +root c = do + guard $ c == "\\sqrt" || c == "\\surd" (ERoot <$> inbrackets <*> texToken) <|> (ESqrt <$> texToken) -mspace :: TP Exp -mspace = do +xspace :: Text -> TP Exp +xspace "\\mspace" = do ctrlseq "mspace" braces $ do len <- many1 digit @@ -633,11 +644,7 @@ case reads len of ((n :: Integer,[]):_) -> return $ ESpace (fromIntegral n/18) _ -> mzero - - -hspace :: TP Exp -hspace = do - ctrlseq "hspace" +xspace "\\hspace" = do braces $ do len <- many1 digit scaleFactor <- @@ -648,20 +655,22 @@ case reads len of ((n :: Integer,[]):_) -> return $ ESpace (fromIntegral n * scaleFactor) _ -> mzero +xspace _ = mzero +mathop :: Text -> TP Exp +mathop c = + case c of + "\\mathop" -> mathopWith Op + "\\mathrel" -> mathopWith Rel + "\\mathbin" -> mathopWith Bin + "\\mathord" -> mathopWith Ord + "\\mathopen" -> mathopWith Open + "\\mathclose" -> mathopWith Close + "\\mathpunct" -> mathopWith Pun + _ -> mzero -mathop :: TP Exp -mathop = mathopWith "mathop" Op - <|> mathopWith "mathrel" Rel - <|> mathopWith "mathbin" Bin - <|> mathopWith "mathord" Ord - <|> mathopWith "mathopen" Open - <|> mathopWith "mathclose" Close - <|> mathopWith "mathpunct" Pun - -mathopWith :: String -> TeXSymbolType -> TP Exp -mathopWith name ty = try $ do - ctrlseq name +mathopWith :: TeXSymbolType -> TP Exp +mathopWith ty = do e <- inbraces <|> expr1 let es' = case e of EGrouped xs -> xs @@ -675,30 +684,37 @@ T.concat $ mapMaybe expToOperatorName xs | otherwise -> return $ EGrouped xs -binary :: TP Exp -binary = do - c <- oneOfCommands binops - a <- texToken - b <- texToken +binary :: Text -> TP Exp +binary c = do case c of - "\\overset" -> return $ EOver False b a - "\\stackrel" -> return $ EOver False b a - "\\underset" -> return $ EUnder False b a - "\\frac" -> return $ EFraction NormalFrac a b - "\\tfrac" -> return $ EFraction InlineFrac a b - "\\dfrac" -> return $ EFraction DisplayFrac a b - "\\binom" -> return $ EDelimited "(" ")" - [Right (EFraction NoLineFrac a b)] - _ -> fail "Unrecognised binary operator" - where - binops = ["\\overset", "\\stackrel", "\\underset", "\\frac", "\\tfrac", "\\dfrac", "\\binom"] + "\\overset" -> do + a <- texToken + b <- texToken + return $ EOver False b a + "\\stackrel" -> do + a <- texToken + b <- texToken + return $ EOver False b a + "\\underset" -> do + a <- texToken + b <- texToken + return $ EUnder False b a + "\\frac" -> EFraction NormalFrac <$> texToken <*> texToken + "\\tfrac" -> EFraction InlineFrac <$> texToken <*> texToken + "\\dfrac" -> EFraction DisplayFrac <$> texToken <*> texToken + "\\binom" -> do + a <- texToken + b <- texToken + return $ EDelimited "(" ")" [Right (EFraction NoLineFrac a b)] + _ -> mzero texSymbol :: TP Exp -texSymbol = operator <|> tSymbol <|> negated +texSymbol = operator <|> + try (do c <- anyCtrlSeq + tSymbol c <|> negated c) -negated :: TP Exp -negated = do - ctrlseq "not" +negated :: Text -> TP Exp +negated "\\not" = do sym <- texSymbol <|> texChar case sym of ESymbol Rel x -> return $ ESymbol Rel $ toNeg x @@ -706,8 +722,9 @@ ENumber x -> return $ ENumber $ toNeg x EIdentifier x -> return $ EIdentifier $ toNeg x _ -> mzero +negated _ = mzero -toNeg :: T.Text -> T.Text +toNeg :: Text -> Text toNeg x = case x of "\x2203" -> "\x2204" "\x2208" -> "\x2209" @@ -738,7 +755,7 @@ _ -> x <> "\x0338" -oneOfCommands :: [T.Text] -> TP T.Text +oneOfCommands :: [Text] -> TP Text oneOfCommands cmds = try $ do cmd <- oneOfStrings cmds case T.unpack cmd of @@ -751,7 +768,7 @@ spaces return cmd -oneOfStrings' :: (Char -> Char -> Bool) -> [(String, T.Text)] -> TP T.Text +oneOfStrings' :: (Char -> Char -> Bool) -> [(String, Text)] -> TP Text oneOfStrings' _ [] = mzero oneOfStrings' matches strs = try $ do c <- anyChar @@ -766,7 +783,7 @@ -- | Parses one of a list of strings. If the list contains -- two strings one of which is a prefix of the other, the longer -- string will be matched if possible. -oneOfStrings :: [T.Text] -> TP T.Text +oneOfStrings :: [Text] -> TP Text oneOfStrings strs = oneOfStrings' (==) strs' <??> (intercalate ", " $ map show strs) where strs' = map (\x -> (T.unpack x, x)) strs @@ -780,9 +797,8 @@ infix 0 <??> -tSymbol :: TP Exp -tSymbol = try $ do - sym <- anyCtrlSeq +tSymbol :: Text -> TP Exp +tSymbol sym = case M.lookup sym symbols of Just acc@(ESymbol Accent _) -> (\t -> EOver False t acc) <$> texToken @@ -825,16 +841,16 @@ brackets :: TP a -> TP a brackets p = lexeme $ char '[' *> spaces *> p <* spaces <* char ']' -textStr :: T.Text -> TP T.Text +textStr :: Text -> TP Text textStr t = string (T.unpack t) $> t -countChar :: Int -> TP Char -> TP T.Text +countChar :: Int -> TP Char -> TP Text countChar n = fmap T.pack . count n symbol :: String -> TP String symbol s = lexeme $ try $ string s -enclosures :: M.Map T.Text Exp +enclosures :: M.Map Text Exp enclosures = M.fromList [ ("(", ESymbol Open "(") , (")", ESymbol Close ")") @@ -868,7 +884,7 @@ , ("\\urcorner", ESymbol Close "\x231D") ] -operators :: M.Map T.Text Exp +operators :: M.Map Text Exp operators = M.fromList [ ("+", ESymbol Bin "+") , ("-", ESymbol Bin "\x2212") @@ -891,7 +907,7 @@ , ("/", ESymbol Ord "/") , ("~", ESpace (4/18)) ] -symbols :: M.Map T.Text Exp +symbols :: M.Map Text Exp symbols = M.fromList [ ("\\$",ESymbol Ord "$") , ("\\%",ESymbol Ord "%") @@ -3816,17 +3832,17 @@ -- text mode parsing -textual :: TP T.Text +textual :: TP Text textual = regular <|> sps <|> ligature <|> textCommand <?> "text" -sps :: TP T.Text +sps :: TP Text sps = " " <$ skipMany1 (oneOf " \t\n") -regular :: TP T.Text +regular :: TP Text regular = T.pack <$> many1 (noneOf "`'-~${}\\ \t") -ligature :: TP T.Text +ligature :: TP Text ligature = try ("\x2014" <$ string "---") <|> try ("\x2013" <$ string "--") <|> try (textStr "-") @@ -3836,7 +3852,7 @@ <|> try ("\x2018" <$ string "`") <|> try ("\xA0" <$ string "~") -textCommand :: TP T.Text +textCommand :: TP Text textCommand = do cmd <- oneOfCommands (M.keys textCommands) optional $ try (char '{' >> spaces >> char '}') @@ -3848,7 +3864,7 @@ tok = (try $ char '{' *> spaces *> anyChar <* spaces <* char '}') <|> anyChar -textCommands :: M.Map T.Text (TP T.Text) +textCommands :: M.Map Text (TP Text) textCommands = M.fromList [ ("\\#", return "#") , ("\\$", return "$") @@ -3886,12 +3902,12 @@ , ("\\ ", return " ") ] -parseC :: TP T.Text +parseC :: TP Text parseC = try $ char '`' >> countChar 1 anyChar -- the functions below taken from pandoc: -grave :: Char -> T.Text +grave :: Char -> Text grave 'A' = "??" grave 'E' = "??" grave 'I' = "??" @@ -3904,7 +3920,7 @@ grave 'u' = "??" grave c = T.singleton c -acute :: Char -> T.Text +acute :: Char -> Text acute 'A' = "??" acute 'E' = "??" acute 'I' = "??" @@ -3931,7 +3947,7 @@ acute 'z' = "??" acute c = T.singleton c -circ :: Char -> T.Text +circ :: Char -> Text circ 'A' = "??" circ 'E' = "??" circ 'I' = "??" @@ -3958,7 +3974,7 @@ circ 'y' = "??" circ c = T.singleton c -tilde :: Char -> T.Text +tilde :: Char -> Text tilde 'A' = "??" tilde 'a' = "??" tilde 'O' = "??" @@ -3971,7 +3987,7 @@ tilde 'n' = "??" tilde c = T.singleton c -umlaut :: Char -> T.Text +umlaut :: Char -> Text umlaut 'A' = "??" umlaut 'E' = "??" umlaut 'I' = "??" @@ -3984,7 +4000,7 @@ umlaut 'u' = "??" umlaut c = T.singleton c -dot :: Char -> T.Text +dot :: Char -> Text dot 'C' = "??" dot 'c' = "??" dot 'E' = "??" @@ -3996,7 +4012,7 @@ dot 'z' = "??" dot c = T.singleton c -macron :: Char -> T.Text +macron :: Char -> Text macron 'A' = "??" macron 'E' = "??" macron 'I' = "??" @@ -4009,7 +4025,7 @@ macron 'u' = "??" macron c = T.singleton c -cedilla :: Char -> T.Text +cedilla :: Char -> Text cedilla 'c' = "??" cedilla 'C' = "??" cedilla 's' = "??" @@ -4024,7 +4040,7 @@ cedilla 'O' = "O??" cedilla c = T.singleton c -hacek :: Char -> T.Text +hacek :: Char -> Text hacek 'A' = "??" hacek 'a' = "??" hacek 'C' = "??" @@ -4060,7 +4076,7 @@ hacek 'z' = "??" hacek c = T.singleton c -breve :: Char -> T.Text +breve :: Char -> Text breve 'A' = "??" breve 'a' = "??" breve 'E' = "??" @@ -4077,17 +4093,16 @@ -- siunitx -siunitx :: TP Exp -siunitx = try $ do - name <- T.dropWhile (=='\\') <$> anyCtrlSeq - case name of - "si" -> dosi - "SI" -> doSI - "SIrange" -> doSIrange True - "numrange" -> doSIrange False - "numlist" -> doSInumlist - "num" -> doSInum - "ang" -> doSIang +siunitx :: Text -> TP Exp +siunitx c = do + case c of + "\\si" -> dosi + "\\SI" -> doSI + "\\SIrange" -> doSIrange True + "\\numrange" -> doSIrange False + "\\numlist" -> doSInumlist + "\\num" -> doSInum + "\\ang" -> doSIang _ -> mzero -- converts e.g. \SIrange{100}{200}{\ms} to "100 ms--200 ms" @@ -4191,7 +4206,7 @@ ] Nothing -> fail "not an siunit unit command" -siUnitMap :: M.Map T.Text Exp +siUnitMap :: M.Map Text Exp siUnitMap = M.fromList [ ("fg", str "fg") , ("pg", str "pg") diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.12.1/texmath.cabal new/texmath-0.12.1.1/texmath.cabal --- old/texmath-0.12.1/texmath.cabal 2020-12-28 06:43:42.000000000 +0100 +++ new/texmath-0.12.1.1/texmath.cabal 2021-02-07 07:06:37.000000000 +0100 @@ -1,5 +1,5 @@ Name: texmath -Version: 0.12.1 +Version: 0.12.1.1 Cabal-Version: >= 1.10 Build-type: Simple Synopsis: Conversion between formats used to represent mathematics.