From 965f1ddd4a9d1317455094b8c41016624d92f8ce Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Sat, 13 May 2017 23:30:13 +0200 Subject: Update dates in copyright notices This follows the suggestions given by the FSF for GPL licensed software. --- src/Text/Pandoc/Readers/Org.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Readers/Org.hs') diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index 5e509178d..2b29bcfda 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2014-2016 Albert Krewinkel +Copyright (C) 2014-2017 Albert Krewinkel 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 @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Org - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel -- cgit v1.2.3 From 94b3dacb4ea7e5e99ab62286b13877b92f9391b3 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 10 Jun 2017 18:26:44 +0200 Subject: Changed all readers to take Text instead of String. Readers: Renamed StringReader -> TextReader. Updated tests. API change. --- src/Text/Pandoc/App.hs | 6 +- src/Text/Pandoc/Lua/PandocModule.hs | 5 +- src/Text/Pandoc/Readers.hs | 1 - src/Text/Pandoc/Readers/CommonMark.hs | 6 +- src/Text/Pandoc/Readers/DocBook.hs | 8 +- src/Text/Pandoc/Readers/EPUB.hs | 4 +- src/Text/Pandoc/Readers/HTML.hs | 6 +- src/Text/Pandoc/Readers/Haddock.hs | 5 +- src/Text/Pandoc/Readers/LaTeX.hs | 5 +- src/Text/Pandoc/Readers/Markdown.hs | 5 +- src/Text/Pandoc/Readers/MediaWiki.hs | 5 +- src/Text/Pandoc/Readers/Native.hs | 21 +- src/Text/Pandoc/Readers/OPML.hs | 10 +- src/Text/Pandoc/Readers/Org.hs | 7 +- src/Text/Pandoc/Readers/RST.hs | 7 +- src/Text/Pandoc/Readers/TWiki.hs | 7 +- src/Text/Pandoc/Readers/Textile.hs | 7 +- src/Text/Pandoc/Readers/Txt2Tags.hs | 7 +- test/Tests/Command.hs | 3 +- test/Tests/Helpers.hs | 4 + test/Tests/Readers/Docx.hs | 4 +- test/Tests/Readers/HTML.hs | 3 +- test/Tests/Readers/LaTeX.hs | 14 +- test/Tests/Readers/Markdown.hs | 48 +- test/Tests/Readers/Odt.hs | 6 +- test/Tests/Readers/Org.hs | 984 +++++++++++++++++----------------- test/Tests/Readers/RST.hs | 24 +- test/Tests/Readers/Txt2Tags.hs | 78 +-- test/Tests/Writers/Docx.hs | 6 +- 29 files changed, 672 insertions(+), 624 deletions(-) (limited to 'src/Text/Pandoc/Readers/Org.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 1d42e4854..c39bda859 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -405,11 +405,11 @@ convertWithOpts opts = do let sourceToDoc :: [FilePath] -> PandocIO Pandoc sourceToDoc sources' = case reader of - StringReader r + TextReader r | optFileScope opts || readerName == "json" -> - mconcat <$> mapM (readSource >=> r readerOpts . T.unpack) sources + mconcat <$> mapM (readSource >=> r readerOpts) sources | otherwise -> - readSources sources' >>= r readerOpts . T.unpack + readSources sources' >>= r readerOpts ByteStringReader r -> mconcat <$> mapM (readFile' >=> r readerOpts) sources diff --git a/src/Text/Pandoc/Lua/PandocModule.hs b/src/Text/Pandoc/Lua/PandocModule.hs index 8e0f3a5b4..27c19d4f0 100644 --- a/src/Text/Pandoc/Lua/PandocModule.hs +++ b/src/Text/Pandoc/Lua/PandocModule.hs @@ -30,6 +30,7 @@ module Text.Pandoc.Lua.PandocModule ( pushPandocModule ) where import Control.Monad (unless) import Data.ByteString.Char8 (unpack) import Data.Default (Default (..)) +import Data.Text (pack) import Scripting.Lua (LuaState, call, push, pushhsfunction, rawset) import Text.Pandoc.Class hiding (readDataFile) import Text.Pandoc.Definition (Pandoc) @@ -58,8 +59,8 @@ read_doc formatSpec content = do Left s -> return $ Left s Right reader -> case reader of - StringReader r -> do - res <- runIO $ r def content + TextReader r -> do + res <- runIO $ r def (pack content) case res of Left s -> return . Left $ show s Right pd -> return $ Right pd diff --git a/src/Text/Pandoc/Readers.hs b/src/Text/Pandoc/Readers.hs index 5cc37cd72..004fefe25 100644 --- a/src/Text/Pandoc/Readers.hs +++ b/src/Text/Pandoc/Readers.hs @@ -94,7 +94,6 @@ import Text.Parsec.Error import qualified Text.Pandoc.UTF8 as UTF8 import qualified Data.ByteString.Lazy as BL import Data.Text (Text) -import qualified Data.Text.Lazy as TL data Reader m = TextReader (ReaderOptions -> Text -> m Pandoc) | ByteStringReader (ReaderOptions -> BL.ByteString -> m Pandoc) diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs index e98ee066e..3c62f8db5 100644 --- a/src/Text/Pandoc/Readers/CommonMark.hs +++ b/src/Text/Pandoc/Readers/CommonMark.hs @@ -34,15 +34,15 @@ where import CMark import Data.List (groupBy) -import Data.Text (pack, unpack) +import Data.Text (Text, unpack) import Text.Pandoc.Class (PandocMonad) import Text.Pandoc.Definition import Text.Pandoc.Options -- | Parse a CommonMark formatted string into a 'Pandoc' structure. -readCommonMark :: PandocMonad m => ReaderOptions -> String -> m Pandoc +readCommonMark :: PandocMonad m => ReaderOptions -> Text -> m Pandoc readCommonMark opts s = return $ - nodeToPandoc $ commonmarkToNode opts' $ pack s + nodeToPandoc $ commonmarkToNode opts' s where opts' = if extensionEnabled Ext_smart (readerExtensions opts) then [optNormalize, optSmart] else [optNormalize] diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index bef256a93..bd3c7c356 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -16,6 +16,8 @@ import Text.TeXMath (readMathML, writeTeX) import Data.Default import Data.Foldable (asum) import Text.Pandoc.Class (PandocMonad) +import Data.Text (Text) +import qualified Data.Text as T {- @@ -522,11 +524,11 @@ instance Default DBState where , dbContent = [] } -readDocBook :: PandocMonad m => ReaderOptions -> String -> m Pandoc +readDocBook :: PandocMonad m => ReaderOptions -> Text -> m Pandoc readDocBook _ inp = do - let tree = normalizeTree . parseXML . handleInstructions $ inp + let tree = normalizeTree . parseXML . handleInstructions $ T.unpack inp (bs, st') <- flip runStateT (def{ dbContent = tree }) $ mapM parseBlock $ tree - return $ Pandoc (dbMeta st') (toList . mconcat $ bs) + return $ Pandoc (dbMeta st') (toList . mconcat $ bs) -- We treat specially (issue #1236), converting it -- to
, since xml-light doesn't parse the instruction correctly. diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index db58e9654..c0d8029dc 100644 --- a/src/Text/Pandoc/Readers/EPUB.hs +++ b/src/Text/Pandoc/Readers/EPUB.hs @@ -13,6 +13,8 @@ import Control.DeepSeq (NFData, deepseq) import Control.Monad (guard, liftM) import Control.Monad.Except (throwError) import qualified Data.ByteString.Lazy as BL (ByteString) +import qualified Data.Text.Lazy.Encoding as TL +import qualified Data.Text.Lazy as TL import Data.List (isInfixOf, isPrefixOf) import qualified Data.Map as M (Map, elems, fromList, lookup) import Data.Maybe (fromMaybe, mapMaybe) @@ -73,7 +75,7 @@ archiveToEPUB os archive = do mimeToReader "application/xhtml+xml" (unEscapeString -> root) (unEscapeString -> path) = do fname <- findEntryByPathE (root path) archive - html <- readHtml os' . UTF8.toStringLazy $ fromEntry fname + html <- readHtml os' . TL.toStrict . TL.decodeUtf8 $ fromEntry fname return $ fixInternalReferences path html mimeToReader s _ (unEscapeString -> path) | s `elem` imageMimes = return $ imageToPandoc path diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index c1bdb4d09..3bccf89fb 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -59,6 +59,7 @@ import Control.Monad ( guard, mzero, void, unless ) import Control.Arrow ((***)) import Control.Applicative ( (<|>) ) import Data.Monoid (First (..)) +import Data.Text (Text, unpack) import Text.TeXMath (readMathML, writeTeX) import Data.Default (Default (..), def) import Control.Monad.Reader (ask, asks, local, ReaderT, runReaderT, lift) @@ -74,11 +75,12 @@ import Control.Monad.Except (throwError) -- | Convert HTML-formatted string to 'Pandoc' document. readHtml :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assumes @'\n'@ line endings) + -> Text -- ^ String to parse (assumes @'\n'@ line endings) -> m Pandoc readHtml opts inp = do let tags = stripPrefixes . canonicalizeTags $ - parseTagsOptions parseOptions{ optTagPosition = True } inp + parseTagsOptions parseOptions{ optTagPosition = True } + (unpack inp) parseDoc = do blocks <- (fixPlains False) . mconcat <$> manyTill block eof meta <- stateMeta . parserState <$> getState diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs index 28caa528e..b22b71b96 100644 --- a/src/Text/Pandoc/Readers/Haddock.hs +++ b/src/Text/Pandoc/Readers/Haddock.hs @@ -16,6 +16,7 @@ module Text.Pandoc.Readers.Haddock import Control.Monad.Except (throwError) import Data.List (intersperse, stripPrefix) +import Data.Text (Text, unpack) import Data.Maybe (fromMaybe) import Data.Monoid ((<>)) import Documentation.Haddock.Parser @@ -32,9 +33,9 @@ import Text.Pandoc.Shared (splitBy, trim) -- | Parse Haddock markup and return a 'Pandoc' document. readHaddock :: PandocMonad m => ReaderOptions - -> String + -> Text -> m Pandoc -readHaddock opts s = case readHaddockEither opts s of +readHaddock opts s = case readHaddockEither opts (unpack s) of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index b65ae15ad..796d2789e 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -39,6 +39,7 @@ import Control.Applicative (many, optional, (<|>)) import Control.Monad import Control.Monad.Except (throwError) import Data.Char (chr, isAlphaNum, isLetter, ord) +import Data.Text (Text, unpack) import Data.List (intercalate, isPrefixOf) import qualified Data.Map as M import Data.Maybe (fromMaybe, maybeToList) @@ -59,10 +60,10 @@ import Text.Pandoc.Walk -- | Parse LaTeX from string and return 'Pandoc' document. readLaTeX :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assumes @'\n'@ line endings) + -> Text -- ^ String to parse (assumes @'\n'@ line endings) -> m Pandoc readLaTeX opts ltx = do - parsed <- readWithM parseLaTeX def{ stateOptions = opts } ltx + parsed <- readWithM parseLaTeX def{ stateOptions = opts } (unpack ltx) case parsed of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 5694c4354..5e966a17e 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -70,10 +70,11 @@ type MarkdownParser m = ParserT [Char] ParserState m -- | Read markdown from an input string and return a Pandoc document. readMarkdown :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readMarkdown opts s = do - parsed <- (readWithM parseMarkdown) def{ stateOptions = opts } (s ++ "\n\n") + parsed <- (readWithM parseMarkdown) def{ stateOptions = opts } + (T.unpack s ++ "\n\n") case parsed of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index 3f6142f00..a3ff60c14 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -41,6 +41,7 @@ module Text.Pandoc.Readers.MediaWiki ( readMediaWiki ) where import Control.Monad import Control.Monad.Except (throwError) import Data.Char (isDigit, isSpace) +import Data.Text (Text, unpack) import qualified Data.Foldable as F import Data.List (intercalate, intersperse, isPrefixOf) import qualified Data.Map as M @@ -64,7 +65,7 @@ import Text.Pandoc.XML (fromEntities) -- | Read mediawiki from an input string and return a Pandoc document. readMediaWiki :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readMediaWiki opts s = do parsed <- readWithM parseMediaWiki MWState{ mwOptions = opts @@ -76,7 +77,7 @@ readMediaWiki opts s = do , mwLogMessages = [] , mwInTT = False } - (s ++ "\n") + (unpack s ++ "\n") case parsed of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs index 8f42a45de..abc2ed38a 100644 --- a/src/Text/Pandoc/Readers/Native.hs +++ b/src/Text/Pandoc/Readers/Native.hs @@ -37,6 +37,7 @@ import Text.Pandoc.Shared (safeRead) import Control.Monad.Except (throwError) import Text.Pandoc.Class import Text.Pandoc.Error +import Data.Text (Text, unpack) -- | Read native formatted text and return a Pandoc document. -- The input may be a full pandoc document, a block list, a block, @@ -50,22 +51,22 @@ import Text.Pandoc.Error -- readNative :: PandocMonad m => ReaderOptions - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readNative _ s = - case maybe (Pandoc nullMeta <$> readBlocks s) Right (safeRead s) of + case maybe (Pandoc nullMeta <$> readBlocks s) Right (safeRead (unpack s)) of Right doc -> return doc Left _ -> throwError $ PandocParseError "couldn't read native" -readBlocks :: String -> Either PandocError [Block] -readBlocks s = maybe ((:[]) <$> readBlock s) Right (safeRead s) +readBlocks :: Text -> Either PandocError [Block] +readBlocks s = maybe ((:[]) <$> readBlock s) Right (safeRead (unpack s)) -readBlock :: String -> Either PandocError Block -readBlock s = maybe (Plain <$> readInlines s) Right (safeRead s) +readBlock :: Text -> Either PandocError Block +readBlock s = maybe (Plain <$> readInlines s) Right (safeRead (unpack s)) -readInlines :: String -> Either PandocError [Inline] -readInlines s = maybe ((:[]) <$> readInline s) Right (safeRead s) +readInlines :: Text -> Either PandocError [Inline] +readInlines s = maybe ((:[]) <$> readInline s) Right (safeRead (unpack s)) -readInline :: String -> Either PandocError Inline -readInline s = maybe (Left . PandocParseError $ "Could not read: " ++ s) Right (safeRead s) +readInline :: Text -> Either PandocError Inline +readInline s = maybe (Left . PandocParseError $ "Could not read: " ++ unpack s) Right (safeRead (unpack s)) diff --git a/src/Text/Pandoc/Readers/OPML.hs b/src/Text/Pandoc/Readers/OPML.hs index cf1c8f479..591d7590e 100644 --- a/src/Text/Pandoc/Readers/OPML.hs +++ b/src/Text/Pandoc/Readers/OPML.hs @@ -2,6 +2,7 @@ module Text.Pandoc.Readers.OPML ( readOPML ) where import Control.Monad.State import Data.Char (toUpper) +import Data.Text (Text, unpack, pack) import Data.Default import Data.Generics import Text.HTML.TagSoup.Entity (lookupEntity) @@ -28,9 +29,10 @@ instance Default OPMLState where , opmlDocDate = mempty } -readOPML :: PandocMonad m => ReaderOptions -> String -> m Pandoc +readOPML :: PandocMonad m => ReaderOptions -> Text -> m Pandoc readOPML _ inp = do - (bs, st') <- flip runStateT def (mapM parseBlock $ normalizeTree $ parseXML inp) + (bs, st') <- flip runStateT def + (mapM parseBlock $ normalizeTree $ parseXML (unpack inp)) return $ setTitle (opmlDocTitle st') $ setAuthors (opmlDocAuthors st') $ @@ -69,10 +71,10 @@ asHtml :: PandocMonad m => String -> OPML m Inlines asHtml s = (\(Pandoc _ bs) -> case bs of [Plain ils] -> fromList ils - _ -> mempty) <$> (lift $ readHtml def s) + _ -> mempty) <$> (lift $ readHtml def (pack s)) asMarkdown :: PandocMonad m => String -> OPML m Blocks -asMarkdown s = (\(Pandoc _ bs) -> fromList bs) <$> (lift $ readMarkdown def s) +asMarkdown s = (\(Pandoc _ bs) -> fromList bs) <$> (lift $ readMarkdown def (pack s)) getBlocks :: PandocMonad m => Element -> OPML m Blocks getBlocks e = mconcat <$> (mapM parseBlock $ elContent e) diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index 2b29bcfda..5e0d67d10 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -40,15 +40,18 @@ import Text.Pandoc.Parsing (reportLogMessages) import Control.Monad.Except (throwError) import Control.Monad.Reader (runReaderT) +import Data.Text (Text) +import qualified Data.Text as T -- | Parse org-mode string and return a Pandoc document. readOrg :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readOrg opts s = do parsed <- flip runReaderT def $ - readWithM parseOrg (optionsToParserState opts) (s ++ "\n\n") + readWithM parseOrg (optionsToParserState opts) + (T.unpack s ++ "\n\n") case parsed of Right result -> return result Left _ -> throwError $ PandocParseError "problem parsing org" diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index b242d6428..fb5f6f2d4 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -53,6 +53,8 @@ import Text.Pandoc.Options import Text.Pandoc.Parsing import Text.Pandoc.Shared import Text.Printf (printf) +import Data.Text (Text) +import qualified Data.Text as T -- TODO: -- [ ] .. parsed-literal @@ -62,10 +64,11 @@ import Text.Printf (printf) -- | Parse reStructuredText string and return Pandoc document. readRST :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readRST opts s = do - parsed <- (readWithM parseRST) def{ stateOptions = opts } (s ++ "\n\n") + parsed <- (readWithM parseRST) def{ stateOptions = opts } + (T.unpack s ++ "\n\n") case parsed of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs index fcb95fc35..9e544c4ac 100644 --- a/src/Text/Pandoc/Readers/TWiki.hs +++ b/src/Text/Pandoc/Readers/TWiki.hs @@ -49,14 +49,17 @@ import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (enclosed, macro, nested) import Text.Pandoc.Readers.HTML (htmlTag, isCommentTag) import Text.Pandoc.XML (fromEntities) +import Data.Text (Text) +import qualified Data.Text as T -- | Read twiki from an input string and return a Pandoc document. readTWiki :: PandocMonad m => ReaderOptions - -> String + -> Text -> m Pandoc readTWiki opts s = do - res <- readWithM parseTWiki def{ stateOptions = opts } (s ++ "\n\n") + res <- readWithM parseTWiki def{ stateOptions = opts } + (T.unpack s ++ "\n\n") case res of Left e -> throwError e Right d -> return d diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index 0b964dd63..1669e3e51 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -70,14 +70,17 @@ import Text.Pandoc.Parsing import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isInlineTag) import Text.Pandoc.Readers.LaTeX (rawLaTeXBlock, rawLaTeXInline) import Text.Pandoc.Shared (trim) +import Data.Text (Text) +import qualified Data.Text as T -- | Parse a Textile text and return a Pandoc document. readTextile :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readTextile opts s = do - parsed <- readWithM parseTextile def{ stateOptions = opts } (s ++ "\n\n") + parsed <- readWithM parseTextile def{ stateOptions = opts } + (T.unpack s ++ "\n\n") case parsed of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index d8791869d..260bb7fff 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -45,7 +45,8 @@ import Text.Pandoc.Shared (compactify, compactifyDL, escapeURI) import Control.Monad (guard, void, when) import Control.Monad.Reader (Reader, asks, runReader) import Data.Default - +import Data.Text (Text) +import qualified Data.Text as T import Control.Monad.Except (catchError, throwError) import Data.Time.Format (formatTime) import Text.Pandoc.Class (PandocMonad) @@ -90,11 +91,11 @@ getT2TMeta = do -- | Read Txt2Tags from an input string returning a Pandoc document readTxt2Tags :: PandocMonad m => ReaderOptions - -> String + -> Text -> m Pandoc readTxt2Tags opts s = do meta <- getT2TMeta - let parsed = flip runReader meta $ readWithM parseT2T (def {stateOptions = opts}) (s ++ "\n\n") + let parsed = flip runReader meta $ readWithM parseT2T (def {stateOptions = opts}) (T.unpack s ++ "\n\n") case parsed of Right result -> return $ result Left e -> throwError e diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs index 588c0c06c..1f3694f60 100644 --- a/test/Tests/Command.hs +++ b/test/Tests/Command.hs @@ -13,6 +13,7 @@ import Test.Tasty.HUnit import Tests.Helpers import Text.Pandoc import Text.Pandoc.Shared (trimr) +import qualified Data.ByteString as BS import qualified Text.Pandoc.UTF8 as UTF8 import System.IO.Unsafe (unsafePerformIO) -- TODO temporary @@ -83,7 +84,7 @@ runCommandTest pandocpath (num, code) = extractCommandTest :: FilePath -> FilePath -> TestTree extractCommandTest pandocpath fp = unsafePerformIO $ do - contents <- UTF8.readFile ("command" fp) + contents <- UTF8.toText <$> BS.readFile ("command" fp) Pandoc _ blocks <- runIOorExplode (readMarkdown def{ readerExtensions = pandocExtensions } contents) let codeblocks = map extractCode $ filter isCodeBlock $ blocks diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs index 7e8ebb01a..3a82867cb 100644 --- a/test/Tests/Helpers.hs +++ b/test/Tests/Helpers.hs @@ -15,6 +15,7 @@ module Tests.Helpers ( test import Data.Algorithm.Diff import qualified Data.Map as M +import Data.Text (Text, unpack) import System.Directory import System.Environment.Executable (getExecutablePath) import System.Exit @@ -120,6 +121,9 @@ instance ToString Inlines where instance ToString String where toString = id +instance ToString Text where + toString = unpack + class ToPandoc a where toPandoc :: a -> Pandoc diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs index 028a4ff2f..e29f0acad 100644 --- a/test/Tests/Readers/Docx.hs +++ b/test/Tests/Readers/Docx.hs @@ -2,11 +2,13 @@ module Tests.Readers.Docx (tests) where import Codec.Archive.Zip import qualified Data.ByteString.Lazy as B +import qualified Data.ByteString as BS import qualified Data.Map as M import Test.Tasty import Test.Tasty.HUnit import Tests.Helpers import Text.Pandoc +import Text.Pandoc.UTF8 as UTF8 import qualified Text.Pandoc.Class as P import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory) import System.IO.Unsafe -- TODO temporary @@ -40,7 +42,7 @@ compareOutput :: ReaderOptions -> IO (NoNormPandoc, NoNormPandoc) compareOutput opts docxFile nativeFile = do df <- B.readFile docxFile - nf <- Prelude.readFile nativeFile + nf <- UTF8.toText <$> BS.readFile nativeFile p <- runIOorExplode $ readDocx opts df df' <- runIOorExplode $ readNative def nf return $ (noNorm p, noNorm df') diff --git a/test/Tests/Readers/HTML.hs b/test/Tests/Readers/HTML.hs index e2262d131..8647540b6 100644 --- a/test/Tests/Readers/HTML.hs +++ b/test/Tests/Readers/HTML.hs @@ -6,8 +6,9 @@ import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder +import Data.Text (Text) -html :: String -> Pandoc +html :: Text -> Pandoc html = purely $ readHtml def tests :: [TestTree] diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs index 75547ed6b..390d80df9 100644 --- a/test/Tests/Readers/LaTeX.hs +++ b/test/Tests/Readers/LaTeX.hs @@ -6,14 +6,16 @@ import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder +import Data.Text (Text, pack) +import qualified Data.Text as T -latex :: String -> Pandoc +latex :: Text -> Pandoc latex = purely $ readLaTeX def{ readerExtensions = getDefaultExtensions "latex" } infix 4 =: (=:) :: ToString c - => String -> (String, c) -> TestTree + => String -> (Text, c) -> TestTree (=:) = test latex simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks @@ -74,7 +76,7 @@ tests = [ testGroup "basic" "\\begin{tabular}{|rl|}One & Two\\\\ \\end{tabular}" =?> simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] , "Multi line table" =: - unlines [ "\\begin{tabular}{|c|}" + T.unlines [ "\\begin{tabular}{|c|}" , "One\\\\" , "Two\\\\" , "Three\\\\" @@ -91,7 +93,7 @@ tests = [ testGroup "basic" "\\begin{tabular}{@{}r@{}l}One & Two\\\\ \\end{tabular}" =?> simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] , "Table with custom column separators" =: - unlines [ "\\begin{tabular}{@{($\\to$)}r@{\\hspace{2cm}}l}" + T.unlines [ "\\begin{tabular}{@{($\\to$)}r@{\\hspace{2cm}}l}" , "One&Two\\\\" , "\\end{tabular}" ] =?> simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] @@ -108,10 +110,10 @@ tests = [ testGroup "basic" , let hex = ['0'..'9']++['a'..'f'] in testGroup "Character Escapes" [ "Two-character escapes" =: - concat ["^^"++[i,j] | i <- hex, j <- hex] =?> + mconcat ["^^" <> T.pack [i,j] | i <- hex, j <- hex] =?> para (str ['\0'..'\255']) , "One-character escapes" =: - concat ["^^"++[i] | i <- hex] =?> + mconcat ["^^" <> T.pack [i] | i <- hex] =?> para (str $ ['p'..'y']++['!'..'&']) ] ] diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs index e1d0c8e1f..1cd32b87d 100644 --- a/test/Tests/Readers/Markdown.hs +++ b/test/Tests/Readers/Markdown.hs @@ -1,38 +1,40 @@ {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Markdown (tests) where +import Data.Text (Text, unpack) +import qualified Data.Text as T import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder -markdown :: String -> Pandoc +markdown :: Text -> Pandoc markdown = purely $ readMarkdown def { readerExtensions = disableExtension Ext_smart pandocExtensions } -markdownSmart :: String -> Pandoc +markdownSmart :: Text -> Pandoc markdownSmart = purely $ readMarkdown def { readerExtensions = enableExtension Ext_smart pandocExtensions } -markdownCDL :: String -> Pandoc +markdownCDL :: Text -> Pandoc markdownCDL = purely $ readMarkdown def { readerExtensions = enableExtension Ext_compact_definition_lists pandocExtensions } -markdownGH :: String -> Pandoc +markdownGH :: Text -> Pandoc markdownGH = purely $ readMarkdown def { readerExtensions = githubMarkdownExtensions } infix 4 =: (=:) :: ToString c - => String -> (String, c) -> TestTree + => String -> (Text, c) -> TestTree (=:) = test markdown -testBareLink :: (String, Inlines) -> TestTree +testBareLink :: (Text, Inlines) -> TestTree testBareLink (inp, ils) = test (purely $ readMarkdown def{ readerExtensions = extensionsFromList [Ext_autolink_bare_uris, Ext_raw_html] }) - inp (inp, doc $ para ils) + (unpack inp) (inp, doc $ para ils) autolink :: String -> Inlines autolink = autolinkWith nullAttr @@ -40,7 +42,7 @@ autolink = autolinkWith nullAttr autolinkWith :: Attr -> String -> Inlines autolinkWith attr s = linkWith attr s "" (str s) -bareLinkTests :: [(String, Inlines)] +bareLinkTests :: [(Text, Inlines)] bareLinkTests = [ ("http://google.com is a search engine.", autolink "http://google.com" <> " is a search engine.") @@ -376,10 +378,10 @@ tests = [ testGroup "inline code" rawBlock "html" "" <> divWith nullAttr (para $ text "with this div too.")] , test markdownGH "issue #1636" $ - unlines [ "* a" - , "* b" - , "* c" - , " * d" ] + T.unlines [ "* a" + , "* b" + , "* c" + , " * d" ] =?> bulletList [ plain "a" , plain "b" @@ -419,9 +421,9 @@ tests = [ testGroup "inline code" , let citation = cite [Citation "cita" [] [] AuthorInText 0 0] (str "@cita") in testGroup "footnote/link following citation" -- issue #2083 [ "footnote" =: - unlines [ "@cita[^note]" - , "" - , "[^note]: note" ] =?> + T.unlines [ "@cita[^note]" + , "" + , "[^note]: note" ] =?> para ( citation <> note (para $ str "note") ) @@ -431,22 +433,22 @@ tests = [ testGroup "inline code" citation <> space <> link "http://www.com" "" (str "link") ) , "reference link" =: - unlines [ "@cita [link][link]" - , "" - , "[link]: http://www.com" ] =?> + T.unlines [ "@cita [link][link]" + , "" + , "[link]: http://www.com" ] =?> para ( citation <> space <> link "http://www.com" "" (str "link") ) , "short reference link" =: - unlines [ "@cita [link]" - , "" - , "[link]: http://www.com" ] =?> + T.unlines [ "@cita [link]" + , "" + , "[link]: http://www.com" ] =?> para ( citation <> space <> link "http://www.com" "" (str "link") ) , "implicit header link" =: - unlines [ "# Header" - , "@cita [Header]" ] =?> + T.unlines [ "# Header" + , "@cita [Header]" ] =?> headerWith ("header",[],[]) 1 (str "Header") <> para ( citation <> space <> link "#header" "" (str "Header") ) diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs index 6fc062158..61ccc8819 100644 --- a/test/Tests/Readers/Odt.hs +++ b/test/Tests/Readers/Odt.hs @@ -2,6 +2,8 @@ module Tests.Readers.Odt (tests) where import Control.Monad (liftM) import qualified Data.ByteString.Lazy as B +import qualified Data.ByteString as BS +import qualified Text.Pandoc.UTF8 as UTF8 import qualified Data.Map as M import Test.Tasty import Tests.Helpers @@ -58,7 +60,7 @@ type TestCreator = ReaderOptions compareOdtToNative :: TestCreator compareOdtToNative opts odtPath nativePath = do - nativeFile <- Prelude.readFile nativePath + nativeFile <- UTF8.toText <$> BS.readFile nativePath odtFile <- B.readFile odtPath native <- getNoNormVia id "native" <$> runIO (readNative def nativeFile) odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile) @@ -66,7 +68,7 @@ compareOdtToNative opts odtPath nativePath = do compareOdtToMarkdown :: TestCreator compareOdtToMarkdown opts odtPath markdownPath = do - markdownFile <- Prelude.readFile markdownPath + markdownFile <- UTF8.toText <$> BS.readFile markdownPath odtFile <- B.readFile odtPath markdown <- getNoNormVia id "markdown" <$> runIO (readMarkdown def{ readerExtensions = pandocExtensions } diff --git a/test/Tests/Readers/Org.hs b/test/Tests/Readers/Org.hs index 4644d13a0..45b10da42 100644 --- a/test/Tests/Readers/Org.hs +++ b/test/Tests/Readers/Org.hs @@ -2,21 +2,23 @@ module Tests.Readers.Org (tests) where import Data.List (intersperse) +import Data.Text (Text) +import qualified Data.Text as T import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Builder -org :: String -> Pandoc +org :: Text -> Pandoc org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" } -orgSmart :: String -> Pandoc +orgSmart :: Text -> Pandoc orgSmart = purely $ readOrg def { readerExtensions = enableExtension Ext_smart $ getDefaultExtensions "org" } infix 4 =: (=:) :: ToString c - => String -> (String, c) -> TestTree + => String -> (Text, c) -> TestTree (=:) = test org spcSep :: [Inlines] -> Inlines @@ -112,17 +114,17 @@ tests = para (note $ para "Schreib mir eine E-Mail") , "Markup-chars not occuring on word break are symbols" =: - unlines [ "this+that+ +so+on" - , "seven*eight* nine*" - , "+not+funny+" - ] =?> + T.unlines [ "this+that+ +so+on" + , "seven*eight* nine*" + , "+not+funny+" + ] =?> para ("this+that+ +so+on" <> softbreak <> "seven*eight* nine*" <> softbreak <> strikeout "not+funny") , "No empty markup" =: - "// ** __ ++ == ~~ $$" =?> - para (spcSep [ "//", "**", "__", "++", "==", "~~", "$$" ]) + "// ** __ <> == ~~ $$" =?> + para (spcSep [ "//", "**", "__", "<>", "==", "~~", "$$" ]) , "Adherence to Org's rules for markup borders" =: "/t/& a/ / ./r/ (*l*) /e/! /b/." =?> @@ -143,11 +145,11 @@ tests = para "/nada,/" , "Markup should work properly after a blank line" =: - unlines ["foo", "", "/bar/"] =?> + T.unlines ["foo", "", "/bar/"] =?> (para $ text "foo") <> (para $ emph $ text "bar") , "Inline math must stay within three lines" =: - unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?> + T.unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?> para ((math "a\nb\nc") <> softbreak <> "$d" <> softbreak <> "e" <> softbreak <> "f" <> softbreak <> "g$") @@ -169,17 +171,17 @@ tests = softbreak <> "emph/") , "Sub- and superscript expressions" =: - unlines [ "a_(a(b)(c)d)" - , "e^(f(g)h)" - , "i_(jk)l)" - , "m^()n" - , "o_{p{q{}r}}" - , "s^{t{u}v}" - , "w_{xy}z}" - , "1^{}2" - , "3_{{}}" - , "4^(a(*b(c*)d))" - ] =?> + T.unlines [ "a_(a(b)(c)d)" + , "e^(f(g)h)" + , "i_(jk)l)" + , "m^()n" + , "o_{p{q{}r}}" + , "s^{t{u}v}" + , "w_{xy}z}" + , "1^{}2" + , "3_{{}}" + , "4^(a(*b(c*)d))" + ] =?> para (mconcat $ intersperse softbreak [ "a" <> subscript "(a(b)(c)d)" , "e" <> superscript "(f(g)h)" @@ -206,17 +208,17 @@ tests = (para $ image "sunrise.jpg" "" "") , "Multiple images within a paragraph" =: - unlines [ "[[file:sunrise.jpg]]" - , "[[file:sunset.jpg]]" - ] =?> + T.unlines [ "[[file:sunrise.jpg]]" + , "[[file:sunset.jpg]]" + ] =?> (para $ (image "sunrise.jpg" "" "") <> softbreak <> (image "sunset.jpg" "" "")) , "Image with html attributes" =: - unlines [ "#+ATTR_HTML: :width 50%" - , "[[file:guinea-pig.gif]]" - ] =?> + T.unlines [ "#+ATTR_HTML: :width 50%" + , "[[file:guinea-pig.gif]]" + ] =?> (para $ imageWith ("", [], [("width", "50%")]) "guinea-pig.gif" "" "") ] @@ -511,21 +513,21 @@ tests = in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}") , "Macro" =: - unlines [ "#+MACRO: HELLO /Hello, $1/" - , "{{{HELLO(World)}}}" - ] =?> + T.unlines [ "#+MACRO: HELLO /Hello, $1/" + , "{{{HELLO(World)}}}" + ] =?> para (emph "Hello, World") , "Macro repeting its argument" =: - unlines [ "#+MACRO: HELLO $1$1" - , "{{{HELLO(moin)}}}" - ] =?> + T.unlines [ "#+MACRO: HELLO $1$1" + , "{{{HELLO(moin)}}}" + ] =?> para "moinmoin" , "Macro called with too few arguments" =: - unlines [ "#+MACRO: HELLO Foo $1 $2 Bar" - , "{{{HELLO()}}}" - ] =?> + T.unlines [ "#+MACRO: HELLO Foo $1 $2 Bar" + , "{{{HELLO()}}}" + ] =?> para "Foo Bar" ] @@ -539,10 +541,10 @@ tests = para "#-tag" , "Comment surrounded by Text" =: - unlines [ "Before" - , "# Comment" - , "After" - ] =?> + T.unlines [ "Before" + , "# Comment" + , "After" + ] =?> mconcat [ para "Before" , para "After" ] @@ -579,10 +581,10 @@ tests = in Pandoc meta mempty , "Properties drawer" =: - unlines [ " :PROPERTIES:" - , " :setting: foo" - , " :END:" - ] =?> + T.unlines [ " :PROPERTIES:" + , " :setting: foo" + , " :END:" + ] =?> (mempty::Blocks) , "LaTeX_headers options are translated to header-includes" =: @@ -610,46 +612,46 @@ tests = in Pandoc meta mempty , "later meta definitions take precedence" =: - unlines [ "#+AUTHOR: this will not be used" - , "#+author: Max" - ] =?> + T.unlines [ "#+AUTHOR: this will not be used" + , "#+author: Max" + ] =?> let author = MetaInlines [Str "Max"] meta = setMeta "author" (MetaList [author]) $ nullMeta in Pandoc meta mempty , "Logbook drawer" =: - unlines [ " :LogBook:" - , " - State \"DONE\" from \"TODO\" [2014-03-03 Mon 11:00]" - , " :END:" - ] =?> + T.unlines [ " :LogBook:" + , " - State \"DONE\" from \"TODO\" [2014-03-03 Mon 11:00]" + , " :END:" + ] =?> (mempty::Blocks) , "Drawer surrounded by text" =: - unlines [ "Before" - , ":PROPERTIES:" - , ":END:" - , "After" - ] =?> + T.unlines [ "Before" + , ":PROPERTIES:" + , ":END:" + , "After" + ] =?> para "Before" <> para "After" , "Drawer markers must be the only text in the line" =: - unlines [ " :LOGBOOK: foo" - , " :END: bar" - ] =?> + T.unlines [ " :LOGBOOK: foo" + , " :END: bar" + ] =?> para (":LOGBOOK: foo" <> softbreak <> ":END: bar") , "Drawers can be arbitrary" =: - unlines [ ":FOO:" - , "/bar/" - , ":END:" - ] =?> + T.unlines [ ":FOO:" + , "/bar/" + , ":END:" + ] =?> divWith (mempty, ["FOO", "drawer"], mempty) (para $ emph "bar") , "Anchor reference" =: - unlines [ "<> Target." - , "" - , "[[link-here][See here!]]" - ] =?> + T.unlines [ "<> Target." + , "" + , "[[link-here][See here!]]" + ] =?> (para (spanWith ("link-here", [], []) mempty <> "Target.") <> para (link "#link-here" "" ("See" <> space <> "here!"))) @@ -658,112 +660,112 @@ tests = (para (emph $ "Where's" <> space <> "Wally?")) , "Link to nonexistent anchor" =: - unlines [ "<> Target." - , "" - , "[[link$here][See here!]]" - ] =?> + T.unlines [ "<> Target." + , "" + , "[[link$here][See here!]]" + ] =?> (para (spanWith ("link-here", [], []) mempty <> "Target.") <> para (emph ("See" <> space <> "here!"))) , "Link abbreviation" =: - unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s" - , "[[wp:Org_mode][Wikipedia on Org-mode]]" - ] =?> + T.unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s" + , "[[wp:Org_mode][Wikipedia on Org-mode]]" + ] =?> (para (link "https://en.wikipedia.org/wiki/Org_mode" "" ("Wikipedia" <> space <> "on" <> space <> "Org-mode"))) , "Link abbreviation, defined after first use" =: - unlines [ "[[zl:non-sense][Non-sense articles]]" - , "#+LINK: zl http://zeitlens.com/tags/%s.html" - ] =?> + T.unlines [ "[[zl:non-sense][Non-sense articles]]" + , "#+LINK: zl http://zeitlens.com/tags/%s.html" + ] =?> (para (link "http://zeitlens.com/tags/non-sense.html" "" ("Non-sense" <> space <> "articles"))) , "Link abbreviation, URL encoded arguments" =: - unlines [ "#+link: expl http://example.com/%h/foo" - , "[[expl:Hello, World!][Moin!]]" - ] =?> + T.unlines [ "#+link: expl http://example.com/%h/foo" + , "[[expl:Hello, World!][Moin!]]" + ] =?> (para (link "http://example.com/Hello%2C%20World%21/foo" "" "Moin!")) , "Link abbreviation, append arguments" =: - unlines [ "#+link: expl http://example.com/" - , "[[expl:foo][bar]]" - ] =?> + T.unlines [ "#+link: expl http://example.com/" + , "[[expl:foo][bar]]" + ] =?> (para (link "http://example.com/foo" "" "bar")) , testGroup "export options" [ "disable simple sub/superscript syntax" =: - unlines [ "#+OPTIONS: ^:nil" - , "a^b" - ] =?> + T.unlines [ "#+OPTIONS: ^:nil" + , "a^b" + ] =?> para "a^b" , "directly select drawers to be exported" =: - unlines [ "#+OPTIONS: d:(\"IMPORTANT\")" - , ":IMPORTANT:" - , "23" - , ":END:" - , ":BORING:" - , "very boring" - , ":END:" - ] =?> + T.unlines [ "#+OPTIONS: d:(\"IMPORTANT\")" + , ":IMPORTANT:" + , "23" + , ":END:" + , ":BORING:" + , "very boring" + , ":END:" + ] =?> divWith (mempty, ["IMPORTANT", "drawer"], mempty) (para "23") , "exclude drawers from being exported" =: - unlines [ "#+OPTIONS: d:(not \"BORING\")" - , ":IMPORTANT:" - , "5" - , ":END:" - , ":BORING:" - , "very boring" - , ":END:" - ] =?> + T.unlines [ "#+OPTIONS: d:(not \"BORING\")" + , ":IMPORTANT:" + , "5" + , ":END:" + , ":BORING:" + , "very boring" + , ":END:" + ] =?> divWith (mempty, ["IMPORTANT", "drawer"], mempty) (para "5") , "don't include archive trees" =: - unlines [ "#+OPTIONS: arch:nil" - , "* old :ARCHIVE:" - ] =?> + T.unlines [ "#+OPTIONS: arch:nil" + , "* old :ARCHIVE:" + ] =?> (mempty ::Blocks) , "include complete archive trees" =: - unlines [ "#+OPTIONS: arch:t" - , "* old :ARCHIVE:" - , " boring" - ] =?> + T.unlines [ "#+OPTIONS: arch:t" + , "* old :ARCHIVE:" + , " boring" + ] =?> mconcat [ headerWith ("old", [], mempty) 1 ("old" <> space <> tagSpan "ARCHIVE") , para "boring" ] , "include archive tree header only" =: - unlines [ "#+OPTIONS: arch:headline" - , "* old :ARCHIVE:" - , " boring" - ] =?> + T.unlines [ "#+OPTIONS: arch:headline" + , "* old :ARCHIVE:" + , " boring" + ] =?> headerWith ("old", [], mempty) 1 ("old" <> space <> tagSpan "ARCHIVE") , "limit headline depth" =: - unlines [ "#+OPTIONS: H:2" - , "* top-level section" - , "** subsection" - , "*** list item 1" - , "*** list item 2" - ] =?> + T.unlines [ "#+OPTIONS: H:2" + , "* top-level section" + , "** subsection" + , "*** list item 1" + , "*** list item 2" + ] =?> mconcat [ headerWith ("top-level-section", [], []) 1 "top-level section" , headerWith ("subsection", [], []) 2 "subsection" , orderedList [ para "list item 1", para "list item 2" ] ] , "turn all headlines into lists" =: - unlines [ "#+OPTIONS: H:0" - , "first block" - , "* top-level section 1" - , "** subsection" - , "* top-level section 2" - ] =?> + T.unlines [ "#+OPTIONS: H:0" + , "first block" + , "* top-level section 1" + , "** subsection" + , "* top-level section 2" + ] =?> mconcat [ para "first block" , orderedList [ (para "top-level section 1" <> @@ -772,33 +774,33 @@ tests = ] , "disable author export" =: - unlines [ "#+OPTIONS: author:nil" - , "#+AUTHOR: ShyGuy" - ] =?> + T.unlines [ "#+OPTIONS: author:nil" + , "#+AUTHOR: ShyGuy" + ] =?> Pandoc nullMeta mempty , "disable creator export" =: - unlines [ "#+OPTIONS: creator:nil" - , "#+creator: The Architect" - ] =?> + T.unlines [ "#+OPTIONS: creator:nil" + , "#+creator: The Architect" + ] =?> Pandoc nullMeta mempty , "disable email export" =: - unlines [ "#+OPTIONS: email:nil" - , "#+email: no-mail-please@example.com" - ] =?> + T.unlines [ "#+OPTIONS: email:nil" + , "#+email: no-mail-please@example.com" + ] =?> Pandoc nullMeta mempty , "disable inclusion of todo keywords" =: - unlines [ "#+OPTIONS: todo:nil" - , "** DONE todo export" - ] =?> + T.unlines [ "#+OPTIONS: todo:nil" + , "** DONE todo export" + ] =?> headerWith ("todo-export", [], []) 2 "todo export" , "remove tags from headlines" =: - unlines [ "#+OPTIONS: tags:nil" - , "* Headline :hello:world:" - ] =?> + T.unlines [ "#+OPTIONS: tags:nil" + , "* Headline :hello:world:" + ] =?> headerWith ("headline", [], mempty) 1 "Headline" ] ] @@ -820,10 +822,10 @@ tests = ("Third" <> space <> "Level" <> space <> "Headline") , "Compact Headers with Paragraph" =: - unlines [ "* First Level" - , "** Second Level" - , " Text" - ] =?> + T.unlines [ "* First Level" + , "** Second Level" + , " Text" + ] =?> mconcat [ headerWith ("first-level", [], []) 1 ("First" <> space <> "Level") @@ -834,12 +836,12 @@ tests = ] , "Separated Headers with Paragraph" =: - unlines [ "* First Level" - , "" - , "** Second Level" - , "" - , " Text" - ] =?> + T.unlines [ "* First Level" + , "" + , "** Second Level" + , "" + , " Text" + ] =?> mconcat [ headerWith ("first-level", [], []) 1 ("First" <> space <> "Level") @@ -850,10 +852,10 @@ tests = ] , "Headers not preceded by a blank line" =: - unlines [ "** eat dinner" - , "Spaghetti and meatballs tonight." - , "** walk dog" - ] =?> + T.unlines [ "** eat dinner" + , "Spaghetti and meatballs tonight." + , "** walk dog" + ] =?> mconcat [ headerWith ("eat-dinner", [], []) 2 ("eat" <> space <> "dinner") @@ -879,21 +881,21 @@ tests = headerWith ("waiting-header", [], []) 1 "WAITING header" , "Custom todo keywords" =: - unlines [ "#+TODO: WAITING CANCELLED" - , "* WAITING compile" - , "* CANCELLED lunch" - ] =?> + T.unlines [ "#+TODO: WAITING CANCELLED" + , "* WAITING compile" + , "* CANCELLED lunch" + ] =?> let todoSpan = spanWith ("", ["todo", "WAITING"], []) "WAITING" doneSpan = spanWith ("", ["done", "CANCELLED"], []) "CANCELLED" in headerWith ("compile", [], []) 1 (todoSpan <> space <> "compile") <> headerWith ("lunch", [], []) 1 (doneSpan <> space <> "lunch") , "Custom todo keywords with multiple done-states" =: - unlines [ "#+TODO: WAITING | DONE CANCELLED " - , "* WAITING compile" - , "* CANCELLED lunch" - , "* DONE todo-feature" - ] =?> + T.unlines [ "#+TODO: WAITING | DONE CANCELLED " + , "* WAITING compile" + , "* CANCELLED lunch" + , "* DONE todo-feature" + ] =?> let waiting = spanWith ("", ["todo", "WAITING"], []) "WAITING" cancelled = spanWith ("", ["done", "CANCELLED"], []) "CANCELLED" done = spanWith ("", ["done", "DONE"], []) "DONE" @@ -903,10 +905,10 @@ tests = ] , "Tagged headers" =: - unlines [ "* Personal :PERSONAL:" - , "** Call Mom :@PHONE:" - , "** Call John :@PHONE:JOHN: " - ] =?> + T.unlines [ "* Personal :PERSONAL:" + , "** Call Mom :@PHONE:" + , "** Call John :@PHONE:JOHN: " + ] =?> mconcat [ headerWith ("personal", [], []) 1 ("Personal " <> tagSpan "PERSONAL") @@ -923,10 +925,10 @@ tests = headerWith ("this-is-not-tagged", [], []) 1 "This: is not: tagged" , "Header starting with strokeout text" =: - unlines [ "foo" - , "" - , "* +thing+ other thing" - ] =?> + T.unlines [ "foo" + , "" + , "* +thing+ other thing" + ] =?> mconcat [ para "foo" , headerWith ("thing-other-thing", [], []) 1 @@ -934,11 +936,11 @@ tests = ] , "Comment Trees" =: - unlines [ "* COMMENT A comment tree" - , " Not much going on here" - , "** This will be dropped" - , "* Comment tree above" - ] =?> + T.unlines [ "* COMMENT A comment tree" + , " Not much going on here" + , "** This will be dropped" + , "* Comment tree above" + ] =?> headerWith ("comment-tree-above", [], []) 1 "Comment tree above" , "Nothing but a COMMENT header" =: @@ -946,38 +948,38 @@ tests = (mempty::Blocks) , "Tree with :noexport:" =: - unlines [ "* Should be ignored :archive:noexport:old:" - , "** Old stuff" - , " This is not going to be exported" - ] =?> + T.unlines [ "* Should be ignored :archive:noexport:old:" + , "** Old stuff" + , " This is not going to be exported" + ] =?> (mempty::Blocks) , "Subtree with :noexport:" =: - unlines [ "* Exported" - , "** This isn't exported :noexport:" - , "*** This neither" - , "** But this is" - ] =?> + T.unlines [ "* Exported" + , "** This isn't exported :noexport:" + , "*** This neither" + , "** But this is" + ] =?> mconcat [ headerWith ("exported", [], []) 1 "Exported" , headerWith ("but-this-is", [], []) 2 "But this is" ] , "Preferences are treated as header attributes" =: - unlines [ "* foo" - , " :PROPERTIES:" - , " :custom_id: fubar" - , " :bar: baz" - , " :END:" - ] =?> + T.unlines [ "* foo" + , " :PROPERTIES:" + , " :custom_id: fubar" + , " :bar: baz" + , " :END:" + ] =?> headerWith ("fubar", [], [("bar", "baz")]) 1 "foo" , "Headers marked with a unnumbered property get a class of the same name" =: - unlines [ "* Not numbered" - , " :PROPERTIES:" - , " :UNNUMBERED: t" - , " :END:" - ] =?> + T.unlines [ "* Not numbered" + , " :PROPERTIES:" + , " :UNNUMBERED: t" + , " :END:" + ] =?> headerWith ("not-numbered", ["unnumbered"], []) 1 "Not numbered" ] , "Paragraph starting with an asterisk" =: @@ -985,23 +987,23 @@ tests = para "*five" , "Paragraph containing asterisk at beginning of line" =: - unlines [ "lucky" - , "*star" - ] =?> + T.unlines [ "lucky" + , "*star" + ] =?> para ("lucky" <> softbreak <> "*star") , "Example block" =: - unlines [ ": echo hello" - , ": echo dear tester" - ] =?> + T.unlines [ ": echo hello" + , ": echo dear tester" + ] =?> codeBlockWith ("", ["example"], []) "echo hello\necho dear tester\n" , "Example block surrounded by text" =: - unlines [ "Greetings" - , ": echo hello" - , ": echo dear tester" - , "Bye" - ] =?> + T.unlines [ "Greetings" + , ": echo hello" + , ": echo dear tester" + , "Bye" + ] =?> mconcat [ para "Greetings" , codeBlockWith ("", ["example"], []) "echo hello\necho dear tester\n" @@ -1009,10 +1011,10 @@ tests = ] , "Horizontal Rule" =: - unlines [ "before" - , "-----" - , "after" - ] =?> + T.unlines [ "before" + , "-----" + , "after" + ] =?> mconcat [ para "before" , horizontalRule , para "after" @@ -1023,67 +1025,67 @@ tests = para "\8212\8211 em and en dash" , "Comment Block" =: - unlines [ "#+BEGIN_COMMENT" - , "stuff" - , "bla" - , "#+END_COMMENT"] =?> + T.unlines [ "#+BEGIN_COMMENT" + , "stuff" + , "bla" + , "#+END_COMMENT"] =?> (mempty::Blocks) , testGroup "Figures" $ [ "Figure" =: - unlines [ "#+caption: A very courageous man." - , "#+name: goodguy" - , "[[file:edward.jpg]]" - ] =?> + T.unlines [ "#+caption: A very courageous man." + , "#+name: goodguy" + , "[[file:edward.jpg]]" + ] =?> para (image "edward.jpg" "fig:goodguy" "A very courageous man.") , "Figure with no name" =: - unlines [ "#+caption: I've been through the desert on this" - , "[[file:horse.png]]" - ] =?> + T.unlines [ "#+caption: I've been through the desert on this" + , "[[file:horse.png]]" + ] =?> para (image "horse.png" "fig:" "I've been through the desert on this") , "Figure with `fig:` prefix in name" =: - unlines [ "#+caption: Used as a metapher in evolutionary biology." - , "#+name: fig:redqueen" - , "[[./the-red-queen.jpg]]" - ] =?> + T.unlines [ "#+caption: Used as a metapher in evolutionary biology." + , "#+name: fig:redqueen" + , "[[./the-red-queen.jpg]]" + ] =?> para (image "./the-red-queen.jpg" "fig:redqueen" "Used as a metapher in evolutionary biology.") , "Figure with HTML attributes" =: - unlines [ "#+CAPTION: mah brain just explodid" - , "#+NAME: lambdacat" - , "#+ATTR_HTML: :style color: blue :role button" - , "[[file:lambdacat.jpg]]" - ] =?> + T.unlines [ "#+CAPTION: mah brain just explodid" + , "#+NAME: lambdacat" + , "#+ATTR_HTML: :style color: blue :role button" + , "[[file:lambdacat.jpg]]" + ] =?> let kv = [("style", "color: blue"), ("role", "button")] name = "fig:lambdacat" caption = "mah brain just explodid" in para (imageWith (mempty, mempty, kv) "lambdacat.jpg" name caption) , "Labelled figure" =: - unlines [ "#+CAPTION: My figure" - , "#+LABEL: fig:myfig" - , "[[file:blub.png]]" - ] =?> + T.unlines [ "#+CAPTION: My figure" + , "#+LABEL: fig:myfig" + , "[[file:blub.png]]" + ] =?> let attr = ("fig:myfig", mempty, mempty) in para (imageWith attr "blub.png" "fig:" "My figure") , "Figure with empty caption" =: - unlines [ "#+CAPTION:" - , "[[file:guess.jpg]]" - ] =?> + T.unlines [ "#+CAPTION:" + , "[[file:guess.jpg]]" + ] =?> para (image "guess.jpg" "fig:" "") ] , "Footnote" =: - unlines [ "A footnote[1]" - , "" - , "[1] First paragraph" - , "" - , "second paragraph" - ] =?> + T.unlines [ "A footnote[1]" + , "" + , "[1] First paragraph" + , "" + , "second paragraph" + ] =?> para (mconcat [ "A", space, "footnote" , note $ mconcat [ para ("First" <> space <> "paragraph") @@ -1092,12 +1094,12 @@ tests = ]) , "Two footnotes" =: - unlines [ "Footnotes[fn:1][fn:2]" - , "" - , "[fn:1] First note." - , "" - , "[fn:2] Second note." - ] =?> + T.unlines [ "Footnotes[fn:1][fn:2]" + , "" + , "[fn:1] First note." + , "" + , "[fn:2] Second note." + ] =?> para (mconcat [ "Footnotes" , note $ para ("First" <> space <> "note.") @@ -1105,32 +1107,32 @@ tests = ]) , "Emphasized text before footnote" =: - unlines [ "/text/[fn:1]" - , "" - , "[fn:1] unicorn" - ] =?> + T.unlines [ "/text/[fn:1]" + , "" + , "[fn:1] unicorn" + ] =?> para (mconcat [ emph "text" , note . para $ "unicorn" ]) , "Footnote that starts with emphasized text" =: - unlines [ "text[fn:1]" - , "" - , "[fn:1] /emphasized/" - ] =?> + T.unlines [ "text[fn:1]" + , "" + , "[fn:1] /emphasized/" + ] =?> para (mconcat [ "text" , note . para $ emph "emphasized" ]) , "Footnote followed by header" =: - unlines [ "Another note[fn:yay]" - , "" - , "[fn:yay] This is great!" - , "" - , "** Headline" - ] =?> + T.unlines [ "Another note[fn:yay]" + , "" + , "[fn:yay] This is great!" + , "" + , "** Headline" + ] =?> mconcat [ para (mconcat [ "Another", space, "note" @@ -1142,43 +1144,43 @@ tests = , testGroup "Lists" $ [ "Simple Bullet Lists" =: - ("- Item1\n" ++ + ("- Item1\n" <> "- Item2\n") =?> bulletList [ plain "Item1" , plain "Item2" ] , "Indented Bullet Lists" =: - (" - Item1\n" ++ + (" - Item1\n" <> " - Item2\n") =?> bulletList [ plain "Item1" , plain "Item2" ] , "Unindented *" =: - ("- Item1\n" ++ + ("- Item1\n" <> "* Item2\n") =?> bulletList [ plain "Item1" ] <> headerWith ("item2", [], []) 1 "Item2" , "Multi-line Bullet Lists" =: - ("- *Fat\n" ++ - " Tony*\n" ++ - "- /Sideshow\n" ++ + ("- *Fat\n" <> + " Tony*\n" <> + "- /Sideshow\n" <> " Bob/") =?> bulletList [ plain $ strong ("Fat" <> softbreak <> "Tony") , plain $ emph ("Sideshow" <> softbreak <> "Bob") ] , "Nested Bullet Lists" =: - ("- Discovery\n" ++ - " + One More Time\n" ++ - " + Harder, Better, Faster, Stronger\n" ++ - "- Homework\n" ++ - " + Around the World\n"++ - "- Human After All\n" ++ - " + Technologic\n" ++ + ("- Discovery\n" <> + " + One More Time\n" <> + " + Harder, Better, Faster, Stronger\n" <> + "- Homework\n" <> + " + Around the World\n"<> + "- Human After All\n" <> + " + Technologic\n" <> " + Robot Rock\n") =?> bulletList [ mconcat [ plain "Discovery" @@ -1234,7 +1236,7 @@ tests = ] , "Simple Ordered List" =: - ("1. Item1\n" ++ + ("1. Item1\n" <> "2. Item2\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ plain "Item1" @@ -1243,7 +1245,7 @@ tests = in orderedListWith listStyle listStructure , "Simple Ordered List with Parens" =: - ("1) Item1\n" ++ + ("1) Item1\n" <> "2) Item2\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ plain "Item1" @@ -1252,7 +1254,7 @@ tests = in orderedListWith listStyle listStructure , "Indented Ordered List" =: - (" 1. Item1\n" ++ + (" 1. Item1\n" <> " 2. Item2\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ plain "Item1" @@ -1261,11 +1263,11 @@ tests = in orderedListWith listStyle listStructure , "Nested Ordered Lists" =: - ("1. One\n" ++ - " 1. One-One\n" ++ - " 2. One-Two\n" ++ - "2. Two\n" ++ - " 1. Two-One\n"++ + ("1. One\n" <> + " 1. One-One\n" <> + " 2. One-Two\n" <> + "2. Two\n" <> + " 1. Two-One\n"<> " 2. Two-Two\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ mconcat @@ -1284,25 +1286,25 @@ tests = in orderedListWith listStyle listStructure , "Ordered List in Bullet List" =: - ("- Emacs\n" ++ + ("- Emacs\n" <> " 1. Org\n") =?> bulletList [ (plain "Emacs") <> (orderedList [ plain "Org"]) ] , "Bullet List in Ordered List" =: - ("1. GNU\n" ++ + ("1. GNU\n" <> " - Freedom\n") =?> orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ] , "Definition List" =: - unlines [ "- PLL :: phase-locked loop" - , "- TTL ::" - , " transistor-transistor logic" - , "- PSK :: phase-shift keying" - , "" - , " a digital modulation scheme" - ] =?> + T.unlines [ "- PLL :: phase-locked loop" + , "- TTL ::" + , " transistor-transistor logic" + , "- PSK :: phase-shift keying" + , "" + , " a digital modulation scheme" + ] =?> definitionList [ ("PLL", [ plain $ "phase-locked" <> space <> "loop" ]) , ("TTL", [ plain $ "transistor-transistor" <> space <> "logic" ]) @@ -1317,11 +1319,11 @@ tests = " - Elijah Wood :: He plays Frodo" =?> definitionList [ ("Elijah" <> space <> "Wood", [plain $ "He" <> space <> "plays" <> space <> "Frodo"])] , "Compact definition list" =: - unlines [ "- ATP :: adenosine 5' triphosphate" - , "- DNA :: deoxyribonucleic acid" - , "- PCR :: polymerase chain reaction" - , "" - ] =?> + T.unlines [ "- ATP :: adenosine 5' triphosphate" + , "- DNA :: deoxyribonucleic acid" + , "- PCR :: polymerase chain reaction" + , "" + ] =?> definitionList [ ("ATP", [ plain $ spcSep [ "adenosine", "5'", "triphosphate" ] ]) , ("DNA", [ plain $ spcSep [ "deoxyribonucleic", "acid" ] ]) @@ -1343,21 +1345,21 @@ tests = bulletList [ plain "std::cout" ] , "Loose bullet list" =: - unlines [ "- apple" - , "" - , "- orange" - , "" - , "- peach" - ] =?> + T.unlines [ "- apple" + , "" + , "- orange" + , "" + , "- peach" + ] =?> bulletList [ para "apple" , para "orange" , para "peach" ] , "Recognize preceding paragraphs in non-list contexts" =: - unlines [ "CLOSED: [2015-10-19 Mon 15:03]" - , "- Note taken on [2015-10-19 Mon 13:24]" - ] =?> + T.unlines [ "CLOSED: [2015-10-19 Mon 15:03]" + , "- Note taken on [2015-10-19 Mon 13:24]" + ] =?> mconcat [ para "CLOSED: [2015-10-19 Mon 15:03]" , bulletList [ plain "Note taken on [2015-10-19 Mon 13:24]" ] ] @@ -1373,10 +1375,10 @@ tests = simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] , "Multi line table" =: - unlines [ "| One |" - , "| Two |" - , "| Three |" - ] =?> + T.unlines [ "| One |" + , "| Two |" + , "| Three |" + ] =?> simpleTable' 1 mempty [ [ plain "One" ] , [ plain "Two" ] @@ -1388,10 +1390,10 @@ tests = simpleTable' 1 mempty [[mempty]] , "Glider Table" =: - unlines [ "| 1 | 0 | 0 |" - , "| 0 | 1 | 1 |" - , "| 1 | 1 | 0 |" - ] =?> + T.unlines [ "| 1 | 0 | 0 |" + , "| 0 | 1 | 1 |" + , "| 1 | 1 | 0 |" + ] =?> simpleTable' 3 mempty [ [ plain "1", plain "0", plain "0" ] , [ plain "0", plain "1", plain "1" ] @@ -1399,42 +1401,42 @@ tests = ] , "Table between Paragraphs" =: - unlines [ "Before" - , "| One | Two |" - , "After" - ] =?> + T.unlines [ "Before" + , "| One | Two |" + , "After" + ] =?> mconcat [ para "Before" , simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] , para "After" ] , "Table with Header" =: - unlines [ "| Species | Status |" - , "|--------------+--------------|" - , "| cervisiae | domesticated |" - , "| paradoxus | wild |" - ] =?> + T.unlines [ "| Species | Status |" + , "|--------------+--------------|" + , "| cervisiae | domesticated |" + , "| paradoxus | wild |" + ] =?> simpleTable [ plain "Species", plain "Status" ] [ [ plain "cervisiae", plain "domesticated" ] , [ plain "paradoxus", plain "wild" ] ] , "Table with final hline" =: - unlines [ "| cervisiae | domesticated |" - , "| paradoxus | wild |" - , "|--------------+--------------|" - ] =?> + T.unlines [ "| cervisiae | domesticated |" + , "| paradoxus | wild |" + , "|--------------+--------------|" + ] =?> simpleTable' 2 mempty [ [ plain "cervisiae", plain "domesticated" ] , [ plain "paradoxus", plain "wild" ] ] , "Table in a box" =: - unlines [ "|---------|---------|" - , "| static | Haskell |" - , "| dynamic | Lisp |" - , "|---------+---------|" - ] =?> + T.unlines [ "|---------|---------|" + , "| static | Haskell |" + , "| dynamic | Lisp |" + , "|---------+---------|" + ] =?> simpleTable' 2 mempty [ [ plain "static", plain "Haskell" ] , [ plain "dynamic", plain "Lisp" ] @@ -1445,18 +1447,18 @@ tests = simpleTable' 3 mempty [[mempty, mempty, plain "c"]] , "Table with empty rows" =: - unlines [ "| first |" - , "| |" - , "| third |" - ] =?> + T.unlines [ "| first |" + , "| |" + , "| third |" + ] =?> simpleTable' 1 mempty [[plain "first"], [mempty], [plain "third"]] , "Table with alignment row" =: - unlines [ "| Numbers | Text | More |" - , "| | | |" - , "| 1 | One | foo |" - , "| 2 | Two | bar |" - ] =?> + T.unlines [ "| Numbers | Text | More |" + , "| | | |" + , "| 1 | One | foo |" + , "| 2 | Two | bar |" + ] =?> table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0]) [] [ [ plain "Numbers", plain "Text", plain "More" ] @@ -1473,12 +1475,12 @@ tests = simpleTable' 1 mempty [ [ plain "incomplete-but-valid" ] ] , "Table with differing row lengths" =: - unlines [ "| Numbers | Text " - , "|-" - , "| | |" - , "| 1 | One | foo |" - , "| 2" - ] =?> + T.unlines [ "| Numbers | Text " + , "|-" + , "| | |" + , "| 1 | One | foo |" + , "| 2" + ] =?> table "" (zip [AlignCenter, AlignRight] [0, 0]) [ plain "Numbers", plain "Text" ] [ [ plain "1" , plain "One" , plain "foo" ] @@ -1486,10 +1488,10 @@ tests = ] , "Table with caption" =: - unlines [ "#+CAPTION: Hitchhiker's Multiplication Table" - , "| x | 6 |" - , "| 9 | 42 |" - ] =?> + T.unlines [ "#+CAPTION: Hitchhiker's Multiplication Table" + , "| x | 6 |" + , "| 9 | 42 |" + ] =?> table "Hitchhiker's Multiplication Table" [(AlignDefault, 0), (AlignDefault, 0)] [] @@ -1500,59 +1502,59 @@ tests = , testGroup "Blocks and fragments" [ "Source block" =: - unlines [ " #+BEGIN_SRC haskell" - , " main = putStrLn greeting" - , " where greeting = \"moin\"" - , " #+END_SRC" ] =?> + T.unlines [ " #+BEGIN_SRC haskell" + , " main = putStrLn greeting" + , " where greeting = \"moin\"" + , " #+END_SRC" ] =?> let attr' = ("", ["haskell"], []) - code' = "main = putStrLn greeting\n" ++ + code' = "main = putStrLn greeting\n" <> " where greeting = \"moin\"\n" in codeBlockWith attr' code' , "Source block with indented code" =: - unlines [ " #+BEGIN_SRC haskell" - , " main = putStrLn greeting" - , " where greeting = \"moin\"" - , " #+END_SRC" ] =?> + T.unlines [ " #+BEGIN_SRC haskell" + , " main = putStrLn greeting" + , " where greeting = \"moin\"" + , " #+END_SRC" ] =?> let attr' = ("", ["haskell"], []) - code' = "main = putStrLn greeting\n" ++ + code' = "main = putStrLn greeting\n" <> " where greeting = \"moin\"\n" in codeBlockWith attr' code' , "Source block with tab-indented code" =: - unlines [ "\t#+BEGIN_SRC haskell" - , "\tmain = putStrLn greeting" - , "\t where greeting = \"moin\"" - , "\t#+END_SRC" ] =?> + T.unlines [ "\t#+BEGIN_SRC haskell" + , "\tmain = putStrLn greeting" + , "\t where greeting = \"moin\"" + , "\t#+END_SRC" ] =?> let attr' = ("", ["haskell"], []) - code' = "main = putStrLn greeting\n" ++ + code' = "main = putStrLn greeting\n" <> " where greeting = \"moin\"\n" in codeBlockWith attr' code' , "Empty source block" =: - unlines [ " #+BEGIN_SRC haskell" - , " #+END_SRC" ] =?> + T.unlines [ " #+BEGIN_SRC haskell" + , " #+END_SRC" ] =?> let attr' = ("", ["haskell"], []) code' = "" in codeBlockWith attr' code' , "Source block between paragraphs" =: - unlines [ "Low German greeting" - , " #+BEGIN_SRC haskell" - , " main = putStrLn greeting" - , " where greeting = \"Moin!\"" - , " #+END_SRC" ] =?> + T.unlines [ "Low German greeting" + , " #+BEGIN_SRC haskell" + , " main = putStrLn greeting" + , " where greeting = \"Moin!\"" + , " #+END_SRC" ] =?> let attr' = ("", ["haskell"], []) - code' = "main = putStrLn greeting\n" ++ + code' = "main = putStrLn greeting\n" <> " where greeting = \"Moin!\"\n" in mconcat [ para $ spcSep [ "Low", "German", "greeting" ] , codeBlockWith attr' code' ] , "Source block with babel arguments" =: - unlines [ "#+BEGIN_SRC emacs-lisp :exports both" - , "(progn (message \"Hello, World!\")" - , " (+ 23 42))" - , "#+END_SRC" ] =?> + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" ] =?> let classes = [ "commonlisp" ] -- as kate doesn't know emacs-lisp syntax params = [ ("data-org-language", "emacs-lisp") , ("exports", "both") @@ -1562,13 +1564,13 @@ tests = in codeBlockWith ("", classes, params) code' , "Source block with results and :exports both" =: - unlines [ "#+BEGIN_SRC emacs-lisp :exports both" - , "(progn (message \"Hello, World!\")" - , " (+ 23 42))" - , "#+END_SRC" - , "" - , "#+RESULTS:" - , ": 65"] =?> + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65"] =?> let classes = [ "commonlisp" ] params = [ ("data-org-language", "emacs-lisp") , ("exports", "both") @@ -1581,13 +1583,13 @@ tests = codeBlockWith ("", ["example"], []) results' , "Source block with results and :exports code" =: - unlines [ "#+BEGIN_SRC emacs-lisp :exports code" - , "(progn (message \"Hello, World!\")" - , " (+ 23 42))" - , "#+END_SRC" - , "" - , "#+RESULTS:" - , ": 65" ] =?> + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports code" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65" ] =?> let classes = [ "commonlisp" ] params = [ ("data-org-language", "emacs-lisp") , ("exports", "code") @@ -1597,87 +1599,87 @@ tests = in codeBlockWith ("", classes, params) code' , "Source block with results and :exports results" =: - unlines [ "#+BEGIN_SRC emacs-lisp :exports results" - , "(progn (message \"Hello, World!\")" - , " (+ 23 42))" - , "#+END_SRC" - , "" - , "#+RESULTS:" - , ": 65" ] =?> + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports results" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65" ] =?> let results' = "65\n" in codeBlockWith ("", ["example"], []) results' , "Source block with results and :exports none" =: - unlines [ "#+BEGIN_SRC emacs-lisp :exports none" - , "(progn (message \"Hello, World!\")" - , " (+ 23 42))" - , "#+END_SRC" - , "" - , "#+RESULTS:" - , ": 65" ] =?> + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports none" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65" ] =?> (mempty :: Blocks) , "Source block with toggling header arguments" =: - unlines [ "#+BEGIN_SRC sh :noeval" - , "echo $HOME" - , "#+END_SRC" - ] =?> + T.unlines [ "#+BEGIN_SRC sh :noeval" + , "echo $HOME" + , "#+END_SRC" + ] =?> let classes = [ "bash" ] params = [ ("data-org-language", "sh"), ("noeval", "yes") ] in codeBlockWith ("", classes, params) "echo $HOME\n" , "Source block with line number switch" =: - unlines [ "#+BEGIN_SRC sh -n 10" - , ":() { :|:& };:" - , "#+END_SRC" - ] =?> + T.unlines [ "#+BEGIN_SRC sh -n 10" + , ":() { :|:& };:" + , "#+END_SRC" + ] =?> let classes = [ "bash", "numberLines" ] params = [ ("data-org-language", "sh"), ("startFrom", "10") ] in codeBlockWith ("", classes, params) ":() { :|:& };:\n" , "Source block with multi-word parameter values" =: - unlines [ "#+BEGIN_SRC dot :cmdline -Kdot -Tpng " - , "digraph { id [label=\"ID\"] }" - , "#+END_SRC" - ] =?> + T.unlines [ "#+BEGIN_SRC dot :cmdline -Kdot -Tpng " + , "digraph { id [label=\"ID\"] }" + , "#+END_SRC" + ] =?> let classes = [ "dot" ] params = [ ("cmdline", "-Kdot -Tpng") ] in codeBlockWith ("", classes, params) "digraph { id [label=\"ID\"] }\n" , "Example block" =: - unlines [ "#+begin_example" - , "A chosen representation of" - , "a rule." - , "#+eND_exAMPle" - ] =?> + T.unlines [ "#+begin_example" + , "A chosen representation of" + , "a rule." + , "#+eND_exAMPle" + ] =?> codeBlockWith ("", ["example"], []) "A chosen representation of\na rule.\n" , "HTML block" =: - unlines [ "#+BEGIN_HTML" - , "" - , "#+END_HTML" - ] =?> + T.unlines [ "#+BEGIN_HTML" + , "" + , "#+END_HTML" + ] =?> rawBlock "html" "\n" , "Quote block" =: - unlines [ "#+BEGIN_QUOTE" - , "/Niemand/ hat die Absicht, eine Mauer zu errichten!" - , "#+END_QUOTE" - ] =?> + T.unlines [ "#+BEGIN_QUOTE" + , "/Niemand/ hat die Absicht, eine Mauer zu errichten!" + , "#+END_QUOTE" + ] =?> blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht," , "eine", "Mauer", "zu", "errichten!" ])) , "Verse block" =: - unlines [ "The first lines of Goethe's /Faust/:" - , "#+begin_verse" - , "Habe nun, ach! Philosophie," - , "Juristerei und Medizin," - , "Und leider auch Theologie!" - , "Durchaus studiert, mit heißem Bemühn." - , "#+end_verse" - ] =?> + T.unlines [ "The first lines of Goethe's /Faust/:" + , "#+begin_verse" + , "Habe nun, ach! Philosophie," + , "Juristerei und Medizin," + , "Und leider auch Theologie!" + , "Durchaus studiert, mit heißem Bemühn." + , "#+end_verse" + ] =?> mconcat [ para $ spcSep [ "The", "first", "lines", "of" , "Goethe's", emph "Faust" <> ":"] @@ -1690,27 +1692,27 @@ tests = ] , "Verse block with blank lines" =: - unlines [ "#+BEGIN_VERSE" - , "foo" - , "" - , "bar" - , "#+END_VERSE" - ] =?> + T.unlines [ "#+BEGIN_VERSE" + , "foo" + , "" + , "bar" + , "#+END_VERSE" + ] =?> lineBlock [ "foo", mempty, "bar" ] , "Verse block with varying indentation" =: - unlines [ "#+BEGIN_VERSE" - , " hello darkness" - , "my old friend" - , "#+END_VERSE" - ] =?> + T.unlines [ "#+BEGIN_VERSE" + , " hello darkness" + , "my old friend" + , "#+END_VERSE" + ] =?> lineBlock [ "\160\160hello darkness", "my old friend" ] , "Raw block LaTeX" =: - unlines [ "#+BEGIN_LaTeX" - , "The category $\\cat{Set}$ is adhesive." - , "#+END_LaTeX" - ] =?> + T.unlines [ "#+BEGIN_LaTeX" + , "The category $\\cat{Set}$ is adhesive." + , "#+END_LaTeX" + ] =?> rawBlock "latex" "The category $\\cat{Set}$ is adhesive.\n" , "Raw LaTeX line" =: @@ -1726,24 +1728,24 @@ tests = rawBlock "html" "" , "Export block HTML" =: - unlines [ "#+BEGIN_export html" - , "Hello, World!" - , "#+END_export" - ] =?> + T.unlines [ "#+BEGIN_export html" + , "Hello, World!" + , "#+END_export" + ] =?> rawBlock "html" "Hello, World!\n" , "LaTeX fragment" =: - unlines [ "\\begin{equation}" - , "X_i = \\begin{cases}" - , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\" - , " C_{\\alpha(i)} & \\text{otherwise}" - , " \\end{cases}" - , "\\end{equation}" - ] =?> + T.unlines [ "\\begin{equation}" + , "X_i = \\begin{cases}" + , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\" + , " C_{\\alpha(i)} & \\text{otherwise}" + , " \\end{cases}" + , "\\end{equation}" + ] =?> rawBlock "latex" (unlines [ "\\begin{equation}" , "X_i = \\begin{cases}" - , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" ++ + , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" <> " \\alpha(i)\\\\" , " C_{\\alpha(i)} & \\text{otherwise}" , " \\end{cases}" @@ -1751,13 +1753,13 @@ tests = ]) , "Code block with caption" =: - unlines [ "#+CAPTION: Functor laws in Haskell" - , "#+NAME: functor-laws" - , "#+BEGIN_SRC haskell" - , "fmap id = id" - , "fmap (p . q) = (fmap p) . (fmap q)" - , "#+END_SRC" - ] =?> + T.unlines [ "#+CAPTION: Functor laws in Haskell" + , "#+NAME: functor-laws" + , "#+BEGIN_SRC haskell" + , "fmap id = id" + , "fmap (p . q) = (fmap p) . (fmap q)" + , "#+END_SRC" + ] =?> divWith nullAttr (mappend @@ -1769,28 +1771,28 @@ tests = ]))) , "Convert blank lines in blocks to single newlines" =: - unlines [ "#+begin_html" - , "" - , "boring" - , "" - , "#+end_html" - ] =?> + T.unlines [ "#+begin_html" + , "" + , "boring" + , "" + , "#+end_html" + ] =?> rawBlock "html" "\nboring\n\n" , "Accept `ATTR_HTML` attributes for generic block" =: - unlines [ "#+ATTR_HTML: :title hello, world :id test :class fun code" - , "#+BEGIN_TEST" - , "nonsense" - , "#+END_TEST" - ] =?> + T.unlines [ "#+ATTR_HTML: :title hello, world :id test :class fun code" + , "#+BEGIN_TEST" + , "nonsense" + , "#+END_TEST" + ] =?> let attr = ("test", ["fun", "code", "TEST"], [("title", "hello, world")]) in divWith attr (para "nonsense") , "Non-letter chars in source block parameters" =: - unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich" - , "code body" - , "#+END_SRC" - ] =?> + T.unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich" + , "code body" + , "#+END_SRC" + ] =?> let params = [ ("data-org-language", "C") , ("tangle", "xxxx.c") , ("city", "Zürich") diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs index 7f67ee742..cbca1564f 100644 --- a/test/Tests/Readers/RST.hs +++ b/test/Tests/Readers/RST.hs @@ -2,25 +2,27 @@ {-# LANGUAGE ScopedTypeVariables #-} module Tests.Readers.RST (tests) where +import Data.Text (Text) +import qualified Data.Text as T import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder -rst :: String -> Pandoc +rst :: Text -> Pandoc rst = purely $ readRST def{ readerStandalone = True } infix 4 =: (=:) :: ToString c - => String -> (String, c) -> TestTree + => String -> (Text, c) -> TestTree (=:) = test rst tests :: [TestTree] tests = [ "line block with blank line" =: "| a\n|\n| b" =?> lineBlock [ "a", mempty, "\160b" ] , testGroup "field list" - [ "general" =: unlines + [ "general" =: T.unlines [ "para" , "" , ":Hostname: media08" @@ -44,7 +46,7 @@ tests = [ "line block with blank line" =: , (text "Parameter i", [para "integer"]) , (str "Final", [para "item\non two lines"]) ]) - , "metadata" =: unlines + , "metadata" =: T.unlines [ "=====" , "Title" , "=====" @@ -58,7 +60,7 @@ tests = [ "line block with blank line" =: $ setMeta "title" ("Title" :: Inlines) $ setMeta "subtitle" ("Subtitle" :: Inlines) $ doc mempty ) - , "with inline markup" =: unlines + , "with inline markup" =: T.unlines [ ":*Date*: today" , "" , ".." @@ -80,7 +82,7 @@ tests = [ "line block with blank line" =: ]) ] , "URLs with following punctuation" =: - ("http://google.com, http://yahoo.com; http://foo.bar.baz.\n" ++ + ("http://google.com, http://yahoo.com; http://foo.bar.baz.\n" <> "http://foo.bar/baz_(bam) (http://foo.bar)") =?> para (link "http://google.com" "" "http://google.com" <> ", " <> link "http://yahoo.com" "" "http://yahoo.com" <> "; " <> @@ -89,10 +91,10 @@ tests = [ "line block with blank line" =: link "http://foo.bar/baz_(bam)" "" "http://foo.bar/baz_(bam)" <> " (" <> link "http://foo.bar" "" "http://foo.bar" <> ")") , "Reference names with special characters" =: - ("A-1-B_2_C:3:D+4+E.5.F_\n\n" ++ + ("A-1-B_2_C:3:D+4+E.5.F_\n\n" <> ".. _A-1-B_2_C:3:D+4+E.5.F: https://example.com\n") =?> para (link "https://example.com" "" "A-1-B_2_C:3:D+4+E.5.F") - , "Code directive with class and number-lines" =: unlines + , "Code directive with class and number-lines" =: T.unlines [ ".. code::python" , " :number-lines: 34" , " :class: class1 class2 class3" @@ -107,7 +109,7 @@ tests = [ "line block with blank line" =: ) "def func(x):\n return y" ) - , "Code directive with number-lines, no line specified" =: unlines + , "Code directive with number-lines, no line specified" =: T.unlines [ ".. code::python" , " :number-lines: " , "" @@ -122,7 +124,7 @@ tests = [ "line block with blank line" =: "def func(x):\n return y" ) , testGroup "literal / line / code blocks" - [ "indented literal block" =: unlines + [ "indented literal block" =: T.unlines [ "::" , "" , " block quotes" @@ -163,7 +165,7 @@ tests = [ "line block with blank line" =: , "unknown role" =: ":unknown:`text`" =?> para (str "text") ] , testGroup "footnotes" - [ "remove space before note" =: unlines + [ "remove space before note" =: T.unlines [ "foo [1]_" , "" , ".. [1]" diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs index f6fa4f989..580815279 100644 --- a/test/Tests/Readers/Txt2Tags.hs +++ b/test/Tests/Readers/Txt2Tags.hs @@ -2,6 +2,8 @@ module Tests.Readers.Txt2Tags (tests) where import Data.List (intersperse) +import Data.Text (Text) +import qualified Data.Text as T import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -9,7 +11,7 @@ import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder import Text.Pandoc.Class -t2t :: String -> Pandoc +t2t :: Text -> Pandoc -- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def t2t = purely $ \s -> do putCommonState @@ -20,7 +22,7 @@ t2t = purely $ \s -> do infix 4 =: (=:) :: ToString c - => String -> (String, c) -> TestTree + => String -> (Text, c) -> TestTree (=:) = test t2t spcSep :: [Inlines] -> Inlines @@ -154,7 +156,7 @@ tests = "== header ==[lab/el]" =?> para (text "== header ==[lab/el]") , "Headers not preceded by a blank line" =: - unlines [ "++ eat dinner ++" + T.unlines [ "++ eat dinner ++" , "Spaghetti and meatballs tonight." , "== walk dog ==" ] =?> @@ -168,16 +170,16 @@ tests = para "=five" , "Paragraph containing asterisk at beginning of line" =: - unlines [ "lucky" + T.unlines [ "lucky" , "*star" ] =?> para ("lucky" <> softbreak <> "*star") , "Horizontal Rule" =: - unlines [ "before" - , replicate 20 '-' - , replicate 20 '=' - , replicate 20 '_' + T.unlines [ "before" + , T.replicate 20 "-" + , T.replicate 20 "=" + , T.replicate 20 "_" , "after" ] =?> mconcat [ para "before" @@ -188,7 +190,7 @@ tests = ] , "Comment Block" =: - unlines [ "%%%" + T.unlines [ "%%%" , "stuff" , "bla" , "%%%"] =?> @@ -199,14 +201,14 @@ tests = , testGroup "Lists" $ [ "Simple Bullet Lists" =: - ("- Item1\n" ++ + ("- Item1\n" <> "- Item2\n") =?> bulletList [ plain "Item1" , plain "Item2" ] , "Indented Bullet Lists" =: - (" - Item1\n" ++ + (" - Item1\n" <> " - Item2\n") =?> bulletList [ plain "Item1" , plain "Item2" @@ -215,13 +217,13 @@ tests = , "Nested Bullet Lists" =: - ("- Discovery\n" ++ - " + One More Time\n" ++ - " + Harder, Better, Faster, Stronger\n" ++ - "- Homework\n" ++ - " + Around the World\n"++ - "- Human After All\n" ++ - " + Technologic\n" ++ + ("- Discovery\n" <> + " + One More Time\n" <> + " + Harder, Better, Faster, Stronger\n" <> + "- Homework\n" <> + " + Around the World\n"<> + "- Human After All\n" <> + " + Technologic\n" <> " + Robot Rock\n") =?> bulletList [ mconcat [ plain "Discovery" @@ -250,7 +252,7 @@ tests = ] , "Simple Ordered List" =: - ("+ Item1\n" ++ + ("+ Item1\n" <> "+ Item2\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ plain "Item1" @@ -260,7 +262,7 @@ tests = , "Indented Ordered List" =: - (" + Item1\n" ++ + (" + Item1\n" <> " + Item2\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ plain "Item1" @@ -269,11 +271,11 @@ tests = in orderedListWith listStyle listStructure , "Nested Ordered Lists" =: - ("+ One\n" ++ - " + One-One\n" ++ - " + One-Two\n" ++ - "+ Two\n" ++ - " + Two-One\n"++ + ("+ One\n" <> + " + One-One\n" <> + " + One-Two\n" <> + "+ Two\n" <> + " + Two-One\n"<> " + Two-Two\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ mconcat @@ -292,19 +294,19 @@ tests = in orderedListWith listStyle listStructure , "Ordered List in Bullet List" =: - ("- Emacs\n" ++ + ("- Emacs\n" <> " + Org\n") =?> bulletList [ (plain "Emacs") <> (orderedList [ plain "Org"]) ] , "Bullet List in Ordered List" =: - ("+ GNU\n" ++ + ("+ GNU\n" <> " - Freedom\n") =?> orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ] , "Definition List" =: - unlines [ ": PLL" + T.unlines [ ": PLL" , " phase-locked loop" , ": TTL" , " transistor-transistor logic" @@ -318,7 +320,7 @@ tests = , "Loose bullet list" =: - unlines [ "- apple" + T.unlines [ "- apple" , "" , "- orange" , "" @@ -340,7 +342,7 @@ tests = simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] , "Multi line table" =: - unlines [ "| One |" + T.unlines [ "| One |" , "| Two |" , "| Three |" ] =?> @@ -355,7 +357,7 @@ tests = simpleTable' 1 mempty [[mempty]] , "Glider Table" =: - unlines [ "| 1 | 0 | 0 |" + T.unlines [ "| 1 | 0 | 0 |" , "| 0 | 1 | 1 |" , "| 1 | 1 | 0 |" ] =?> @@ -367,7 +369,7 @@ tests = , "Table with Header" =: - unlines [ "|| Species | Status |" + T.unlines [ "|| Species | Status |" , "| cervisiae | domesticated |" , "| paradoxus | wild |" ] =?> @@ -377,7 +379,7 @@ tests = ] , "Table alignment determined by spacing" =: - unlines [ "| Numbers | Text | More |" + T.unlines [ "| Numbers | Text | More |" , "| 1 | One | foo |" , "| 2 | Two | bar |" ] =?> @@ -394,7 +396,7 @@ tests = , "Table with differing row lengths" =: - unlines [ "|| Numbers | Text " + T.unlines [ "|| Numbers | Text " , "| 1 | One | foo |" , "| 2 " ] =?> @@ -408,23 +410,23 @@ tests = , testGroup "Blocks and fragments" [ "Source block" =: - unlines [ "```" + T.unlines [ "```" , "main = putStrLn greeting" , " where greeting = \"moin\"" , "```" ] =?> - let code' = "main = putStrLn greeting\n" ++ + let code' = "main = putStrLn greeting\n" <> " where greeting = \"moin\"\n" in codeBlock code' , "tagged block" =: - unlines [ "'''" + T.unlines [ "'''" , "" , "'''" ] =?> rawBlock "html" "\n" , "Quote block" =: - unlines ["\t//Niemand// hat die Absicht, eine Mauer zu errichten!" + T.unlines ["\t//Niemand// hat die Absicht, eine Mauer zu errichten!" ] =?> blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht," , "eine", "Mauer", "zu", "errichten!" diff --git a/test/Tests/Writers/Docx.hs b/test/Tests/Writers/Docx.hs index 2d7179199..215952893 100644 --- a/test/Tests/Writers/Docx.hs +++ b/test/Tests/Writers/Docx.hs @@ -10,6 +10,8 @@ import Text.Pandoc.Readers.Docx import Text.Pandoc.Readers.Native import Text.Pandoc.Writers.Docx import System.IO.Unsafe (unsafePerformIO) -- TODO temporary +import qualified Data.ByteString as BS +import qualified Text.Pandoc.UTF8 as UTF8 type Options = (WriterOptions, ReaderOptions) @@ -18,8 +20,8 @@ compareOutput :: Options -> FilePath -> IO (Pandoc, Pandoc) compareOutput opts nativeFileIn nativeFileOut = do - nf <- Prelude.readFile nativeFileIn - nf' <- Prelude.readFile nativeFileOut + nf <- UTF8.toText <$> BS.readFile nativeFileIn + nf' <- UTF8.toText <$> BS.readFile nativeFileOut let wopts = fst opts df <- runIOorExplode $ do d <- readNative def nf -- cgit v1.2.3