OMath parser: Change signature of exported function.

This changes the signature of the exported `readOMML` to `String ->
Either String [Exp]`, so it can now, in theory, be slotted into
TeXMath. It doesn't have any real error reporting yet, but that might
make more sense once I put it in a branch, and understand how it works
in the other readers.

It also now reads strings that parse to either oMath or oMathPara
elements. Note that the distinction is lost in the output. It's up to
the caller to remember the display type.
This commit is contained in:
Jesse Rosenthal 2014-08-08 16:17:40 -04:00
parent e5fb97ff4f
commit a426812ccc
3 changed files with 24 additions and 12 deletions

View file

@ -321,7 +321,7 @@ runToInlines (InlineDrawing fp bs) = do
modify $ \s -> s { docxMediaBag = insertMedia fp Nothing bs mediaBag }
return [Image [] (fp, "")]
parPartToInlines :: ParPart -> DocxContext [Inline]
@ -507,10 +507,9 @@ bodyPartToBlocks (Tbl cap _ look (r:rs)) = do
widths = replicate size 0 :: [Double]
return [Table caption alignments widths hdrCells cells]
bodyPartToBlocks (OMathPara exps) = do
return [Para $
map (\e -> Math DisplayMath (writeTeX e))
exps]
bodyPartToBlocks (OMathPara e) = do
return [Para [Math DisplayMath (writeTeX e)]]
-- replace targets with generated anchors.
rewriteLink :: Inline -> DocxContext Inline

View file

@ -38,11 +38,20 @@ import Data.Maybe (mapMaybe, fromMaybe)
import Data.List (intersperse)
import qualified Text.TeXMath.Types as TM
readOMML :: Element -> Maybe [TM.Exp]
readOMML element | isElem "m" "oMath" element =
Just $ concat $ mapMaybe (elemToExps') (elChildren element)
readOMML _ = Nothing
readOMML :: String -> Either String [TM.Exp]
readOMML s | Just e <- parseXMLDoc s =
case elemToOMML e of
Just exs -> Right exs
Nothing -> Left "xml file was not an <m:oMathPara> or <m:oMath> element."
readOMML _ = Left "Couldn't parse OMML file"
elemToOMML :: Element -> Maybe [TM.Exp]
elemToOMML element | isElem "m" "oMathPara" element = do
let expList = mapMaybe elemToOMML (elChildren element)
return $ map (\l -> if length l == 1 then (head l) else TM.EGrouped l) expList
elemToOMML element | isElem "m" "oMath" element =
Just $ concat $ mapMaybe (elemToExps') (elChildren element)
elemToOMML _ = Nothing
isElem :: String -> String -> Element -> Bool
isElem prefix name element =

View file

@ -86,6 +86,10 @@ maybeToD :: Maybe a -> D a
maybeToD (Just a) = return a
maybeToD Nothing = throwError DocxError
eitherToD :: Either a b -> D b
eitherToD (Right b) = return b
eitherToD (Left _) = throwError DocxError
concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b]
concatMapM f xs = liftM concat (mapM f xs)
@ -150,7 +154,7 @@ defaultParagraphStyle = ParagraphStyle { pStyle = []
data BodyPart = Paragraph ParagraphStyle [ParPart]
| ListItem ParagraphStyle String String Level [ParPart]
| Tbl String TblGrid TblLook [Row]
| OMathPara [[Exp]]
| OMathPara [Exp]
deriving Show
type TblGrid = [Integer]
@ -475,7 +479,7 @@ elemToBodyPart ns element
| isElem ns "w" "p" element
, (c:_) <- findChildren (elemName ns "m" "oMathPara") element =
do
expsLst <- mapD (\e -> (maybeToD $ readOMML e)) (elChildren c)
expsLst <- eitherToD $ readOMML $ showElement c
return $ OMathPara expsLst
elemToBodyPart ns element
| isElem ns "w" "p" element
@ -575,7 +579,7 @@ elemToParPart ns element
Nothing -> ExternalHyperLink "" runs
elemToParPart ns element
| isElem ns "m" "oMath" element =
(maybeToD $ readOMML element) >>= (return . PlainOMath)
(eitherToD $ readOMML $ showElement element) >>= (return . PlainOMath)
elemToParPart _ _ = throwError WrongElem
lookupFootnote :: String -> Notes -> Maybe Element