aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorJesse Rosenthal <jrosenthal@jhu.edu>2014-08-16 15:07:41 -0400
committerJesse Rosenthal <jrosenthal@jhu.edu>2014-08-16 15:07:41 -0400
commit9bb0b99981bb23eb0afe1befa78f34614fff3ecf (patch)
treef01367a5bb30ded6f8e09eb0504aedae5f6d43a7 /src/Text/Pandoc
parent180f5cbe631f63bb9ea9791bb02a8c9fa0ce0c37 (diff)
downloadpandoc-9bb0b99981bb23eb0afe1befa78f34614fff3ecf.tar.gz
Docx reader: Remove unnecessary plural functions
functions like runElemsToInlines and parPartsToInlines are just defined in terms of concatting and mapping their singular version (e.g. `runElemToInlines`). Having two functions with almost identical names makes it easier to introduce errors. It's easy enough to just concat and map inline, and it makes it clearer what is going on in the code.
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs16
1 files changed, 5 insertions, 11 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 1419eea08..a1c16a03a 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -165,7 +165,7 @@ bodyPartsToMeta' (bp : bps)
| (Paragraph pPr parParts) <- bp
, (c : _)<- intersect (pStyle pPr) (M.keys metaStyles)
, (Just metaField) <- M.lookup c metaStyles = do
- inlines <- parPartsToInlines parParts
+ inlines <- concatReduce <$> mapM parPartToInlines parParts
remaining <- bodyPartsToMeta' bps
let
f (MetaInlines ils) (MetaInlines ils') = MetaBlocks [Para ils, Para ils']
@@ -218,11 +218,8 @@ runElemToString (TextRun s) = s
runElemToString (LnBrk) = ['\n']
runElemToString (Tab) = ['\t']
-runElemsToString :: [RunElem] -> String
-runElemsToString = concatMap runElemToString
-
runToString :: Run -> String
-runToString (Run _ runElems) = runElemsToString runElems
+runToString (Run _ runElems) = concatMap runElemToString runElems
runToString _ = ""
parPartToString :: ParPart -> String
@@ -272,7 +269,7 @@ runToInlines :: Run -> DocxContext Inlines
runToInlines (Run rs runElems)
| Just s <- rStyle rs
, s `elem` codeStyles =
- return $ code $ runElemsToString runElems
+ return $ code $ concatMap runElemToString runElems
| otherwise = do
let ils = concatReduce (map runElemToInlines runElems)
return $ (runStyleToTransform rs) ils
@@ -383,9 +380,6 @@ makeHeaderAnchor' (Header n (_, classes, kvs) ils) =
return $ Header n (newIdent, classes, kvs) ils
makeHeaderAnchor' blk = return blk
-parPartsToInlines :: [ParPart] -> DocxContext Inlines
-parPartsToInlines parparts = concatReduce <$> mapM parPartToInlines parparts
-
cellToBlocks :: Cell -> DocxContext Blocks
cellToBlocks (Cell bps) = concatReduce <$> mapM bodyPartToBlocks bps
@@ -447,12 +441,12 @@ bodyPartToBlocks (Paragraph pPr parparts)
| (c : cs) <- filter (isJust . isHeaderClass) $ pStyle pPr
, Just n <- isHeaderClass c = do
ils <- local (\s-> s{docxInHeaderBlock=True}) $
- (parPartsToInlines parparts)
+ (concatReduce <$> mapM parPartToInlines parparts)
makeHeaderAnchor $
headerWith ("", delete ("Heading" ++ show n) cs, []) n ils
| otherwise = do
- ils <- parPartsToInlines parparts >>=
+ ils <- concatReduce <$> mapM parPartToInlines parparts >>=
(return . fromList . trimLineBreaks . normalizeSpaces . toList)
dropIls <- gets docxDropCap
let ils' = dropIls <> ils