aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs21
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs20
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs8
3 files changed, 24 insertions, 25 deletions
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 84bf95dfb..f8e3370e4 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -32,8 +32,7 @@ import Data.List ( intercalate )
import System.FilePath ( (</>) )
import qualified Data.ByteString.Lazy as B
import qualified Data.Map as M
-import Data.ByteString.Lazy.UTF8 ( fromString, toString )
-import Text.Pandoc.UTF8 as UTF8
+import qualified Text.Pandoc.UTF8 as UTF8
import System.IO ( stderr )
import Codec.Archive.Zip
import Data.Time.Clock.POSIX
@@ -126,7 +125,7 @@ writeDocx opts doc@(Pandoc (Meta tit auths date) _) = do
let newrels = map toImgRel imgs
let relpath = "word/_rels/document.xml.rels"
let reldoc = case findEntryByPath relpath refArchive >>=
- parseXMLDoc . toString . fromEntry of
+ parseXMLDoc . UTF8.toStringLazy . fromEntry of
Just d -> d
Nothing -> error $ relpath ++ "missing in reference docx"
let reldoc' = reldoc{ elContent = elContent reldoc ++ map Elem newrels }
@@ -138,21 +137,21 @@ writeDocx opts doc@(Pandoc (Meta tit auths date) _) = do
let toLinkRel (src,ident) = mknode "Relationship" [("Type","http://schemas.openxmlformats.org/officeDocument/2006/relationships/hyperlink"),("Id",ident),("Target",src),("TargetMode","External") ] ()
let newrels' = map toLinkRel $ M.toList $ stExternalLinks st
let reldoc'' = reldoc' { elContent = elContent reldoc' ++ map Elem newrels' }
- let relEntry = toEntry relpath epochtime $ fromString $ showTopElement' reldoc''
- let contentEntry = toEntry "word/document.xml" epochtime $ fromString $ showTopElement' newContents
+ let relEntry = toEntry relpath epochtime $ UTF8.fromStringLazy $ showTopElement' reldoc''
+ let contentEntry = toEntry "word/document.xml" epochtime $ UTF8.fromStringLazy $ showTopElement' newContents
-- styles
let newstyles = styleToOpenXml $ writerHighlightStyle opts
let stylepath = "word/styles.xml"
let styledoc = case findEntryByPath stylepath refArchive >>=
- parseXMLDoc . toString . fromEntry of
+ parseXMLDoc . UTF8.toStringLazy . fromEntry of
Just d -> d
Nothing -> error $ "Unable to parse " ++ stylepath ++
" from reference.docx"
let styledoc' = styledoc{ elContent = elContent styledoc ++ map Elem newstyles }
- let styleEntry = toEntry stylepath epochtime $ fromString $ showTopElement' styledoc'
+ let styleEntry = toEntry stylepath epochtime $ UTF8.fromStringLazy $ showTopElement' styledoc'
-- construct word/numbering.xml
let numpath = "word/numbering.xml"
- let numEntry = toEntry numpath epochtime $ fromString $ showTopElement'
+ let numEntry = toEntry numpath epochtime $ UTF8.fromStringLazy $ showTopElement'
$ mkNumbering (stNumStyles st) (stLists st)
let docPropsPath = "docProps/core.xml"
let docProps = mknode "cp:coreProperties"
@@ -166,16 +165,16 @@ writeDocx opts doc@(Pandoc (Meta tit auths date) _) = do
(maybe "" id $ normalizeDate $ stringify date)
: mknode "dcterms:modified" [("xsi:type","dcterms:W3CDTF")] () -- put current time here
: map (mknode "dc:creator" [] . stringify) auths
- let docPropsEntry = toEntry docPropsPath epochtime $ fromString $ showTopElement' docProps
+ let docPropsEntry = toEntry docPropsPath epochtime $ UTF8.fromStringLazy $ showTopElement' docProps
let relsPath = "_rels/.rels"
rels <- case findEntryByPath relsPath refArchive of
- Just e -> return $ toString $ fromEntry e
+ Just e -> return $ UTF8.toStringLazy $ fromEntry e
Nothing -> err 57 "could not find .rels/_rels in reference docx"
-- fix .rels/_rels, which can get screwed up when reference.docx is edited by Word
let rels' = substitute "http://schemas.openxmlformats.org/package/2006/relationships/metadata/core-properties"
"http://schemas.openxmlformats.org/officedocument/2006/relationships/metadata/core-properties"
rels
- let relsEntry = toEntry relsPath epochtime $ fromString rels'
+ let relsEntry = toEntry relsPath epochtime $ UTF8.fromStringLazy rels'
let archive = foldr addEntryToArchive refArchive $
relsEntry : contentEntry : relEntry : numEntry : styleEntry : docPropsEntry : imageEntries
return $ fromArchive archive
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 6f8931caa..3fac93c05 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -35,7 +35,7 @@ import System.Environment ( getEnv )
import Text.Printf (printf)
import System.FilePath ( (</>), (<.>), takeBaseName, takeExtension, takeFileName )
import qualified Data.ByteString.Lazy as B
-import Data.ByteString.Lazy.UTF8 ( fromString )
+import Text.Pandoc.UTF8 ( fromStringLazy )
import Codec.Archive.Zip
import Data.Time.Clock.POSIX
import Text.Pandoc.Shared hiding ( Element )
@@ -82,7 +82,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
Nothing -> return ([],[])
Just img -> do
let coverImage = "cover-image" ++ takeExtension img
- let cpContent = fromString $ writeHtmlString
+ let cpContent = fromStringLazy $ writeHtmlString
opts'{writerTemplate = coverImageTemplate,
writerVariables = ("coverimage",coverImage):vars}
(Pandoc meta [])
@@ -91,7 +91,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
, [mkEntry coverImage imgContent] )
-- title page
- let tpContent = fromString $ writeHtmlString
+ let tpContent = fromStringLazy $ writeHtmlString
opts'{writerTemplate = titlePageTemplate}
(Pandoc meta [])
let tpEntry = mkEntry "title_page.xhtml" tpContent
@@ -125,7 +125,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
let chapterToEntry :: Int -> Pandoc -> Entry
chapterToEntry num chap = mkEntry
(showChapter num) $
- fromString $ chapToHtml chap
+ fromStringLazy $ chapToHtml chap
let chapterEntries = zipWith chapterToEntry [1..] chapters
-- contents.opf
@@ -157,7 +157,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
let plainTitle = plainify $ docTitle meta
let plainAuthors = map plainify $ docAuthors meta
let plainDate = maybe "" id $ normalizeDate $ stringify $ docDate meta
- let contentsData = fromString $ ppTopElement $
+ let contentsData = fromStringLazy $ ppTopElement $
unode "package" ! [("version","2.0")
,("xmlns","http://www.idpf.org/2007/opf")
,("unique-identifier","BookId")] $
@@ -189,7 +189,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
, unode "content" ! [("src",
eRelativePath ent)] $ ()
]
- let tocData = fromString $ ppTopElement $
+ let tocData = fromStringLazy $ ppTopElement $
unode "ncx" ! [("version","2005-1")
,("xmlns","http://www.daisy.org/z3986/2005/ncx/")] $
[ unode "head" $
@@ -214,10 +214,10 @@ writeEPUB opts doc@(Pandoc meta _) = do
let tocEntry = mkEntry "toc.ncx" tocData
-- mimetype
- let mimetypeEntry = mkEntry "mimetype" $ fromString "application/epub+zip"
+ let mimetypeEntry = mkEntry "mimetype" $ fromStringLazy "application/epub+zip"
-- container.xml
- let containerData = fromString $ ppTopElement $
+ let containerData = fromStringLazy $ ppTopElement $
unode "container" ! [("version","1.0")
,("xmlns","urn:oasis:names:tc:opendocument:xmlns:container")] $
unode "rootfiles" $
@@ -226,7 +226,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
let containerEntry = mkEntry "META-INF/container.xml" containerData
-- com.apple.ibooks.display-options.xml
- let apple = fromString $ ppTopElement $
+ let apple = fromStringLazy $ ppTopElement $
unode "display_options" $
unode "platform" ! [("name","*")] $
unode "option" ! [("name","specified-fonts")] $ "true"
@@ -236,7 +236,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
stylesheet <- case writerEpubStylesheet opts of
Just s -> return s
Nothing -> readDataFile (writerUserDataDir opts) "epub.css"
- let stylesheetEntry = mkEntry "stylesheet.css" $ fromString stylesheet
+ let stylesheetEntry = mkEntry "stylesheet.css" $ fromStringLazy stylesheet
-- construct archive
let archive = foldr addEntryToArchive emptyArchive
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index f43d0a087..cbff88be5 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -32,7 +32,7 @@ import Data.IORef
import Data.List ( isPrefixOf )
import System.FilePath ( (</>), takeExtension )
import qualified Data.ByteString.Lazy as B
-import Data.ByteString.Lazy.UTF8 ( fromString )
+import Text.Pandoc.UTF8 ( fromStringLazy )
import Codec.Archive.Zip
import Data.Time.Clock.POSIX
import Paths_pandoc ( getDataFileName )
@@ -74,7 +74,7 @@ writeODT opts doc@(Pandoc (Meta title _ _) _) = do
doc' <- bottomUpM (transformPic sourceDir picEntriesRef) doc
let newContents = writeOpenDocument opts{writerWrapText = False} doc'
epochtime <- floor `fmap` getPOSIXTime
- let contentEntry = toEntry "content.xml" epochtime $ fromString newContents
+ let contentEntry = toEntry "content.xml" epochtime $ fromStringLazy newContents
picEntries <- readIORef picEntriesRef
let archive = foldr addEntryToArchive refArchive $ contentEntry : picEntries
-- construct META-INF/manifest.xml based on archive
@@ -86,7 +86,7 @@ writeODT opts doc@(Pandoc (Meta title _ _) _) = do
]
let files = [ ent | ent <- filesInArchive archive, not ("META-INF" `isPrefixOf` ent) ]
let manifestEntry = toEntry "META-INF/manifest.xml" epochtime
- $ fromString $ show
+ $ fromStringLazy $ show
$ text "<?xml version=\"1.0\" encoding=\"utf-8\"?>"
$$
( inTags True "manifest:manifest"
@@ -100,7 +100,7 @@ writeODT opts doc@(Pandoc (Meta title _ _) _) = do
)
let archive' = addEntryToArchive manifestEntry archive
let metaEntry = toEntry "meta.xml" epochtime
- $ fromString $ show
+ $ fromStringLazy $ show
$ text "<?xml version=\"1.0\" encoding=\"utf-8\"?>"
$$
( inTags True "office:document-meta"