aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/OPML.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/OPML.hs')
-rw-r--r--src/Text/Pandoc/Writers/OPML.hs19
1 files changed, 11 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Writers/OPML.hs b/src/Text/Pandoc/Writers/OPML.hs
index 98510c40f..4a0a317fa 100644
--- a/src/Text/Pandoc/Writers/OPML.hs
+++ b/src/Text/Pandoc/Writers/OPML.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE CPP #-}
{-
-Copyright (C) 2013-2015 John MacFarlane <jgm@berkeley.edu>
+Copyright (C) 2013-2017 John MacFarlane <jgm@berkeley.edu>
This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.OPML
- Copyright : Copyright (C) 2013-2015 John MacFarlane
+ Copyright : Copyright (C) 2013-2017 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -30,6 +30,8 @@ Conversion of 'Pandoc' documents to OPML XML.
-}
module Text.Pandoc.Writers.OPML ( writeOPML) where
import Control.Monad.Except (throwError)
+import Data.Text (Text, unpack)
+import qualified Data.Text as T
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Compat.Time
@@ -45,7 +47,7 @@ import Text.Pandoc.Writers.Shared
import Text.Pandoc.XML
-- | Convert Pandoc document to string in OPML format.
-writeOPML :: PandocMonad m => WriterOptions -> Pandoc -> m String
+writeOPML :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeOPML opts (Pandoc meta blocks) = do
let elements = hierarchicalize blocks
colwidth = if writerWrapText opts == WrapAuto
@@ -54,7 +56,7 @@ writeOPML opts (Pandoc meta blocks) = do
meta' = B.setMeta "date" (B.str $ convertDate $ docDate meta) meta
metadata <- metaToJSON opts
(writeMarkdown def . Pandoc nullMeta)
- (\ils -> trimr <$> (writeMarkdown def $ Pandoc nullMeta [Plain ils]))
+ (\ils -> T.stripEnd <$> (writeMarkdown def $ Pandoc nullMeta [Plain ils]))
meta'
main <- (render colwidth . vcat) <$> (mapM (elementToOPML opts) elements)
let context = defField "body" main metadata
@@ -63,9 +65,9 @@ writeOPML opts (Pandoc meta blocks) = do
Just tpl -> renderTemplate' tpl context
-writeHtmlInlines :: PandocMonad m => [Inline] -> m String
+writeHtmlInlines :: PandocMonad m => [Inline] -> m Text
writeHtmlInlines ils =
- trim <$> (writeHtml5String def $ Pandoc nullMeta [Plain ils])
+ T.strip <$> (writeHtml5String def $ Pandoc nullMeta [Plain ils])
-- date format: RFC 822: Thu, 14 Jul 2005 23:41:05 GMT
showDateTimeRFC822 :: UTCTime -> String
@@ -95,9 +97,10 @@ elementToOPML opts (Sec _ _num _ title elements) = do
(blocks, rest) = span isBlk elements
htmlIls <- writeHtmlInlines title
md <- if null blocks
- then return []
+ then return mempty
else do blks <- mapM fromBlk blocks
writeMarkdown def $ Pandoc nullMeta blks
- let attrs = [("text", htmlIls)] ++ [("_note", md) | not (null blocks)]
+ let attrs = [("text", unpack htmlIls)] ++
+ [("_note", unpack md) | not (null blocks)]
o <- mapM (elementToOPML opts) rest
return $ inTags True "outline" attrs $ vcat o