aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/OOXML.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/OOXML.hs')
-rw-r--r--src/Text/Pandoc/Writers/OOXML.hs10
1 files changed, 8 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Writers/OOXML.hs b/src/Text/Pandoc/Writers/OOXML.hs
index 97ff86156..3f1d9701c 100644
--- a/src/Text/Pandoc/Writers/OOXML.hs
+++ b/src/Text/Pandoc/Writers/OOXML.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Writers.OOXML
Copyright : Copyright (C) 2012-2019 John MacFarlane
@@ -11,6 +12,7 @@
Functions common to OOXML writers (Docx and Powerpoint)
-}
module Text.Pandoc.Writers.OOXML ( mknode
+ , mktnode
, nodename
, toLazy
, renderXml
@@ -31,6 +33,7 @@ import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BL8
import Data.Maybe (mapMaybe)
+import qualified Data.Text as T
import Text.Pandoc.Class (PandocMonad)
import qualified Text.Pandoc.UTF8 as UTF8
import Text.XML.Light as XML
@@ -39,6 +42,9 @@ mknode :: Node t => String -> [(String,String)] -> t -> Element
mknode s attrs =
add_attrs (map (\(k,v) -> Attr (nodename k) v) attrs) . node (nodename s)
+mktnode :: String -> [(String,String)] -> T.Text -> Element
+mktnode s attrs = mknode s attrs . T.unpack
+
nodename :: String -> QName
nodename s = QName{ qName = name, qURI = Nothing, qPrefix = prefix }
where (name, prefix) = case break (==':') s of
@@ -57,10 +63,10 @@ parseXml refArchive distArchive relpath =
case findEntryByPath relpath refArchive `mplus`
findEntryByPath relpath distArchive of
Nothing -> throwError $ PandocSomeError $
- relpath ++ " missing in reference file"
+ T.pack relpath <> " missing in reference file"
Just e -> case parseXMLDoc . UTF8.toStringLazy . fromEntry $ e of
Nothing -> throwError $ PandocSomeError $
- relpath ++ " corrupt in reference file"
+ T.pack relpath <> " corrupt in reference file"
Just d -> return d
-- Copied from Util