diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Readers/Docx.hs | 9 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Docx/OMath.hs | 17 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Docx/Parse.hs | 10 |
3 files changed, 24 insertions, 12 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index 6dc3f11c2..085ee01fc 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -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 diff --git a/src/Text/Pandoc/Readers/Docx/OMath.hs b/src/Text/Pandoc/Readers/Docx/OMath.hs index 62fc6286c..47f8dd197 100644 --- a/src/Text/Pandoc/Readers/Docx/OMath.hs +++ b/src/Text/Pandoc/Readers/Docx/OMath.hs @@ -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 = +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) -readOMML _ = Nothing - +elemToOMML _ = Nothing isElem :: String -> String -> Element -> Bool isElem prefix name element = diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index 8c9b4d672..beb58fed2 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -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 |