{-# LANGUAGE PatternGuards       #-}
{-# LANGUAGE RankNTypes          #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns        #-}
{-# LANGUAGE FlexibleContexts    #-}
{-# LANGUAGE LambdaCase          #-}
{-# LANGUAGE OverloadedStrings   #-}
{- |
   Module      : Text.Pandoc.Writers.Docx
   Copyright   : Copyright (C) 2012-2021 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable

Conversion of 'Pandoc' documents to docx.
-}
module Text.Pandoc.Writers.Docx ( writeDocx ) where
import Codec.Archive.Zip
import Control.Applicative ((<|>))
import Control.Monad.Except (catchError, throwError)
import Control.Monad.Reader
import Control.Monad.State.Strict
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import Data.Char (isSpace, isLetter)
import Data.List (intercalate, isPrefixOf, isSuffixOf)
import Data.String (fromString)
import qualified Data.Map as M
import Data.Maybe (fromMaybe, isNothing, mapMaybe, maybeToList)
import qualified Data.Set as Set
import qualified Data.Text as T
import Data.Text (Text)
import qualified Data.Text.Lazy as TL
import Data.Time.Clock.POSIX
import Data.Digest.Pure.SHA (sha1, showDigest)
import Skylighting
import Text.Pandoc.BCP47 (getLang, renderLang)
import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang)
import qualified Text.Pandoc.Class.PandocMonad as P
import Data.Time
import Text.Pandoc.UTF8 (fromTextLazy)
import Text.Pandoc.Definition
import Text.Pandoc.Generic
import Text.Pandoc.Highlighting (highlight)
import Text.Pandoc.Error
import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
import Text.Pandoc.MIME (MimeType, extensionFromMimeType, getMimeType,
                         getMimeTypeDef)
import Text.Pandoc.Options
import Text.Pandoc.Writers.Docx.StyleMap
import Text.Pandoc.Shared
import Text.Pandoc.Walk
import Text.Pandoc.Writers.Math
import Text.Pandoc.Writers.Shared
import Text.Printf (printf)
import Text.TeXMath
import Text.Pandoc.Writers.OOXML
import Text.Pandoc.XML.Light as XML
import Data.Generics (mkT, everywhere)

data ListMarker = NoMarker
                | BulletMarker
                | NumberMarker ListNumberStyle ListNumberDelim Int
                deriving (Int -> ListMarker -> ShowS
[ListMarker] -> ShowS
ListMarker -> String
(Int -> ListMarker -> ShowS)
-> (ListMarker -> String)
-> ([ListMarker] -> ShowS)
-> Show ListMarker
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListMarker] -> ShowS
$cshowList :: [ListMarker] -> ShowS
show :: ListMarker -> String
$cshow :: ListMarker -> String
showsPrec :: Int -> ListMarker -> ShowS
$cshowsPrec :: Int -> ListMarker -> ShowS
Show, ReadPrec [ListMarker]
ReadPrec ListMarker
Int -> ReadS ListMarker
ReadS [ListMarker]
(Int -> ReadS ListMarker)
-> ReadS [ListMarker]
-> ReadPrec ListMarker
-> ReadPrec [ListMarker]
-> Read ListMarker
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListMarker]
$creadListPrec :: ReadPrec [ListMarker]
readPrec :: ReadPrec ListMarker
$creadPrec :: ReadPrec ListMarker
readList :: ReadS [ListMarker]
$creadList :: ReadS [ListMarker]
readsPrec :: Int -> ReadS ListMarker
$creadsPrec :: Int -> ReadS ListMarker
Read, ListMarker -> ListMarker -> Bool
(ListMarker -> ListMarker -> Bool)
-> (ListMarker -> ListMarker -> Bool) -> Eq ListMarker
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListMarker -> ListMarker -> Bool
$c/= :: ListMarker -> ListMarker -> Bool
== :: ListMarker -> ListMarker -> Bool
$c== :: ListMarker -> ListMarker -> Bool
Eq, Eq ListMarker
Eq ListMarker
-> (ListMarker -> ListMarker -> Ordering)
-> (ListMarker -> ListMarker -> Bool)
-> (ListMarker -> ListMarker -> Bool)
-> (ListMarker -> ListMarker -> Bool)
-> (ListMarker -> ListMarker -> Bool)
-> (ListMarker -> ListMarker -> ListMarker)
-> (ListMarker -> ListMarker -> ListMarker)
-> Ord ListMarker
ListMarker -> ListMarker -> Bool
ListMarker -> ListMarker -> Ordering
ListMarker -> ListMarker -> ListMarker
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ListMarker -> ListMarker -> ListMarker
$cmin :: ListMarker -> ListMarker -> ListMarker
max :: ListMarker -> ListMarker -> ListMarker
$cmax :: ListMarker -> ListMarker -> ListMarker
>= :: ListMarker -> ListMarker -> Bool
$c>= :: ListMarker -> ListMarker -> Bool
> :: ListMarker -> ListMarker -> Bool
$c> :: ListMarker -> ListMarker -> Bool
<= :: ListMarker -> ListMarker -> Bool
$c<= :: ListMarker -> ListMarker -> Bool
< :: ListMarker -> ListMarker -> Bool
$c< :: ListMarker -> ListMarker -> Bool
compare :: ListMarker -> ListMarker -> Ordering
$ccompare :: ListMarker -> ListMarker -> Ordering
$cp1Ord :: Eq ListMarker
Ord)

listMarkerToId :: ListMarker -> Text
listMarkerToId :: ListMarker -> Text
listMarkerToId ListMarker
NoMarker = Text
"990"
listMarkerToId ListMarker
BulletMarker = Text
"991"
listMarkerToId (NumberMarker ListNumberStyle
sty ListNumberDelim
delim Int
n) = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
  Char
'9' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
'9' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
styNum Char -> ShowS
forall a. a -> [a] -> [a]
: Char
delimNum Char -> ShowS
forall a. a -> [a] -> [a]
: Int -> String
forall a. Show a => a -> String
show Int
n
  where styNum :: Char
styNum = case ListNumberStyle
sty of
                      ListNumberStyle
DefaultStyle -> Char
'2'
                      ListNumberStyle
Example      -> Char
'3'
                      ListNumberStyle
Decimal      -> Char
'4'
                      ListNumberStyle
LowerRoman   -> Char
'5'
                      ListNumberStyle
UpperRoman   -> Char
'6'
                      ListNumberStyle
LowerAlpha   -> Char
'7'
                      ListNumberStyle
UpperAlpha   -> Char
'8'
        delimNum :: Char
delimNum = case ListNumberDelim
delim of
                      ListNumberDelim
DefaultDelim -> Char
'0'
                      ListNumberDelim
Period       -> Char
'1'
                      ListNumberDelim
OneParen     -> Char
'2'
                      ListNumberDelim
TwoParens    -> Char
'3'

data EnvProps = EnvProps{ EnvProps -> Maybe Element
styleElement  :: Maybe Element
                        , EnvProps -> [Element]
otherElements :: [Element]
                        }

instance Semigroup EnvProps where
  EnvProps Maybe Element
s [Element]
es <> :: EnvProps -> EnvProps -> EnvProps
<> EnvProps Maybe Element
s' [Element]
es' = Maybe Element -> [Element] -> EnvProps
EnvProps (Maybe Element
s Maybe Element -> Maybe Element -> Maybe Element
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Element
s') ([Element]
es [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ [Element]
es')

instance Monoid EnvProps where
  mempty :: EnvProps
mempty = Maybe Element -> [Element] -> EnvProps
EnvProps Maybe Element
forall a. Maybe a
Nothing []
  mappend :: EnvProps -> EnvProps -> EnvProps
mappend = EnvProps -> EnvProps -> EnvProps
forall a. Semigroup a => a -> a -> a
(<>)

squashProps :: EnvProps -> [Element]
squashProps :: EnvProps -> [Element]
squashProps (EnvProps Maybe Element
Nothing [Element]
es) = [Element]
es
squashProps (EnvProps (Just Element
e) [Element]
es) = Element
e Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: [Element]
es

data WriterEnv = WriterEnv{ WriterEnv -> EnvProps
envTextProperties :: EnvProps
                          , WriterEnv -> EnvProps
envParaProperties :: EnvProps
                          , WriterEnv -> Bool
envRTL            :: Bool
                          , WriterEnv -> Int
envListLevel      :: Int
                          , WriterEnv -> Int
envListNumId      :: Int
                          , WriterEnv -> Bool
envInDel          :: Bool
                          , WriterEnv -> Text
envChangesAuthor  :: Text
                          , WriterEnv -> Text
envChangesDate    :: Text
                          , WriterEnv -> Integer
envPrintWidth     :: Integer
                          }

defaultWriterEnv :: WriterEnv
defaultWriterEnv :: WriterEnv
defaultWriterEnv = WriterEnv :: EnvProps
-> EnvProps
-> Bool
-> Int
-> Int
-> Bool
-> Text
-> Text
-> Integer
-> WriterEnv
WriterEnv{ envTextProperties :: EnvProps
envTextProperties = EnvProps
forall a. Monoid a => a
mempty
                            , envParaProperties :: EnvProps
envParaProperties = EnvProps
forall a. Monoid a => a
mempty
                            , envRTL :: Bool
envRTL = Bool
False
                            , envListLevel :: Int
envListLevel = -Int
1
                            , envListNumId :: Int
envListNumId = Int
1
                            , envInDel :: Bool
envInDel = Bool
False
                            , envChangesAuthor :: Text
envChangesAuthor  = Text
"unknown"
                            , envChangesDate :: Text
envChangesDate    = Text
"1969-12-31T19:00:00Z"
                            , envPrintWidth :: Integer
envPrintWidth     = Integer
1
                            }

data WriterState = WriterState{
         WriterState -> [Element]
stFootnotes      :: [Element]
       , WriterState -> [([(Text, Text)], [Inline])]
stComments       :: [([(Text, Text)], [Inline])]
       , WriterState -> Set Text
stSectionIds     :: Set.Set Text
       , WriterState -> Map Text Text
stExternalLinks  :: M.Map Text Text
       , WriterState -> Map String (String, String, Maybe Text, ByteString)
stImages         :: M.Map FilePath (String, String, Maybe MimeType, B.ByteString)
       , WriterState -> [ListMarker]
stLists          :: [ListMarker]
       , WriterState -> Int
stInsId          :: Int
       , WriterState -> Int
stDelId          :: Int
       , WriterState -> StyleMaps
stStyleMaps      :: StyleMaps
       , WriterState -> Bool
stFirstPara      :: Bool
       , WriterState -> Bool
stInTable        :: Bool
       , WriterState -> Bool
stInList         :: Bool
       , WriterState -> [Inline]
stTocTitle       :: [Inline]
       , WriterState -> Set ParaStyleName
stDynamicParaProps :: Set.Set ParaStyleName
       , WriterState -> Set CharStyleName
stDynamicTextProps :: Set.Set CharStyleName
       , WriterState -> Int
stCurId          :: Int
       }

defaultWriterState :: WriterState
defaultWriterState :: WriterState
defaultWriterState = WriterState :: [Element]
-> [([(Text, Text)], [Inline])]
-> Set Text
-> Map Text Text
-> Map String (String, String, Maybe Text, ByteString)
-> [ListMarker]
-> Int
-> Int
-> StyleMaps
-> Bool
-> Bool
-> Bool
-> [Inline]
-> Set ParaStyleName
-> Set CharStyleName
-> Int
-> WriterState
WriterState{
        stFootnotes :: [Element]
stFootnotes      = [Element]
defaultFootnotes
      , stComments :: [([(Text, Text)], [Inline])]
stComments       = []
      , stSectionIds :: Set Text
stSectionIds     = Set Text
forall a. Set a
Set.empty
      , stExternalLinks :: Map Text Text
stExternalLinks  = Map Text Text
forall k a. Map k a
M.empty
      , stImages :: Map String (String, String, Maybe Text, ByteString)
stImages         = Map String (String, String, Maybe Text, ByteString)
forall k a. Map k a
M.empty
      , stLists :: [ListMarker]
stLists          = [ListMarker
NoMarker]
      , stInsId :: Int
stInsId          = Int
1
      , stDelId :: Int
stDelId          = Int
1
      , stStyleMaps :: StyleMaps
stStyleMaps      = CharStyleNameMap -> ParaStyleNameMap -> StyleMaps
StyleMaps CharStyleNameMap
forall k a. Map k a
M.empty ParaStyleNameMap
forall k a. Map k a
M.empty
      , stFirstPara :: Bool
stFirstPara      = Bool
False
      , stInTable :: Bool
stInTable        = Bool
False
      , stInList :: Bool
stInList         = Bool
False
      , stTocTitle :: [Inline]
stTocTitle       = [Text -> Inline
Str Text
"Table of Contents"]
      , stDynamicParaProps :: Set ParaStyleName
stDynamicParaProps = Set ParaStyleName
forall a. Set a
Set.empty
      , stDynamicTextProps :: Set CharStyleName
stDynamicTextProps = Set CharStyleName
forall a. Set a
Set.empty
      , stCurId :: Int
stCurId          = Int
20
      }

type WS m = ReaderT WriterEnv (StateT WriterState m)

renumIdMap :: Int -> [Element] -> M.Map Text Text
renumIdMap :: Int -> [Element] -> Map Text Text
renumIdMap Int
_ [] = Map Text Text
forall k a. Map k a
M.empty
renumIdMap Int
n (Element
e:[Element]
es)
  | Just Text
oldId <- QName -> Element -> Maybe Text
findAttr (Text -> Maybe Text -> Maybe Text -> QName
QName Text
"Id" Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing) Element
e =
      Text -> Text -> Map Text Text -> Map Text Text
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
oldId (Text
"rId" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
n) (Int -> [Element] -> Map Text Text
renumIdMap (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) [Element]
es)
  | Bool
otherwise = Int -> [Element] -> Map Text Text
renumIdMap Int
n [Element]
es

replaceAttr :: (QName -> Bool) -> Text -> [XML.Attr] -> [XML.Attr]
replaceAttr :: (QName -> Bool) -> Text -> [Attr] -> [Attr]
replaceAttr QName -> Bool
f Text
val = (Attr -> Attr) -> [Attr] -> [Attr]
forall a b. (a -> b) -> [a] -> [b]
map ((Attr -> Attr) -> [Attr] -> [Attr])
-> (Attr -> Attr) -> [Attr] -> [Attr]
forall a b. (a -> b) -> a -> b
$
    \Attr
a -> if QName -> Bool
f (Attr -> QName
attrKey Attr
a) then QName -> Text -> Attr
XML.Attr (Attr -> QName
attrKey Attr
a) Text
val else Attr
a

renumId :: (QName -> Bool) -> M.Map Text Text -> Element -> Element
renumId :: (QName -> Bool) -> Map Text Text -> Element -> Element
renumId QName -> Bool
f Map Text Text
renumMap Element
e
  | Just Text
oldId <- (QName -> Bool) -> Element -> Maybe Text
findAttrBy QName -> Bool
f Element
e
  , Just Text
newId <- Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
oldId Map Text Text
renumMap =
    let attrs' :: [Attr]
attrs' = (QName -> Bool) -> Text -> [Attr] -> [Attr]
replaceAttr QName -> Bool
f Text
newId (Element -> [Attr]
elAttribs Element
e)
    in
     Element
e { elAttribs :: [Attr]
elAttribs = [Attr]
attrs' }
  | Bool
otherwise = Element
e

renumIds :: (QName -> Bool) -> M.Map Text Text -> [Element] -> [Element]
renumIds :: (QName -> Bool) -> Map Text Text -> [Element] -> [Element]
renumIds QName -> Bool
f Map Text Text
renumMap = (Element -> Element) -> [Element] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map ((QName -> Bool) -> Map Text Text -> Element -> Element
renumId QName -> Bool
f Map Text Text
renumMap)

-- | Certain characters are invalid in XML even if escaped.
-- See #1992
stripInvalidChars :: Text -> Text
stripInvalidChars :: Text -> Text
stripInvalidChars = (Char -> Bool) -> Text -> Text
T.filter Char -> Bool
isValidChar

-- | See XML reference
isValidChar :: Char -> Bool
isValidChar :: Char -> Bool
isValidChar Char
'\t' = Bool
True
isValidChar Char
'\n' = Bool
True
isValidChar Char
'\r' = Bool
True
isValidChar Char
'\xFFFE' = Bool
False
isValidChar Char
'\xFFFF' = Bool
False
isValidChar Char
c = (Char
' ' Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\xD7FF') Bool -> Bool -> Bool
|| (Char
'\xE000' Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
c)

writeDocx :: (PandocMonad m)
          => WriterOptions  -- ^ Writer options
          -> Pandoc         -- ^ Document to convert
          -> m BL.ByteString
writeDocx :: WriterOptions -> Pandoc -> m ByteString
writeDocx WriterOptions
opts Pandoc
doc = do
  let Pandoc Meta
meta [Block]
blocks = (Block -> Block) -> Pandoc -> Pandoc
forall a b. Walkable a b => (a -> a) -> b -> b
walk Block -> Block
fixDisplayMath Pandoc
doc
  let blocks' :: [Block]
blocks' = Bool -> Maybe Int -> [Block] -> [Block]
makeSections Bool
True Maybe Int
forall a. Maybe a
Nothing [Block]
blocks
  let doc' :: Pandoc
doc' = Meta -> [Block] -> Pandoc
Pandoc Meta
meta [Block]
blocks'

  Maybe Text
username <- Text -> m (Maybe Text)
forall (m :: * -> *). PandocMonad m => Text -> m (Maybe Text)
P.lookupEnv Text
"USERNAME"
  UTCTime
utctime <- m UTCTime
forall (m :: * -> *). PandocMonad m => m UTCTime
P.getTimestamp
  Maybe String
oldUserDataDir <- m (Maybe String)
forall (m :: * -> *). PandocMonad m => m (Maybe String)
P.getUserDataDir
  Maybe String -> m ()
forall (m :: * -> *). PandocMonad m => Maybe String -> m ()
P.setUserDataDir Maybe String
forall a. Maybe a
Nothing
  ByteString
res <- String -> m ByteString
forall (m :: * -> *). PandocMonad m => String -> m ByteString
P.readDefaultDataFile String
"reference.docx"
  Maybe String -> m ()
forall (m :: * -> *). PandocMonad m => Maybe String -> m ()
P.setUserDataDir Maybe String
oldUserDataDir
  let distArchive :: Archive
distArchive = ByteString -> Archive
toArchive (ByteString -> Archive) -> ByteString -> Archive
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
BL.fromStrict ByteString
res
  Archive
refArchive <- case WriterOptions -> Maybe String
writerReferenceDoc WriterOptions
opts of
                     Just String
f  -> ByteString -> Archive
toArchive (ByteString -> Archive) -> m ByteString -> m Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> m ByteString
forall (m :: * -> *). PandocMonad m => String -> m ByteString
P.readFileLazy String
f
                     Maybe String
Nothing -> ByteString -> Archive
toArchive (ByteString -> Archive)
-> (ByteString -> ByteString) -> ByteString -> Archive
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.fromStrict (ByteString -> Archive) -> m ByteString -> m Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                        String -> m ByteString
forall (m :: * -> *). PandocMonad m => String -> m ByteString
P.readDataFile String
"reference.docx"

  Element
parsedDoc <- Archive -> Archive -> String -> m Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> String -> m Element
parseXml Archive
refArchive Archive
distArchive String
"word/document.xml"
  let wname :: (Text -> Bool) -> QName -> Bool
wname Text -> Bool
f QName
qn = QName -> Maybe Text
qPrefix QName
qn Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"w" Bool -> Bool -> Bool
&& Text -> Bool
f (QName -> Text
qName QName
qn)
  let mbsectpr :: Maybe Element
mbsectpr = (QName -> Bool) -> Element -> Maybe Element
filterElementName ((Text -> Bool) -> QName -> Bool
wname (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"sectPr")) Element
parsedDoc

  -- Gets the template size
  let mbpgsz :: Maybe Element
mbpgsz = Maybe Element
mbsectpr Maybe Element -> (Element -> Maybe Element) -> Maybe Element
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (QName -> Bool) -> Element -> Maybe Element
filterElementName ((Text -> Bool) -> QName -> Bool
wname (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"pgSz"))
  let mbAttrSzWidth :: Maybe Text
mbAttrSzWidth = Maybe Element
mbpgsz Maybe Element -> (Element -> Maybe Text) -> Maybe Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (QName -> Bool) -> [Attr] -> Maybe Text
lookupAttrBy ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"w") (Text -> Bool) -> (QName -> Text) -> QName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QName -> Text
qName) ([Attr] -> Maybe Text)
-> (Element -> [Attr]) -> Element -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> [Attr]
elAttribs

  let mbpgmar :: Maybe Element
mbpgmar = Maybe Element
mbsectpr Maybe Element -> (Element -> Maybe Element) -> Maybe Element
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (QName -> Bool) -> Element -> Maybe Element
filterElementName ((Text -> Bool) -> QName -> Bool
wname (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"pgMar"))
  let mbAttrMarLeft :: Maybe Text
mbAttrMarLeft = Maybe Element
mbpgmar Maybe Element -> (Element -> Maybe Text) -> Maybe Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (QName -> Bool) -> [Attr] -> Maybe Text
lookupAttrBy ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"left") (Text -> Bool) -> (QName -> Text) -> QName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QName -> Text
qName) ([Attr] -> Maybe Text)
-> (Element -> [Attr]) -> Element -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> [Attr]
elAttribs
  let mbAttrMarRight :: Maybe Text
mbAttrMarRight = Maybe Element
mbpgmar Maybe Element -> (Element -> Maybe Text) -> Maybe Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (QName -> Bool) -> [Attr] -> Maybe Text
lookupAttrBy ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"right") (Text -> Bool) -> (QName -> Text) -> QName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QName -> Text
qName) ([Attr] -> Maybe Text)
-> (Element -> [Attr]) -> Element -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> [Attr]
elAttribs

  -- Get the available area (converting the size and the margins to int and
  -- doing the difference
  let pgContentWidth :: Maybe Integer
pgContentWidth = do
                         Integer
w <- Maybe Text
mbAttrSzWidth Maybe Text -> (Text -> Maybe Integer) -> Maybe Integer
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Integer
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead
                         Integer
r <- Maybe Text
mbAttrMarRight Maybe Text -> (Text -> Maybe Integer) -> Maybe Integer
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Integer
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead
                         Integer
l <- Maybe Text
mbAttrMarLeft Maybe Text -> (Text -> Maybe Integer) -> Maybe Integer
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Integer
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead
                         Integer -> Maybe Integer
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer -> Maybe Integer) -> Integer -> Maybe Integer
forall a b. (a -> b) -> a -> b
$ Integer
w Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
r Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
l

  -- styles
  Maybe Lang
mblang <- Maybe Text -> m (Maybe Lang)
forall (m :: * -> *). PandocMonad m => Maybe Text -> m (Maybe Lang)
toLang (Maybe Text -> m (Maybe Lang)) -> Maybe Text -> m (Maybe Lang)
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Meta -> Maybe Text
getLang WriterOptions
opts Meta
meta
  -- TODO FIXME avoid this generic traversal!
  -- lang is in w:docDefaults /  w:rPr  /  w:lang
  let addLang :: Element -> Element
      addLang :: Element -> Element
addLang = case Maybe Lang
mblang of
                  Maybe Lang
Nothing -> Element -> Element
forall a. a -> a
id
                  Just Lang
l  -> (forall a. Data a => a -> a) -> forall a. Data a => a -> a
everywhere ((Element -> Element) -> a -> a
forall a b. (Typeable a, Typeable b) => (b -> b) -> a -> a
mkT (Text -> Element -> Element
go (Lang -> Text
renderLang Lang
l)))
        where
          go :: Text -> Element -> Element
          go :: Text -> Element -> Element
go Text
l Element
e'
            | QName -> Text
qName (Element -> QName
elName Element
e') Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"lang"
                = Element
e'{ elAttribs :: [Attr]
elAttribs = (Attr -> Attr) -> [Attr] -> [Attr]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Attr -> Attr
setvalattr Text
l) ([Attr] -> [Attr]) -> [Attr] -> [Attr]
forall a b. (a -> b) -> a -> b
$ Element -> [Attr]
elAttribs Element
e' }
            | Bool
otherwise = Element
e'

          setvalattr :: Text -> Attr -> Attr
setvalattr Text
l (XML.Attr qn :: QName
qn@(QName Text
"val" Maybe Text
_ Maybe Text
_) Text
_) = QName -> Text -> Attr
XML.Attr QName
qn Text
l
          setvalattr Text
_ Attr
x                                 = Attr
x

  let stylepath :: String
stylepath = String
"word/styles.xml"
  Element
styledoc <- Element -> Element
addLang (Element -> Element) -> m Element -> m Element
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Archive -> Archive -> String -> m Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> String -> m Element
parseXml Archive
refArchive Archive
distArchive String
stylepath

  -- parse styledoc for heading styles
  let styleMaps :: StyleMaps
styleMaps = Archive -> StyleMaps
getStyleMaps Archive
refArchive

  let tocTitle :: [Inline]
tocTitle = case Text -> Meta -> [Inline]
lookupMetaInlines Text
"toc-title" Meta
meta of
                   [] -> WriterState -> [Inline]
stTocTitle WriterState
defaultWriterState
                   [Inline]
ls -> [Inline]
ls

  let initialSt :: WriterState
initialSt = WriterState
defaultWriterState {
          stStyleMaps :: StyleMaps
stStyleMaps  = StyleMaps
styleMaps
        , stTocTitle :: [Inline]
stTocTitle   = [Inline]
tocTitle
        }

  let isRTLmeta :: Bool
isRTLmeta = case Text -> Meta -> Maybe MetaValue
lookupMeta Text
"dir" Meta
meta of
        Just (MetaString Text
"rtl")        -> Bool
True
        Just (MetaInlines [Str Text
"rtl"]) -> Bool
True
        Maybe MetaValue
_                              -> Bool
False

  let env :: WriterEnv
env = WriterEnv
defaultWriterEnv {
          envRTL :: Bool
envRTL = Bool
isRTLmeta
        , envChangesAuthor :: Text
envChangesAuthor = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"unknown" Maybe Text
username
        , envChangesDate :: Text
envChangesDate   = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ TimeLocale -> String -> UTCTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%FT%XZ" UTCTime
utctime
        , envPrintWidth :: Integer
envPrintWidth = Integer -> (Integer -> Integer) -> Maybe Integer -> Integer
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Integer
420 (Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot` Integer
20) Maybe Integer
pgContentWidth
        }


  (([Content]
contents, [Element]
footnotes, [Element]
comments), WriterState
st) <- StateT WriterState m ([Content], [Element], [Element])
-> WriterState
-> m (([Content], [Element], [Element]), WriterState)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT
                         (ReaderT
  WriterEnv (StateT WriterState m) ([Content], [Element], [Element])
-> WriterEnv
-> StateT WriterState m ([Content], [Element], [Element])
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT
                          (WriterOptions
-> Pandoc
-> ReaderT
     WriterEnv (StateT WriterState m) ([Content], [Element], [Element])
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Pandoc -> WS m ([Content], [Element], [Element])
writeOpenXML WriterOptions
opts{writerWrapText :: WrapOption
writerWrapText = WrapOption
WrapNone} Pandoc
doc')
                          WriterEnv
env)
                         WriterState
initialSt
  let epochtime :: Integer
epochtime = POSIXTime -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor (POSIXTime -> Integer) -> POSIXTime -> Integer
forall a b. (a -> b) -> a -> b
$ UTCTime -> POSIXTime
utcTimeToPOSIXSeconds UTCTime
utctime
  let imgs :: [(String, String, Maybe Text, ByteString)]
imgs = Map String (String, String, Maybe Text, ByteString)
-> [(String, String, Maybe Text, ByteString)]
forall k a. Map k a -> [a]
M.elems (Map String (String, String, Maybe Text, ByteString)
 -> [(String, String, Maybe Text, ByteString)])
-> Map String (String, String, Maybe Text, ByteString)
-> [(String, String, Maybe Text, ByteString)]
forall a b. (a -> b) -> a -> b
$ WriterState -> Map String (String, String, Maybe Text, ByteString)
stImages WriterState
st

  -- create entries for images in word/media/...
  let toImageEntry :: (a, String, c, ByteString) -> Entry
toImageEntry (a
_,String
path,c
_,ByteString
img) = String -> Integer -> ByteString -> Entry
toEntry (String
"word/" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
path) Integer
epochtime (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
toLazy ByteString
img
  let imageEntries :: [Entry]
imageEntries = ((String, String, Maybe Text, ByteString) -> Entry)
-> [(String, String, Maybe Text, ByteString)] -> [Entry]
forall a b. (a -> b) -> [a] -> [b]
map (String, String, Maybe Text, ByteString) -> Entry
forall a c. (a, String, c, ByteString) -> Entry
toImageEntry [(String, String, Maybe Text, ByteString)]
imgs

  let stdAttributes :: [(Text, Text)]
stdAttributes =
            [(Text
"xmlns:w",Text
"http://schemas.openxmlformats.org/wordprocessingml/2006/main")
            ,(Text
"xmlns:m",Text
"http://schemas.openxmlformats.org/officeDocument/2006/math")
            ,(Text
"xmlns:r",Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships")
            ,(Text
"xmlns:o",Text
"urn:schemas-microsoft-com:office:office")
            ,(Text
"xmlns:v",Text
"urn:schemas-microsoft-com:vml")
            ,(Text
"xmlns:w10",Text
"urn:schemas-microsoft-com:office:word")
            ,(Text
"xmlns:a",Text
"http://schemas.openxmlformats.org/drawingml/2006/main")
            ,(Text
"xmlns:pic",Text
"http://schemas.openxmlformats.org/drawingml/2006/picture")
            ,(Text
"xmlns:wp",Text
"http://schemas.openxmlformats.org/drawingml/2006/wordprocessingDrawing")]


  Element
parsedRels <- Archive -> Archive -> String -> m Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> String -> m Element
parseXml Archive
refArchive Archive
distArchive String
"word/_rels/document.xml.rels"
  let isHeaderNode :: Element -> Bool
isHeaderNode Element
e = QName -> Element -> Maybe Text
findAttr (Text -> Maybe Text -> Maybe Text -> QName
QName Text
"Type" Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing) Element
e Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/header"
  let isFooterNode :: Element -> Bool
isFooterNode Element
e = QName -> Element -> Maybe Text
findAttr (Text -> Maybe Text -> Maybe Text -> QName
QName Text
"Type" Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing) Element
e Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/footer"
  let headers :: [Element]
headers = (Element -> Bool) -> Element -> [Element]
filterElements Element -> Bool
isHeaderNode Element
parsedRels
  let footers :: [Element]
footers = (Element -> Bool) -> Element -> [Element]
filterElements Element -> Bool
isFooterNode Element
parsedRels

  let extractTarget :: Element -> Maybe Text
extractTarget = QName -> Element -> Maybe Text
findAttr (Text -> Maybe Text -> Maybe Text -> QName
QName Text
"Target" Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing)

  -- we create [Content_Types].xml and word/_rels/document.xml.rels
  -- from scratch rather than reading from reference.docx,
  -- because Word sometimes changes these files when a reference.docx is modified,
  -- e.g. deleting the reference to footnotes.xml or removing default entries
  -- for image content types.

  -- [Content_Types].xml
  let mkOverrideNode :: (String, Text) -> Element
mkOverrideNode (String
part', Text
contentType') = Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Override"
               [(Text
"PartName", String -> Text
T.pack String
part')
               ,(Text
"ContentType", Text
contentType')] ()
  let mkImageOverride :: (a, String, Maybe Text, d) -> Element
mkImageOverride (a
_, String
imgpath, Maybe Text
mbMimeType, d
_) =
          (String, Text) -> Element
mkOverrideNode (String
"/word/" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
imgpath,
                          Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"application/octet-stream" Maybe Text
mbMimeType)
  let mkMediaOverride :: String -> Element
mkMediaOverride String
imgpath =
          (String, Text) -> Element
mkOverrideNode (String
"/" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
imgpath, String -> Text
getMimeTypeDef String
imgpath)
  let overrides :: [Element]
overrides = ((String, Text) -> Element) -> [(String, Text)] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map (String, Text) -> Element
mkOverrideNode (
                  [(String
"/word/webSettings.xml",
                    Text
"application/vnd.openxmlformats-officedocument.wordprocessingml.webSettings+xml")
                  ,(String
"/word/numbering.xml",
                    Text
"application/vnd.openxmlformats-officedocument.wordprocessingml.numbering+xml")
                  ,(String
"/word/settings.xml",
                    Text
"application/vnd.openxmlformats-officedocument.wordprocessingml.settings+xml")
                  ,(String
"/word/theme/theme1.xml",
                    Text
"application/vnd.openxmlformats-officedocument.theme+xml")
                  ,(String
"/word/fontTable.xml",
                    Text
"application/vnd.openxmlformats-officedocument.wordprocessingml.fontTable+xml")
                  ,(String
"/docProps/app.xml",
                    Text
"application/vnd.openxmlformats-officedocument.extended-properties+xml")
                  ,(String
"/docProps/core.xml",
                    Text
"application/vnd.openxmlformats-package.core-properties+xml")
                  ,(String
"/docProps/custom.xml",
                    Text
"application/vnd.openxmlformats-officedocument.custom-properties+xml")
                  ,(String
"/word/styles.xml",
                    Text
"application/vnd.openxmlformats-officedocument.wordprocessingml.styles+xml")
                  ,(String
"/word/document.xml",
                    Text
"application/vnd.openxmlformats-officedocument.wordprocessingml.document.main+xml")
                  ,(String
"/word/comments.xml",
                    Text
"application/vnd.openxmlformats-officedocument.wordprocessingml.comments+xml")
                  ,(String
"/word/footnotes.xml",
                    Text
"application/vnd.openxmlformats-officedocument.wordprocessingml.footnotes+xml")
                  ] [(String, Text)] -> [(String, Text)] -> [(String, Text)]
forall a. [a] -> [a] -> [a]
++
                  (Element -> (String, Text)) -> [Element] -> [(String, Text)]
forall a b. (a -> b) -> [a] -> [b]
map (\Element
x -> (String -> (Text -> String) -> Maybe Text -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" (Text -> String
T.unpack (Text -> String) -> (Text -> Text) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
"/word/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>)) (Element -> Maybe Text
extractTarget Element
x),
                       Text
"application/vnd.openxmlformats-officedocument.wordprocessingml.header+xml")) [Element]
headers [(String, Text)] -> [(String, Text)] -> [(String, Text)]
forall a. [a] -> [a] -> [a]
++
                  (Element -> (String, Text)) -> [Element] -> [(String, Text)]
forall a b. (a -> b) -> [a] -> [b]
map (\Element
x -> (String -> (Text -> String) -> Maybe Text -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" (Text -> String
T.unpack (Text -> String) -> (Text -> Text) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
"/word/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>)) (Element -> Maybe Text
extractTarget Element
x),
                       Text
"application/vnd.openxmlformats-officedocument.wordprocessingml.footer+xml")) [Element]
footers) [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++
                    ((String, String, Maybe Text, ByteString) -> Element)
-> [(String, String, Maybe Text, ByteString)] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map (String, String, Maybe Text, ByteString) -> Element
forall a d. (a, String, Maybe Text, d) -> Element
mkImageOverride [(String, String, Maybe Text, ByteString)]
imgs [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++
                    [ String -> Element
mkMediaOverride (Entry -> String
eRelativePath Entry
e)
                        | Entry
e <- Archive -> [Entry]
zEntries Archive
refArchive
                        , String
"word/media/" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` Entry -> String
eRelativePath Entry
e ]

  let defaultnodes :: [Element]
defaultnodes = [Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Default"
              [(Text
"Extension",Text
"xml"),(Text
"ContentType",Text
"application/xml")] (),
             Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Default"
              [(Text
"Extension",Text
"rels"),(Text
"ContentType",Text
"application/vnd.openxmlformats-package.relationships+xml")] ()]
  let contentTypesDoc :: Element
contentTypesDoc = Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Types" [(Text
"xmlns",Text
"http://schemas.openxmlformats.org/package/2006/content-types")] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ [Element]
defaultnodes [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ [Element]
overrides
  let contentTypesEntry :: Entry
contentTypesEntry = String -> Integer -> ByteString -> Entry
toEntry String
"[Content_Types].xml" Integer
epochtime
        (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml Element
contentTypesDoc

  -- word/_rels/document.xml.rels
  let toBaseRel :: (Text, Text, Text) -> Element
toBaseRel (Text
url', Text
id', Text
target') = Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Relationship"
                                          [(Text
"Type",Text
url')
                                          ,(Text
"Id",Text
id')
                                          ,(Text
"Target",Text
target')] ()
  let baserels' :: [Element]
baserels' = ((Text, Text, Text) -> Element)
-> [(Text, Text, Text)] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Text, Text) -> Element
toBaseRel
                    [(Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/numbering",
                      Text
"rId1",
                      Text
"numbering.xml")
                    ,(Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/styles",
                      Text
"rId2",
                      Text
"styles.xml")
                    ,(Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/settings",
                      Text
"rId3",
                      Text
"settings.xml")
                    ,(Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/webSettings",
                      Text
"rId4",
                      Text
"webSettings.xml")
                    ,(Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/fontTable",
                      Text
"rId5",
                      Text
"fontTable.xml")
                    ,(Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/theme",
                      Text
"rId6",
                      Text
"theme/theme1.xml")
                    ,(Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/footnotes",
                      Text
"rId7",
                      Text
"footnotes.xml")
                    ,(Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/comments",
                      Text
"rId8",
                      Text
"comments.xml")
                    ]

  let idMap :: Map Text Text
idMap = Int -> [Element] -> Map Text Text
renumIdMap ([Element] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Element]
baserels' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) ([Element]
headers [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ [Element]
footers)
  let renumHeaders :: [Element]
renumHeaders = (QName -> Bool) -> Map Text Text -> [Element] -> [Element]
renumIds (\QName
q -> QName -> Text
qName QName
q Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"Id") Map Text Text
idMap [Element]
headers
  let renumFooters :: [Element]
renumFooters = (QName -> Bool) -> Map Text Text -> [Element] -> [Element]
renumIds (\QName
q -> QName -> Text
qName QName
q Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"Id") Map Text Text
idMap [Element]
footers
  let baserels :: [Element]
baserels = [Element]
baserels' [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ [Element]
renumHeaders [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ [Element]
renumFooters
  let toImgRel :: (String, String, c, d) -> Element
toImgRel (String
ident,String
path,c
_,d
_) =  Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Relationship" [(Text
"Type",Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/image"),(Text
"Id",String -> Text
T.pack String
ident),(Text
"Target",String -> Text
T.pack String
path)] ()
  let imgrels :: [Element]
imgrels = ((String, String, Maybe Text, ByteString) -> Element)
-> [(String, String, Maybe Text, ByteString)] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map (String, String, Maybe Text, ByteString) -> Element
forall c d. (String, String, c, d) -> Element
toImgRel [(String, String, Maybe Text, ByteString)]
imgs
  let toLinkRel :: (Text, Text) -> Element
toLinkRel (Text
src,Text
ident) =  Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Relationship" [(Text
"Type",Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/hyperlink"),(Text
"Id",Text
ident),(Text
"Target",Text
src),(Text
"TargetMode",Text
"External") ] ()
  let linkrels :: [Element]
linkrels = ((Text, Text) -> Element) -> [(Text, Text)] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Text) -> Element
toLinkRel ([(Text, Text)] -> [Element]) -> [(Text, Text)] -> [Element]
forall a b. (a -> b) -> a -> b
$ Map Text Text -> [(Text, Text)]
forall k a. Map k a -> [(k, a)]
M.toList (Map Text Text -> [(Text, Text)])
-> Map Text Text -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ WriterState -> Map Text Text
stExternalLinks WriterState
st
  let reldoc :: Element
reldoc = Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Relationships" [(Text
"xmlns",Text
"http://schemas.openxmlformats.org/package/2006/relationships")] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ [Element]
baserels [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ [Element]
imgrels [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ [Element]
linkrels
  let relEntry :: Entry
relEntry = String -> Integer -> ByteString -> Entry
toEntry String
"word/_rels/document.xml.rels" Integer
epochtime
        (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml Element
reldoc


  -- adjust contents to add sectPr from reference.docx
  let sectpr :: Element
sectpr = case Maybe Element
mbsectpr of
        Just Element
sectpr' -> let cs :: [Element]
cs = (QName -> Bool) -> Map Text Text -> [Element] -> [Element]
renumIds
                                 (\QName
q -> QName -> Text
qName QName
q Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"id" Bool -> Bool -> Bool
&& QName -> Maybe Text
qPrefix QName
q Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"r")
                                 Map Text Text
idMap
                                 (Element -> [Element]
elChildren Element
sectpr')
                        in
                         [Attr] -> Element -> Element
add_attrs (Element -> [Attr]
elAttribs Element
sectpr') (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:sectPr" [] [Element]
cs
        Maybe Element
Nothing      -> Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:sectPr" [] ()

  -- let sectpr = fromMaybe (mknode "w:sectPr" [] ()) mbsectpr'
  let contents' :: [Content]
contents' = [Content]
contents [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Element -> Content
Elem Element
sectpr]
  let docContents :: Element
docContents = Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:document" [(Text, Text)]
stdAttributes
                    (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:body" [] [Content]
contents'



  -- word/document.xml
  let contentEntry :: Entry
contentEntry = String -> Integer -> ByteString -> Entry
toEntry String
"word/document.xml" Integer
epochtime
                     (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml Element
docContents

  -- footnotes
  let notes :: Element
notes = Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:footnotes" [(Text, Text)]
stdAttributes [Element]
footnotes
  let footnotesEntry :: Entry
footnotesEntry = String -> Integer -> ByteString -> Entry
toEntry String
"word/footnotes.xml" Integer
epochtime (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml Element
notes

  -- footnote rels
  let footnoteRelEntry :: Entry
footnoteRelEntry = String -> Integer -> ByteString -> Entry
toEntry String
"word/_rels/footnotes.xml.rels" Integer
epochtime
        (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml (Element -> ByteString) -> Element -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Relationships" [(Text
"xmlns",Text
"http://schemas.openxmlformats.org/package/2006/relationships")]
        [Element]
linkrels

  -- comments
  let commentsEntry :: Entry
commentsEntry = String -> Integer -> ByteString -> Entry
toEntry String
"word/comments.xml" Integer
epochtime
        (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml (Element -> ByteString) -> Element -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:comments" [(Text, Text)]
stdAttributes [Element]
comments

  -- styles

  -- We only want to inject paragraph and text properties that
  -- are not already in the style map. Note that keys in the stylemap
  -- are normalized as lowercase.
  let newDynamicParaProps :: [ParaStyleName]
newDynamicParaProps = (ParaStyleName -> Bool) -> [ParaStyleName] -> [ParaStyleName]
forall a. (a -> Bool) -> [a] -> [a]
filter
        (\ParaStyleName
sty -> Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ParaStyleName -> ParaStyleNameMap -> Bool
forall sn sty. (Ord sn, HasStyleId sty) => sn -> Map sn sty -> Bool
hasStyleName ParaStyleName
sty (ParaStyleNameMap -> Bool) -> ParaStyleNameMap -> Bool
forall a b. (a -> b) -> a -> b
$ StyleMaps -> ParaStyleNameMap
smParaStyle StyleMaps
styleMaps)
        (Set ParaStyleName -> [ParaStyleName]
forall a. Set a -> [a]
Set.toList (Set ParaStyleName -> [ParaStyleName])
-> Set ParaStyleName -> [ParaStyleName]
forall a b. (a -> b) -> a -> b
$ WriterState -> Set ParaStyleName
stDynamicParaProps WriterState
st)

      newDynamicTextProps :: [CharStyleName]
newDynamicTextProps = (CharStyleName -> Bool) -> [CharStyleName] -> [CharStyleName]
forall a. (a -> Bool) -> [a] -> [a]
filter
        (\CharStyleName
sty -> Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ CharStyleName -> CharStyleNameMap -> Bool
forall sn sty. (Ord sn, HasStyleId sty) => sn -> Map sn sty -> Bool
hasStyleName CharStyleName
sty (CharStyleNameMap -> Bool) -> CharStyleNameMap -> Bool
forall a b. (a -> b) -> a -> b
$ StyleMaps -> CharStyleNameMap
smCharStyle StyleMaps
styleMaps)
        (Set CharStyleName -> [CharStyleName]
forall a. Set a -> [a]
Set.toList (Set CharStyleName -> [CharStyleName])
-> Set CharStyleName -> [CharStyleName]
forall a b. (a -> b) -> a -> b
$ WriterState -> Set CharStyleName
stDynamicTextProps WriterState
st)

  let newstyles :: [Element]
newstyles = (ParaStyleName -> Element) -> [ParaStyleName] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map ParaStyleName -> Element
newParaPropToOpenXml [ParaStyleName]
newDynamicParaProps [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++
                  (CharStyleName -> Element) -> [CharStyleName] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map CharStyleName -> Element
newTextPropToOpenXml [CharStyleName]
newDynamicTextProps [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++
                  [Element] -> (Style -> [Element]) -> Maybe Style -> [Element]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (StyleMaps -> Style -> [Element]
styleToOpenXml StyleMaps
styleMaps) (WriterOptions -> Maybe Style
writerHighlightStyle WriterOptions
opts)
  let styledoc' :: Element
styledoc' = Element
styledoc{ elContent :: [Content]
elContent = Element -> [Content]
elContent Element
styledoc [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++
                                           (Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem [Element]
newstyles }
  let styleEntry :: Entry
styleEntry = String -> Integer -> ByteString -> Entry
toEntry String
stylepath Integer
epochtime (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml Element
styledoc'

  -- construct word/numbering.xml
  let numpath :: String
numpath = String
"word/numbering.xml"
  Element
numbering <- Archive -> Archive -> String -> m Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> String -> m Element
parseXml Archive
refArchive Archive
distArchive String
numpath
  let newNumElts :: [Element]
newNumElts = [ListMarker] -> [Element]
mkNumbering (WriterState -> [ListMarker]
stLists WriterState
st)
  let pandocAdded :: Element -> Bool
pandocAdded Element
e =
       case (QName -> Bool) -> Element -> Maybe Text
findAttrBy ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"abstractNumId") (Text -> Bool) -> (QName -> Text) -> QName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QName -> Text
qName) Element
e Maybe Text -> (Text -> Maybe Int) -> Maybe Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead of
         Just Int
numid -> Int
numid Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= (Int
990 :: Int)
         Maybe Int
Nothing    ->
           case (QName -> Bool) -> Element -> Maybe Text
findAttrBy ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"numId") (Text -> Bool) -> (QName -> Text) -> QName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QName -> Text
qName) Element
e Maybe Text -> (Text -> Maybe Int) -> Maybe Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead of
             Just Int
numid -> Int
numid Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= (Int
1000 :: Int)
             Maybe Int
Nothing    -> Bool
False
  let oldElts :: [Element]
oldElts = (Element -> Bool) -> [Element] -> [Element]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Element -> Bool) -> Element -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Bool
pandocAdded) ([Element] -> [Element]) -> [Element] -> [Element]
forall a b. (a -> b) -> a -> b
$ [Content] -> [Element]
onlyElems (Element -> [Content]
elContent Element
numbering)
  let allElts :: [Element]
allElts = [Element]
oldElts [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ [Element]
newNumElts
  let numEntry :: Entry
numEntry = String -> Integer -> ByteString -> Entry
toEntry String
numpath Integer
epochtime (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml Element
numbering{ elContent :: [Content]
elContent =
                       -- we want all the abstractNums first, then the nums,
                       -- otherwise things break:
                       [Element -> Content
Elem Element
e | Element
e <- [Element]
allElts
                               , QName -> Text
qName (Element -> QName
elName Element
e) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"abstractNum" ] [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++
                       [Element -> Content
Elem Element
e | Element
e <- [Element]
allElts
                               , QName -> Text
qName (Element -> QName
elName Element
e) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"num" ] }

  let keywords :: [Text]
keywords = case Text -> Meta -> Maybe MetaValue
lookupMeta Text
"keywords" Meta
meta of
                       Just (MetaList [MetaValue]
xs) -> (MetaValue -> Text) -> [MetaValue] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map MetaValue -> Text
forall a. Walkable Inline a => a -> Text
stringify [MetaValue]
xs
                       Maybe MetaValue
_                  -> []

  -- docProps/core.xml
  let docPropsPath :: String
docPropsPath = String
"docProps/core.xml"
  let extraCoreProps :: [Text]
extraCoreProps = [Text
"subject",Text
"lang",Text
"category",Text
"description"]
  let extraCorePropsMap :: Map Text Text
extraCorePropsMap = [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Text, Text)] -> Map Text Text)
-> [(Text, Text)] -> Map Text Text
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text] -> [(Text, Text)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Text]
extraCoreProps
                       [Text
"dc:subject",Text
"dc:language",Text
"cp:category",Text
"dc:description"]
  let lookupMetaString' :: Text -> Meta -> Text
      lookupMetaString' :: Text -> Meta -> Text
lookupMetaString' Text
key' Meta
meta' =
        case Text
key' of
             Text
"description"    -> Text -> [Text] -> Text
T.intercalate Text
"_x000d_\n" ((Block -> Text) -> [Block] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Block -> Text
forall a. Walkable Inline a => a -> Text
stringify ([Block] -> [Text]) -> [Block] -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> Meta -> [Block]
lookupMetaBlocks Text
"description" Meta
meta')
             Text
key''            -> Text -> Meta -> Text
lookupMetaString Text
key'' Meta
meta'

  let docProps :: Element
docProps = Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"cp:coreProperties"
          [(Text
"xmlns:cp",Text
"http://schemas.openxmlformats.org/package/2006/metadata/core-properties")
          ,(Text
"xmlns:dc",Text
"http://purl.org/dc/elements/1.1/")
          ,(Text
"xmlns:dcterms",Text
"http://purl.org/dc/terms/")
          ,(Text
"xmlns:dcmitype",Text
"http://purl.org/dc/dcmitype/")
          ,(Text
"xmlns:xsi",Text
"http://www.w3.org/2001/XMLSchema-instance")]
          ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Text -> Element
mktnode Text
"dc:title" [] ([Inline] -> Text
forall a. Walkable Inline a => a -> Text
stringify ([Inline] -> Text) -> [Inline] -> Text
forall a b. (a -> b) -> a -> b
$ Meta -> [Inline]
docTitle Meta
meta)
          Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: Text -> [(Text, Text)] -> Text -> Element
mktnode Text
"dc:creator" [] (Text -> [Text] -> Text
T.intercalate Text
"; " (([Inline] -> Text) -> [[Inline]] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map [Inline] -> Text
forall a. Walkable Inline a => a -> Text
stringify ([[Inline]] -> [Text]) -> [[Inline]] -> [Text]
forall a b. (a -> b) -> a -> b
$ Meta -> [[Inline]]
docAuthors Meta
meta))
          Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: [ Text -> [(Text, Text)] -> Text -> Element
mktnode (Text -> Text -> Map Text Text -> Text
forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault Text
"" Text
k Map Text Text
extraCorePropsMap) [] (Text -> Meta -> Text
lookupMetaString' Text
k Meta
meta)
            | Text
k <- Map Text MetaValue -> [Text]
forall k a. Map k a -> [k]
M.keys (Meta -> Map Text MetaValue
unMeta Meta
meta), Text
k Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
extraCoreProps]
          [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ Text -> [(Text, Text)] -> Text -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"cp:keywords" [] (Text -> [Text] -> Text
T.intercalate Text
", " [Text]
keywords)
          Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: (\Text
x -> [ Text -> [(Text, Text)] -> Text -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"dcterms:created" [(Text
"xsi:type",Text
"dcterms:W3CDTF")] Text
x
                   , Text -> [(Text, Text)] -> Text -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"dcterms:modified" [(Text
"xsi:type",Text
"dcterms:W3CDTF")] Text
x
                   ]) (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ TimeLocale -> String -> UTCTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%FT%XZ" UTCTime
utctime)
  let docPropsEntry :: Entry
docPropsEntry = String -> Integer -> ByteString -> Entry
toEntry String
docPropsPath Integer
epochtime (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml Element
docProps

  -- docProps/custom.xml
  let customProperties :: [(Text, Text)]
      customProperties :: [(Text, Text)]
customProperties = [ (Text
k, Text -> Meta -> Text
lookupMetaString Text
k Meta
meta)
                         | Text
k <- Map Text MetaValue -> [Text]
forall k a. Map k a -> [k]
M.keys (Meta -> Map Text MetaValue
unMeta Meta
meta)
                         , Text
k Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` ([Text
"title", Text
"author", Text
"keywords"]
                                       [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text]
extraCoreProps)]
  let mkCustomProp :: (Text, t) -> a -> Element
mkCustomProp (Text
k, t
v) a
pid = Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"property"
         [(Text
"fmtid",Text
"{D5CDD505-2E9C-101B-9397-08002B2CF9AE}")
         ,(Text
"pid", a -> Text
forall a. Show a => a -> Text
tshow a
pid)
         ,(Text
"name", Text
k)] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> t -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"vt:lpwstr" [] t
v
  let customPropsPath :: String
customPropsPath = String
"docProps/custom.xml"
  let customProps :: Element
customProps = Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Properties"
          [(Text
"xmlns",Text
"http://schemas.openxmlformats.org/officeDocument/2006/custom-properties")
          ,(Text
"xmlns:vt",Text
"http://schemas.openxmlformats.org/officeDocument/2006/docPropsVTypes")
          ] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ ((Text, Text) -> Int -> Element)
-> [(Text, Text)] -> [Int] -> [Element]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Text, Text) -> Int -> Element
forall a t. (Show a, Node t) => (Text, t) -> a -> Element
mkCustomProp [(Text, Text)]
customProperties [(Int
2 :: Int)..]
  let customPropsEntry :: Entry
customPropsEntry = String -> Integer -> ByteString -> Entry
toEntry String
customPropsPath Integer
epochtime (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml Element
customProps

  let relsPath :: String
relsPath = String
"_rels/.rels"
  let rels :: Element
rels = Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Relationships" [(Text
"xmlns", Text
"http://schemas.openxmlformats.org/package/2006/relationships")]
        ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ ([(Text, Text)] -> Element) -> [[(Text, Text)]] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map (\[(Text, Text)]
attrs -> Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"Relationship" [(Text, Text)]
attrs ())
        [ [(Text
"Id",Text
"rId1")
          ,(Text
"Type",Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/officeDocument")
          ,(Text
"Target",Text
"word/document.xml")]
        , [(Text
"Id",Text
"rId4")
          ,(Text
"Type",Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/extended-properties")
          ,(Text
"Target",Text
"docProps/app.xml")]
        , [(Text
"Id",Text
"rId3")
          ,(Text
"Type",Text
"http://schemas.openxmlformats.org/package/2006/relationships/metadata/core-properties")
          ,(Text
"Target",Text
"docProps/core.xml")]
        , [(Text
"Id",Text
"rId5")
          ,(Text
"Type",Text
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/custom-properties")
          ,(Text
"Target",Text
"docProps/custom.xml")]
        ]
  let relsEntry :: Entry
relsEntry = String -> Integer -> ByteString -> Entry
toEntry String
relsPath Integer
epochtime (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml Element
rels

  -- we use dist archive for settings.xml, because Word sometimes
  -- adds references to footnotes or endnotes we don't have...
  -- we do, however, copy some settings over from reference
  let settingsPath :: String
settingsPath = String
"word/settings.xml"
      settingsList :: [Text]
settingsList = [ Text
"w:autoHyphenation"
                     , Text
"w:consecutiveHyphenLimit"
                     , Text
"w:hyphenationZone"
                     , Text
"w:doNotHyphenateCap"
                     , Text
"w:evenAndOddHeaders"
                     , Text
"w:proofState"
                     ]
  Entry
settingsEntry <- Archive -> Archive -> String -> Integer -> [Text] -> m Entry
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> String -> Integer -> [Text] -> m Entry
copyChildren Archive
refArchive Archive
distArchive String
settingsPath Integer
epochtime [Text]
settingsList

  let entryFromArchive :: Archive -> String -> m Entry
entryFromArchive Archive
arch String
path =
         m Entry -> (Entry -> m Entry) -> Maybe Entry -> m Entry
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (PandocError -> m Entry
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Entry) -> PandocError -> m Entry
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocSomeError
                           (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
path String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" missing in reference docx")
               Entry -> m Entry
forall (m :: * -> *) a. Monad m => a -> m a
return
               (String -> Archive -> Maybe Entry
findEntryByPath String
path Archive
arch Maybe Entry -> Maybe Entry -> Maybe Entry
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` String -> Archive -> Maybe Entry
findEntryByPath String
path Archive
distArchive)
  Entry
docPropsAppEntry <- Archive -> String -> m Entry
forall (m :: * -> *).
MonadError PandocError m =>
Archive -> String -> m Entry
entryFromArchive Archive
refArchive String
"docProps/app.xml"
  Entry
themeEntry <- Archive -> String -> m Entry
forall (m :: * -> *).
MonadError PandocError m =>
Archive -> String -> m Entry
entryFromArchive Archive
refArchive String
"word/theme/theme1.xml"
  Entry
fontTableEntry <- Archive -> String -> m Entry
forall (m :: * -> *).
MonadError PandocError m =>
Archive -> String -> m Entry
entryFromArchive Archive
refArchive String
"word/fontTable.xml"
  Entry
webSettingsEntry <- Archive -> String -> m Entry
forall (m :: * -> *).
MonadError PandocError m =>
Archive -> String -> m Entry
entryFromArchive Archive
refArchive String
"word/webSettings.xml"
  [Entry]
headerFooterEntries <- (String -> m Entry) -> [String] -> m [Entry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Archive -> String -> m Entry
forall (m :: * -> *).
MonadError PandocError m =>
Archive -> String -> m Entry
entryFromArchive Archive
refArchive (String -> m Entry) -> ShowS -> String -> m Entry
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"word/" String -> ShowS
forall a. [a] -> [a] -> [a]
++)) ([String] -> m [Entry]) -> [String] -> m [Entry]
forall a b. (a -> b) -> a -> b
$
                         (Element -> Maybe String) -> [Element] -> [String]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ((Text -> String) -> Maybe Text -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> String
T.unpack (Maybe Text -> Maybe String)
-> (Element -> Maybe Text) -> Element -> Maybe String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Maybe Text
extractTarget)
                         ([Element]
headers [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ [Element]
footers)
  let miscRelEntries :: [Entry]
miscRelEntries = [ Entry
e | Entry
e <- Archive -> [Entry]
zEntries Archive
refArchive
                       , String
"word/_rels/" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` Entry -> String
eRelativePath Entry
e
                       , String
".xml.rels" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` Entry -> String
eRelativePath Entry
e
                       , Entry -> String
eRelativePath Entry
e String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"word/_rels/document.xml.rels"
                       , Entry -> String
eRelativePath Entry
e String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"word/_rels/footnotes.xml.rels" ]
  let otherMediaEntries :: [Entry]
otherMediaEntries = [ Entry
e | Entry
e <- Archive -> [Entry]
zEntries Archive
refArchive
                          , String
"word/media/" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` Entry -> String
eRelativePath Entry
e ]

  -- Create archive
  let archive :: Archive
archive = (Entry -> Archive -> Archive) -> Archive -> [Entry] -> Archive
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Entry -> Archive -> Archive
addEntryToArchive Archive
emptyArchive ([Entry] -> Archive) -> [Entry] -> Archive
forall a b. (a -> b) -> a -> b
$
                  Entry
contentTypesEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
: Entry
relsEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
: Entry
contentEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
: Entry
relEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
:
                  Entry
footnoteRelEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
: Entry
numEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
: Entry
styleEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
: Entry
footnotesEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
:
                  Entry
commentsEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
:
                  Entry
docPropsEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
: Entry
docPropsAppEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
: Entry
customPropsEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
:
                  Entry
themeEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
:
                  Entry
fontTableEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
: Entry
settingsEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
: Entry
webSettingsEntry Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
:
                  [Entry]
imageEntries [Entry] -> [Entry] -> [Entry]
forall a. [a] -> [a] -> [a]
++ [Entry]
headerFooterEntries [Entry] -> [Entry] -> [Entry]
forall a. [a] -> [a] -> [a]
++
                  [Entry]
miscRelEntries [Entry] -> [Entry] -> [Entry]
forall a. [a] -> [a] -> [a]
++ [Entry]
otherMediaEntries
  ByteString -> m ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> m ByteString) -> ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ Archive -> ByteString
fromArchive Archive
archive

newParaPropToOpenXml :: ParaStyleName -> Element
newParaPropToOpenXml :: ParaStyleName -> Element
newParaPropToOpenXml (ParaStyleName -> Text
forall a. FromStyleName a => a -> Text
fromStyleName -> Text
s) =
  let styleId :: Text
styleId = (Char -> Bool) -> Text -> Text
T.filter (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace) Text
s
  in Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:style" [ (Text
"w:type", Text
"paragraph")
                      , (Text
"w:customStyle", Text
"1")
                      , (Text
"w:styleId", Text
styleId)]
     [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:name" [(Text
"w:val", Text
s)] ()
     , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:basedOn" [(Text
"w:val",Text
"BodyText")] ()
     , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:qFormat" [] ()
     ]

newTextPropToOpenXml :: CharStyleName -> Element
newTextPropToOpenXml :: CharStyleName -> Element
newTextPropToOpenXml (CharStyleName -> Text
forall a. FromStyleName a => a -> Text
fromStyleName -> Text
s) =
  let styleId :: Text
styleId = (Char -> Bool) -> Text -> Text
T.filter (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace) Text
s
  in Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:style" [ (Text
"w:type", Text
"character")
                      , (Text
"w:customStyle", Text
"1")
                      , (Text
"w:styleId", Text
styleId)]
     [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:name" [(Text
"w:val", Text
s)] ()
     , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:basedOn" [(Text
"w:val",Text
"BodyTextChar")] ()
     ]

styleToOpenXml :: StyleMaps -> Style -> [Element]
styleToOpenXml :: StyleMaps -> Style -> [Element]
styleToOpenXml StyleMaps
sm Style
style =
  Maybe Element -> [Element]
forall a. Maybe a -> [a]
maybeToList Maybe Element
parStyle [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ (TokenType -> Maybe Element) -> [TokenType] -> [Element]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe TokenType -> Maybe Element
toStyle [TokenType]
alltoktypes
  where alltoktypes :: [TokenType]
alltoktypes = TokenType -> TokenType -> [TokenType]
forall a. Enum a => a -> a -> [a]
enumFromTo TokenType
KeywordTok TokenType
NormalTok
        toStyle :: TokenType -> Maybe Element
toStyle TokenType
toktype | CharStyleName -> CharStyleNameMap -> Bool
forall sn sty. (Ord sn, HasStyleId sty) => sn -> Map sn sty -> Bool
hasStyleName (String -> CharStyleName
forall a. IsString a => String -> a
fromString (String -> CharStyleName) -> String -> CharStyleName
forall a b. (a -> b) -> a -> b
$ TokenType -> String
forall a. Show a => a -> String
show TokenType
toktype) (StyleMaps -> CharStyleNameMap
smCharStyle StyleMaps
sm) = Maybe Element
forall a. Maybe a
Nothing
                        | Bool
otherwise = Element -> Maybe Element
forall a. a -> Maybe a
Just (Element -> Maybe Element) -> Element -> Maybe Element
forall a b. (a -> b) -> a -> b
$
                          Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:style" [(Text
"w:type",Text
"character"),
                           (Text
"w:customStyle",Text
"1"),(Text
"w:styleId", TokenType -> Text
forall a. Show a => a -> Text
tshow TokenType
toktype)]
                             [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:name" [(Text
"w:val", TokenType -> Text
forall a. Show a => a -> Text
tshow TokenType
toktype)] ()
                             , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:basedOn" [(Text
"w:val",Text
"VerbatimChar")] ()
                             , Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:rPr" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
                               [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:color" [(Text
"w:val", TokenType -> Text
tokCol TokenType
toktype)] ()
                                 | TokenType -> Text
tokCol TokenType
toktype Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"auto" ] [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++
                               [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:shd" [(Text
"w:val",Text
"clear")
                                                ,(Text
"w:fill",TokenType -> Text
tokBg TokenType
toktype)] ()
                                 | TokenType -> Text
tokBg TokenType
toktype Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"auto" ] [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++
                               [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:b" [] () | (TokenStyle -> Bool) -> TokenType -> Bool
tokFeature TokenStyle -> Bool
tokenBold TokenType
toktype ] [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++
                               [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:i" [] () | (TokenStyle -> Bool) -> TokenType -> Bool
tokFeature TokenStyle -> Bool
tokenItalic TokenType
toktype ] [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++
                               [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:u" [] () | (TokenStyle -> Bool) -> TokenType -> Bool
tokFeature TokenStyle -> Bool
tokenUnderline TokenType
toktype ]
                             ]
        tokStyles :: Map TokenType TokenStyle
tokStyles = Style -> Map TokenType TokenStyle
tokenStyles Style
style
        tokFeature :: (TokenStyle -> Bool) -> TokenType -> Bool
tokFeature TokenStyle -> Bool
f TokenType
toktype = Bool -> (TokenStyle -> Bool) -> Maybe TokenStyle -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False TokenStyle -> Bool
f (Maybe TokenStyle -> Bool) -> Maybe TokenStyle -> Bool
forall a b. (a -> b) -> a -> b
$ TokenType -> Map TokenType TokenStyle -> Maybe TokenStyle
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup TokenType
toktype Map TokenType TokenStyle
tokStyles
        tokCol :: TokenType -> Text
tokCol TokenType
toktype = Text -> (Color -> Text) -> Maybe Color -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"auto" (String -> Text
T.pack (String -> Text) -> (Color -> String) -> Color -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
1 ShowS -> (Color -> String) -> Color -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color -> String
forall a. FromColor a => Color -> a
fromColor)
                         (Maybe Color -> Text) -> Maybe Color -> Text
forall a b. (a -> b) -> a -> b
$ (TokenStyle -> Maybe Color
tokenColor (TokenStyle -> Maybe Color) -> Maybe TokenStyle -> Maybe Color
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TokenType -> Map TokenType TokenStyle -> Maybe TokenStyle
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup TokenType
toktype Map TokenType TokenStyle
tokStyles)
                           Maybe Color -> Maybe Color -> Maybe Color
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` Style -> Maybe Color
defaultColor Style
style
        tokBg :: TokenType -> Text
tokBg TokenType
toktype = Text -> (Color -> Text) -> Maybe Color -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"auto" (String -> Text
T.pack (String -> Text) -> (Color -> String) -> Color -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
1 ShowS -> (Color -> String) -> Color -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color -> String
forall a. FromColor a => Color -> a
fromColor)
                         (Maybe Color -> Text) -> Maybe Color -> Text
forall a b. (a -> b) -> a -> b
$ (TokenStyle -> Maybe Color
tokenBackground (TokenStyle -> Maybe Color) -> Maybe TokenStyle -> Maybe Color
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TokenType -> Map TokenType TokenStyle -> Maybe TokenStyle
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup TokenType
toktype Map TokenType TokenStyle
tokStyles)
                           Maybe Color -> Maybe Color -> Maybe Color
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` Style -> Maybe Color
backgroundColor Style
style
        parStyle :: Maybe Element
parStyle | ParaStyleName -> ParaStyleNameMap -> Bool
forall sn sty. (Ord sn, HasStyleId sty) => sn -> Map sn sty -> Bool
hasStyleName ParaStyleName
"Source Code" (StyleMaps -> ParaStyleNameMap
smParaStyle StyleMaps
sm) = Maybe Element
forall a. Maybe a
Nothing
                 | Bool
otherwise = Element -> Maybe Element
forall a. a -> Maybe a
Just (Element -> Maybe Element) -> Element -> Maybe Element
forall a b. (a -> b) -> a -> b
$
                   Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:style" [(Text
"w:type",Text
"paragraph"),
                           (Text
"w:customStyle",Text
"1"),(Text
"w:styleId",Text
"SourceCode")]
                             [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:name" [(Text
"w:val",Text
"Source Code")] ()
                             , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:basedOn" [(Text
"w:val",Text
"Normal")] ()
                             , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:link" [(Text
"w:val",Text
"VerbatimChar")] ()
                             , Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:pPr" []
                               ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:wordWrap" [(Text
"w:val",Text
"off")] ()
                               Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
:
                         [Element] -> (Color -> [Element]) -> Maybe Color -> [Element]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Color
col -> [Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:shd" [(Text
"w:val",Text
"clear"),(Text
"w:fill", String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
1 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Color -> String
forall a. FromColor a => Color -> a
fromColor Color
col)] ()]) (Style -> Maybe Color
backgroundColor Style
style)
                             ]

copyChildren :: (PandocMonad m)
             => Archive -> Archive -> String -> Integer -> [Text] -> m Entry
copyChildren :: Archive -> Archive -> String -> Integer -> [Text] -> m Entry
copyChildren Archive
refArchive Archive
distArchive String
path Integer
timestamp [Text]
elNames = do
  Element
ref  <- Archive -> Archive -> String -> m Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> String -> m Element
parseXml Archive
refArchive Archive
distArchive String
path
  Element
dist <- Archive -> Archive -> String -> m Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> String -> m Element
parseXml Archive
distArchive Archive
distArchive String
path
  Entry -> m Entry
forall (m :: * -> *) a. Monad m => a -> m a
return (Entry -> m Entry) -> Entry -> m Entry
forall a b. (a -> b) -> a -> b
$ String -> Integer -> ByteString -> Entry
toEntry String
path Integer
timestamp (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml Element
dist{
      elContent :: [Content]
elContent = Element -> [Content]
elContent Element
dist [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ Element -> [Content]
copyContent Element
ref
    }
  where
    strName :: QName -> Text
strName QName{qName :: QName -> Text
qName=Text
name, qPrefix :: QName -> Maybe Text
qPrefix=Maybe Text
prefix}
      | Just Text
p <- Maybe Text
prefix = Text
p Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name
      | Bool
otherwise        = Text
name
    shouldCopy :: QName -> Bool
shouldCopy = (Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
elNames) (Text -> Bool) -> (QName -> Text) -> QName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QName -> Text
strName
    cleanElem :: Element -> Content
cleanElem el :: Element
el@Element{elName :: Element -> QName
elName=QName
name} = Element -> Content
Elem Element
el{elName :: QName
elName=QName
name{qURI :: Maybe Text
qURI=Maybe Text
forall a. Maybe a
Nothing}}
    copyContent :: Element -> [Content]
copyContent = (Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
cleanElem ([Element] -> [Content])
-> (Element -> [Element]) -> Element -> [Content]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (QName -> Bool) -> Element -> [Element]
filterChildrenName QName -> Bool
shouldCopy

-- this is the lowest number used for a list numId
baseListId :: Int
baseListId :: Int
baseListId = Int
1000

mkNumbering :: [ListMarker] -> [Element]
mkNumbering :: [ListMarker] -> [Element]
mkNumbering [ListMarker]
lists =
  [Element]
elts [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ (ListMarker -> Int -> Element)
-> [ListMarker] -> [Int] -> [Element]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ListMarker -> Int -> Element
mkNum [ListMarker]
lists [Int
baseListId..(Int
baseListId Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [ListMarker] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ListMarker]
lists Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)]
    where elts :: [Element]
elts = (ListMarker -> Element) -> [ListMarker] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map ListMarker -> Element
mkAbstractNum ([ListMarker] -> [ListMarker]
forall a. Ord a => [a] -> [a]
ordNub [ListMarker]
lists)

maxListLevel :: Int
maxListLevel :: Int
maxListLevel = Int
8

mkNum :: ListMarker -> Int -> Element
mkNum :: ListMarker -> Int -> Element
mkNum ListMarker
marker Int
numid =
  Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:num" [(Text
"w:numId",Int -> Text
forall a. Show a => a -> Text
tshow Int
numid)]
   ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:abstractNumId" [(Text
"w:val",ListMarker -> Text
listMarkerToId ListMarker
marker)] ()
   Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: case ListMarker
marker of
       ListMarker
NoMarker     -> []
       ListMarker
BulletMarker -> []
       NumberMarker ListNumberStyle
_ ListNumberDelim
_ Int
start ->
          (Int -> Element) -> [Int] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map (\Int
lvl -> Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:lvlOverride" [(Text
"w:ilvl",Int -> Text
forall a. Show a => a -> Text
tshow (Int
lvl :: Int))]
              (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:startOverride" [(Text
"w:val",Int -> Text
forall a. Show a => a -> Text
tshow Int
start)] ())
                [Int
0..Int
maxListLevel]

mkAbstractNum :: ListMarker -> Element
mkAbstractNum :: ListMarker -> Element
mkAbstractNum ListMarker
marker =
  Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:abstractNum" [(Text
"w:abstractNumId",ListMarker -> Text
listMarkerToId ListMarker
marker)]
    ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:nsid" [(Text
"w:val", Text
"A" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ListMarker -> Text
listMarkerToId ListMarker
marker)] ()
    Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:multiLevelType" [(Text
"w:val",Text
"multilevel")] ()
    Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: (Int -> Element) -> [Int] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map (ListMarker -> Int -> Element
mkLvl ListMarker
marker)
      [Int
0..Int
maxListLevel]

mkLvl :: ListMarker -> Int -> Element
mkLvl :: ListMarker -> Int -> Element
mkLvl ListMarker
marker Int
lvl =
  Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:lvl" [(Text
"w:ilvl",Int -> Text
forall a. Show a => a -> Text
tshow Int
lvl)] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
    [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:start" [(Text
"w:val",Text
start)] ()
      | ListMarker
marker ListMarker -> ListMarker -> Bool
forall a. Eq a => a -> a -> Bool
/= ListMarker
NoMarker Bool -> Bool -> Bool
&& ListMarker
marker ListMarker -> ListMarker -> Bool
forall a. Eq a => a -> a -> Bool
/= ListMarker
BulletMarker ] [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++
    [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:numFmt" [(Text
"w:val",Text
fmt)] ()
    , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:lvlText" [(Text
"w:val", Text
lvltxt)] ()
    , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:lvlJc" [(Text
"w:val",Text
"left")] ()
    , Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:pPr" []
      [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:ind" [ (Text
"w:left",Int -> Text
forall a. Show a => a -> Text
tshow (Int -> Text) -> Int -> Text
forall a b. (a -> b) -> a -> b
$ Int
lvl Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
step Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
step)
                       , (Text
"w:hanging",Int -> Text
forall a. Show a => a -> Text
tshow (Int
hang :: Int))
                       ] ()
      ]
    ]
    where (Text
fmt, Text
lvltxt, Text
start) =
            case ListMarker
marker of
                 ListMarker
NoMarker             -> (Text
"bullet",Text
" ",Text
"1")
                 ListMarker
BulletMarker         -> (Text
"bullet",Int -> Text
forall t p. (IsString p, Integral t) => t -> p
bulletFor Int
lvl,Text
"1")
                 NumberMarker ListNumberStyle
st ListNumberDelim
de Int
n -> (ListNumberStyle -> Int -> Text
forall p t. (IsString p, Integral t) => ListNumberStyle -> t -> p
styleFor ListNumberStyle
st Int
lvl
                                         ,ListNumberDelim -> Text -> Text
forall a. (Semigroup a, IsString a) => ListNumberDelim -> a -> a
patternFor ListNumberDelim
de (Text
"%" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow (Int
lvl Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))
                                         ,Int -> Text
forall a. Show a => a -> Text
tshow Int
n)
          step :: Int
step = Int
720
          hang :: Int
hang = Int
480
          bulletFor :: t -> p
bulletFor t
0 = p
"\x2022"  -- filled circle
          bulletFor t
1 = p
"\x2013"  -- en dash
          bulletFor t
2 = p
"\x2022"  -- hyphen bullet
          bulletFor t
3 = p
"\x2013"
          bulletFor t
4 = p
"\x2022"
          bulletFor t
5 = p
"\x2013"
          bulletFor t
x = t -> p
bulletFor (t
x t -> t -> t
forall a. Integral a => a -> a -> a
`mod` t
6)
          styleFor :: ListNumberStyle -> t -> p
styleFor ListNumberStyle
UpperAlpha t
_   = p
"upperLetter"
          styleFor ListNumberStyle
LowerAlpha t
_   = p
"lowerLetter"
          styleFor ListNumberStyle
UpperRoman t
_   = p
"upperRoman"
          styleFor ListNumberStyle
LowerRoman t
_   = p
"lowerRoman"
          styleFor ListNumberStyle
Decimal t
_      = p
"decimal"
          styleFor ListNumberStyle
DefaultStyle t
0 = p
"decimal"
          styleFor ListNumberStyle
DefaultStyle t
1 = p
"lowerLetter"
          styleFor ListNumberStyle
DefaultStyle t
2 = p
"lowerRoman"
          styleFor ListNumberStyle
DefaultStyle t
3 = p
"decimal"
          styleFor ListNumberStyle
DefaultStyle t
4 = p
"lowerLetter"
          styleFor ListNumberStyle
DefaultStyle t
5 = p
"lowerRoman"
          styleFor ListNumberStyle
DefaultStyle t
x = ListNumberStyle -> t -> p
styleFor ListNumberStyle
DefaultStyle (t
x t -> t -> t
forall a. Integral a => a -> a -> a
`mod` t
6)
          styleFor ListNumberStyle
_ t
_            = p
"decimal"
          patternFor :: ListNumberDelim -> a -> a
patternFor ListNumberDelim
OneParen a
s  = a
s a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
")"
          patternFor ListNumberDelim
TwoParens a
s = a
"(" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
s a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
")"
          patternFor ListNumberDelim
_ a
s         = a
s a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
"."

getNumId :: (PandocMonad m) => WS m Int
getNumId :: WS m Int
getNumId = (((Int
baseListId Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int -> Int -> Int
forall a. Num a => a -> a -> a
+) (Int -> Int) -> ([ListMarker] -> Int) -> [ListMarker] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ListMarker] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length) ([ListMarker] -> Int)
-> ReaderT WriterEnv (StateT WriterState m) [ListMarker]
-> WS m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (WriterState -> [ListMarker])
-> ReaderT WriterEnv (StateT WriterState m) [ListMarker]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> [ListMarker]
stLists


makeTOC :: (PandocMonad m) => WriterOptions -> WS m [Element]
makeTOC :: WriterOptions -> WS m [Element]
makeTOC WriterOptions
opts = do
  let depth :: Text
depth = Text
"1-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow (WriterOptions -> Int
writerTOCDepth WriterOptions
opts)
  let tocCmd :: Text
tocCmd = Text
"TOC \\o \"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
depth Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\" \\h \\z \\u"
  [Inline]
tocTitle <- (WriterState -> [Inline])
-> ReaderT WriterEnv (StateT WriterState m) [Inline]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> [Inline]
stTocTitle
  [Content]
title <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"TOC Heading") (WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts [[Inline] -> Block
Para [Inline]
tocTitle])
  [Element] -> WS m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return
    [Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:sdt" [] [
      Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:sdtPr" [] (
        Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:docPartObj" []
          [Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:docPartGallery" [(Text
"w:val",Text
"Table of Contents")] (),
          Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:docPartUnique" [] ()]
         -- w:docPartObj
      ), -- w:sdtPr
      Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:sdtContent" [] ([Content]
title [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [ Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$
        Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:p" [] (
          Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" [] [
            Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:fldChar" [(Text
"w:fldCharType",Text
"begin"),(Text
"w:dirty",Text
"true")] (),
            Text -> [(Text, Text)] -> Text -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:instrText" [(Text
"xml:space",Text
"preserve")] Text
tocCmd,
            Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:fldChar" [(Text
"w:fldCharType",Text
"separate")] (),
            Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:fldChar" [(Text
"w:fldCharType",Text
"end")] ()
          ] -- w:r
        ) -- w:p
      ])
    ]] -- w:sdt

-- | Convert Pandoc document to two lists of
-- OpenXML elements (the main document and footnotes).
writeOpenXML :: (PandocMonad m)
             => WriterOptions -> Pandoc
             -> WS m ([Content], [Element], [Element])
writeOpenXML :: WriterOptions -> Pandoc -> WS m ([Content], [Element], [Element])
writeOpenXML WriterOptions
opts (Pandoc Meta
meta [Block]
blocks) = do
  let tit :: [Inline]
tit = Meta -> [Inline]
docTitle Meta
meta
  let auths :: [[Inline]]
auths = Meta -> [[Inline]]
docAuthors Meta
meta
  let dat :: [Inline]
dat = Meta -> [Inline]
docDate Meta
meta
  let abstract' :: [Block]
abstract' = Text -> Meta -> [Block]
lookupMetaBlocks Text
"abstract" Meta
meta
  let subtitle' :: [Inline]
subtitle' = Text -> Meta -> [Inline]
lookupMetaInlines Text
"subtitle" Meta
meta
  let includeTOC :: Bool
includeTOC = WriterOptions -> Bool
writerTableOfContents WriterOptions
opts Bool -> Bool -> Bool
|| Text -> Meta -> Bool
lookupMetaBool Text
"toc" Meta
meta
  [Content]
title <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Title") (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts [[Inline] -> Block
Para [Inline]
tit | Bool -> Bool
not ([Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
tit)]
  [Content]
subtitle <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Subtitle") (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts [[Inline] -> Block
Para [Inline]
subtitle' | Bool -> Bool
not ([Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
subtitle')]
  [Content]
authors <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Author") (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts ([Block] -> WS m [Content]) -> [Block] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$
       ([Inline] -> Block) -> [[Inline]] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
map [Inline] -> Block
Para [[Inline]]
auths
  [Content]
date <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Date") (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts [[Inline] -> Block
Para [Inline]
dat | Bool -> Bool
not ([Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
dat)]
  [Content]
abstract <- if [Block] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Block]
abstract'
                 then [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return []
                 else WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Abstract") (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts [Block]
abstract'
  let convertSpace :: [Inline] -> [Inline]
convertSpace (Str Text
x : Inline
Space : Str Text
y : [Inline]
xs) = Text -> Inline
Str (Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
y) Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline]
xs
      convertSpace (Str Text
x : Str Text
y : [Inline]
xs)         = Text -> Inline
Str (Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
y) Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline]
xs
      convertSpace [Inline]
xs                           = [Inline]
xs
  let blocks' :: [Block]
blocks' = ([Inline] -> [Inline]) -> [Block] -> [Block]
forall a b. (Data a, Data b) => (a -> a) -> b -> b
bottomUp [Inline] -> [Inline]
convertSpace [Block]
blocks
  [Content]
doc' <- WS m ()
forall (m :: * -> *). PandocMonad m => WS m ()
setFirstPara WS m () -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts [Block]
blocks'
  [Element]
notes' <- [Element] -> [Element]
forall a. [a] -> [a]
reverse ([Element] -> [Element])
-> ReaderT WriterEnv (StateT WriterState m) [Element]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (WriterState -> [Element])
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> [Element]
stFootnotes
  [([(Text, Text)], [Inline])]
comments <- [([(Text, Text)], [Inline])] -> [([(Text, Text)], [Inline])]
forall a. [a] -> [a]
reverse ([([(Text, Text)], [Inline])] -> [([(Text, Text)], [Inline])])
-> ReaderT
     WriterEnv (StateT WriterState m) [([(Text, Text)], [Inline])]
-> ReaderT
     WriterEnv (StateT WriterState m) [([(Text, Text)], [Inline])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (WriterState -> [([(Text, Text)], [Inline])])
-> ReaderT
     WriterEnv (StateT WriterState m) [([(Text, Text)], [Inline])]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> [([(Text, Text)], [Inline])]
stComments
  let toComment :: ([(Text, Text)], [Inline])
-> ReaderT WriterEnv (StateT WriterState m) Element
toComment ([(Text, Text)]
kvs, [Inline]
ils) = do
        [Content]
annotation <- WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
ils
        Element -> ReaderT WriterEnv (StateT WriterState m) Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> ReaderT WriterEnv (StateT WriterState m) Element)
-> Element -> ReaderT WriterEnv (StateT WriterState m) Element
forall a b. (a -> b) -> a -> b
$
          Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:comment" [(Text
"w:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
k, Text
v) | (Text
k,Text
v) <- [(Text, Text)]
kvs]
            [ Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:p" [] ([Content] -> Element) -> [Content] -> Element
forall a b. (a -> b) -> a -> b
$
              (Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem
              [ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:pPr" []
                [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:pStyle" [(Text
"w:val", Text
"CommentText")] () ]
              , Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" []
                [ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:rPr" []
                  [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:rStyle" [(Text
"w:val", Text
"CommentReference")] ()
                  , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:annotationRef" [] ()
                  ]
                ]
              ] [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
annotation
            ]
  [Element]
comments' <- (([(Text, Text)], [Inline]) -> WS m Element)
-> [([(Text, Text)], [Inline])]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ([(Text, Text)], [Inline]) -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
([(Text, Text)], [Inline])
-> ReaderT WriterEnv (StateT WriterState m) Element
toComment [([(Text, Text)], [Inline])]
comments
  [Element]
toc <- if Bool
includeTOC
            then WriterOptions -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> WS m [Element]
makeTOC WriterOptions
opts
            else [Element] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return []
  let meta' :: [Content]
meta' = [Content]
title [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
subtitle [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
authors [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
date [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
abstract [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ (Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem [Element]
toc
  ([Content], [Element], [Element])
-> WS m ([Content], [Element], [Element])
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content]
meta' [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
doc', [Element]
notes', [Element]
comments')

-- | Convert a list of Pandoc blocks to OpenXML.
blocksToOpenXML :: (PandocMonad m) => WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML :: WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts = ([[Content]] -> [Content])
-> ReaderT WriterEnv (StateT WriterState m) [[Content]]
-> WS m [Content]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[Content]] -> [Content]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (ReaderT WriterEnv (StateT WriterState m) [[Content]]
 -> WS m [Content])
-> ([Block]
    -> ReaderT WriterEnv (StateT WriterState m) [[Content]])
-> [Block]
-> WS m [Content]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Block -> WS m [Content])
-> [Block] -> ReaderT WriterEnv (StateT WriterState m) [[Content]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (WriterOptions -> Block -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> WS m [Content]
blockToOpenXML WriterOptions
opts) ([Block] -> ReaderT WriterEnv (StateT WriterState m) [[Content]])
-> ([Block] -> [Block])
-> [Block]
-> ReaderT WriterEnv (StateT WriterState m) [[Content]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> [Block]
separateTables

-- Word combines adjacent tables unless you put an empty paragraph between
-- them.  See #4315.
separateTables :: [Block] -> [Block]
separateTables :: [Block] -> [Block]
separateTables [] = []
separateTables (x :: Block
x@Table{}:xs :: [Block]
xs@(Table{}:[Block]
_)) =
  Block
x Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
: Format -> Text -> Block
RawBlock (Text -> Format
Format Text
"openxml") Text
"<w:p />" Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
: [Block] -> [Block]
separateTables [Block]
xs
separateTables (Block
x:[Block]
xs) = Block
x Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
: [Block] -> [Block]
separateTables [Block]
xs

pStyleM :: (PandocMonad m) => ParaStyleName -> WS m XML.Element
pStyleM :: ParaStyleName -> WS m Element
pStyleM ParaStyleName
styleName = do
  ParaStyleNameMap
pStyleMap <- (WriterState -> ParaStyleNameMap)
-> ReaderT WriterEnv (StateT WriterState m) ParaStyleNameMap
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (StyleMaps -> ParaStyleNameMap
smParaStyle (StyleMaps -> ParaStyleNameMap)
-> (WriterState -> StyleMaps) -> WriterState -> ParaStyleNameMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterState -> StyleMaps
stStyleMaps)
  let sty' :: StyleId ParStyle
sty' = ParaStyleName -> ParaStyleNameMap -> StyleId ParStyle
forall sn sty.
(Ord sn, FromStyleName sn, IsString (StyleId sty),
 HasStyleId sty) =>
sn -> Map sn sty -> StyleId sty
getStyleIdFromName ParaStyleName
styleName ParaStyleNameMap
pStyleMap
  Element -> WS m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> WS m Element) -> Element -> WS m Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:pStyle" [(Text
"w:val", ParaStyleId -> Text
forall a. FromStyleId a => a -> Text
fromStyleId ParaStyleId
sty')] ()

rStyleM :: (PandocMonad m) => CharStyleName -> WS m XML.Element
rStyleM :: CharStyleName -> WS m Element
rStyleM CharStyleName
styleName = do
  CharStyleNameMap
cStyleMap <- (WriterState -> CharStyleNameMap)
-> ReaderT WriterEnv (StateT WriterState m) CharStyleNameMap
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (StyleMaps -> CharStyleNameMap
smCharStyle (StyleMaps -> CharStyleNameMap)
-> (WriterState -> StyleMaps) -> WriterState -> CharStyleNameMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterState -> StyleMaps
stStyleMaps)
  let sty' :: StyleId CharStyle
sty' = CharStyleName -> CharStyleNameMap -> StyleId CharStyle
forall sn sty.
(Ord sn, FromStyleName sn, IsString (StyleId sty),
 HasStyleId sty) =>
sn -> Map sn sty -> StyleId sty
getStyleIdFromName CharStyleName
styleName CharStyleNameMap
cStyleMap
  Element -> WS m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> WS m Element) -> Element -> WS m Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:rStyle" [(Text
"w:val", CharStyleId -> Text
forall a. FromStyleId a => a -> Text
fromStyleId CharStyleId
sty')] ()

getUniqueId :: (PandocMonad m) => WS m Text
-- the + 20 is to ensure that there are no clashes with the rIds
-- already in word/document.xml.rel
getUniqueId :: WS m Text
getUniqueId = do
  Int
n <- (WriterState -> Int)
-> ReaderT WriterEnv (StateT WriterState m) Int
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Int
stCurId
  (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{stCurId :: Int
stCurId = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1}
  Text -> WS m Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> WS m Text) -> Text -> WS m Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. Show a => a -> Text
tshow Int
n

-- | Key for specifying user-defined docx styles.
dynamicStyleKey :: Text
dynamicStyleKey :: Text
dynamicStyleKey = Text
"custom-style"

-- | Convert a Pandoc block element to OpenXML.
blockToOpenXML :: (PandocMonad m) => WriterOptions -> Block -> WS m [Content]
blockToOpenXML :: WriterOptions -> Block -> WS m [Content]
blockToOpenXML WriterOptions
opts Block
blk = WS m [Content] -> WS m [Content]
forall (m :: * -> *) a. PandocMonad m => WS m a -> WS m a
withDirection (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Block -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> WS m [Content]
blockToOpenXML' WriterOptions
opts Block
blk

blockToOpenXML' :: (PandocMonad m) => WriterOptions -> Block -> WS m [Content]
blockToOpenXML' :: WriterOptions -> Block -> WS m [Content]
blockToOpenXML' WriterOptions
_ Block
Null = [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return []
blockToOpenXML' WriterOptions
opts (Div (Text
ident,[Text]
_classes,[(Text, Text)]
kvs) [Block]
bs) = do
  WS m [Content] -> WS m [Content]
stylemod <- case Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
dynamicStyleKey [(Text, Text)]
kvs of
                   Just (String -> ParaStyleName
forall a. IsString a => String -> a
fromString (String -> ParaStyleName)
-> (Text -> String) -> Text -> ParaStyleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack -> ParaStyleName
sty) -> do
                      (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s ->
                        WriterState
s{stDynamicParaProps :: Set ParaStyleName
stDynamicParaProps = ParaStyleName -> Set ParaStyleName -> Set ParaStyleName
forall a. Ord a => a -> Set a -> Set a
Set.insert ParaStyleName
sty
                             (WriterState -> Set ParaStyleName
stDynamicParaProps WriterState
s)}
                      (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return ((WS m [Content] -> WS m [Content])
 -> ReaderT
      WriterEnv
      (StateT WriterState m)
      (WS m [Content] -> WS m [Content]))
-> (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall a b. (a -> b) -> a -> b
$ WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
sty)
                   Maybe Text
_ -> (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return WS m [Content] -> WS m [Content]
forall a. a -> a
id
  WS m [Content] -> WS m [Content]
dirmod <- case Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"dir" [(Text, Text)]
kvs of
                 Just Text
"rtl" -> (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return ((WS m [Content] -> WS m [Content])
 -> ReaderT
      WriterEnv
      (StateT WriterState m)
      (WS m [Content] -> WS m [Content]))
-> (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall a b. (a -> b) -> a -> b
$ (WriterEnv -> WriterEnv) -> WS m [Content] -> WS m [Content]
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env { envRTL :: Bool
envRTL = Bool
True })
                 Just Text
"ltr" -> (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return ((WS m [Content] -> WS m [Content])
 -> ReaderT
      WriterEnv
      (StateT WriterState m)
      (WS m [Content] -> WS m [Content]))
-> (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall a b. (a -> b) -> a -> b
$ (WriterEnv -> WriterEnv) -> WS m [Content] -> WS m [Content]
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env { envRTL :: Bool
envRTL = Bool
False })
                 Maybe Text
_ -> (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return WS m [Content] -> WS m [Content]
forall a. a -> a
id
  let ([Block]
hs, [Block]
bs') = if Text
ident Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"refs"
                     then (Block -> Bool) -> [Block] -> ([Block], [Block])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Block -> Bool
isHeaderBlock [Block]
bs
                     else ([], [Block]
bs)
  let bibmod :: WS m a -> WS m a
bibmod = if Text
ident Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"refs"
                  then WS m Element -> WS m a -> WS m a
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Bibliography")
                  else WS m a -> WS m a
forall a. a -> a
id
  [Content]
header <- WS m [Content] -> WS m [Content]
dirmod (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WS m [Content] -> WS m [Content]
stylemod (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts [Block]
hs
  [Content]
contents <- WS m [Content] -> WS m [Content]
dirmod (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WS m [Content] -> WS m [Content]
forall a. WS m a -> WS m a
bibmod (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WS m [Content] -> WS m [Content]
stylemod (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts [Block]
bs'
  Text -> [Content] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
Text -> [Content] -> WS m [Content]
wrapBookmark Text
ident ([Content] -> WS m [Content]) -> [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ [Content]
header [Content] -> [Content] -> [Content]
forall a. Semigroup a => a -> a -> a
<> [Content]
contents
blockToOpenXML' WriterOptions
opts (Header Int
lev (Text
ident,[Text]
_,[(Text, Text)]
kvs) [Inline]
lst) = do
  ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => WS m ()
setFirstPara
  [Element]
paraProps <- WS m Element -> WS m [Element] -> WS m [Element]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM (String -> ParaStyleName
forall a. IsString a => String -> a
fromString (String -> ParaStyleName) -> String -> ParaStyleName
forall a b. (a -> b) -> a -> b
$ String
"Heading "String -> ShowS
forall a. [a] -> [a] -> [a]
++Int -> String
forall a. Show a => a -> String
show Int
lev)) (WS m [Element] -> WS m [Element])
-> WS m [Element] -> WS m [Element]
forall a b. (a -> b) -> a -> b
$
                    Bool -> WS m [Element]
forall (m :: * -> *). PandocMonad m => Bool -> WS m [Element]
getParaProps Bool
False
  [Content]
number <-
        if WriterOptions -> Bool
writerNumberSections WriterOptions
opts
           then
             case Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"number" [(Text, Text)]
kvs of
                Just Text
n -> do
                   [Content]
num <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withTextPropM (CharStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
CharStyleName -> WS m Element
rStyleM CharStyleName
"SectionNumber")
                            (WriterOptions -> Inline -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> WS m [Content]
inlineToOpenXML WriterOptions
opts (Text -> Inline
Str Text
n))
                   [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> WS m [Content]) -> [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ [Content]
num [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" [] [Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:tab" [] ()]]
                Maybe Text
Nothing -> [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return []
           else [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return []
  [Content]
contents <- ([Content]
number [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++) ([Content] -> [Content]) -> WS m [Content] -> WS m [Content]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
lst
  if Text -> Bool
T.null Text
ident
     then [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:p" [] ((Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem [Element]
paraProps [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
contents)]
     else do
       let bookmarkName :: Text
bookmarkName = Text
ident
       (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s{ stSectionIds :: Set Text
stSectionIds = Text -> Set Text -> Set Text
forall a. Ord a => a -> Set a -> Set a
Set.insert Text
bookmarkName
                                      (Set Text -> Set Text) -> Set Text -> Set Text
forall a b. (a -> b) -> a -> b
$ WriterState -> Set Text
stSectionIds WriterState
s }
       [Content]
bookmarkedContents <- Text -> [Content] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
Text -> [Content] -> WS m [Content]
wrapBookmark Text
bookmarkName [Content]
contents
       [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:p" [] ((Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem [Element]
paraProps [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
bookmarkedContents)]
blockToOpenXML' WriterOptions
opts (Plain [Inline]
lst) = do
  Bool
isInTable <- (WriterState -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stInTable
  Bool
isInList <- (WriterState -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stInList
  let block :: WS m [Content]
block = WriterOptions -> Block -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> WS m [Content]
blockToOpenXML WriterOptions
opts ([Inline] -> Block
Para [Inline]
lst)
  Element
prop <- ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Compact"
  if Bool
isInTable Bool -> Bool -> Bool
|| Bool
isInList
     then Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withParaProp Element
prop WS m [Content]
block
     else WS m [Content]
block
-- title beginning with fig: indicates that the image is a figure
blockToOpenXML' WriterOptions
opts (Para [Image (Text, [Text], [(Text, Text)])
attr [Inline]
alt (Text
src,Text -> Text -> Maybe Text
T.stripPrefix Text
"fig:" -> Just Text
tit)]) = do
  ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => WS m ()
setFirstPara
  Element
prop <- ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM (ParaStyleName -> WS m Element) -> ParaStyleName -> WS m Element
forall a b. (a -> b) -> a -> b
$
        if [Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
alt
        then ParaStyleName
"Figure"
        else ParaStyleName
"Captioned Figure"
  [Element]
paraProps <- (WriterEnv -> WriterEnv) -> WS m [Element] -> WS m [Element]
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env { envParaProperties :: EnvProps
envParaProperties = Maybe Element -> [Element] -> EnvProps
EnvProps (Element -> Maybe Element
forall a. a -> Maybe a
Just Element
prop) [] EnvProps -> EnvProps -> EnvProps
forall a. Semigroup a => a -> a -> a
<> WriterEnv -> EnvProps
envParaProperties WriterEnv
env }) (Bool -> WS m [Element]
forall (m :: * -> *). PandocMonad m => Bool -> WS m [Element]
getParaProps Bool
False)
  [Content]
contents <- WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [(Text, [Text], [(Text, Text)])
-> [Inline] -> (Text, Text) -> Inline
Image (Text, [Text], [(Text, Text)])
attr [Inline]
alt (Text
src,Text
tit)]
  [Content]
captionNode <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Image Caption")
                 (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Block -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> WS m [Content]
blockToOpenXML WriterOptions
opts ([Inline] -> Block
Para [Inline]
alt)
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> WS m [Content]) -> [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$
    Element -> Content
Elem (Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:p" [] ((Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem [Element]
paraProps [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
contents))
    Content -> [Content] -> [Content]
forall a. a -> [a] -> [a]
: [Content]
captionNode
blockToOpenXML' WriterOptions
opts (Para [Inline]
lst)
  | [Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
lst Bool -> Bool -> Bool
&& Bool -> Bool
not (Extension -> WriterOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_empty_paragraphs WriterOptions
opts) = [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return []
  | Bool
otherwise = do
      Bool
isFirstPara <- (WriterState -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stFirstPara
      let displayMathPara :: Bool
displayMathPara = case [Inline]
lst of
                                 [Inline
x] -> Inline -> Bool
isDisplayMath Inline
x
                                 [Inline]
_   -> Bool
False
      [Element]
paraProps <- Bool -> WS m [Element]
forall (m :: * -> *). PandocMonad m => Bool -> WS m [Element]
getParaProps Bool
displayMathPara
      Element
bodyTextStyle <- ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM (ParaStyleName -> WS m Element) -> ParaStyleName -> WS m Element
forall a b. (a -> b) -> a -> b
$ if Bool
isFirstPara
                       then ParaStyleName
"First Paragraph"
                       else ParaStyleName
"Body Text"
      let paraProps' :: [Element]
paraProps' = case [Element]
paraProps of
            []               -> [Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:pPr" [] [Element
bodyTextStyle]]
            [Element]
ps               -> [Element]
ps
      (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s { stFirstPara :: Bool
stFirstPara = Bool
False }
      [Content]
contents <- WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
lst
      [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:p" [] ((Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem [Element]
paraProps' [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
contents)]
blockToOpenXML' WriterOptions
opts (LineBlock [[Inline]]
lns) = WriterOptions -> Block -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> WS m [Content]
blockToOpenXML WriterOptions
opts (Block -> WS m [Content]) -> Block -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ [[Inline]] -> Block
linesToPara [[Inline]]
lns
blockToOpenXML' WriterOptions
_ b :: Block
b@(RawBlock Format
format Text
str)
  | Format
format Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"openxml" = [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [
        CData -> Content
Text (CDataKind -> Text -> Maybe Integer -> CData
CData CDataKind
CDataRaw Text
str Maybe Integer
forall a. Maybe a
Nothing)
      ]
  | Bool
otherwise                  = do
      LogMessage -> ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ReaderT WriterEnv (StateT WriterState m) ())
-> LogMessage -> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ Block -> LogMessage
BlockNotRendered Block
b
      [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return []
blockToOpenXML' WriterOptions
opts (BlockQuote [Block]
blocks) = do
  [Content]
p <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Block Text")
       (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts [Block]
blocks
  ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => WS m ()
setFirstPara
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Content]
p
blockToOpenXML' WriterOptions
opts (CodeBlock attrs :: (Text, [Text], [(Text, Text)])
attrs@(Text
ident, [Text]
_, [(Text, Text)]
_) Text
str) = do
  [Content]
p <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Source Code") (WriterOptions -> Block -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> WS m [Content]
blockToOpenXML WriterOptions
opts (Block -> WS m [Content]) -> Block -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ [Inline] -> Block
Para [(Text, [Text], [(Text, Text)]) -> Text -> Inline
Code (Text, [Text], [(Text, Text)])
attrs Text
str])
  ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => WS m ()
setFirstPara
  Text -> [Content] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
Text -> [Content] -> WS m [Content]
wrapBookmark Text
ident [Content]
p
blockToOpenXML' WriterOptions
_ Block
HorizontalRule = do
  ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => WS m ()
setFirstPara
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [ Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$
    Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:p" [] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" [] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:pict" []
    (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"v:rect" [(Text
"style",Text
"width:0;height:1.5pt"),
                       (Text
"o:hralign",Text
"center"),
                       (Text
"o:hrstd",Text
"t"),(Text
"o:hr",Text
"t")] () ]
blockToOpenXML' WriterOptions
opts (Table (Text, [Text], [(Text, Text)])
_ Caption
blkCapt [ColSpec]
specs TableHead
thead [TableBody]
tbody TableFoot
tfoot) = do
  let ([Inline]
caption, [Alignment]
aligns, [Double]
widths, [[Block]]
headers, [[[Block]]]
rows) = Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> ([Inline], [Alignment], [Double], [[Block]], [[[Block]]])
toLegacyTable Caption
blkCapt [ColSpec]
specs TableHead
thead [TableBody]
tbody TableFoot
tfoot
  ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => WS m ()
setFirstPara
  (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s { stInTable :: Bool
stInTable = Bool
True }
  let captionStr :: Text
captionStr = [Inline] -> Text
forall a. Walkable Inline a => a -> Text
stringify [Inline]
caption
  [Content]
caption' <- if [Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
caption
                 then [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return []
                 else WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Table Caption")
                      (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Block -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> WS m [Content]
blockToOpenXML WriterOptions
opts ([Inline] -> Block
Para [Inline]
caption)
  let alignmentFor :: Alignment -> Element
alignmentFor Alignment
al = Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:jc" [(Text
"w:val",Alignment -> Text
alignmentToString Alignment
al)] ()
  -- Table cells require a <w:p> element, even an empty one!
  -- Not in the spec but in Word 2007, 2010. See #4953. And
  -- apparently the last element must be a <w:p>, see #6983.
  let cellToOpenXML :: (Alignment, [Block])
-> ReaderT WriterEnv (StateT WriterState m) [Content]
cellToOpenXML (Alignment
al, [Block]
cell) = do
        [Content]
es <- Element
-> ReaderT WriterEnv (StateT WriterState m) [Content]
-> ReaderT WriterEnv (StateT WriterState m) [Content]
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withParaProp (Alignment -> Element
alignmentFor Alignment
al) (ReaderT WriterEnv (StateT WriterState m) [Content]
 -> ReaderT WriterEnv (StateT WriterState m) [Content])
-> ReaderT WriterEnv (StateT WriterState m) [Content]
-> ReaderT WriterEnv (StateT WriterState m) [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions
-> [Block] -> ReaderT WriterEnv (StateT WriterState m) [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts [Block]
cell
        [Content] -> ReaderT WriterEnv (StateT WriterState m) [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> ReaderT WriterEnv (StateT WriterState m) [Content])
-> [Content] -> ReaderT WriterEnv (StateT WriterState m) [Content]
forall a b. (a -> b) -> a -> b
$
          case [Element] -> [Element]
forall a. [a] -> [a]
reverse ([Content] -> [Element]
onlyElems [Content]
es) of
            Element
b:Element
e:[Element]
_ | QName -> Text
qName (Element -> QName
elName Element
b) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"bookmarkEnd"
                  , QName -> Text
qName (Element -> QName
elName Element
e) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"p" -> [Content]
es
            Element
e:[Element]
_   | QName -> Text
qName (Element -> QName
elName Element
e) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"p" -> [Content]
es
            [Element]
_ -> [Content]
es [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:p" [] ()]
  [[Content]]
headers' <- ((Alignment, [Block]) -> WS m [Content])
-> [(Alignment, [Block])]
-> ReaderT WriterEnv (StateT WriterState m) [[Content]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Alignment, [Block]) -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
(Alignment, [Block])
-> ReaderT WriterEnv (StateT WriterState m) [Content]
cellToOpenXML ([(Alignment, [Block])]
 -> ReaderT WriterEnv (StateT WriterState m) [[Content]])
-> [(Alignment, [Block])]
-> ReaderT WriterEnv (StateT WriterState m) [[Content]]
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [[Block]] -> [(Alignment, [Block])]
forall a b. [a] -> [b] -> [(a, b)]
zip [Alignment]
aligns [[Block]]
headers
  [[[Content]]]
rows' <- ([[Block]] -> ReaderT WriterEnv (StateT WriterState m) [[Content]])
-> [[[Block]]]
-> ReaderT WriterEnv (StateT WriterState m) [[[Content]]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (((Alignment, [Block]) -> WS m [Content])
-> [(Alignment, [Block])]
-> ReaderT WriterEnv (StateT WriterState m) [[Content]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Alignment, [Block]) -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
(Alignment, [Block])
-> ReaderT WriterEnv (StateT WriterState m) [Content]
cellToOpenXML ([(Alignment, [Block])]
 -> ReaderT WriterEnv (StateT WriterState m) [[Content]])
-> ([[Block]] -> [(Alignment, [Block])])
-> [[Block]]
-> ReaderT WriterEnv (StateT WriterState m) [[Content]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Alignment] -> [[Block]] -> [(Alignment, [Block])]
forall a b. [a] -> [b] -> [(a, b)]
zip [Alignment]
aligns) [[[Block]]]
rows
  Element
compactStyle <- ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Compact"
  let emptyCell' :: [Content]
emptyCell' = [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:p" [] [Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:pPr" [] [Element
compactStyle]]]
  let mkcell :: [Content] -> Element
mkcell [Content]
contents = Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:tc" []
                            ([Content] -> Element) -> [Content] -> Element
forall a b. (a -> b) -> a -> b
$ if [Content] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Content]
contents
                                 then [Content]
emptyCell'
                                 else [Content]
contents
  let mkrow :: [[Content]] -> Element
mkrow [[Content]]
cells =
         Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:tr" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
           ([Content] -> Element) -> [[Content]] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map [Content] -> Element
mkcell [[Content]]
cells
  let textwidth :: Double
textwidth = Double
7920  -- 5.5 in in twips, 1/20 pt
  let fullrow :: Double
fullrow = Double
5000 -- 100% specified in pct
  let (Int
rowwidth :: Int) = Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (Double -> Int) -> Double -> Int
forall a b. (a -> b) -> a -> b
$ Double
fullrow Double -> Double -> Double
forall a. Num a => a -> a -> a
* [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Double]
widths
  let mkgridcol :: Double -> Element
mkgridcol Double
w = Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:gridCol"
                       [(Text
"w:w", Integer -> Text
forall a. Show a => a -> Text
tshow (Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor (Double
textwidth Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
w) :: Integer))] ()
  let hasHeader :: Bool
hasHeader = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ([Block] -> Bool) -> [[Block]] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all [Block] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Block]]
headers
  (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s { stInTable :: Bool
stInTable = Bool
False }
  -- for compatibility with Word <= 2007, we include a val with a bitmask
  -- 0×0020  Apply first row conditional formatting
  -- 0×0040  Apply last row conditional formatting
  -- 0×0080  Apply first column conditional formatting
  -- 0×0100  Apply last column conditional formatting
  -- 0×0200  Do not apply row banding conditional formatting
  -- 0×0400  Do not apply column banding conditional formattin
  let tblLookVal :: Int
      tblLookVal :: Int
tblLookVal = if Bool
hasHeader then Int
0x20 else Int
0
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> WS m [Content]) -> [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$
    [Content]
caption' [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++
    [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$
     Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:tbl" []
      ( Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:tblPr" []
        (   Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:tblStyle" [(Text
"w:val",Text
"Table")] () Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
:
            Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:tblW" [(Text
"w:type", Text
"pct"), (Text
"w:w", Int -> Text
forall a. Show a => a -> Text
tshow Int
rowwidth)] () Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
:
            Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:tblLook" [(Text
"w:firstRow",if Bool
hasHeader then Text
"1" else Text
"0")
                               ,(Text
"w:lastRow",Text
"0")
                               ,(Text
"w:firstColumn",Text
"0")
                               ,(Text
"w:lastColumn",Text
"0")
                               ,(Text
"w:noHBand",Text
"0")
                               ,(Text
"w:noVBand",Text
"0")
                               ,(Text
"w:val", String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> Int -> String
forall r. PrintfType r => String -> r
printf String
"%04x" Int
tblLookVal)
                               ] () Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
:
          [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:tblCaption" [(Text
"w:val", Text
captionStr)] ()
          | Bool -> Bool
not ([Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
caption) ] )
      Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:tblGrid" []
        (if (Double -> Bool) -> [Double] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
==Double
0) [Double]
widths
            then []
            else (Double -> Element) -> [Double] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map Double -> Element
mkgridcol [Double]
widths)
      Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: [ [[Content]] -> Element
mkrow [[Content]]
headers' | Bool
hasHeader ] [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++
      ([[Content]] -> Element) -> [[[Content]]] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map [[Content]] -> Element
mkrow [[[Content]]]
rows'
      )]
blockToOpenXML' WriterOptions
opts Block
el
  | BulletList [[Block]]
lst <- Block
el = ListMarker -> [[Block]] -> WS m [Content]
forall (m :: * -> *) (t :: * -> *).
(PandocMonad m, Traversable t) =>
ListMarker
-> t [Block] -> ReaderT WriterEnv (StateT WriterState m) [Content]
addOpenXMLList ListMarker
BulletMarker [[Block]]
lst
  | OrderedList (Int
start, ListNumberStyle
numstyle, ListNumberDelim
numdelim) [[Block]]
lst <- Block
el
  = ListMarker -> [[Block]] -> WS m [Content]
forall (m :: * -> *) (t :: * -> *).
(PandocMonad m, Traversable t) =>
ListMarker
-> t [Block] -> ReaderT WriterEnv (StateT WriterState m) [Content]
addOpenXMLList (ListNumberStyle -> ListNumberDelim -> Int -> ListMarker
NumberMarker ListNumberStyle
numstyle ListNumberDelim
numdelim Int
start) [[Block]]
lst
  where
    addOpenXMLList :: ListMarker
-> t [Block] -> ReaderT WriterEnv (StateT WriterState m) [Content]
addOpenXMLList ListMarker
marker t [Block]
lst = do
      ListMarker -> WS m ()
forall (m :: * -> *). PandocMonad m => ListMarker -> WS m ()
addList ListMarker
marker
      Int
numid  <- WS m Int
forall (m :: * -> *). PandocMonad m => WS m Int
getNumId
      [Content]
l <- ReaderT WriterEnv (StateT WriterState m) [Content]
-> ReaderT WriterEnv (StateT WriterState m) [Content]
forall (m :: * -> *) a. PandocMonad m => WS m a -> WS m a
asList (ReaderT WriterEnv (StateT WriterState m) [Content]
 -> ReaderT WriterEnv (StateT WriterState m) [Content])
-> ReaderT WriterEnv (StateT WriterState m) [Content]
-> ReaderT WriterEnv (StateT WriterState m) [Content]
forall a b. (a -> b) -> a -> b
$ t [Content] -> [Content]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (t [Content] -> [Content])
-> ReaderT WriterEnv (StateT WriterState m) (t [Content])
-> ReaderT WriterEnv (StateT WriterState m) [Content]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ([Block] -> ReaderT WriterEnv (StateT WriterState m) [Content])
-> t [Block]
-> ReaderT WriterEnv (StateT WriterState m) (t [Content])
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (WriterOptions
-> Int
-> [Block]
-> ReaderT WriterEnv (StateT WriterState m) [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Int -> [Block] -> WS m [Content]
listItemToOpenXML WriterOptions
opts Int
numid) t [Block]
lst
      WS m ()
forall (m :: * -> *). PandocMonad m => WS m ()
setFirstPara
      [Content] -> ReaderT WriterEnv (StateT WriterState m) [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Content]
l
blockToOpenXML' WriterOptions
opts (DefinitionList [([Inline], [[Block]])]
items) = do
  [Content]
l <- [[Content]] -> [Content]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Content]] -> [Content])
-> ReaderT WriterEnv (StateT WriterState m) [[Content]]
-> WS m [Content]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (([Inline], [[Block]]) -> WS m [Content])
-> [([Inline], [[Block]])]
-> ReaderT WriterEnv (StateT WriterState m) [[Content]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (WriterOptions -> ([Inline], [[Block]]) -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> ([Inline], [[Block]]) -> WS m [Content]
definitionListItemToOpenXML WriterOptions
opts) [([Inline], [[Block]])]
items
  ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => WS m ()
setFirstPara
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Content]
l

definitionListItemToOpenXML  :: (PandocMonad m)
                             => WriterOptions -> ([Inline],[[Block]])
                             -> WS m [Content]
definitionListItemToOpenXML :: WriterOptions -> ([Inline], [[Block]]) -> WS m [Content]
definitionListItemToOpenXML WriterOptions
opts ([Inline]
term,[[Block]]
defs) = do
  [Content]
term' <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Definition Term")
           (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Block -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> WS m [Content]
blockToOpenXML WriterOptions
opts ([Inline] -> Block
Para [Inline]
term)
  [Content]
defs' <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Definition")
           (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ [[Content]] -> [Content]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Content]] -> [Content])
-> ReaderT WriterEnv (StateT WriterState m) [[Content]]
-> WS m [Content]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ([Block] -> WS m [Content])
-> [[Block]]
-> ReaderT WriterEnv (StateT WriterState m) [[Content]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts) [[Block]]
defs
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> WS m [Content]) -> [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ [Content]
term' [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
defs'

addList :: (PandocMonad m) => ListMarker -> WS m ()
addList :: ListMarker -> WS m ()
addList ListMarker
marker = do
  [ListMarker]
lists <- (WriterState -> [ListMarker])
-> ReaderT WriterEnv (StateT WriterState m) [ListMarker]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> [ListMarker]
stLists
  (WriterState -> WriterState) -> WS m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> WS m ())
-> (WriterState -> WriterState) -> WS m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ stLists :: [ListMarker]
stLists = [ListMarker]
lists [ListMarker] -> [ListMarker] -> [ListMarker]
forall a. [a] -> [a] -> [a]
++ [ListMarker
marker] }

listItemToOpenXML :: (PandocMonad m)
                  => WriterOptions
                  -> Int -> [Block]
                  -> WS m [Content]
listItemToOpenXML :: WriterOptions -> Int -> [Block] -> WS m [Content]
listItemToOpenXML WriterOptions
_ Int
_ []                  = [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return []
listItemToOpenXML WriterOptions
opts Int
numid (Block
first:[Block]
rest) = do
  Bool
oldInList <- (WriterState -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stInList
  (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ stInList :: Bool
stInList = Bool
True }
  let isListBlock :: Block -> Bool
isListBlock = \case
        BulletList{}  -> Bool
True
        OrderedList{} -> Bool
True
        Block
_             -> Bool
False
  -- Prepend an empty string if the first entry is another
  -- list. Otherwise the outer bullet will disappear.
  let (Block
first', [Block]
rest') = if Block -> Bool
isListBlock Block
first
                           then ([Inline] -> Block
Plain [Text -> Inline
Str Text
""] , Block
firstBlock -> [Block] -> [Block]
forall a. a -> [a] -> [a]
:[Block]
rest)
                           else (Block
first, [Block]
rest)
  [Content]
first'' <- Int -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a. PandocMonad m => Int -> WS m a -> WS m a
withNumId Int
numid (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Block -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> WS m [Content]
blockToOpenXML WriterOptions
opts Block
first'
  -- baseListId is the code for no list marker:
  [Content]
rest''  <- Int -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a. PandocMonad m => Int -> WS m a -> WS m a
withNumId Int
baseListId (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts [Block]
rest'
  (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ stInList :: Bool
stInList = Bool
oldInList }
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> WS m [Content]) -> [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ [Content]
first'' [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Content]
rest''

alignmentToString :: Alignment -> Text
alignmentToString :: Alignment -> Text
alignmentToString Alignment
alignment = case Alignment
alignment of
                                 Alignment
AlignLeft    -> Text
"left"
                                 Alignment
AlignRight   -> Text
"right"
                                 Alignment
AlignCenter  -> Text
"center"
                                 Alignment
AlignDefault -> Text
"left"

-- | Convert a list of inline elements to OpenXML.
inlinesToOpenXML :: PandocMonad m => WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML :: WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
lst = [[Content]] -> [Content]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Content]] -> [Content])
-> ReaderT WriterEnv (StateT WriterState m) [[Content]]
-> WS m [Content]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (Inline -> WS m [Content])
-> [Inline] -> ReaderT WriterEnv (StateT WriterState m) [[Content]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (WriterOptions -> Inline -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> WS m [Content]
inlineToOpenXML WriterOptions
opts) [Inline]
lst

withNumId :: (PandocMonad m) => Int -> WS m a -> WS m a
withNumId :: Int -> WS m a -> WS m a
withNumId Int
numid = (WriterEnv -> WriterEnv) -> WS m a -> WS m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local ((WriterEnv -> WriterEnv) -> WS m a -> WS m a)
-> (WriterEnv -> WriterEnv) -> WS m a -> WS m a
forall a b. (a -> b) -> a -> b
$ \WriterEnv
env -> WriterEnv
env{ envListNumId :: Int
envListNumId = Int
numid }

asList :: (PandocMonad m) => WS m a -> WS m a
asList :: WS m a -> WS m a
asList = (WriterEnv -> WriterEnv) -> WS m a -> WS m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local ((WriterEnv -> WriterEnv) -> WS m a -> WS m a)
-> (WriterEnv -> WriterEnv) -> WS m a -> WS m a
forall a b. (a -> b) -> a -> b
$ \WriterEnv
env -> WriterEnv
env{ envListLevel :: Int
envListLevel = WriterEnv -> Int
envListLevel WriterEnv
env Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }

isStyle :: Element -> Bool
isStyle :: Element -> Bool
isStyle Element
e = [(Text, Text)] -> Text -> Text -> Element -> Bool
isElem [] Text
"w" Text
"rStyle" Element
e Bool -> Bool -> Bool
||
            [(Text, Text)] -> Text -> Text -> Element -> Bool
isElem [] Text
"w" Text
"pStyle" Element
e

getTextProps :: (PandocMonad m) => WS m [Element]
getTextProps :: WS m [Element]
getTextProps = do
  EnvProps
props <- (WriterEnv -> EnvProps)
-> ReaderT WriterEnv (StateT WriterState m) EnvProps
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> EnvProps
envTextProperties
  let squashed :: [Element]
squashed = EnvProps -> [Element]
squashProps EnvProps
props
  [Element] -> WS m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:rPr" [] [Element]
squashed | (Bool -> Bool
not (Bool -> Bool) -> ([Element] -> Bool) -> [Element] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Element] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) [Element]
squashed]

withTextProp :: PandocMonad m => Element -> WS m a -> WS m a
withTextProp :: Element -> WS m a -> WS m a
withTextProp Element
d WS m a
p =
  (WriterEnv -> WriterEnv) -> WS m a -> WS m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env {envTextProperties :: EnvProps
envTextProperties = EnvProps
ep EnvProps -> EnvProps -> EnvProps
forall a. Semigroup a => a -> a -> a
<> WriterEnv -> EnvProps
envTextProperties WriterEnv
env}) WS m a
p
  where ep :: EnvProps
ep = if Element -> Bool
isStyle Element
d then Maybe Element -> [Element] -> EnvProps
EnvProps (Element -> Maybe Element
forall a. a -> Maybe a
Just Element
d) [] else Maybe Element -> [Element] -> EnvProps
EnvProps Maybe Element
forall a. Maybe a
Nothing [Element
d]

withTextPropM :: PandocMonad m => WS m Element -> WS m a -> WS m a
withTextPropM :: WS m Element -> WS m a -> WS m a
withTextPropM WS m Element
md WS m a
p = do
  Element
d <- WS m Element
md
  Element -> WS m a -> WS m a
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withTextProp Element
d WS m a
p

getParaProps :: PandocMonad m => Bool -> WS m [Element]
getParaProps :: Bool -> WS m [Element]
getParaProps Bool
displayMathPara = do
  EnvProps
props <- (WriterEnv -> EnvProps)
-> ReaderT WriterEnv (StateT WriterState m) EnvProps
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> EnvProps
envParaProperties
  Int
listLevel <- (WriterEnv -> Int) -> ReaderT WriterEnv (StateT WriterState m) Int
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Int
envListLevel
  Int
numid <- (WriterEnv -> Int) -> ReaderT WriterEnv (StateT WriterState m) Int
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Int
envListNumId
  let listPr :: [Element]
listPr = [Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:numPr" []
                [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:ilvl" [(Text
"w:val",Int -> Text
forall a. Show a => a -> Text
tshow Int
listLevel)] ()
                , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:numId" [(Text
"w:val",Int -> Text
forall a. Show a => a -> Text
tshow Int
numid)] () ] | Int
listLevel Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
displayMathPara]
  [Element] -> WS m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Element] -> WS m [Element]) -> [Element] -> WS m [Element]
forall a b. (a -> b) -> a -> b
$ case [Element]
listPr [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ EnvProps -> [Element]
squashProps EnvProps
props of
                [] -> []
                [Element]
ps -> [Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:pPr" [] [Element]
ps]

withParaProp :: PandocMonad m => Element -> WS m a -> WS m a
withParaProp :: Element -> WS m a -> WS m a
withParaProp Element
d WS m a
p =
  (WriterEnv -> WriterEnv) -> WS m a -> WS m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env {envParaProperties :: EnvProps
envParaProperties = EnvProps
ep EnvProps -> EnvProps -> EnvProps
forall a. Semigroup a => a -> a -> a
<> WriterEnv -> EnvProps
envParaProperties WriterEnv
env}) WS m a
p
  where ep :: EnvProps
ep = if Element -> Bool
isStyle Element
d then Maybe Element -> [Element] -> EnvProps
EnvProps (Element -> Maybe Element
forall a. a -> Maybe a
Just Element
d) [] else Maybe Element -> [Element] -> EnvProps
EnvProps Maybe Element
forall a. Maybe a
Nothing [Element
d]

withParaPropM :: PandocMonad m => WS m Element -> WS m a -> WS m a
withParaPropM :: WS m Element -> WS m a -> WS m a
withParaPropM WS m Element
md WS m a
p = do
  Element
d <- WS m Element
md
  Element -> WS m a -> WS m a
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withParaProp Element
d WS m a
p

formattedString :: PandocMonad m => Text -> WS m [Element]
formattedString :: Text -> WS m [Element]
formattedString Text
str =
  -- properly handle soft hyphens
  case (Char -> Bool) -> Text -> [Text]
splitTextBy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'\173') Text
str of
      [Text
w] -> Text -> WS m [Element]
forall (m :: * -> *). PandocMonad m => Text -> WS m [Element]
formattedString' Text
w
      [Text]
ws  -> do
         [Element]
sh <- [Element] -> WS m [Element]
forall (m :: * -> *). PandocMonad m => [Element] -> WS m [Element]
formattedRun [Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:softHyphen" [] ()]
         [Element] -> [[Element]] -> [Element]
forall a. [a] -> [[a]] -> [a]
intercalate [Element]
sh ([[Element]] -> [Element])
-> ReaderT WriterEnv (StateT WriterState m) [[Element]]
-> WS m [Element]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> WS m [Element])
-> [Text] -> ReaderT WriterEnv (StateT WriterState m) [[Element]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Text -> WS m [Element]
forall (m :: * -> *). PandocMonad m => Text -> WS m [Element]
formattedString' [Text]
ws

formattedString' :: PandocMonad m => Text -> WS m [Element]
formattedString' :: Text -> WS m [Element]
formattedString' Text
str = do
  Bool
inDel <- (WriterEnv -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Bool
envInDel
  [Element] -> WS m [Element]
forall (m :: * -> *). PandocMonad m => [Element] -> WS m [Element]
formattedRun [ Text -> [(Text, Text)] -> Text -> Element
mktnode (if Bool
inDel then Text
"w:delText" else Text
"w:t")
                 [(Text
"xml:space",Text
"preserve")] (Text -> Text
stripInvalidChars Text
str) ]

formattedRun :: PandocMonad m => [Element] -> WS m [Element]
formattedRun :: [Element] -> WS m [Element]
formattedRun [Element]
els = do
  [Element]
props <- WS m [Element]
forall (m :: * -> *). PandocMonad m => WS m [Element]
getTextProps
  [Element] -> WS m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ [Element]
props [Element] -> [Element] -> [Element]
forall a. [a] -> [a] -> [a]
++ [Element]
els ]

setFirstPara :: PandocMonad m => WS m ()
setFirstPara :: WS m ()
setFirstPara =  (WriterState -> WriterState) -> WS m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> WS m ())
-> (WriterState -> WriterState) -> WS m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s { stFirstPara :: Bool
stFirstPara = Bool
True }

-- | Convert an inline element to OpenXML.
inlineToOpenXML :: PandocMonad m => WriterOptions -> Inline -> WS m [Content]
inlineToOpenXML :: WriterOptions -> Inline -> WS m [Content]
inlineToOpenXML WriterOptions
opts Inline
il = WS m [Content] -> WS m [Content]
forall (m :: * -> *) a. PandocMonad m => WS m a -> WS m a
withDirection (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> Inline -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> WS m [Content]
inlineToOpenXML' WriterOptions
opts Inline
il

inlineToOpenXML' :: PandocMonad m => WriterOptions -> Inline -> WS m [Content]
inlineToOpenXML' :: WriterOptions -> Inline -> WS m [Content]
inlineToOpenXML' WriterOptions
_ (Str Text
str) =
  (Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem ([Element] -> [Content])
-> ReaderT WriterEnv (StateT WriterState m) [Element]
-> WS m [Content]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *). PandocMonad m => Text -> WS m [Element]
formattedString Text
str
inlineToOpenXML' WriterOptions
opts Inline
Space = WriterOptions -> Inline -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> WS m [Content]
inlineToOpenXML WriterOptions
opts (Text -> Inline
Str Text
" ")
inlineToOpenXML' WriterOptions
opts Inline
SoftBreak = WriterOptions -> Inline -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> WS m [Content]
inlineToOpenXML WriterOptions
opts (Text -> Inline
Str Text
" ")
inlineToOpenXML' WriterOptions
opts (Span (Text
"",[Text
"csl-block"],[]) [Inline]
ils) =
  WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
ils
inlineToOpenXML' WriterOptions
opts (Span (Text
"",[Text
"csl-left-margin"],[]) [Inline]
ils) =
  WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
ils
inlineToOpenXML' WriterOptions
opts (Span (Text
"",[Text
"csl-right-inline"],[]) [Inline]
ils) =
   ([Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$
     Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" []
     (Text -> [(Text, Text)] -> Text -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:t"
       [(Text
"xml:space",Text
"preserve")]
       (Text
"\t" :: Text))] [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++)
    ([Content] -> [Content]) -> WS m [Content] -> WS m [Content]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
ils
inlineToOpenXML' WriterOptions
opts (Span (Text
"",[Text
"csl-indent"],[]) [Inline]
ils) =
  WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
ils
inlineToOpenXML' WriterOptions
_ (Span (Text
ident,[Text
"comment-start"],[(Text, Text)]
kvs) [Inline]
ils) = do
  -- prefer the "id" in kvs, since that is the one produced by the docx
  -- reader.
  let ident' :: Text
ident' = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
ident (Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"id" [(Text, Text)]
kvs)
      kvs' :: [(Text, Text)]
kvs' = ((Text, Text) -> Bool) -> [(Text, Text)] -> [(Text, Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Text
"id" Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/=) (Text -> Bool) -> ((Text, Text) -> Text) -> (Text, Text) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> Text
forall a b. (a, b) -> a
fst) [(Text, Text)]
kvs
  (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ stComments :: [([(Text, Text)], [Inline])]
stComments = ((Text
"id",Text
ident')(Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
:[(Text, Text)]
kvs', [Inline]
ils) ([(Text, Text)], [Inline])
-> [([(Text, Text)], [Inline])] -> [([(Text, Text)], [Inline])]
forall a. a -> [a] -> [a]
: WriterState -> [([(Text, Text)], [Inline])]
stComments WriterState
st }
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [ Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:commentRangeStart" [(Text
"w:id", Text
ident')] () ]
inlineToOpenXML' WriterOptions
_ (Span (Text
ident,[Text
"comment-end"],[(Text, Text)]
kvs) [Inline]
_) =
  -- prefer the "id" in kvs, since that is the one produced by the docx
  -- reader.
  let ident' :: Text
ident' = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
ident (Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"id" [(Text, Text)]
kvs)
  in [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> WS m [Content])
-> ([Element] -> [Content]) -> [Element] -> WS m [Content]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem ([Element] -> WS m [Content]) -> [Element] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$
     [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:commentRangeEnd" [(Text
"w:id", Text
ident')] ()
     , Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" []
       [ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:rPr" []
         [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:rStyle" [(Text
"w:val", Text
"CommentReference")] () ]
       , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:commentReference" [(Text
"w:id", Text
ident')] () ]
     ]
inlineToOpenXML' WriterOptions
opts (Span (Text
ident,[Text]
classes,[(Text, Text)]
kvs) [Inline]
ils) = do
  WS m [Content] -> WS m [Content]
stylemod <- case Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
dynamicStyleKey [(Text, Text)]
kvs of
                   Just (String -> CharStyleName
forall a. IsString a => String -> a
fromString (String -> CharStyleName)
-> (Text -> String) -> Text -> CharStyleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack -> CharStyleName
sty) -> do
                      (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s ->
                        WriterState
s{stDynamicTextProps :: Set CharStyleName
stDynamicTextProps = CharStyleName -> Set CharStyleName -> Set CharStyleName
forall a. Ord a => a -> Set a -> Set a
Set.insert CharStyleName
sty
                              (WriterState -> Set CharStyleName
stDynamicTextProps WriterState
s)}
                      (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return ((WS m [Content] -> WS m [Content])
 -> ReaderT
      WriterEnv
      (StateT WriterState m)
      (WS m [Content] -> WS m [Content]))
-> (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall a b. (a -> b) -> a -> b
$ WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withTextPropM (CharStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
CharStyleName -> WS m Element
rStyleM CharStyleName
sty)
                   Maybe Text
_ -> (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return WS m [Content] -> WS m [Content]
forall a. a -> a
id
  let dirmod :: ReaderT WriterEnv (StateT WriterState m) a
-> ReaderT WriterEnv (StateT WriterState m) a
dirmod = case Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"dir" [(Text, Text)]
kvs of
                 Just Text
"rtl" -> (WriterEnv -> WriterEnv)
-> ReaderT WriterEnv (StateT WriterState m) a
-> ReaderT WriterEnv (StateT WriterState m) a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env { envRTL :: Bool
envRTL = Bool
True })
                 Just Text
"ltr" -> (WriterEnv -> WriterEnv)
-> ReaderT WriterEnv (StateT WriterState m) a
-> ReaderT WriterEnv (StateT WriterState m) a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env { envRTL :: Bool
envRTL = Bool
False })
                 Maybe Text
_          -> ReaderT WriterEnv (StateT WriterState m) a
-> ReaderT WriterEnv (StateT WriterState m) a
forall a. a -> a
id
      off :: Text -> WS m a -> WS m a
off Text
x = Element -> WS m a -> WS m a
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withTextProp (Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
x [(Text
"w:val",Text
"0")] ())
      pmod :: WS m a -> WS m a
pmod =  (if Text
"csl-no-emph" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes then Text -> WS m a -> WS m a
forall (m :: * -> *) a. PandocMonad m => Text -> WS m a -> WS m a
off Text
"w:i" else WS m a -> WS m a
forall a. a -> a
id) (WS m a -> WS m a) -> (WS m a -> WS m a) -> WS m a -> WS m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              (if Text
"csl-no-strong" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes then Text -> WS m a -> WS m a
forall (m :: * -> *) a. PandocMonad m => Text -> WS m a -> WS m a
off Text
"w:b" else WS m a -> WS m a
forall a. a -> a
id) (WS m a -> WS m a) -> (WS m a -> WS m a) -> WS m a -> WS m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              (if Text
"csl-no-smallcaps" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes
                  then Text -> WS m a -> WS m a
forall (m :: * -> *) a. PandocMonad m => Text -> WS m a -> WS m a
off Text
"w:smallCaps"
                  else WS m a -> WS m a
forall a. a -> a
id)
      getChangeAuthorDate :: ReaderT WriterEnv (StateT WriterState m) [(Text, Text)]
getChangeAuthorDate = do
        Text
defaultAuthor <- (WriterEnv -> Text)
-> ReaderT WriterEnv (StateT WriterState m) Text
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Text
envChangesAuthor
        let author :: Text
author = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
defaultAuthor (Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"author" [(Text, Text)]
kvs)
        let mdate :: Maybe Text
mdate = Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"date" [(Text, Text)]
kvs
        [(Text, Text)]
-> ReaderT WriterEnv (StateT WriterState m) [(Text, Text)]
forall (m :: * -> *) a. Monad m => a -> m a
return ([(Text, Text)]
 -> ReaderT WriterEnv (StateT WriterState m) [(Text, Text)])
-> [(Text, Text)]
-> ReaderT WriterEnv (StateT WriterState m) [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ (Text
"w: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
"w:date", Text
date)]) Maybe Text
mdate
  WS m [Content] -> WS m [Content]
insmod <- if Text
"insertion" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes
               then do
                 [(Text, Text)]
changeAuthorDate <- ReaderT WriterEnv (StateT WriterState m) [(Text, Text)]
getChangeAuthorDate
                 Int
insId <- (WriterState -> Int)
-> ReaderT WriterEnv (StateT WriterState m) Int
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Int
stInsId
                 (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s{stInsId :: Int
stInsId = Int
insId Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1}
                 (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return ((WS m [Content] -> WS m [Content])
 -> ReaderT
      WriterEnv
      (StateT WriterState m)
      (WS m [Content] -> WS m [Content]))
-> (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall a b. (a -> b) -> a -> b
$ \WS m [Content]
f -> do
                   [Content]
x <- WS m [Content]
f
                   [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$
                           Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:ins"
                             ((Text
"w:id", Int -> Text
forall a. Show a => a -> Text
tshow Int
insId) (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: [(Text, Text)]
changeAuthorDate) [Content]
x]
               else (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return WS m [Content] -> WS m [Content]
forall a. a -> a
id
  WS m [Content] -> WS m [Content]
delmod <- if Text
"deletion" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes
               then do
                 [(Text, Text)]
changeAuthorDate <- ReaderT WriterEnv (StateT WriterState m) [(Text, Text)]
getChangeAuthorDate
                 Int
delId <- (WriterState -> Int)
-> ReaderT WriterEnv (StateT WriterState m) Int
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Int
stDelId
                 (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s{stDelId :: Int
stDelId = Int
delId Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1}
                 (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return ((WS m [Content] -> WS m [Content])
 -> ReaderT
      WriterEnv
      (StateT WriterState m)
      (WS m [Content] -> WS m [Content]))
-> (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall a b. (a -> b) -> a -> b
$ \WS m [Content]
f -> (WriterEnv -> WriterEnv) -> WS m [Content] -> WS m [Content]
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env->WriterEnv
env{envInDel :: Bool
envInDel=Bool
True}) (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ do
                   [Content]
x <- WS m [Content]
f
                   [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:del"
                             ((Text
"w:id", Int -> Text
forall a. Show a => a -> Text
tshow Int
delId) (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: [(Text, Text)]
changeAuthorDate) [Content]
x]
               else (WS m [Content] -> WS m [Content])
-> ReaderT
     WriterEnv (StateT WriterState m) (WS m [Content] -> WS m [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return WS m [Content] -> WS m [Content]
forall a. a -> a
id
  [Content]
contents <- WS m [Content] -> WS m [Content]
insmod (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WS m [Content] -> WS m [Content]
delmod (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WS m [Content] -> WS m [Content]
forall a.
ReaderT WriterEnv (StateT WriterState m) a
-> ReaderT WriterEnv (StateT WriterState m) a
dirmod (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WS m [Content] -> WS m [Content]
stylemod (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WS m [Content] -> WS m [Content]
forall a.
ReaderT WriterEnv (StateT WriterState m) a
-> ReaderT WriterEnv (StateT WriterState m) a
pmod
                     (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
ils
  Text -> [Content] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
Text -> [Content] -> WS m [Content]
wrapBookmark Text
ident [Content]
contents
inlineToOpenXML' WriterOptions
opts (Strong [Inline]
lst) =
  Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withTextProp (Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:b" [] ()) (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$
  Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withTextProp (Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:bCs" [] ()) (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ -- needed for LTR, #6911
  WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
lst
inlineToOpenXML' WriterOptions
opts (Emph [Inline]
lst) =
  Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withTextProp (Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:i" [] ()) (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$
  Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withTextProp (Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:iCs" [] ()) (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$  -- needed for LTR, #6911
  WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
lst
inlineToOpenXML' WriterOptions
opts (Underline [Inline]
lst) =
  Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withTextProp (Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:u" [(Text
"w:val",Text
"single")] ()) (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$
    WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
lst
inlineToOpenXML' WriterOptions
opts (Subscript [Inline]
lst) =
  Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withTextProp (Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:vertAlign" [(Text
"w:val",Text
"subscript")] ())
  (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
lst
inlineToOpenXML' WriterOptions
opts (Superscript [Inline]
lst) =
  Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withTextProp (Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:vertAlign" [(Text
"w:val",Text
"superscript")] ())
  (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
lst
inlineToOpenXML' WriterOptions
opts (SmallCaps [Inline]
lst) =
  Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withTextProp (Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:smallCaps" [] ())
  (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
lst
inlineToOpenXML' WriterOptions
opts (Strikeout [Inline]
lst) =
  Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
Element -> WS m a -> WS m a
withTextProp (Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:strike" [] ())
  (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
lst
inlineToOpenXML' WriterOptions
_ Inline
LineBreak = [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element -> Content
Elem Element
br]
inlineToOpenXML' WriterOptions
_ il :: Inline
il@(RawInline Format
f Text
str)
  | Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"openxml" = [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return
                            [CData -> Content
Text (CDataKind -> Text -> Maybe Integer -> CData
CData CDataKind
CDataRaw Text
str Maybe Integer
forall a. Maybe a
Nothing)]
  | Bool
otherwise             = do
      LogMessage -> ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ReaderT WriterEnv (StateT WriterState m) ())
-> LogMessage -> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ Inline -> LogMessage
InlineNotRendered Inline
il
      [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return []
inlineToOpenXML' WriterOptions
opts (Quoted QuoteType
quoteType [Inline]
lst) =
  WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts ([Inline] -> WS m [Content]) -> [Inline] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ [Text -> Inline
Str Text
open] [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Inline]
lst [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Text -> Inline
Str Text
close]
    where (Text
open, Text
close) = case QuoteType
quoteType of
                            QuoteType
SingleQuote -> (Text
"\x2018", Text
"\x2019")
                            QuoteType
DoubleQuote -> (Text
"\x201C", Text
"\x201D")
inlineToOpenXML' WriterOptions
opts (Math MathType
mathType Text
str) = do
  Bool
-> ReaderT WriterEnv (StateT WriterState m) ()
-> ReaderT WriterEnv (StateT WriterState m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (MathType
mathType MathType -> MathType -> Bool
forall a. Eq a => a -> a -> Bool
== MathType
DisplayMath) ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => WS m ()
setFirstPara
  Either Inline Element
res <- (StateT WriterState m (Either Inline Element)
-> ReaderT WriterEnv (StateT WriterState m) (Either Inline Element)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT WriterState m (Either Inline Element)
 -> ReaderT
      WriterEnv (StateT WriterState m) (Either Inline Element))
-> (m (Either Inline Element)
    -> StateT WriterState m (Either Inline Element))
-> m (Either Inline Element)
-> ReaderT WriterEnv (StateT WriterState m) (Either Inline Element)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Either Inline Element)
-> StateT WriterState m (Either Inline Element)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift) ((DisplayType -> [Exp] -> Element)
-> MathType -> Text -> m (Either Inline Element)
forall (m :: * -> *) a.
PandocMonad m =>
(DisplayType -> [Exp] -> a)
-> MathType -> Text -> m (Either Inline a)
convertMath DisplayType -> [Exp] -> Element
writeOMML MathType
mathType Text
str)
  case Either Inline Element
res of
       Right Element
r -> [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Element -> Element
fromXLElement Element
r]
       Left Inline
il -> WriterOptions -> Inline -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> WS m [Content]
inlineToOpenXML' WriterOptions
opts Inline
il
inlineToOpenXML' WriterOptions
opts (Cite [Citation]
_ [Inline]
lst) = WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
lst
inlineToOpenXML' WriterOptions
opts (Code (Text, [Text], [(Text, Text)])
attrs Text
str) = do
  let alltoktypes :: [TokenType]
alltoktypes = [TokenType
KeywordTok ..]
  [(TokenType, Element)]
tokTypesMap <- (TokenType
 -> ReaderT WriterEnv (StateT WriterState m) (TokenType, Element))
-> [TokenType]
-> ReaderT WriterEnv (StateT WriterState m) [(TokenType, Element)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\TokenType
tt -> (,) TokenType
tt (Element -> (TokenType, Element))
-> WS m Element
-> ReaderT WriterEnv (StateT WriterState m) (TokenType, Element)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CharStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
CharStyleName -> WS m Element
rStyleM (String -> CharStyleName
forall a. IsString a => String -> a
fromString (String -> CharStyleName) -> String -> CharStyleName
forall a b. (a -> b) -> a -> b
$ TokenType -> String
forall a. Show a => a -> String
show TokenType
tt)) [TokenType]
alltoktypes
  let unhighlighted :: WS m [Content]
unhighlighted = ((Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem ([Element] -> [Content])
-> ([[Element]] -> [Element]) -> [[Element]] -> [Content]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Element] -> [[Element]] -> [Element]
forall a. [a] -> [[a]] -> [a]
intercalate [Element
br]) ([[Element]] -> [Content])
-> ReaderT WriterEnv (StateT WriterState m) [[Element]]
-> WS m [Content]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
                       (Text -> ReaderT WriterEnv (StateT WriterState m) [Element])
-> [Text] -> ReaderT WriterEnv (StateT WriterState m) [[Element]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Text -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *). PandocMonad m => Text -> WS m [Element]
formattedString (Text -> [Text]
T.lines Text
str)
      formatOpenXML :: p -> [[(TokenType, t)]] -> [Element]
formatOpenXML p
_fmtOpts = [Element] -> [[Element]] -> [Element]
forall a. [a] -> [[a]] -> [a]
intercalate [Element
br] ([[Element]] -> [Element])
-> ([[(TokenType, t)]] -> [[Element]])
-> [[(TokenType, t)]]
-> [Element]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([(TokenType, t)] -> [Element])
-> [[(TokenType, t)]] -> [[Element]]
forall a b. (a -> b) -> [a] -> [b]
map (((TokenType, t) -> Element) -> [(TokenType, t)] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map (TokenType, t) -> Element
forall t. Node t => (TokenType, t) -> Element
toHlTok)
      toHlTok :: (TokenType, t) -> Element
toHlTok (TokenType
toktype,t
tok) =
        Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" []
          [ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:rPr" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
            Maybe Element -> [Element]
forall a. Maybe a -> [a]
maybeToList (TokenType -> [(TokenType, Element)] -> Maybe Element
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup TokenType
toktype [(TokenType, Element)]
tokTypesMap)
            , Text -> [(Text, Text)] -> t -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:t" [(Text
"xml:space",Text
"preserve")] t
tok ]
  WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withTextPropM (CharStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
CharStyleName -> WS m Element
rStyleM CharStyleName
"Verbatim Char")
    (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ if Maybe Style -> Bool
forall a. Maybe a -> Bool
isNothing (WriterOptions -> Maybe Style
writerHighlightStyle WriterOptions
opts)
          then WS m [Content]
unhighlighted
          else case SyntaxMap
-> (FormatOptions -> [SourceLine] -> [Element])
-> (Text, [Text], [(Text, Text)])
-> Text
-> Either Text [Element]
forall a.
SyntaxMap
-> (FormatOptions -> [SourceLine] -> a)
-> (Text, [Text], [(Text, Text)])
-> Text
-> Either Text a
highlight (WriterOptions -> SyntaxMap
writerSyntaxMap WriterOptions
opts)
                      FormatOptions -> [SourceLine] -> [Element]
forall t p. Node t => p -> [[(TokenType, t)]] -> [Element]
formatOpenXML (Text, [Text], [(Text, Text)])
attrs Text
str of
                    Right [Element]
h  -> [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return ((Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem [Element]
h)
                    Left Text
msg -> do
                      Bool
-> ReaderT WriterEnv (StateT WriterState m) ()
-> ReaderT WriterEnv (StateT WriterState m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Bool
T.null Text
msg) (ReaderT WriterEnv (StateT WriterState m) ()
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> ReaderT WriterEnv (StateT WriterState m) ()
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ LogMessage -> ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ReaderT WriterEnv (StateT WriterState m) ())
-> LogMessage -> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ Text -> LogMessage
CouldNotHighlight Text
msg
                      WS m [Content]
unhighlighted
inlineToOpenXML' WriterOptions
opts (Note [Block]
bs) = do
  [Element]
notes <- (WriterState -> [Element])
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> [Element]
stFootnotes
  Text
notenum <- ReaderT WriterEnv (StateT WriterState m) Text
forall (m :: * -> *). PandocMonad m => WS m Text
getUniqueId
  Element
footnoteStyle <- CharStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
CharStyleName -> WS m Element
rStyleM CharStyleName
"Footnote Reference"
  let notemarker :: Element
notemarker = Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" []
                   [ Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:rPr" [] Element
footnoteStyle
                   , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:footnoteRef" [] () ]
  let notemarkerXml :: Inline
notemarkerXml = Format -> Text -> Inline
RawInline (Text -> Format
Format Text
"openxml") (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ Element -> Text
ppElement Element
notemarker
  let insertNoteRef :: [Block] -> [Block]
insertNoteRef (Plain [Inline]
ils : [Block]
xs) = [Inline] -> Block
Plain (Inline
notemarkerXml Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: Inline
Space Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline]
ils) Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
: [Block]
xs
      insertNoteRef (Para [Inline]
ils  : [Block]
xs) = [Inline] -> Block
Para  (Inline
notemarkerXml Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: Inline
Space Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline]
ils) Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
: [Block]
xs
      insertNoteRef [Block]
xs               = [Inline] -> Block
Para [Inline
notemarkerXml] Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
: [Block]
xs

  [Content]
contents <- (WriterEnv -> WriterEnv) -> WS m [Content] -> WS m [Content]
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env{ envListLevel :: Int
envListLevel = -Int
1
                                , envParaProperties :: EnvProps
envParaProperties = EnvProps
forall a. Monoid a => a
mempty
                                , envTextProperties :: EnvProps
envTextProperties = EnvProps
forall a. Monoid a => a
mempty })
              (WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withParaPropM (ParaStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
ParaStyleName -> WS m Element
pStyleM ParaStyleName
"Footnote Text") (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Block] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> WS m [Content]
blocksToOpenXML WriterOptions
opts
                ([Block] -> WS m [Content]) -> [Block] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ [Block] -> [Block]
insertNoteRef [Block]
bs)
  let newnote :: Element
newnote = Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:footnote" [(Text
"w:id", Text
notenum)] [Content]
contents
  (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s{ stFootnotes :: [Element]
stFootnotes = Element
newnote Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: [Element]
notes }
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [ Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" []
           [ Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:rPr" [] Element
footnoteStyle
           , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:footnoteReference" [(Text
"w:id", Text
notenum)] () ] ]
-- internal link:
inlineToOpenXML' WriterOptions
opts (Link (Text, [Text], [(Text, Text)])
_ [Inline]
txt (Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'#', Text
xs),Text
_)) = do
  [Content]
contents <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withTextPropM (CharStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
CharStyleName -> WS m Element
rStyleM CharStyleName
"Hyperlink") (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
txt
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return
    [ Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:hyperlink" [(Text
"w:anchor", Text -> Text
toBookmarkName Text
xs)] [Content]
contents ]
-- external link:
inlineToOpenXML' WriterOptions
opts (Link (Text, [Text], [(Text, Text)])
_ [Inline]
txt (Text
src,Text
_)) = do
  [Content]
contents <- WS m Element -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a.
PandocMonad m =>
WS m Element -> WS m a -> WS m a
withTextPropM (CharStyleName -> WS m Element
forall (m :: * -> *).
PandocMonad m =>
CharStyleName -> WS m Element
rStyleM CharStyleName
"Hyperlink") (WS m [Content] -> WS m [Content])
-> WS m [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
txt
  Map Text Text
extlinks <- (WriterState -> Map Text Text)
-> ReaderT WriterEnv (StateT WriterState m) (Map Text Text)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Text Text
stExternalLinks
  Text
id' <- case Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
src Map Text Text
extlinks of
            Just Text
i   -> Text -> ReaderT WriterEnv (StateT WriterState m) Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
i
            Maybe Text
Nothing  -> do
              Text
i <- (Text
"rId" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text)
-> ReaderT WriterEnv (StateT WriterState m) Text
-> ReaderT WriterEnv (StateT WriterState m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT WriterEnv (StateT WriterState m) Text
forall (m :: * -> *). PandocMonad m => WS m Text
getUniqueId
              (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st{ stExternalLinks :: Map Text Text
stExternalLinks =
                        Text -> Text -> Map Text Text -> Map Text Text
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
src Text
i Map Text Text
extlinks }
              Text -> ReaderT WriterEnv (StateT WriterState m) Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
i
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [ Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Content] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:hyperlink" [(Text
"r:id",Text
id')] [Content]
contents ]
inlineToOpenXML' WriterOptions
opts (Image attr :: (Text, [Text], [(Text, Text)])
attr@(Text
imgident, [Text]
_, [(Text, Text)]
_) [Inline]
alt (Text
src, Text
title)) = do
  Integer
pageWidth <- (WriterEnv -> Integer)
-> ReaderT WriterEnv (StateT WriterState m) Integer
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Integer
envPrintWidth
  Map String (String, String, Maybe Text, ByteString)
imgs <- (WriterState
 -> Map String (String, String, Maybe Text, ByteString))
-> ReaderT
     WriterEnv
     (StateT WriterState m)
     (Map String (String, String, Maybe Text, ByteString))
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map String (String, String, Maybe Text, ByteString)
stImages
  let
    stImage :: Maybe (String, String, Maybe Text, ByteString)
stImage = String
-> Map String (String, String, Maybe Text, ByteString)
-> Maybe (String, String, Maybe Text, ByteString)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text -> String
T.unpack Text
src) Map String (String, String, Maybe Text, ByteString)
imgs
    generateImgElt :: (String, b, c, ByteString) -> Element
generateImgElt (String
ident, b
_, c
_, ByteString
img) =
      let
        (Double
xpt,Double
ypt) = WriterOptions
-> (Text, [Text], [(Text, Text)]) -> ImageSize -> (Double, Double)
desiredSizeInPoints WriterOptions
opts (Text, [Text], [(Text, Text)])
attr
               ((Text -> ImageSize)
-> (ImageSize -> ImageSize) -> Either Text ImageSize -> ImageSize
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (ImageSize -> Text -> ImageSize
forall a b. a -> b -> a
const ImageSize
forall a. Default a => a
def) ImageSize -> ImageSize
forall a. a -> a
id (WriterOptions -> ByteString -> Either Text ImageSize
imageSize WriterOptions
opts ByteString
img))
        -- 12700 emu = 1 pt
        (Integer
xemu,Integer
yemu) = (Double, Double) -> Integer -> (Integer, Integer)
fitToPage (Double
xpt Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
12700, Double
ypt Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
12700)
                                (Integer
pageWidth Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
12700)
        cNvPicPr :: Element
cNvPicPr = Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"pic:cNvPicPr" [] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$
                         Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:picLocks" [(Text
"noChangeArrowheads",Text
"1")
                                             ,(Text
"noChangeAspect",Text
"1")] ()
        nvPicPr :: Element
nvPicPr  = Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"pic:nvPicPr" []
                        [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"pic:cNvPr"
                            [(Text
"descr",Text
src),(Text
"id",Text
"0"),(Text
"name",Text
"Picture")] ()
                        , Element
cNvPicPr ]
        blipFill :: Element
blipFill = Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"pic:blipFill" []
          [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:blip" [(Text
"r:embed",String -> Text
T.pack String
ident)] ()
          , Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:stretch" [] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$
              Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:fillRect" [] ()
          ]
        xfrm :: Element
xfrm =    Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:xfrm" []
                        [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:off" [(Text
"x",Text
"0"),(Text
"y",Text
"0")] ()
                        , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:ext" [(Text
"cx",Integer -> Text
forall a. Show a => a -> Text
tshow Integer
xemu)
                                         ,(Text
"cy",Integer -> Text
forall a. Show a => a -> Text
tshow Integer
yemu)] () ]
        prstGeom :: Element
prstGeom = Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:prstGeom" [(Text
"prst",Text
"rect")] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$
                         Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:avLst" [] ()
        ln :: Element
ln =      Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:ln" [(Text
"w",Text
"9525")]
                        [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:noFill" [] ()
                        , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:headEnd" [] ()
                        , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:tailEnd" [] () ]
        spPr :: Element
spPr =    Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"pic:spPr" [(Text
"bwMode",Text
"auto")]
                        [Element
xfrm, Element
prstGeom, Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:noFill" [] (), Element
ln]
        graphic :: Element
graphic = Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:graphic" [] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$
          Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"a:graphicData"
            [(Text
"uri",Text
"http://schemas.openxmlformats.org/drawingml/2006/picture")]
            [ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"pic:pic" []
              [ Element
nvPicPr
              , Element
blipFill
              , Element
spPr
              ]
            ]
        imgElt :: Element
imgElt = Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" [] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$
          Text -> [(Text, Text)] -> Element -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:drawing" [] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$
            Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"wp:inline" []
              [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"wp:extent" [(Text
"cx",Integer -> Text
forall a. Show a => a -> Text
tshow Integer
xemu),(Text
"cy",Integer -> Text
forall a. Show a => a -> Text
tshow Integer
yemu)] ()
              , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"wp:effectExtent"
                [(Text
"b",Text
"0"),(Text
"l",Text
"0"),(Text
"r",Text
"0"),(Text
"t",Text
"0")] ()
              , Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"wp:docPr"
                [ (Text
"descr", [Inline] -> Text
forall a. Walkable Inline a => a -> Text
stringify [Inline]
alt)
                , (Text
"title", Text
title)
                , (Text
"id",Text
"1")
                , (Text
"name",Text
"Picture")
                ] ()
              , Element
graphic
              ]
      in
        Element
imgElt

  Text -> [Content] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
Text -> [Content] -> WS m [Content]
wrapBookmark Text
imgident ([Content] -> WS m [Content]) -> WS m [Content] -> WS m [Content]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< case Maybe (String, String, Maybe Text, ByteString)
stImage of
    Just (String, String, Maybe Text, ByteString)
imgData -> [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ (String, String, Maybe Text, ByteString) -> Element
forall b c. (String, b, c, ByteString) -> Element
generateImgElt (String, String, Maybe Text, ByteString)
imgData]
    Maybe (String, String, Maybe Text, ByteString)
Nothing -> ( do --try
      (ByteString
img, Maybe Text
mt) <- Text
-> ReaderT
     WriterEnv (StateT WriterState m) (ByteString, Maybe Text)
forall (m :: * -> *).
PandocMonad m =>
Text -> m (ByteString, Maybe Text)
P.fetchItem Text
src
      Text
ident <- (Text
"rId" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text)
-> ReaderT WriterEnv (StateT WriterState m) Text
-> ReaderT WriterEnv (StateT WriterState m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT WriterEnv (StateT WriterState m) Text
forall (m :: * -> *). PandocMonad m => WS m Text
getUniqueId

      let
        imgext :: Text
imgext = case Maybe Text
mt Maybe Text -> (Text -> Maybe Text) -> Maybe Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Text
extensionFromMimeType of
          Just Text
x    -> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x
          Maybe Text
Nothing   -> case ByteString -> Maybe ImageType
imageType ByteString
img of
            Just ImageType
Png  -> Text
".png"
            Just ImageType
Jpeg -> Text
".jpeg"
            Just ImageType
Gif  -> Text
".gif"
            Just ImageType
Pdf  -> Text
".pdf"
            Just ImageType
Eps  -> Text
".eps"
            Just ImageType
Svg  -> Text
".svg"
            Just ImageType
Emf  -> Text
".emf"
            Maybe ImageType
Nothing   -> Text
""
        imgpath :: Text
imgpath = Text
"media/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ident Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
imgext
        mbMimeType :: Maybe Text
mbMimeType = Maybe Text
mt Maybe Text -> Maybe Text -> Maybe Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> String -> Maybe Text
getMimeType (Text -> String
T.unpack Text
imgpath)

        imgData :: (String, String, Maybe Text, ByteString)
imgData = (Text -> String
T.unpack Text
ident, Text -> String
T.unpack Text
imgpath, Maybe Text
mbMimeType, ByteString
img)

      if Text -> Bool
T.null Text
imgext
         then -- without an extension there is no rule for content type
           WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
alt -- return alt to avoid corrupted docx
         else do
           -- insert mime type to use in constructing [Content_Types].xml
           (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState)
 -> ReaderT WriterEnv (StateT WriterState m) ())
-> (WriterState -> WriterState)
-> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ \WriterState
st -> WriterState
st { stImages :: Map String (String, String, Maybe Text, ByteString)
stImages = String
-> (String, String, Maybe Text, ByteString)
-> Map String (String, String, Maybe Text, ByteString)
-> Map String (String, String, Maybe Text, ByteString)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (Text -> String
T.unpack Text
src) (String, String, Maybe Text, ByteString)
imgData (Map String (String, String, Maybe Text, ByteString)
 -> Map String (String, String, Maybe Text, ByteString))
-> Map String (String, String, Maybe Text, ByteString)
-> Map String (String, String, Maybe Text, ByteString)
forall a b. (a -> b) -> a -> b
$ WriterState -> Map String (String, String, Maybe Text, ByteString)
stImages WriterState
st }
           [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element -> Content
Elem (Element -> Content) -> Element -> Content
forall a b. (a -> b) -> a -> b
$ (String, String, Maybe Text, ByteString) -> Element
forall b c. (String, b, c, ByteString) -> Element
generateImgElt (String, String, Maybe Text, ByteString)
imgData]
      )
      WS m [Content] -> (PandocError -> WS m [Content]) -> WS m [Content]
forall e (m :: * -> *) a.
MonadError e m =>
m a -> (e -> m a) -> m a
`catchError` ( \PandocError
e -> do
        LogMessage -> ReaderT WriterEnv (StateT WriterState m) ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ReaderT WriterEnv (StateT WriterState m) ())
-> LogMessage -> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$ Text -> Text -> LogMessage
CouldNotFetchResource Text
src (Text -> LogMessage) -> Text -> LogMessage
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (PandocError -> String
forall a. Show a => a -> String
show PandocError
e)
        -- emit alt text
        WriterOptions -> [Inline] -> WS m [Content]
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> WS m [Content]
inlinesToOpenXML WriterOptions
opts [Inline]
alt
      )

br :: Element
br :: Element
br = Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" [] [Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:br" [] ()]

-- Word will insert these footnotes into the settings.xml file
-- (whether or not they're visible in the document). If they're in the
-- file, but not in the footnotes.xml file, it will produce
-- problems. So we want to make sure we insert them into our document.
defaultFootnotes :: [Element]
defaultFootnotes :: [Element]
defaultFootnotes = [ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:footnote"
                     [(Text
"w:type", Text
"separator"), (Text
"w:id", Text
"-1")]
                     [ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:p" []
                       [Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" []
                        [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:separator" [] ()]]]
                   , Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:footnote"
                     [(Text
"w:type", Text
"continuationSeparator"), (Text
"w:id", Text
"0")]
                     [ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:p" []
                       [ Text -> [(Text, Text)] -> [Element] -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:r" []
                         [ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:continuationSeparator" [] ()]]]]


withDirection :: PandocMonad m => WS m a -> WS m a
withDirection :: WS m a -> WS m a
withDirection WS m a
x = do
  Bool
isRTL <- (WriterEnv -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Bool
envRTL
  EnvProps
paraProps <- (WriterEnv -> EnvProps)
-> ReaderT WriterEnv (StateT WriterState m) EnvProps
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> EnvProps
envParaProperties
  EnvProps
textProps <- (WriterEnv -> EnvProps)
-> ReaderT WriterEnv (StateT WriterState m) EnvProps
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> EnvProps
envTextProperties
  -- We want to clean all bidirection (bidi) and right-to-left (rtl)
  -- properties from the props first. This is because we don't want
  -- them to stack up.
  let paraProps' :: [Element]
paraProps' = (Element -> Bool) -> [Element] -> [Element]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Element
e -> (QName -> Text
qName (QName -> Text) -> (Element -> QName) -> Element -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> QName
elName) Element
e Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"bidi") (EnvProps -> [Element]
otherElements EnvProps
paraProps)
      textProps' :: [Element]
textProps' = (Element -> Bool) -> [Element] -> [Element]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Element
e -> (QName -> Text
qName (QName -> Text) -> (Element -> QName) -> Element -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> QName
elName) Element
e Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"rtl") (EnvProps -> [Element]
otherElements EnvProps
textProps)
      paraStyle :: Maybe Element
paraStyle = EnvProps -> Maybe Element
styleElement EnvProps
paraProps
      textStyle :: Maybe Element
textStyle = EnvProps -> Maybe Element
styleElement EnvProps
textProps
  if Bool
isRTL
    -- if we are going right-to-left, we (re?)add the properties.
    then ((WriterEnv -> WriterEnv) -> WS m a -> WS m a)
-> WS m a -> (WriterEnv -> WriterEnv) -> WS m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (WriterEnv -> WriterEnv) -> WS m a -> WS m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local WS m a
x ((WriterEnv -> WriterEnv) -> WS m a)
-> (WriterEnv -> WriterEnv) -> WS m a
forall a b. (a -> b) -> a -> b
$
         \WriterEnv
env -> WriterEnv
env { envParaProperties :: EnvProps
envParaProperties = Maybe Element -> [Element] -> EnvProps
EnvProps Maybe Element
paraStyle ([Element] -> EnvProps) -> [Element] -> EnvProps
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:bidi" [] () Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: [Element]
paraProps'
                     , envTextProperties :: EnvProps
envTextProperties = Maybe Element -> [Element] -> EnvProps
EnvProps Maybe Element
textStyle ([Element] -> EnvProps) -> [Element] -> EnvProps
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:rtl" [] () Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: [Element]
textProps'
                     }
    else ((WriterEnv -> WriterEnv) -> WS m a -> WS m a)
-> WS m a -> (WriterEnv -> WriterEnv) -> WS m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (WriterEnv -> WriterEnv) -> WS m a -> WS m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local WS m a
x ((WriterEnv -> WriterEnv) -> WS m a)
-> (WriterEnv -> WriterEnv) -> WS m a
forall a b. (a -> b) -> a -> b
$ \WriterEnv
env -> WriterEnv
env { envParaProperties :: EnvProps
envParaProperties = Maybe Element -> [Element] -> EnvProps
EnvProps Maybe Element
paraStyle [Element]
paraProps'
                                    , envTextProperties :: EnvProps
envTextProperties = Maybe Element -> [Element] -> EnvProps
EnvProps Maybe Element
textStyle [Element]
textProps'
                                    }

wrapBookmark :: (PandocMonad m) => Text -> [Content] -> WS m [Content]
wrapBookmark :: Text -> [Content] -> WS m [Content]
wrapBookmark Text
"" [Content]
contents = [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return [Content]
contents
wrapBookmark Text
ident [Content]
contents = do
  Text
id' <- WS m Text
forall (m :: * -> *). PandocMonad m => WS m Text
getUniqueId
  let bookmarkStart :: Element
bookmarkStart = Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:bookmarkStart"
                       [(Text
"w:id", Text
id')
                       ,(Text
"w:name", Text -> Text
toBookmarkName Text
ident)] ()
      bookmarkEnd :: Element
bookmarkEnd = Text -> [(Text, Text)] -> () -> Element
forall t. Node t => Text -> [(Text, Text)] -> t -> Element
mknode Text
"w:bookmarkEnd" [(Text
"w:id", Text
id')] ()
  [Content] -> WS m [Content]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> WS m [Content]) -> [Content] -> WS m [Content]
forall a b. (a -> b) -> a -> b
$ Element -> Content
Elem Element
bookmarkStart Content -> [Content] -> [Content]
forall a. a -> [a] -> [a]
: [Content]
contents [Content] -> [Content] -> [Content]
forall a. [a] -> [a] -> [a]
++ [Element -> Content
Elem Element
bookmarkEnd]

-- Word imposes a 40 character limit on bookmark names and requires
-- that they begin with a letter.  So we just use a hash of the
-- identifier when otherwise we'd have an illegal bookmark name.
toBookmarkName :: Text -> Text
toBookmarkName :: Text -> Text
toBookmarkName Text
s
  | Just (Char
c, Text
_) <- Text -> Maybe (Char, Text)
T.uncons Text
s
  , Char -> Bool
isLetter Char
c
  , Text -> Int
T.length Text
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
40 = Text
s
  | Bool
otherwise = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Char
'X' Char -> ShowS
forall a. a -> [a] -> [a]
: Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
1 (Digest SHA1State -> String
forall t. Digest t -> String
showDigest (ByteString -> Digest SHA1State
sha1 (Text -> ByteString
fromTextLazy (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> Text
TL.fromStrict Text
s)))