aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Docx
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2021-03-11 15:49:27 -0800
committerJohn MacFarlane <[email protected]>2021-03-13 15:05:37 -0800
commit8be95ad8e5150d5cab66c4abdf59baaf4670c6c8 (patch)
tree9655036efbaabda6a2a7802dc971c7fba5a987ca /src/Text/Pandoc/Readers/Docx
parent35b66a76718205c303f416bf0afc01c098e8a171 (diff)
Use custom Prelude based on relude.relude
The Prelude now longer exports partial functions, so a large number of uses of these functions in the code base have been rewritten. A .ghci file has been added; this is necessary for ghci to work properly with the custom Prelude. Currently there are lots of compiler warnings. We should either fix these or go to using a custom Prelude that changes less than relude.
Diffstat (limited to 'src/Text/Pandoc/Readers/Docx')
-rw-r--r--src/Text/Pandoc/Readers/Docx/Combine.hs4
-rw-r--r--src/Text/Pandoc/Readers/Docx/Lists.hs17
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs5
3 files changed, 15 insertions, 11 deletions
diff --git a/src/Text/Pandoc/Readers/Docx/Combine.hs b/src/Text/Pandoc/Readers/Docx/Combine.hs
index bcf26c4a3..96e86f136 100644
--- a/src/Text/Pandoc/Readers/Docx/Combine.hs
+++ b/src/Text/Pandoc/Readers/Docx/Combine.hs
@@ -61,7 +61,7 @@ import Data.List
import Data.Bifunctor
import Data.Sequence ( ViewL (..), ViewR (..), viewl, viewr, spanr, spanl
, (><), (|>) )
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as B
data Modifier a = Modifier (a -> a)
| AttrModifier (Attr -> a -> a) Attr
@@ -101,7 +101,7 @@ unstackInlines ms = case ilModifierAndInnards ms of
ilModifierAndInnards :: Inlines -> Maybe (Modifier Inlines, Inlines)
ilModifierAndInnards ils = case viewl $ unMany ils of
- x :< xs | null xs -> second fromList <$> case x of
+ x :< xs | null xs -> second B.fromList <$> case x of
Emph lst -> Just (Modifier emph, lst)
Strong lst -> Just (Modifier strong, lst)
SmallCaps lst -> Just (Modifier smallcaps, lst)
diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs
index e63f8457e..a86a608c7 100644
--- a/src/Text/Pandoc/Readers/Docx/Lists.hs
+++ b/src/Text/Pandoc/Readers/Docx/Lists.hs
@@ -17,7 +17,7 @@ module Text.Pandoc.Readers.Docx.Lists ( blocksToBullets
, listParagraphStyles
) where
-import Data.List
+import Data.List (intersect, delete, (\\))
import Data.Maybe
import Data.String (fromString)
import qualified Data.Text as T
@@ -109,12 +109,15 @@ handleListParagraphs (blk:blks) = blk : handleListParagraphs blks
separateBlocks' :: Block -> [[Block]] -> [[Block]]
separateBlocks' blk [[]] = [[blk]]
-separateBlocks' b@(BulletList _) acc = init acc ++ [last acc ++ [b]]
-separateBlocks' b@(OrderedList _ _) acc = init acc ++ [last acc ++ [b]]
+separateBlocks' b@(BulletList _) acc = fromMaybe acc $ flip viaNonEmpty acc $
+ \accNE -> init accNE ++ [last accNE ++ [b]]
+separateBlocks' b@(OrderedList _ _) acc = fromMaybe acc $ flip viaNonEmpty acc $
+ \accNE -> init accNE ++ [last accNE ++ [b]]
-- The following is for the invisible bullet lists. This is how
-- pandoc-generated ooxml does multiparagraph item lists.
separateBlocks' b acc | fmap trim (getText b) == Just "" =
- init acc ++ [last acc ++ [b]]
+ fromMaybe acc $ flip viaNonEmpty acc $
+ \accNE -> init accNE ++ [last accNE ++ [b]]
separateBlocks' b acc = acc ++ [[b]]
separateBlocks :: [Block] -> [[Block]]
@@ -178,9 +181,9 @@ blocksToDefinitions' ((defTerm, defItems):defs) acc
defItems2 = if remainingAttr2 == ("", [], [])
then blks2
else [Div remainingAttr2 blks2]
- defAcc' = if null defItems
- then (defTerm, [defItems2]) : defs
- else (defTerm, init defItems ++ [last defItems ++ defItems2]) : defs
+ defAcc' = fromMaybe ((defTerm, [defItems2]) : defs) $
+ flip viaNonEmpty defItems $ \items ->
+ (defTerm, init items ++ [last items ++ defItems2]) : defs
in
blocksToDefinitions' defAcc' acc blks
blocksToDefinitions' [] acc (b:blks) =
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index f8ed248d7..818374398 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -60,7 +60,6 @@ import Control.Monad.State.Strict
import Data.Bits ((.|.))
import qualified Data.ByteString.Lazy as B
import Data.Char (chr, ord, readLitChar)
-import Data.List
import qualified Data.Map as M
import qualified Data.Text as T
import Data.Text (Text)
@@ -909,7 +908,9 @@ elemToRun ns element
| isElem ns "w" "r" element
, Just altCont <- findChildByName ns "mc" "AlternateContent" element =
do let choices = findChildrenByName ns "mc" "Choice" altCont
- choiceChildren = map head $ filter (not . null) $ map elChildren choices
+ choiceChildren = mapMaybe (\n -> case elChildren n of
+ [] -> Nothing
+ (x:_) -> Just x) choices
outputs <- mapD (childElemToRun ns) choiceChildren
case outputs of
r : _ -> return r