diff options
author | Nikolay Yakimov <root@livid.pp.ru> | 2019-09-08 16:47:44 +0300 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2019-09-21 11:18:15 -0700 |
commit | fd14ad52618c98928ab83aa43689158cc788c4a8 (patch) | |
tree | 23a7b07782bc5ddad6f6090cd091fae6d4e8b2d4 /src/Text/Pandoc/Readers/Docx | |
parent | 6ceed9593a933bb53db7feaca7cae0e2979b4918 (diff) | |
download | pandoc-fd14ad52618c98928ab83aa43689158cc788c4a8.tar.gz |
[Docx Reader] Code clean-up
Reduce code duplication, remove redundant brackets, use newtype instead of data where appropriate
Diffstat (limited to 'src/Text/Pandoc/Readers/Docx')
-rw-r--r-- | src/Text/Pandoc/Readers/Docx/Parse.hs | 32 |
1 files changed, 14 insertions, 18 deletions
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index f725660b9..330c9208f 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -121,9 +121,9 @@ unwrap :: NameSpaces -> Content -> [Content] unwrap ns (Elem element) | isElem ns "w" "sdt" element , Just sdtContent <- findChildByName ns "w" "sdtContent" element - = concatMap ((unwrap ns) . Elem) (elChildren sdtContent) + = concatMap (unwrap ns . Elem) (elChildren sdtContent) | isElem ns "w" "smartTag" element - = concatMap ((unwrap ns) . Elem) (elChildren element) + = concatMap (unwrap ns . Elem) (elChildren element) unwrap _ content = [content] unwrapChild :: NameSpaces -> Content -> Content @@ -149,13 +149,13 @@ walkDocument ns element = _ -> Nothing -data Docx = Docx Document +newtype Docx = Docx Document deriving Show data Document = Document NameSpaces Body deriving Show -data Body = Body [BodyPart] +newtype Body = Body [BodyPart] deriving Show type Media = [(FilePath, B.ByteString)] @@ -242,16 +242,16 @@ data BodyPart = Paragraph ParagraphStyle [ParPart] type TblGrid = [Integer] -data TblLook = TblLook {firstRowFormatting::Bool} +newtype TblLook = TblLook {firstRowFormatting::Bool} deriving Show defaultTblLook :: TblLook defaultTblLook = TblLook{firstRowFormatting = False} -data Row = Row [Cell] +newtype Row = Row [Cell] deriving Show -data Cell = Cell [BodyPart] +newtype Cell = Cell [BodyPart] deriving Show -- (width, height) in EMUs @@ -495,7 +495,7 @@ filePathToRelType "word/_rels/endnotes.xml.rels" _ = Just InEndnote -- -- to see if it's a documentPath, we have to check against the dynamic -- -- docPath specified in "_rels/.rels" filePathToRelType path docXmlPath = - if path == "word/_rels/" ++ (takeFileName docXmlPath) ++ ".rels" + if path == "word/_rels/" ++ takeFileName docXmlPath ++ ".rels" then Just InDocument else Nothing @@ -537,7 +537,7 @@ lookupLevel numId ilvl (Numbering _ numbs absNumbs) = do case lvlOverride of Just (LevelOverride _ _ (Just lvl')) -> Just lvl' Just (LevelOverride _ (Just strt) _) -> - lookup ilvl $ map (\(Level i fmt s _) -> (i, (Level i fmt s (Just strt)))) lvls + lookup ilvl $ map (\(Level i fmt s _) -> (i, Level i fmt s (Just strt))) lvls _ -> lookup ilvl $ map (\l@(Level i _ _ _) -> (i, l)) lvls @@ -703,23 +703,19 @@ elemToBodyPart ns element elemToBodyPart ns element | isElem ns "w" "p" element , Just (numId, lvl) <- getNumInfo ns element = do - sty <- asks envParStyles - let parstyle = elemToParagraphStyle ns element sty + parstyle <- elemToParagraphStyle ns element <$> asks envParStyles parparts <- mapD (elemToParPart ns) (elChildren element) - num <- asks envNumbering - let levelInfo = lookupLevel numId lvl num + levelInfo <- lookupLevel numId lvl <$> asks envNumbering return $ ListItem parstyle numId lvl levelInfo parparts elemToBodyPart ns element | isElem ns "w" "p" element = do - sty <- asks envParStyles - let parstyle = elemToParagraphStyle ns element sty + parstyle <- elemToParagraphStyle ns element <$> asks envParStyles parparts <- mapD (elemToParPart ns) (elChildren element) -- Word uses list enumeration for numbered headings, so we only -- want to infer a list from the styles if it is NOT a heading. case pHeading parstyle of Nothing | Just (numId, lvl) <- pNumInfo parstyle -> do - num <- asks envNumbering - let levelInfo = lookupLevel numId lvl num + levelInfo <- lookupLevel numId lvl <$> asks envNumbering return $ ListItem parstyle numId lvl levelInfo parparts _ -> return $ Paragraph parstyle parparts elemToBodyPart ns element @@ -727,7 +723,7 @@ elemToBodyPart ns element let caption' = findChildByName ns "w" "tblPr" element >>= findChildByName ns "w" "tblCaption" >>= findAttrByName ns "w" "val" - caption = (fromMaybe "" caption') + caption = fromMaybe "" caption' grid' = case findChildByName ns "w" "tblGrid" element of Just g -> elemToTblGrid ns g Nothing -> return [] |