aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/ODT.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/ODT.hs')
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs47
1 files changed, 24 insertions, 23 deletions
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index 3d8bfbca7..a5ea4b641 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -1,5 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Writers.ODT
Copyright : Copyright (C) 2008-2019 John MacFarlane
@@ -18,9 +19,9 @@ import Control.Monad.Except (catchError)
import Control.Monad.State.Strict
import qualified Data.ByteString.Lazy as B
import Data.Generics (everywhere', mkT)
-import Data.List (isPrefixOf, intercalate)
-import Data.Maybe (fromMaybe)
+import Data.List (isPrefixOf)
import qualified Data.Map as Map
+import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Data.Time
import System.FilePath (takeDirectory, takeExtension, (<.>))
@@ -33,7 +34,7 @@ import Text.Pandoc.Logging
import Text.Pandoc.MIME (extensionFromMimeType, getMimeType)
import Text.Pandoc.Options (WrapOption (..), WriterOptions (..))
import Text.DocLayout
-import Text.Pandoc.Shared (stringify, pandocVersion)
+import Text.Pandoc.Shared (stringify, pandocVersion, tshow)
import Text.Pandoc.Writers.Shared (lookupMetaString, lookupMetaBlocks,
fixDisplayMath)
import Text.Pandoc.UTF8 (fromStringLazy, fromTextLazy, toStringLazy)
@@ -89,7 +90,7 @@ pandocToODT opts doc@(Pandoc meta _) = do
Nothing -> empty
Just m -> selfClosingTag "manifest:file-entry"
[("manifest:media-type", m)
- ,("manifest:full-path", fp)
+ ,("manifest:full-path", T.pack fp)
,("manifest:version", "1.2")
]
let files = [ ent | ent <- filesInArchive archive,
@@ -114,7 +115,7 @@ pandocToODT opts doc@(Pandoc meta _) = do
let userDefinedMetaFields = [k | k <- Map.keys (unMeta meta)
, k `notElem` ["title", "lang", "author"
, "description", "subject", "keywords"]]
- let escapedText = text . escapeStringForXML
+ let escapedText = text . T.unpack . escapeStringForXML
let keywords = case lookupMeta "keywords" meta of
Just (MetaList xs) -> map stringify xs
_ -> []
@@ -136,17 +137,17 @@ pandocToODT opts doc@(Pandoc meta _) = do
,("xmlns:ooo","http://openoffice.org/2004/office")
,("xmlns:grddl","http://www.w3.org/2003/g/data-view#")
,("office:version","1.2")] ( inTags True "office:meta" [] $
- ( metaTag "meta:generator" ("Pandoc/" ++ pandocVersion)
+ ( metaTag "meta:generator" ("Pandoc/" <> pandocVersion)
$$
metaTag "dc:title" (stringify title)
$$
metaTag "dc:description"
- (intercalate "\n" (map stringify $
+ (T.intercalate "\n" (map stringify $
lookupMetaBlocks "description" meta))
$$
metaTag "dc:subject" (lookupMetaString "subject" meta)
$$
- metaTag "meta:keyword" (intercalate ", " keywords)
+ metaTag "meta:keyword" (T.intercalate ", " keywords)
$$
case lang of
Just l -> metaTag "dc:language" (renderLang l)
@@ -156,8 +157,8 @@ pandocToODT opts doc@(Pandoc meta _) = do
$$ metaTag "dc:creator" a
$$ metaTag "meta:creation-date" d
$$ metaTag "dc:date" d
- ) (formatTime defaultTimeLocale "%FT%XZ" utctime)
- (intercalate "; " (map stringify authors))
+ ) (T.pack $ formatTime defaultTimeLocale "%FT%XZ" utctime)
+ (T.intercalate "; " (map stringify authors))
$$
vcat userDefinedMeta
)
@@ -190,9 +191,9 @@ updateStyleWithLang (Just lang) arch = do
addLang :: Lang -> Element -> Element
addLang lang = everywhere' (mkT updateLangAttr)
where updateLangAttr (Attr n@(QName "language" _ (Just "fo")) _)
- = Attr n (langLanguage lang)
+ = Attr n (T.unpack $ langLanguage lang)
updateLangAttr (Attr n@(QName "country" _ (Just "fo")) _)
- = Attr n (langRegion lang)
+ = Attr n (T.unpack $ langRegion lang)
updateLangAttr x = x
-- | transform both Image and Math elements
@@ -206,12 +207,12 @@ transformPicMath opts (Image attr@(id', cls, _) lab (src,t)) = catchError
return (100, 100)
let dims =
case (getDim Width, getDim Height) of
- (Just w, Just h) -> [("width", show w), ("height", show h)]
- (Just w@(Percent _), Nothing) -> [("rel-width", show w),("rel-height", "scale"),("width", show ptX ++ "pt"),("height", show ptY ++ "pt")]
- (Nothing, Just h@(Percent _)) -> [("rel-width", "scale"),("rel-height", show h),("width", show ptX ++ "pt"),("height", show ptY ++ "pt")]
- (Just w@(Inch i), Nothing) -> [("width", show w), ("height", show (i / ratio) ++ "in")]
- (Nothing, Just h@(Inch i)) -> [("width", show (i * ratio) ++ "in"), ("height", show h)]
- _ -> [("width", show ptX ++ "pt"), ("height", show ptY ++ "pt")]
+ (Just w, Just h) -> [("width", tshow w), ("height", tshow h)]
+ (Just w@(Percent _), Nothing) -> [("rel-width", tshow w),("rel-height", "scale"),("width", tshow ptX <> "pt"),("height", tshow ptY <> "pt")]
+ (Nothing, Just h@(Percent _)) -> [("rel-width", "scale"),("rel-height", tshow h),("width", tshow ptX <> "pt"),("height", tshow ptY <> "pt")]
+ (Just w@(Inch i), Nothing) -> [("width", tshow w), ("height", tshow (i / ratio) <> "in")]
+ (Nothing, Just h@(Inch i)) -> [("width", tshow (i * ratio) <> "in"), ("height", tshow h)]
+ _ -> [("width", tshow ptX <> "pt"), ("height", tshow ptY <> "pt")]
where
ratio = ptX / ptY
getDim dir = case dimension dir attr of
@@ -220,16 +221,16 @@ transformPicMath opts (Image attr@(id', cls, _) lab (src,t)) = catchError
Nothing -> Nothing
let newattr = (id', cls, dims)
entries <- gets stEntries
- let extension = fromMaybe (takeExtension $ takeWhile (/='?') src)
+ let extension = maybe (takeExtension $ takeWhile (/='?') $ T.unpack src) T.unpack
(mbMimeType >>= extensionFromMimeType)
let newsrc = "Pictures/" ++ show (length entries) <.> extension
let toLazy = B.fromChunks . (:[])
epochtime <- floor `fmap` lift P.getPOSIXTime
let entry = toEntry newsrc epochtime $ toLazy img
modify $ \st -> st{ stEntries = entry : entries }
- return $ Image newattr lab (newsrc, t))
+ return $ Image newattr lab (T.pack newsrc, t))
(\e -> do
- report $ CouldNotFetchResource src (show e)
+ report $ CouldNotFetchResource src $ T.pack (show e)
return $ Emph lab)
transformPicMath _ (Math t math) = do
@@ -257,7 +258,7 @@ transformPicMath _ (Math t math) = do
,("text:anchor-type","paragraph")]
else [("draw:style-name","fr1")
,("text:anchor-type","as-char")]) $
- selfClosingTag "draw:object" [("xlink:href", dirname)
+ selfClosingTag "draw:object" [("xlink:href", T.pack dirname)
, ("xlink:type", "simple")
, ("xlink:show", "embed")
, ("xlink:actuate", "onLoad")]