aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Docx
diff options
context:
space:
mode:
authorYan Pashkovsky <Yanpas@users.noreply.github.com>2018-05-09 19:48:34 +0300
committerGitHub <noreply@github.com>2018-05-09 19:48:34 +0300
commita337685fe0ab9c63b9456f27787bbe4f0d785a94 (patch)
treee9fc4dfc0802f8acd97f06a8cc8d7c89b5a988ab /src/Text/Pandoc/Readers/Docx
parent8e9973b9f761262b6871206f741ac3f2a25aa6bb (diff)
parent5f33d2e0cd9f19566904c93be04f586de811dd75 (diff)
downloadpandoc-a337685fe0ab9c63b9456f27787bbe4f0d785a94.tar.gz
Merge branch 'master' into groff_reader
Diffstat (limited to 'src/Text/Pandoc/Readers/Docx')
-rw-r--r--src/Text/Pandoc/Readers/Docx/Combine.hs6
-rw-r--r--src/Text/Pandoc/Readers/Docx/Fields.hs2
-rw-r--r--src/Text/Pandoc/Readers/Docx/Lists.hs2
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs27
-rw-r--r--src/Text/Pandoc/Readers/Docx/StyleMap.hs2
-rw-r--r--src/Text/Pandoc/Readers/Docx/Util.hs2
6 files changed, 27 insertions, 14 deletions
diff --git a/src/Text/Pandoc/Readers/Docx/Combine.hs b/src/Text/Pandoc/Readers/Docx/Combine.hs
index 003265e6e..108c4bbe5 100644
--- a/src/Text/Pandoc/Readers/Docx/Combine.hs
+++ b/src/Text/Pandoc/Readers/Docx/Combine.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE TypeSynonymInstances #-}
@@ -7,6 +8,7 @@ module Text.Pandoc.Readers.Docx.Combine ( smushInlines
)
where
+import Prelude
import Data.List
import Data.Sequence (ViewL (..), ViewR (..), viewl, viewr, (><), (|>))
import qualified Data.Sequence as Seq (null)
@@ -133,6 +135,10 @@ combineBlocks bs cs
| bs' :> BlockQuote bs'' <- viewr (unMany bs)
, BlockQuote cs'' :< cs' <- viewl (unMany cs) =
Many $ (bs' |> BlockQuote (bs'' <> cs'')) >< cs'
+ | bs' :> CodeBlock attr codeStr <- viewr (unMany bs)
+ , CodeBlock attr' codeStr' :< cs' <- viewl (unMany cs)
+ , attr == attr' =
+ Many $ (bs' |> CodeBlock attr (codeStr <> "\n" <> codeStr')) >< cs'
combineBlocks bs cs = bs <> cs
instance (Monoid a, Eq a) => Eq (Modifier a) where
diff --git a/src/Text/Pandoc/Readers/Docx/Fields.hs b/src/Text/Pandoc/Readers/Docx/Fields.hs
index 6eeb55d2f..c3f54560b 100644
--- a/src/Text/Pandoc/Readers/Docx/Fields.hs
+++ b/src/Text/Pandoc/Readers/Docx/Fields.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE NoImplicitPrelude #-}
{-
Copyright (C) 2014-2018 Jesse Rosenthal <jrosenthal@jhu.edu>
@@ -32,6 +33,7 @@ module Text.Pandoc.Readers.Docx.Fields ( FieldInfo(..)
, parseFieldInfo
) where
+import Prelude
import Text.Parsec
import Text.Parsec.String (Parser)
diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs
index c0f05094a..49ea71601 100644
--- a/src/Text/Pandoc/Readers/Docx/Lists.hs
+++ b/src/Text/Pandoc/Readers/Docx/Lists.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE NoImplicitPrelude #-}
{-
Copyright (C) 2014-2018 Jesse Rosenthal <jrosenthal@jhu.edu>
@@ -33,6 +34,7 @@ module Text.Pandoc.Readers.Docx.Lists ( blocksToBullets
, listParagraphDivs
) where
+import Prelude
import Data.List
import Data.Maybe
import Text.Pandoc.Generic (bottomUp)
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index c123a0018..4c4c06073 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE ViewPatterns #-}
@@ -58,6 +59,7 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..)
, archiveToDocx
, archiveToDocxWithWarnings
) where
+import Prelude
import Codec.Archive.Zip
import Control.Applicative ((<|>))
import Control.Monad.Except
@@ -132,21 +134,23 @@ mapD f xs =
in
concatMapM handler xs
-unwrapSDT :: NameSpaces -> Content -> [Content]
-unwrapSDT ns (Elem element)
+unwrap :: NameSpaces -> Content -> [Content]
+unwrap ns (Elem element)
| isElem ns "w" "sdt" element
, Just sdtContent <- findChildByName ns "w" "sdtContent" element
- = map Elem $ elChildren sdtContent
-unwrapSDT _ content = [content]
+ = concatMap ((unwrap ns) . Elem) (elChildren sdtContent)
+ | isElem ns "w" "smartTag" element
+ = concatMap ((unwrap ns) . Elem) (elChildren element)
+unwrap _ content = [content]
-unwrapSDTchild :: NameSpaces -> Content -> Content
-unwrapSDTchild ns (Elem element) =
- Elem $ element { elContent = concatMap (unwrapSDT ns) (elContent element) }
-unwrapSDTchild _ content = content
+unwrapChild :: NameSpaces -> Content -> Content
+unwrapChild ns (Elem element) =
+ Elem $ element { elContent = concatMap (unwrap ns) (elContent element) }
+unwrapChild _ content = content
walkDocument' :: NameSpaces -> XMLC.Cursor -> XMLC.Cursor
walkDocument' ns cur =
- let modifiedCur = XMLC.modifyContent (unwrapSDTchild ns) cur
+ let modifiedCur = XMLC.modifyContent (unwrapChild ns) cur
in
case XMLC.nextDF modifiedCur of
Just cur' -> walkDocument' ns cur'
@@ -275,7 +279,6 @@ data ParPart = PlainRun Run
| Drawing FilePath String String B.ByteString Extent -- title, alt
| Chart -- placeholder for now
| PlainOMath [Exp]
- | SmartTag [Run]
| Field FieldInfo [Run]
| NullParPart -- when we need to return nothing, but
-- not because of an error.
@@ -826,10 +829,6 @@ elemToParPart ns element
runs <- mapD (elemToRun ns) (elChildren element)
return $ ChangedRuns change runs
elemToParPart ns element
- | isElem ns "w" "smartTag" element = do
- runs <- mapD (elemToRun ns) (elChildren element)
- return $ SmartTag runs
-elemToParPart ns element
| isElem ns "w" "bookmarkStart" element
, Just bmId <- findAttrByName ns "w" "id" element
, Just bmName <- findAttrByName ns "w" "name" element =
diff --git a/src/Text/Pandoc/Readers/Docx/StyleMap.hs b/src/Text/Pandoc/Readers/Docx/StyleMap.hs
index b32a73770..6ccda3ccc 100644
--- a/src/Text/Pandoc/Readers/Docx/StyleMap.hs
+++ b/src/Text/Pandoc/Readers/Docx/StyleMap.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE NoImplicitPrelude #-}
module Text.Pandoc.Readers.Docx.StyleMap ( StyleMaps(..)
, alterMap
, getMap
@@ -7,6 +8,7 @@ module Text.Pandoc.Readers.Docx.StyleMap ( StyleMaps(..)
, hasStyleName
) where
+import Prelude
import Control.Monad.State.Strict
import Data.Char (toLower)
import qualified Data.Map as M
diff --git a/src/Text/Pandoc/Readers/Docx/Util.hs b/src/Text/Pandoc/Readers/Docx/Util.hs
index d9d65bc07..088950d26 100644
--- a/src/Text/Pandoc/Readers/Docx/Util.hs
+++ b/src/Text/Pandoc/Readers/Docx/Util.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE NoImplicitPrelude #-}
module Text.Pandoc.Readers.Docx.Util (
NameSpaces
, elemName
@@ -8,6 +9,7 @@ module Text.Pandoc.Readers.Docx.Util (
, findAttrByName
) where
+import Prelude
import Data.Maybe (mapMaybe)
import Text.XML.Light