{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{- |
   Module      : Text.Pandoc.Writers.Powerpoint.Output
   Copyright   : Copyright (C) 2017-2020 Jesse Rosenthal
   License     : GNU GPL, version 2 or above

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

Conversion of Presentation datatype (defined in
Text.Pandoc.Writers.Powerpoint.Presentation) to a zip archive.
-}

module Text.Pandoc.Writers.Powerpoint.Output ( presentationToArchive
                                             ) where

import Control.Monad.Except (throwError, catchError)
import Control.Monad.Reader
import Control.Monad.State
import Codec.Archive.Zip
import Data.Char (toUpper)
import Data.List (intercalate, stripPrefix, nub, union, isPrefixOf, intersperse)
import Data.Default
import qualified Data.Text as T
import Data.Time (formatTime, defaultTimeLocale)
import Data.Time.Clock (UTCTime)
import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds, posixSecondsToUTCTime)
import System.FilePath.Posix (splitDirectories, splitExtension, takeExtension)
import Text.XML.Light
import Text.Pandoc.Definition
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Error (PandocError(..))
import qualified Text.Pandoc.Class.PandocMonad as P
import Text.Pandoc.Options
import Text.Pandoc.MIME
import qualified Data.ByteString.Lazy as BL
import Text.Pandoc.Writers.OOXML
import qualified Data.Map as M
import Data.Maybe (mapMaybe, listToMaybe, fromMaybe, maybeToList, catMaybes, isJust)
import Text.Pandoc.ImageSize
import Control.Applicative ((<|>))
import System.FilePath.Glob
import Text.DocTemplates (FromContext(lookupContext))
import Text.TeXMath
import Text.Pandoc.Writers.Math (convertMath)
import Text.Pandoc.Writers.Powerpoint.Presentation
import Skylighting (fromColor)

-- |The 'EMU' type is used to specify sizes in English Metric Units.
type EMU = Integer

-- |The 'pixelsToEmu' function converts a size in pixels to one
-- in English Metric Units. It assumes a DPI of 72.
pixelsToEmu :: Pixels -> EMU
pixelsToEmu :: Pixels -> Pixels
pixelsToEmu = (Pixels
12700 Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
*)

-- This populates the global ids map with images already in the
-- template, so the ids won't be used by images introduced by the
-- user.
initialGlobalIds :: Archive -> Archive -> M.Map FilePath Int
initialGlobalIds :: Archive -> Archive -> Map FilePath Int
initialGlobalIds Archive
refArchive Archive
distArchive =
  let archiveFiles :: [FilePath]
archiveFiles = Archive -> [FilePath]
filesInArchive Archive
refArchive [FilePath] -> [FilePath] -> [FilePath]
forall a. Eq a => [a] -> [a] -> [a]
`union` Archive -> [FilePath]
filesInArchive Archive
distArchive
      mediaPaths :: [FilePath]
mediaPaths = (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf FilePath
"ppt/media/image") [FilePath]
archiveFiles

      go :: FilePath -> Maybe (FilePath, Int)
      go :: FilePath -> Maybe (FilePath, Int)
go FilePath
fp = do
        FilePath
s <- FilePath -> FilePath -> Maybe FilePath
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix FilePath
"ppt/media/image" (FilePath -> Maybe FilePath) -> FilePath -> Maybe FilePath
forall a b. (a -> b) -> a -> b
$ (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> a
fst ((FilePath, FilePath) -> FilePath)
-> (FilePath, FilePath) -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> (FilePath, FilePath)
splitExtension FilePath
fp
        (Int
n, FilePath
_) <- [(Int, FilePath)] -> Maybe (Int, FilePath)
forall a. [a] -> Maybe a
listToMaybe ([(Int, FilePath)] -> Maybe (Int, FilePath))
-> [(Int, FilePath)] -> Maybe (Int, FilePath)
forall a b. (a -> b) -> a -> b
$ ReadS Int
forall a. Read a => ReadS a
reads FilePath
s
        (FilePath, Int) -> Maybe (FilePath, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
fp, Int
n)
  in
    [(FilePath, Int)] -> Map FilePath Int
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(FilePath, Int)] -> Map FilePath Int)
-> [(FilePath, Int)] -> Map FilePath Int
forall a b. (a -> b) -> a -> b
$ (FilePath -> Maybe (FilePath, Int))
-> [FilePath] -> [(FilePath, Int)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe FilePath -> Maybe (FilePath, Int)
go [FilePath]
mediaPaths

getPresentationSize :: Archive -> Archive -> Maybe (Integer, Integer)
getPresentationSize :: Archive -> Archive -> Maybe (Pixels, Pixels)
getPresentationSize Archive
refArchive Archive
distArchive = do
  Entry
entry <- FilePath -> Archive -> Maybe Entry
findEntryByPath FilePath
"ppt/presentation.xml" Archive
refArchive  Maybe Entry -> Maybe Entry -> Maybe Entry
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
           FilePath -> Archive -> Maybe Entry
findEntryByPath FilePath
"ppt/presentation.xml" Archive
distArchive
  Element
presElement <- FilePath -> Maybe Element
forall s. XmlSource s => s -> Maybe Element
parseXMLDoc (FilePath -> Maybe Element) -> FilePath -> Maybe Element
forall a b. (a -> b) -> a -> b
$ ByteString -> FilePath
UTF8.toStringLazy (ByteString -> FilePath) -> ByteString -> FilePath
forall a b. (a -> b) -> a -> b
$ Entry -> ByteString
fromEntry Entry
entry
  let ns :: NameSpaces
ns = Element -> NameSpaces
elemToNameSpaces Element
presElement
  Element
sldSize <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"sldSz") Element
presElement
  FilePath
cxS <- QName -> Element -> Maybe FilePath
findAttr (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"cx" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
sldSize
  FilePath
cyS <- QName -> Element -> Maybe FilePath
findAttr (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"cy" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
sldSize
  (Pixels
cx, FilePath
_) <- [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a. [a] -> Maybe a
listToMaybe ([(Pixels, FilePath)] -> Maybe (Pixels, FilePath))
-> [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a b. (a -> b) -> a -> b
$ ReadS Pixels
forall a. Read a => ReadS a
reads FilePath
cxS :: Maybe (Integer, String)
  (Pixels
cy, FilePath
_) <- [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a. [a] -> Maybe a
listToMaybe ([(Pixels, FilePath)] -> Maybe (Pixels, FilePath))
-> [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a b. (a -> b) -> a -> b
$ ReadS Pixels
forall a. Read a => ReadS a
reads FilePath
cyS :: Maybe (Integer, String)
  (Pixels, Pixels) -> Maybe (Pixels, Pixels)
forall (m :: * -> *) a. Monad m => a -> m a
return (Pixels
cx Pixels -> Pixels -> Pixels
forall a. Integral a => a -> a -> a
`div` Pixels
12700, Pixels
cy Pixels -> Pixels -> Pixels
forall a. Integral a => a -> a -> a
`div` Pixels
12700)

data WriterEnv = WriterEnv { WriterEnv -> Archive
envRefArchive :: Archive
                           , WriterEnv -> Archive
envDistArchive :: Archive
                           , WriterEnv -> UTCTime
envUTCTime :: UTCTime
                           , WriterEnv -> WriterOptions
envOpts :: WriterOptions
                           , WriterEnv -> (Pixels, Pixels)
envPresentationSize :: (Integer, Integer)
                           , WriterEnv -> Bool
envSlideHasHeader :: Bool
                           , WriterEnv -> Bool
envInList :: Bool
                           , WriterEnv -> Bool
envInNoteSlide :: Bool
                           , WriterEnv -> Int
envCurSlideId :: Int
                           -- the difference between the number at
                           -- the end of the slide file name and
                           -- the rId number
                           , WriterEnv -> Int
envSlideIdOffset :: Int
                           , WriterEnv -> ContentType
envContentType :: ContentType
                           , WriterEnv -> Map SlideId Int
envSlideIdMap :: M.Map SlideId Int
                           -- maps the slide number to the
                           -- corresponding notes id number. If there
                           -- are no notes for a slide, there will be
                           -- no entry in the map for it.
                           , WriterEnv -> Map Int Int
envSpeakerNotesIdMap :: M.Map Int Int
                           , WriterEnv -> Bool
envInSpeakerNotes :: Bool
                           }
                 deriving (Int -> WriterEnv -> ShowS
[WriterEnv] -> ShowS
WriterEnv -> FilePath
(Int -> WriterEnv -> ShowS)
-> (WriterEnv -> FilePath)
-> ([WriterEnv] -> ShowS)
-> Show WriterEnv
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [WriterEnv] -> ShowS
$cshowList :: [WriterEnv] -> ShowS
show :: WriterEnv -> FilePath
$cshow :: WriterEnv -> FilePath
showsPrec :: Int -> WriterEnv -> ShowS
$cshowsPrec :: Int -> WriterEnv -> ShowS
Show)

instance Default WriterEnv where
  def :: WriterEnv
def = WriterEnv :: Archive
-> Archive
-> UTCTime
-> WriterOptions
-> (Pixels, Pixels)
-> Bool
-> Bool
-> Bool
-> Int
-> Int
-> ContentType
-> Map SlideId Int
-> Map Int Int
-> Bool
-> WriterEnv
WriterEnv { envRefArchive :: Archive
envRefArchive = Archive
emptyArchive
                  , envDistArchive :: Archive
envDistArchive = Archive
emptyArchive
                  , envUTCTime :: UTCTime
envUTCTime = POSIXTime -> UTCTime
posixSecondsToUTCTime POSIXTime
0
                  , envOpts :: WriterOptions
envOpts = WriterOptions
forall a. Default a => a
def
                  , envPresentationSize :: (Pixels, Pixels)
envPresentationSize = (Pixels
720, Pixels
540)
                  , envSlideHasHeader :: Bool
envSlideHasHeader = Bool
False
                  , envInList :: Bool
envInList = Bool
False
                  , envInNoteSlide :: Bool
envInNoteSlide = Bool
False
                  , envCurSlideId :: Int
envCurSlideId = Int
1
                  , envSlideIdOffset :: Int
envSlideIdOffset = Int
1
                  , envContentType :: ContentType
envContentType = ContentType
NormalContent
                  , envSlideIdMap :: Map SlideId Int
envSlideIdMap = Map SlideId Int
forall a. Monoid a => a
mempty
                  , envSpeakerNotesIdMap :: Map Int Int
envSpeakerNotesIdMap = Map Int Int
forall a. Monoid a => a
mempty
                  , envInSpeakerNotes :: Bool
envInSpeakerNotes = Bool
False
                  }

data ContentType = NormalContent
                 | TwoColumnLeftContent
                 | TwoColumnRightContent
                 deriving (Int -> ContentType -> ShowS
[ContentType] -> ShowS
ContentType -> FilePath
(Int -> ContentType -> ShowS)
-> (ContentType -> FilePath)
-> ([ContentType] -> ShowS)
-> Show ContentType
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ContentType] -> ShowS
$cshowList :: [ContentType] -> ShowS
show :: ContentType -> FilePath
$cshow :: ContentType -> FilePath
showsPrec :: Int -> ContentType -> ShowS
$cshowsPrec :: Int -> ContentType -> ShowS
Show, ContentType -> ContentType -> Bool
(ContentType -> ContentType -> Bool)
-> (ContentType -> ContentType -> Bool) -> Eq ContentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContentType -> ContentType -> Bool
$c/= :: ContentType -> ContentType -> Bool
== :: ContentType -> ContentType -> Bool
$c== :: ContentType -> ContentType -> Bool
Eq)

data MediaInfo = MediaInfo { MediaInfo -> FilePath
mInfoFilePath :: FilePath
                           , MediaInfo -> Int
mInfoLocalId  :: Int
                           , MediaInfo -> Int
mInfoGlobalId :: Int
                           , MediaInfo -> Maybe MimeType
mInfoMimeType :: Maybe MimeType
                           , MediaInfo -> Maybe MimeType
mInfoExt      :: Maybe T.Text
                           , MediaInfo -> Bool
mInfoCaption  :: Bool
                           } deriving (Int -> MediaInfo -> ShowS
[MediaInfo] -> ShowS
MediaInfo -> FilePath
(Int -> MediaInfo -> ShowS)
-> (MediaInfo -> FilePath)
-> ([MediaInfo] -> ShowS)
-> Show MediaInfo
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [MediaInfo] -> ShowS
$cshowList :: [MediaInfo] -> ShowS
show :: MediaInfo -> FilePath
$cshow :: MediaInfo -> FilePath
showsPrec :: Int -> MediaInfo -> ShowS
$cshowsPrec :: Int -> MediaInfo -> ShowS
Show, MediaInfo -> MediaInfo -> Bool
(MediaInfo -> MediaInfo -> Bool)
-> (MediaInfo -> MediaInfo -> Bool) -> Eq MediaInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediaInfo -> MediaInfo -> Bool
$c/= :: MediaInfo -> MediaInfo -> Bool
== :: MediaInfo -> MediaInfo -> Bool
$c== :: MediaInfo -> MediaInfo -> Bool
Eq)

data WriterState = WriterState { WriterState -> Map Int (Map Int LinkTarget)
stLinkIds :: M.Map Int (M.Map Int LinkTarget)
                               -- (FP, Local ID, Global ID, Maybe Mime)
                               , WriterState -> Map Int [MediaInfo]
stMediaIds :: M.Map Int [MediaInfo]
                               , WriterState -> Map FilePath Int
stMediaGlobalIds :: M.Map FilePath Int
                               } deriving (Int -> WriterState -> ShowS
[WriterState] -> ShowS
WriterState -> FilePath
(Int -> WriterState -> ShowS)
-> (WriterState -> FilePath)
-> ([WriterState] -> ShowS)
-> Show WriterState
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [WriterState] -> ShowS
$cshowList :: [WriterState] -> ShowS
show :: WriterState -> FilePath
$cshow :: WriterState -> FilePath
showsPrec :: Int -> WriterState -> ShowS
$cshowsPrec :: Int -> WriterState -> ShowS
Show, WriterState -> WriterState -> Bool
(WriterState -> WriterState -> Bool)
-> (WriterState -> WriterState -> Bool) -> Eq WriterState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WriterState -> WriterState -> Bool
$c/= :: WriterState -> WriterState -> Bool
== :: WriterState -> WriterState -> Bool
$c== :: WriterState -> WriterState -> Bool
Eq)

instance Default WriterState where
  def :: WriterState
def = WriterState :: Map Int (Map Int LinkTarget)
-> Map Int [MediaInfo] -> Map FilePath Int -> WriterState
WriterState { stLinkIds :: Map Int (Map Int LinkTarget)
stLinkIds = Map Int (Map Int LinkTarget)
forall a. Monoid a => a
mempty
                    , stMediaIds :: Map Int [MediaInfo]
stMediaIds = Map Int [MediaInfo]
forall a. Monoid a => a
mempty
                    , stMediaGlobalIds :: Map FilePath Int
stMediaGlobalIds = Map FilePath Int
forall a. Monoid a => a
mempty
                    }

type P m = ReaderT WriterEnv (StateT WriterState m)

runP :: Monad m => WriterEnv -> WriterState -> P m a -> m a
runP :: WriterEnv -> WriterState -> P m a -> m a
runP WriterEnv
env WriterState
st P m a
p = StateT WriterState m a -> WriterState -> m a
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (P m a -> WriterEnv -> StateT WriterState m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT P m a
p WriterEnv
env) WriterState
st

--------------------------------------------------------------------

findAttrText :: QName -> Element -> Maybe T.Text
findAttrText :: QName -> Element -> Maybe MimeType
findAttrText QName
n = (FilePath -> MimeType) -> Maybe FilePath -> Maybe MimeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> MimeType
T.pack (Maybe FilePath -> Maybe MimeType)
-> (Element -> Maybe FilePath) -> Element -> Maybe MimeType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QName -> Element -> Maybe FilePath
findAttr QName
n

monospaceFont :: Monad m => P m T.Text
monospaceFont :: P m MimeType
monospaceFont = do
  Context MimeType
vars <- WriterOptions -> Context MimeType
writerVariables (WriterOptions -> Context MimeType)
-> ReaderT WriterEnv (StateT WriterState m) WriterOptions
-> ReaderT WriterEnv (StateT WriterState m) (Context MimeType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (WriterEnv -> WriterOptions)
-> ReaderT WriterEnv (StateT WriterState m) WriterOptions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> WriterOptions
envOpts
  case MimeType -> Context MimeType -> Maybe MimeType
forall a b. FromContext a b => MimeType -> Context a -> Maybe b
lookupContext MimeType
"monofont" Context MimeType
vars of
    Just MimeType
s -> MimeType -> P m MimeType
forall (m :: * -> *) a. Monad m => a -> m a
return MimeType
s
    Maybe MimeType
Nothing -> MimeType -> P m MimeType
forall (m :: * -> *) a. Monad m => a -> m a
return MimeType
"Courier"

-- Kept as string for XML.Light
fontSizeAttributes :: Monad m => RunProps -> P m [(String, String)]
fontSizeAttributes :: RunProps -> P m NameSpaces
fontSizeAttributes RunProps { rPropForceSize :: RunProps -> Maybe Pixels
rPropForceSize = Just Pixels
sz } =
  NameSpaces -> P m NameSpaces
forall (m :: * -> *) a. Monad m => a -> m a
return [(FilePath
"sz", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels
sz Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
100)]
fontSizeAttributes RunProps
_ = NameSpaces -> P m NameSpaces
forall (m :: * -> *) a. Monad m => a -> m a
return []

copyFileToArchive :: PandocMonad m => Archive -> FilePath -> P m Archive
copyFileToArchive :: Archive -> FilePath -> P m Archive
copyFileToArchive Archive
arch FilePath
fp = do
  Archive
refArchive <- (WriterEnv -> Archive) -> P m Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envRefArchive
  Archive
distArchive <- (WriterEnv -> Archive) -> P m Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envDistArchive
  case FilePath -> Archive -> Maybe Entry
findEntryByPath FilePath
fp Archive
refArchive Maybe Entry -> Maybe Entry -> Maybe Entry
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` FilePath -> Archive -> Maybe Entry
findEntryByPath FilePath
fp Archive
distArchive of
    Maybe Entry
Nothing -> PandocError -> P m Archive
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> P m Archive) -> PandocError -> P m Archive
forall a b. (a -> b) -> a -> b
$ MimeType -> PandocError
PandocSomeError
                          (MimeType -> PandocError) -> MimeType -> PandocError
forall a b. (a -> b) -> a -> b
$ FilePath -> MimeType
T.pack
                          (FilePath -> MimeType) -> FilePath -> MimeType
forall a b. (a -> b) -> a -> b
$ FilePath
fp FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
" missing in reference file"
    Just Entry
e -> Archive -> P m Archive
forall (m :: * -> *) a. Monad m => a -> m a
return (Archive -> P m Archive) -> Archive -> P m Archive
forall a b. (a -> b) -> a -> b
$ Entry -> Archive -> Archive
addEntryToArchive Entry
e Archive
arch

alwaysInheritedPatterns :: [Pattern]
alwaysInheritedPatterns :: [Pattern]
alwaysInheritedPatterns =
  (FilePath -> Pattern) -> [FilePath] -> [Pattern]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Pattern
compile [ FilePath
"docProps/app.xml"
              , FilePath
"ppt/slideLayouts/slideLayout*.xml"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout*.xml.rels"
              , FilePath
"ppt/slideMasters/slideMaster1.xml"
              , FilePath
"ppt/slideMasters/_rels/slideMaster1.xml.rels"
              , FilePath
"ppt/theme/theme1.xml"
              , FilePath
"ppt/theme/_rels/theme1.xml.rels"
              , FilePath
"ppt/presProps.xml"
              , FilePath
"ppt/tableStyles.xml"
              , FilePath
"ppt/media/image*"
              ]

-- We only look for these under special conditions
contingentInheritedPatterns :: Presentation -> [Pattern]
contingentInheritedPatterns :: Presentation -> [Pattern]
contingentInheritedPatterns Presentation
pres = [] [Pattern] -> [Pattern] -> [Pattern]
forall a. Semigroup a => a -> a -> a
<>
  if Presentation -> Bool
presHasSpeakerNotes Presentation
pres
  then (FilePath -> Pattern) -> [FilePath] -> [Pattern]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Pattern
compile [ FilePath
"ppt/notesMasters/notesMaster*.xml"
                   , FilePath
"ppt/notesMasters/_rels/notesMaster*.xml.rels"
                   , FilePath
"ppt/theme/theme2.xml"
                   , FilePath
"ppt/theme/_rels/theme2.xml.rels"
                   ]
  else []

inheritedPatterns :: Presentation -> [Pattern]
inheritedPatterns :: Presentation -> [Pattern]
inheritedPatterns Presentation
pres =
  [Pattern]
alwaysInheritedPatterns [Pattern] -> [Pattern] -> [Pattern]
forall a. Semigroup a => a -> a -> a
<> Presentation -> [Pattern]
contingentInheritedPatterns Presentation
pres

patternToFilePaths :: PandocMonad m => Pattern -> P m [FilePath]
patternToFilePaths :: Pattern -> P m [FilePath]
patternToFilePaths Pattern
pat = do
  Archive
refArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envRefArchive
  Archive
distArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envDistArchive

  let archiveFiles :: [FilePath]
archiveFiles = Archive -> [FilePath]
filesInArchive Archive
refArchive [FilePath] -> [FilePath] -> [FilePath]
forall a. Eq a => [a] -> [a] -> [a]
`union` Archive -> [FilePath]
filesInArchive Archive
distArchive
  [FilePath] -> P m [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> P m [FilePath]) -> [FilePath] -> P m [FilePath]
forall a b. (a -> b) -> a -> b
$ (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (Pattern -> FilePath -> Bool
match Pattern
pat) [FilePath]
archiveFiles

patternsToFilePaths :: PandocMonad m => [Pattern] -> P m [FilePath]
patternsToFilePaths :: [Pattern] -> P m [FilePath]
patternsToFilePaths [Pattern]
pats = [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FilePath]] -> [FilePath])
-> ReaderT WriterEnv (StateT WriterState m) [[FilePath]]
-> P m [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Pattern -> P m [FilePath])
-> [Pattern]
-> ReaderT WriterEnv (StateT WriterState m) [[FilePath]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Pattern -> P m [FilePath]
forall (m :: * -> *). PandocMonad m => Pattern -> P m [FilePath]
patternToFilePaths [Pattern]
pats

-- Here are the files we'll require to make a Powerpoint document. If
-- any of these are missing, we should error out of our build.
requiredFiles :: [FilePath]
requiredFiles :: [FilePath]
requiredFiles = [ FilePath
"docProps/app.xml"
                , FilePath
"ppt/presProps.xml"
                , FilePath
"ppt/slideLayouts/slideLayout1.xml"
                , FilePath
"ppt/slideLayouts/_rels/slideLayout1.xml.rels"
                , FilePath
"ppt/slideLayouts/slideLayout2.xml"
                , FilePath
"ppt/slideLayouts/_rels/slideLayout2.xml.rels"
                , FilePath
"ppt/slideLayouts/slideLayout3.xml"
                , FilePath
"ppt/slideLayouts/_rels/slideLayout3.xml.rels"
                , FilePath
"ppt/slideLayouts/slideLayout4.xml"
                , FilePath
"ppt/slideLayouts/_rels/slideLayout4.xml.rels"
                , FilePath
"ppt/slideMasters/slideMaster1.xml"
                , FilePath
"ppt/slideMasters/_rels/slideMaster1.xml.rels"
                , FilePath
"ppt/theme/theme1.xml"
                , FilePath
"ppt/tableStyles.xml"
                ]

presentationToArchiveP :: PandocMonad m => Presentation -> P m Archive
presentationToArchiveP :: Presentation -> P m Archive
presentationToArchiveP p :: Presentation
p@(Presentation DocProps
docProps [Slide]
slides) = do
  [FilePath]
filePaths <- [Pattern] -> P m [FilePath]
forall (m :: * -> *). PandocMonad m => [Pattern] -> P m [FilePath]
patternsToFilePaths ([Pattern] -> P m [FilePath]) -> [Pattern] -> P m [FilePath]
forall a b. (a -> b) -> a -> b
$ Presentation -> [Pattern]
inheritedPatterns Presentation
p

  -- make sure all required files are available:
  let missingFiles :: [FilePath]
missingFiles = (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [FilePath]
filePaths) [FilePath]
requiredFiles
  Bool
-> ReaderT WriterEnv (StateT WriterState m) ()
-> ReaderT WriterEnv (StateT WriterState m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
missingFiles)
    (PandocError -> ReaderT WriterEnv (StateT WriterState m) ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> ReaderT WriterEnv (StateT WriterState m) ())
-> PandocError -> ReaderT WriterEnv (StateT WriterState m) ()
forall a b. (a -> b) -> a -> b
$
      MimeType -> PandocError
PandocSomeError (MimeType -> PandocError) -> MimeType -> PandocError
forall a b. (a -> b) -> a -> b
$
      MimeType
"The following required files are missing:\n" MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<>
      [MimeType] -> MimeType
T.unlines ((FilePath -> MimeType) -> [FilePath] -> [MimeType]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> MimeType
T.pack (FilePath -> MimeType) -> ShowS -> FilePath -> MimeType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
"  " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<>)) [FilePath]
missingFiles)
    )

  Archive
newArch' <- (Archive -> FilePath -> P m Archive)
-> Archive -> [FilePath] -> P m Archive
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM Archive -> FilePath -> P m Archive
forall (m :: * -> *).
PandocMonad m =>
Archive -> FilePath -> P m Archive
copyFileToArchive Archive
emptyArchive [FilePath]
filePaths
  -- we make a modified ppt/viewProps.xml out of the presentation viewProps
  Entry
viewPropsEntry <- P m Entry
forall (m :: * -> *). PandocMonad m => P m Entry
makeViewPropsEntry
  -- we make a docProps/core.xml entry out of the presentation docprops
  Entry
docPropsEntry <- DocProps -> P m Entry
forall (m :: * -> *). PandocMonad m => DocProps -> P m Entry
docPropsToEntry DocProps
docProps
  -- we make a docProps/custom.xml entry out of the custom properties
  Entry
docCustomPropsEntry <- DocProps -> P m Entry
forall (m :: * -> *). PandocMonad m => DocProps -> P m Entry
docCustomPropsToEntry DocProps
docProps
  -- we make this ourself in case there's something unexpected in the
  -- one in the reference doc.
  Entry
relsEntry <- P m Entry
forall (m :: * -> *). PandocMonad m => P m Entry
topLevelRelsEntry
  -- presentation entry and rels. We have to do the rels first to make
  -- sure we know the correct offset for the rIds.
  Entry
presEntry <- Presentation -> P m Entry
forall (m :: * -> *). PandocMonad m => Presentation -> P m Entry
presentationToPresEntry Presentation
p
  Entry
presRelsEntry <- Presentation -> P m Entry
forall (m :: * -> *). PandocMonad m => Presentation -> P m Entry
presentationToRelsEntry Presentation
p
  [Entry]
slideEntries <- (Slide -> P m Entry)
-> [Slide] -> ReaderT WriterEnv (StateT WriterState m) [Entry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Slide -> P m Entry
forall (m :: * -> *). PandocMonad m => Slide -> P m Entry
slideToEntry [Slide]
slides
  [Entry]
slideRelEntries <- (Slide -> P m Entry)
-> [Slide] -> ReaderT WriterEnv (StateT WriterState m) [Entry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Slide -> P m Entry
forall (m :: * -> *). PandocMonad m => Slide -> P m Entry
slideToSlideRelEntry [Slide]
slides
  [Entry]
spkNotesEntries <- [Maybe Entry] -> [Entry]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Entry] -> [Entry])
-> ReaderT WriterEnv (StateT WriterState m) [Maybe Entry]
-> ReaderT WriterEnv (StateT WriterState m) [Entry]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Slide -> ReaderT WriterEnv (StateT WriterState m) (Maybe Entry))
-> [Slide]
-> ReaderT WriterEnv (StateT WriterState m) [Maybe Entry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Slide -> ReaderT WriterEnv (StateT WriterState m) (Maybe Entry)
forall (m :: * -> *). PandocMonad m => Slide -> P m (Maybe Entry)
slideToSpeakerNotesEntry [Slide]
slides
  [Entry]
spkNotesRelEntries <- [Maybe Entry] -> [Entry]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Entry] -> [Entry])
-> ReaderT WriterEnv (StateT WriterState m) [Maybe Entry]
-> ReaderT WriterEnv (StateT WriterState m) [Entry]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Slide -> ReaderT WriterEnv (StateT WriterState m) (Maybe Entry))
-> [Slide]
-> ReaderT WriterEnv (StateT WriterState m) [Maybe Entry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Slide -> ReaderT WriterEnv (StateT WriterState m) (Maybe Entry)
forall (m :: * -> *). PandocMonad m => Slide -> P m (Maybe Entry)
slideToSpeakerNotesRelEntry [Slide]
slides
  -- These have to come after everything, because they need the info
  -- built up in the state.
  [Entry]
mediaEntries <- ReaderT WriterEnv (StateT WriterState m) [Entry]
forall (m :: * -> *). PandocMonad m => P m [Entry]
makeMediaEntries
  Entry
contentTypesEntry <- Presentation -> P m ContentTypes
forall (m :: * -> *).
PandocMonad m =>
Presentation -> P m ContentTypes
presentationToContentTypes Presentation
p P m ContentTypes -> (ContentTypes -> P m Entry) -> P m Entry
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ContentTypes -> P m Entry
forall (m :: * -> *). PandocMonad m => ContentTypes -> P m Entry
contentTypesToEntry
  -- fold everything into our inherited archive and return it.
  Archive -> P m Archive
forall (m :: * -> *) a. Monad m => a -> m a
return (Archive -> P m Archive) -> Archive -> P m Archive
forall a b. (a -> b) -> a -> b
$ (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
newArch' ([Entry] -> Archive) -> [Entry] -> Archive
forall a b. (a -> b) -> a -> b
$
    [Entry]
slideEntries [Entry] -> [Entry] -> [Entry]
forall a. Semigroup a => a -> a -> a
<>
    [Entry]
slideRelEntries [Entry] -> [Entry] -> [Entry]
forall a. Semigroup a => a -> a -> a
<>
    [Entry]
spkNotesEntries [Entry] -> [Entry] -> [Entry]
forall a. Semigroup a => a -> a -> a
<>
    [Entry]
spkNotesRelEntries [Entry] -> [Entry] -> [Entry]
forall a. Semigroup a => a -> a -> a
<>
    [Entry]
mediaEntries [Entry] -> [Entry] -> [Entry]
forall a. Semigroup a => a -> a -> a
<>
    [Entry
contentTypesEntry, Entry
docPropsEntry, Entry
docCustomPropsEntry, Entry
relsEntry,
     Entry
presEntry, Entry
presRelsEntry, Entry
viewPropsEntry]

makeSlideIdMap :: Presentation -> M.Map SlideId Int
makeSlideIdMap :: Presentation -> Map SlideId Int
makeSlideIdMap (Presentation DocProps
_ [Slide]
slides) =
  [(SlideId, Int)] -> Map SlideId Int
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(SlideId, Int)] -> Map SlideId Int)
-> [(SlideId, Int)] -> Map SlideId Int
forall a b. (a -> b) -> a -> b
$ (Slide -> SlideId) -> [Slide] -> [SlideId]
forall a b. (a -> b) -> [a] -> [b]
map Slide -> SlideId
slideId [Slide]
slides [SlideId] -> [Int] -> [(SlideId, Int)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` [Int
1..]

makeSpeakerNotesMap :: Presentation -> M.Map Int Int
makeSpeakerNotesMap :: Presentation -> Map Int Int
makeSpeakerNotesMap (Presentation DocProps
_ [Slide]
slides) =
  [(Int, Int)] -> Map Int Int
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Int, Int)] -> Map Int Int) -> [(Int, Int)] -> Map Int Int
forall a b. (a -> b) -> a -> b
$
    ((Slide, Int) -> Maybe Int) -> [(Slide, Int)] -> [Int]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Slide, Int) -> Maybe Int
forall a. (Slide, a) -> Maybe a
f ([Slide]
slides [Slide] -> [Int] -> [(Slide, Int)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` [Int
1..]) [Int] -> [Int] -> [(Int, Int)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` [Int
1..]
  where f :: (Slide, a) -> Maybe a
f (Slide SlideId
_ Layout
_ SpeakerNotes
notes, a
n) = if SpeakerNotes
notes SpeakerNotes -> SpeakerNotes -> Bool
forall a. Eq a => a -> a -> Bool
== SpeakerNotes
forall a. Monoid a => a
mempty
                                 then Maybe a
forall a. Maybe a
Nothing
                                 else a -> Maybe a
forall a. a -> Maybe a
Just a
n

presentationToArchive :: PandocMonad m => WriterOptions -> Presentation -> m Archive
presentationToArchive :: WriterOptions -> Presentation -> m Archive
presentationToArchive WriterOptions
opts Presentation
pres = do
  Archive
distArchive <- 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
<$>
                      FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
P.readDefaultDataFile FilePath
"reference.pptx"
  Archive
refArchive <- case WriterOptions -> Maybe FilePath
writerReferenceDoc WriterOptions
opts of
                     Just FilePath
f  -> ByteString -> Archive
toArchive (ByteString -> Archive) -> m ByteString -> m Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
P.readFileLazy FilePath
f
                     Maybe FilePath
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
<$>
                        FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
P.readDataFile FilePath
"reference.pptx"

  UTCTime
utctime <- m UTCTime
forall (m :: * -> *). PandocMonad m => m UTCTime
P.getCurrentTime

  (Pixels, Pixels)
presSize <- case Archive -> Archive -> Maybe (Pixels, Pixels)
getPresentationSize Archive
refArchive Archive
distArchive of
                Just (Pixels, Pixels)
sz -> (Pixels, Pixels) -> m (Pixels, Pixels)
forall (m :: * -> *) a. Monad m => a -> m a
return (Pixels, Pixels)
sz
                Maybe (Pixels, Pixels)
Nothing -> PandocError -> m (Pixels, Pixels)
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m (Pixels, Pixels))
-> PandocError -> m (Pixels, Pixels)
forall a b. (a -> b) -> a -> b
$
                           MimeType -> PandocError
PandocSomeError
                           MimeType
"Could not determine presentation size"

  let env :: WriterEnv
env = WriterEnv
forall a. Default a => a
def { envRefArchive :: Archive
envRefArchive = Archive
refArchive
                , envDistArchive :: Archive
envDistArchive = Archive
distArchive
                , envUTCTime :: UTCTime
envUTCTime = UTCTime
utctime
                , envOpts :: WriterOptions
envOpts = WriterOptions
opts
                , envPresentationSize :: (Pixels, Pixels)
envPresentationSize = (Pixels, Pixels)
presSize
                , envSlideIdMap :: Map SlideId Int
envSlideIdMap = Presentation -> Map SlideId Int
makeSlideIdMap Presentation
pres
                , envSpeakerNotesIdMap :: Map Int Int
envSpeakerNotesIdMap = Presentation -> Map Int Int
makeSpeakerNotesMap Presentation
pres
                }

  let st :: WriterState
st = WriterState
forall a. Default a => a
def { stMediaGlobalIds :: Map FilePath Int
stMediaGlobalIds = Archive -> Archive -> Map FilePath Int
initialGlobalIds Archive
refArchive Archive
distArchive
               }

  WriterEnv -> WriterState -> P m Archive -> m Archive
forall (m :: * -> *) a.
Monad m =>
WriterEnv -> WriterState -> P m a -> m a
runP WriterEnv
env WriterState
st (P m Archive -> m Archive) -> P m Archive -> m Archive
forall a b. (a -> b) -> a -> b
$ Presentation -> P m Archive
forall (m :: * -> *). PandocMonad m => Presentation -> P m Archive
presentationToArchiveP Presentation
pres



--------------------------------------------------

-- Check to see if the presentation has speaker notes. This will
-- influence whether we import the notesMaster template.
presHasSpeakerNotes :: Presentation -> Bool
presHasSpeakerNotes :: Presentation -> Bool
presHasSpeakerNotes (Presentation DocProps
_ [Slide]
slides) =
  Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Slide -> Bool) -> [Slide] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((SpeakerNotes
forall a. Monoid a => a
mempty SpeakerNotes -> SpeakerNotes -> Bool
forall a. Eq a => a -> a -> Bool
==) (SpeakerNotes -> Bool) -> (Slide -> SpeakerNotes) -> Slide -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Slide -> SpeakerNotes
slideSpeakerNotes) [Slide]
slides

curSlideHasSpeakerNotes :: PandocMonad m => P m Bool
curSlideHasSpeakerNotes :: P m Bool
curSlideHasSpeakerNotes =
  Int -> Map Int Int -> Bool
forall k a. Ord k => k -> Map k a -> Bool
M.member (Int -> Map Int Int -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Int
-> ReaderT WriterEnv (StateT WriterState m) (Map Int Int -> Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (WriterEnv -> Int) -> ReaderT WriterEnv (StateT WriterState m) Int
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Int
envCurSlideId ReaderT WriterEnv (StateT WriterState m) (Map Int Int -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) (Map Int Int)
-> P m Bool
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (WriterEnv -> Map Int Int)
-> ReaderT WriterEnv (StateT WriterState m) (Map Int Int)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Map Int Int
envSpeakerNotesIdMap

--------------------------------------------------

getLayout :: PandocMonad m => Layout -> P m Element
getLayout :: Layout -> P m Element
getLayout Layout
layout = do
  let layoutpath :: FilePath
layoutpath = case Layout
layout of
        MetadataSlide{}  -> FilePath
"ppt/slideLayouts/slideLayout1.xml"
        TitleSlide{}     -> FilePath
"ppt/slideLayouts/slideLayout3.xml"
        ContentSlide{}   -> FilePath
"ppt/slideLayouts/slideLayout2.xml"
        TwoColumnSlide{} -> FilePath
"ppt/slideLayouts/slideLayout4.xml"
  Archive
refArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envRefArchive
  Archive
distArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envDistArchive
  Archive -> Archive -> FilePath -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> FilePath -> m Element
parseXml Archive
refArchive Archive
distArchive FilePath
layoutpath

shapeHasId :: NameSpaces -> T.Text -> Element -> Bool
shapeHasId :: NameSpaces -> MimeType -> Element -> Bool
shapeHasId NameSpaces
ns MimeType
ident Element
element
  | Just Element
nvSpPr <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"nvSpPr") Element
element
  , Just Element
cNvPr <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"cNvPr") Element
nvSpPr
  , Just MimeType
nm <- QName -> Element -> Maybe MimeType
findAttrText (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"id" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
cNvPr =
      MimeType
nm MimeType -> MimeType -> Bool
forall a. Eq a => a -> a -> Bool
== MimeType
ident
  | Bool
otherwise = Bool
False

getContentShape :: PandocMonad m => NameSpaces -> Element -> P m Element
getContentShape :: NameSpaces -> Element -> P m Element
getContentShape NameSpaces
ns Element
spTreeElem
  | NameSpaces -> FilePath -> FilePath -> Element -> Bool
isElem NameSpaces
ns FilePath
"p" FilePath
"spTree" Element
spTreeElem = do
      ContentType
contentType <- (WriterEnv -> ContentType)
-> ReaderT WriterEnv (StateT WriterState m) ContentType
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> ContentType
envContentType
      let contentShapes :: [Element]
contentShapes = NameSpaces -> Element -> PHType -> [Element]
getShapesByPlaceHolderType NameSpaces
ns Element
spTreeElem PHType
ObjType
      case ContentType
contentType of
        ContentType
NormalContent | (Element
sp : [Element]
_) <- [Element]
contentShapes -> Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return Element
sp
        ContentType
TwoColumnLeftContent | (Element
sp : [Element]
_) <- [Element]
contentShapes -> Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return Element
sp
        ContentType
TwoColumnRightContent | (Element
_ : Element
sp : [Element]
_) <- [Element]
contentShapes -> Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return Element
sp
        ContentType
_ -> PandocError -> P m Element
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> P m Element) -> PandocError -> P m Element
forall a b. (a -> b) -> a -> b
$ MimeType -> PandocError
PandocSomeError
             MimeType
"Could not find shape for Powerpoint content"
getContentShape NameSpaces
_ Element
_ = PandocError -> P m Element
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> P m Element) -> PandocError -> P m Element
forall a b. (a -> b) -> a -> b
$ MimeType -> PandocError
PandocSomeError
                      MimeType
"Attempted to find content on non shapeTree"

getShapeDimensions :: NameSpaces
                   -> Element
                   -> Maybe ((Integer, Integer), (Integer, Integer))
getShapeDimensions :: NameSpaces -> Element -> Maybe ((Pixels, Pixels), (Pixels, Pixels))
getShapeDimensions NameSpaces
ns Element
element
  | NameSpaces -> FilePath -> FilePath -> Element -> Bool
isElem NameSpaces
ns FilePath
"p" FilePath
"sp" Element
element = do
      Element
spPr <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"spPr") Element
element
      Element
xfrm <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"a" FilePath
"xfrm") Element
spPr
      Element
off <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"a" FilePath
"off") Element
xfrm
      FilePath
xS <- QName -> Element -> Maybe FilePath
findAttr (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"x" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
off
      FilePath
yS <- QName -> Element -> Maybe FilePath
findAttr (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"y" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
off
      Element
ext <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"a" FilePath
"ext") Element
xfrm
      FilePath
cxS <- QName -> Element -> Maybe FilePath
findAttr (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"cx" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
ext
      FilePath
cyS <- QName -> Element -> Maybe FilePath
findAttr (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"cy" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
ext
      (Pixels
x, FilePath
_) <- [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a. [a] -> Maybe a
listToMaybe ([(Pixels, FilePath)] -> Maybe (Pixels, FilePath))
-> [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a b. (a -> b) -> a -> b
$ ReadS Pixels
forall a. Read a => ReadS a
reads FilePath
xS
      (Pixels
y, FilePath
_) <- [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a. [a] -> Maybe a
listToMaybe ([(Pixels, FilePath)] -> Maybe (Pixels, FilePath))
-> [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a b. (a -> b) -> a -> b
$ ReadS Pixels
forall a. Read a => ReadS a
reads FilePath
yS
      (Pixels
cx, FilePath
_) <- [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a. [a] -> Maybe a
listToMaybe ([(Pixels, FilePath)] -> Maybe (Pixels, FilePath))
-> [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a b. (a -> b) -> a -> b
$ ReadS Pixels
forall a. Read a => ReadS a
reads FilePath
cxS
      (Pixels
cy, FilePath
_) <- [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a. [a] -> Maybe a
listToMaybe ([(Pixels, FilePath)] -> Maybe (Pixels, FilePath))
-> [(Pixels, FilePath)] -> Maybe (Pixels, FilePath)
forall a b. (a -> b) -> a -> b
$ ReadS Pixels
forall a. Read a => ReadS a
reads FilePath
cyS
      ((Pixels, Pixels), (Pixels, Pixels))
-> Maybe ((Pixels, Pixels), (Pixels, Pixels))
forall (m :: * -> *) a. Monad m => a -> m a
return ((Pixels
x Pixels -> Pixels -> Pixels
forall a. Integral a => a -> a -> a
`div` Pixels
12700, Pixels
y Pixels -> Pixels -> Pixels
forall a. Integral a => a -> a -> a
`div` Pixels
12700),
              (Pixels
cx Pixels -> Pixels -> Pixels
forall a. Integral a => a -> a -> a
`div` Pixels
12700, Pixels
cy Pixels -> Pixels -> Pixels
forall a. Integral a => a -> a -> a
`div` Pixels
12700))
  | Bool
otherwise = Maybe ((Pixels, Pixels), (Pixels, Pixels))
forall a. Maybe a
Nothing


getMasterShapeDimensionsById :: T.Text
                             -> Element
                             -> Maybe ((Integer, Integer), (Integer, Integer))
getMasterShapeDimensionsById :: MimeType -> Element -> Maybe ((Pixels, Pixels), (Pixels, Pixels))
getMasterShapeDimensionsById MimeType
ident Element
master = do
  let ns :: NameSpaces
ns = Element -> NameSpaces
elemToNameSpaces Element
master
  Element
cSld <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"cSld") Element
master
  Element
spTree <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"spTree") Element
cSld
  Element
sp <- (Element -> Bool) -> Element -> Maybe Element
filterChild (\Element
e -> NameSpaces -> FilePath -> FilePath -> Element -> Bool
isElem NameSpaces
ns FilePath
"p" FilePath
"sp" Element
e Bool -> Bool -> Bool
&& NameSpaces -> MimeType -> Element -> Bool
shapeHasId NameSpaces
ns MimeType
ident Element
e) Element
spTree
  NameSpaces -> Element -> Maybe ((Pixels, Pixels), (Pixels, Pixels))
getShapeDimensions NameSpaces
ns Element
sp

getContentShapeSize :: PandocMonad m
                    => NameSpaces
                    -> Element
                    -> Element
                    -> P m ((Integer, Integer), (Integer, Integer))
getContentShapeSize :: NameSpaces
-> Element -> Element -> P m ((Pixels, Pixels), (Pixels, Pixels))
getContentShapeSize NameSpaces
ns Element
layout Element
master
  | NameSpaces -> FilePath -> FilePath -> Element -> Bool
isElem NameSpaces
ns FilePath
"p" FilePath
"sldLayout" Element
layout
  , Just Element
cSld <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"cSld") Element
layout
  , Just Element
spTree <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"spTree") Element
cSld = do
      Element
sp  <- NameSpaces -> Element -> P m Element
forall (m :: * -> *).
PandocMonad m =>
NameSpaces -> Element -> P m Element
getContentShape NameSpaces
ns Element
spTree
      case NameSpaces -> Element -> Maybe ((Pixels, Pixels), (Pixels, Pixels))
getShapeDimensions NameSpaces
ns Element
sp of
        Just ((Pixels, Pixels), (Pixels, Pixels))
sz -> ((Pixels, Pixels), (Pixels, Pixels))
-> P m ((Pixels, Pixels), (Pixels, Pixels))
forall (m :: * -> *) a. Monad m => a -> m a
return ((Pixels, Pixels), (Pixels, Pixels))
sz
        Maybe ((Pixels, Pixels), (Pixels, Pixels))
Nothing -> do let mbSz :: Maybe ((Pixels, Pixels), (Pixels, Pixels))
mbSz =
                            QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"nvSpPr") Element
sp Maybe Element -> (Element -> Maybe Element) -> Maybe Element
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                            QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"cNvPr") Maybe Element -> (Element -> Maybe MimeType) -> Maybe MimeType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                            QName -> Element -> Maybe MimeType
findAttrText (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"id" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Maybe MimeType
-> (MimeType -> Maybe ((Pixels, Pixels), (Pixels, Pixels)))
-> Maybe ((Pixels, Pixels), (Pixels, Pixels))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                            (MimeType -> Element -> Maybe ((Pixels, Pixels), (Pixels, Pixels)))
-> Element
-> MimeType
-> Maybe ((Pixels, Pixels), (Pixels, Pixels))
forall a b c. (a -> b -> c) -> b -> a -> c
flip MimeType -> Element -> Maybe ((Pixels, Pixels), (Pixels, Pixels))
getMasterShapeDimensionsById Element
master
                      case Maybe ((Pixels, Pixels), (Pixels, Pixels))
mbSz of
                        Just ((Pixels, Pixels), (Pixels, Pixels))
sz' -> ((Pixels, Pixels), (Pixels, Pixels))
-> P m ((Pixels, Pixels), (Pixels, Pixels))
forall (m :: * -> *) a. Monad m => a -> m a
return ((Pixels, Pixels), (Pixels, Pixels))
sz'
                        Maybe ((Pixels, Pixels), (Pixels, Pixels))
Nothing -> PandocError -> P m ((Pixels, Pixels), (Pixels, Pixels))
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> P m ((Pixels, Pixels), (Pixels, Pixels)))
-> PandocError -> P m ((Pixels, Pixels), (Pixels, Pixels))
forall a b. (a -> b) -> a -> b
$ MimeType -> PandocError
PandocSomeError
                                   MimeType
"Couldn't find necessary content shape size"
getContentShapeSize NameSpaces
_ Element
_ Element
_ = PandocError -> P m ((Pixels, Pixels), (Pixels, Pixels))
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> P m ((Pixels, Pixels), (Pixels, Pixels)))
-> PandocError -> P m ((Pixels, Pixels), (Pixels, Pixels))
forall a b. (a -> b) -> a -> b
$ MimeType -> PandocError
PandocSomeError
                            MimeType
"Attempted to find content shape size in non-layout"

buildSpTree :: NameSpaces -> Element -> [Element] -> Element
buildSpTree :: NameSpaces -> Element -> [Element] -> Element
buildSpTree NameSpaces
ns Element
spTreeElem [Element]
newShapes =
  Element
emptySpTreeElem { elContent :: [Content]
elContent = [Content]
newContent }
  where newContent :: [Content]
newContent = Element -> [Content]
elContent Element
emptySpTreeElem [Content] -> [Content] -> [Content]
forall a. Semigroup a => a -> a -> a
<> (Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem [Element]
newShapes
        emptySpTreeElem :: Element
emptySpTreeElem = Element
spTreeElem { elContent :: [Content]
elContent = (Content -> Bool) -> [Content] -> [Content]
forall a. (a -> Bool) -> [a] -> [a]
filter Content -> Bool
fn (Element -> [Content]
elContent Element
spTreeElem) }
        fn :: Content -> Bool
        fn :: Content -> Bool
fn (Elem Element
e) = NameSpaces -> FilePath -> FilePath -> Element -> Bool
isElem NameSpaces
ns FilePath
"p" FilePath
"nvGrpSpPr" Element
e Bool -> Bool -> Bool
||
                      NameSpaces -> FilePath -> FilePath -> Element -> Bool
isElem NameSpaces
ns FilePath
"p" FilePath
"grpSpPr" Element
e
        fn Content
_        = Bool
True

replaceNamedChildren :: NameSpaces
                     -> String
                     -> String
                     -> [Element]
                     -> Element
                     -> Element
replaceNamedChildren :: NameSpaces
-> FilePath -> FilePath -> [Element] -> Element -> Element
replaceNamedChildren NameSpaces
ns FilePath
prefix FilePath
name [Element]
newKids Element
element =
  Element
element { elContent :: [Content]
elContent = [[Content]] -> [Content]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Content]] -> [Content]) -> [[Content]] -> [Content]
forall a b. (a -> b) -> a -> b
$ Bool -> [Content] -> [[Content]]
fun Bool
True ([Content] -> [[Content]]) -> [Content] -> [[Content]]
forall a b. (a -> b) -> a -> b
$ Element -> [Content]
elContent Element
element }
  where
    fun :: Bool -> [Content] -> [[Content]]
    fun :: Bool -> [Content] -> [[Content]]
fun Bool
_ [] = []
    fun Bool
switch (Elem Element
e : [Content]
conts) | NameSpaces -> FilePath -> FilePath -> Element -> Bool
isElem NameSpaces
ns FilePath
prefix FilePath
name Element
e =
                                      if Bool
switch
                                      then (Element -> Content) -> [Element] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Content
Elem [Element]
newKids [Content] -> [[Content]] -> [[Content]]
forall a. a -> [a] -> [a]
: Bool -> [Content] -> [[Content]]
fun Bool
False [Content]
conts
                                      else Bool -> [Content] -> [[Content]]
fun Bool
False [Content]
conts
    fun Bool
switch (Content
cont : [Content]
conts) = [Content
cont] [Content] -> [[Content]] -> [[Content]]
forall a. a -> [a] -> [a]
: Bool -> [Content] -> [[Content]]
fun Bool
switch [Content]
conts

----------------------------------------------------------------

registerLink :: PandocMonad m => LinkTarget -> P m Int
registerLink :: LinkTarget -> P m Int
registerLink LinkTarget
link = do
  Int
curSlideId <- (WriterEnv -> Int) -> P m Int
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Int
envCurSlideId
  Map Int (Map Int LinkTarget)
linkReg <- (WriterState -> Map Int (Map Int LinkTarget))
-> ReaderT
     WriterEnv (StateT WriterState m) (Map Int (Map Int LinkTarget))
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Int (Map Int LinkTarget)
stLinkIds
  Map Int [MediaInfo]
mediaReg <- (WriterState -> Map Int [MediaInfo])
-> ReaderT WriterEnv (StateT WriterState m) (Map Int [MediaInfo])
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Int [MediaInfo]
stMediaIds
  Bool
hasSpeakerNotes <- P m Bool
forall (m :: * -> *). PandocMonad m => P m Bool
curSlideHasSpeakerNotes
  let maxLinkId :: Int
maxLinkId = case Int -> Map Int (Map Int LinkTarget) -> Maybe (Map Int LinkTarget)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
curSlideId Map Int (Map Int LinkTarget)
linkReg of
        Just Map Int LinkTarget
mp -> case Map Int LinkTarget -> [Int]
forall k a. Map k a -> [k]
M.keys Map Int LinkTarget
mp of
          [] -> if Bool
hasSpeakerNotes then Int
2 else Int
1
          [Int]
ks -> [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [Int]
ks
        Maybe (Map Int LinkTarget)
Nothing -> if Bool
hasSpeakerNotes then Int
2 else Int
1
      maxMediaId :: Int
maxMediaId = case Int -> Map Int [MediaInfo] -> Maybe [MediaInfo]
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
curSlideId Map Int [MediaInfo]
mediaReg of
        Just [] -> if Bool
hasSpeakerNotes then Int
2 else Int
1
        Just [MediaInfo]
mInfos -> [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (MediaInfo -> Int) -> [MediaInfo] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map MediaInfo -> Int
mInfoLocalId [MediaInfo]
mInfos
        Maybe [MediaInfo]
Nothing -> if Bool
hasSpeakerNotes then Int
2 else Int
1
      maxId :: Int
maxId = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
maxLinkId Int
maxMediaId
      slideLinks :: Map Int LinkTarget
slideLinks = case Int -> Map Int (Map Int LinkTarget) -> Maybe (Map Int LinkTarget)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
curSlideId Map Int (Map Int LinkTarget)
linkReg of
        Just Map Int LinkTarget
mp -> Int -> LinkTarget -> Map Int LinkTarget -> Map Int LinkTarget
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (Int
maxId Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) LinkTarget
link Map Int LinkTarget
mp
        Maybe (Map Int LinkTarget)
Nothing -> Int -> LinkTarget -> Map Int LinkTarget
forall k a. k -> a -> Map k a
M.singleton (Int
maxId Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) LinkTarget
link
  (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{ stLinkIds :: Map Int (Map Int LinkTarget)
stLinkIds = Int
-> Map Int LinkTarget
-> Map Int (Map Int LinkTarget)
-> Map Int (Map Int LinkTarget)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Int
curSlideId Map Int LinkTarget
slideLinks Map Int (Map Int LinkTarget)
linkReg}
  Int -> P m Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> P m Int) -> Int -> P m Int
forall a b. (a -> b) -> a -> b
$ Int
maxId Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1

registerMedia :: PandocMonad m => FilePath -> [ParaElem] -> P m MediaInfo
registerMedia :: FilePath -> [ParaElem] -> P m MediaInfo
registerMedia FilePath
fp [ParaElem]
caption = do
  Int
curSlideId <- (WriterEnv -> Int) -> ReaderT WriterEnv (StateT WriterState m) Int
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Int
envCurSlideId
  Map Int (Map Int LinkTarget)
linkReg <- (WriterState -> Map Int (Map Int LinkTarget))
-> ReaderT
     WriterEnv (StateT WriterState m) (Map Int (Map Int LinkTarget))
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Int (Map Int LinkTarget)
stLinkIds
  Map Int [MediaInfo]
mediaReg <- (WriterState -> Map Int [MediaInfo])
-> ReaderT WriterEnv (StateT WriterState m) (Map Int [MediaInfo])
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Int [MediaInfo]
stMediaIds
  Map FilePath Int
globalIds <- (WriterState -> Map FilePath Int)
-> ReaderT WriterEnv (StateT WriterState m) (Map FilePath Int)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map FilePath Int
stMediaGlobalIds
  Bool
hasSpeakerNotes <- P m Bool
forall (m :: * -> *). PandocMonad m => P m Bool
curSlideHasSpeakerNotes
  let maxLinkId :: Int
maxLinkId = case Int -> Map Int (Map Int LinkTarget) -> Maybe (Map Int LinkTarget)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
curSlideId Map Int (Map Int LinkTarget)
linkReg of
        Just Map Int LinkTarget
mp -> case Map Int LinkTarget -> [Int]
forall k a. Map k a -> [k]
M.keys Map Int LinkTarget
mp of
          [] -> if Bool
hasSpeakerNotes then Int
2 else Int
1
          [Int]
ks -> [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [Int]
ks
        Maybe (Map Int LinkTarget)
Nothing -> if Bool
hasSpeakerNotes then Int
2 else Int
1
      maxMediaId :: Int
maxMediaId = case Int -> Map Int [MediaInfo] -> Maybe [MediaInfo]
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
curSlideId Map Int [MediaInfo]
mediaReg of
        Just [] -> if Bool
hasSpeakerNotes then Int
2 else Int
1
        Just [MediaInfo]
mInfos -> [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (MediaInfo -> Int) -> [MediaInfo] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map MediaInfo -> Int
mInfoLocalId [MediaInfo]
mInfos
        Maybe [MediaInfo]
Nothing -> if Bool
hasSpeakerNotes then Int
2 else Int
1
      maxLocalId :: Int
maxLocalId = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
maxLinkId Int
maxMediaId

      maxGlobalId :: Int
maxGlobalId = case Map FilePath Int -> [Int]
forall k a. Map k a -> [a]
M.elems Map FilePath Int
globalIds of
        [] -> Int
0
        [Int]
ids -> [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [Int]
ids

  (ByteString
imgBytes, Maybe MimeType
mbMt) <- MimeType
-> ReaderT
     WriterEnv (StateT WriterState m) (ByteString, Maybe MimeType)
forall (m :: * -> *).
PandocMonad m =>
MimeType -> m (ByteString, Maybe MimeType)
P.fetchItem (MimeType
 -> ReaderT
      WriterEnv (StateT WriterState m) (ByteString, Maybe MimeType))
-> MimeType
-> ReaderT
     WriterEnv (StateT WriterState m) (ByteString, Maybe MimeType)
forall a b. (a -> b) -> a -> b
$ FilePath -> MimeType
T.pack FilePath
fp
  let imgExt :: Maybe MimeType
imgExt = (Maybe MimeType
mbMt Maybe MimeType -> (MimeType -> Maybe MimeType) -> Maybe MimeType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MimeType -> Maybe MimeType
extensionFromMimeType Maybe MimeType -> (MimeType -> Maybe MimeType) -> Maybe MimeType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\MimeType
x -> MimeType -> Maybe MimeType
forall (m :: * -> *) a. Monad m => a -> m a
return (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
"." MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
x))
               Maybe MimeType -> Maybe MimeType -> Maybe MimeType
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
               case ByteString -> Maybe ImageType
imageType ByteString
imgBytes of
                 Just ImageType
Png  -> MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just MimeType
".png"
                 Just ImageType
Jpeg -> MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just MimeType
".jpeg"
                 Just ImageType
Gif  -> MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just MimeType
".gif"
                 Just ImageType
Pdf  -> MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just MimeType
".pdf"
                 Just ImageType
Eps  -> MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just MimeType
".eps"
                 Just ImageType
Svg  -> MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just MimeType
".svg"
                 Just ImageType
Emf  -> MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just MimeType
".emf"
                 Maybe ImageType
Nothing   -> Maybe MimeType
forall a. Maybe a
Nothing

  let newGlobalId :: Int
newGlobalId = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe (Int
maxGlobalId Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (FilePath -> Map FilePath Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup FilePath
fp Map FilePath Int
globalIds)

  let newGlobalIds :: Map FilePath Int
newGlobalIds = FilePath -> Int -> Map FilePath Int -> Map FilePath Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert FilePath
fp Int
newGlobalId Map FilePath Int
globalIds

  let mediaInfo :: MediaInfo
mediaInfo = MediaInfo :: FilePath
-> Int
-> Int
-> Maybe MimeType
-> Maybe MimeType
-> Bool
-> MediaInfo
MediaInfo { mInfoFilePath :: FilePath
mInfoFilePath = FilePath
fp
                            , mInfoLocalId :: Int
mInfoLocalId = Int
maxLocalId Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
                            , mInfoGlobalId :: Int
mInfoGlobalId = Int
newGlobalId
                            , mInfoMimeType :: Maybe MimeType
mInfoMimeType = Maybe MimeType
mbMt
                            , mInfoExt :: Maybe MimeType
mInfoExt = Maybe MimeType
imgExt
                            , mInfoCaption :: Bool
mInfoCaption = (Bool -> Bool
not (Bool -> Bool) -> ([ParaElem] -> Bool) -> [ParaElem] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ParaElem] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) [ParaElem]
caption
                            }

  let slideMediaInfos :: [MediaInfo]
slideMediaInfos = case Int -> Map Int [MediaInfo] -> Maybe [MediaInfo]
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
curSlideId Map Int [MediaInfo]
mediaReg of
        Just [MediaInfo]
minfos -> MediaInfo
mediaInfo MediaInfo -> [MediaInfo] -> [MediaInfo]
forall a. a -> [a] -> [a]
: [MediaInfo]
minfos
        Maybe [MediaInfo]
Nothing     -> [MediaInfo
mediaInfo]


  (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{ stMediaIds :: Map Int [MediaInfo]
stMediaIds = Int -> [MediaInfo] -> Map Int [MediaInfo] -> Map Int [MediaInfo]
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Int
curSlideId [MediaInfo]
slideMediaInfos Map Int [MediaInfo]
mediaReg
                    , stMediaGlobalIds :: Map FilePath Int
stMediaGlobalIds = Map FilePath Int
newGlobalIds
                    }
  MediaInfo -> P m MediaInfo
forall (m :: * -> *) a. Monad m => a -> m a
return MediaInfo
mediaInfo

makeMediaEntry :: PandocMonad m => MediaInfo -> P m Entry
makeMediaEntry :: MediaInfo -> P m Entry
makeMediaEntry MediaInfo
mInfo = do
  Pixels
epochtime <- POSIXTime -> Pixels
forall a b. (RealFrac a, Integral b) => a -> b
floor (POSIXTime -> Pixels)
-> (UTCTime -> POSIXTime) -> UTCTime -> Pixels
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> POSIXTime
utcTimeToPOSIXSeconds (UTCTime -> Pixels)
-> ReaderT WriterEnv (StateT WriterState m) UTCTime
-> ReaderT WriterEnv (StateT WriterState m) Pixels
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (WriterEnv -> UTCTime)
-> ReaderT WriterEnv (StateT WriterState m) UTCTime
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> UTCTime
envUTCTime
  (ByteString
imgBytes, Maybe MimeType
_) <- MimeType
-> ReaderT
     WriterEnv (StateT WriterState m) (ByteString, Maybe MimeType)
forall (m :: * -> *).
PandocMonad m =>
MimeType -> m (ByteString, Maybe MimeType)
P.fetchItem (FilePath -> MimeType
T.pack (FilePath -> MimeType) -> FilePath -> MimeType
forall a b. (a -> b) -> a -> b
$ MediaInfo -> FilePath
mInfoFilePath MediaInfo
mInfo)
  let ext :: MimeType
ext = MimeType -> Maybe MimeType -> MimeType
forall a. a -> Maybe a -> a
fromMaybe MimeType
"" (MediaInfo -> Maybe MimeType
mInfoExt MediaInfo
mInfo)
  let fp :: FilePath
fp = FilePath
"ppt/media/image" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<>
          Int -> FilePath
forall a. Show a => a -> FilePath
show (MediaInfo -> Int
mInfoGlobalId MediaInfo
mInfo) FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> MimeType -> FilePath
T.unpack MimeType
ext
  Entry -> P m Entry
forall (m :: * -> *) a. Monad m => a -> m a
return (Entry -> P m Entry) -> Entry -> P m Entry
forall a b. (a -> b) -> a -> b
$ FilePath -> Pixels -> ByteString -> Entry
toEntry FilePath
fp Pixels
epochtime (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
BL.fromStrict ByteString
imgBytes

makeMediaEntries :: PandocMonad m => P m [Entry]
makeMediaEntries :: P m [Entry]
makeMediaEntries = do
  Map Int [MediaInfo]
mediaInfos <- (WriterState -> Map Int [MediaInfo])
-> ReaderT WriterEnv (StateT WriterState m) (Map Int [MediaInfo])
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Int [MediaInfo]
stMediaIds
  let allInfos :: [MediaInfo]
allInfos = [[MediaInfo]] -> [MediaInfo]
forall a. Monoid a => [a] -> a
mconcat ([[MediaInfo]] -> [MediaInfo]) -> [[MediaInfo]] -> [MediaInfo]
forall a b. (a -> b) -> a -> b
$ Map Int [MediaInfo] -> [[MediaInfo]]
forall k a. Map k a -> [a]
M.elems Map Int [MediaInfo]
mediaInfos
  (MediaInfo -> ReaderT WriterEnv (StateT WriterState m) Entry)
-> [MediaInfo] -> P m [Entry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM MediaInfo -> ReaderT WriterEnv (StateT WriterState m) Entry
forall (m :: * -> *). PandocMonad m => MediaInfo -> P m Entry
makeMediaEntry [MediaInfo]
allInfos

-- -- | Scales the image to fit the page
-- -- sizes are passed in emu
-- fitToPage' :: (Double, Double)  -- image size in emu
--            -> Integer           -- pageWidth
--            -> Integer           -- pageHeight
--            -> (Integer, Integer) -- imagesize
-- fitToPage' (x, y) pageWidth pageHeight
--   -- Fixes width to the page width and scales the height
--   | x <= fromIntegral pageWidth && y <= fromIntegral pageHeight =
--       (floor x, floor y)
--   | x / fromIntegral pageWidth > y / fromIntegral pageWidth =
--       (pageWidth, floor $ ((fromIntegral pageWidth) / x) * y)
--   | otherwise =
--       (floor $ ((fromIntegral pageHeight) / y) * x, pageHeight)

-- positionImage :: (Double, Double) -> Integer -> Integer -> (Integer, Integer)
-- positionImage (x, y) pageWidth pageHeight =
--   let (x', y') = fitToPage' (x, y) pageWidth pageHeight
--   in
--     ((pageWidth - x') `div` 2, (pageHeight - y') `div`  2)

getMaster :: PandocMonad m => P m Element
getMaster :: P m Element
getMaster = do
  Archive
refArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envRefArchive
  Archive
distArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envDistArchive
  Archive -> Archive -> FilePath -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> FilePath -> m Element
parseXml Archive
refArchive Archive
distArchive FilePath
"ppt/slideMasters/slideMaster1.xml"

-- We want to get the header dimensions, so we can make sure that the
-- image goes underneath it. We only use this in a content slide if it
-- has a header.

-- getHeaderSize :: PandocMonad m => P m ((Integer, Integer), (Integer, Integer))
-- getHeaderSize = do
--   master <- getMaster
--   let ns = elemToNameSpaces master
--       sps = [master] >>=
--             findChildren (elemName ns "p" "cSld") >>=
--             findChildren (elemName ns "p" "spTree") >>=
--             findChildren (elemName ns "p" "sp")
--       mbXfrm =
--         listToMaybe (filter (shapeHasName ns "Title Placeholder 1") sps) >>=
--         findChild (elemName ns "p" "spPr") >>=
--         findChild (elemName ns "a" "xfrm")
--       xoff = mbXfrm >>=
--              findChild (elemName ns "a" "off") >>=
--              findAttr (QName "x" Nothing Nothing) >>=
--              (listToMaybe . (\s -> reads s :: [(Integer, String)]))
--       yoff = mbXfrm >>=
--              findChild (elemName ns "a" "off") >>=
--              findAttr (QName "y" Nothing Nothing) >>=
--              (listToMaybe . (\s -> reads s :: [(Integer, String)]))
--       xext = mbXfrm >>=
--              findChild (elemName ns "a" "ext") >>=
--              findAttr (QName "cx" Nothing Nothing) >>=
--              (listToMaybe . (\s -> reads s :: [(Integer, String)]))
--       yext = mbXfrm >>=
--              findChild (elemName ns "a" "ext") >>=
--              findAttr (QName "cy" Nothing Nothing) >>=
--              (listToMaybe . (\s -> reads s :: [(Integer, String)]))
--       off = case xoff of
--               Just (xoff', _) | Just (yoff',_) <- yoff -> (xoff', yoff')
--               _                               -> (1043490, 1027664)
--       ext = case xext of
--               Just (xext', _) | Just (yext',_) <- yext -> (xext', yext')
--               _                               -> (7024744, 1143000)
--   return $ (off, ext)

-- Hard-coded for now
-- captionPosition :: ((Integer, Integer), (Integer, Integer))
-- captionPosition = ((457200, 6061972), (8229600, 527087))

captionHeight :: Integer
captionHeight :: Pixels
captionHeight = Pixels
40

createCaption :: PandocMonad m
              => ((Integer, Integer), (Integer, Integer))
              -> [ParaElem]
              -> P m Element
createCaption :: ((Pixels, Pixels), (Pixels, Pixels)) -> [ParaElem] -> P m Element
createCaption ((Pixels, Pixels), (Pixels, Pixels))
contentShapeDimensions [ParaElem]
paraElements = do
  let para :: Paragraph
para = ParaProps -> [ParaElem] -> Paragraph
Paragraph ParaProps
forall a. Default a => a
def{pPropAlign :: Maybe Algnment
pPropAlign = Algnment -> Maybe Algnment
forall a. a -> Maybe a
Just Algnment
AlgnCenter} [ParaElem]
paraElements
  [Element]
elements <- (Paragraph -> P m Element)
-> [Paragraph]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Paragraph -> P m Element
forall (m :: * -> *). PandocMonad m => Paragraph -> P m Element
paragraphToElement [Paragraph
para]
  let ((Pixels
x, Pixels
y), (Pixels
cx, Pixels
cy)) = ((Pixels, Pixels), (Pixels, Pixels))
contentShapeDimensions
  let txBody :: Element
txBody = FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:txBody" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
               [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:bodyPr" [] (), FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:lstStyle" [] ()] [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
elements
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$
    FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sp" [] [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvSpPr" []
                       [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvPr" [(FilePath
"id",FilePath
"1"), (FilePath
"name",FilePath
"TextBox 3")] ()
                       , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvSpPr" [(FilePath
"txBox", FilePath
"1")] ()
                       , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvPr" [] ()
                       ]
                     , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:spPr" []
                       [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:xfrm" []
                         [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:off" [(FilePath
"x", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels
12700 Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
x),
                                           (FilePath
"y", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels
12700 Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* (Pixels
y Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
+ Pixels
cy Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
- Pixels
captionHeight))] ()
                         , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:ext" [(FilePath
"cx", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels
12700 Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
cx),
                                           (FilePath
"cy", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels
12700 Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
captionHeight)] ()
                         ]
                       , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:prstGeom" [(FilePath
"prst", FilePath
"rect")]
                         [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:avLst" [] ()
                         ]
                       , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:noFill" [] ()
                       ]
                     , Element
txBody
                     ]

makePicElements :: PandocMonad m
                => Element
                -> PicProps
                -> MediaInfo
                -> [ParaElem]
                -> P m [Element]
makePicElements :: Element -> PicProps -> MediaInfo -> [ParaElem] -> P m [Element]
makePicElements Element
layout PicProps
picProps MediaInfo
mInfo [ParaElem]
alt = do
  WriterOptions
opts <- (WriterEnv -> WriterOptions)
-> ReaderT WriterEnv (StateT WriterState m) WriterOptions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> WriterOptions
envOpts
  (Pixels
pageWidth, Pixels
pageHeight) <- (WriterEnv -> (Pixels, Pixels))
-> ReaderT WriterEnv (StateT WriterState m) (Pixels, Pixels)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> (Pixels, Pixels)
envPresentationSize
  -- hasHeader <- asks envSlideHasHeader
  let hasCaption :: Bool
hasCaption = MediaInfo -> Bool
mInfoCaption MediaInfo
mInfo
  (ByteString
imgBytes, Maybe MimeType
_) <- MimeType
-> ReaderT
     WriterEnv (StateT WriterState m) (ByteString, Maybe MimeType)
forall (m :: * -> *).
PandocMonad m =>
MimeType -> m (ByteString, Maybe MimeType)
P.fetchItem (FilePath -> MimeType
T.pack (FilePath -> MimeType) -> FilePath -> MimeType
forall a b. (a -> b) -> a -> b
$ MediaInfo -> FilePath
mInfoFilePath MediaInfo
mInfo)
  let (Pixels
pxX, Pixels
pxY) = case WriterOptions -> ByteString -> Either MimeType ImageSize
imageSize WriterOptions
opts ByteString
imgBytes of
        Right ImageSize
sz -> ImageSize -> (Pixels, Pixels)
sizeInPixels ImageSize
sz
        Left MimeType
_   -> ImageSize -> (Pixels, Pixels)
sizeInPixels ImageSize
forall a. Default a => a
def
  Element
master <- P m Element
forall (m :: * -> *). PandocMonad m => P m Element
getMaster
  let ns :: NameSpaces
ns = Element -> NameSpaces
elemToNameSpaces Element
layout
  ((Pixels
x, Pixels
y), (Pixels
cx, Pixels
cytmp)) <- NameSpaces
-> Element -> Element -> P m ((Pixels, Pixels), (Pixels, Pixels))
forall (m :: * -> *).
PandocMonad m =>
NameSpaces
-> Element -> Element -> P m ((Pixels, Pixels), (Pixels, Pixels))
getContentShapeSize NameSpaces
ns Element
layout Element
master
                           P m ((Pixels, Pixels), (Pixels, Pixels))
-> (PandocError -> P m ((Pixels, Pixels), (Pixels, Pixels)))
-> P m ((Pixels, Pixels), (Pixels, Pixels))
forall e (m :: * -> *) a.
MonadError e m =>
m a -> (e -> m a) -> m a
`catchError`
                           (\PandocError
_ -> ((Pixels, Pixels), (Pixels, Pixels))
-> P m ((Pixels, Pixels), (Pixels, Pixels))
forall (m :: * -> *) a. Monad m => a -> m a
return ((Pixels
0, Pixels
0), (Pixels
pageWidth, Pixels
pageHeight)))

  let cy :: Pixels
cy = if Bool
hasCaption then Pixels
cytmp Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
- Pixels
captionHeight else Pixels
cytmp

  let imgRatio :: Double
imgRatio = Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
pxX Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
pxY :: Double
      boxRatio :: Double
boxRatio = Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
cx Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
cy :: Double
      (Double
dimX, Double
dimY) = if Double
imgRatio Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
boxRatio
                     then (Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
cx, Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
cx Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
imgRatio)
                     else (Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
cy Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
imgRatio, Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
cy)

      (Pixels
dimX', Pixels
dimY') = (Double -> Pixels
forall a b. (RealFrac a, Integral b) => a -> b
round Double
dimX Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
12700, Double -> Pixels
forall a b. (RealFrac a, Integral b) => a -> b
round Double
dimY Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
12700) :: (Integer, Integer)
      (Double
xoff, Double
yoff) = (Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
x Double -> Double -> Double
forall a. Num a => a -> a -> a
+ (Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
cx Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
dimX) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2,
                      Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
y Double -> Double -> Double
forall a. Num a => a -> a -> a
+ (Pixels -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Pixels
cy Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
dimY) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2)
      (Pixels
xoff', Pixels
yoff') = (Double -> Pixels
forall a b. (RealFrac a, Integral b) => a -> b
round Double
xoff Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
12700, Double -> Pixels
forall a b. (RealFrac a, Integral b) => a -> b
round Double
yoff Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
12700) :: (Integer, Integer)

  let cNvPicPr :: Element
cNvPicPr = FilePath -> NameSpaces -> Element -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvPicPr" [] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$
                 FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:picLocks" [(FilePath
"noGrp",FilePath
"1")
                                     ,(FilePath
"noChangeAspect",FilePath
"1")] ()
  -- cNvPr will contain the link information so we do that separately,
  -- and register the link if necessary.
  let cNvPrAttr :: NameSpaces
cNvPrAttr = [(FilePath
"descr", MediaInfo -> FilePath
mInfoFilePath MediaInfo
mInfo), (FilePath
"id",FilePath
"0"),(FilePath
"name",FilePath
"Picture 1")]
  Element
cNvPr <- case PicProps -> Maybe LinkTarget
picPropLink PicProps
picProps of
    Just LinkTarget
link -> do Int
idNum <- LinkTarget -> P m Int
forall (m :: * -> *). PandocMonad m => LinkTarget -> P m Int
registerLink LinkTarget
link
                    Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> Element -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvPr" NameSpaces
cNvPrAttr (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$
                      FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:hlinkClick" [(FilePath
"r:id", FilePath
"rId" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
idNum)] ()
    Maybe LinkTarget
Nothing   -> Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvPr" NameSpaces
cNvPrAttr ()
  let nvPicPr :: Element
nvPicPr  = FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvPicPr" []
                 [ Element
cNvPr
                 , Element
cNvPicPr
                 , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvPr" [] ()]
  let blipFill :: Element
blipFill = FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:blipFill" []
                 [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:blip" [(FilePath
"r:embed", FilePath
"rId" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<>
          Int -> FilePath
forall a. Show a => a -> FilePath
show (MediaInfo -> Int
mInfoLocalId MediaInfo
mInfo))] ()
                 , FilePath -> NameSpaces -> Element -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:stretch" [] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$
                   FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:fillRect" [] () ]
  let xfrm :: Element
xfrm =    FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:xfrm" []
                [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:off" [(FilePath
"x",Pixels -> FilePath
forall a. Show a => a -> FilePath
show Pixels
xoff'), (FilePath
"y",Pixels -> FilePath
forall a. Show a => a -> FilePath
show Pixels
yoff')] ()
                , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:ext" [(FilePath
"cx",Pixels -> FilePath
forall a. Show a => a -> FilePath
show Pixels
dimX')
                                 ,(FilePath
"cy",Pixels -> FilePath
forall a. Show a => a -> FilePath
show Pixels
dimY')] () ]
  let prstGeom :: Element
prstGeom = FilePath -> NameSpaces -> Element -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:prstGeom" [(FilePath
"prst",FilePath
"rect")] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$
                 FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:avLst" [] ()
  let ln :: Element
ln =      FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:ln" [(FilePath
"w",FilePath
"9525")]
                [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:noFill" [] ()
                , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:headEnd" [] ()
                , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:tailEnd" [] () ]
  let spPr :: Element
spPr =    FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:spPr" [(FilePath
"bwMode",FilePath
"auto")]
                [Element
xfrm, Element
prstGeom, FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:noFill" [] (), Element
ln]

  let picShape :: Element
picShape = FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:pic" []
                 [ Element
nvPicPr
                 , Element
blipFill
                 , Element
spPr ]

  -- And now, maybe create the caption:
  if Bool
hasCaption
    then do Element
cap <- ((Pixels, Pixels), (Pixels, Pixels)) -> [ParaElem] -> P m Element
forall (m :: * -> *).
PandocMonad m =>
((Pixels, Pixels), (Pixels, Pixels)) -> [ParaElem] -> P m Element
createCaption ((Pixels
x, Pixels
y), (Pixels
cx, Pixels
cytmp)) [ParaElem]
alt
            [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element
picShape, Element
cap]
    else [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element
picShape]


paraElemToElements :: PandocMonad m => ParaElem -> P m [Element]
paraElemToElements :: ParaElem -> P m [Element]
paraElemToElements ParaElem
Break = [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:br" [] ()]
paraElemToElements (Run RunProps
rpr MimeType
s) = do
  NameSpaces
sizeAttrs <- RunProps -> P m NameSpaces
forall (m :: * -> *). Monad m => RunProps -> P m NameSpaces
fontSizeAttributes RunProps
rpr
  let attrs :: NameSpaces
attrs = NameSpaces
sizeAttrs NameSpaces -> NameSpaces -> NameSpaces
forall a. Semigroup a => a -> a -> a
<>
        (
        [(FilePath
"b", FilePath
"1") | RunProps -> Bool
rPropBold RunProps
rpr]) NameSpaces -> NameSpaces -> NameSpaces
forall a. Semigroup a => a -> a -> a
<>
        (
        [(FilePath
"i", FilePath
"1") | RunProps -> Bool
rPropItalics RunProps
rpr]) NameSpaces -> NameSpaces -> NameSpaces
forall a. Semigroup a => a -> a -> a
<>
        (
        [(FilePath
"u", FilePath
"sng") | RunProps -> Bool
rPropUnderline RunProps
rpr]) NameSpaces -> NameSpaces -> NameSpaces
forall a. Semigroup a => a -> a -> a
<>
        (case RunProps -> Maybe Strikethrough
rStrikethrough RunProps
rpr of
            Just Strikethrough
NoStrike     -> [(FilePath
"strike", FilePath
"noStrike")]
            Just Strikethrough
SingleStrike -> [(FilePath
"strike", FilePath
"sngStrike")]
            Just Strikethrough
DoubleStrike -> [(FilePath
"strike", FilePath
"dblStrike")]
            Maybe Strikethrough
Nothing -> []) NameSpaces -> NameSpaces -> NameSpaces
forall a. Semigroup a => a -> a -> a
<>
        (case RunProps -> Maybe Int
rBaseline RunProps
rpr of
            Just Int
n -> [(FilePath
"baseline", Int -> FilePath
forall a. Show a => a -> FilePath
show Int
n)]
            Maybe Int
Nothing -> []) NameSpaces -> NameSpaces -> NameSpaces
forall a. Semigroup a => a -> a -> a
<>
        (case RunProps -> Maybe Capitals
rCap RunProps
rpr of
            Just Capitals
NoCapitals -> [(FilePath
"cap", FilePath
"none")]
            Just Capitals
SmallCapitals -> [(FilePath
"cap", FilePath
"small")]
            Just Capitals
AllCapitals -> [(FilePath
"cap", FilePath
"all")]
            Maybe Capitals
Nothing -> []) NameSpaces -> NameSpaces -> NameSpaces
forall a. Semigroup a => a -> a -> a
<>
        []
  [Element]
linkProps <- case RunProps -> Maybe LinkTarget
rLink RunProps
rpr of
                 Just LinkTarget
link -> do
                   Int
idNum <- LinkTarget -> P m Int
forall (m :: * -> *). PandocMonad m => LinkTarget -> P m Int
registerLink LinkTarget
link
                   -- first we have to make sure that if it's an
                   -- anchor, it's in the anchor map. If not, there's
                   -- no link.
                   [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Element] -> P m [Element]) -> [Element] -> P m [Element]
forall a b. (a -> b) -> a -> b
$ case LinkTarget
link of
                     InternalTarget SlideId
_ ->
                       let linkAttrs :: NameSpaces
linkAttrs =
                             [ (FilePath
"r:id", FilePath
"rId" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
idNum)
                             , (FilePath
"action", FilePath
"ppaction://hlinksldjump")
                             ]
                       in [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:hlinkClick" NameSpaces
linkAttrs ()]
                     -- external
                     ExternalTarget (MimeType, MimeType)
_ ->
                       let linkAttrs :: NameSpaces
linkAttrs =
                             [ (FilePath
"r:id", FilePath
"rId" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
idNum)
                             ]
                       in [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:hlinkClick" NameSpaces
linkAttrs ()]
                 Maybe LinkTarget
Nothing -> [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return []
  let colorContents :: [Element]
colorContents = case RunProps -> Maybe Color
rSolidFill RunProps
rpr of
                        Just Color
color ->
                          case Color -> FilePath
forall a. FromColor a => Color -> a
fromColor Color
color of
                            Char
'#':FilePath
hx ->  [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:solidFill" []
                                        [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:srgbClr" [(FilePath
"val", (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper FilePath
hx)] ()]
                                       ]
                            FilePath
_ -> []
                        Maybe Color
Nothing -> []
  MimeType
codeFont <- P m MimeType
forall (m :: * -> *). Monad m => P m MimeType
monospaceFont
  let codeContents :: [Element]
codeContents =
        [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:latin" [(FilePath
"typeface", MimeType -> FilePath
T.unpack MimeType
codeFont)] () | RunProps -> Bool
rPropCode RunProps
rpr]
  let propContents :: [Element]
propContents = [Element]
linkProps [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
colorContents [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
codeContents
  [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:r" [] [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:rPr" NameSpaces
attrs [Element]
propContents
                          , FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:t" [] (FilePath -> Element) -> FilePath -> Element
forall a b. (a -> b) -> a -> b
$ MimeType -> FilePath
T.unpack MimeType
s
                          ]]
paraElemToElements (MathElem MathType
mathType TeXString
texStr) = do
  Bool
isInSpkrNotes <- (WriterEnv -> Bool)
-> ReaderT WriterEnv (StateT WriterState m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Bool
envInSpeakerNotes
  if Bool
isInSpkrNotes
    then ParaElem -> P m [Element]
forall (m :: * -> *). PandocMonad m => ParaElem -> P m [Element]
paraElemToElements (ParaElem -> P m [Element]) -> ParaElem -> P m [Element]
forall a b. (a -> b) -> a -> b
$ RunProps -> MimeType -> ParaElem
Run RunProps
forall a. Default a => a
def (MimeType -> ParaElem) -> MimeType -> ParaElem
forall a b. (a -> b) -> a -> b
$ TeXString -> MimeType
unTeXString TeXString
texStr
    else do Either Inline Element
res <- (DisplayType -> [Exp] -> Element)
-> MathType
-> MimeType
-> ReaderT WriterEnv (StateT WriterState m) (Either Inline Element)
forall (m :: * -> *) a.
PandocMonad m =>
(DisplayType -> [Exp] -> a)
-> MathType -> MimeType -> m (Either Inline a)
convertMath DisplayType -> [Exp] -> Element
writeOMML MathType
mathType (TeXString -> MimeType
unTeXString TeXString
texStr)
            case Either Inline Element
res of
              Right Element
r -> [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [FilePath -> NameSpaces -> Element -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a14:m" [] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$ Element -> Element
addMathInfo Element
r]
              Left (Str MimeType
s) -> ParaElem -> P m [Element]
forall (m :: * -> *). PandocMonad m => ParaElem -> P m [Element]
paraElemToElements (RunProps -> MimeType -> ParaElem
Run RunProps
forall a. Default a => a
def MimeType
s)
              Left Inline
_       -> PandocError -> P m [Element]
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> P m [Element]) -> PandocError -> P m [Element]
forall a b. (a -> b) -> a -> b
$ MimeType -> PandocError
PandocShouldNeverHappenError MimeType
"non-string math fallback"
paraElemToElements (RawOOXMLParaElem MimeType
str) = [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [ Element
x | Elem Element
x <- MimeType -> [Content]
forall s. XmlSource s => s -> [Content]
parseXML MimeType
str ]


-- This is a bit of a kludge -- really requires adding an option to
-- TeXMath, but since that's a different package, we'll do this one
-- step at a time.
addMathInfo :: Element -> Element
addMathInfo :: Element -> Element
addMathInfo Element
element =
  let mathspace :: Attr
mathspace = Attr :: QName -> FilePath -> Attr
Attr { attrKey :: QName
attrKey = FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"m" Maybe FilePath
forall a. Maybe a
Nothing (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
"xmlns")
                       , attrVal :: FilePath
attrVal = FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/math"
                       }
  in Attr -> Element -> Element
add_attr Attr
mathspace Element
element

-- We look through the element to see if it contains an a14:m
-- element. If so, we surround it. This is a bit ugly, but it seems
-- more dependable than looking through shapes for math. Plus this is
-- an xml implementation detail, so it seems to make sense to do it at
-- the xml level.
surroundWithMathAlternate :: Element -> Element
surroundWithMathAlternate :: Element -> Element
surroundWithMathAlternate Element
element =
  case QName -> Element -> Maybe Element
findElement (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"m" Maybe FilePath
forall a. Maybe a
Nothing (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
"a14")) Element
element of
    Just Element
_ ->
      FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"mc:AlternateContent"
         [(FilePath
"xmlns:mc", FilePath
"http://schemas.openxmlformats.org/markup-compatibility/2006")
         ] [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"mc:Choice"
             [ (FilePath
"xmlns:a14", FilePath
"http://schemas.microsoft.com/office/drawing/2010/main")
             , (FilePath
"Requires", FilePath
"a14")] [ Element
element ]
           ]
    Maybe Element
Nothing -> Element
element

paragraphToElement :: PandocMonad m => Paragraph -> P m Element
paragraphToElement :: Paragraph -> P m Element
paragraphToElement Paragraph
par = do
  let
    attrs :: NameSpaces
attrs = [(FilePath
"lvl", Int -> FilePath
forall a. Show a => a -> FilePath
show (Int -> FilePath) -> Int -> FilePath
forall a b. (a -> b) -> a -> b
$ ParaProps -> Int
pPropLevel (ParaProps -> Int) -> ParaProps -> Int
forall a b. (a -> b) -> a -> b
$ Paragraph -> ParaProps
paraProps Paragraph
par)] NameSpaces -> NameSpaces -> NameSpaces
forall a. Semigroup a => a -> a -> a
<>
            (case ParaProps -> Maybe Pixels
pPropMarginLeft (Paragraph -> ParaProps
paraProps Paragraph
par) of
               Just Pixels
px -> [(FilePath
"marL", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels -> Pixels
pixelsToEmu Pixels
px)]
               Maybe Pixels
Nothing -> []
            ) NameSpaces -> NameSpaces -> NameSpaces
forall a. Semigroup a => a -> a -> a
<>
            (case ParaProps -> Maybe Pixels
pPropIndent (Paragraph -> ParaProps
paraProps Paragraph
par) of
               Just Pixels
px -> [(FilePath
"indent", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels -> Pixels
pixelsToEmu Pixels
px)]
               Maybe Pixels
Nothing -> []
            ) NameSpaces -> NameSpaces -> NameSpaces
forall a. Semigroup a => a -> a -> a
<>
            (case ParaProps -> Maybe Algnment
pPropAlign (Paragraph -> ParaProps
paraProps Paragraph
par) of
               Just Algnment
AlgnLeft -> [(FilePath
"algn", FilePath
"l")]
               Just Algnment
AlgnRight -> [(FilePath
"algn", FilePath
"r")]
               Just Algnment
AlgnCenter -> [(FilePath
"algn", FilePath
"ctr")]
               Maybe Algnment
Nothing -> []
            )
    props :: [Element]
props = [] [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<>
            (case ParaProps -> Maybe Pixels
pPropSpaceBefore (ParaProps -> Maybe Pixels) -> ParaProps -> Maybe Pixels
forall a b. (a -> b) -> a -> b
$ Paragraph -> ParaProps
paraProps Paragraph
par of
               Just Pixels
px -> [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:spcBef" [] [
                              FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:spcPts" [(FilePath
"val", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels
100 Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
px)] ()
                              ]
                          ]
               Maybe Pixels
Nothing -> []
            ) [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<>
            (case ParaProps -> Maybe BulletType
pPropBullet (ParaProps -> Maybe BulletType) -> ParaProps -> Maybe BulletType
forall a b. (a -> b) -> a -> b
$ Paragraph -> ParaProps
paraProps Paragraph
par of
               Just BulletType
Bullet -> []
               Just (AutoNumbering ListAttributes
attrs') ->
                 [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:buAutoNum" (ListAttributes -> NameSpaces
autoNumAttrs ListAttributes
attrs') ()]
               Maybe BulletType
Nothing -> [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:buNone" [] ()]
            )
  [Element]
paras <- [[Element]] -> [Element]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[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
<$> (ParaElem -> ReaderT WriterEnv (StateT WriterState m) [Element])
-> [ParaElem]
-> ReaderT WriterEnv (StateT WriterState m) [[Element]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ParaElem -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *). PandocMonad m => ParaElem -> P m [Element]
paraElemToElements (Paragraph -> [ParaElem]
paraElems Paragraph
par)
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:p" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:pPr" NameSpaces
attrs [Element]
props] [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
paras

shapeToElement :: PandocMonad m => Element -> Shape -> P m Element
shapeToElement :: Element -> Shape -> P m Element
shapeToElement Element
layout (TextBox [Paragraph]
paras)
  | NameSpaces
ns <- Element -> NameSpaces
elemToNameSpaces Element
layout
  , Just Element
cSld <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"cSld") Element
layout
  , Just Element
spTree <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"spTree") Element
cSld = do
      Element
sp <- NameSpaces -> Element -> P m Element
forall (m :: * -> *).
PandocMonad m =>
NameSpaces -> Element -> P m Element
getContentShape NameSpaces
ns Element
spTree
      [Element]
elements <- (Paragraph -> P m Element)
-> [Paragraph]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Paragraph -> P m Element
forall (m :: * -> *). PandocMonad m => Paragraph -> P m Element
paragraphToElement [Paragraph]
paras
      let txBody :: Element
txBody = FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:txBody" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
                   [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:bodyPr" [] (), FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:lstStyle" [] ()] [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
elements
          emptySpPr :: Element
emptySpPr = FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:spPr" [] ()
      Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return
        (Element -> P m Element)
-> (Element -> Element) -> Element -> P m Element
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Element
surroundWithMathAlternate
        (Element -> Element) -> (Element -> Element) -> Element -> Element
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameSpaces
-> FilePath -> FilePath -> [Element] -> Element -> Element
replaceNamedChildren NameSpaces
ns FilePath
"p" FilePath
"txBody" [Element
txBody]
        (Element -> Element) -> (Element -> Element) -> Element -> Element
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameSpaces
-> FilePath -> FilePath -> [Element] -> Element -> Element
replaceNamedChildren NameSpaces
ns FilePath
"p" FilePath
"spPr" [Element
emptySpPr]
        (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ Element
sp
-- GraphicFrame and Pic should never reach this.
shapeToElement Element
_ Shape
_ = Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sp" [] ()

shapeToElements :: PandocMonad m => Element -> Shape -> P m [Element]
shapeToElements :: Element -> Shape -> P m [Element]
shapeToElements Element
layout (Pic PicProps
picProps FilePath
fp [ParaElem]
alt) = do
  MediaInfo
mInfo <- FilePath -> [ParaElem] -> P m MediaInfo
forall (m :: * -> *).
PandocMonad m =>
FilePath -> [ParaElem] -> P m MediaInfo
registerMedia FilePath
fp [ParaElem]
alt
  case MediaInfo -> Maybe MimeType
mInfoExt MediaInfo
mInfo of
    Just MimeType
_ ->
      Element -> PicProps -> MediaInfo -> [ParaElem] -> P m [Element]
forall (m :: * -> *).
PandocMonad m =>
Element -> PicProps -> MediaInfo -> [ParaElem] -> P m [Element]
makePicElements Element
layout PicProps
picProps MediaInfo
mInfo [ParaElem]
alt
    Maybe MimeType
Nothing -> Element -> Shape -> P m [Element]
forall (m :: * -> *).
PandocMonad m =>
Element -> Shape -> P m [Element]
shapeToElements Element
layout (Shape -> P m [Element]) -> Shape -> P m [Element]
forall a b. (a -> b) -> a -> b
$ [Paragraph] -> Shape
TextBox [ParaProps -> [ParaElem] -> Paragraph
Paragraph ParaProps
forall a. Default a => a
def [ParaElem]
alt]
shapeToElements Element
layout (GraphicFrame [Graphic]
tbls [ParaElem]
cptn) =
  Element -> [Graphic] -> [ParaElem] -> P m [Element]
forall (m :: * -> *).
PandocMonad m =>
Element -> [Graphic] -> [ParaElem] -> P m [Element]
graphicFrameToElements Element
layout [Graphic]
tbls [ParaElem]
cptn
shapeToElements Element
_ (RawOOXMLShape MimeType
str) = [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [ Element
x | Elem Element
x <- MimeType -> [Content]
forall s. XmlSource s => s -> [Content]
parseXML MimeType
str ]
shapeToElements Element
layout Shape
shp = do
  Element
element <- Element -> Shape -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Element -> Shape -> P m Element
shapeToElement Element
layout Shape
shp
  [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element
element]

shapesToElements :: PandocMonad m => Element -> [Shape] -> P m [Element]
shapesToElements :: Element -> [Shape] -> P m [Element]
shapesToElements Element
layout [Shape]
shps =
 [[Element]] -> [Element]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Element]] -> [Element])
-> ReaderT WriterEnv (StateT WriterState m) [[Element]]
-> P m [Element]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Shape -> P m [Element])
-> [Shape] -> ReaderT WriterEnv (StateT WriterState m) [[Element]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Element -> Shape -> P m [Element]
forall (m :: * -> *).
PandocMonad m =>
Element -> Shape -> P m [Element]
shapeToElements Element
layout) [Shape]
shps

graphicFrameToElements :: PandocMonad m => Element -> [Graphic] -> [ParaElem] -> P m [Element]
graphicFrameToElements :: Element -> [Graphic] -> [ParaElem] -> P m [Element]
graphicFrameToElements Element
layout [Graphic]
tbls [ParaElem]
caption = do
  -- get the sizing
  Element
master <- P m Element
forall (m :: * -> *). PandocMonad m => P m Element
getMaster
  (Pixels
pageWidth, Pixels
pageHeight) <- (WriterEnv -> (Pixels, Pixels))
-> ReaderT WriterEnv (StateT WriterState m) (Pixels, Pixels)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> (Pixels, Pixels)
envPresentationSize
  let ns :: NameSpaces
ns = Element -> NameSpaces
elemToNameSpaces Element
layout
  ((Pixels
x, Pixels
y), (Pixels
cx, Pixels
cytmp)) <- NameSpaces
-> Element -> Element -> P m ((Pixels, Pixels), (Pixels, Pixels))
forall (m :: * -> *).
PandocMonad m =>
NameSpaces
-> Element -> Element -> P m ((Pixels, Pixels), (Pixels, Pixels))
getContentShapeSize NameSpaces
ns Element
layout Element
master
                           P m ((Pixels, Pixels), (Pixels, Pixels))
-> (PandocError -> P m ((Pixels, Pixels), (Pixels, Pixels)))
-> P m ((Pixels, Pixels), (Pixels, Pixels))
forall e (m :: * -> *) a.
MonadError e m =>
m a -> (e -> m a) -> m a
`catchError`
                           (\PandocError
_ -> ((Pixels, Pixels), (Pixels, Pixels))
-> P m ((Pixels, Pixels), (Pixels, Pixels))
forall (m :: * -> *) a. Monad m => a -> m a
return ((Pixels
0, Pixels
0), (Pixels
pageWidth, Pixels
pageHeight)))

  let cy :: Pixels
cy = if Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [ParaElem] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ParaElem]
caption then Pixels
cytmp Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
- Pixels
captionHeight else Pixels
cytmp

  [Element]
elements <- (Graphic -> P m Element) -> [Graphic] -> P m [Element]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Pixels -> Graphic -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Pixels -> Graphic -> P m Element
graphicToElement Pixels
cx) [Graphic]
tbls
  let graphicFrameElts :: Element
graphicFrameElts =
        FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:graphicFrame" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
        [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvGraphicFramePr" []
          [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvPr" [(FilePath
"id", FilePath
"6"), (FilePath
"name", FilePath
"Content Placeholder 5")] ()
          , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvGraphicFramePr" []
            [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:graphicFrameLocks" [(FilePath
"noGrp", FilePath
"1")] ()]
          , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvPr" []
            [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:ph" [(FilePath
"idx", FilePath
"1")] ()]
          ]
        , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:xfrm" []
          [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:off" [(FilePath
"x", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels
12700 Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
x), (FilePath
"y", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels
12700 Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
y)] ()
          , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:ext" [(FilePath
"cx", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels
12700 Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
cx), (FilePath
"cy", Pixels -> FilePath
forall a. Show a => a -> FilePath
show (Pixels -> FilePath) -> Pixels -> FilePath
forall a b. (a -> b) -> a -> b
$ Pixels
12700 Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
cy)] ()
          ]
        ] [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
elements

  if Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [ParaElem] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ParaElem]
caption
    then do Element
capElt <- ((Pixels, Pixels), (Pixels, Pixels)) -> [ParaElem] -> P m Element
forall (m :: * -> *).
PandocMonad m =>
((Pixels, Pixels), (Pixels, Pixels)) -> [ParaElem] -> P m Element
createCaption ((Pixels
x, Pixels
y), (Pixels
cx, Pixels
cytmp)) [ParaElem]
caption
            [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element
graphicFrameElts, Element
capElt]
    else [Element] -> P m [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return [Element
graphicFrameElts]

getDefaultTableStyle :: PandocMonad m => P m (Maybe T.Text)
getDefaultTableStyle :: P m (Maybe MimeType)
getDefaultTableStyle = do
  Archive
refArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envRefArchive
  Archive
distArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envDistArchive
  Element
tblStyleLst <- Archive
-> Archive
-> FilePath
-> ReaderT WriterEnv (StateT WriterState m) Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> FilePath -> m Element
parseXml Archive
refArchive Archive
distArchive FilePath
"ppt/tableStyles.xml"
  Maybe MimeType -> P m (Maybe MimeType)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe MimeType -> P m (Maybe MimeType))
-> Maybe MimeType -> P m (Maybe MimeType)
forall a b. (a -> b) -> a -> b
$ QName -> Element -> Maybe MimeType
findAttrText (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"def" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
tblStyleLst

graphicToElement :: PandocMonad m => Integer -> Graphic -> P m Element
graphicToElement :: Pixels -> Graphic -> P m Element
graphicToElement Pixels
tableWidth (Tbl TableProps
tblPr [[Paragraph]]
hdrCells [[[Paragraph]]]
rows) = do
  let colWidths :: [Pixels]
colWidths = if [[Paragraph]] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Paragraph]]
hdrCells
                  then case [[[Paragraph]]]
rows of
                         [[Paragraph]]
r : [[[Paragraph]]]
_ | Bool -> Bool
not ([[Paragraph]] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Paragraph]]
r) -> Int -> Pixels -> [Pixels]
forall a. Int -> a -> [a]
replicate ([[Paragraph]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Paragraph]]
r) (Pixels -> [Pixels]) -> Pixels -> [Pixels]
forall a b. (a -> b) -> a -> b
$
                                                 Pixels
tableWidth Pixels -> Pixels -> Pixels
forall a. Integral a => a -> a -> a
`div` Int -> Pixels
forall a. Integral a => a -> Pixels
toInteger ([[Paragraph]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Paragraph]]
r)
                         -- satisfy the compiler. This is the same as
                         -- saying that rows is empty, but the compiler
                         -- won't understand that `[]` exhausts the
                         -- alternatives.
                         [[[Paragraph]]]
_ -> []
                  else Int -> Pixels -> [Pixels]
forall a. Int -> a -> [a]
replicate ([[Paragraph]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Paragraph]]
hdrCells) (Pixels -> [Pixels]) -> Pixels -> [Pixels]
forall a b. (a -> b) -> a -> b
$
                       Pixels
tableWidth Pixels -> Pixels -> Pixels
forall a. Integral a => a -> a -> a
`div` Int -> Pixels
forall a. Integral a => a -> Pixels
toInteger ([[Paragraph]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Paragraph]]
hdrCells)

  let cellToOpenXML :: [Paragraph] -> ReaderT WriterEnv (StateT WriterState m) [Element]
cellToOpenXML [Paragraph]
paras =
        do [Element]
elements <- (Paragraph -> ReaderT WriterEnv (StateT WriterState m) Element)
-> [Paragraph]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Paragraph -> ReaderT WriterEnv (StateT WriterState m) Element
forall (m :: * -> *). PandocMonad m => Paragraph -> P m Element
paragraphToElement [Paragraph]
paras
           let elements' :: [Element]
elements' = if [Element] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Element]
elements
                           then [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:p" [] [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:endParaRPr" [] ()]]
                           else [Element]
elements

           [Element] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return
             [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:txBody" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
               [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:bodyPr" [] ()
               , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:lstStyle" [] ()]
               [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
elements']
  [[Element]]
headers' <- ([Paragraph] -> ReaderT WriterEnv (StateT WriterState m) [Element])
-> [[Paragraph]]
-> ReaderT WriterEnv (StateT WriterState m) [[Element]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM [Paragraph] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *).
PandocMonad m =>
[Paragraph] -> ReaderT WriterEnv (StateT WriterState m) [Element]
cellToOpenXML [[Paragraph]]
hdrCells
  [[[Element]]]
rows' <- ([[Paragraph]]
 -> ReaderT WriterEnv (StateT WriterState m) [[Element]])
-> [[[Paragraph]]]
-> ReaderT WriterEnv (StateT WriterState m) [[[Element]]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (([Paragraph] -> ReaderT WriterEnv (StateT WriterState m) [Element])
-> [[Paragraph]]
-> ReaderT WriterEnv (StateT WriterState m) [[Element]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM [Paragraph] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *).
PandocMonad m =>
[Paragraph] -> ReaderT WriterEnv (StateT WriterState m) [Element]
cellToOpenXML) [[[Paragraph]]]
rows
  let borderProps :: Element
borderProps = FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:tcPr" [] ()
  let emptyCell' :: [Element]
emptyCell' = [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:p" [] [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:pPr" [] ()]]
  let mkcell :: Bool -> [Element] -> Element
mkcell Bool
border [Element]
contents = FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:tc" []
                            ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ (if [Element] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Element]
contents
                               then [Element]
emptyCell'
                               else [Element]
contents) [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [ Element
borderProps | Bool
border ]
  let mkrow :: Bool -> [[Element]] -> Element
mkrow Bool
border [[Element]]
cells = FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:tr" [(FilePath
"h", FilePath
"0")] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ ([Element] -> Element) -> [[Element]] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> [Element] -> Element
mkcell Bool
border) [[Element]]
cells

  let mkgridcol :: Pixels -> Element
mkgridcol Pixels
w = FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:gridCol"
                       [(FilePath
"w", Pixels -> FilePath
forall a. Show a => a -> FilePath
show ((Pixels
12700 Pixels -> Pixels -> Pixels
forall a. Num a => a -> a -> a
* Pixels
w) :: Integer))] ()
  let hasHeader :: Bool
hasHeader = Bool -> Bool
not (([Paragraph] -> Bool) -> [[Paragraph]] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all [Paragraph] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Paragraph]]
hdrCells)

  Maybe MimeType
mbDefTblStyle <- P m (Maybe MimeType)
forall (m :: * -> *). PandocMonad m => P m (Maybe MimeType)
getDefaultTableStyle
  let tblPrElt :: Element
tblPrElt = FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:tblPr"
                 [ (FilePath
"firstRow", if TableProps -> Bool
tblPrFirstRow TableProps
tblPr then FilePath
"1" else FilePath
"0")
                 , (FilePath
"bandRow", if TableProps -> Bool
tblPrBandRow TableProps
tblPr then FilePath
"1" else FilePath
"0")
                 ] (case Maybe MimeType
mbDefTblStyle of
                      Maybe MimeType
Nothing -> []
                      Just MimeType
sty -> [FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:tableStyleId" [] (FilePath -> Element) -> FilePath -> Element
forall a b. (a -> b) -> a -> b
$ MimeType -> FilePath
T.unpack MimeType
sty])

  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:graphic" []
    [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:graphicData" [(FilePath
"uri", FilePath
"http://schemas.openxmlformats.org/drawingml/2006/table")]
     [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:tbl" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
      [ Element
tblPrElt
      , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:tblGrid" [] (if (Pixels -> Bool) -> [Pixels] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Pixels -> Pixels -> Bool
forall a. Eq a => a -> a -> Bool
==Pixels
0) [Pixels]
colWidths
                               then []
                               else (Pixels -> Element) -> [Pixels] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map Pixels -> Element
mkgridcol [Pixels]
colWidths)
      ]
      [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [ Bool -> [[Element]] -> Element
mkrow Bool
True [[Element]]
headers' | Bool
hasHeader ] [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> ([[Element]] -> Element) -> [[[Element]]] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> [[Element]] -> Element
mkrow Bool
False) [[[Element]]]
rows'
     ]
    ]


-- We get the shape by placeholder type. If there is NO type, it
-- defaults to a content placeholder.

data PHType = PHType T.Text | ObjType
  deriving (Int -> PHType -> ShowS
[PHType] -> ShowS
PHType -> FilePath
(Int -> PHType -> ShowS)
-> (PHType -> FilePath) -> ([PHType] -> ShowS) -> Show PHType
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [PHType] -> ShowS
$cshowList :: [PHType] -> ShowS
show :: PHType -> FilePath
$cshow :: PHType -> FilePath
showsPrec :: Int -> PHType -> ShowS
$cshowsPrec :: Int -> PHType -> ShowS
Show, PHType -> PHType -> Bool
(PHType -> PHType -> Bool)
-> (PHType -> PHType -> Bool) -> Eq PHType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PHType -> PHType -> Bool
$c/= :: PHType -> PHType -> Bool
== :: PHType -> PHType -> Bool
$c== :: PHType -> PHType -> Bool
Eq)

findPHType :: NameSpaces -> Element -> PHType -> Bool
findPHType :: NameSpaces -> Element -> PHType -> Bool
findPHType NameSpaces
ns Element
spElem PHType
phType
  | NameSpaces -> FilePath -> FilePath -> Element -> Bool
isElem NameSpaces
ns FilePath
"p" FilePath
"sp" Element
spElem =
    let mbPHElem :: Maybe Element
mbPHElem = (Element -> Maybe Element
forall a. a -> Maybe a
Just Element
spElem Maybe Element -> (Element -> Maybe Element) -> Maybe Element
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                   QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"nvSpPr") Maybe Element -> (Element -> Maybe Element) -> Maybe Element
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                   QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"nvPr") Maybe Element -> (Element -> Maybe Element) -> Maybe Element
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                   QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"ph"))
    in
      case Maybe Element
mbPHElem of
        -- if it's a named PHType, we want to check that the attribute
        -- value matches.
        Just Element
phElem | (PHType MimeType
tp) <- PHType
phType ->
                        case QName -> Element -> Maybe MimeType
findAttrText (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"type" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
phElem of
                          Just MimeType
tp' -> MimeType
tp MimeType -> MimeType -> Bool
forall a. Eq a => a -> a -> Bool
== MimeType
tp'
                          Maybe MimeType
Nothing -> Bool
False
        -- if it's an ObjType, we want to check that there is NO
        -- "type" attribute. In other words, a lookup should return nothing.
        Just Element
phElem | PHType
ObjType <- PHType
phType ->
                        case QName -> Element -> Maybe FilePath
findAttr (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"type" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
phElem of
                          Just FilePath
_ -> Bool
False
                          Maybe FilePath
Nothing -> Bool
True
        Maybe Element
Nothing -> Bool
False
findPHType NameSpaces
_ Element
_ PHType
_ = Bool
False

getShapesByPlaceHolderType :: NameSpaces -> Element -> PHType -> [Element]
getShapesByPlaceHolderType :: NameSpaces -> Element -> PHType -> [Element]
getShapesByPlaceHolderType NameSpaces
ns Element
spTreeElem PHType
phType
  | NameSpaces -> FilePath -> FilePath -> Element -> Bool
isElem NameSpaces
ns FilePath
"p" FilePath
"spTree" Element
spTreeElem =
      (Element -> Bool) -> Element -> [Element]
filterChildren (\Element
e -> NameSpaces -> Element -> PHType -> Bool
findPHType NameSpaces
ns Element
e PHType
phType) Element
spTreeElem
  | Bool
otherwise = []

getShapeByPlaceHolderType :: NameSpaces -> Element -> PHType -> Maybe Element
getShapeByPlaceHolderType :: NameSpaces -> Element -> PHType -> Maybe Element
getShapeByPlaceHolderType NameSpaces
ns Element
spTreeElem PHType
phType =
  [Element] -> Maybe Element
forall a. [a] -> Maybe a
listToMaybe ([Element] -> Maybe Element) -> [Element] -> Maybe Element
forall a b. (a -> b) -> a -> b
$ NameSpaces -> Element -> PHType -> [Element]
getShapesByPlaceHolderType NameSpaces
ns Element
spTreeElem PHType
phType

-- Like the above, but it tries a number of different placeholder types
getShapeByPlaceHolderTypes :: NameSpaces -> Element -> [PHType] -> Maybe Element
getShapeByPlaceHolderTypes :: NameSpaces -> Element -> [PHType] -> Maybe Element
getShapeByPlaceHolderTypes NameSpaces
_ Element
_ [] = Maybe Element
forall a. Maybe a
Nothing
getShapeByPlaceHolderTypes NameSpaces
ns Element
spTreeElem (PHType
s:[PHType]
ss) =
  case NameSpaces -> Element -> PHType -> Maybe Element
getShapeByPlaceHolderType NameSpaces
ns Element
spTreeElem PHType
s of
    Just Element
element -> Element -> Maybe Element
forall a. a -> Maybe a
Just Element
element
    Maybe Element
Nothing -> NameSpaces -> Element -> [PHType] -> Maybe Element
getShapeByPlaceHolderTypes NameSpaces
ns Element
spTreeElem [PHType]
ss

nonBodyTextToElement :: PandocMonad m => Element -> [PHType] -> [ParaElem] -> P m Element
nonBodyTextToElement :: Element -> [PHType] -> [ParaElem] -> P m Element
nonBodyTextToElement Element
layout [PHType]
phTypes [ParaElem]
paraElements
  | NameSpaces
ns <- Element -> NameSpaces
elemToNameSpaces Element
layout
  , Just Element
cSld <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"cSld") Element
layout
  , Just Element
spTree <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"spTree") Element
cSld
  , Just Element
sp <- NameSpaces -> Element -> [PHType] -> Maybe Element
getShapeByPlaceHolderTypes NameSpaces
ns Element
spTree [PHType]
phTypes = do
      let hdrPara :: Paragraph
hdrPara = ParaProps -> [ParaElem] -> Paragraph
Paragraph ParaProps
forall a. Default a => a
def [ParaElem]
paraElements
      Element
element <- Paragraph -> P m Element
forall (m :: * -> *). PandocMonad m => Paragraph -> P m Element
paragraphToElement Paragraph
hdrPara
      let txBody :: Element
txBody = FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:txBody" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
                   [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:bodyPr" [] (), FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:lstStyle" [] ()] [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<>
                   [Element
element]
      Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ NameSpaces
-> FilePath -> FilePath -> [Element] -> Element -> Element
replaceNamedChildren NameSpaces
ns FilePath
"p" FilePath
"txBody" [Element
txBody] Element
sp
  -- XXX: TODO
  | Bool
otherwise = Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sp" [] ()

contentToElement :: PandocMonad m => Element -> [ParaElem] -> [Shape] -> P m Element
contentToElement :: Element -> [ParaElem] -> [Shape] -> P m Element
contentToElement Element
layout [ParaElem]
hdrShape [Shape]
shapes
  | NameSpaces
ns <- Element -> NameSpaces
elemToNameSpaces Element
layout
  , Just Element
cSld <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"cSld") Element
layout
  , Just Element
spTree <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"spTree") Element
cSld = do
      Element
element <- Element -> [PHType] -> [ParaElem] -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Element -> [PHType] -> [ParaElem] -> P m Element
nonBodyTextToElement Element
layout [MimeType -> PHType
PHType MimeType
"title"] [ParaElem]
hdrShape
      let hdrShapeElements :: [Element]
hdrShapeElements = [Element
element | Bool -> Bool
not ([ParaElem] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ParaElem]
hdrShape)]
      [Element]
contentElements <- (WriterEnv -> WriterEnv)
-> ReaderT WriterEnv (StateT WriterState m) [Element]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local
                         (\WriterEnv
env -> WriterEnv
env {envContentType :: ContentType
envContentType = ContentType
NormalContent})
                         (Element
-> [Shape] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *).
PandocMonad m =>
Element -> [Shape] -> P m [Element]
shapesToElements Element
layout [Shape]
shapes)
      Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ NameSpaces -> Element -> [Element] -> Element
buildSpTree NameSpaces
ns Element
spTree ([Element]
hdrShapeElements [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
contentElements)
contentToElement Element
_ [ParaElem]
_ [Shape]
_ = Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sp" [] ()

twoColumnToElement :: PandocMonad m => Element -> [ParaElem] -> [Shape] -> [Shape] -> P m Element
twoColumnToElement :: Element -> [ParaElem] -> [Shape] -> [Shape] -> P m Element
twoColumnToElement Element
layout [ParaElem]
hdrShape [Shape]
shapesL [Shape]
shapesR
  | NameSpaces
ns <- Element -> NameSpaces
elemToNameSpaces Element
layout
  , Just Element
cSld <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"cSld") Element
layout
  , Just Element
spTree <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"spTree") Element
cSld = do
      Element
element <- Element -> [PHType] -> [ParaElem] -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Element -> [PHType] -> [ParaElem] -> P m Element
nonBodyTextToElement Element
layout [MimeType -> PHType
PHType MimeType
"title"] [ParaElem]
hdrShape
      let hdrShapeElements :: [Element]
hdrShapeElements = [Element
element | Bool -> Bool
not ([ParaElem] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ParaElem]
hdrShape)]
      [Element]
contentElementsL <- (WriterEnv -> WriterEnv)
-> ReaderT WriterEnv (StateT WriterState m) [Element]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local
                          (\WriterEnv
env -> WriterEnv
env {envContentType :: ContentType
envContentType =ContentType
TwoColumnLeftContent})
                          (Element
-> [Shape] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *).
PandocMonad m =>
Element -> [Shape] -> P m [Element]
shapesToElements Element
layout [Shape]
shapesL)
      [Element]
contentElementsR <- (WriterEnv -> WriterEnv)
-> ReaderT WriterEnv (StateT WriterState m) [Element]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local
                          (\WriterEnv
env -> WriterEnv
env {envContentType :: ContentType
envContentType =ContentType
TwoColumnRightContent})
                          (Element
-> [Shape] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *).
PandocMonad m =>
Element -> [Shape] -> P m [Element]
shapesToElements Element
layout [Shape]
shapesR)
      -- let contentElementsL' = map (setIdx ns "1") contentElementsL
      --     contentElementsR' = map (setIdx ns "2") contentElementsR
      Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ NameSpaces -> Element -> [Element] -> Element
buildSpTree NameSpaces
ns Element
spTree ([Element]
hdrShapeElements [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
contentElementsL [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
contentElementsR)
twoColumnToElement Element
_ [ParaElem]
_ [Shape]
_ [Shape]
_= Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sp" [] ()


titleToElement :: PandocMonad m => Element -> [ParaElem] -> P m Element
titleToElement :: Element -> [ParaElem] -> P m Element
titleToElement Element
layout [ParaElem]
titleElems
  | NameSpaces
ns <- Element -> NameSpaces
elemToNameSpaces Element
layout
  , Just Element
cSld <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"cSld") Element
layout
  , Just Element
spTree <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"spTree") Element
cSld = do
      Element
element <- Element -> [PHType] -> [ParaElem] -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Element -> [PHType] -> [ParaElem] -> P m Element
nonBodyTextToElement Element
layout [MimeType -> PHType
PHType MimeType
"title", MimeType -> PHType
PHType MimeType
"ctrTitle"] [ParaElem]
titleElems
      let titleShapeElements :: [Element]
titleShapeElements = [Element
element | Bool -> Bool
not ([ParaElem] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ParaElem]
titleElems)]
      Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ NameSpaces -> Element -> [Element] -> Element
buildSpTree NameSpaces
ns Element
spTree [Element]
titleShapeElements
titleToElement Element
_ [ParaElem]
_ = Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sp" [] ()

metadataToElement :: PandocMonad m => Element -> [ParaElem] -> [ParaElem] -> [[ParaElem]] -> [ParaElem] -> P m Element
metadataToElement :: Element
-> [ParaElem]
-> [ParaElem]
-> [[ParaElem]]
-> [ParaElem]
-> P m Element
metadataToElement Element
layout [ParaElem]
titleElems [ParaElem]
subtitleElems [[ParaElem]]
authorsElems [ParaElem]
dateElems
  | NameSpaces
ns <- Element -> NameSpaces
elemToNameSpaces Element
layout
  , Just Element
cSld <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"cSld") Element
layout
  , Just Element
spTree <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"spTree") Element
cSld = do
      [Element]
titleShapeElements <- if [ParaElem] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ParaElem]
titleElems
                            then [Element] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return []
                            else [P m Element] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Element -> [PHType] -> [ParaElem] -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Element -> [PHType] -> [ParaElem] -> P m Element
nonBodyTextToElement Element
layout [MimeType -> PHType
PHType MimeType
"ctrTitle"] [ParaElem]
titleElems]
      let combinedAuthorElems :: [ParaElem]
combinedAuthorElems = [ParaElem] -> [[ParaElem]] -> [ParaElem]
forall a. [a] -> [[a]] -> [a]
intercalate [ParaElem
Break] [[ParaElem]]
authorsElems
          subtitleAndAuthorElems :: [ParaElem]
subtitleAndAuthorElems = [ParaElem] -> [[ParaElem]] -> [ParaElem]
forall a. [a] -> [[a]] -> [a]
intercalate [ParaElem
Break, ParaElem
Break] [[ParaElem]
subtitleElems, [ParaElem]
combinedAuthorElems]
      [Element]
subtitleShapeElements <- if [ParaElem] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ParaElem]
subtitleAndAuthorElems
                               then [Element] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return []
                               else [P m Element] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Element -> [PHType] -> [ParaElem] -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Element -> [PHType] -> [ParaElem] -> P m Element
nonBodyTextToElement Element
layout [MimeType -> PHType
PHType MimeType
"subTitle"] [ParaElem]
subtitleAndAuthorElems]
      [Element]
dateShapeElements <- if [ParaElem] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ParaElem]
dateElems
                           then [Element] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return []
                           else [P m Element] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Element -> [PHType] -> [ParaElem] -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Element -> [PHType] -> [ParaElem] -> P m Element
nonBodyTextToElement Element
layout [MimeType -> PHType
PHType MimeType
"dt"] [ParaElem]
dateElems]
      Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ NameSpaces -> Element -> [Element] -> Element
buildSpTree NameSpaces
ns Element
spTree ([Element]
titleShapeElements [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
subtitleShapeElements [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
dateShapeElements)
metadataToElement Element
_ [ParaElem]
_ [ParaElem]
_ [[ParaElem]]
_ [ParaElem]
_ = Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sp" [] ()

slideToElement :: PandocMonad m => Slide -> P m Element
slideToElement :: Slide -> P m Element
slideToElement (Slide SlideId
_ l :: Layout
l@(ContentSlide [ParaElem]
hdrElems [Shape]
shapes) SpeakerNotes
_ )= do
  Element
layout <- Layout -> P m Element
forall (m :: * -> *). PandocMonad m => Layout -> P m Element
getLayout Layout
l
  Element
spTree <- (WriterEnv -> WriterEnv) -> P m Element -> P m Element
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> if [ParaElem] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ParaElem]
hdrElems
                           then WriterEnv
env
                           else WriterEnv
env{envSlideHasHeader :: Bool
envSlideHasHeader=Bool
True}) (P m Element -> P m Element) -> P m Element -> P m Element
forall a b. (a -> b) -> a -> b
$
            Element -> [ParaElem] -> [Shape] -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Element -> [ParaElem] -> [Shape] -> P m Element
contentToElement Element
layout [ParaElem]
hdrElems [Shape]
shapes
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sld"
    [ (FilePath
"xmlns:a", FilePath
"http://schemas.openxmlformats.org/drawingml/2006/main"),
      (FilePath
"xmlns:r", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships"),
      (FilePath
"xmlns:p", FilePath
"http://schemas.openxmlformats.org/presentationml/2006/main")
    ] [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cSld" [] [Element
spTree]]
slideToElement (Slide SlideId
_ l :: Layout
l@(TwoColumnSlide [ParaElem]
hdrElems [Shape]
shapesL [Shape]
shapesR) SpeakerNotes
_) = do
  Element
layout <- Layout -> P m Element
forall (m :: * -> *). PandocMonad m => Layout -> P m Element
getLayout Layout
l
  Element
spTree <- (WriterEnv -> WriterEnv) -> P m Element -> P m Element
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> if [ParaElem] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ParaElem]
hdrElems
                           then WriterEnv
env
                           else WriterEnv
env{envSlideHasHeader :: Bool
envSlideHasHeader=Bool
True}) (P m Element -> P m Element) -> P m Element -> P m Element
forall a b. (a -> b) -> a -> b
$
            Element -> [ParaElem] -> [Shape] -> [Shape] -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Element -> [ParaElem] -> [Shape] -> [Shape] -> P m Element
twoColumnToElement Element
layout [ParaElem]
hdrElems [Shape]
shapesL [Shape]
shapesR
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sld"
    [ (FilePath
"xmlns:a", FilePath
"http://schemas.openxmlformats.org/drawingml/2006/main"),
      (FilePath
"xmlns:r", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships"),
      (FilePath
"xmlns:p", FilePath
"http://schemas.openxmlformats.org/presentationml/2006/main")
    ] [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cSld" [] [Element
spTree]]
slideToElement (Slide SlideId
_ l :: Layout
l@(TitleSlide [ParaElem]
hdrElems) SpeakerNotes
_) = do
  Element
layout <- Layout -> P m Element
forall (m :: * -> *). PandocMonad m => Layout -> P m Element
getLayout Layout
l
  Element
spTree <- Element -> [ParaElem] -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Element -> [ParaElem] -> P m Element
titleToElement Element
layout [ParaElem]
hdrElems
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sld"
    [ (FilePath
"xmlns:a", FilePath
"http://schemas.openxmlformats.org/drawingml/2006/main"),
      (FilePath
"xmlns:r", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships"),
      (FilePath
"xmlns:p", FilePath
"http://schemas.openxmlformats.org/presentationml/2006/main")
    ] [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cSld" [] [Element
spTree]]
slideToElement (Slide SlideId
_ l :: Layout
l@(MetadataSlide [ParaElem]
titleElems [ParaElem]
subtitleElems [[ParaElem]]
authorElems [ParaElem]
dateElems) SpeakerNotes
_) = do
  Element
layout <- Layout -> P m Element
forall (m :: * -> *). PandocMonad m => Layout -> P m Element
getLayout Layout
l
  Element
spTree <- Element
-> [ParaElem]
-> [ParaElem]
-> [[ParaElem]]
-> [ParaElem]
-> P m Element
forall (m :: * -> *).
PandocMonad m =>
Element
-> [ParaElem]
-> [ParaElem]
-> [[ParaElem]]
-> [ParaElem]
-> P m Element
metadataToElement Element
layout [ParaElem]
titleElems [ParaElem]
subtitleElems [[ParaElem]]
authorElems [ParaElem]
dateElems
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sld"
    [ (FilePath
"xmlns:a", FilePath
"http://schemas.openxmlformats.org/drawingml/2006/main"),
      (FilePath
"xmlns:r", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships"),
      (FilePath
"xmlns:p", FilePath
"http://schemas.openxmlformats.org/presentationml/2006/main")
    ] [FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cSld" [] [Element
spTree]]


--------------------------------------------------------------------
-- Notes:

getNotesMaster :: PandocMonad m => P m Element
getNotesMaster :: P m Element
getNotesMaster = do
  Archive
refArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envRefArchive
  Archive
distArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envDistArchive
  Archive -> Archive -> FilePath -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> FilePath -> m Element
parseXml Archive
refArchive Archive
distArchive FilePath
"ppt/notesMasters/notesMaster1.xml"

getSlideNumberFieldId :: PandocMonad m => Element -> P m T.Text
getSlideNumberFieldId :: Element -> P m MimeType
getSlideNumberFieldId Element
notesMaster
  | NameSpaces
ns <- Element -> NameSpaces
elemToNameSpaces Element
notesMaster
  , Just Element
cSld <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"cSld") Element
notesMaster
  , Just Element
spTree <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"spTree") Element
cSld
  , Just Element
sp <- NameSpaces -> Element -> PHType -> Maybe Element
getShapeByPlaceHolderType NameSpaces
ns Element
spTree (MimeType -> PHType
PHType MimeType
"sldNum")
  , Just Element
txBody <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"p" FilePath
"txBody") Element
sp
  , Just Element
p <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"a" FilePath
"p") Element
txBody
  , Just Element
fld <- QName -> Element -> Maybe Element
findChild (NameSpaces -> FilePath -> FilePath -> QName
elemName NameSpaces
ns FilePath
"a" FilePath
"fld") Element
p
  , Just MimeType
fldId <- QName -> Element -> Maybe MimeType
findAttrText (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"id" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
fld =
      MimeType -> P m MimeType
forall (m :: * -> *) a. Monad m => a -> m a
return MimeType
fldId
  | Bool
otherwise = PandocError -> P m MimeType
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> P m MimeType) -> PandocError -> P m MimeType
forall a b. (a -> b) -> a -> b
$
                MimeType -> PandocError
PandocSomeError
                MimeType
"No field id for slide numbers in notesMaster.xml"

speakerNotesSlideImage :: Element
speakerNotesSlideImage :: Element
speakerNotesSlideImage =
  FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sp" []
  [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvSpPr" []
    [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvPr" [ (FilePath
"id", FilePath
"2")
                       , (FilePath
"name", FilePath
"Slide Image Placeholder 1")
                       ] ()
    , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvSpPr" []
      [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:spLocks" [ (FilePath
"noGrp", FilePath
"1")
                           , (FilePath
"noRot", FilePath
"1")
                           , (FilePath
"noChangeAspect", FilePath
"1")
                           ] ()
      ]
    , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvPr" []
      [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:ph" [(FilePath
"type", FilePath
"sldImg")] ()]
    ]
  , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:spPr" [] ()
  ]

-- we want to wipe links from the speaker notes in the
-- paragraphs. Powerpoint doesn't allow you to input them, and it
-- would provide extra complications.
removeParaLinks :: Paragraph -> Paragraph
removeParaLinks :: Paragraph -> Paragraph
removeParaLinks Paragraph
paragraph = Paragraph
paragraph{paraElems :: [ParaElem]
paraElems = (ParaElem -> ParaElem) -> [ParaElem] -> [ParaElem]
forall a b. (a -> b) -> [a] -> [b]
map ParaElem -> ParaElem
f (Paragraph -> [ParaElem]
paraElems Paragraph
paragraph)}
  where f :: ParaElem -> ParaElem
f (Run RunProps
rProps MimeType
s) = RunProps -> MimeType -> ParaElem
Run RunProps
rProps{rLink :: Maybe LinkTarget
rLink=Maybe LinkTarget
forall a. Maybe a
Nothing} MimeType
s
        f ParaElem
pe             = ParaElem
pe

-- put an empty paragraph between paragraphs for more expected spacing.
spaceParas :: [Paragraph] -> [Paragraph]
spaceParas :: [Paragraph] -> [Paragraph]
spaceParas = Paragraph -> [Paragraph] -> [Paragraph]
forall a. a -> [a] -> [a]
intersperse (ParaProps -> [ParaElem] -> Paragraph
Paragraph ParaProps
forall a. Default a => a
def [])

speakerNotesBody :: PandocMonad m => [Paragraph] -> P m Element
speakerNotesBody :: [Paragraph] -> P m Element
speakerNotesBody [Paragraph]
paras = do
  [Element]
elements <- (WriterEnv -> WriterEnv)
-> ReaderT WriterEnv (StateT WriterState m) [Element]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env{envInSpeakerNotes :: Bool
envInSpeakerNotes = Bool
True}) (ReaderT WriterEnv (StateT WriterState m) [Element]
 -> ReaderT WriterEnv (StateT WriterState m) [Element])
-> ReaderT WriterEnv (StateT WriterState m) [Element]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall a b. (a -> b) -> a -> b
$
              (Paragraph -> P m Element)
-> [Paragraph]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Paragraph -> P m Element
forall (m :: * -> *). PandocMonad m => Paragraph -> P m Element
paragraphToElement ([Paragraph] -> ReaderT WriterEnv (StateT WriterState m) [Element])
-> [Paragraph]
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall a b. (a -> b) -> a -> b
$ [Paragraph] -> [Paragraph]
spaceParas ([Paragraph] -> [Paragraph]) -> [Paragraph] -> [Paragraph]
forall a b. (a -> b) -> a -> b
$ (Paragraph -> Paragraph) -> [Paragraph] -> [Paragraph]
forall a b. (a -> b) -> [a] -> [b]
map Paragraph -> Paragraph
removeParaLinks [Paragraph]
paras
  let txBody :: Element
txBody = FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:txBody" [] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
               [FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:bodyPr" [] (), FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:lstStyle" [] ()] [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
elements
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$
    FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sp" []
    [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvSpPr" []
      [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvPr" [ (FilePath
"id", FilePath
"3")
                         , (FilePath
"name", FilePath
"Notes Placeholder 2")
                         ] ()
      , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvSpPr" []
        [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:spLocks" [(FilePath
"noGrp", FilePath
"1")] ()]
      , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvPr" []
        [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:ph" [(FilePath
"type", FilePath
"body"), (FilePath
"idx", FilePath
"1")] ()]
      ]
    , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:spPr" [] ()
    , Element
txBody
    ]

speakerNotesSlideNumber :: Int -> T.Text -> Element
speakerNotesSlideNumber :: Int -> MimeType -> Element
speakerNotesSlideNumber Int
pgNum MimeType
fieldId =
  FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sp" []
  [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvSpPr" []
    [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvPr" [ (FilePath
"id", FilePath
"4")
                       , (FilePath
"name", FilePath
"Slide Number Placeholder 3")
                       ] ()
    , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvSpPr" []
      [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:spLocks" [(FilePath
"noGrp", FilePath
"1")] ()]
    , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvPr" []
      [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:ph" [ (FilePath
"type", FilePath
"sldNum")
                      , (FilePath
"sz", FilePath
"quarter")
                      , (FilePath
"idx", FilePath
"10")
                      ] ()
      ]
    ]
  , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:spPr" [] ()
  , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:txBody" []
    [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:bodyPr" [] ()
    , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:lstStyle" [] ()
    , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:p" []
      [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:fld" [ (FilePath
"id", MimeType -> FilePath
T.unpack MimeType
fieldId)
                       , (FilePath
"type", FilePath
"slidenum")
                       ]
        [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:rPr" [(FilePath
"lang", FilePath
"en-US")] ()
        , FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:t" [] (Int -> FilePath
forall a. Show a => a -> FilePath
show Int
pgNum)
        ]
      , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:endParaRPr" [(FilePath
"lang", FilePath
"en-US")] ()
      ]
    ]
  ]

slideToSpeakerNotesElement :: PandocMonad m => Slide -> P m (Maybe Element)
slideToSpeakerNotesElement :: Slide -> P m (Maybe Element)
slideToSpeakerNotesElement (Slide SlideId
_ Layout
_ (SpeakerNotes [])) = Maybe Element -> P m (Maybe Element)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Element
forall a. Maybe a
Nothing
slideToSpeakerNotesElement slide :: Slide
slide@(Slide SlideId
_ Layout
_ (SpeakerNotes [Paragraph]
paras)) = do
  Element
master <- P m Element
forall (m :: * -> *). PandocMonad m => P m Element
getNotesMaster
  MimeType
fieldId  <- Element -> P m MimeType
forall (m :: * -> *). PandocMonad m => Element -> P m MimeType
getSlideNumberFieldId Element
master
  Int
num <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  let imgShape :: Element
imgShape = Element
speakerNotesSlideImage
      sldNumShape :: Element
sldNumShape = Int -> MimeType -> Element
speakerNotesSlideNumber Int
num MimeType
fieldId
  Element
bodyShape <- [Paragraph] -> P m Element
forall (m :: * -> *). PandocMonad m => [Paragraph] -> P m Element
speakerNotesBody [Paragraph]
paras
  Maybe Element -> P m (Maybe Element)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Element -> P m (Maybe Element))
-> Maybe Element -> P m (Maybe Element)
forall a b. (a -> b) -> a -> b
$ Element -> Maybe Element
forall a. a -> Maybe a
Just (Element -> Maybe Element) -> Element -> Maybe Element
forall a b. (a -> b) -> a -> b
$
    FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:notes"
    [ (FilePath
"xmlns:a", FilePath
"http://schemas.openxmlformats.org/drawingml/2006/main")
    , (FilePath
"xmlns:r", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships")
    , (FilePath
"xmlns:p", FilePath
"http://schemas.openxmlformats.org/presentationml/2006/main")
    ] [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cSld" []
        [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:spTree" []
          [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvGrpSpPr" []
            [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvPr" [(FilePath
"id", FilePath
"1"), (FilePath
"name", FilePath
"")] ()
            , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:cNvGrpSpPr" [] ()
            , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:nvPr" [] ()
            ]
          , FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:grpSpPr" []
            [ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:xfrm" []
              [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:off" [(FilePath
"x", FilePath
"0"), (FilePath
"y", FilePath
"0")] ()
              , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:ext" [(FilePath
"cx", FilePath
"0"), (FilePath
"cy", FilePath
"0")] ()
              , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:chOff" [(FilePath
"x", FilePath
"0"), (FilePath
"y", FilePath
"0")] ()
              , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"a:chExt" [(FilePath
"cx", FilePath
"0"), (FilePath
"cy", FilePath
"0")] ()
              ]
            ]
          , Element
imgShape
          , Element
bodyShape
          , Element
sldNumShape
          ]
        ]
      ]

-----------------------------------------------------------------------

getSlideIdNum :: PandocMonad m => SlideId -> P m Int
getSlideIdNum :: SlideId -> P m Int
getSlideIdNum SlideId
sldId = do
  Map SlideId Int
slideIdMap <- (WriterEnv -> Map SlideId Int)
-> ReaderT WriterEnv (StateT WriterState m) (Map SlideId Int)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Map SlideId Int
envSlideIdMap
  case  SlideId -> Map SlideId Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup SlideId
sldId Map SlideId Int
slideIdMap of
    Just Int
n -> Int -> P m Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
n
    Maybe Int
Nothing -> PandocError -> P m Int
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> P m Int) -> PandocError -> P m Int
forall a b. (a -> b) -> a -> b
$
               MimeType -> PandocError
PandocShouldNeverHappenError (MimeType -> PandocError) -> MimeType -> PandocError
forall a b. (a -> b) -> a -> b
$
               MimeType
"Slide Id " MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> FilePath -> MimeType
T.pack (SlideId -> FilePath
forall a. Show a => a -> FilePath
show SlideId
sldId) MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
" not found."

slideNum :: PandocMonad m => Slide -> P m Int
slideNum :: Slide -> P m Int
slideNum Slide
slide = SlideId -> P m Int
forall (m :: * -> *). PandocMonad m => SlideId -> P m Int
getSlideIdNum (SlideId -> P m Int) -> SlideId -> P m Int
forall a b. (a -> b) -> a -> b
$ Slide -> SlideId
slideId Slide
slide

idNumToFilePath :: Int -> FilePath
idNumToFilePath :: Int -> FilePath
idNumToFilePath Int
idNum = FilePath
"slide" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
idNum FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
".xml"

slideToFilePath :: PandocMonad m => Slide -> P m FilePath
slideToFilePath :: Slide -> P m FilePath
slideToFilePath Slide
slide = do
  Int
idNum <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  FilePath -> P m FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> P m FilePath) -> FilePath -> P m FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"slide" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
idNum FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
".xml"

slideToRelId :: PandocMonad m => Slide -> P m T.Text
slideToRelId :: Slide -> P m MimeType
slideToRelId Slide
slide = do
  Int
n <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  Int
offset <- (WriterEnv -> Int) -> P m Int
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Int
envSlideIdOffset
  MimeType -> P m MimeType
forall (m :: * -> *) a. Monad m => a -> m a
return (MimeType -> P m MimeType) -> MimeType -> P m MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
"rId" MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> FilePath -> MimeType
T.pack (Int -> FilePath
forall a. Show a => a -> FilePath
show (Int -> FilePath) -> Int -> FilePath
forall a b. (a -> b) -> a -> b
$ Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
offset)


data Relationship = Relationship { Relationship -> Int
relId :: Int
                                 , Relationship -> MimeType
relType :: MimeType
                                 , Relationship -> FilePath
relTarget :: FilePath
                                 } deriving (Int -> Relationship -> ShowS
[Relationship] -> ShowS
Relationship -> FilePath
(Int -> Relationship -> ShowS)
-> (Relationship -> FilePath)
-> ([Relationship] -> ShowS)
-> Show Relationship
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Relationship] -> ShowS
$cshowList :: [Relationship] -> ShowS
show :: Relationship -> FilePath
$cshow :: Relationship -> FilePath
showsPrec :: Int -> Relationship -> ShowS
$cshowsPrec :: Int -> Relationship -> ShowS
Show, Relationship -> Relationship -> Bool
(Relationship -> Relationship -> Bool)
-> (Relationship -> Relationship -> Bool) -> Eq Relationship
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Relationship -> Relationship -> Bool
$c/= :: Relationship -> Relationship -> Bool
== :: Relationship -> Relationship -> Bool
$c== :: Relationship -> Relationship -> Bool
Eq)

elementToRel :: Element -> Maybe Relationship
elementToRel :: Element -> Maybe Relationship
elementToRel Element
element
  | Element -> QName
elName Element
element QName -> QName -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"Relationship" (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
"http://schemas.openxmlformats.org/package/2006/relationships") Maybe FilePath
forall a. Maybe a
Nothing =
      do FilePath
rId <- QName -> Element -> Maybe FilePath
findAttr (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"Id" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
element
         FilePath
numStr <- FilePath -> FilePath -> Maybe FilePath
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix FilePath
"rId" FilePath
rId
         Int
num <- case ReadS Int
forall a. Read a => ReadS a
reads FilePath
numStr :: [(Int, String)] of
           (Int
n, FilePath
_) : [(Int, FilePath)]
_ -> Int -> Maybe Int
forall a. a -> Maybe a
Just Int
n
           []         -> Maybe Int
forall a. Maybe a
Nothing
         MimeType
type' <- QName -> Element -> Maybe MimeType
findAttrText (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"Type" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
element
         FilePath
target <- QName -> Element -> Maybe FilePath
findAttr (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"Target" Maybe FilePath
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) Element
element
         Relationship -> Maybe Relationship
forall (m :: * -> *) a. Monad m => a -> m a
return (Relationship -> Maybe Relationship)
-> Relationship -> Maybe Relationship
forall a b. (a -> b) -> a -> b
$ Int -> MimeType -> FilePath -> Relationship
Relationship Int
num MimeType
type' FilePath
target
  | Bool
otherwise = Maybe Relationship
forall a. Maybe a
Nothing

slideToPresRel :: PandocMonad m => Slide -> P m Relationship
slideToPresRel :: Slide -> P m Relationship
slideToPresRel Slide
slide = do
  Int
idNum <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  Int
n <- (WriterEnv -> Int) -> P m Int
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Int
envSlideIdOffset
  let rId :: Int
rId = Int
idNum Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n
      fp :: FilePath
fp = FilePath
"slides/" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
idNumToFilePath Int
idNum
  Relationship -> P m Relationship
forall (m :: * -> *) a. Monad m => a -> m a
return (Relationship -> P m Relationship)
-> Relationship -> P m Relationship
forall a b. (a -> b) -> a -> b
$ Relationship :: Int -> MimeType -> FilePath -> Relationship
Relationship { relId :: Int
relId = Int
rId
                        , relType :: MimeType
relType = MimeType
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/slide"
                        , relTarget :: FilePath
relTarget = FilePath
fp
                        }

getRels :: PandocMonad m => P m [Relationship]
getRels :: P m [Relationship]
getRels = do
  Archive
refArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envRefArchive
  Archive
distArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envDistArchive
  Element
relsElem <- Archive
-> Archive
-> FilePath
-> ReaderT WriterEnv (StateT WriterState m) Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> FilePath -> m Element
parseXml Archive
refArchive Archive
distArchive FilePath
"ppt/_rels/presentation.xml.rels"
  let globalNS :: FilePath
globalNS = FilePath
"http://schemas.openxmlformats.org/package/2006/relationships"
  let relElems :: [Element]
relElems = QName -> Element -> [Element]
findChildren (FilePath -> Maybe FilePath -> Maybe FilePath -> QName
QName FilePath
"Relationship" (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
globalNS) Maybe FilePath
forall a. Maybe a
Nothing) Element
relsElem
  [Relationship] -> P m [Relationship]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Relationship] -> P m [Relationship])
-> [Relationship] -> P m [Relationship]
forall a b. (a -> b) -> a -> b
$ (Element -> Maybe Relationship) -> [Element] -> [Relationship]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Element -> Maybe Relationship
elementToRel [Element]
relElems

presentationToRels :: PandocMonad m => Presentation -> P m [Relationship]
presentationToRels :: Presentation -> P m [Relationship]
presentationToRels pres :: Presentation
pres@(Presentation DocProps
_ [Slide]
slides) = do
  [Relationship]
mySlideRels <- (Slide -> ReaderT WriterEnv (StateT WriterState m) Relationship)
-> [Slide] -> P m [Relationship]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Slide -> ReaderT WriterEnv (StateT WriterState m) Relationship
forall (m :: * -> *). PandocMonad m => Slide -> P m Relationship
slideToPresRel [Slide]
slides
  let notesMasterRels :: [Relationship]
notesMasterRels =
        [Relationship :: Int -> MimeType -> FilePath -> Relationship
Relationship { relId :: Int
relId = [Relationship] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Relationship]
mySlideRels Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2
                         , relType :: MimeType
relType = MimeType
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/notesMaster"
                         , relTarget :: FilePath
relTarget = FilePath
"notesMasters/notesMaster1.xml"
                         } | Presentation -> Bool
presHasSpeakerNotes Presentation
pres]
      insertedRels :: [Relationship]
insertedRels = [Relationship]
mySlideRels [Relationship] -> [Relationship] -> [Relationship]
forall a. Semigroup a => a -> a -> a
<> [Relationship]
notesMasterRels
  [Relationship]
rels <- P m [Relationship]
forall (m :: * -> *). PandocMonad m => P m [Relationship]
getRels
  -- we remove the slide rels and the notesmaster (if it's
  -- there). We'll put these back in ourselves, if necessary.
  let relsWeKeep :: [Relationship]
relsWeKeep = (Relationship -> Bool) -> [Relationship] -> [Relationship]
forall a. (a -> Bool) -> [a] -> [a]
filter
                   (\Relationship
r -> Relationship -> MimeType
relType Relationship
r MimeType -> MimeType -> Bool
forall a. Eq a => a -> a -> Bool
/= MimeType
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/slide" Bool -> Bool -> Bool
&&
                          Relationship -> MimeType
relType Relationship
r MimeType -> MimeType -> Bool
forall a. Eq a => a -> a -> Bool
/= MimeType
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/notesMaster")
                   [Relationship]
rels
  -- We want to make room for the slides in the id space. The slides
  -- will start at Id2 (since Id1 is for the slide master). There are
  -- two slides in the data file, but that might change in the future,
  -- so we will do this:
  --
  -- 1. We look to see what the minimum relWithoutSlide id (greater than 1) is.
  -- 2. We add the difference between this and the number of slides to
  -- all relWithoutSlide rels (unless they're 1)
  -- 3. If we have a notesmaster slide, we make space for that as well.

  let minRelNotOne :: Int
minRelNotOne = case (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int
1Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<) ([Int] -> [Int]) -> [Int] -> [Int]
forall a b. (a -> b) -> a -> b
$ (Relationship -> Int) -> [Relationship] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Relationship -> Int
relId [Relationship]
relsWeKeep of
        [] -> Int
0                 -- doesn't matter in this case, since
                                -- there will be nothing to map the
                                -- function over
        [Int]
l  -> [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum [Int]
l

      modifyRelNum :: Int -> Int
      modifyRelNum :: Int -> Int
modifyRelNum Int
1 = Int
1
      modifyRelNum Int
n = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
minRelNotOne Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [Relationship] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Relationship]
insertedRels

      relsWeKeep' :: [Relationship]
relsWeKeep' = (Relationship -> Relationship) -> [Relationship] -> [Relationship]
forall a b. (a -> b) -> [a] -> [b]
map (\Relationship
r -> Relationship
r{relId :: Int
relId = Int -> Int
modifyRelNum (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Relationship -> Int
relId Relationship
r}) [Relationship]
relsWeKeep

  [Relationship] -> P m [Relationship]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Relationship] -> P m [Relationship])
-> [Relationship] -> P m [Relationship]
forall a b. (a -> b) -> a -> b
$ [Relationship]
insertedRels [Relationship] -> [Relationship] -> [Relationship]
forall a. Semigroup a => a -> a -> a
<> [Relationship]
relsWeKeep'

-- We make this ourselves, in case there's a thumbnail in the one from
-- the template.
topLevelRels :: [Relationship]
topLevelRels :: [Relationship]
topLevelRels =
  [ Relationship :: Int -> MimeType -> FilePath -> Relationship
Relationship { relId :: Int
relId = Int
1
                 , relType :: MimeType
relType = MimeType
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/officeDocument"
                 , relTarget :: FilePath
relTarget = FilePath
"ppt/presentation.xml"
                 }
  , Relationship :: Int -> MimeType -> FilePath -> Relationship
Relationship { relId :: Int
relId = Int
2
                 , relType :: MimeType
relType = MimeType
"http://schemas.openxmlformats.org/package/2006/relationships/metadata/core-properties"
                 , relTarget :: FilePath
relTarget = FilePath
"docProps/core.xml"
                 }
  , Relationship :: Int -> MimeType -> FilePath -> Relationship
Relationship { relId :: Int
relId = Int
3
                 , relType :: MimeType
relType = MimeType
"http://schemas.openxmlformats.org/package/2006/relationships/metadata/extended-properties"
                 , relTarget :: FilePath
relTarget = FilePath
"docProps/app.xml"
                 }
  , Relationship :: Int -> MimeType -> FilePath -> Relationship
Relationship { relId :: Int
relId = Int
4
                 , relType :: MimeType
relType = MimeType
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/custom-properties"
                 , relTarget :: FilePath
relTarget = FilePath
"docProps/custom.xml"
                 }
  ]

topLevelRelsEntry :: PandocMonad m => P m Entry
topLevelRelsEntry :: P m Entry
topLevelRelsEntry = FilePath -> Element -> P m Entry
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Element -> P m Entry
elemToEntry FilePath
"_rels/.rels" (Element -> P m Entry) -> Element -> P m Entry
forall a b. (a -> b) -> a -> b
$ [Relationship] -> Element
relsToElement [Relationship]
topLevelRels

relToElement :: Relationship -> Element
relToElement :: Relationship -> Element
relToElement Relationship
rel = FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Relationship" [ (FilePath
"Id", FilePath
"rId" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<>
    Int -> FilePath
forall a. Show a => a -> FilePath
show (Relationship -> Int
relId Relationship
rel))
                                         , (FilePath
"Type", MimeType -> FilePath
T.unpack (MimeType -> FilePath) -> MimeType -> FilePath
forall a b. (a -> b) -> a -> b
$ Relationship -> MimeType
relType Relationship
rel)
                                         , (FilePath
"Target", Relationship -> FilePath
relTarget Relationship
rel) ] ()

relsToElement :: [Relationship] -> Element
relsToElement :: [Relationship] -> Element
relsToElement [Relationship]
rels = FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Relationships"
                     [(FilePath
"xmlns", FilePath
"http://schemas.openxmlformats.org/package/2006/relationships")]
                     ((Relationship -> Element) -> [Relationship] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map Relationship -> Element
relToElement [Relationship]
rels)

presentationToRelsEntry :: PandocMonad m => Presentation -> P m Entry
presentationToRelsEntry :: Presentation -> P m Entry
presentationToRelsEntry Presentation
pres = do
  [Relationship]
rels <- Presentation -> P m [Relationship]
forall (m :: * -> *).
PandocMonad m =>
Presentation -> P m [Relationship]
presentationToRels Presentation
pres
  FilePath -> Element -> P m Entry
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Element -> P m Entry
elemToEntry FilePath
"ppt/_rels/presentation.xml.rels" (Element -> P m Entry) -> Element -> P m Entry
forall a b. (a -> b) -> a -> b
$ [Relationship] -> Element
relsToElement [Relationship]
rels

elemToEntry :: PandocMonad m => FilePath -> Element -> P m Entry
elemToEntry :: FilePath -> Element -> P m Entry
elemToEntry FilePath
fp Element
element = do
  Pixels
epochtime <- POSIXTime -> Pixels
forall a b. (RealFrac a, Integral b) => a -> b
floor (POSIXTime -> Pixels)
-> (UTCTime -> POSIXTime) -> UTCTime -> Pixels
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> POSIXTime
utcTimeToPOSIXSeconds (UTCTime -> Pixels)
-> ReaderT WriterEnv (StateT WriterState m) UTCTime
-> ReaderT WriterEnv (StateT WriterState m) Pixels
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (WriterEnv -> UTCTime)
-> ReaderT WriterEnv (StateT WriterState m) UTCTime
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> UTCTime
envUTCTime
  Entry -> P m Entry
forall (m :: * -> *) a. Monad m => a -> m a
return (Entry -> P m Entry) -> Entry -> P m Entry
forall a b. (a -> b) -> a -> b
$ FilePath -> Pixels -> ByteString -> Entry
toEntry FilePath
fp Pixels
epochtime (ByteString -> Entry) -> ByteString -> Entry
forall a b. (a -> b) -> a -> b
$ Element -> ByteString
renderXml Element
element

slideToEntry :: PandocMonad m => Slide -> P m Entry
slideToEntry :: Slide -> P m Entry
slideToEntry Slide
slide = do
  Int
idNum <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  (WriterEnv -> WriterEnv) -> P m Entry -> P m Entry
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env{envCurSlideId :: Int
envCurSlideId = Int
idNum}) (P m Entry -> P m Entry) -> P m Entry -> P m Entry
forall a b. (a -> b) -> a -> b
$ do
    Element
element <- Slide -> P m Element
forall (m :: * -> *). PandocMonad m => Slide -> P m Element
slideToElement Slide
slide
    FilePath -> Element -> P m Entry
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Element -> P m Entry
elemToEntry (FilePath
"ppt/slides/" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
idNumToFilePath Int
idNum) Element
element

slideToSpeakerNotesEntry :: PandocMonad m => Slide -> P m (Maybe Entry)
slideToSpeakerNotesEntry :: Slide -> P m (Maybe Entry)
slideToSpeakerNotesEntry Slide
slide = do
  Int
idNum <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  (WriterEnv -> WriterEnv) -> P m (Maybe Entry) -> P m (Maybe Entry)
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterEnv
env -> WriterEnv
env{envCurSlideId :: Int
envCurSlideId = Int
idNum}) (P m (Maybe Entry) -> P m (Maybe Entry))
-> P m (Maybe Entry) -> P m (Maybe Entry)
forall a b. (a -> b) -> a -> b
$ do
    Maybe Element
mbElement <- Slide -> P m (Maybe Element)
forall (m :: * -> *). PandocMonad m => Slide -> P m (Maybe Element)
slideToSpeakerNotesElement Slide
slide
    Maybe Int
mbNotesIdNum <- do Map Int Int
mp <- (WriterEnv -> Map Int Int)
-> ReaderT WriterEnv (StateT WriterState m) (Map Int Int)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Map Int Int
envSpeakerNotesIdMap
                       Maybe Int -> ReaderT WriterEnv (StateT WriterState m) (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Int -> ReaderT WriterEnv (StateT WriterState m) (Maybe Int))
-> Maybe Int
-> ReaderT WriterEnv (StateT WriterState m) (Maybe Int)
forall a b. (a -> b) -> a -> b
$ Int -> Map Int Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
idNum Map Int Int
mp
    case Maybe Element
mbElement of
      Just Element
element | Just Int
notesIdNum <- Maybe Int
mbNotesIdNum ->
                       Entry -> Maybe Entry
forall a. a -> Maybe a
Just (Entry -> Maybe Entry)
-> ReaderT WriterEnv (StateT WriterState m) Entry
-> P m (Maybe Entry)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                       FilePath
-> Element -> ReaderT WriterEnv (StateT WriterState m) Entry
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Element -> P m Entry
elemToEntry
                       (FilePath
"ppt/notesSlides/notesSlide" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
notesIdNum FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
".xml")
                       Element
element
      Maybe Element
_ -> Maybe Entry -> P m (Maybe Entry)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Entry
forall a. Maybe a
Nothing

slideToSpeakerNotesRelElement :: PandocMonad m => Slide -> P m (Maybe Element)
slideToSpeakerNotesRelElement :: Slide -> P m (Maybe Element)
slideToSpeakerNotesRelElement (Slide SlideId
_ Layout
_ (SpeakerNotes [])) = Maybe Element -> P m (Maybe Element)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Element
forall a. Maybe a
Nothing
slideToSpeakerNotesRelElement slide :: Slide
slide@Slide{} = do
  Int
idNum <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  Maybe Element -> P m (Maybe Element)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Element -> P m (Maybe Element))
-> Maybe Element -> P m (Maybe Element)
forall a b. (a -> b) -> a -> b
$ Element -> Maybe Element
forall a. a -> Maybe a
Just (Element -> Maybe Element) -> Element -> Maybe Element
forall a b. (a -> b) -> a -> b
$
    FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Relationships"
    [(FilePath
"xmlns", FilePath
"http://schemas.openxmlformats.org/package/2006/relationships")]
    [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Relationship" [ (FilePath
"Id", FilePath
"rId2")
                            , (FilePath
"Type", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/slide")
                            , (FilePath
"Target", FilePath
"../slides/slide" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
idNum FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
".xml")
                            ] ()
    , FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Relationship" [ (FilePath
"Id", FilePath
"rId1")
                            , (FilePath
"Type", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/notesMaster")
                            , (FilePath
"Target", FilePath
"../notesMasters/notesMaster1.xml")
                            ] ()
    ]


slideToSpeakerNotesRelEntry :: PandocMonad m => Slide -> P m (Maybe Entry)
slideToSpeakerNotesRelEntry :: Slide -> P m (Maybe Entry)
slideToSpeakerNotesRelEntry Slide
slide = do
  Int
idNum <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  Maybe Element
mbElement <- Slide -> P m (Maybe Element)
forall (m :: * -> *). PandocMonad m => Slide -> P m (Maybe Element)
slideToSpeakerNotesRelElement Slide
slide
  Map Int Int
mp <- (WriterEnv -> Map Int Int)
-> ReaderT WriterEnv (StateT WriterState m) (Map Int Int)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Map Int Int
envSpeakerNotesIdMap
  let mbNotesIdNum :: Maybe Int
mbNotesIdNum = Int -> Map Int Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
idNum Map Int Int
mp
  case Maybe Element
mbElement of
    Just Element
element | Just Int
notesIdNum <- Maybe Int
mbNotesIdNum ->
      Entry -> Maybe Entry
forall a. a -> Maybe a
Just (Entry -> Maybe Entry)
-> ReaderT WriterEnv (StateT WriterState m) Entry
-> P m (Maybe Entry)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
      FilePath
-> Element -> ReaderT WriterEnv (StateT WriterState m) Entry
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Element -> P m Entry
elemToEntry
      (FilePath
"ppt/notesSlides/_rels/notesSlide" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
notesIdNum FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
".xml.rels")
      Element
element
    Maybe Element
_ -> Maybe Entry -> P m (Maybe Entry)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Entry
forall a. Maybe a
Nothing

slideToSlideRelEntry :: PandocMonad m => Slide -> P m Entry
slideToSlideRelEntry :: Slide -> P m Entry
slideToSlideRelEntry Slide
slide = do
  Int
idNum <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  Element
element <- Slide -> P m Element
forall (m :: * -> *). PandocMonad m => Slide -> P m Element
slideToSlideRelElement Slide
slide
  FilePath -> Element -> P m Entry
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Element -> P m Entry
elemToEntry (FilePath
"ppt/slides/_rels/" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
idNumToFilePath Int
idNum FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
".rels") Element
element

linkRelElement :: PandocMonad m => (Int, LinkTarget) -> P m Element
linkRelElement :: (Int, LinkTarget) -> P m Element
linkRelElement (Int
rIdNum, InternalTarget SlideId
targetId) = do
  Int
targetIdNum <- SlideId -> P m Int
forall (m :: * -> *). PandocMonad m => SlideId -> P m Int
getSlideIdNum SlideId
targetId
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$
    FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Relationship" [ (FilePath
"Id", FilePath
"rId" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
rIdNum)
                          , (FilePath
"Type", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/slide")
                          , (FilePath
"Target", FilePath
"slide" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
targetIdNum FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
".xml")
                          ] ()
linkRelElement (Int
rIdNum, ExternalTarget (MimeType
url, MimeType
_)) =
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$
    FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Relationship" [ (FilePath
"Id", FilePath
"rId" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
rIdNum)
                          , (FilePath
"Type", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/hyperlink")
                          , (FilePath
"Target", MimeType -> FilePath
T.unpack MimeType
url)
                          , (FilePath
"TargetMode", FilePath
"External")
                          ] ()

linkRelElements :: PandocMonad m => M.Map Int LinkTarget -> P m [Element]
linkRelElements :: Map Int LinkTarget -> P m [Element]
linkRelElements Map Int LinkTarget
mp = ((Int, LinkTarget)
 -> ReaderT WriterEnv (StateT WriterState m) Element)
-> [(Int, LinkTarget)] -> P m [Element]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Int, LinkTarget)
-> ReaderT WriterEnv (StateT WriterState m) Element
forall (m :: * -> *).
PandocMonad m =>
(Int, LinkTarget) -> P m Element
linkRelElement (Map Int LinkTarget -> [(Int, LinkTarget)]
forall k a. Map k a -> [(k, a)]
M.toList Map Int LinkTarget
mp)

mediaRelElement :: MediaInfo -> Element
mediaRelElement :: MediaInfo -> Element
mediaRelElement MediaInfo
mInfo =
  let ext :: MimeType
ext = MimeType -> Maybe MimeType -> MimeType
forall a. a -> Maybe a -> a
fromMaybe MimeType
"" (MediaInfo -> Maybe MimeType
mInfoExt MediaInfo
mInfo)
  in
    FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Relationship" [ (FilePath
"Id", FilePath
"rId" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<>
      Int -> FilePath
forall a. Show a => a -> FilePath
show (MediaInfo -> Int
mInfoLocalId MediaInfo
mInfo))
                          , (FilePath
"Type", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/image")
                          , (FilePath
"Target", FilePath
"../media/image" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<>
      Int -> FilePath
forall a. Show a => a -> FilePath
show (MediaInfo -> Int
mInfoGlobalId MediaInfo
mInfo) FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> MimeType -> FilePath
T.unpack MimeType
ext)
                          ] ()

speakerNotesSlideRelElement :: PandocMonad m => Slide -> P m (Maybe Element)
speakerNotesSlideRelElement :: Slide -> P m (Maybe Element)
speakerNotesSlideRelElement Slide
slide = do
  Int
idNum <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  Map Int Int
mp <- (WriterEnv -> Map Int Int)
-> ReaderT WriterEnv (StateT WriterState m) (Map Int Int)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Map Int Int
envSpeakerNotesIdMap
  Maybe Element -> P m (Maybe Element)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Element -> P m (Maybe Element))
-> Maybe Element -> P m (Maybe Element)
forall a b. (a -> b) -> a -> b
$ case Int -> Map Int Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
idNum Map Int Int
mp of
    Maybe Int
Nothing -> Maybe Element
forall a. Maybe a
Nothing
    Just Int
n ->
      let target :: FilePath
target = FilePath
"../notesSlides/notesSlide" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
n FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
".xml"
      in Element -> Maybe Element
forall a. a -> Maybe a
Just (Element -> Maybe Element) -> Element -> Maybe Element
forall a b. (a -> b) -> a -> b
$
         FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Relationship" [ (FilePath
"Id", FilePath
"rId2")
                               , (FilePath
"Type", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/notesSlide")
                               , (FilePath
"Target", FilePath
target)
                               ] ()

slideToSlideRelElement :: PandocMonad m => Slide -> P m Element
slideToSlideRelElement :: Slide -> P m Element
slideToSlideRelElement Slide
slide = do
  Int
idNum <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  let target :: FilePath
target =  case Slide
slide of
        (Slide SlideId
_ MetadataSlide{} SpeakerNotes
_)  -> FilePath
"../slideLayouts/slideLayout1.xml"
        (Slide SlideId
_ TitleSlide{} SpeakerNotes
_)     -> FilePath
"../slideLayouts/slideLayout3.xml"
        (Slide SlideId
_ ContentSlide{} SpeakerNotes
_)   -> FilePath
"../slideLayouts/slideLayout2.xml"
        (Slide SlideId
_ TwoColumnSlide{} SpeakerNotes
_) -> FilePath
"../slideLayouts/slideLayout4.xml"

  [Element]
speakerNotesRels <- Maybe Element -> [Element]
forall a. Maybe a -> [a]
maybeToList (Maybe Element -> [Element])
-> ReaderT WriterEnv (StateT WriterState m) (Maybe Element)
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Slide -> ReaderT WriterEnv (StateT WriterState m) (Maybe Element)
forall (m :: * -> *). PandocMonad m => Slide -> P m (Maybe Element)
speakerNotesSlideRelElement Slide
slide

  Map Int (Map Int LinkTarget)
linkIds <- (WriterState -> Map Int (Map Int LinkTarget))
-> ReaderT
     WriterEnv (StateT WriterState m) (Map Int (Map Int LinkTarget))
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Int (Map Int LinkTarget)
stLinkIds
  Map Int [MediaInfo]
mediaIds <- (WriterState -> Map Int [MediaInfo])
-> ReaderT WriterEnv (StateT WriterState m) (Map Int [MediaInfo])
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Int [MediaInfo]
stMediaIds

  [Element]
linkRels <- case Int -> Map Int (Map Int LinkTarget) -> Maybe (Map Int LinkTarget)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
idNum Map Int (Map Int LinkTarget)
linkIds of
                Just Map Int LinkTarget
mp -> Map Int LinkTarget
-> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *).
PandocMonad m =>
Map Int LinkTarget -> P m [Element]
linkRelElements Map Int LinkTarget
mp
                Maybe (Map Int LinkTarget)
Nothing -> [Element] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (m :: * -> *) a. Monad m => a -> m a
return []
  let mediaRels :: [Element]
mediaRels = case Int -> Map Int [MediaInfo] -> Maybe [MediaInfo]
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
idNum Map Int [MediaInfo]
mediaIds of
                   Just [MediaInfo]
mInfos -> (MediaInfo -> Element) -> [MediaInfo] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map MediaInfo -> Element
mediaRelElement [MediaInfo]
mInfos
                   Maybe [MediaInfo]
Nothing -> []

  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$
    FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Relationships"
    [(FilePath
"xmlns", FilePath
"http://schemas.openxmlformats.org/package/2006/relationships")]
    ([FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Relationship" [ (FilePath
"Id", FilePath
"rId1")
                           , (FilePath
"Type", FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/relationships/slideLayout")
                           , (FilePath
"Target", FilePath
target)] ()
    ] [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
speakerNotesRels [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
linkRels [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> [Element]
mediaRels)

slideToSldIdElement :: PandocMonad m => Slide -> P m Element
slideToSldIdElement :: Slide -> P m Element
slideToSldIdElement Slide
slide = do
  Int
n <- Slide -> P m Int
forall (m :: * -> *). PandocMonad m => Slide -> P m Int
slideNum Slide
slide
  let id' :: FilePath
id' = Int -> FilePath
forall a. Show a => a -> FilePath
show (Int -> FilePath) -> Int -> FilePath
forall a b. (a -> b) -> a -> b
$ Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
255
  MimeType
rId <- Slide -> P m MimeType
forall (m :: * -> *). PandocMonad m => Slide -> P m MimeType
slideToRelId Slide
slide
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sldId" [(FilePath
"id", FilePath
id'), (FilePath
"r:id", MimeType -> FilePath
T.unpack MimeType
rId)] ()

presentationToSldIdLst :: PandocMonad m => Presentation -> P m Element
presentationToSldIdLst :: Presentation -> P m Element
presentationToSldIdLst (Presentation DocProps
_ [Slide]
slides) = do
  [Element]
ids <- (Slide -> P m Element)
-> [Slide] -> ReaderT WriterEnv (StateT WriterState m) [Element]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Slide -> P m Element
forall (m :: * -> *). PandocMonad m => Slide -> P m Element
slideToSldIdElement [Slide]
slides
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:sldIdLst" [] [Element]
ids

presentationToPresentationElement :: PandocMonad m => Presentation -> P m Element
presentationToPresentationElement :: Presentation -> P m Element
presentationToPresentationElement pres :: Presentation
pres@(Presentation DocProps
_ [Slide]
slds) = do
  Archive
refArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envRefArchive
  Archive
distArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envDistArchive
  Element
element <- Archive -> Archive -> FilePath -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> FilePath -> m Element
parseXml Archive
refArchive Archive
distArchive FilePath
"ppt/presentation.xml"
  Element
sldIdLst <- Presentation -> P m Element
forall (m :: * -> *). PandocMonad m => Presentation -> P m Element
presentationToSldIdLst Presentation
pres

  let modifySldIdLst :: Content -> Content
      modifySldIdLst :: Content -> Content
modifySldIdLst (Elem Element
e) = case Element -> QName
elName Element
e of
        (QName FilePath
"sldIdLst" Maybe FilePath
_ Maybe FilePath
_) -> Element -> Content
Elem Element
sldIdLst
        QName
_                      -> Element -> Content
Elem Element
e
      modifySldIdLst Content
ct = Content
ct

      notesMasterRId :: Int
notesMasterRId = [Slide] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Slide]
slds Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2

      notesMasterElem :: Element
notesMasterElem =  FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"p:notesMasterIdLst" []
                         [ FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode
                           FilePath
"p:NotesMasterId"
                           [(FilePath
"r:id", FilePath
"rId" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
notesMasterRId)]
                           ()
                         ]

      -- if there's a notesMasterIdLst in the presentation.xml file,
      -- we want to remove it. We then want to put our own, if
      -- necessary, after the slideMasterIdLst element. We also remove
      -- handouts master, since we don't want it.

      removeUnwantedMaster' :: Content -> [Content]
      removeUnwantedMaster' :: Content -> [Content]
removeUnwantedMaster' (Elem Element
e) = case Element -> QName
elName Element
e of
        (QName FilePath
"notesMasterIdLst" Maybe FilePath
_ Maybe FilePath
_) -> []
        (QName FilePath
"handoutMasterIdLst" Maybe FilePath
_ Maybe FilePath
_) -> []
        QName
_                              -> [Element -> Content
Elem Element
e]
      removeUnwantedMaster' Content
ct = [Content
ct]

      removeUnwantedMaster :: [Content] -> [Content]
      removeUnwantedMaster :: [Content] -> [Content]
removeUnwantedMaster = (Content -> [Content]) -> [Content] -> [Content]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Content -> [Content]
removeUnwantedMaster'

      insertNotesMaster' :: Content -> [Content]
      insertNotesMaster' :: Content -> [Content]
insertNotesMaster' (Elem Element
e) = case Element -> QName
elName Element
e of
        (QName FilePath
"sldMasterIdLst" Maybe FilePath
_ Maybe FilePath
_) -> [Element -> Content
Elem Element
e, Element -> Content
Elem Element
notesMasterElem]
        QName
_                            -> [Element -> Content
Elem Element
e]
      insertNotesMaster' Content
ct = [Content
ct]

      insertNotesMaster :: [Content] -> [Content]
      insertNotesMaster :: [Content] -> [Content]
insertNotesMaster = if Presentation -> Bool
presHasSpeakerNotes Presentation
pres
                          then (Content -> [Content]) -> [Content] -> [Content]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Content -> [Content]
insertNotesMaster'
                          else [Content] -> [Content]
forall a. a -> a
id

      newContent :: [Content]
newContent = [Content] -> [Content]
insertNotesMaster ([Content] -> [Content]) -> [Content] -> [Content]
forall a b. (a -> b) -> a -> b
$
                   [Content] -> [Content]
removeUnwantedMaster ([Content] -> [Content]) -> [Content] -> [Content]
forall a b. (a -> b) -> a -> b
$
                   (Content -> Content) -> [Content] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map Content -> Content
modifySldIdLst ([Content] -> [Content]) -> [Content] -> [Content]
forall a b. (a -> b) -> a -> b
$
                   Element -> [Content]
elContent Element
element

  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ Element
element{elContent :: [Content]
elContent = [Content]
newContent}

presentationToPresEntry :: PandocMonad m => Presentation -> P m Entry
presentationToPresEntry :: Presentation -> P m Entry
presentationToPresEntry Presentation
pres = Presentation -> P m Element
forall (m :: * -> *). PandocMonad m => Presentation -> P m Element
presentationToPresentationElement Presentation
pres P m Element -> (Element -> P m Entry) -> P m Entry
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
  FilePath -> Element -> P m Entry
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Element -> P m Entry
elemToEntry FilePath
"ppt/presentation.xml"

-- adapted from the Docx writer
docPropsElement :: PandocMonad m => DocProps -> P m Element
docPropsElement :: DocProps -> P m Element
docPropsElement DocProps
docProps = do
  UTCTime
utctime <- (WriterEnv -> UTCTime)
-> ReaderT WriterEnv (StateT WriterState m) UTCTime
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> UTCTime
envUTCTime
  let keywords :: MimeType
keywords = case DocProps -> Maybe [MimeType]
dcKeywords DocProps
docProps of
        Just [MimeType]
xs -> MimeType -> [MimeType] -> MimeType
T.intercalate MimeType
", " [MimeType]
xs
        Maybe [MimeType]
Nothing -> MimeType
""
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$
    FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"cp:coreProperties"
    [(FilePath
"xmlns:cp",FilePath
"http://schemas.openxmlformats.org/package/2006/metadata/core-properties")
    ,(FilePath
"xmlns:dc",FilePath
"http://purl.org/dc/elements/1.1/")
    ,(FilePath
"xmlns:dcterms",FilePath
"http://purl.org/dc/terms/")
    ,(FilePath
"xmlns:dcmitype",FilePath
"http://purl.org/dc/dcmitype/")
    ,(FilePath
"xmlns:xsi",FilePath
"http://www.w3.org/2001/XMLSchema-instance")]
    ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$
      FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"dc:title" [] (FilePath -> (MimeType -> FilePath) -> Maybe MimeType -> FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FilePath
"" MimeType -> FilePath
T.unpack (Maybe MimeType -> FilePath) -> Maybe MimeType -> FilePath
forall a b. (a -> b) -> a -> b
$ DocProps -> Maybe MimeType
dcTitle DocProps
docProps)
    Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
:
      FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"dc:creator" [] (FilePath -> (MimeType -> FilePath) -> Maybe MimeType -> FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FilePath
"" MimeType -> FilePath
T.unpack (Maybe MimeType -> FilePath) -> Maybe MimeType -> FilePath
forall a b. (a -> b) -> a -> b
$ DocProps -> Maybe MimeType
dcCreator DocProps
docProps)
    Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
:
      FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"cp:keywords" [] (MimeType -> FilePath
T.unpack MimeType
keywords)
    Element -> [Element] -> [Element]
forall a. a -> [a] -> [a]
: ( [FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"dc:subject" [] (FilePath -> Element) -> FilePath -> Element
forall a b. (a -> b) -> a -> b
$ FilePath -> (MimeType -> FilePath) -> Maybe MimeType -> FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FilePath
"" MimeType -> FilePath
T.unpack (Maybe MimeType -> FilePath) -> Maybe MimeType -> FilePath
forall a b. (a -> b) -> a -> b
$ DocProps -> Maybe MimeType
dcSubject DocProps
docProps | Maybe MimeType -> Bool
forall a. Maybe a -> Bool
isJust (DocProps -> Maybe MimeType
dcSubject DocProps
docProps)])
    [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> ( [FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"dc:description" [] (FilePath -> Element) -> FilePath -> Element
forall a b. (a -> b) -> a -> b
$ FilePath -> (MimeType -> FilePath) -> Maybe MimeType -> FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FilePath
"" MimeType -> FilePath
T.unpack (Maybe MimeType -> FilePath) -> Maybe MimeType -> FilePath
forall a b. (a -> b) -> a -> b
$ DocProps -> Maybe MimeType
dcDescription DocProps
docProps | Maybe MimeType -> Bool
forall a. Maybe a -> Bool
isJust (DocProps -> Maybe MimeType
dcDescription DocProps
docProps)])
    [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> ( [FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"cp:category" [] (FilePath -> Element) -> FilePath -> Element
forall a b. (a -> b) -> a -> b
$ FilePath -> (MimeType -> FilePath) -> Maybe MimeType -> FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FilePath
"" MimeType -> FilePath
T.unpack (Maybe MimeType -> FilePath) -> Maybe MimeType -> FilePath
forall a b. (a -> b) -> a -> b
$ DocProps -> Maybe MimeType
cpCategory DocProps
docProps | Maybe MimeType -> Bool
forall a. Maybe a -> Bool
isJust (DocProps -> Maybe MimeType
cpCategory DocProps
docProps)])
    [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<> (\FilePath
x -> [ FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"dcterms:created" [(FilePath
"xsi:type",FilePath
"dcterms:W3CDTF")] FilePath
x
             , FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"dcterms:modified" [(FilePath
"xsi:type",FilePath
"dcterms:W3CDTF")] FilePath
x
             ]) (TimeLocale -> FilePath -> UTCTime -> FilePath
forall t. FormatTime t => TimeLocale -> FilePath -> t -> FilePath
formatTime TimeLocale
defaultTimeLocale FilePath
"%FT%XZ" UTCTime
utctime)

docPropsToEntry :: PandocMonad m => DocProps -> P m Entry
docPropsToEntry :: DocProps -> P m Entry
docPropsToEntry DocProps
docProps = DocProps -> P m Element
forall (m :: * -> *). PandocMonad m => DocProps -> P m Element
docPropsElement DocProps
docProps P m Element -> (Element -> P m Entry) -> P m Entry
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           FilePath -> Element -> P m Entry
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Element -> P m Entry
elemToEntry FilePath
"docProps/core.xml"

-- adapted from the Docx writer
docCustomPropsElement :: PandocMonad m => DocProps -> P m Element
docCustomPropsElement :: DocProps -> P m Element
docCustomPropsElement DocProps
docProps = do
  let mkCustomProp :: (MimeType, MimeType) -> a -> Element
mkCustomProp (MimeType
k, MimeType
v) a
pid = FilePath -> NameSpaces -> Element -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"property"
         [(FilePath
"fmtid",FilePath
"{D5CDD505-2E9C-101B-9397-08002B2CF9AE}")
         ,(FilePath
"pid", a -> FilePath
forall a. Show a => a -> FilePath
show a
pid)
         ,(FilePath
"name", MimeType -> FilePath
T.unpack MimeType
k)] (Element -> Element) -> Element -> Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> FilePath -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"vt:lpwstr" [] (MimeType -> FilePath
T.unpack MimeType
v)
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$ FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Properties"
          [(FilePath
"xmlns",FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/custom-properties")
          ,(FilePath
"xmlns:vt",FilePath
"http://schemas.openxmlformats.org/officeDocument/2006/docPropsVTypes")
          ] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$ ((MimeType, MimeType) -> Int -> Element)
-> [(MimeType, MimeType)] -> [Int] -> [Element]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (MimeType, MimeType) -> Int -> Element
forall a. Show a => (MimeType, MimeType) -> a -> Element
mkCustomProp ([(MimeType, MimeType)]
-> Maybe [(MimeType, MimeType)] -> [(MimeType, MimeType)]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [(MimeType, MimeType)] -> [(MimeType, MimeType)])
-> Maybe [(MimeType, MimeType)] -> [(MimeType, MimeType)]
forall a b. (a -> b) -> a -> b
$ DocProps -> Maybe [(MimeType, MimeType)]
customProperties DocProps
docProps) [(Int
2 :: Int)..]

docCustomPropsToEntry :: PandocMonad m => DocProps -> P m Entry
docCustomPropsToEntry :: DocProps -> P m Entry
docCustomPropsToEntry DocProps
docProps = DocProps -> P m Element
forall (m :: * -> *). PandocMonad m => DocProps -> P m Element
docCustomPropsElement DocProps
docProps P m Element -> (Element -> P m Entry) -> P m Entry
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                           FilePath -> Element -> P m Entry
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Element -> P m Entry
elemToEntry FilePath
"docProps/custom.xml"

-- We read from the template, but we remove the lastView, so it always
-- opens on slide view. Templates will sometimes be open in master
-- view for editing.
viewPropsElement :: PandocMonad m => P m Element
viewPropsElement :: P m Element
viewPropsElement = do
  Archive
refArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envRefArchive
  Archive
distArchive <- (WriterEnv -> Archive)
-> ReaderT WriterEnv (StateT WriterState m) Archive
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Archive
envDistArchive
  Element
viewPrElement <- Archive -> Archive -> FilePath -> P m Element
forall (m :: * -> *).
PandocMonad m =>
Archive -> Archive -> FilePath -> m Element
parseXml Archive
refArchive Archive
distArchive FilePath
"ppt/viewProps.xml"
  -- remove  "lastView" if it exists:
  let notLastView :: Text.XML.Light.Attr -> Bool
      notLastView :: Attr -> Bool
notLastView Attr
attr =
          QName -> FilePath
qName (Attr -> QName
attrKey Attr
attr) FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= FilePath
"lastView"
  Element -> P m Element
forall (m :: * -> *) a. Monad m => a -> m a
return (Element -> P m Element) -> Element -> P m Element
forall a b. (a -> b) -> a -> b
$
    Element
viewPrElement {elAttribs :: [Attr]
elAttribs = (Attr -> Bool) -> [Attr] -> [Attr]
forall a. (a -> Bool) -> [a] -> [a]
filter Attr -> Bool
notLastView (Element -> [Attr]
elAttribs Element
viewPrElement)}

makeViewPropsEntry :: PandocMonad m => P m Entry
makeViewPropsEntry :: P m Entry
makeViewPropsEntry = P m Element
forall (m :: * -> *). PandocMonad m => P m Element
viewPropsElement P m Element -> (Element -> P m Entry) -> P m Entry
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FilePath -> Element -> P m Entry
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Element -> P m Entry
elemToEntry FilePath
"ppt/viewProps.xml"

defaultContentTypeToElem :: DefaultContentType -> Element
defaultContentTypeToElem :: DefaultContentType -> Element
defaultContentTypeToElem DefaultContentType
dct =
  FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Default"
  [(FilePath
"Extension", MimeType -> FilePath
T.unpack (MimeType -> FilePath) -> MimeType -> FilePath
forall a b. (a -> b) -> a -> b
$ DefaultContentType -> MimeType
defContentTypesExt DefaultContentType
dct),
    (FilePath
"ContentType", MimeType -> FilePath
T.unpack (MimeType -> FilePath) -> MimeType -> FilePath
forall a b. (a -> b) -> a -> b
$ DefaultContentType -> MimeType
defContentTypesType DefaultContentType
dct)]
  ()

overrideContentTypeToElem :: OverrideContentType -> Element
overrideContentTypeToElem :: OverrideContentType -> Element
overrideContentTypeToElem OverrideContentType
oct =
  FilePath -> NameSpaces -> () -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Override"
  [(FilePath
"PartName", OverrideContentType -> FilePath
overrideContentTypesPart OverrideContentType
oct),
    (FilePath
"ContentType", MimeType -> FilePath
T.unpack (MimeType -> FilePath) -> MimeType -> FilePath
forall a b. (a -> b) -> a -> b
$ OverrideContentType -> MimeType
overrideContentTypesType OverrideContentType
oct)]
  ()

contentTypesToElement :: ContentTypes -> Element
contentTypesToElement :: ContentTypes -> Element
contentTypesToElement ContentTypes
ct =
  let ns :: FilePath
ns = FilePath
"http://schemas.openxmlformats.org/package/2006/content-types"
  in
    FilePath -> NameSpaces -> [Element] -> Element
forall t. Node t => FilePath -> NameSpaces -> t -> Element
mknode FilePath
"Types" [(FilePath
"xmlns", FilePath
ns)] ([Element] -> Element) -> [Element] -> Element
forall a b. (a -> b) -> a -> b
$

      (DefaultContentType -> Element)
-> [DefaultContentType] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map DefaultContentType -> Element
defaultContentTypeToElem (ContentTypes -> [DefaultContentType]
contentTypesDefaults ContentTypes
ct) [Element] -> [Element] -> [Element]
forall a. Semigroup a => a -> a -> a
<>
      (OverrideContentType -> Element)
-> [OverrideContentType] -> [Element]
forall a b. (a -> b) -> [a] -> [b]
map OverrideContentType -> Element
overrideContentTypeToElem (ContentTypes -> [OverrideContentType]
contentTypesOverrides ContentTypes
ct)

data DefaultContentType = DefaultContentType
                           { DefaultContentType -> MimeType
defContentTypesExt :: T.Text
                           , DefaultContentType -> MimeType
defContentTypesType:: MimeType
                           }
                         deriving (Int -> DefaultContentType -> ShowS
[DefaultContentType] -> ShowS
DefaultContentType -> FilePath
(Int -> DefaultContentType -> ShowS)
-> (DefaultContentType -> FilePath)
-> ([DefaultContentType] -> ShowS)
-> Show DefaultContentType
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [DefaultContentType] -> ShowS
$cshowList :: [DefaultContentType] -> ShowS
show :: DefaultContentType -> FilePath
$cshow :: DefaultContentType -> FilePath
showsPrec :: Int -> DefaultContentType -> ShowS
$cshowsPrec :: Int -> DefaultContentType -> ShowS
Show, DefaultContentType -> DefaultContentType -> Bool
(DefaultContentType -> DefaultContentType -> Bool)
-> (DefaultContentType -> DefaultContentType -> Bool)
-> Eq DefaultContentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefaultContentType -> DefaultContentType -> Bool
$c/= :: DefaultContentType -> DefaultContentType -> Bool
== :: DefaultContentType -> DefaultContentType -> Bool
$c== :: DefaultContentType -> DefaultContentType -> Bool
Eq)

data OverrideContentType = OverrideContentType
                           { OverrideContentType -> FilePath
overrideContentTypesPart :: FilePath
                           , OverrideContentType -> MimeType
overrideContentTypesType :: MimeType
                           }
                          deriving (Int -> OverrideContentType -> ShowS
[OverrideContentType] -> ShowS
OverrideContentType -> FilePath
(Int -> OverrideContentType -> ShowS)
-> (OverrideContentType -> FilePath)
-> ([OverrideContentType] -> ShowS)
-> Show OverrideContentType
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [OverrideContentType] -> ShowS
$cshowList :: [OverrideContentType] -> ShowS
show :: OverrideContentType -> FilePath
$cshow :: OverrideContentType -> FilePath
showsPrec :: Int -> OverrideContentType -> ShowS
$cshowsPrec :: Int -> OverrideContentType -> ShowS
Show, OverrideContentType -> OverrideContentType -> Bool
(OverrideContentType -> OverrideContentType -> Bool)
-> (OverrideContentType -> OverrideContentType -> Bool)
-> Eq OverrideContentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OverrideContentType -> OverrideContentType -> Bool
$c/= :: OverrideContentType -> OverrideContentType -> Bool
== :: OverrideContentType -> OverrideContentType -> Bool
$c== :: OverrideContentType -> OverrideContentType -> Bool
Eq)

data ContentTypes = ContentTypes { ContentTypes -> [DefaultContentType]
contentTypesDefaults :: [DefaultContentType]
                                 , ContentTypes -> [OverrideContentType]
contentTypesOverrides :: [OverrideContentType]
                                 }
                    deriving (Int -> ContentTypes -> ShowS
[ContentTypes] -> ShowS
ContentTypes -> FilePath
(Int -> ContentTypes -> ShowS)
-> (ContentTypes -> FilePath)
-> ([ContentTypes] -> ShowS)
-> Show ContentTypes
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ContentTypes] -> ShowS
$cshowList :: [ContentTypes] -> ShowS
show :: ContentTypes -> FilePath
$cshow :: ContentTypes -> FilePath
showsPrec :: Int -> ContentTypes -> ShowS
$cshowsPrec :: Int -> ContentTypes -> ShowS
Show, ContentTypes -> ContentTypes -> Bool
(ContentTypes -> ContentTypes -> Bool)
-> (ContentTypes -> ContentTypes -> Bool) -> Eq ContentTypes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContentTypes -> ContentTypes -> Bool
$c/= :: ContentTypes -> ContentTypes -> Bool
== :: ContentTypes -> ContentTypes -> Bool
$c== :: ContentTypes -> ContentTypes -> Bool
Eq)

contentTypesToEntry :: PandocMonad m => ContentTypes -> P m Entry
contentTypesToEntry :: ContentTypes -> P m Entry
contentTypesToEntry ContentTypes
ct = FilePath -> Element -> P m Entry
forall (m :: * -> *).
PandocMonad m =>
FilePath -> Element -> P m Entry
elemToEntry FilePath
"[Content_Types].xml" (Element -> P m Entry) -> Element -> P m Entry
forall a b. (a -> b) -> a -> b
$ ContentTypes -> Element
contentTypesToElement ContentTypes
ct

pathToOverride :: FilePath -> Maybe OverrideContentType
pathToOverride :: FilePath -> Maybe OverrideContentType
pathToOverride FilePath
fp = FilePath -> MimeType -> OverrideContentType
OverrideContentType (FilePath
"/" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
fp) (MimeType -> OverrideContentType)
-> Maybe MimeType -> Maybe OverrideContentType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> Maybe MimeType
getContentType FilePath
fp

mediaFileContentType :: FilePath -> Maybe DefaultContentType
mediaFileContentType :: FilePath -> Maybe DefaultContentType
mediaFileContentType FilePath
fp = case ShowS
takeExtension FilePath
fp of
  Char
'.' : FilePath
ext -> DefaultContentType -> Maybe DefaultContentType
forall a. a -> Maybe a
Just (DefaultContentType -> Maybe DefaultContentType)
-> DefaultContentType -> Maybe DefaultContentType
forall a b. (a -> b) -> a -> b
$
               DefaultContentType :: MimeType -> MimeType -> DefaultContentType
DefaultContentType { defContentTypesExt :: MimeType
defContentTypesExt = FilePath -> MimeType
T.pack FilePath
ext
                                  , defContentTypesType :: MimeType
defContentTypesType =
                                      MimeType -> Maybe MimeType -> MimeType
forall a. a -> Maybe a -> a
fromMaybe MimeType
"application/octet-stream" (FilePath -> Maybe MimeType
getMimeType FilePath
fp)
                                  }
  FilePath
_ -> Maybe DefaultContentType
forall a. Maybe a
Nothing

mediaContentType :: MediaInfo -> Maybe DefaultContentType
mediaContentType :: MediaInfo -> Maybe DefaultContentType
mediaContentType MediaInfo
mInfo
  | Just MimeType
t <- MediaInfo -> Maybe MimeType
mInfoExt MediaInfo
mInfo
  , Just (Char
'.', MimeType
ext) <- MimeType -> Maybe (Char, MimeType)
T.uncons MimeType
t =
      DefaultContentType -> Maybe DefaultContentType
forall a. a -> Maybe a
Just (DefaultContentType -> Maybe DefaultContentType)
-> DefaultContentType -> Maybe DefaultContentType
forall a b. (a -> b) -> a -> b
$ DefaultContentType :: MimeType -> MimeType -> DefaultContentType
DefaultContentType { defContentTypesExt :: MimeType
defContentTypesExt = MimeType
ext
                                , defContentTypesType :: MimeType
defContentTypesType =
                                    MimeType -> Maybe MimeType -> MimeType
forall a. a -> Maybe a -> a
fromMaybe MimeType
"application/octet-stream" (MediaInfo -> Maybe MimeType
mInfoMimeType MediaInfo
mInfo)
                                }
  | Bool
otherwise = Maybe DefaultContentType
forall a. Maybe a
Nothing

getSpeakerNotesFilePaths :: PandocMonad m => P m [FilePath]
getSpeakerNotesFilePaths :: P m [FilePath]
getSpeakerNotesFilePaths = do
  Map Int Int
mp <- (WriterEnv -> Map Int Int)
-> ReaderT WriterEnv (StateT WriterState m) (Map Int Int)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterEnv -> Map Int Int
envSpeakerNotesIdMap
  let notesIdNums :: [Int]
notesIdNums = Map Int Int -> [Int]
forall k a. Map k a -> [a]
M.elems Map Int Int
mp
  [FilePath] -> P m [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> P m [FilePath]) -> [FilePath] -> P m [FilePath]
forall a b. (a -> b) -> a -> b
$ (Int -> FilePath) -> [Int] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\Int
n -> FilePath
"ppt/notesSlides/notesSlide" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
n FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
".xml") [Int]
notesIdNums

presentationToContentTypes :: PandocMonad m => Presentation -> P m ContentTypes
presentationToContentTypes :: Presentation -> P m ContentTypes
presentationToContentTypes p :: Presentation
p@(Presentation DocProps
_ [Slide]
slides) = do
  [MediaInfo]
mediaInfos <- [[MediaInfo]] -> [MediaInfo]
forall a. Monoid a => [a] -> a
mconcat ([[MediaInfo]] -> [MediaInfo])
-> (Map Int [MediaInfo] -> [[MediaInfo]])
-> Map Int [MediaInfo]
-> [MediaInfo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Int [MediaInfo] -> [[MediaInfo]]
forall k a. Map k a -> [a]
M.elems (Map Int [MediaInfo] -> [MediaInfo])
-> ReaderT WriterEnv (StateT WriterState m) (Map Int [MediaInfo])
-> ReaderT WriterEnv (StateT WriterState m) [MediaInfo]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (WriterState -> Map Int [MediaInfo])
-> ReaderT WriterEnv (StateT WriterState m) (Map Int [MediaInfo])
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Map Int [MediaInfo]
stMediaIds
  [FilePath]
filePaths <- [Pattern] -> P m [FilePath]
forall (m :: * -> *). PandocMonad m => [Pattern] -> P m [FilePath]
patternsToFilePaths ([Pattern] -> P m [FilePath]) -> [Pattern] -> P m [FilePath]
forall a b. (a -> b) -> a -> b
$ Presentation -> [Pattern]
inheritedPatterns Presentation
p
  let mediaFps :: [FilePath]
mediaFps = (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (Pattern -> FilePath -> Bool
match (FilePath -> Pattern
compile FilePath
"ppt/media/image*")) [FilePath]
filePaths
  let defaults :: [DefaultContentType]
defaults = [ MimeType -> MimeType -> DefaultContentType
DefaultContentType MimeType
"xml" MimeType
"application/xml"
                 , MimeType -> MimeType -> DefaultContentType
DefaultContentType MimeType
"rels" MimeType
"application/vnd.openxmlformats-package.relationships+xml"
                 ]
      mediaDefaults :: [DefaultContentType]
mediaDefaults = [DefaultContentType] -> [DefaultContentType]
forall a. Eq a => [a] -> [a]
nub ([DefaultContentType] -> [DefaultContentType])
-> [DefaultContentType] -> [DefaultContentType]
forall a b. (a -> b) -> a -> b
$
                      (MediaInfo -> Maybe DefaultContentType)
-> [MediaInfo] -> [DefaultContentType]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe MediaInfo -> Maybe DefaultContentType
mediaContentType [MediaInfo]
mediaInfos [DefaultContentType]
-> [DefaultContentType] -> [DefaultContentType]
forall a. Semigroup a => a -> a -> a
<>
                      (FilePath -> Maybe DefaultContentType)
-> [FilePath] -> [DefaultContentType]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe FilePath -> Maybe DefaultContentType
mediaFileContentType [FilePath]
mediaFps

      inheritedOverrides :: [OverrideContentType]
inheritedOverrides = (FilePath -> Maybe OverrideContentType)
-> [FilePath] -> [OverrideContentType]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe FilePath -> Maybe OverrideContentType
pathToOverride [FilePath]
filePaths
      createdOverrides :: [OverrideContentType]
createdOverrides = (FilePath -> Maybe OverrideContentType)
-> [FilePath] -> [OverrideContentType]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe FilePath -> Maybe OverrideContentType
pathToOverride [ FilePath
"docProps/core.xml"
                                                 , FilePath
"docProps/custom.xml"
                                                 , FilePath
"ppt/presentation.xml"
                                                 , FilePath
"ppt/viewProps.xml"
                                                 ]
  [FilePath]
relativePaths <- (Slide -> ReaderT WriterEnv (StateT WriterState m) FilePath)
-> [Slide] -> P m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Slide -> ReaderT WriterEnv (StateT WriterState m) FilePath
forall (m :: * -> *). PandocMonad m => Slide -> P m FilePath
slideToFilePath [Slide]
slides
  let slideOverrides :: [OverrideContentType]
slideOverrides = (FilePath -> Maybe OverrideContentType)
-> [FilePath] -> [OverrideContentType]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe
                       (\FilePath
fp -> FilePath -> Maybe OverrideContentType
pathToOverride (FilePath -> Maybe OverrideContentType)
-> FilePath -> Maybe OverrideContentType
forall a b. (a -> b) -> a -> b
$ FilePath
"ppt/slides/" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
fp)
                       [FilePath]
relativePaths
  [OverrideContentType]
speakerNotesOverrides <- (FilePath -> Maybe OverrideContentType)
-> [FilePath] -> [OverrideContentType]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe FilePath -> Maybe OverrideContentType
pathToOverride ([FilePath] -> [OverrideContentType])
-> P m [FilePath]
-> ReaderT WriterEnv (StateT WriterState m) [OverrideContentType]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> P m [FilePath]
forall (m :: * -> *). PandocMonad m => P m [FilePath]
getSpeakerNotesFilePaths
  ContentTypes -> P m ContentTypes
forall (m :: * -> *) a. Monad m => a -> m a
return (ContentTypes -> P m ContentTypes)
-> ContentTypes -> P m ContentTypes
forall a b. (a -> b) -> a -> b
$ [DefaultContentType] -> [OverrideContentType] -> ContentTypes
ContentTypes
    ([DefaultContentType]
defaults [DefaultContentType]
-> [DefaultContentType] -> [DefaultContentType]
forall a. Semigroup a => a -> a -> a
<> [DefaultContentType]
mediaDefaults)
    ([OverrideContentType]
inheritedOverrides [OverrideContentType]
-> [OverrideContentType] -> [OverrideContentType]
forall a. Semigroup a => a -> a -> a
<> [OverrideContentType]
createdOverrides [OverrideContentType]
-> [OverrideContentType] -> [OverrideContentType]
forall a. Semigroup a => a -> a -> a
<> [OverrideContentType]
slideOverrides [OverrideContentType]
-> [OverrideContentType] -> [OverrideContentType]
forall a. Semigroup a => a -> a -> a
<> [OverrideContentType]
speakerNotesOverrides)

presML :: T.Text
presML :: MimeType
presML = MimeType
"application/vnd.openxmlformats-officedocument.presentationml"

noPresML :: T.Text
noPresML :: MimeType
noPresML = MimeType
"application/vnd.openxmlformats-officedocument"

getContentType :: FilePath -> Maybe MimeType
getContentType :: FilePath -> Maybe MimeType
getContentType FilePath
fp
  | FilePath
fp FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"ppt/presentation.xml" = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
presML MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
".presentation.main+xml"
  | FilePath
fp FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"ppt/presProps.xml" = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
presML MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
".presProps+xml"
  | FilePath
fp FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"ppt/viewProps.xml" = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
presML MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
".viewProps+xml"
  | FilePath
fp FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"ppt/tableStyles.xml" = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
presML MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
".tableStyles+xml"
  | FilePath
fp FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"docProps/core.xml" = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just MimeType
"application/vnd.openxmlformats-package.core-properties+xml"
  | FilePath
fp FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"docProps/custom.xml" = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just MimeType
"application/vnd.openxmlformats-officedocument.custom-properties+xml"
  | FilePath
fp FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"docProps/app.xml" = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
noPresML MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
".extended-properties+xml"
  | [FilePath
"ppt", FilePath
"slideMasters", FilePath
f] <- FilePath -> [FilePath]
splitDirectories FilePath
fp
  , (FilePath
_, FilePath
".xml") <- FilePath -> (FilePath, FilePath)
splitExtension FilePath
f =
      MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
presML MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
".slideMaster+xml"
  | [FilePath
"ppt", FilePath
"slides", FilePath
f] <- FilePath -> [FilePath]
splitDirectories FilePath
fp
  , (FilePath
_, FilePath
".xml") <- FilePath -> (FilePath, FilePath)
splitExtension FilePath
f =
      MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
presML MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
".slide+xml"
  | [FilePath
"ppt", FilePath
"notesMasters", FilePath
f] <- FilePath -> [FilePath]
splitDirectories FilePath
fp
  , (FilePath
_, FilePath
".xml") <- FilePath -> (FilePath, FilePath)
splitExtension FilePath
f =
      MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
presML MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
".notesMaster+xml"
  | [FilePath
"ppt", FilePath
"notesSlides", FilePath
f] <- FilePath -> [FilePath]
splitDirectories FilePath
fp
  , (FilePath
_, FilePath
".xml") <- FilePath -> (FilePath, FilePath)
splitExtension FilePath
f =
      MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
presML MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
".notesSlide+xml"
  | [FilePath
"ppt", FilePath
"theme", FilePath
f] <- FilePath -> [FilePath]
splitDirectories FilePath
fp
  , (FilePath
_, FilePath
".xml") <- FilePath -> (FilePath, FilePath)
splitExtension FilePath
f =
      MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
noPresML MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
".theme+xml"
  | [FilePath
"ppt", FilePath
"slideLayouts", FilePath
_] <- FilePath -> [FilePath]
splitDirectories FilePath
fp=
      MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (MimeType -> Maybe MimeType) -> MimeType -> Maybe MimeType
forall a b. (a -> b) -> a -> b
$ MimeType
presML MimeType -> MimeType -> MimeType
forall a. Semigroup a => a -> a -> a
<> MimeType
".slideLayout+xml"
  | Bool
otherwise = Maybe MimeType
forall a. Maybe a
Nothing

-- Kept as String for XML.Light
autoNumAttrs :: ListAttributes -> [(String, String)]
autoNumAttrs :: ListAttributes -> NameSpaces
autoNumAttrs (Int
startNum, ListNumberStyle
numStyle, ListNumberDelim
numDelim) =
  NameSpaces
numAttr NameSpaces -> NameSpaces -> NameSpaces
forall a. Semigroup a => a -> a -> a
<> NameSpaces
typeAttr
  where
    numAttr :: NameSpaces
numAttr = [(FilePath
"startAt", Int -> FilePath
forall a. Show a => a -> FilePath
show Int
startNum) | Int
startNum Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1]
    typeAttr :: NameSpaces
typeAttr = [(FilePath
"type", FilePath
typeString FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
delimString)]
    typeString :: FilePath
typeString = case ListNumberStyle
numStyle of
      ListNumberStyle
Decimal -> FilePath
"arabic"
      ListNumberStyle
UpperAlpha -> FilePath
"alphaUc"
      ListNumberStyle
LowerAlpha -> FilePath
"alphaLc"
      ListNumberStyle
UpperRoman -> FilePath
"romanUc"
      ListNumberStyle
LowerRoman -> FilePath
"romanLc"
      ListNumberStyle
_          -> FilePath
"arabic"
    delimString :: FilePath
delimString = case ListNumberDelim
numDelim of
      ListNumberDelim
Period -> FilePath
"Period"
      ListNumberDelim
OneParen -> FilePath
"ParenR"
      ListNumberDelim
TwoParens -> FilePath
"ParenBoth"
      ListNumberDelim
_         -> FilePath
"Period"