Hello community, here is the log from the commit of package texmath for openSUSE:Factory checked in at 2017-03-03 17:53:12 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Comparing /work/SRC/openSUSE:Factory/texmath (Old) and /work/SRC/openSUSE:Factory/.texmath.new (New) ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Package is "texmath" Fri Mar 3 17:53:12 2017 rev:20 rq:461709 version:0.9.1 Changes: -------- --- /work/SRC/openSUSE:Factory/texmath/texmath.changes 2016-11-05 21:26:50.000000000 +0100 +++ /work/SRC/openSUSE:Factory/.texmath.new/texmath.changes 2017-03-03 17:53:13.431486002 +0100 @@ -1,0 +2,5 @@ +Sun Feb 12 14:19:55 UTC 2017 - [email protected] + +- Update to version 0.9.1 with cabal2obs. + +------------------------------------------------------------------- Old: ---- texmath-0.8.6.7.tar.gz New: ---- texmath-0.9.1.tar.gz ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ Other differences: ------------------ ++++++ texmath.spec ++++++ --- /var/tmp/diff_new_pack.Y60EUG/_old 2017-03-03 17:53:13.991406918 +0100 +++ /var/tmp/diff_new_pack.Y60EUG/_new 2017-03-03 17:53:13.995406353 +0100 @@ -1,7 +1,7 @@ # # spec file for package texmath # -# Copyright (c) 2016 SUSE LINUX GmbH, Nuernberg, Germany. +# Copyright (c) 2017 SUSE LINUX GmbH, Nuernberg, Germany. # # 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.8.6.7 +Version: 0.9.1 Release: 0 Summary: Conversion between formats used to represent mathematics License: GPL-2.0 @@ -100,7 +100,7 @@ %install %ghc_lib_install -%ghc_fix_dynamic_rpath %{pkg_name} +%ghc_fix_rpath %{pkg_name}-%{version} %check %cabal_test ++++++ texmath-0.8.6.7.tar.gz -> texmath-0.9.1.tar.gz ++++++ diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/changelog new/texmath-0.9.1/changelog --- old/texmath-0.8.6.7/changelog 2016-10-28 20:43:31.000000000 +0200 +++ new/texmath-0.9.1/changelog 2017-02-03 21:17:30.000000000 +0100 @@ -1,3 +1,33 @@ +texmath (0.9.1) + + * Pandoc writer: add thin space after math operators. + * TeX reader: improve parsing of `\mathop` to allow + multi-character operator names. + * Minor optimizations. + * Added Ord instances to Exp and associated types. + +texmath (0.9) + + * OMML writer: Properly handle nary inside delimiters (#92). + Previously under-overs inside delimiters didn't get + converted to nary the way they did outside of delimiters. + * TeX reader: Support bm, mathbold, pmd. + * OMML reader: Handle w:sym (#65). + * New module, Text.TeXMath.Unicode.Fonts, for MS font code point + lookup. Copied from pandoc Text.Pandoc.Readers.Docx.Fonts, + which will be changed to import this. [API change] + * Fixed typo in test program for round-trip tests. + * Parse math inside text constructions (#62). E.g. + `\text{if $y$ is greater than $0$}` Text and math can nest indefinitely. + * Modify test suite so tests can be marked as "ought to raise error." + So far this is only used in mml. If the test is called foo + and `readers/mml/foo.error` exists, then the test is expected + to raise a parse error. + * MathML reader err: Don't print colon after line number. + * Restore proper error handling to MathML reader. Note that the tests + need to be redone, since they assumed the old behavior of just + returning empty elements on parse errors. + texmath (0.8.6.7) * TeX reader: treat backslash + newline as like backslash + space. diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/src/Text/TeXMath/Readers/MathML.hs new/texmath-0.9.1/src/Text/TeXMath/Readers/MathML.hs --- old/texmath-0.8.6.7/src/Text/TeXMath/Readers/MathML.hs 2014-08-10 02:44:23.000000000 +0200 +++ new/texmath-0.9.1/src/Text/TeXMath/Readers/MathML.hs 2017-02-03 19:34:29.000000000 +0100 @@ -120,7 +120,9 @@ "mtable" -> mkE <$> table e "maction" -> mkE <$> action e "semantics" -> mkE <$> semantics e - _ -> return $ mkE empty + "maligngroup" -> return $ mkE empty + "malignmark" -> return $ mkE empty + _ -> throwError $ "Unexpected element " ++ err e where mkE :: Exp -> [IR Exp] mkE = (:[]) . E @@ -560,7 +562,7 @@ nargs n xs = length xs == n err :: Element -> String -err e = name e ++ " line: " ++ (show $ elLine e) ++ (show e) +err e = name e ++ maybe "" (\x -> " line " ++ show x) (elLine e) findAttrQ :: String -> Element -> MML (Maybe String) findAttrQ s e = do diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/src/Text/TeXMath/Readers/OMML.hs new/texmath-0.9.1/src/Text/TeXMath/Readers/OMML.hs --- old/texmath-0.8.6.7/src/Text/TeXMath/Readers/OMML.hs 2015-03-15 18:58:32.000000000 +0100 +++ new/texmath-0.9.1/src/Text/TeXMath/Readers/OMML.hs 2017-02-03 19:34:29.000000000 +0100 @@ -35,11 +35,12 @@ import Text.XML.Light import Data.Maybe (isJust, mapMaybe, fromMaybe) import Data.List (intercalate) -import Data.Char (isDigit) +import Data.Char (isDigit, readLitChar) import Text.TeXMath.Types import Text.TeXMath.Shared (fixTree, getSpaceWidth, getOperator) import Text.TeXMath.Unicode.ToTeX (getSymbolType) import Control.Applicative ((<$>)) +import Text.TeXMath.Unicode.Fonts (getUnicode, stringToFont) readOMML :: String -> Either String [Exp] readOMML s | Just e <- parseXMLDoc s = @@ -163,6 +164,7 @@ || isElem "w" "delText" element = Just $ TextRun $ strContent element | isElem "w" "br" element = Just LnBrk | isElem "w" "tab" element = Just Tab + | isElem "w" "sym" element = Just $ TextRun $ getSymChar element | otherwise = Nothing elemToOMathRunElems :: Element -> Maybe [OMathRunElem] @@ -467,3 +469,17 @@ expToString (EGrouped exps) = concatMap expToString exps expToString (EStyled _ exps) = concatMap expToString exps expToString _ = "" + +-- The char attribute is a hex string +getSymChar :: Element -> String +getSymChar element + | Just s <- lowerFromPrivate <$> getCodepoint + , Just font <- getFont = + let [(char, _)] = readLitChar ("\\x" ++ s) in + maybe "" (:[]) $ getUnicode font char + where + getCodepoint = findAttrBy (hasElemName "w" "char") element + getFont = stringToFont =<< findAttrBy (hasElemName "w" "font") element + lowerFromPrivate ('F':xs) = '0':xs + lowerFromPrivate xs = xs +getSymChar _ = "" diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/src/Text/TeXMath/Readers/TeX.hs new/texmath-0.9.1/src/Text/TeXMath/Readers/TeX.hs --- old/texmath-0.8.6.7/src/Text/TeXMath/Readers/TeX.hs 2016-10-28 20:40:11.000000000 +0200 +++ new/texmath-0.9.1/src/Text/TeXMath/Readers/TeX.hs 2017-02-03 21:06:56.000000000 +0100 @@ -143,6 +143,7 @@ operatorname :: TP (Exp, Bool) operatorname = do ctrlseq "operatorname" + -- these are slightly different but we won't worry about that here... convertible <- (char '*' >> spaces >> return True) <|> return False op <- expToOperatorName <$> texToken maybe mzero (\s -> return (EMathOperator s, convertible)) op @@ -187,10 +188,11 @@ <|> return Nothing binomCmd :: TP String -binomCmd = oneOfCommands (map fst binomCmds) +binomCmd = oneOfCommands (M.keys binomCmds) -binomCmds :: [(String, Exp -> Exp -> Exp)] -binomCmds = [ ("\\choose", \x y -> +binomCmds :: M.Map String (Exp -> Exp -> Exp) +binomCmds = M.fromList + [ ("\\choose", \x y -> EDelimited "(" ")" [Right (EFraction NoLineFrac x y)]) , ("\\brack", \x y -> EDelimited "[" "]" [Right (EFraction NoLineFrac x y)]) @@ -233,7 +235,7 @@ else many (notFollowedBy binomCmd >> p) let withCmd :: String -> TP Exp withCmd cmd = - case lookup cmd binomCmds of + case M.lookup cmd binomCmds of Just f -> f <$> (asGroup <$> pure initial) <*> (asGroup <$> many p) Nothing -> fail $ "Unknown command " ++ cmd @@ -504,6 +506,9 @@ , ("\\mathup", EStyled TextNormal) , ("\\mathbf", EStyled TextBold) , ("\\boldsymbol", EStyled TextBold) + , ("\\bm", EStyled TextBold) + , ("\\mathbold", EStyled TextBold) + , ("\\pmb", EStyled TextBold) , ("\\mathbfup", EStyled TextBold) , ("\\mathit", EStyled TextItalic) , ("\\mathtt", EStyled TextMonospace) @@ -540,7 +545,28 @@ text :: TP Exp text = do c <- oneOfCommands (M.keys textOps) - maybe mzero (<$> (bracedText <* spaces)) $ M.lookup c textOps + op <- maybe mzero return $ M.lookup c textOps + char '{' + let chunk = ((op . concat) <$> many1 textual) + <|> (char '{' *> (asGroup <$> manyTill chunk (char '}'))) + <|> innermath + contents <- manyTill chunk (char '}') + spaces + case contents of + [] -> return (op "") + [x] -> return x + xs -> return (EGrouped xs) + +innermath :: TP Exp +innermath = choice $ map innerMathWith + [("$","$"),("$$","$$"),("\\(","\\)"),("\\[","\\]")] + +innerMathWith :: (String, String) -> TP Exp +innerMathWith (opener, closer) = do + try (string opener) + e <- manyExp expr + string closer + return e textOps :: M.Map String (String -> Exp) textOps = M.fromList @@ -598,7 +624,10 @@ case e of ESymbol _ x -> return $ ESymbol ty x EIdentifier x -> return $ ESymbol ty x - x -> return x + x | ty == Op -> case expToOperatorName x of + Just y -> return $ EMathOperator y + _ -> return x + | otherwise -> return x binary :: TP Exp binary = do @@ -3682,7 +3711,7 @@ -- text mode parsing textual :: TP String -textual = regular <|> sps <|> ligature <|> textCommand <|> bracedText +textual = regular <|> sps <|> ligature <|> textCommand <?> "text" sps :: TP String @@ -3704,17 +3733,11 @@ textCommand :: TP String textCommand = do cmd <- oneOfCommands (M.keys textCommands) + optional $ try (char '{' >> spaces >> char '}') case M.lookup cmd textCommands of Nothing -> fail ("Unknown control sequence " ++ cmd) Just c -> c -bracedText :: TP String -bracedText = do - char '{' - inner <- concat <$> many textual - char '}' - return inner - tok :: TP Char tok = (try $ char '{' *> spaces *> anyChar <* spaces <* char '}') <|> anyChar diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/src/Text/TeXMath/Shared.hs new/texmath-0.9.1/src/Text/TeXMath/Shared.hs --- old/texmath-0.8.6.7/src/Text/TeXMath/Shared.hs 2016-02-08 07:18:07.000000000 +0100 +++ new/texmath-0.9.1/src/Text/TeXMath/Shared.hs 2017-02-03 21:13:23.000000000 +0100 @@ -39,6 +39,7 @@ import Text.TeXMath.Types import Text.TeXMath.TeX import qualified Data.Map as M +import qualified Data.Set as Set import Data.Maybe (fromMaybe) import Data.Ratio ((%)) import Data.List (sort) @@ -83,7 +84,7 @@ (snd <$> M.lookup t textTypesMap) in if textPackage textCmd e then textCmd - else fromMaybe "\\mathrm" (lookup textCmd alts) + else fromMaybe "\\mathrm" (M.lookup textCmd alts) -- | Maps MathML mathvariant to the corresponing TextType getTextType :: String -> TextType @@ -127,10 +128,10 @@ -- Operator Table getOperator :: Exp -> Maybe TeX -getOperator op = fmap ControlSeq $ lookup op operators +getOperator op = fmap ControlSeq $ M.lookup op operators -operators :: [(Exp, String)] -operators = +operators :: M.Map Exp String +operators = M.fromList [ (EMathOperator "arccos", "\\arccos") , (EMathOperator "arcsin", "\\arcsin") , (EMathOperator "arctan", "\\arctan") @@ -212,18 +213,28 @@ , ( TextBoldFraktur , ("bold-fraktur","\\mathbffrak")) , ( TextSansSerifItalic , ("sans-serif-italic","\\mathsfit")) ] -unicodeMath, base :: [String] -unicodeMath = ["\\mathbfit", "\\mathbfsfup", "\\mathbfsfit", "\\mathbfscr", "\\mathbffrak", "\\mathsfit"] -base = ["\\mathbb", "\\mathrm", "\\mathbf", "\\mathit", "\\mathsf", "\\mathtt", "\\mathfrak", "\\mathcal"] - -alts :: [(String, String)] -alts = [ ("\\mathbfit", "\\mathbf"), ("\\mathbfsfup", "\\mathbf"), ("\\mathbfsfit", "\\mathbf") - , ("\\mathbfscr", "\\mathcal"), ("\\mathbffrak", "\\mathfrak"), ("\\mathsfit", "\\mathsf")] +unicodeMath, base :: Set.Set String +unicodeMath = Set.fromList + ["\\mathbfit", "\\mathbfsfup", "\\mathbfsfit", "\\mathbfscr", + "\\mathbffrak", "\\mathsfit"] +base = Set.fromList + ["\\mathbb", "\\mathrm", "\\mathbf", "\\mathit", "\\mathsf", + "\\mathtt", "\\mathfrak", "\\mathcal"] + +alts :: M.Map String String +alts = M.fromList + [ ("\\mathbfit", "\\mathbf") + , ("\\mathbfsfup", "\\mathbf") + , ("\\mathbfsfit", "\\mathbf") + , ("\\mathbfscr", "\\mathcal") + , ("\\mathbffrak", "\\mathfrak") + , ("\\mathsfit", "\\mathsf") + ] textPackage :: String -> [String] -> Bool textPackage s e - | s `elem` unicodeMath = "unicode-math" `elem` e - | s `elem` base = True + | s `Set.member` unicodeMath = "unicode-math" `elem` e + | s `Set.member` base = True | otherwise = True -- | Mapping between LaTeX scaling commands and the scaling factor @@ -325,10 +336,9 @@ -- Converts unit to multiplier to reach em unitToMultiplier :: String -> Maybe Rational -unitToMultiplier s = lookup s units +unitToMultiplier s = M.lookup s units where - units = - [ ( "pt" , 10) + units = M.fromList [ ( "pt" , 10) , ( "mm" , (351/10)) , ( "cm" , (35/100)) , ( "in" , (14/100)) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/src/Text/TeXMath/Types.hs new/texmath-0.9.1/src/Text/TeXMath/Types.hs --- old/texmath-0.8.6.7/src/Text/TeXMath/Types.hs 2015-03-15 18:53:51.000000000 +0100 +++ new/texmath-0.9.1/src/Text/TeXMath/Types.hs 2017-02-03 21:14:51.000000000 +0100 @@ -32,16 +32,16 @@ data TeXSymbolType = Ord | Op | Bin | Rel | Open | Close | Pun | Accent | Fence | TOver | TUnder | Alpha | BotAccent | Rad - deriving (Show, Read, Eq, Data, Typeable) + deriving (Show, Read, Eq, Ord, Data, Typeable) data Alignment = AlignLeft | AlignCenter | AlignRight | AlignDefault - deriving (Show, Read, Eq, Data, Typeable) + deriving (Show, Read, Eq, Ord, Data, Typeable) data FractionType = NormalFrac -- ^ Displayed or textual, acc to 'DisplayType' | DisplayFrac -- ^ Force display mode | InlineFrac -- ^ Force inline mode (textual) | NoLineFrac -- ^ No line between top and bottom - deriving (Show, Read, Eq, Data, Typeable) + deriving (Show, Read, Eq, Ord, Data, Typeable) type ArrayLine = [[Exp]] @@ -90,7 +90,7 @@ -- the same length. | EText TextType String -- ^ Some normal text, possibly styled. | EStyled TextType [Exp] -- ^ A group of styled expressions. - deriving (Show, Read, Eq, Data, Typeable) + deriving (Show, Read, Eq, Ord, Data, Typeable) -- | An @EDelimited@ element contains a string of ordinary expressions -- (represented here as @Right@ values) or fences (represented here as @@ -100,7 +100,7 @@ data DisplayType = DisplayBlock -- ^ A displayed formula. | DisplayInline -- ^ A formula rendered inline in text. - deriving (Show, Eq) + deriving (Show, Eq, Ord) data TextType = TextNormal | TextBold @@ -116,7 +116,7 @@ | TextBoldScript | TextBoldFraktur | TextSansSerifItalic - deriving (Show, Ord, Read, Eq, Data, Typeable) + deriving (Show, Read, Eq, Ord, Data, Typeable) data FormType = FPrefix | FPostfix | FInfix deriving (Show, Ord, Eq) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/src/Text/TeXMath/Unicode/Fonts.hs new/texmath-0.9.1/src/Text/TeXMath/Unicode/Fonts.hs --- old/texmath-0.8.6.7/src/Text/TeXMath/Unicode/Fonts.hs 1970-01-01 01:00:00.000000000 +0100 +++ new/texmath-0.9.1/src/Text/TeXMath/Unicode/Fonts.hs 2017-02-03 21:19:21.000000000 +0100 @@ -0,0 +1,243 @@ +{- +Copyright (C) 2014 Matthew Pickering <[email protected]> + +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 +-} + +{- | + Module : Text.TeXMath.Unicode.Fonts + Copyright : Copyright (C) 2014 Matthew Pickering + License : GNU GPL, version 2 or above + + Maintainer : Matthew Pickering <[email protected]> + Stability : alpha + Portability : portable + +Utilities to convert between MS font codepoints and unicode characters. +-} +module Text.TeXMath.Unicode.Fonts (getUnicode, Font(..), stringToFont) where +import qualified Data.Map as M + +-- | Enumeration of recognised fonts +data Font = Symbol -- ^ <http://en.wikipedia.org/wiki/Symbol_(typeface) Adobe Symbol> + deriving (Show, Eq) + +-- | Parse font name into Font if possible. +stringToFont :: String -> Maybe Font +stringToFont "Symbol" = Just Symbol +stringToFont _ = Nothing + +-- | Given a font and codepoint, returns the corresponding unicode +-- character +getUnicode :: Font -> Char -> Maybe Char +getUnicode Symbol c = M.lookup c symbol + +-- Generated from lib/fonts/symbol.txt +symbol :: M.Map Char Char +symbol = M.fromList + [ (' ',' ') + , (' ','\160') + , ('!','!') + , ('"','\8704') + , ('#','#') + , ('$','\8707') + , ('%','%') + , ('&','&') + , ('\'','\8715') + , ('(','(') + , (')',')') + , ('*','\8727') + , ('+','+') + , (',',',') + , ('-','\8722') + , ('.','.') + , ('/','/') + , ('0','0') + , ('1','1') + , ('2','2') + , ('3','3') + , ('4','4') + , ('5','5') + , ('6','6') + , ('7','7') + , ('8','8') + , ('9','9') + , (':',':') + , (';',';') + , ('<','<') + , ('=','=') + , ('>','>') + , ('?','?') + , ('@','\8773') + , ('A','\913') + , ('B','\914') + , ('C','\935') + , ('D','\916') + , ('D','\8710') + , ('E','\917') + , ('F','\934') + , ('G','\915') + , ('H','\919') + , ('I','\921') + , ('J','\977') + , ('K','\922') + , ('L','\923') + , ('M','\924') + , ('N','\925') + , ('O','\927') + , ('P','\928') + , ('Q','\920') + , ('R','\929') + , ('S','\931') + , ('T','\932') + , ('U','\933') + , ('V','\962') + , ('W','\937') + , ('W','\8486') + , ('X','\926') + , ('Y','\936') + , ('Z','\918') + , ('[','[') + , ('\\','\8756') + , (']',']') + , ('^','\8869') + , ('_','_') + , ('`','\63717') + , ('a','\945') + , ('b','\946') + , ('c','\967') + , ('d','\948') + , ('e','\949') + , ('f','\966') + , ('g','\947') + , ('h','\951') + , ('i','\953') + , ('j','\981') + , ('k','\954') + , ('l','\955') + , ('m','\181') + , ('m','\956') + , ('n','\957') + , ('o','\959') + , ('p','\960') + , ('q','\952') + , ('r','\961') + , ('s','\963') + , ('t','\964') + , ('u','\965') + , ('v','\982') + , ('w','\969') + , ('x','\958') + , ('y','\968') + , ('z','\950') + , ('{','{') + , ('|','|') + , ('}','}') + , ('~','\8764') + , ('\160','\8364') + , ('\161','\978') + , ('\162','\8242') + , ('\163','\8804') + , ('\164','\8260') + , ('\164','\8725') + , ('\165','\8734') + , ('\166','\402') + , ('\167','\9827') + , ('\168','\9830') + , ('\169','\9829') + , ('\170','\9824') + , ('\171','\8596') + , ('\172','\8592') + , ('\173','\8593') + , ('\174','\8594') + , ('\175','\8595') + , ('\176','\176') + , ('\177','\177') + , ('\178','\8243') + , ('\179','\8805') + , ('\180','\215') + , ('\181','\8733') + , ('\182','\8706') + , ('\183','\8226') + , ('\184','\247') + , ('\185','\8800') + , ('\186','\8801') + , ('\187','\8776') + , ('\188','\8230') + , ('\189','\63718') + , ('\190','\63719') + , ('\191','\8629') + , ('\192','\8501') + , ('\193','\8465') + , ('\194','\8476') + , ('\195','\8472') + , ('\196','\8855') + , ('\197','\8853') + , ('\198','\8709') + , ('\199','\8745') + , ('\200','\8746') + , ('\201','\8835') + , ('\202','\8839') + , ('\203','\8836') + , ('\204','\8834') + , ('\205','\8838') + , ('\206','\8712') + , ('\207','\8713') + , ('\208','\8736') + , ('\209','\8711') + , ('\210','\63194') + , ('\211','\63193') + , ('\212','\63195') + , ('\213','\8719') + , ('\214','\8730') + , ('\215','\8901') + , ('\216','\172') + , ('\217','\8743') + , ('\218','\8744') + , ('\219','\8660') + , ('\220','\8656') + , ('\221','\8657') + , ('\222','\8658') + , ('\223','\8659') + , ('\224','\9674') + , ('\225','\9001') + , ('\226','\63720') + , ('\227','\63721') + , ('\228','\63722') + , ('\229','\8721') + , ('\230','\63723') + , ('\231','\63724') + , ('\232','\63725') + , ('\233','\63726') + , ('\234','\63727') + , ('\235','\63728') + , ('\236','\63729') + , ('\237','\63730') + , ('\238','\63731') + , ('\239','\63732') + , ('\241','\9002') + , ('\242','\8747') + , ('\243','\8992') + , ('\244','\63733') + , ('\245','\8993') + , ('\246','\63734') + , ('\247','\63735') + , ('\248','\63736') + , ('\249','\63737') + , ('\250','\63738') + , ('\251','\63739') + , ('\252','\63740') + , ('\253','\63741') + , ('\254','\63742')] diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/src/Text/TeXMath/Writers/OMML.hs new/texmath-0.9.1/src/Text/TeXMath/Writers/OMML.hs --- old/texmath-0.8.6.7/src/Text/TeXMath/Writers/OMML.hs 2016-07-24 19:51:45.000000000 +0200 +++ new/texmath-0.9.1/src/Text/TeXMath/Writers/OMML.hs 2017-02-03 19:34:29.000000000 +0100 @@ -30,6 +30,7 @@ writeOMML :: DisplayType -> [Exp] -> Element writeOMML dt = container . concatMap (showExp []) . everywhere (mkT $ handleDownup dt) + . everywhere (mkT $ handleDownup' dt) where container = case dt of DisplayBlock -> \x -> mnode "oMathPara" [ mnode "oMathParaPr" @@ -133,13 +134,44 @@ | isNary x -> EGrouped [ESubsup x emptyGroup y, next] : rest ESubsup x y z | isNary x -> EGrouped [ESubsup x y z, next] : rest - _ -> exp' : next : rest + _ -> exp' : xs where (next, rest) = case xs of (t:ts) -> (t,ts) [] -> (emptyGroup, []) emptyGroup = EGrouped [] handleDownup _ [] = [] +-- TODO This duplication is ugly and inefficient. See #92. +handleDownup' :: DisplayType -> [InEDelimited] -> [InEDelimited] +handleDownup' dt ((Right exp') : xs) = + case exp' of + EOver convertible x y + | isNary x -> + Right (EGrouped [EUnderover convertible x emptyGroup y, next]) : + rest + | convertible && dt == DisplayInline -> Right (ESuper x y) : xs + EUnder convertible x y + | isNary x -> + Right (EGrouped [EUnderover convertible x y emptyGroup, next]) : + rest + | convertible && dt == DisplayInline -> Right (ESub x y) : xs + EUnderover convertible x y z + | isNary x -> + Right (EGrouped [EUnderover convertible x y z, next]) : rest + | convertible && dt == DisplayInline -> Right (ESubsup x y z) : xs + ESub x y + | isNary x -> Right (EGrouped [ESubsup x y emptyGroup, next]) : rest + ESuper x y + | isNary x -> Right (EGrouped [ESubsup x emptyGroup y, next]) : rest + ESubsup x y z + | isNary x -> Right (EGrouped [ESubsup x y z, next]) : rest + _ -> Right exp' : xs + where (next, rest) = case xs of + (Right t:ts) -> (t,ts) + _ -> (emptyGroup, xs) + emptyGroup = EGrouped [] +handleDownup' _ xs = xs + showExp :: [Element] -> Exp -> [Element] showExp props e = case e of diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/src/Text/TeXMath/Writers/Pandoc.hs new/texmath-0.9.1/src/Text/TeXMath/Writers/Pandoc.hs --- old/texmath-0.8.6.7/src/Text/TeXMath/Writers/Pandoc.hs 2015-11-21 19:13:12.000000000 +0100 +++ new/texmath-0.9.1/src/Text/TeXMath/Writers/Pandoc.hs 2017-02-03 20:20:19.000000000 +0100 @@ -47,6 +47,8 @@ addSpaces (x : ESymbol t2 s2 : xs) | not (null xs) = x : addSpace t2 (ESymbol t2 s2) ++ addSpaces xs +addSpaces (EMathOperator s : xs) = + EMathOperator s : thinspace : addSpaces xs addSpaces (x : xs) = x : addSpaces xs addSpaces [] = [] @@ -57,9 +59,11 @@ Rel -> [widespace, x, widespace] Pun -> [x, thinspace] _ -> [x] - where thinspace = EText TextNormal "\x2006" - medspace = EText TextNormal "\x2005" - widespace = EText TextNormal "\x2004" + +thinspace, medspace, widespace :: Exp +thinspace = EText TextNormal "\x2006" +medspace = EText TextNormal "\x2005" +widespace = EText TextNormal "\x2004" renderStr :: TextType -> String -> Inline renderStr tt s = diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/readers/mml/badTag1.native new/texmath-0.9.1/tests/readers/mml/badTag1.native --- old/texmath-0.8.6.7/tests/readers/mml/badTag1.native 2016-03-30 06:27:56.000000000 +0200 +++ new/texmath-0.9.1/tests/readers/mml/badTag1.native 1970-01-01 01:00:00.000000000 +0100 @@ -1 +0,0 @@ -[ESuper (ENumber "5") (EGrouped []),ESymbol Bin "+",ESuper (EGrouped []) (ENumber "5"),ESymbol Bin "+",EGrouped [ENumber "5",ENumber "5"],ESymbol Bin "+",EGrouped []] diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/readers/mml/badTagPhantom2.native new/texmath-0.9.1/tests/readers/mml/badTagPhantom2.native --- old/texmath-0.8.6.7/tests/readers/mml/badTagPhantom2.native 2016-03-30 06:27:56.000000000 +0200 +++ new/texmath-0.9.1/tests/readers/mml/badTagPhantom2.native 1970-01-01 01:00:00.000000000 +0100 @@ -1 +0,0 @@ -[ENumber "2",ESymbol Bin "+",EPhantom (EGrouped [])] diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/readers/mml/complex4.native new/texmath-0.9.1/tests/readers/mml/complex4.native --- old/texmath-0.8.6.7/tests/readers/mml/complex4.native 2016-03-30 06:27:57.000000000 +0200 +++ new/texmath-0.9.1/tests/readers/mml/complex4.native 1970-01-01 01:00:00.000000000 +0100 @@ -1 +0,0 @@ -[] diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/readers/mml/nestedMath3.native new/texmath-0.9.1/tests/readers/mml/nestedMath3.native --- old/texmath-0.8.6.7/tests/readers/mml/nestedMath3.native 2016-03-30 06:27:59.000000000 +0200 +++ new/texmath-0.9.1/tests/readers/mml/nestedMath3.native 1970-01-01 01:00:00.000000000 +0100 @@ -1 +0,0 @@ -[] diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/readers/tex/math-in-text.native new/texmath-0.9.1/tests/readers/tex/math-in-text.native --- old/texmath-0.8.6.7/tests/readers/tex/math-in-text.native 1970-01-01 01:00:00.000000000 +0100 +++ new/texmath-0.9.1/tests/readers/tex/math-in-text.native 2016-11-29 23:35:35.000000000 +0100 @@ -0,0 +1 @@ +[ESuper (EIdentifier "X") (ENumber "2"),ESymbol Rel "=",EIdentifier "y",EGrouped [EText TextNormal " under ",ESub (EIdentifier "H") (ENumber "0"),EText TextNormal " except when ",EGrouped [EIdentifier "x",EGrouped [EText TextBold " is less than ",EIdentifier "z",EText TextBold "."]]]] diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/src/math-in-text.tex new/texmath-0.9.1/tests/src/math-in-text.tex --- old/texmath-0.8.6.7/tests/src/math-in-text.tex 1970-01-01 01:00:00.000000000 +0100 +++ new/texmath-0.9.1/tests/src/math-in-text.tex 2016-11-29 23:35:35.000000000 +0100 @@ -0,0 +1 @@ +X^2 = y \text{ under $H_0$ except when $x \textbf{ is less than \(z\).}$} diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/test-texmath.hs new/texmath-0.9.1/tests/test-texmath.hs --- old/texmath-0.8.6.7/tests/test-texmath.hs 2014-08-10 06:33:21.000000000 +0200 +++ new/texmath-0.9.1/tests/test-texmath.hs 2016-11-29 23:35:35.000000000 +0100 @@ -52,7 +52,7 @@ texs <- runRoundTrip "tex" writeTeX readTeX ommls <- runRoundTrip "omml" (ppTopElement . writeOMML DisplayBlock) readOMML - mathmls <- runRoundTrip "mmml" + mathmls <- runRoundTrip "mml" (ppTopElement . writeMathML DisplayBlock) readMathML return $ texs ++ ommls ++ mathmls @@ -150,17 +150,32 @@ runReaderTest regen fn input output = do inp_t <- readFile' input let result = ensureFinalNewline <$> fn inp_t - when regen $ - writeFile output (either (const "") id result) - out_t <- ensureFinalNewline <$> readFile' output - case result of - Left msg -> printError input output msg >> - return (Error input output) - Right r - | r == out_t -> printPass input output >> - return (Pass input output) - | otherwise -> printFail input (Right output) r >> - return (Fail input output) + let errfile = dropExtension output ++ ".error" + errorExpected <- doesFileExist errfile + if errorExpected + then + case result of + Left _ -> do + printPass input errfile + return (Pass input errfile) + Right _ -> do + printError input errfile "error expected but not raised" + return (Error input errfile) + else do + when regen $ + writeFile output (either (const "") id result) + out_t <- ensureFinalNewline <$> readFile' output + case result of + Left msg -> do + printError input output msg + return (Error input output) + Right r + | r == out_t -> do + printPass input output + return (Pass input output) + | otherwise -> do + printFail input (Right output) r + return (Fail input output) runRoundTripTest :: String -> ([Exp] -> String) diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/writers/complex1.omml new/texmath-0.9.1/tests/writers/complex1.omml --- old/texmath-0.8.6.7/tests/writers/complex1.omml 2016-05-08 04:55:10.000000000 +0200 +++ new/texmath-0.9.1/tests/writers/complex1.omml 2017-01-16 20:33:08.000000000 +0100 @@ -137,22 +137,14 @@ <m:grow /> </m:dPr> <m:e> - <m:limLow> - <m:e> - <m:limUpp> - <m:e> - <m:r> - <m:t>∑</m:t> - </m:r> - </m:e> - <m:lim> - <m:r> - <m:t>n</m:t> - </m:r> - </m:lim> - </m:limUpp> - </m:e> - <m:lim> + <m:nary> + <m:naryPr> + <m:chr m:val="∑" /> + <m:limLoc m:val="undOvr" /> + <m:subHide m:val="0" /> + <m:supHide m:val="0" /> + </m:naryPr> + <m:sub> <m:r> <m:t>k</m:t> </m:r> @@ -162,21 +154,28 @@ <m:r> <m:t>1</m:t> </m:r> - </m:lim> - </m:limLow> - <m:sSubSup> - <m:e> + </m:sub> + <m:sup> <m:r> - <m:t>a</m:t> + <m:t>n</m:t> </m:r> + </m:sup> + <m:e> + <m:sSubSup> + <m:e> + <m:r> + <m:t>a</m:t> + </m:r> + </m:e> + <m:sub> + <m:r> + <m:t>k</m:t> + </m:r> + </m:sub> + <m:sup /> + </m:sSubSup> </m:e> - <m:sub> - <m:r> - <m:t>k</m:t> - </m:r> - </m:sub> - <m:sup /> - </m:sSubSup> + </m:nary> <m:sSubSup> <m:e> <m:r> @@ -210,22 +209,14 @@ <m:grow /> </m:dPr> <m:e> - <m:limLow> - <m:e> - <m:limUpp> - <m:e> - <m:r> - <m:t>∑</m:t> - </m:r> - </m:e> - <m:lim> - <m:r> - <m:t>n</m:t> - </m:r> - </m:lim> - </m:limUpp> - </m:e> - <m:lim> + <m:nary> + <m:naryPr> + <m:chr m:val="∑" /> + <m:limLoc m:val="undOvr" /> + <m:subHide m:val="0" /> + <m:supHide m:val="0" /> + </m:naryPr> + <m:sub> <m:r> <m:t>k</m:t> </m:r> @@ -235,25 +226,32 @@ <m:r> <m:t>1</m:t> </m:r> - </m:lim> - </m:limLow> - <m:sSubSup> - <m:e> - <m:r> - <m:t>a</m:t> - </m:r> - </m:e> - <m:sub> - <m:r> - <m:t>k</m:t> - </m:r> </m:sub> <m:sup> <m:r> - <m:t>2</m:t> + <m:t>n</m:t> </m:r> </m:sup> - </m:sSubSup> + <m:e> + <m:sSubSup> + <m:e> + <m:r> + <m:t>a</m:t> + </m:r> + </m:e> + <m:sub> + <m:r> + <m:t>k</m:t> + </m:r> + </m:sub> + <m:sup> + <m:r> + <m:t>2</m:t> + </m:r> + </m:sup> + </m:sSubSup> + </m:e> + </m:nary> </m:e> </m:d> <m:d> @@ -263,22 +261,14 @@ <m:grow /> </m:dPr> <m:e> - <m:limLow> - <m:e> - <m:limUpp> - <m:e> - <m:r> - <m:t>∑</m:t> - </m:r> - </m:e> - <m:lim> - <m:r> - <m:t>n</m:t> - </m:r> - </m:lim> - </m:limUpp> - </m:e> - <m:lim> + <m:nary> + <m:naryPr> + <m:chr m:val="∑" /> + <m:limLoc m:val="undOvr" /> + <m:subHide m:val="0" /> + <m:supHide m:val="0" /> + </m:naryPr> + <m:sub> <m:r> <m:t>k</m:t> </m:r> @@ -288,25 +278,32 @@ <m:r> <m:t>1</m:t> </m:r> - </m:lim> - </m:limLow> - <m:sSubSup> - <m:e> - <m:r> - <m:t>b</m:t> - </m:r> - </m:e> - <m:sub> - <m:r> - <m:t>k</m:t> - </m:r> </m:sub> <m:sup> <m:r> - <m:t>2</m:t> + <m:t>n</m:t> </m:r> </m:sup> - </m:sSubSup> + <m:e> + <m:sSubSup> + <m:e> + <m:r> + <m:t>b</m:t> + </m:r> + </m:e> + <m:sub> + <m:r> + <m:t>k</m:t> + </m:r> + </m:sub> + <m:sup> + <m:r> + <m:t>2</m:t> + </m:r> + </m:sup> + </m:sSubSup> + </m:e> + </m:nary> </m:e> </m:d> </m:e> diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/writers/complex3.omml new/texmath-0.9.1/tests/writers/complex3.omml --- old/texmath-0.8.6.7/tests/writers/complex3.omml 2016-05-08 04:55:10.000000000 +0200 +++ new/texmath-0.9.1/tests/writers/complex3.omml 2017-01-16 20:33:08.000000000 +0100 @@ -22747,27 +22747,25 @@ <m:r> <m:t>↑</m:t> </m:r> - <m:limLow> - <m:e> - <m:limUpp> - <m:e> - <m:r> - <m:t>∑</m:t> - </m:r> - </m:e> - <m:lim> - <m:r> - <m:t>2</m:t> - </m:r> - </m:lim> - </m:limUpp> - </m:e> - <m:lim> + <m:nary> + <m:naryPr> + <m:chr m:val="∑" /> + <m:limLoc m:val="undOvr" /> + <m:subHide m:val="0" /> + <m:supHide m:val="0" /> + </m:naryPr> + <m:sub> <m:r> <m:t>1</m:t> </m:r> - </m:lim> - </m:limLow> + </m:sub> + <m:sup> + <m:r> + <m:t>2</m:t> + </m:r> + </m:sup> + <m:e /> + </m:nary> </m:e> </m:d> </m:e> @@ -22824,27 +22822,25 @@ <m:r> <m:t>|</m:t> </m:r> - <m:limLow> - <m:e> - <m:limUpp> - <m:e> - <m:r> - <m:t>∑</m:t> - </m:r> - </m:e> - <m:lim> - <m:r> - <m:t>2</m:t> - </m:r> - </m:lim> - </m:limUpp> - </m:e> - <m:lim> + <m:nary> + <m:naryPr> + <m:chr m:val="∑" /> + <m:limLoc m:val="undOvr" /> + <m:subHide m:val="0" /> + <m:supHide m:val="0" /> + </m:naryPr> + <m:sub> <m:r> <m:t>1</m:t> </m:r> - </m:lim> - </m:limLow> + </m:sub> + <m:sup> + <m:r> + <m:t>2</m:t> + </m:r> + </m:sup> + <m:e /> + </m:nary> </m:e> </m:d> </m:e> @@ -22901,27 +22897,25 @@ <m:r> <m:t>|</m:t> </m:r> - <m:limLow> - <m:e> - <m:limUpp> - <m:e> - <m:r> - <m:t>∑</m:t> - </m:r> - </m:e> - <m:lim> - <m:r> - <m:t>2</m:t> - </m:r> - </m:lim> - </m:limUpp> - </m:e> - <m:lim> + <m:nary> + <m:naryPr> + <m:chr m:val="∑" /> + <m:limLoc m:val="undOvr" /> + <m:subHide m:val="0" /> + <m:supHide m:val="0" /> + </m:naryPr> + <m:sub> <m:r> <m:t>1</m:t> </m:r> - </m:lim> - </m:limLow> + </m:sub> + <m:sup> + <m:r> + <m:t>2</m:t> + </m:r> + </m:sup> + <m:e /> + </m:nary> </m:e> </m:d> </m:e> @@ -22988,27 +22982,25 @@ <m:r> <m:t>↕</m:t> </m:r> - <m:limLow> - <m:e> - <m:limUpp> - <m:e> - <m:r> - <m:t>∑</m:t> - </m:r> - </m:e> - <m:lim> - <m:r> - <m:t>2</m:t> - </m:r> - </m:lim> - </m:limUpp> - </m:e> - <m:lim> + <m:nary> + <m:naryPr> + <m:chr m:val="∑" /> + <m:limLoc m:val="undOvr" /> + <m:subHide m:val="0" /> + <m:supHide m:val="0" /> + </m:naryPr> + <m:sub> <m:r> <m:t>1</m:t> </m:r> - </m:lim> - </m:limLow> + </m:sub> + <m:sup> + <m:r> + <m:t>2</m:t> + </m:r> + </m:sup> + <m:e /> + </m:nary> </m:e> </m:d> <m:r> diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/writers/math-in-text.mml new/texmath-0.9.1/tests/writers/math-in-text.mml --- old/texmath-0.8.6.7/tests/writers/math-in-text.mml 1970-01-01 01:00:00.000000000 +0100 +++ new/texmath-0.9.1/tests/writers/math-in-text.mml 2016-11-29 23:35:35.000000000 +0100 @@ -0,0 +1,39 @@ +<?xml version='1.0' ?> +<math display="block" xmlns="http://www.w3.org/1998/Math/MathML"> + <mrow> + <msup> + <mi>X</mi> + <mn>2</mn> + </msup> + <mo>=</mo> + <mi>y</mi> + <mrow> + <mrow> + <mspace width="0.333em" /> + <mtext mathvariant="normal"> under </mtext> + <mspace width="0.333em" /> + </mrow> + <msub> + <mi>H</mi> + <mn>0</mn> + </msub> + <mrow> + <mspace width="0.333em" /> + <mtext mathvariant="normal"> except when </mtext> + <mspace width="0.333em" /> + </mrow> + <mrow> + <mi>x</mi> + <mrow> + <mrow> + <mspace width="0.333em" /> + <mtext mathvariant="bold"> 𝐢𝐬 𝐥𝐞𝐬𝐬 𝐭𝐡𝐚𝐧 </mtext> + <mspace width="0.333em" /> + </mrow> + <mi>z</mi> + <mtext mathvariant="bold">.</mtext> + </mrow> + </mrow> + </mrow> + </mrow> +</math> diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/writers/math-in-text.omml new/texmath-0.9.1/tests/writers/math-in-text.omml --- old/texmath-0.8.6.7/tests/writers/math-in-text.omml 1970-01-01 01:00:00.000000000 +0100 +++ new/texmath-0.9.1/tests/writers/math-in-text.omml 2016-11-29 23:35:35.000000000 +0100 @@ -0,0 +1,68 @@ +<?xml version='1.0' ?> +<m:oMathPara> + <m:oMathParaPr> + <m:jc m:val="center" /> + </m:oMathParaPr> + <m:oMath> + <m:sSup> + <m:e> + <m:r> + <m:t>X</m:t> + </m:r> + </m:e> + <m:sup> + <m:r> + <m:t>2</m:t> + </m:r> + </m:sup> + </m:sSup> + <m:r> + <m:t>=</m:t> + </m:r> + <m:r> + <m:t>y</m:t> + </m:r> + <m:r> + <m:rPr> + <m:sty m:val="p" /> + </m:rPr> + <m:t> under </m:t> + </m:r> + <m:sSub> + <m:e> + <m:r> + <m:t>H</m:t> + </m:r> + </m:e> + <m:sub> + <m:r> + <m:t>0</m:t> + </m:r> + </m:sub> + </m:sSub> + <m:r> + <m:rPr> + <m:sty m:val="p" /> + </m:rPr> + <m:t> except when </m:t> + </m:r> + <m:r> + <m:t>x</m:t> + </m:r> + <m:r> + <m:rPr> + <m:sty m:val="b" /> + </m:rPr> + <m:t> is less than </m:t> + </m:r> + <m:r> + <m:t>z</m:t> + </m:r> + <m:r> + <m:rPr> + <m:sty m:val="b" /> + </m:rPr> + <m:t>.</m:t> + </m:r> + </m:oMath> +</m:oMathPara> diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/tests/writers/math-in-text.tex new/texmath-0.9.1/tests/writers/math-in-text.tex --- old/texmath-0.8.6.7/tests/writers/math-in-text.tex 1970-01-01 01:00:00.000000000 +0100 +++ new/texmath-0.9.1/tests/writers/math-in-text.tex 2016-11-29 23:35:35.000000000 +0100 @@ -0,0 +1 @@ +X^{2} = y{\text{\ under\ }H_{0}\text{\ except\ when\ }{x{\textbf{\ is\ less\ than\ }z\textbf{.}}}} diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' '--exclude=.svnignore' old/texmath-0.8.6.7/texmath.cabal new/texmath-0.9.1/texmath.cabal --- old/texmath-0.8.6.7/texmath.cabal 2016-10-28 20:43:37.000000000 +0200 +++ new/texmath-0.9.1/texmath.cabal 2017-02-03 21:01:13.000000000 +0100 @@ -1,5 +1,5 @@ Name: texmath -Version: 0.8.6.7 +Version: 0.9.1 Cabal-Version: >= 1.10 Build-type: Simple Synopsis: Conversion between formats used to represent mathematics. @@ -52,6 +52,7 @@ tests/src/*.tex tests/src/*.omml tests/readers/mml/*.native + tests/readers/mml/*.error tests/readers/tex/*.native tests/readers/omml/*.native tests/writers/*.mml @@ -101,7 +102,8 @@ Text.TeXMath.Writers.TeX, Text.TeXMath.Unicode.ToUnicode, Text.TeXMath.Unicode.ToTeX, - Text.TeXMath.Unicode.ToASCII + Text.TeXMath.Unicode.ToASCII, + Text.TeXMath.Unicode.Fonts Other-modules: Text.TeXMath.Compat, Text.TeXMath.Shared, Text.TeXMath.TeX,
