{-# LANGUAGE CPP               #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards     #-}
{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE ViewPatterns      #-}
{- |
   Module      : Text.Pandoc.Readers.Docx
   Copyright   : Copyright (C) 2014-2020 Jesse Rosenthal
   License     : GNU GPL, version 2 or above

   Maintainer  : Jesse Rosenthal <jrosenthal@jhu.edu>
   Stability   : alpha
   Portability : portable

Conversion of Docx type (defined in Text.Pandoc.Readers.Docx.Parse)
to 'Pandoc' document.  -}

{-
Current state of implementation of Docx entities ([x] means
implemented, [-] means partially implemented):

* Blocks

  - [X] Para
  - [X] CodeBlock (styled with `SourceCode`)
  - [X] BlockQuote (styled with `Quote`, `BlockQuote`, or, optionally,
        indented)
  - [X] OrderedList
  - [X] BulletList
  - [X] DefinitionList (styled with adjacent `DefinitionTerm` and `Definition`)
  - [X] Header (styled with `Heading#`)
  - [ ] HorizontalRule
  - [-] Table (column widths and alignments not yet implemented)

* Inlines

  - [X] Str
  - [X] Emph
  - [X] Strong
  - [X] Strikeout
  - [X] Superscript
  - [X] Subscript
  - [X] SmallCaps
  - [-] Underline (was previously converted to Emph)
  - [ ] Quoted
  - [ ] Cite
  - [X] Code (styled with `VerbatimChar`)
  - [X] Space
  - [X] LineBreak (these are invisible in Word: entered with Shift-Return)
  - [X] Math
  - [X] Link (links to an arbitrary bookmark create a span with the target as
        id and "anchor" class)
  - [X] Image
  - [X] Note (Footnotes and Endnotes are silently combined.)
-}

module Text.Pandoc.Readers.Docx
       ( readDocx
       ) where

import Codec.Archive.Zip
import Control.Monad.Reader
import Control.Monad.State.Strict
import Data.Bifunctor (bimap, first)
import qualified Data.ByteString.Lazy as B
import Data.Default (Default)
import Data.List (delete, intersect, foldl')
import Data.Char (isSpace)
import qualified Data.Map as M
import qualified Data.Text as T
import Data.Maybe (catMaybes, isJust, fromMaybe)
import Data.Sequence (ViewL (..), viewl)
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import Text.Pandoc.Builder as Pandoc
import Text.Pandoc.MediaBag (MediaBag)
import Text.Pandoc.Options
import Text.Pandoc.Readers.Docx.Combine
import Text.Pandoc.Readers.Docx.Lists
import Text.Pandoc.Readers.Docx.Parse as Docx
import Text.Pandoc.Shared
import Text.Pandoc.Walk
import Text.TeXMath (writeTeX)
import Control.Monad.Except (throwError)
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import qualified Text.Pandoc.Class.PandocMonad as P
import Text.Pandoc.Error
import Text.Pandoc.Logging
import Data.List.NonEmpty (nonEmpty)

readDocx :: PandocMonad m
         => ReaderOptions
         -> B.ByteString
         -> m Pandoc
readDocx :: ReaderOptions -> ByteString -> m Pandoc
readDocx ReaderOptions
opts ByteString
bytes =
  case ByteString -> Either String Archive
toArchiveOrFail ByteString
bytes of
    Right Archive
archive ->
      case Archive -> Either DocxError (Docx, [Text])
archiveToDocxWithWarnings Archive
archive of
        Right (Docx
docx, [Text]
parserWarnings) -> do
          (Text -> m ()) -> [Text] -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (LogMessage -> m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
P.report (LogMessage -> m ()) -> (Text -> LogMessage) -> Text -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> LogMessage
DocxParserWarning) [Text]
parserWarnings
          (Meta
meta, [Block]
blks) <- ReaderOptions -> Docx -> m (Meta, [Block])
forall (m :: * -> *).
PandocMonad m =>
ReaderOptions -> Docx -> m (Meta, [Block])
docxToOutput ReaderOptions
opts Docx
docx
          Pandoc -> m Pandoc
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Meta -> [Block] -> Pandoc
Pandoc Meta
meta [Block]
blks
        Left DocxError
docxerr -> PandocError -> m Pandoc
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Pandoc) -> PandocError -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocSomeError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$
                         Text
"couldn't parse docx file: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (DocxError -> String
forall a. Show a => a -> String
show DocxError
docxerr)
    Left String
err -> PandocError -> m Pandoc
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Pandoc) -> PandocError -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocSomeError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$
                  Text
"couldn't unpack docx container: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
err

data DState = DState { DState -> Map Text Text
docxAnchorMap :: M.Map T.Text T.Text
                     , DState -> Set Text
docxAnchorSet :: Set.Set T.Text
                     , DState -> Maybe Text
docxImmedPrevAnchor :: Maybe T.Text
                     , DState -> MediaBag
docxMediaBag  :: MediaBag
                     , DState -> Inlines
docxDropCap   :: Inlines
                     -- keep track of (numId, lvl) values for
                     -- restarting
                     , DState -> Map (Text, Text) Integer
docxListState :: M.Map (T.Text, T.Text) Integer
                     , DState -> Inlines
docxPrevPara  :: Inlines
                     , DState -> [Blocks]
docxTableCaptions :: [Blocks]
                     }

instance Default DState where
  def :: DState
def = DState :: Map Text Text
-> Set Text
-> Maybe Text
-> MediaBag
-> Inlines
-> Map (Text, Text) Integer
-> Inlines
-> [Blocks]
-> DState
DState { docxAnchorMap :: Map Text Text
docxAnchorMap = Map Text Text
forall k a. Map k a
M.empty
               , docxAnchorSet :: Set Text
docxAnchorSet = Set Text
forall a. Monoid a => a
mempty
               , docxImmedPrevAnchor :: Maybe Text
docxImmedPrevAnchor = Maybe Text
forall a. Maybe a
Nothing
               , docxMediaBag :: MediaBag
docxMediaBag  = MediaBag
forall a. Monoid a => a
mempty
               , docxDropCap :: Inlines
docxDropCap   = Inlines
forall a. Monoid a => a
mempty
               , docxListState :: Map (Text, Text) Integer
docxListState = Map (Text, Text) Integer
forall k a. Map k a
M.empty
               , docxPrevPara :: Inlines
docxPrevPara  = Inlines
forall a. Monoid a => a
mempty
               , docxTableCaptions :: [Blocks]
docxTableCaptions = []
               }

data DEnv = DEnv { DEnv -> ReaderOptions
docxOptions       :: ReaderOptions
                 , DEnv -> Bool
docxInHeaderBlock :: Bool
                 , DEnv -> Bool
docxInBidi        :: Bool
                 }

instance Default DEnv where
  def :: DEnv
def = ReaderOptions -> Bool -> Bool -> DEnv
DEnv ReaderOptions
forall a. Default a => a
def Bool
False Bool
False

type DocxContext m = ReaderT DEnv (StateT DState m)

evalDocxContext :: PandocMonad m => DocxContext m a -> DEnv -> DState -> m a
evalDocxContext :: DocxContext m a -> DEnv -> DState -> m a
evalDocxContext DocxContext m a
ctx DEnv
env DState
st = (StateT DState m a -> DState -> m a)
-> DState -> StateT DState m a -> m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip StateT DState m a -> DState -> m a
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT DState
st (StateT DState m a -> m a) -> StateT DState m a -> m a
forall a b. (a -> b) -> a -> b
$ DocxContext m a -> DEnv -> StateT DState m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT DocxContext m a
ctx DEnv
env

-- This is empty, but we put it in for future-proofing.
spansToKeep :: [CharStyleName]
spansToKeep :: [CharStyleName]
spansToKeep = []

divsToKeep :: [ParaStyleName]
divsToKeep :: [ParaStyleName]
divsToKeep = [ParaStyleName
"Definition", ParaStyleName
"Definition Term"]

metaStyles :: M.Map ParaStyleName T.Text
metaStyles :: Map ParaStyleName Text
metaStyles = [(ParaStyleName, Text)] -> Map ParaStyleName Text
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [ (ParaStyleName
"Title", Text
"title")
                        , (ParaStyleName
"Subtitle", Text
"subtitle")
                        , (ParaStyleName
"Author", Text
"author")
                        , (ParaStyleName
"Date", Text
"date")
                        , (ParaStyleName
"Abstract", Text
"abstract")]

sepBodyParts :: [BodyPart] -> ([BodyPart], [BodyPart])
sepBodyParts :: [BodyPart] -> ([BodyPart], [BodyPart])
sepBodyParts = (BodyPart -> Bool) -> [BodyPart] -> ([BodyPart], [BodyPart])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (\BodyPart
bp -> BodyPart -> Bool
isMetaPar BodyPart
bp Bool -> Bool -> Bool
|| BodyPart -> Bool
isEmptyPar BodyPart
bp)

isMetaPar :: BodyPart -> Bool
isMetaPar :: BodyPart -> Bool
isMetaPar (Paragraph ParagraphStyle
pPr [ParPart]
_) =
  Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [ParaStyleName] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([ParaStyleName] -> Bool) -> [ParaStyleName] -> Bool
forall a b. (a -> b) -> a -> b
$ [ParaStyleName] -> [ParaStyleName] -> [ParaStyleName]
forall a. Eq a => [a] -> [a] -> [a]
intersect ([ParStyle] -> [StyleName ParStyle]
forall (t :: * -> *) a.
(Functor t, HasStyleName a) =>
t a -> t (StyleName a)
getStyleNames ([ParStyle] -> [StyleName ParStyle])
-> [ParStyle] -> [StyleName ParStyle]
forall a b. (a -> b) -> a -> b
$ ParagraphStyle -> [ParStyle]
pStyle ParagraphStyle
pPr) (Map ParaStyleName Text -> [ParaStyleName]
forall k a. Map k a -> [k]
M.keys Map ParaStyleName Text
metaStyles)
isMetaPar BodyPart
_ = Bool
False

isEmptyPar :: BodyPart -> Bool
isEmptyPar :: BodyPart -> Bool
isEmptyPar (Paragraph ParagraphStyle
_ [ParPart]
parParts) =
  (ParPart -> Bool) -> [ParPart] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ParPart -> Bool
isEmptyParPart [ParPart]
parParts
  where
    isEmptyParPart :: ParPart -> Bool
isEmptyParPart (PlainRun (Run RunStyle
_ [RunElem]
runElems)) = (RunElem -> Bool) -> [RunElem] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all RunElem -> Bool
isEmptyElem [RunElem]
runElems
    isEmptyParPart ParPart
_                           = Bool
False
    isEmptyElem :: RunElem -> Bool
isEmptyElem (TextRun Text
s) = Text -> Text
trim Text
s Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
""
    isEmptyElem RunElem
_           = Bool
True
isEmptyPar BodyPart
_ = Bool
False

bodyPartsToMeta' :: PandocMonad m => [BodyPart] -> DocxContext m (M.Map T.Text MetaValue)
bodyPartsToMeta' :: [BodyPart] -> DocxContext m (Map Text MetaValue)
bodyPartsToMeta' [] = Map Text MetaValue -> DocxContext m (Map Text MetaValue)
forall (m :: * -> *) a. Monad m => a -> m a
return Map Text MetaValue
forall k a. Map k a
M.empty
bodyPartsToMeta' (BodyPart
bp : [BodyPart]
bps)
  | (Paragraph ParagraphStyle
pPr [ParPart]
parParts) <- BodyPart
bp
  , (ParaStyleName
c : [ParaStyleName]
_)<- [ParStyle] -> [StyleName ParStyle]
forall (t :: * -> *) a.
(Functor t, HasStyleName a) =>
t a -> t (StyleName a)
getStyleNames (ParagraphStyle -> [ParStyle]
pStyle ParagraphStyle
pPr) [ParaStyleName] -> [ParaStyleName] -> [ParaStyleName]
forall a. Eq a => [a] -> [a] -> [a]
`intersect` Map ParaStyleName Text -> [ParaStyleName]
forall k a. Map k a -> [k]
M.keys Map ParaStyleName Text
metaStyles
  , (Just Text
metaField) <- ParaStyleName -> Map ParaStyleName Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup ParaStyleName
c Map ParaStyleName Text
metaStyles = do
    Inlines
inlines <- [Inlines] -> Inlines
smushInlines ([Inlines] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Inlines]
-> ReaderT DEnv (StateT DState m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParPart -> ReaderT DEnv (StateT DState m) Inlines)
-> [ParPart] -> ReaderT DEnv (StateT DState m) [Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ParPart -> ReaderT DEnv (StateT DState m) Inlines
forall (m :: * -> *).
PandocMonad m =>
ParPart -> DocxContext m Inlines
parPartToInlines [ParPart]
parParts
    Map Text MetaValue
remaining <- [BodyPart] -> DocxContext m (Map Text MetaValue)
forall (m :: * -> *).
PandocMonad m =>
[BodyPart] -> DocxContext m (Map Text MetaValue)
bodyPartsToMeta' [BodyPart]
bps
    let
      f :: MetaValue -> MetaValue -> MetaValue
f (MetaInlines [Inline]
ils) (MetaInlines [Inline]
ils') = [Block] -> MetaValue
MetaBlocks [[Inline] -> Block
Para [Inline]
ils, [Inline] -> Block
Para [Inline]
ils']
      f (MetaInlines [Inline]
ils) (MetaBlocks [Block]
blks) = [Block] -> MetaValue
MetaBlocks ([Inline] -> Block
Para [Inline]
ils Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
: [Block]
blks)
      f MetaValue
m (MetaList [MetaValue]
mv) = [MetaValue] -> MetaValue
MetaList (MetaValue
m MetaValue -> [MetaValue] -> [MetaValue]
forall a. a -> [a] -> [a]
: [MetaValue]
mv)
      f MetaValue
m MetaValue
n             = [MetaValue] -> MetaValue
MetaList [MetaValue
m, MetaValue
n]
    Map Text MetaValue -> DocxContext m (Map Text MetaValue)
forall (m :: * -> *) a. Monad m => a -> m a
return (Map Text MetaValue -> DocxContext m (Map Text MetaValue))
-> Map Text MetaValue -> DocxContext m (Map Text MetaValue)
forall a b. (a -> b) -> a -> b
$ (MetaValue -> MetaValue -> MetaValue)
-> Text -> MetaValue -> Map Text MetaValue -> Map Text MetaValue
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
M.insertWith MetaValue -> MetaValue -> MetaValue
f Text
metaField ([Inline] -> MetaValue
MetaInlines (Inlines -> [Inline]
forall a. Many a -> [a]
toList Inlines
inlines)) Map Text MetaValue
remaining
bodyPartsToMeta' (BodyPart
_ : [BodyPart]
bps) = [BodyPart] -> DocxContext m (Map Text MetaValue)
forall (m :: * -> *).
PandocMonad m =>
[BodyPart] -> DocxContext m (Map Text MetaValue)
bodyPartsToMeta' [BodyPart]
bps

bodyPartsToMeta :: PandocMonad m => [BodyPart] -> DocxContext m Meta
bodyPartsToMeta :: [BodyPart] -> DocxContext m Meta
bodyPartsToMeta [BodyPart]
bps = do
  Map Text MetaValue
mp <- [BodyPart] -> DocxContext m (Map Text MetaValue)
forall (m :: * -> *).
PandocMonad m =>
[BodyPart] -> DocxContext m (Map Text MetaValue)
bodyPartsToMeta' [BodyPart]
bps
  let mp' :: Map Text MetaValue
mp' =
        case Text -> Map Text MetaValue -> Maybe MetaValue
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
"author" Map Text MetaValue
mp of
          Just MetaValue
mv -> Text -> MetaValue -> Map Text MetaValue -> Map Text MetaValue
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
"author" (MetaValue -> MetaValue
fixAuthors MetaValue
mv) Map Text MetaValue
mp
          Maybe MetaValue
Nothing -> Map Text MetaValue
mp
  Meta -> DocxContext m Meta
forall (m :: * -> *) a. Monad m => a -> m a
return (Meta -> DocxContext m Meta) -> Meta -> DocxContext m Meta
forall a b. (a -> b) -> a -> b
$ Map Text MetaValue -> Meta
Meta Map Text MetaValue
mp'

fixAuthors :: MetaValue -> MetaValue
fixAuthors :: MetaValue -> MetaValue
fixAuthors (MetaBlocks [Block]
blks) = [MetaValue] -> MetaValue
MetaList [[Inline] -> MetaValue
MetaInlines [Inline]
ils | Para [Inline]
ils <- [Block]
blks]
fixAuthors MetaValue
mv = MetaValue
mv

isInheritedFromStyles :: (Eq (StyleName s), HasStyleName s, HasParentStyle s) => [StyleName s] -> s -> Bool
isInheritedFromStyles :: [StyleName s] -> s -> Bool
isInheritedFromStyles [StyleName s]
names s
sty
  | s -> StyleName s
forall a. HasStyleName a => a -> StyleName a
getStyleName s
sty StyleName s -> [StyleName s] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [StyleName s]
names = Bool
True
  | Just s
psty <- s -> Maybe s
forall a. HasParentStyle a => a -> Maybe a
getParentStyle s
sty = [StyleName s] -> s -> Bool
forall s.
(Eq (StyleName s), HasStyleName s, HasParentStyle s) =>
[StyleName s] -> s -> Bool
isInheritedFromStyles [StyleName s]
names s
psty
  | Bool
otherwise = Bool
False

hasStylesInheritedFrom :: [ParaStyleName] -> ParagraphStyle -> Bool
hasStylesInheritedFrom :: [ParaStyleName] -> ParagraphStyle -> Bool
hasStylesInheritedFrom [ParaStyleName]
ns ParagraphStyle
s = (ParStyle -> Bool) -> [ParStyle] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ([StyleName ParStyle] -> ParStyle -> Bool
forall s.
(Eq (StyleName s), HasStyleName s, HasParentStyle s) =>
[StyleName s] -> s -> Bool
isInheritedFromStyles [StyleName ParStyle]
[ParaStyleName]
ns) ([ParStyle] -> Bool) -> [ParStyle] -> Bool
forall a b. (a -> b) -> a -> b
$ ParagraphStyle -> [ParStyle]
pStyle ParagraphStyle
s

removeStyleNamed :: ParaStyleName -> ParagraphStyle -> ParagraphStyle
removeStyleNamed :: ParaStyleName -> ParagraphStyle -> ParagraphStyle
removeStyleNamed ParaStyleName
sn ParagraphStyle
ps = ParagraphStyle
ps{pStyle :: [ParStyle]
pStyle = (ParStyle -> Bool) -> [ParStyle] -> [ParStyle]
forall a. (a -> Bool) -> [a] -> [a]
filter (\ParStyle
psd -> ParStyle -> StyleName ParStyle
forall a. HasStyleName a => a -> StyleName a
getStyleName ParStyle
psd ParaStyleName -> ParaStyleName -> Bool
forall a. Eq a => a -> a -> Bool
/= ParaStyleName
sn) ([ParStyle] -> [ParStyle]) -> [ParStyle] -> [ParStyle]
forall a b. (a -> b) -> a -> b
$ ParagraphStyle -> [ParStyle]
pStyle ParagraphStyle
ps}

isCodeCharStyle :: CharStyle -> Bool
isCodeCharStyle :: CharStyle -> Bool
isCodeCharStyle = [StyleName CharStyle] -> CharStyle -> Bool
forall s.
(Eq (StyleName s), HasStyleName s, HasParentStyle s) =>
[StyleName s] -> s -> Bool
isInheritedFromStyles [StyleName CharStyle
"Verbatim Char"]

isCodeDiv :: ParagraphStyle -> Bool
isCodeDiv :: ParagraphStyle -> Bool
isCodeDiv = [ParaStyleName] -> ParagraphStyle -> Bool
hasStylesInheritedFrom [ParaStyleName
"Source Code"]

isBlockQuote :: ParStyle -> Bool
isBlockQuote :: ParStyle -> Bool
isBlockQuote =
  [StyleName ParStyle] -> ParStyle -> Bool
forall s.
(Eq (StyleName s), HasStyleName s, HasParentStyle s) =>
[StyleName s] -> s -> Bool
isInheritedFromStyles [
    StyleName ParStyle
"Quote", StyleName ParStyle
"Block Text", StyleName ParStyle
"Block Quote", StyleName ParStyle
"Block Quotation"
    ]

runElemToInlines :: RunElem -> Inlines
runElemToInlines :: RunElem -> Inlines
runElemToInlines (TextRun Text
s)   = Text -> Inlines
text Text
s
runElemToInlines RunElem
LnBrk         = Inlines
linebreak
runElemToInlines RunElem
Tab           = Inlines
space
runElemToInlines RunElem
SoftHyphen    = Text -> Inlines
text Text
"\xad"
runElemToInlines RunElem
NoBreakHyphen = Text -> Inlines
text Text
"\x2011"

runElemToText :: RunElem -> T.Text
runElemToText :: RunElem -> Text
runElemToText (TextRun Text
s)   = Text
s
runElemToText RunElem
LnBrk         = Char -> Text
T.singleton Char
'\n'
runElemToText RunElem
Tab           = Char -> Text
T.singleton Char
'\t'
runElemToText RunElem
SoftHyphen    = Char -> Text
T.singleton Char
'\xad'
runElemToText RunElem
NoBreakHyphen = Char -> Text
T.singleton Char
'\x2011'

runToText :: Run -> T.Text
runToText :: Run -> Text
runToText (Run RunStyle
_ [RunElem]
runElems) = [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (RunElem -> Text) -> [RunElem] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map RunElem -> Text
runElemToText [RunElem]
runElems
runToText Run
_                = Text
""

parPartToText :: ParPart -> T.Text
parPartToText :: ParPart -> Text
parPartToText (PlainRun Run
run)             = Run -> Text
runToText Run
run
parPartToText (InternalHyperLink Text
_ [Run]
runs) = [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Run -> Text) -> [Run] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Run -> Text
runToText [Run]
runs
parPartToText (ExternalHyperLink Text
_ [Run]
runs) = [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Run -> Text) -> [Run] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Run -> Text
runToText [Run]
runs
parPartToText ParPart
_                          = Text
""

blacklistedCharStyles :: [CharStyleName]
blacklistedCharStyles :: [CharStyleName]
blacklistedCharStyles = [CharStyleName
"Hyperlink"]

resolveDependentRunStyle :: PandocMonad m => RunStyle -> DocxContext m RunStyle
resolveDependentRunStyle :: RunStyle -> DocxContext m RunStyle
resolveDependentRunStyle RunStyle
rPr
  | Just CharStyle
s  <- RunStyle -> Maybe CharStyle
rParentStyle RunStyle
rPr
  , CharStyle -> StyleName CharStyle
forall a. HasStyleName a => a -> StyleName a
getStyleName CharStyle
s CharStyleName -> [CharStyleName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [CharStyleName]
blacklistedCharStyles = do
      ReaderOptions
opts <- (DEnv -> ReaderOptions)
-> ReaderT DEnv (StateT DState m) ReaderOptions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DEnv -> ReaderOptions
docxOptions
      if Extension -> ReaderOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_styles ReaderOptions
opts
        then RunStyle -> DocxContext m RunStyle
forall (m :: * -> *) a. Monad m => a -> m a
return RunStyle
rPr
        else RunStyle -> RunStyle -> RunStyle
leftBiasedMergeRunStyle RunStyle
rPr (RunStyle -> RunStyle)
-> DocxContext m RunStyle -> DocxContext m RunStyle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RunStyle -> DocxContext m RunStyle
forall (m :: * -> *).
PandocMonad m =>
RunStyle -> DocxContext m RunStyle
resolveDependentRunStyle (CharStyle -> RunStyle
cStyleData CharStyle
s)
  | Bool
otherwise = RunStyle -> DocxContext m RunStyle
forall (m :: * -> *) a. Monad m => a -> m a
return RunStyle
rPr

runStyleToTransform :: PandocMonad m => RunStyle -> DocxContext m (Inlines -> Inlines)
runStyleToTransform :: RunStyle -> DocxContext m (Inlines -> Inlines)
runStyleToTransform RunStyle
rPr' = do
  ReaderOptions
opts <- (DEnv -> ReaderOptions)
-> ReaderT DEnv (StateT DState m) ReaderOptions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DEnv -> ReaderOptions
docxOptions
  Bool
inBidi <- (DEnv -> Bool) -> ReaderT DEnv (StateT DState m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DEnv -> Bool
docxInBidi
  let styles :: Bool
styles = Extension -> ReaderOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_styles ReaderOptions
opts
      ctl :: Bool
ctl = (Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== RunStyle -> Maybe Bool
isRTL RunStyle
rPr') Bool -> Bool -> Bool
|| (Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== RunStyle -> Maybe Bool
isForceCTL RunStyle
rPr')
      italic :: RunStyle -> Maybe Bool
italic RunStyle
rPr | Bool
ctl = RunStyle -> Maybe Bool
isItalicCTL RunStyle
rPr
                 | Bool
otherwise = RunStyle -> Maybe Bool
isItalic RunStyle
rPr
      bold :: RunStyle -> Maybe Bool
bold RunStyle
rPr | Bool
ctl = RunStyle -> Maybe Bool
isBoldCTL RunStyle
rPr
               | Bool
otherwise = RunStyle -> Maybe Bool
isBold RunStyle
rPr
      go :: RunStyle -> Inlines -> Inlines
go RunStyle
rPr
        | Just CharStyleName
sn <- CharStyle -> CharStyleName
forall a. HasStyleName a => a -> StyleName a
getStyleName (CharStyle -> CharStyleName)
-> Maybe CharStyle -> Maybe CharStyleName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RunStyle -> Maybe CharStyle
rParentStyle RunStyle
rPr
        , CharStyleName
sn CharStyleName -> [CharStyleName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [CharStyleName]
spansToKeep =
            Attr -> Inlines -> Inlines
spanWith (Text
"", [CharStyleName -> Text
forall a. FromStyleName a => a -> Text
normalizeToClassName CharStyleName
sn], [])
            (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunStyle -> Inlines -> Inlines
go RunStyle
rPr{rParentStyle :: Maybe CharStyle
rParentStyle = Maybe CharStyle
forall a. Maybe a
Nothing}
        | Bool
styles, Just CharStyle
s <- RunStyle -> Maybe CharStyle
rParentStyle RunStyle
rPr =
             Attr -> Inlines -> Inlines
spanWith (CharStyle -> Attr
forall a. (Eq (StyleName a), HasStyleName a) => a -> Attr
extraAttr CharStyle
s) (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunStyle -> Inlines -> Inlines
go RunStyle
rPr{rParentStyle :: Maybe CharStyle
rParentStyle = Maybe CharStyle
forall a. Maybe a
Nothing}
        | Just Bool
True <- RunStyle -> Maybe Bool
italic RunStyle
rPr =
            Inlines -> Inlines
emph (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunStyle -> Inlines -> Inlines
go RunStyle
rPr{isItalic :: Maybe Bool
isItalic = Maybe Bool
forall a. Maybe a
Nothing, isItalicCTL :: Maybe Bool
isItalicCTL = Maybe Bool
forall a. Maybe a
Nothing}
        | Just Bool
True <- RunStyle -> Maybe Bool
bold RunStyle
rPr =
            Inlines -> Inlines
strong (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunStyle -> Inlines -> Inlines
go RunStyle
rPr{isBold :: Maybe Bool
isBold = Maybe Bool
forall a. Maybe a
Nothing, isBoldCTL :: Maybe Bool
isBoldCTL = Maybe Bool
forall a. Maybe a
Nothing}
        | Just Bool
True <- RunStyle -> Maybe Bool
isSmallCaps RunStyle
rPr =
            Inlines -> Inlines
smallcaps (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunStyle -> Inlines -> Inlines
go RunStyle
rPr{isSmallCaps :: Maybe Bool
isSmallCaps = Maybe Bool
forall a. Maybe a
Nothing}
        | Just Bool
True <- RunStyle -> Maybe Bool
isStrike RunStyle
rPr =
            Inlines -> Inlines
strikeout (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunStyle -> Inlines -> Inlines
go RunStyle
rPr{isStrike :: Maybe Bool
isStrike = Maybe Bool
forall a. Maybe a
Nothing}
        | Just Bool
True <- RunStyle -> Maybe Bool
isRTL RunStyle
rPr =
            Attr -> Inlines -> Inlines
spanWith (Text
"",[],[(Text
"dir",Text
"rtl")]) (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunStyle -> Inlines -> Inlines
go RunStyle
rPr{isRTL :: Maybe Bool
isRTL = Maybe Bool
forall a. Maybe a
Nothing}
        | Bool
inBidi, Just Bool
False <- RunStyle -> Maybe Bool
isRTL RunStyle
rPr =
            Attr -> Inlines -> Inlines
spanWith (Text
"",[],[(Text
"dir",Text
"ltr")]) (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunStyle -> Inlines -> Inlines
go RunStyle
rPr{isRTL :: Maybe Bool
isRTL = Maybe Bool
forall a. Maybe a
Nothing}
        | Just VertAlign
SupScrpt <- RunStyle -> Maybe VertAlign
rVertAlign RunStyle
rPr =
            Inlines -> Inlines
superscript (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunStyle -> Inlines -> Inlines
go RunStyle
rPr{rVertAlign :: Maybe VertAlign
rVertAlign = Maybe VertAlign
forall a. Maybe a
Nothing}
        | Just VertAlign
SubScrpt <- RunStyle -> Maybe VertAlign
rVertAlign RunStyle
rPr =
            Inlines -> Inlines
subscript (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunStyle -> Inlines -> Inlines
go RunStyle
rPr{rVertAlign :: Maybe VertAlign
rVertAlign = Maybe VertAlign
forall a. Maybe a
Nothing}
        | Just Text
"single" <- RunStyle -> Maybe Text
rUnderline RunStyle
rPr =
            Inlines -> Inlines
Pandoc.underline (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RunStyle -> Inlines -> Inlines
go RunStyle
rPr{rUnderline :: Maybe Text
rUnderline = Maybe Text
forall a. Maybe a
Nothing}
        | Bool
otherwise = Inlines -> Inlines
forall a. a -> a
id
  (Inlines -> Inlines) -> DocxContext m (Inlines -> Inlines)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Inlines -> Inlines) -> DocxContext m (Inlines -> Inlines))
-> (Inlines -> Inlines) -> DocxContext m (Inlines -> Inlines)
forall a b. (a -> b) -> a -> b
$ RunStyle -> Inlines -> Inlines
go RunStyle
rPr'


runToInlines :: PandocMonad m => Run -> DocxContext m Inlines
runToInlines :: Run -> DocxContext m Inlines
runToInlines (Run RunStyle
rs [RunElem]
runElems)
  | Bool -> (CharStyle -> Bool) -> Maybe CharStyle -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False CharStyle -> Bool
isCodeCharStyle (Maybe CharStyle -> Bool) -> Maybe CharStyle -> Bool
forall a b. (a -> b) -> a -> b
$ RunStyle -> Maybe CharStyle
rParentStyle RunStyle
rs = do
      RunStyle
rPr <- RunStyle -> DocxContext m RunStyle
forall (m :: * -> *).
PandocMonad m =>
RunStyle -> DocxContext m RunStyle
resolveDependentRunStyle RunStyle
rs
      let codeString :: Inlines
codeString = Text -> Inlines
code (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (RunElem -> Text) -> [RunElem] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map RunElem -> Text
runElemToText [RunElem]
runElems
      Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ case RunStyle -> Maybe VertAlign
rVertAlign RunStyle
rPr of
        Just VertAlign
SupScrpt -> Inlines -> Inlines
superscript Inlines
codeString
        Just VertAlign
SubScrpt -> Inlines -> Inlines
subscript Inlines
codeString
        Maybe VertAlign
_             -> Inlines
codeString
  | Bool
otherwise = do
      RunStyle
rPr <- RunStyle -> DocxContext m RunStyle
forall (m :: * -> *).
PandocMonad m =>
RunStyle -> DocxContext m RunStyle
resolveDependentRunStyle RunStyle
rs
      let ils :: Inlines
ils = [Inlines] -> Inlines
smushInlines ((RunElem -> Inlines) -> [RunElem] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map RunElem -> Inlines
runElemToInlines [RunElem]
runElems)
      Inlines -> Inlines
transform <- RunStyle -> DocxContext m (Inlines -> Inlines)
forall (m :: * -> *).
PandocMonad m =>
RunStyle -> DocxContext m (Inlines -> Inlines)
runStyleToTransform RunStyle
rPr
      Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
transform Inlines
ils
runToInlines (Footnote [BodyPart]
bps) = Blocks -> Inlines
note (Blocks -> Inlines) -> ([Blocks] -> Blocks) -> [Blocks] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> Blocks
smushBlocks ([Blocks] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Blocks] -> DocxContext m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (BodyPart -> ReaderT DEnv (StateT DState m) Blocks)
-> [BodyPart] -> ReaderT DEnv (StateT DState m) [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM BodyPart -> ReaderT DEnv (StateT DState m) Blocks
forall (m :: * -> *).
PandocMonad m =>
BodyPart -> DocxContext m Blocks
bodyPartToBlocks [BodyPart]
bps
runToInlines (Endnote [BodyPart]
bps) = Blocks -> Inlines
note (Blocks -> Inlines) -> ([Blocks] -> Blocks) -> [Blocks] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> Blocks
smushBlocks ([Blocks] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Blocks] -> DocxContext m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (BodyPart -> ReaderT DEnv (StateT DState m) Blocks)
-> [BodyPart] -> ReaderT DEnv (StateT DState m) [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM BodyPart -> ReaderT DEnv (StateT DState m) Blocks
forall (m :: * -> *).
PandocMonad m =>
BodyPart -> DocxContext m Blocks
bodyPartToBlocks [BodyPart]
bps
runToInlines (InlineDrawing String
fp Text
title Text
alt ByteString
bs Extent
ext) = do
  (StateT DState m () -> ReaderT DEnv (StateT DState m) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT DState m () -> ReaderT DEnv (StateT DState m) ())
-> (m () -> StateT DState m ())
-> m ()
-> ReaderT DEnv (StateT DState m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m () -> StateT DState m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift) (m () -> ReaderT DEnv (StateT DState m) ())
-> m () -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> ByteString -> m ()
forall (m :: * -> *).
PandocMonad m =>
String -> Maybe Text -> ByteString -> m ()
P.insertMedia String
fp Maybe Text
forall a. Maybe a
Nothing ByteString
bs
  Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
imageWith (Extent -> Attr
extentToAttr Extent
ext) (String -> Text
T.pack String
fp) Text
title (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
text Text
alt
runToInlines Run
InlineChart = Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
spanWith (Text
"", [Text
"chart"], []) (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
text Text
"[CHART]"

extentToAttr :: Extent -> Attr
extentToAttr :: Extent -> Attr
extentToAttr (Just (Double
w, Double
h)) =
  (Text
"", [], [(Text
"width", Double -> Text
forall a. (Show a, Fractional a) => a -> Text
showDim Double
w), (Text
"height", Double -> Text
forall a. (Show a, Fractional a) => a -> Text
showDim Double
h)] )
  where
    showDim :: a -> Text
showDim a
d = a -> Text
forall a. Show a => a -> Text
tshow (a
d a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
914400) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"in"
extentToAttr Extent
_ = Attr
nullAttr

blocksToInlinesWarn :: PandocMonad m => T.Text -> Blocks -> DocxContext m Inlines
blocksToInlinesWarn :: Text -> Blocks -> DocxContext m Inlines
blocksToInlinesWarn Text
cmtId Blocks
blks = do
  let paraOrPlain :: Block -> Bool
      paraOrPlain :: Block -> Bool
paraOrPlain (Para [Inline]
_)  = Bool
True
      paraOrPlain (Plain [Inline]
_) = Bool
True
      paraOrPlain Block
_         = Bool
False
  Bool
-> ReaderT DEnv (StateT DState m) ()
-> ReaderT DEnv (StateT DState m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Block -> Bool) -> Blocks -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Block -> Bool
paraOrPlain Blocks
blks) (ReaderT DEnv (StateT DState m) ()
 -> ReaderT DEnv (StateT DState m) ())
-> ReaderT DEnv (StateT DState m) ()
-> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$
    StateT DState m () -> ReaderT DEnv (StateT DState m) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT DState m () -> ReaderT DEnv (StateT DState m) ())
-> StateT DState m () -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ LogMessage -> StateT DState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
P.report (LogMessage -> StateT DState m ())
-> LogMessage -> StateT DState m ()
forall a b. (a -> b) -> a -> b
$ Text -> LogMessage
DocxParserWarning (Text -> LogMessage) -> Text -> LogMessage
forall a b. (a -> b) -> a -> b
$
      Text
"Docx comment " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cmtId Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" will not retain formatting"
  Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ [Block] -> Inlines
blocksToInlines' (Blocks -> [Block]
forall a. Many a -> [a]
toList Blocks
blks)

-- The majority of work in this function is done in the primed
-- subfunction `partPartToInlines'`. We make this wrapper so that we
-- don't have to modify `docxImmedPrevAnchor` state after every function.
parPartToInlines :: PandocMonad m => ParPart -> DocxContext m Inlines
parPartToInlines :: ParPart -> DocxContext m Inlines
parPartToInlines ParPart
parPart =
  case ParPart
parPart of
    (BookMark Text
_ Text
anchor) | Text
anchor Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Text]
dummyAnchors -> do
      Bool
inHdrBool <- (DEnv -> Bool) -> ReaderT DEnv (StateT DState m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DEnv -> Bool
docxInHeaderBlock
      Inlines
ils <- ParPart -> DocxContext m Inlines
forall (m :: * -> *).
PandocMonad m =>
ParPart -> DocxContext m Inlines
parPartToInlines' ParPart
parPart
      Maybe Text
immedPrevAnchor <- (DState -> Maybe Text)
-> ReaderT DEnv (StateT DState m) (Maybe Text)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DState -> Maybe Text
docxImmedPrevAnchor
      Bool
-> ReaderT DEnv (StateT DState m) ()
-> ReaderT DEnv (StateT DState m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust Maybe Text
immedPrevAnchor Bool -> Bool -> Bool
|| Bool
inHdrBool)
        ((DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s{ docxImmedPrevAnchor :: Maybe Text
docxImmedPrevAnchor = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
anchor})
      Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
ils
    ParPart
_ -> do
      Inlines
ils <- ParPart -> DocxContext m Inlines
forall (m :: * -> *).
PandocMonad m =>
ParPart -> DocxContext m Inlines
parPartToInlines' ParPart
parPart
      (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s{ docxImmedPrevAnchor :: Maybe Text
docxImmedPrevAnchor = Maybe Text
forall a. Maybe a
Nothing}
      Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
ils

parPartToInlines' :: PandocMonad m => ParPart -> DocxContext m Inlines
parPartToInlines' :: ParPart -> DocxContext m Inlines
parPartToInlines' (PlainRun Run
r) = Run -> DocxContext m Inlines
forall (m :: * -> *). PandocMonad m => Run -> DocxContext m Inlines
runToInlines Run
r
parPartToInlines' (ChangedRuns (TrackedChange ChangeType
Insertion (ChangeInfo Text
_ Text
author Maybe Text
date)) [Run]
runs) = do
  ReaderOptions
opts <- (DEnv -> ReaderOptions)
-> ReaderT DEnv (StateT DState m) ReaderOptions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DEnv -> ReaderOptions
docxOptions
  case ReaderOptions -> TrackChanges
readerTrackChanges ReaderOptions
opts of
    TrackChanges
AcceptChanges -> [Inlines] -> Inlines
smushInlines ([Inlines] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Inlines]
-> DocxContext m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Run -> DocxContext m Inlines)
-> [Run] -> ReaderT DEnv (StateT DState m) [Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Run -> DocxContext m Inlines
forall (m :: * -> *). PandocMonad m => Run -> DocxContext m Inlines
runToInlines [Run]
runs
    TrackChanges
RejectChanges -> Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
    TrackChanges
AllChanges    -> do
      Inlines
ils <- [Inlines] -> Inlines
smushInlines ([Inlines] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Inlines]
-> DocxContext m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Run -> DocxContext m Inlines)
-> [Run] -> ReaderT DEnv (StateT DState m) [Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Run -> DocxContext m Inlines
forall (m :: * -> *). PandocMonad m => Run -> DocxContext m Inlines
runToInlines [Run]
runs
      let attr :: Attr
attr = (Text
"", [Text
"insertion"], Text -> Maybe Text -> [(Text, Text)]
addAuthorAndDate Text
author Maybe Text
date)
      Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
spanWith Attr
attr Inlines
ils
parPartToInlines' (ChangedRuns (TrackedChange ChangeType
Deletion (ChangeInfo Text
_ Text
author Maybe Text
date)) [Run]
runs) = do
  ReaderOptions
opts <- (DEnv -> ReaderOptions)
-> ReaderT DEnv (StateT DState m) ReaderOptions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DEnv -> ReaderOptions
docxOptions
  case ReaderOptions -> TrackChanges
readerTrackChanges ReaderOptions
opts of
    TrackChanges
AcceptChanges -> Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
    TrackChanges
RejectChanges -> [Inlines] -> Inlines
smushInlines ([Inlines] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Inlines]
-> DocxContext m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Run -> DocxContext m Inlines)
-> [Run] -> ReaderT DEnv (StateT DState m) [Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Run -> DocxContext m Inlines
forall (m :: * -> *). PandocMonad m => Run -> DocxContext m Inlines
runToInlines [Run]
runs
    TrackChanges
AllChanges    -> do
      Inlines
ils <- [Inlines] -> Inlines
smushInlines ([Inlines] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Inlines]
-> DocxContext m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Run -> DocxContext m Inlines)
-> [Run] -> ReaderT DEnv (StateT DState m) [Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Run -> DocxContext m Inlines
forall (m :: * -> *). PandocMonad m => Run -> DocxContext m Inlines
runToInlines [Run]
runs
      let attr :: Attr
attr = (Text
"", [Text
"deletion"], Text -> Maybe Text -> [(Text, Text)]
addAuthorAndDate Text
author Maybe Text
date)
      Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
spanWith Attr
attr Inlines
ils
parPartToInlines' (CommentStart Text
cmtId Text
author Maybe Text
date [BodyPart]
bodyParts) = do
  ReaderOptions
opts <- (DEnv -> ReaderOptions)
-> ReaderT DEnv (StateT DState m) ReaderOptions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DEnv -> ReaderOptions
docxOptions
  case ReaderOptions -> TrackChanges
readerTrackChanges ReaderOptions
opts of
    TrackChanges
AllChanges -> do
      Blocks
blks <- [Blocks] -> Blocks
smushBlocks ([Blocks] -> Blocks)
-> ReaderT DEnv (StateT DState m) [Blocks]
-> ReaderT DEnv (StateT DState m) Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (BodyPart -> ReaderT DEnv (StateT DState m) Blocks)
-> [BodyPart] -> ReaderT DEnv (StateT DState m) [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM BodyPart -> ReaderT DEnv (StateT DState m) Blocks
forall (m :: * -> *).
PandocMonad m =>
BodyPart -> DocxContext m Blocks
bodyPartToBlocks [BodyPart]
bodyParts
      Inlines
ils <- Text -> Blocks -> DocxContext m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Blocks -> DocxContext m Inlines
blocksToInlinesWarn Text
cmtId Blocks
blks
      let attr :: Attr
attr = (Text
"", [Text
"comment-start"], (Text
"id", Text
cmtId) (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: Text -> Maybe Text -> [(Text, Text)]
addAuthorAndDate Text
author Maybe Text
date)
      Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
spanWith Attr
attr Inlines
ils
    TrackChanges
_ -> Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
parPartToInlines' (CommentEnd Text
cmtId) = do
  ReaderOptions
opts <- (DEnv -> ReaderOptions)
-> ReaderT DEnv (StateT DState m) ReaderOptions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DEnv -> ReaderOptions
docxOptions
  case ReaderOptions -> TrackChanges
readerTrackChanges ReaderOptions
opts of
    TrackChanges
AllChanges -> do
      let attr :: Attr
attr = (Text
"", [Text
"comment-end"], [(Text
"id", Text
cmtId)])
      Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
spanWith Attr
attr Inlines
forall a. Monoid a => a
mempty
    TrackChanges
_ -> Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
parPartToInlines' (BookMark Text
_ Text
anchor) | Text
anchor Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
dummyAnchors =
  Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
parPartToInlines' (BookMark Text
_ Text
anchor) =
  -- We record these, so we can make sure not to overwrite
  -- user-defined anchor links with header auto ids.
  do
    -- get whether we're in a header.
    Bool
inHdrBool <- (DEnv -> Bool) -> ReaderT DEnv (StateT DState m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DEnv -> Bool
docxInHeaderBlock
    -- Get the anchor map.
    Map Text Text
anchorMap <- (DState -> Map Text Text)
-> ReaderT DEnv (StateT DState m) (Map Text Text)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DState -> Map Text Text
docxAnchorMap
    -- We don't want to rewrite if we're in a header, since we'll take
    -- care of that later, when we make the header anchor. If the
    -- bookmark were already in uniqueIdent form, this would lead to a
    -- duplication. Otherwise, we check to see if the id is already in
    -- there. Rewrite if necessary. This will have the possible effect
    -- of rewriting user-defined anchor links. However, since these
    -- are not defined in pandoc, it seems like a necessary evil to
    -- avoid an extra pass.
    Maybe Text
immedPrevAnchor <- (DState -> Maybe Text)
-> ReaderT DEnv (StateT DState m) (Maybe Text)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DState -> Maybe Text
docxImmedPrevAnchor
    case Maybe Text
immedPrevAnchor of
      Just Text
prevAnchor -> do
        Bool
-> ReaderT DEnv (StateT DState m) ()
-> ReaderT DEnv (StateT DState m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
inHdrBool
          ((DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s { docxAnchorMap :: Map Text Text
docxAnchorMap = Text -> Text -> Map Text Text -> Map Text Text
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
anchor Text
prevAnchor Map Text Text
anchorMap})
        Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
      Maybe Text
Nothing -> do
        Extensions
exts <- (DEnv -> Extensions) -> ReaderT DEnv (StateT DState m) Extensions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (ReaderOptions -> Extensions
readerExtensions (ReaderOptions -> Extensions)
-> (DEnv -> ReaderOptions) -> DEnv -> Extensions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DEnv -> ReaderOptions
docxOptions)
        let newAnchor :: Text
newAnchor =
              if Bool -> Bool
not Bool
inHdrBool Bool -> Bool -> Bool
&& Text
anchor Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Map Text Text -> [Text]
forall k a. Map k a -> [a]
M.elems Map Text Text
anchorMap
              then Extensions -> [Inline] -> Set Text -> Text
uniqueIdent Extensions
exts [Text -> Inline
Str Text
anchor]
                     ([Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList ([Text] -> Set Text) -> [Text] -> Set Text
forall a b. (a -> b) -> a -> b
$ Map Text Text -> [Text]
forall k a. Map k a -> [a]
M.elems Map Text Text
anchorMap)
              else Text
anchor
        Bool
-> ReaderT DEnv (StateT DState m) ()
-> ReaderT DEnv (StateT DState m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
inHdrBool
          ((DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s { docxAnchorMap :: Map Text Text
docxAnchorMap = Text -> Text -> Map Text Text -> Map Text Text
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
anchor Text
newAnchor Map Text Text
anchorMap})
        Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
spanWith (Text
newAnchor, [Text
"anchor"], []) Inlines
forall a. Monoid a => a
mempty
parPartToInlines' (Drawing String
fp Text
title Text
alt ByteString
bs Extent
ext) = do
  (StateT DState m () -> ReaderT DEnv (StateT DState m) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT DState m () -> ReaderT DEnv (StateT DState m) ())
-> (m () -> StateT DState m ())
-> m ()
-> ReaderT DEnv (StateT DState m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m () -> StateT DState m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift) (m () -> ReaderT DEnv (StateT DState m) ())
-> m () -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> ByteString -> m ()
forall (m :: * -> *).
PandocMonad m =>
String -> Maybe Text -> ByteString -> m ()
P.insertMedia String
fp Maybe Text
forall a. Maybe a
Nothing ByteString
bs
  Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
imageWith (Extent -> Attr
extentToAttr Extent
ext) (String -> Text
T.pack String
fp) Text
title (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
text Text
alt
parPartToInlines' ParPart
Chart =
  Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
spanWith (Text
"", [Text
"chart"], []) (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
text Text
"[CHART]"
parPartToInlines' (InternalHyperLink Text
anchor [Run]
runs) = do
  Inlines
ils <- [Inlines] -> Inlines
smushInlines ([Inlines] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Inlines]
-> DocxContext m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Run -> DocxContext m Inlines)
-> [Run] -> ReaderT DEnv (StateT DState m) [Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Run -> DocxContext m Inlines
forall (m :: * -> *). PandocMonad m => Run -> DocxContext m Inlines
runToInlines [Run]
runs
  Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
link (Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
anchor) Text
"" Inlines
ils
parPartToInlines' (ExternalHyperLink Text
target [Run]
runs) = do
  Inlines
ils <- [Inlines] -> Inlines
smushInlines ([Inlines] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Inlines]
-> DocxContext m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Run -> DocxContext m Inlines)
-> [Run] -> ReaderT DEnv (StateT DState m) [Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Run -> DocxContext m Inlines
forall (m :: * -> *). PandocMonad m => Run -> DocxContext m Inlines
runToInlines [Run]
runs
  Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
link Text
target Text
"" Inlines
ils
parPartToInlines' (PlainOMath [Exp]
exps) =
  Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> DocxContext m Inlines)
-> Inlines -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
math (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ [Exp] -> Text
writeTeX [Exp]
exps
parPartToInlines' (Field FieldInfo
info [Run]
runs) =
  case FieldInfo
info of
    HyperlinkField Text
url -> ParPart -> DocxContext m Inlines
forall (m :: * -> *).
PandocMonad m =>
ParPart -> DocxContext m Inlines
parPartToInlines' (ParPart -> DocxContext m Inlines)
-> ParPart -> DocxContext m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> [Run] -> ParPart
ExternalHyperLink Text
url [Run]
runs
    FieldInfo
UnknownField -> [Inlines] -> Inlines
smushInlines ([Inlines] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Inlines]
-> DocxContext m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Run -> DocxContext m Inlines)
-> [Run] -> ReaderT DEnv (StateT DState m) [Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Run -> DocxContext m Inlines
forall (m :: * -> *). PandocMonad m => Run -> DocxContext m Inlines
runToInlines [Run]
runs
parPartToInlines' ParPart
NullParPart = Inlines -> DocxContext m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty

isAnchorSpan :: Inline -> Bool
isAnchorSpan :: Inline -> Bool
isAnchorSpan (Span (Text
_, [Text
"anchor"], []) [Inline]
_) = Bool
True
isAnchorSpan Inline
_ = Bool
False

dummyAnchors :: [T.Text]
dummyAnchors :: [Text]
dummyAnchors = [Text
"_GoBack"]

makeHeaderAnchor :: PandocMonad m => Blocks -> DocxContext m Blocks
makeHeaderAnchor :: Blocks -> DocxContext m Blocks
makeHeaderAnchor Blocks
bs = (Block -> ReaderT DEnv (StateT DState m) Block)
-> Blocks -> DocxContext m Blocks
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Block -> ReaderT DEnv (StateT DState m) Block
forall (m :: * -> *). PandocMonad m => Block -> DocxContext m Block
makeHeaderAnchor' Blocks
bs

makeHeaderAnchor' :: PandocMonad m => Block -> DocxContext m Block
-- If there is an anchor already there (an anchor span in the header,
-- to be exact), we rename and associate the new id with the old one.
makeHeaderAnchor' :: Block -> DocxContext m Block
makeHeaderAnchor' (Header Int
n (Text
ident, [Text]
classes, [(Text, Text)]
kvs) [Inline]
ils)
  | (Inline
c:[Inline]
_) <- (Inline -> Bool) -> [Inline] -> [Inline]
forall a. (a -> Bool) -> [a] -> [a]
filter Inline -> Bool
isAnchorSpan [Inline]
ils
  , (Span (Text
anchIdent, [Text
"anchor"], [(Text, Text)]
_) [Inline]
cIls) <- Inline
c = do
    Map Text Text
hdrIDMap <- (DState -> Map Text Text)
-> ReaderT DEnv (StateT DState m) (Map Text Text)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DState -> Map Text Text
docxAnchorMap
    Extensions
exts <- (DEnv -> Extensions) -> ReaderT DEnv (StateT DState m) Extensions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (ReaderOptions -> Extensions
readerExtensions (ReaderOptions -> Extensions)
-> (DEnv -> ReaderOptions) -> DEnv -> Extensions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DEnv -> ReaderOptions
docxOptions)
    let newIdent :: Text
newIdent = if Text -> Bool
T.null Text
ident
                   then Extensions -> [Inline] -> Set Text -> Text
uniqueIdent Extensions
exts [Inline]
ils ([Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList ([Text] -> Set Text) -> [Text] -> Set Text
forall a b. (a -> b) -> a -> b
$ Map Text Text -> [Text]
forall k a. Map k a -> [a]
M.elems Map Text Text
hdrIDMap)
                   else Text
ident
        newIls :: [Inline]
newIls = (Inline -> [Inline]) -> [Inline] -> [Inline]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Inline -> [Inline]
f [Inline]
ils where f :: Inline -> [Inline]
f Inline
il | Inline
il Inline -> Inline -> Bool
forall a. Eq a => a -> a -> Bool
== Inline
c   = [Inline]
cIls
                                            | Bool
otherwise = [Inline
il]
    (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s {docxAnchorMap :: Map Text Text
docxAnchorMap = Text -> Text -> Map Text Text -> Map Text Text
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
anchIdent Text
newIdent Map Text Text
hdrIDMap}
    Block -> DocxContext m Block
forall (m :: * -> *). PandocMonad m => Block -> DocxContext m Block
makeHeaderAnchor' (Block -> DocxContext m Block) -> Block -> DocxContext m Block
forall a b. (a -> b) -> a -> b
$ Int -> Attr -> [Inline] -> Block
Header Int
n (Text
newIdent, [Text]
classes, [(Text, Text)]
kvs) [Inline]
newIls
-- Otherwise we just give it a name, and register that name (associate
-- it with itself.)
makeHeaderAnchor' (Header Int
n (Text
ident, [Text]
classes, [(Text, Text)]
kvs) [Inline]
ils) =
  do
    Map Text Text
hdrIDMap <- (DState -> Map Text Text)
-> ReaderT DEnv (StateT DState m) (Map Text Text)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DState -> Map Text Text
docxAnchorMap
    Extensions
exts <- (DEnv -> Extensions) -> ReaderT DEnv (StateT DState m) Extensions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (ReaderOptions -> Extensions
readerExtensions (ReaderOptions -> Extensions)
-> (DEnv -> ReaderOptions) -> DEnv -> Extensions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DEnv -> ReaderOptions
docxOptions)
    let newIdent :: Text
newIdent = if Text -> Bool
T.null Text
ident
                   then Extensions -> [Inline] -> Set Text -> Text
uniqueIdent Extensions
exts [Inline]
ils ([Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList ([Text] -> Set Text) -> [Text] -> Set Text
forall a b. (a -> b) -> a -> b
$ Map Text Text -> [Text]
forall k a. Map k a -> [a]
M.elems Map Text Text
hdrIDMap)
                   else Text
ident
    (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s {docxAnchorMap :: Map Text Text
docxAnchorMap = Text -> Text -> Map Text Text -> Map Text Text
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
newIdent Text
newIdent Map Text Text
hdrIDMap}
    Block -> DocxContext m Block
forall (m :: * -> *) a. Monad m => a -> m a
return (Block -> DocxContext m Block) -> Block -> DocxContext m Block
forall a b. (a -> b) -> a -> b
$ Int -> Attr -> [Inline] -> Block
Header Int
n (Text
newIdent, [Text]
classes, [(Text, Text)]
kvs) [Inline]
ils
makeHeaderAnchor' Block
blk = Block -> DocxContext m Block
forall (m :: * -> *) a. Monad m => a -> m a
return Block
blk

-- Rewrite a standalone paragraph block as a plain
singleParaToPlain :: Blocks -> Blocks
singleParaToPlain :: Blocks -> Blocks
singleParaToPlain Blocks
blks
  | (Para [Inline]
ils :< Seq Block
seeq) <- Seq Block -> ViewL Block
forall a. Seq a -> ViewL a
viewl (Seq Block -> ViewL Block) -> Seq Block -> ViewL Block
forall a b. (a -> b) -> a -> b
$ Blocks -> Seq Block
forall a. Many a -> Seq a
unMany Blocks
blks
  , Seq Block -> Bool
forall a. Seq a -> Bool
Seq.null Seq Block
seeq =
      Block -> Blocks
forall a. a -> Many a
singleton (Block -> Blocks) -> Block -> Blocks
forall a b. (a -> b) -> a -> b
$ [Inline] -> Block
Plain [Inline]
ils
singleParaToPlain Blocks
blks = Blocks
blks

cellToCell :: PandocMonad m => RowSpan -> Docx.Cell -> DocxContext m Pandoc.Cell
cellToCell :: RowSpan -> Cell -> DocxContext m Cell
cellToCell RowSpan
rowSpan (Docx.Cell Integer
gridSpan VMerge
_ [BodyPart]
bps) = do
  Blocks
blks <- [Blocks] -> Blocks
smushBlocks ([Blocks] -> Blocks)
-> ReaderT DEnv (StateT DState m) [Blocks]
-> ReaderT DEnv (StateT DState m) Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (BodyPart -> ReaderT DEnv (StateT DState m) Blocks)
-> [BodyPart] -> ReaderT DEnv (StateT DState m) [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM BodyPart -> ReaderT DEnv (StateT DState m) Blocks
forall (m :: * -> *).
PandocMonad m =>
BodyPart -> DocxContext m Blocks
bodyPartToBlocks [BodyPart]
bps
  let blks' :: Blocks
blks' = Blocks -> Blocks
singleParaToPlain (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$ [Block] -> Blocks
forall a. [a] -> Many a
fromList ([Block] -> Blocks) -> [Block] -> Blocks
forall a b. (a -> b) -> a -> b
$ [Block] -> [Block]
blocksToDefinitions ([Block] -> [Block]) -> [Block] -> [Block]
forall a b. (a -> b) -> a -> b
$ [Block] -> [Block]
blocksToBullets ([Block] -> [Block]) -> [Block] -> [Block]
forall a b. (a -> b) -> a -> b
$ Blocks -> [Block]
forall a. Many a -> [a]
toList Blocks
blks
  Cell -> DocxContext m Cell
forall (m :: * -> *) a. Monad m => a -> m a
return (Alignment -> RowSpan -> ColSpan -> Blocks -> Cell
cell Alignment
AlignDefault RowSpan
rowSpan (Int -> ColSpan
ColSpan (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
gridSpan)) Blocks
blks')

rowsToRows :: PandocMonad m => [Docx.Row] -> DocxContext m [Pandoc.Row]
rowsToRows :: [Row] -> DocxContext m [Row]
rowsToRows [Row]
rows = do
  let rowspans :: [[(RowSpan, Cell)]]
rowspans = (([(Int, Cell)] -> [(RowSpan, Cell)])
-> [[(Int, Cell)]] -> [[(RowSpan, Cell)]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([(Int, Cell)] -> [(RowSpan, Cell)])
 -> [[(Int, Cell)]] -> [[(RowSpan, Cell)]])
-> (((Int, Cell) -> (RowSpan, Cell))
    -> [(Int, Cell)] -> [(RowSpan, Cell)])
-> ((Int, Cell) -> (RowSpan, Cell))
-> [[(Int, Cell)]]
-> [[(RowSpan, Cell)]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Cell) -> (RowSpan, Cell))
-> [(Int, Cell)] -> [(RowSpan, Cell)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) ((Int -> RowSpan) -> (Int, Cell) -> (RowSpan, Cell)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Int -> RowSpan
RowSpan) ([Row] -> [[(Int, Cell)]]
Docx.rowsToRowspans [Row]
rows)
  [[Cell]]
cells <- ([(RowSpan, Cell)] -> ReaderT DEnv (StateT DState m) [Cell])
-> [[(RowSpan, Cell)]] -> ReaderT DEnv (StateT DState m) [[Cell]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (((RowSpan, Cell) -> ReaderT DEnv (StateT DState m) Cell)
-> [(RowSpan, Cell)] -> ReaderT DEnv (StateT DState m) [Cell]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((RowSpan -> Cell -> ReaderT DEnv (StateT DState m) Cell)
-> (RowSpan, Cell) -> ReaderT DEnv (StateT DState m) Cell
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry RowSpan -> Cell -> ReaderT DEnv (StateT DState m) Cell
forall (m :: * -> *).
PandocMonad m =>
RowSpan -> Cell -> DocxContext m Cell
cellToCell)) [[(RowSpan, Cell)]]
rowspans
  [Row] -> DocxContext m [Row]
forall (m :: * -> *) a. Monad m => a -> m a
return (([Cell] -> Row) -> [[Cell]] -> [Row]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Cell] -> Row
Pandoc.Row Attr
nullAttr) [[Cell]]
cells)

splitHeaderRows :: Bool -> [Docx.Row] -> ([Docx.Row], [Docx.Row])
splitHeaderRows :: Bool -> [Row] -> ([Row], [Row])
splitHeaderRows Bool
hasFirstRowFormatting [Row]
rs = ([Row] -> [Row])
-> ([Row] -> [Row]) -> ([Row], [Row]) -> ([Row], [Row])
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap [Row] -> [Row]
forall a. [a] -> [a]
reverse [Row] -> [Row]
forall a. [a] -> [a]
reverse (([Row], [Row]) -> ([Row], [Row]))
-> ([Row], [Row]) -> ([Row], [Row])
forall a b. (a -> b) -> a -> b
$ (([Row], [Row]), Bool) -> ([Row], [Row])
forall a b. (a, b) -> a
fst
  ((([Row], [Row]), Bool) -> ([Row], [Row]))
-> (([Row], [Row]), Bool) -> ([Row], [Row])
forall a b. (a -> b) -> a -> b
$ if Bool
hasFirstRowFormatting
    then ((([Row], [Row]), Bool) -> Row -> (([Row], [Row]), Bool))
-> (([Row], [Row]), Bool) -> [Row] -> (([Row], [Row]), Bool)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (([Row], [Row]), Bool) -> Row -> (([Row], [Row]), Bool)
f ((Int -> [Row] -> [Row]
forall a. Int -> [a] -> [a]
take Int
1 [Row]
rs, []), Bool
True) (Int -> [Row] -> [Row]
forall a. Int -> [a] -> [a]
drop Int
1 [Row]
rs)
    else ((([Row], [Row]), Bool) -> Row -> (([Row], [Row]), Bool))
-> (([Row], [Row]), Bool) -> [Row] -> (([Row], [Row]), Bool)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (([Row], [Row]), Bool) -> Row -> (([Row], [Row]), Bool)
f (([], []), Bool
False) [Row]
rs
  where
    f :: (([Row], [Row]), Bool) -> Row -> (([Row], [Row]), Bool)
f (([Row]
headerRows, [Row]
bodyRows), Bool
previousRowWasHeader) r :: Row
r@(Docx.Row TblHeader
h [Cell]
cs)
      | TblHeader
h TblHeader -> TblHeader -> Bool
forall a. Eq a => a -> a -> Bool
== TblHeader
HasTblHeader Bool -> Bool -> Bool
|| (Bool
previousRowWasHeader Bool -> Bool -> Bool
&& (Cell -> Bool) -> [Cell] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Cell -> Bool
isContinuationCell [Cell]
cs)
        = ((Row
r Row -> [Row] -> [Row]
forall a. a -> [a] -> [a]
: [Row]
headerRows, [Row]
bodyRows), Bool
True)
      | Bool
otherwise
        = (([Row]
headerRows, Row
r Row -> [Row] -> [Row]
forall a. a -> [a] -> [a]
: [Row]
bodyRows), Bool
False)

    isContinuationCell :: Cell -> Bool
isContinuationCell (Docx.Cell Integer
_ VMerge
vm [BodyPart]
_) = VMerge
vm VMerge -> VMerge -> Bool
forall a. Eq a => a -> a -> Bool
== VMerge
Docx.Continue


-- like trimInlines, but also take out linebreaks
trimSps :: Inlines -> Inlines
trimSps :: Inlines -> Inlines
trimSps (Many Seq Inline
ils) = Seq Inline -> Inlines
forall a. Seq a -> Many a
Many (Seq Inline -> Inlines) -> Seq Inline -> Inlines
forall a b. (a -> b) -> a -> b
$ (Inline -> Bool) -> Seq Inline -> Seq Inline
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.dropWhileL Inline -> Bool
isSp (Seq Inline -> Seq Inline) -> Seq Inline -> Seq Inline
forall a b. (a -> b) -> a -> b
$(Inline -> Bool) -> Seq Inline -> Seq Inline
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.dropWhileR Inline -> Bool
isSp Seq Inline
ils
  where isSp :: Inline -> Bool
isSp Inline
Space     = Bool
True
        isSp Inline
SoftBreak = Bool
True
        isSp Inline
LineBreak = Bool
True
        isSp Inline
_         = Bool
False

extraAttr :: (Eq (StyleName a), HasStyleName a) => a -> Attr
extraAttr :: a -> Attr
extraAttr a
s = (Text
"", [], [(Text
"custom-style", StyleName a -> Text
forall a. FromStyleName a => a -> Text
fromStyleName (StyleName a -> Text) -> StyleName a -> Text
forall a b. (a -> b) -> a -> b
$ a -> StyleName a
forall a. HasStyleName a => a -> StyleName a
getStyleName a
s)])

parStyleToTransform :: PandocMonad m => ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform :: ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform ParagraphStyle
pPr = case ParagraphStyle -> [ParStyle]
pStyle ParagraphStyle
pPr of
  c :: ParStyle
c@(ParStyle -> StyleName ParStyle
forall a. HasStyleName a => a -> StyleName a
getStyleName -> StyleName ParStyle
styleName):[ParStyle]
cs
    | StyleName ParStyle
ParaStyleName
styleName ParaStyleName -> [ParaStyleName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ParaStyleName]
divsToKeep -> do
        let pPr' :: ParagraphStyle
pPr' = ParagraphStyle
pPr { pStyle :: [ParStyle]
pStyle = [ParStyle]
cs }
        Blocks -> Blocks
transform <- ParagraphStyle -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *).
PandocMonad m =>
ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform ParagraphStyle
pPr'
        (Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks))
-> (Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks)
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
divWith (Text
"", [ParaStyleName -> Text
forall a. FromStyleName a => a -> Text
normalizeToClassName StyleName ParStyle
ParaStyleName
styleName], []) (Blocks -> Blocks) -> (Blocks -> Blocks) -> Blocks -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> Blocks
transform
    | StyleName ParStyle
ParaStyleName
styleName ParaStyleName -> [ParaStyleName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ParaStyleName]
listParagraphStyles -> do
        let pPr' :: ParagraphStyle
pPr' = ParagraphStyle
pPr { pStyle :: [ParStyle]
pStyle = [ParStyle]
cs, indentation :: Maybe ParIndentation
indentation = Maybe ParIndentation
forall a. Maybe a
Nothing}
        Blocks -> Blocks
transform <- ParagraphStyle -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *).
PandocMonad m =>
ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform ParagraphStyle
pPr'
        (Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks))
-> (Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks)
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
divWith (Text
"", [ParaStyleName -> Text
forall a. FromStyleName a => a -> Text
normalizeToClassName StyleName ParStyle
ParaStyleName
styleName], []) (Blocks -> Blocks) -> (Blocks -> Blocks) -> Blocks -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> Blocks
transform
    | Bool
otherwise -> do
        let pPr' :: ParagraphStyle
pPr' = ParagraphStyle
pPr { pStyle :: [ParStyle]
pStyle = [ParStyle]
cs }
        Blocks -> Blocks
transform <- ParagraphStyle -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *).
PandocMonad m =>
ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform ParagraphStyle
pPr'
        Bool
styles <- (DEnv -> Bool) -> ReaderT DEnv (StateT DState m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Extension -> ReaderOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_styles (ReaderOptions -> Bool) -> (DEnv -> ReaderOptions) -> DEnv -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DEnv -> ReaderOptions
docxOptions)
        (Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks))
-> (Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks)
forall a b. (a -> b) -> a -> b
$
          (if Bool
styles then Attr -> Blocks -> Blocks
divWith (ParStyle -> Attr
forall a. (Eq (StyleName a), HasStyleName a) => a -> Attr
extraAttr ParStyle
c) else Blocks -> Blocks
forall a. a -> a
id)
          (Blocks -> Blocks) -> (Blocks -> Blocks) -> Blocks -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if ParStyle -> Bool
isBlockQuote ParStyle
c then Blocks -> Blocks
blockQuote else Blocks -> Blocks
forall a. a -> a
id)
          (Blocks -> Blocks) -> (Blocks -> Blocks) -> Blocks -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> Blocks
transform
  []
    | Just Integer
left <- ParagraphStyle -> Maybe ParIndentation
indentation ParagraphStyle
pPr Maybe ParIndentation
-> (ParIndentation -> Maybe Integer) -> Maybe Integer
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ParIndentation -> Maybe Integer
leftParIndent -> do
        let pPr' :: ParagraphStyle
pPr' = ParagraphStyle
pPr { indentation :: Maybe ParIndentation
indentation = Maybe ParIndentation
forall a. Maybe a
Nothing }
            hang :: Integer
hang = Integer -> Maybe Integer -> Integer
forall a. a -> Maybe a -> a
fromMaybe Integer
0 (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ ParagraphStyle -> Maybe ParIndentation
indentation ParagraphStyle
pPr Maybe ParIndentation
-> (ParIndentation -> Maybe Integer) -> Maybe Integer
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ParIndentation -> Maybe Integer
hangingParIndent
        Blocks -> Blocks
transform <- ParagraphStyle -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *).
PandocMonad m =>
ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform ParagraphStyle
pPr'
        (Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks))
-> (Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks)
forall a b. (a -> b) -> a -> b
$ if (Integer
left Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
hang) Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0
                 then Blocks -> Blocks
blockQuote (Blocks -> Blocks) -> (Blocks -> Blocks) -> Blocks -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> Blocks
transform
                 else Blocks -> Blocks
transform
    | Bool
otherwise -> (Blocks -> Blocks) -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks -> Blocks
forall a. a -> a
id

normalizeToClassName :: (FromStyleName a) => a -> T.Text
normalizeToClassName :: a -> Text
normalizeToClassName = (Char -> Char) -> Text -> Text
T.map Char -> Char
go (Text -> Text) -> (a -> Text) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. FromStyleName a => a -> Text
fromStyleName
  where go :: Char -> Char
go Char
c | Char -> Bool
isSpace Char
c = Char
'-'
             | Bool
otherwise = Char
c

bodyPartToTableCaption :: PandocMonad m => BodyPart -> DocxContext m (Maybe Blocks)
bodyPartToTableCaption :: BodyPart -> DocxContext m (Maybe Blocks)
bodyPartToTableCaption (TblCaption ParagraphStyle
pPr [ParPart]
parparts) =
  Blocks -> Maybe Blocks
forall a. a -> Maybe a
Just (Blocks -> Maybe Blocks)
-> ReaderT DEnv (StateT DState m) Blocks
-> DocxContext m (Maybe Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BodyPart -> ReaderT DEnv (StateT DState m) Blocks
forall (m :: * -> *).
PandocMonad m =>
BodyPart -> DocxContext m Blocks
bodyPartToBlocks (ParagraphStyle -> [ParPart] -> BodyPart
Paragraph ParagraphStyle
pPr [ParPart]
parparts)
bodyPartToTableCaption BodyPart
_ = Maybe Blocks -> DocxContext m (Maybe Blocks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Blocks
forall a. Maybe a
Nothing

bodyPartToBlocks :: PandocMonad m => BodyPart -> DocxContext m Blocks
bodyPartToBlocks :: BodyPart -> DocxContext m Blocks
bodyPartToBlocks (Paragraph ParagraphStyle
pPr [ParPart]
parparts)
  | Just Bool
True <- ParagraphStyle -> Maybe Bool
pBidi ParagraphStyle
pPr = do
      let pPr' :: ParagraphStyle
pPr' = ParagraphStyle
pPr { pBidi :: Maybe Bool
pBidi = Maybe Bool
forall a. Maybe a
Nothing }
      (DEnv -> DEnv) -> DocxContext m Blocks -> DocxContext m Blocks
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\DEnv
s -> DEnv
s{ docxInBidi :: Bool
docxInBidi = Bool
True })
        (BodyPart -> DocxContext m Blocks
forall (m :: * -> *).
PandocMonad m =>
BodyPart -> DocxContext m Blocks
bodyPartToBlocks (ParagraphStyle -> [ParPart] -> BodyPart
Paragraph ParagraphStyle
pPr' [ParPart]
parparts))
  | ParagraphStyle -> Bool
isCodeDiv ParagraphStyle
pPr = do
      Blocks -> Blocks
transform <- ParagraphStyle -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *).
PandocMonad m =>
ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform ParagraphStyle
pPr
      Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DocxContext m Blocks) -> Blocks -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$
        Blocks -> Blocks
transform (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$
        Text -> Blocks
codeBlock (Text -> Blocks) -> Text -> Blocks
forall a b. (a -> b) -> a -> b
$
        [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$
        (ParPart -> Text) -> [ParPart] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ParPart -> Text
parPartToText [ParPart]
parparts
  | Just (ParaStyleName
style, Int
n) <- ParagraphStyle -> Maybe (ParaStyleName, Int)
pHeading ParagraphStyle
pPr = do
    Inlines
ils <-(DEnv -> DEnv)
-> ReaderT DEnv (StateT DState m) Inlines
-> ReaderT DEnv (StateT DState m) Inlines
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\DEnv
s-> DEnv
s{docxInHeaderBlock :: Bool
docxInHeaderBlock=Bool
True})
           ([Inlines] -> Inlines
smushInlines ([Inlines] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Inlines]
-> ReaderT DEnv (StateT DState m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParPart -> ReaderT DEnv (StateT DState m) Inlines)
-> [ParPart] -> ReaderT DEnv (StateT DState m) [Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ParPart -> ReaderT DEnv (StateT DState m) Inlines
forall (m :: * -> *).
PandocMonad m =>
ParPart -> DocxContext m Inlines
parPartToInlines [ParPart]
parparts)
    Blocks -> DocxContext m Blocks
forall (m :: * -> *).
PandocMonad m =>
Blocks -> DocxContext m Blocks
makeHeaderAnchor (Blocks -> DocxContext m Blocks) -> Blocks -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$
      Attr -> Int -> Inlines -> Blocks
headerWith (Text
"", (ParaStyleName -> Text) -> [ParaStyleName] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ParaStyleName -> Text
forall a. FromStyleName a => a -> Text
normalizeToClassName ([ParaStyleName] -> [Text])
-> ([ParaStyleName] -> [ParaStyleName])
-> [ParaStyleName]
-> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParaStyleName -> [ParaStyleName] -> [ParaStyleName]
forall a. Eq a => a -> [a] -> [a]
delete ParaStyleName
style ([ParaStyleName] -> [Text]) -> [ParaStyleName] -> [Text]
forall a b. (a -> b) -> a -> b
$ [ParStyle] -> [StyleName ParStyle]
forall (t :: * -> *) a.
(Functor t, HasStyleName a) =>
t a -> t (StyleName a)
getStyleNames (ParagraphStyle -> [ParStyle]
pStyle ParagraphStyle
pPr), []) Int
n Inlines
ils
  | Bool
otherwise = do
    Inlines
ils <- Inlines -> Inlines
trimSps (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
smushInlines ([Inlines] -> Inlines)
-> ReaderT DEnv (StateT DState m) [Inlines]
-> ReaderT DEnv (StateT DState m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParPart -> ReaderT DEnv (StateT DState m) Inlines)
-> [ParPart] -> ReaderT DEnv (StateT DState m) [Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ParPart -> ReaderT DEnv (StateT DState m) Inlines
forall (m :: * -> *).
PandocMonad m =>
ParPart -> DocxContext m Inlines
parPartToInlines [ParPart]
parparts
    Inlines
prevParaIls <- (DState -> Inlines) -> ReaderT DEnv (StateT DState m) Inlines
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DState -> Inlines
docxPrevPara
    Inlines
dropIls <- (DState -> Inlines) -> ReaderT DEnv (StateT DState m) Inlines
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DState -> Inlines
docxDropCap
    let ils' :: Inlines
ils' = Inlines
dropIls Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
ils
    let (Inlines -> Blocks
paraOrPlain, ParagraphStyle
pPr')
          | [ParaStyleName] -> ParagraphStyle -> Bool
hasStylesInheritedFrom [ParaStyleName
"Compact"] ParagraphStyle
pPr = (Inlines -> Blocks
plain, ParaStyleName -> ParagraphStyle -> ParagraphStyle
removeStyleNamed ParaStyleName
"Compact" ParagraphStyle
pPr)
          | Bool
otherwise = (Inlines -> Blocks
para, ParagraphStyle
pPr)
    if ParagraphStyle -> Bool
dropCap ParagraphStyle
pPr'
      then do (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s { docxDropCap :: Inlines
docxDropCap = Inlines
ils' }
              Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
      else do (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s { docxDropCap :: Inlines
docxDropCap = Inlines
forall a. Monoid a => a
mempty }
              let ils'' :: Inlines
ils'' = (if Inlines -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
prevParaIls then Inlines
forall a. Monoid a => a
mempty
                          else Inlines
prevParaIls Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
space) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
ils'
                  handleInsertion :: DocxContext m Blocks
handleInsertion = do
                    (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s {docxPrevPara :: Inlines
docxPrevPara = Inlines
forall a. Monoid a => a
mempty}
                    Blocks -> Blocks
transform <- ParagraphStyle -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *).
PandocMonad m =>
ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform ParagraphStyle
pPr'
                    Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DocxContext m Blocks) -> Blocks -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks -> Blocks
transform (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
paraOrPlain Inlines
ils''
              ReaderOptions
opts <- (DEnv -> ReaderOptions)
-> ReaderT DEnv (StateT DState m) ReaderOptions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks DEnv -> ReaderOptions
docxOptions
              case (ParagraphStyle -> Maybe TrackedChange
pChange ParagraphStyle
pPr', ReaderOptions -> TrackChanges
readerTrackChanges ReaderOptions
opts) of
                  (Maybe TrackedChange, TrackChanges)
_ | Inlines -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
ils'', Bool -> Bool
not (Extension -> ReaderOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_empty_paragraphs ReaderOptions
opts) ->
                    Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
                  (Just (TrackedChange ChangeType
Insertion ChangeInfo
_), TrackChanges
AcceptChanges) ->
                      DocxContext m Blocks
handleInsertion
                  (Just (TrackedChange ChangeType
Insertion ChangeInfo
_), TrackChanges
RejectChanges) -> do
                      (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s {docxPrevPara :: Inlines
docxPrevPara = Inlines
ils''}
                      Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
                  (Just (TrackedChange ChangeType
Insertion (ChangeInfo Text
_ Text
cAuthor Maybe Text
cDate))
                   , TrackChanges
AllChanges) -> do
                      let attr :: Attr
attr = (Text
"", [Text
"paragraph-insertion"], Text -> Maybe Text -> [(Text, Text)]
addAuthorAndDate Text
cAuthor Maybe Text
cDate)
                          insertMark :: Inlines
insertMark = Attr -> Inlines -> Inlines
spanWith Attr
attr Inlines
forall a. Monoid a => a
mempty
                      Blocks -> Blocks
transform <- ParagraphStyle -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *).
PandocMonad m =>
ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform ParagraphStyle
pPr'
                      Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DocxContext m Blocks) -> Blocks -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks -> Blocks
transform (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$
                        Inlines -> Blocks
paraOrPlain (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines
ils'' Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
insertMark
                  (Just (TrackedChange ChangeType
Deletion ChangeInfo
_), TrackChanges
AcceptChanges) -> do
                      (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s {docxPrevPara :: Inlines
docxPrevPara = Inlines
ils''}
                      Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
                  (Just (TrackedChange ChangeType
Deletion ChangeInfo
_), TrackChanges
RejectChanges) ->
                      DocxContext m Blocks
handleInsertion
                  (Just (TrackedChange ChangeType
Deletion (ChangeInfo Text
_ Text
cAuthor Maybe Text
cDate))
                   , TrackChanges
AllChanges) -> do
                      let attr :: Attr
attr = (Text
"", [Text
"paragraph-deletion"], Text -> Maybe Text -> [(Text, Text)]
addAuthorAndDate Text
cAuthor Maybe Text
cDate)
                          insertMark :: Inlines
insertMark = Attr -> Inlines -> Inlines
spanWith Attr
attr Inlines
forall a. Monoid a => a
mempty
                      Blocks -> Blocks
transform <- ParagraphStyle -> DocxContext m (Blocks -> Blocks)
forall (m :: * -> *).
PandocMonad m =>
ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform ParagraphStyle
pPr'
                      Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DocxContext m Blocks) -> Blocks -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks -> Blocks
transform (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$
                        Inlines -> Blocks
paraOrPlain (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines
ils'' Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
insertMark
                  (Maybe TrackedChange, TrackChanges)
_ -> DocxContext m Blocks
handleInsertion
bodyPartToBlocks (ListItem ParagraphStyle
pPr Text
numId Text
lvl (Just Level
levelInfo) [ParPart]
parparts) = do
  -- We check whether this current numId has previously been used,
  -- since Docx expects us to pick up where we left off.
  Map (Text, Text) Integer
listState <- (DState -> Map (Text, Text) Integer)
-> ReaderT DEnv (StateT DState m) (Map (Text, Text) Integer)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DState -> Map (Text, Text) Integer
docxListState
  let startFromState :: Maybe Integer
startFromState = (Text, Text) -> Map (Text, Text) Integer -> Maybe Integer
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text
numId, Text
lvl) Map (Text, Text) Integer
listState
      Level Text
_ Text
fmt Text
txt Maybe Integer
startFromLevelInfo = Level
levelInfo
      start :: Integer
start = case Maybe Integer
startFromState of
        Just Integer
n -> Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1
        Maybe Integer
Nothing -> Integer -> Maybe Integer -> Integer
forall a. a -> Maybe a -> a
fromMaybe Integer
1 Maybe Integer
startFromLevelInfo
      kvs :: [(Text, Text)]
kvs = [ (Text
"level", Text
lvl)
            , (Text
"num-id", Text
numId)
            , (Text
"format", Text
fmt)
            , (Text
"text", Text
txt)
            , (Text
"start", Integer -> Text
forall a. Show a => a -> Text
tshow Integer
start)
            ]
  (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
st -> DState
st{ docxListState :: Map (Text, Text) Integer
docxListState =
    -- expire all the continuation data for lists of level > this one:
    -- a new level 1 list item resets continuation for level 2+
    let notExpired :: (a, Text) -> p -> Bool
notExpired (a
_, Text
lvl') p
_ = Text
lvl' Text -> Text -> Bool
forall a. Ord a => a -> a -> Bool
<= Text
lvl
    in (Text, Text)
-> Integer -> Map (Text, Text) Integer -> Map (Text, Text) Integer
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (Text
numId, Text
lvl) Integer
start (((Text, Text) -> Integer -> Bool)
-> Map (Text, Text) Integer -> Map (Text, Text) Integer
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
M.filterWithKey (Text, Text) -> Integer -> Bool
forall a p. (a, Text) -> p -> Bool
notExpired Map (Text, Text) Integer
listState) }
  Blocks
blks <- BodyPart -> DocxContext m Blocks
forall (m :: * -> *).
PandocMonad m =>
BodyPart -> DocxContext m Blocks
bodyPartToBlocks (ParagraphStyle -> [ParPart] -> BodyPart
Paragraph ParagraphStyle
pPr [ParPart]
parparts)
  Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DocxContext m Blocks) -> Blocks -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
divWith (Text
"", [Text
"list-item"], [(Text, Text)]
kvs) Blocks
blks
bodyPartToBlocks (ListItem ParagraphStyle
pPr Text
_ Text
_ Maybe Level
_ [ParPart]
parparts) =
  let pPr' :: ParagraphStyle
pPr' = ParagraphStyle
pPr {pStyle :: [ParStyle]
pStyle = ParaStyleName -> ParStyle
constructBogusParStyleData ParaStyleName
"list-paragraph"ParStyle -> [ParStyle] -> [ParStyle]
forall a. a -> [a] -> [a]
: ParagraphStyle -> [ParStyle]
pStyle ParagraphStyle
pPr}
  in
    BodyPart -> DocxContext m Blocks
forall (m :: * -> *).
PandocMonad m =>
BodyPart -> DocxContext m Blocks
bodyPartToBlocks (BodyPart -> DocxContext m Blocks)
-> BodyPart -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$ ParagraphStyle -> [ParPart] -> BodyPart
Paragraph ParagraphStyle
pPr' [ParPart]
parparts
bodyPartToBlocks (TblCaption ParagraphStyle
_ [ParPart]
_) =
  Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DocxContext m Blocks) -> Blocks -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
para Inlines
forall a. Monoid a => a
mempty -- collected separately
bodyPartToBlocks (Tbl Text
_ TblGrid
_ TblLook
_ []) =
  Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DocxContext m Blocks) -> Blocks -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
para Inlines
forall a. Monoid a => a
mempty
bodyPartToBlocks (Tbl Text
cap TblGrid
grid TblLook
look [Row]
parts) = do
  [Blocks]
captions <- (DState -> [Blocks]) -> ReaderT DEnv (StateT DState m) [Blocks]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DState -> [Blocks]
docxTableCaptions
  Blocks
fullCaption <- case [Blocks]
captions of
    Blocks
c : [Blocks]
cs -> do
      (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DState
s -> DState
s { docxTableCaptions :: [Blocks]
docxTableCaptions = [Blocks]
cs })
      Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
c
    [] -> Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DocxContext m Blocks) -> Blocks -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$ if Text -> Bool
T.null Text
cap then Blocks
forall a. Monoid a => a
mempty else Inlines -> Blocks
plain (Text -> Inlines
text Text
cap)
  let shortCaption :: Maybe [Inline]
shortCaption = if Text -> Bool
T.null Text
cap then Maybe [Inline]
forall a. Maybe a
Nothing else [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just (Inlines -> [Inline]
forall a. Many a -> [a]
toList (Text -> Inlines
text Text
cap))
      cap' :: Caption
cap' = Maybe [Inline] -> Blocks -> Caption
caption Maybe [Inline]
shortCaption Blocks
fullCaption
      ([Row]
hdr, [Row]
rows) = Bool -> [Row] -> ([Row], [Row])
splitHeaderRows (TblLook -> Bool
firstRowFormatting TblLook
look) [Row]
parts

  let width :: Int
width = Int -> (NonEmpty Int -> Int) -> Maybe (NonEmpty Int) -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 NonEmpty Int -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (Maybe (NonEmpty Int) -> Int) -> Maybe (NonEmpty Int) -> Int
forall a b. (a -> b) -> a -> b
$ [Int] -> Maybe (NonEmpty Int)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty ([Int] -> Maybe (NonEmpty Int)) -> [Int] -> Maybe (NonEmpty Int)
forall a b. (a -> b) -> a -> b
$ (Row -> Int) -> [Row] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Row -> Int
rowLength [Row]
parts
      rowLength :: Docx.Row -> Int
      rowLength :: Row -> Int
rowLength (Docx.Row TblHeader
_ [Cell]
c) = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Cell -> Int) -> [Cell] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Docx.Cell Integer
gridSpan VMerge
_ [BodyPart]
_) -> Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
gridSpan) [Cell]
c)

  [Row]
headerCells <- [Row] -> DocxContext m [Row]
forall (m :: * -> *). PandocMonad m => [Row] -> DocxContext m [Row]
rowsToRows [Row]
hdr
  [Row]
bodyCells <- [Row] -> DocxContext m [Row]
forall (m :: * -> *). PandocMonad m => [Row] -> DocxContext m [Row]
rowsToRows [Row]
rows

      -- Horizontal column alignment goes to the default at the moment. Getting
      -- it might be difficult, since there doesn't seem to be a column entity
      -- in docx.
  let alignments :: [Alignment]
alignments = Int -> Alignment -> [Alignment]
forall a. Int -> a -> [a]
replicate Int
width Alignment
AlignDefault
      totalWidth :: Integer
totalWidth = TblGrid -> Integer
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum TblGrid
grid
      widths :: [ColWidth]
widths = (\Integer
w -> Double -> ColWidth
ColWidth (Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
w Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
totalWidth)) (Integer -> ColWidth) -> TblGrid -> [ColWidth]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TblGrid
grid

  Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DocxContext m Blocks) -> Blocks -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$ Caption
-> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Blocks
table Caption
cap'
                 ([Alignment] -> [ColWidth] -> [ColSpec]
forall a b. [a] -> [b] -> [(a, b)]
zip [Alignment]
alignments [ColWidth]
widths)
                 (Attr -> [Row] -> TableHead
TableHead Attr
nullAttr [Row]
headerCells)
                 [Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
nullAttr RowHeadColumns
0 [] [Row]
bodyCells]
                 (Attr -> [Row] -> TableFoot
TableFoot Attr
nullAttr [])
bodyPartToBlocks (OMathPara [Exp]
e) =
  Blocks -> DocxContext m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DocxContext m Blocks) -> Blocks -> DocxContext m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
para (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
displayMath ([Exp] -> Text
writeTeX [Exp]
e)

-- replace targets with generated anchors.
rewriteLink' :: PandocMonad m => Inline -> DocxContext m Inline
rewriteLink' :: Inline -> DocxContext m Inline
rewriteLink' l :: Inline
l@(Link Attr
attr [Inline]
ils (Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'#',Text
target), Text
title)) = do
  Map Text Text
anchorMap <- (DState -> Map Text Text)
-> ReaderT DEnv (StateT DState m) (Map Text Text)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DState -> Map Text Text
docxAnchorMap
  case Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
target Map Text Text
anchorMap of
    Just Text
newTarget -> do
      (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s{docxAnchorSet :: Set Text
docxAnchorSet = Text -> Set Text -> Set Text
forall a. Ord a => a -> Set a -> Set a
Set.insert Text
newTarget (DState -> Set Text
docxAnchorSet DState
s)}
      Inline -> DocxContext m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return (Inline -> DocxContext m Inline) -> Inline -> DocxContext m Inline
forall a b. (a -> b) -> a -> b
$ Attr -> [Inline] -> (Text, Text) -> Inline
Link Attr
attr [Inline]
ils (Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
newTarget, Text
title)
    Maybe Text
Nothing        -> do
      (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DState -> DState) -> ReaderT DEnv (StateT DState m) ())
-> (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall a b. (a -> b) -> a -> b
$ \DState
s -> DState
s{docxAnchorSet :: Set Text
docxAnchorSet = Text -> Set Text -> Set Text
forall a. Ord a => a -> Set a -> Set a
Set.insert Text
target (DState -> Set Text
docxAnchorSet DState
s)}
      Inline -> DocxContext m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return Inline
l
rewriteLink' Inline
il = Inline -> DocxContext m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return Inline
il

rewriteLinks :: PandocMonad m => [Block] -> DocxContext m [Block]
rewriteLinks :: [Block] -> DocxContext m [Block]
rewriteLinks = (Block -> ReaderT DEnv (StateT DState m) Block)
-> [Block] -> DocxContext m [Block]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((Inline -> ReaderT DEnv (StateT DState m) Inline)
-> Block -> ReaderT DEnv (StateT DState m) Block
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM Inline -> ReaderT DEnv (StateT DState m) Inline
forall (m :: * -> *).
PandocMonad m =>
Inline -> DocxContext m Inline
rewriteLink')

removeOrphanAnchors'' :: PandocMonad m => Inline -> DocxContext m [Inline]
removeOrphanAnchors'' :: Inline -> DocxContext m [Inline]
removeOrphanAnchors'' s :: Inline
s@(Span (Text
ident, [Text]
classes, [(Text, Text)]
_) [Inline]
ils)
  | Text
"anchor" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes = do
      Set Text
anchorSet <- (DState -> Set Text) -> ReaderT DEnv (StateT DState m) (Set Text)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DState -> Set Text
docxAnchorSet
      [Inline] -> DocxContext m [Inline]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Inline] -> DocxContext m [Inline])
-> [Inline] -> DocxContext m [Inline]
forall a b. (a -> b) -> a -> b
$ if Text
ident Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Text
anchorSet
               then [Inline
s]
               else [Inline]
ils
removeOrphanAnchors'' Inline
il = [Inline] -> DocxContext m [Inline]
forall (m :: * -> *) a. Monad m => a -> m a
return [Inline
il]

removeOrphanAnchors' :: PandocMonad m => [Inline] -> DocxContext m [Inline]
removeOrphanAnchors' :: [Inline] -> DocxContext m [Inline]
removeOrphanAnchors' [Inline]
ils = ([[Inline]] -> [Inline])
-> ReaderT DEnv (StateT DState m) [[Inline]]
-> DocxContext m [Inline]
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM [[Inline]] -> [Inline]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (ReaderT DEnv (StateT DState m) [[Inline]]
 -> DocxContext m [Inline])
-> ReaderT DEnv (StateT DState m) [[Inline]]
-> DocxContext m [Inline]
forall a b. (a -> b) -> a -> b
$ (Inline -> DocxContext m [Inline])
-> [Inline] -> ReaderT DEnv (StateT DState m) [[Inline]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> DocxContext m [Inline]
forall (m :: * -> *).
PandocMonad m =>
Inline -> DocxContext m [Inline]
removeOrphanAnchors'' [Inline]
ils

removeOrphanAnchors :: PandocMonad m => [Block] -> DocxContext m [Block]
removeOrphanAnchors :: [Block] -> DocxContext m [Block]
removeOrphanAnchors = (Block -> ReaderT DEnv (StateT DState m) Block)
-> [Block] -> DocxContext m [Block]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (([Inline] -> ReaderT DEnv (StateT DState m) [Inline])
-> Block -> ReaderT DEnv (StateT DState m) Block
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM [Inline] -> ReaderT DEnv (StateT DState m) [Inline]
forall (m :: * -> *).
PandocMonad m =>
[Inline] -> DocxContext m [Inline]
removeOrphanAnchors')

bodyToOutput :: PandocMonad m => Body -> DocxContext m (Meta, [Block])
bodyToOutput :: Body -> DocxContext m (Meta, [Block])
bodyToOutput (Body [BodyPart]
bps) = do
  let ([BodyPart]
metabps, [BodyPart]
blkbps) = [BodyPart] -> ([BodyPart], [BodyPart])
sepBodyParts [BodyPart]
bps
  Meta
meta <- [BodyPart] -> DocxContext m Meta
forall (m :: * -> *).
PandocMonad m =>
[BodyPart] -> DocxContext m Meta
bodyPartsToMeta [BodyPart]
metabps
  [Blocks]
captions <- [Maybe Blocks] -> [Blocks]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Blocks] -> [Blocks])
-> ReaderT DEnv (StateT DState m) [Maybe Blocks]
-> ReaderT DEnv (StateT DState m) [Blocks]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (BodyPart -> ReaderT DEnv (StateT DState m) (Maybe Blocks))
-> [BodyPart] -> ReaderT DEnv (StateT DState m) [Maybe Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM BodyPart -> ReaderT DEnv (StateT DState m) (Maybe Blocks)
forall (m :: * -> *).
PandocMonad m =>
BodyPart -> DocxContext m (Maybe Blocks)
bodyPartToTableCaption [BodyPart]
blkbps
  (DState -> DState) -> ReaderT DEnv (StateT DState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DState
s -> DState
s { docxTableCaptions :: [Blocks]
docxTableCaptions = [Blocks]
captions })
  Blocks
blks <- [Blocks] -> Blocks
smushBlocks ([Blocks] -> Blocks)
-> ReaderT DEnv (StateT DState m) [Blocks]
-> ReaderT DEnv (StateT DState m) Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (BodyPart -> ReaderT DEnv (StateT DState m) Blocks)
-> [BodyPart] -> ReaderT DEnv (StateT DState m) [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM BodyPart -> ReaderT DEnv (StateT DState m) Blocks
forall (m :: * -> *).
PandocMonad m =>
BodyPart -> DocxContext m Blocks
bodyPartToBlocks [BodyPart]
blkbps
  [Block]
blks' <- [Block] -> DocxContext m [Block]
forall (m :: * -> *).
PandocMonad m =>
[Block] -> DocxContext m [Block]
rewriteLinks ([Block] -> DocxContext m [Block])
-> [Block] -> DocxContext m [Block]
forall a b. (a -> b) -> a -> b
$ [Block] -> [Block]
blocksToDefinitions ([Block] -> [Block]) -> [Block] -> [Block]
forall a b. (a -> b) -> a -> b
$ [Block] -> [Block]
blocksToBullets ([Block] -> [Block]) -> [Block] -> [Block]
forall a b. (a -> b) -> a -> b
$ Blocks -> [Block]
forall a. Many a -> [a]
toList Blocks
blks
  [Block]
blks'' <- [Block] -> DocxContext m [Block]
forall (m :: * -> *).
PandocMonad m =>
[Block] -> DocxContext m [Block]
removeOrphanAnchors [Block]
blks'
  (Meta, [Block]) -> DocxContext m (Meta, [Block])
forall (m :: * -> *) a. Monad m => a -> m a
return (Meta
meta, [Block]
blks'')

docxToOutput :: PandocMonad m
             => ReaderOptions
             -> Docx
             -> m (Meta, [Block])
docxToOutput :: ReaderOptions -> Docx -> m (Meta, [Block])
docxToOutput ReaderOptions
opts (Docx (Document Map Text Text
_ Body
body)) =
  let dEnv :: DEnv
dEnv   = DEnv
forall a. Default a => a
def { docxOptions :: ReaderOptions
docxOptions  = ReaderOptions
opts} in
   DocxContext m (Meta, [Block])
-> DEnv -> DState -> m (Meta, [Block])
forall (m :: * -> *) a.
PandocMonad m =>
DocxContext m a -> DEnv -> DState -> m a
evalDocxContext (Body -> DocxContext m (Meta, [Block])
forall (m :: * -> *).
PandocMonad m =>
Body -> DocxContext m (Meta, [Block])
bodyToOutput Body
body) DEnv
dEnv DState
forall a. Default a => a
def

addAuthorAndDate :: T.Text -> Maybe T.Text -> [(T.Text, T.Text)]
addAuthorAndDate :: Text -> Maybe Text -> [(Text, Text)]
addAuthorAndDate Text
author Maybe Text
mdate =
  (Text
"author", Text
author) (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: [(Text, Text)]
-> (Text -> [(Text, Text)]) -> Maybe Text -> [(Text, Text)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
date -> [(Text
"date", Text
date)]) Maybe Text
mdate