From d414b2543a1686007e84c54bc711dff969dfb569 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 12:49:25 +0200 Subject: Remove https flag. Supporting two completely different libraries for fetching from URLs makes it difficult to trap errors, because of different error types expected from the libraries. There's no clear reason not to build with these https-capable libraires. --- src/Text/Pandoc/Shared.hs | 21 --------------------- 1 file changed, 21 deletions(-) (limited to 'src/Text/Pandoc/Shared.hs') diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 8256d14c0..44a26509b 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -140,7 +140,6 @@ import Text.Pandoc.Data (dataFiles) #else import Paths_pandoc (getDataFileName) #endif -#ifdef HTTP_CLIENT import Network.HTTP.Client (httpLbs, responseBody, responseHeaders, Request(port,host,requestHeaders)) import Network.HTTP.Client (parseRequest) @@ -150,12 +149,6 @@ import Network.HTTP.Client.TLS (tlsManagerSettings) import System.Environment (getEnv) import Network.HTTP.Types.Header ( hContentType, hUserAgent) import Network (withSocketsDo) -#else -import Network.URI (parseURI) -import Network.HTTP (findHeader, rspBody, - RequestMethod(..), HeaderName(..), mkRequest) -import Network.Browser (browse, setAllowRedirects, setOutHandler, request) -#endif -- | Version number of pandoc library. pandocVersion :: String @@ -715,7 +708,6 @@ openURL u let mime = takeWhile (/=',') u'' contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u'' in return (decodeLenient contents, Just mime) -#ifdef HTTP_CLIENT | otherwise = withSocketsDo $ do let parseReq = parseRequest (proxy :: Either IOError String) <- @@ -738,19 +730,6 @@ openURL u resp <- newManager tlsManagerSettings >>= httpLbs req'' return (BS.concat $ toChunks $ responseBody resp, UTF8.toString `fmap` lookup hContentType (responseHeaders resp)) -#else - | otherwise = getBodyAndMimeType `fmap` browse - (do liftIO $ UTF8.hPutStrLn stderr $ "Fetching " ++ u ++ "..." - setOutHandler $ const (return ()) - setAllowRedirects True - request (getRequest' u')) - where getBodyAndMimeType (_, r) = (rspBody r, findHeader HdrContentType r) - getRequest' uriString = case parseURI uriString of - Nothing -> error ("Not a valid URL: " ++ - uriString) - Just v -> mkRequest GET v - u' = escapeURIString (/= '|') u -- pipes are rejected by Network.URI -#endif -- -- Error reporting -- cgit v1.2.3 From 99be906101f7852e84e5da9c3b66dd6d99f649da Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 13:11:04 +0200 Subject: Added PandocHttpException, trap exceptions in fetching from URLs. Closes #3646. --- src/Text/Pandoc/App.hs | 17 +++++++++++++---- src/Text/Pandoc/Class.hs | 5 ++++- src/Text/Pandoc/Error.hs | 4 ++++ src/Text/Pandoc/Shared.hs | 9 +++++---- 4 files changed, 26 insertions(+), 9 deletions(-) (limited to 'src/Text/Pandoc/Shared.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 2efa69944..a1691c5e2 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -376,7 +376,7 @@ convertWithOpts opts = do then 0 else optTabStop opts) - readSources :: (Functor m, MonadIO m) => [FilePath] -> m String + readSources :: [FilePath] -> PandocIO String readSources srcs = convertTabs . intercalate "\n" <$> mapM readSource srcs @@ -751,6 +751,11 @@ fillMedia sourceURL d = walkM handleImage d "replacing image with description" -- emit alt text return $ Span ("",["image"],[]) lab + PandocHttpError u er -> do + report $ CouldNotFetchResource u + (show er ++ "\rReplacing image with description.") + -- emit alt text + return $ Span ("",["image"],[]) lab _ -> throwError e) handleImage x = return x @@ -800,7 +805,7 @@ applyFilters mbDatadir filters args d = do expandedFilters <- mapM (expandFilterPath mbDatadir) filters foldrM ($) d $ map (flip externalFilter args) expandedFilters -readSource :: MonadIO m => FilePath -> m String +readSource :: FilePath -> PandocIO String readSource "-" = liftIO UTF8.getContents readSource src = case parseURI src of Just u | uriScheme u `elem` ["http:","https:"] -> @@ -809,8 +814,12 @@ readSource src = case parseURI src of liftIO $ UTF8.readFile (uriPath u) _ -> liftIO $ UTF8.readFile src -readURI :: MonadIO m => FilePath -> m String -readURI src = liftIO $ (UTF8.toString . fst) <$> openURL src +readURI :: FilePath -> PandocIO String +readURI src = do + res <- liftIO $ openURL src + case res of + Left e -> throwError $ PandocHttpError src e + Right (contents, _) -> return $ UTF8.toString contents readFile' :: MonadIO m => FilePath -> m B.ByteString readFile' "-" = liftIO B.getContents diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index ad9901125..939e0bd18 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -242,7 +242,10 @@ instance PandocMonad PandocIO where newUniqueHash = hashUnique <$> (liftIO IO.newUnique) openURL u = do report $ Fetching u - liftIOError IO.openURL u + res <- liftIO (IO.openURL u) + case res of + Right r -> return r + Left e -> throwError $ PandocHttpError u e readFileLazy s = liftIOError BL.readFile s readFileStrict s = liftIOError B.readFile s readDataFile mfp fname = liftIOError (IO.readDataFile mfp) fname diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index a6db5e047..9b3f1b902 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -42,10 +42,12 @@ import Text.Parsec.Pos hiding (Line) import qualified Text.Pandoc.UTF8 as UTF8 import System.Exit (exitWith, ExitCode(..)) import System.IO (stderr) +import Network.HTTP.Client (HttpException) type Input = String data PandocError = PandocIOError String IOError + | PandocHttpError String HttpException | PandocShouldNeverHappenError String | PandocSomeError String | PandocParseError String @@ -70,6 +72,8 @@ handleError (Right r) = return r handleError (Left e) = case e of PandocIOError _ err' -> ioError err' + PandocHttpError u err' -> err 61 $ + "Could not fetch " ++ u ++ "\n" ++ show err' PandocShouldNeverHappenError s -> err 62 s PandocSomeError s -> err 63 s PandocParseError s -> err 64 s diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 44a26509b..0ebaf0f89 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -141,7 +141,8 @@ import Text.Pandoc.Data (dataFiles) import Paths_pandoc (getDataFileName) #endif import Network.HTTP.Client (httpLbs, responseBody, responseHeaders, - Request(port,host,requestHeaders)) + Request(port,host,requestHeaders), + HttpException) import Network.HTTP.Client (parseRequest) import Network.HTTP.Client (newManager) import Network.HTTP.Client.Internal (addProxy) @@ -702,13 +703,13 @@ readDataFileUTF8 userDir fname = UTF8.toString `fmap` readDataFile userDir fname -- | Read from a URL and return raw data and maybe mime type. -openURL :: String -> IO (BS.ByteString, Maybe MimeType) +openURL :: String -> IO (Either HttpException (BS.ByteString, Maybe MimeType)) openURL u | Just u'' <- stripPrefix "data:" u = let mime = takeWhile (/=',') u'' contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u'' - in return (decodeLenient contents, Just mime) - | otherwise = withSocketsDo $ do + in return $ Right (decodeLenient contents, Just mime) + | otherwise = E.try $ withSocketsDo $ do let parseReq = parseRequest (proxy :: Either IOError String) <- tryIOError $ getEnv "http_proxy" -- cgit v1.2.3 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. --- COPYRIGHT | 11 ++++++----- MANUAL.txt | 2 +- README.md | 2 +- src/Text/Pandoc.hs | 4 ++-- src/Text/Pandoc/App.hs | 4 ++-- src/Text/Pandoc/Asciify.hs | 4 ++-- src/Text/Pandoc/Error.hs | 4 ++-- src/Text/Pandoc/Highlighting.hs | 4 ++-- src/Text/Pandoc/ImageSize.hs | 4 ++-- src/Text/Pandoc/Logging.hs | 2 +- src/Text/Pandoc/Lua/SharedInstances.hs | 2 +- src/Text/Pandoc/Lua/StackInstances.hs | 4 ++-- src/Text/Pandoc/Lua/Util.hs | 2 +- src/Text/Pandoc/MIME.hs | 4 ++-- src/Text/Pandoc/MediaBag.hs | 4 ++-- src/Text/Pandoc/Options.hs | 4 ++-- src/Text/Pandoc/PDF.hs | 4 ++-- src/Text/Pandoc/Parsing.hs | 4 ++-- src/Text/Pandoc/Pretty.hs | 4 ++-- src/Text/Pandoc/Process.hs | 4 ++-- src/Text/Pandoc/Readers/Docx.hs | 4 ++-- src/Text/Pandoc/Readers/Docx/Lists.hs | 4 ++-- src/Text/Pandoc/Readers/Docx/Parse.hs | 4 ++-- src/Text/Pandoc/Readers/HTML.hs | 4 ++-- src/Text/Pandoc/Readers/LaTeX.hs | 4 ++-- src/Text/Pandoc/Readers/Markdown.hs | 4 ++-- src/Text/Pandoc/Readers/MediaWiki.hs | 4 ++-- src/Text/Pandoc/Readers/Native.hs | 4 ++-- src/Text/Pandoc/Readers/Org.hs | 4 ++-- src/Text/Pandoc/Readers/Org/BlockStarts.hs | 4 ++-- src/Text/Pandoc/Readers/Org/ExportSettings.hs | 2 +- src/Text/Pandoc/Readers/Org/Inlines.hs | 4 ++-- src/Text/Pandoc/Readers/Org/ParserState.hs | 4 ++-- src/Text/Pandoc/Readers/Org/Parsing.hs | 4 ++-- src/Text/Pandoc/Readers/Org/Shared.hs | 4 ++-- src/Text/Pandoc/Readers/RST.hs | 4 ++-- src/Text/Pandoc/Readers/Textile.hs | 7 ++++--- src/Text/Pandoc/SelfContained.hs | 4 ++-- src/Text/Pandoc/Shared.hs | 4 ++-- src/Text/Pandoc/Slides.hs | 4 ++-- src/Text/Pandoc/Templates.hs | 4 ++-- src/Text/Pandoc/UTF8.hs | 4 ++-- src/Text/Pandoc/UUID.hs | 4 ++-- src/Text/Pandoc/Writers.hs | 4 ++-- src/Text/Pandoc/Writers/AsciiDoc.hs | 4 ++-- src/Text/Pandoc/Writers/ConTeXt.hs | 4 ++-- src/Text/Pandoc/Writers/Custom.hs | 4 ++-- src/Text/Pandoc/Writers/Docbook.hs | 4 ++-- src/Text/Pandoc/Writers/Docx.hs | 4 ++-- src/Text/Pandoc/Writers/DokuWiki.hs | 4 ++-- src/Text/Pandoc/Writers/EPUB.hs | 4 ++-- src/Text/Pandoc/Writers/FB2.hs | 4 ++-- src/Text/Pandoc/Writers/HTML.hs | 4 ++-- src/Text/Pandoc/Writers/Haddock.hs | 4 ++-- src/Text/Pandoc/Writers/ICML.hs | 2 +- src/Text/Pandoc/Writers/JATS.hs | 2 +- src/Text/Pandoc/Writers/LaTeX.hs | 4 ++-- src/Text/Pandoc/Writers/Man.hs | 4 ++-- src/Text/Pandoc/Writers/Markdown.hs | 4 ++-- src/Text/Pandoc/Writers/MediaWiki.hs | 4 ++-- src/Text/Pandoc/Writers/Ms.hs | 4 ++-- src/Text/Pandoc/Writers/Native.hs | 4 ++-- src/Text/Pandoc/Writers/ODT.hs | 4 ++-- src/Text/Pandoc/Writers/OPML.hs | 4 ++-- src/Text/Pandoc/Writers/OpenDocument.hs | 4 ++-- src/Text/Pandoc/Writers/Org.hs | 8 +++++--- src/Text/Pandoc/Writers/RST.hs | 4 ++-- src/Text/Pandoc/Writers/RTF.hs | 4 ++-- src/Text/Pandoc/Writers/Shared.hs | 4 ++-- src/Text/Pandoc/Writers/TEI.hs | 4 ++-- src/Text/Pandoc/Writers/Texinfo.hs | 6 ++++-- src/Text/Pandoc/Writers/Textile.hs | 4 ++-- src/Text/Pandoc/Writers/ZimWiki.hs | 5 +++-- src/Text/Pandoc/XML.hs | 4 ++-- 74 files changed, 152 insertions(+), 145 deletions(-) (limited to 'src/Text/Pandoc/Shared.hs') diff --git a/COPYRIGHT b/COPYRIGHT index 9d6a78da5..73fae62af 100644 --- a/COPYRIGHT +++ b/COPYRIGHT @@ -33,32 +33,33 @@ licenses. ---------------------------------------------------------------------- src/Text/Pandoc/Writers/Texinfo.hs -Copyright (C) 2008-2015 John MacFarlane and Peter Wang +Copyright (C) 2008-2017 John MacFarlane and Peter Wang Released under the GNU General Public License version 2 or later. ---------------------------------------------------------------------- src/Text/Pandoc/Writers/OpenDocument.hs -Copyright (C) 2008-2015 Andrea Rossato and John MacFarlane +Copyright (C) 2008-2017 Andrea Rossato and John MacFarlane Released under the GNU General Public License version 2 or later. ---------------------------------------------------------------------- src/Text/Pandoc/Writers/Org.hs -Copyright (C) 2010-2015 Puneeth Chaganti and John MacFarlane +Copyright (C) 2010-2017 Puneeth Chaganti, John MacFarlane, and + Albert Krewinkel Released under the GNU General Public License version 2 or later. ---------------------------------------------------------------------- src/Text/Pandoc/Readers/Textile.hs -Copyright (C) 2010-2015 Paul Rivier and John MacFarlane +Copyright (C) 2010-2017 Paul Rivier and John MacFarlane Released under the GNU General Public License version 2 or later. ---------------------------------------------------------------------- src/Text/Pandoc/Readers/Org.hs test/Tests/Readers/Org.hs -Copyright (C) 2014-2015 Albert Krewinkel +Copyright (C) 2014-2017 Albert Krewinkel Released under the GNU General Public License version 2 or later. diff --git a/MANUAL.txt b/MANUAL.txt index 032ab5972..fad4683d4 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -4148,7 +4148,7 @@ which you can modify according to your needs, do Authors ======= -© 2006-2016 John MacFarlane (jgm@berkeley.edu). Released under the +© 2006-2017 John MacFarlane (jgm@berkeley.edu). Released under the [GPL], version 2 or greater. This software carries no warranty of any kind. (See COPYRIGHT for full copyright and warranty notices.) diff --git a/README.md b/README.md index 590bddb5b..ebd5ba2e8 100644 --- a/README.md +++ b/README.md @@ -140,7 +140,7 @@ new issue. License ------- -© 2006-2016 John MacFarlane (jgm@berkeley.edu). Released under the +© 2006-2017 John MacFarlane (jgm@berkeley.edu). Released under the [GPL], version 2 or greater. This software carries no warranty of any kind. (See COPYRIGHT for full copyright and warranty notices.) diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 345ef3b18..8ee1adf13 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -2,7 +2,7 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index f340259f3..157100507 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -2,7 +2,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.App - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Asciify.hs b/src/Text/Pandoc/Asciify.hs index 411a112b2..7125e5bcd 100644 --- a/src/Text/Pandoc/Asciify.hs +++ b/src/Text/Pandoc/Asciify.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2013-2016 John MacFarlane +Copyright (C) 2013-2017 John MacFarlane 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.Asciify - Copyright : Copyright (C) 2013-2016 John MacFarlane + Copyright : Copyright (C) 2013-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index 9b3f1b902..077413056 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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.Error - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Highlighting.hs b/src/Text/Pandoc/Highlighting.hs index f249f96ad..183155d5b 100644 --- a/src/Text/Pandoc/Highlighting.hs +++ b/src/Text/Pandoc/Highlighting.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2008-2016 John MacFarlane +Copyright (C) 2008-2017 John MacFarlane 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.Highlighting - Copyright : Copyright (C) 2008-2016 John MacFarlane + Copyright : Copyright (C) 2008-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs index 8b2d577a9..a0800e499 100644 --- a/src/Text/Pandoc/ImageSize.hs +++ b/src/Text/Pandoc/ImageSize.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings, ScopedTypeVariables, CPP #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-} {- - Copyright (C) 2011-2016 John MacFarlane + Copyright (C) 2011-2017 John MacFarlane 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 @@ -20,7 +20,7 @@ {- | Module : Text.Pandoc.ImageSize -Copyright : Copyright (C) 2011-2016 John MacFarlane +Copyright : Copyright (C) 2011-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index 59b010034..2cca4b7d3 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Module : Text.Pandoc.Logging - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Lua/SharedInstances.hs b/src/Text/Pandoc/Lua/SharedInstances.hs index 3d2d29ebf..019a82446 100644 --- a/src/Text/Pandoc/Lua/SharedInstances.hs +++ b/src/Text/Pandoc/Lua/SharedInstances.hs @@ -1,5 +1,5 @@ {- -Copyright © 2012-2016 John MacFarlane +Copyright © 2012-2017 John MacFarlane 2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs index 03f6e06e2..cfc4389c2 100644 --- a/src/Text/Pandoc/Lua/StackInstances.hs +++ b/src/Text/Pandoc/Lua/StackInstances.hs @@ -1,5 +1,5 @@ {- -Copyright © 2012-2015 John MacFarlane +Copyright © 2012-2017 John MacFarlane 2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {-# OPTIONS_GHC -fno-warn-orphans #-} {- | Module : Text.Pandoc.Lua.StackInstances - Copyright : © 2012-2016 John MacFarlane + Copyright : © 2012-2017 John MacFarlane © 2017 Albert Krewinkel License : GNU GPL, version 2 or above diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs index f0b87c231..ff07ba7d7 100644 --- a/src/Text/Pandoc/Lua/Util.hs +++ b/src/Text/Pandoc/Lua/Util.hs @@ -1,5 +1,5 @@ {- -Copyright © 2012-2016 John MacFarlane +Copyright © 2012-2017 John MacFarlane 2017 Albert Krewinkel This program is free software; you can redistribute it and/or modify diff --git a/src/Text/Pandoc/MIME.hs b/src/Text/Pandoc/MIME.hs index 2e4a97b71..162112634 100644 --- a/src/Text/Pandoc/MIME.hs +++ b/src/Text/Pandoc/MIME.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2011-2016 John MacFarlane +Copyright (C) 2011-2017 John MacFarlane 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.MIME - Copyright : Copyright (C) 2011-2016 John MacFarlane + Copyright : Copyright (C) 2011-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/MediaBag.hs b/src/Text/Pandoc/MediaBag.hs index b865f97c2..980511acc 100644 --- a/src/Text/Pandoc/MediaBag.hs +++ b/src/Text/Pandoc/MediaBag.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {- -Copyright (C) 2014 John MacFarlane +Copyright (C) 2014-2015, 2017 John MacFarlane 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 @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.MediaBag - Copyright : Copyright (C) 2014 John MacFarlane + Copyright : Copyright (C) 2014-2015, 2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 0b09f0497..6757c6782 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {- -Copyright (C) 2012-2016 John MacFarlane +Copyright (C) 2012-2017 John MacFarlane 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 @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Options - Copyright : Copyright (C) 2012-2016 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 7097337e2..cc9b38f7f 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -2,7 +2,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2012-2016 John MacFarlane +Copyright (C) 2012-2017 John MacFarlane 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 @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.PDF - Copyright : Copyright (C) 2012-2016 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index fa3ff898e..e90f64c5b 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -7,7 +7,7 @@ , IncoherentInstances #-} {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -26,7 +26,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Parsing - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs index 32e60843c..a432949c8 100644 --- a/src/Text/Pandoc/Pretty.hs +++ b/src/Text/Pandoc/Pretty.hs @@ -1,7 +1,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {- -Copyright (C) 2010-2016 John MacFarlane +Copyright (C) 2010-2017 John MacFarlane 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 @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111(-1)307 USA {- | Module : Text.Pandoc.Pretty - Copyright : Copyright (C) 2010-2016 John MacFarlane + Copyright : Copyright (C) 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Process.hs b/src/Text/Pandoc/Process.hs index 1014f37dd..b2a0c17f1 100644 --- a/src/Text/Pandoc/Process.hs +++ b/src/Text/Pandoc/Process.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2013-2016 John MacFarlane +Copyright (C) 2013-2017 John MacFarlane 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.Process - Copyright : Copyright (C) 2013-2016 John MacFarlane + Copyright : Copyright (C) 2013-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index 683277993..2757314ab 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -3,7 +3,7 @@ {-# LANGUAGE PatternGuards #-} {- -Copyright (C) 2014-2016 Jesse Rosenthal +Copyright (C) 2014-2017 Jesse Rosenthal 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 @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Docx - Copyright : Copyright (C) 2014-2016 Jesse Rosenthal + Copyright : Copyright (C) 2014-2017 Jesse Rosenthal License : GNU GPL, version 2 or above Maintainer : Jesse Rosenthal diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs index 94b4d919a..8be2e1894 100644 --- a/src/Text/Pandoc/Readers/Docx/Lists.hs +++ b/src/Text/Pandoc/Readers/Docx/Lists.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2014-2016 Jesse Rosenthal +Copyright (C) 2014-2017 Jesse Rosenthal 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.Docx.Lists - Copyright : Copyright (C) 2014-2016 Jesse Rosenthal + Copyright : Copyright (C) 2014-2017 Jesse Rosenthal License : GNU GPL, version 2 or above Maintainer : Jesse Rosenthal diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index 0f23555f4..e6736100f 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -3,7 +3,7 @@ {-# LANGUAGE ViewPatterns #-} {- -Copyright (C) 2014-2016 Jesse Rosenthal +Copyright (C) 2014-2017 Jesse Rosenthal 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 @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Docx.Parse - Copyright : Copyright (C) 2014-2016 Jesse Rosenthal + Copyright : Copyright (C) 2014-2017 Jesse Rosenthal License : GNU GPL, version 2 or above Maintainer : Jesse Rosenthal diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 14b051539..650454ae6 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -1,7 +1,7 @@ {-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, ViewPatterns#-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.HTML - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index b13fc215b..9a887c40c 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.LaTeX - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 4ff5a1845..0c0d07140 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -2,7 +2,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Markdown - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index b35f39aad..c860a0cdf 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -3,7 +3,7 @@ {-# LANGUAGE TypeSynonymInstances #-} -- RelaxedPolyRec needed for inlinesBetween on GHC < 7 {- - Copyright (C) 2012-2015 John MacFarlane + Copyright (C) 2012-2017 John MacFarlane 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 @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.MediaWiki - Copyright : Copyright (C) 2012-2015 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs index 2e307fa4f..8f42a45de 100644 --- a/src/Text/Pandoc/Readers/Native.hs +++ b/src/Text/Pandoc/Readers/Native.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2011-2015 John MacFarlane +Copyright (C) 2011-2017 John MacFarlane 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.Native - Copyright : Copyright (C) 2011-2015 John MacFarlane + Copyright : Copyright (C) 2011-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane 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 diff --git a/src/Text/Pandoc/Readers/Org/BlockStarts.hs b/src/Text/Pandoc/Readers/Org/BlockStarts.hs index f05725f16..066bde9e0 100644 --- a/src/Text/Pandoc/Readers/Org/BlockStarts.hs +++ b/src/Text/Pandoc/Readers/Org/BlockStarts.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.Options - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Readers/Org/ExportSettings.hs b/src/Text/Pandoc/Readers/Org/ExportSettings.hs index 1d6fdd7e1..934191e71 100644 --- a/src/Text/Pandoc/Readers/Org/ExportSettings.hs +++ b/src/Text/Pandoc/Readers/Org/ExportSettings.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 diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index 5772e4157..800264db0 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -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 @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Org.Options - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index e47565814..f530d1d03 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -2,7 +2,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} {- -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 @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Org.Options - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs index aa3a08279..50f5ebae5 100644 --- a/src/Text/Pandoc/Readers/Org/Parsing.hs +++ b/src/Text/Pandoc/Readers/Org/Parsing.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.Options - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs index f89ce6732..95424319f 100644 --- a/src/Text/Pandoc/Readers/Org/Shared.hs +++ b/src/Text/Pandoc/Readers/Org/Shared.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -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 @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Org.Options - Copyright : Copyright (C) 2014-2016 Albert Krewinkel + Copyright : Copyright (C) 2014-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 628351f36..868bfafa4 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -2,7 +2,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.RST - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index 047aa061c..df057837f 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -1,6 +1,6 @@ {- -Copyright (C) 2010-2015 Paul Rivier | tr '*#' '.@' - and John MacFarlane +Copyright (C) 2010-2012 Paul Rivier | tr '*#' '.@' + 2010-2017 John MacFarlane 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,8 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Readers.Textile - Copyright : Copyright (C) 2010-2015 Paul Rivier and John MacFarlane + Copyright : Copyright (C) 2010-2012 Paul Rivier + 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : Paul Rivier diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index 6391ef0e0..c0a12adf2 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2011-2016 John MacFarlane +Copyright (C) 2011-2017 John MacFarlane 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.SelfContained - Copyright : Copyright (C) 2011-2016 John MacFarlane + Copyright : Copyright (C) 2011-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 0ebaf0f89..3a61656e5 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -2,7 +2,7 @@ FlexibleContexts, ScopedTypeVariables, PatternGuards, ViewPatterns #-} {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Shared - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Slides.hs b/src/Text/Pandoc/Slides.hs index b53e0eb6d..cd7695dbe 100644 --- a/src/Text/Pandoc/Slides.hs +++ b/src/Text/Pandoc/Slides.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2012-2016 John MacFarlane +Copyright (C) 2012-2017 John MacFarlane 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.Slides - Copyright : Copyright (C) 2012-2016 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs index 26aeb9a73..9b635a97b 100644 --- a/src/Text/Pandoc/Templates.hs +++ b/src/Text/Pandoc/Templates.hs @@ -3,7 +3,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeSynonymInstances #-} {- -Copyright (C) 2009-2016 John MacFarlane +Copyright (C) 2009-2017 John MacFarlane 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 @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Templates - Copyright : Copyright (C) 2009-2016 John MacFarlane + Copyright : Copyright (C) 2009-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs index d88a44948..e27a24e63 100644 --- a/src/Text/Pandoc/UTF8.hs +++ b/src/Text/Pandoc/UTF8.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2010-2016 John MacFarlane +Copyright (C) 2010-2017 John MacFarlane 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.UTF8 - Copyright : Copyright (C) 2010-2016 John MacFarlane + Copyright : Copyright (C) 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/UUID.hs b/src/Text/Pandoc/UUID.hs index 9446c4692..989dd20c6 100644 --- a/src/Text/Pandoc/UUID.hs +++ b/src/Text/Pandoc/UUID.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2010-2016 John MacFarlane +Copyright (C) 2010-2017 John MacFarlane 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.UUID - Copyright : Copyright (C) 2010-2016 John MacFarlane + Copyright : Copyright (C) 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs index 0181f41c9..62445c072 100644 --- a/src/Text/Pandoc/Writers.hs +++ b/src/Text/Pandoc/Writers.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index 20fa7c209..e0085fb1a 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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.AsciiDoc - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 57f920259..eef16d3da 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2007-2015 John MacFarlane +Copyright (C) 2007-2017 John MacFarlane 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.ConTeXt - Copyright : Copyright (C) 2007-2015 John MacFarlane + Copyright : Copyright (C) 2007-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index ce90e4834..b33acb17c 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -6,7 +6,7 @@ #else {-# LANGUAGE OverlappingInstances #-} #endif -{- Copyright (C) 2012-2015 John MacFarlane +{- Copyright (C) 2012-2017 John MacFarlane 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 @@ -25,7 +25,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Custom - Copyright : Copyright (C) 2012-2015 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index dce2cbd3e..1afdfc457 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Docbook - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 620f9060e..b58c983a1 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -4,7 +4,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ViewPatterns #-} {- -Copyright (C) 2012-2015 John MacFarlane +Copyright (C) 2012-2017 John MacFarlane 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 @@ -23,7 +23,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Docx - Copyright : Copyright (C) 2012-2015 John MacFarlane + Copyright : Copyright (C) 2012-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 5e29acbaf..81987dc44 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2008-2015 John MacFarlane +Copyright (C) 2008-2017 John MacFarlane 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.Writers.DokuWiki - Copyright : Copyright (C) 2008-2015 John MacFarlane + Copyright : Copyright (C) 2008-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : Clare Macrae diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 5b64564ce..c8d64cf0b 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -3,7 +3,7 @@ {-# LANGUAGE PatternGuards #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2010-2015 John MacFarlane +Copyright (C) 2010-2017 John MacFarlane 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 @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.EPUB - Copyright : Copyright (C) 2010-2015 John MacFarlane + Copyright : Copyright (C) 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index b8806a261..0926cc331 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -1,8 +1,8 @@ {-# LANGUAGE PatternGuards #-} {- -Copyright (c) 2011-2012, Sergey Astanin -All rights reserved. +Copyright (c) 2011-2012 Sergey Astanin + 2012-2017 John MacFarlane 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 diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 9f41f77d1..63e839684 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -3,7 +3,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ViewPatterns #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.HTML - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index eae1377cd..812b46c30 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -2,7 +2,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {- -Copyright (C) 2014 John MacFarlane +Copyright (C) 2014-2015, 2017 John MacFarlane 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 @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Haddock - Copyright : Copyright (C) 2014 John MacFarlane + Copyright : Copyright (C) 2014-2015,2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 4d9998665..2f7a4889f 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -4,7 +4,7 @@ {- | Module : Text.Pandoc.Writers.ICML - Copyright : Copyright (C) 2013-2016 github.com/mb21 + Copyright : Copyright (C) 2013-2017 github.com/mb21 License : GNU GPL, version 2 or above Stability : alpha diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index aca7dc969..0b5108a79 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 000f4f8fb..26508b7c3 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -2,7 +2,7 @@ {-# LANGUAGE PatternGuards #-} {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.LaTeX - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 1f3e17c16..f3d356de7 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2007-2015 John MacFarlane +Copyright (C) 2007-2017 John MacFarlane 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.Writers.Man - Copyright : Copyright (C) 2007-2015 John MacFarlane + Copyright : Copyright (C) 2007-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index e67dcef6c..37bb98f5f 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -3,7 +3,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Markdown - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index def245e38..439bbb2f9 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2008-2015 John MacFarlane +Copyright (C) 2008-2017 John MacFarlane 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.Writers.MediaWiki - Copyright : Copyright (C) 2008-2015 John MacFarlane + Copyright : Copyright (C) 2008-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 534f26a5a..5dd225e19 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2007-2015 John MacFarlane +Copyright (C) 2007-2017 John MacFarlane 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.Writers.Ms - Copyright : Copyright (C) 2007-2015 John MacFarlane + Copyright : Copyright (C) 2007-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs index b031a0231..653efb3ce 100644 --- a/src/Text/Pandoc/Writers/Native.hs +++ b/src/Text/Pandoc/Writers/Native.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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.Native - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 6c6f38dbe..68e68c659 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2008-2015 John MacFarlane +Copyright (C) 2008-2017 John MacFarlane 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.ODT - Copyright : Copyright (C) 2008-2015 John MacFarlane + Copyright : Copyright (C) 2008-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/OPML.hs b/src/Text/Pandoc/Writers/OPML.hs index 98510c40f..cdb6ab0d1 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 +Copyright (C) 2013-2017 John MacFarlane 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 diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 491069343..53c1d0c59 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -2,7 +2,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- -Copyright (C) 2008-2015 Andrea Rossato +Copyright (C) 2008-2017 Andrea Rossato and John MacFarlane. This program is free software; you can redistribute it and/or modify @@ -22,7 +22,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.OpenDocument - Copyright : Copyright (C) 2008-2015 Andrea Rossato and John MacFarlane + Copyright : Copyright (C) 2008-2017 Andrea Rossato and John MacFarlane License : GNU GPL, version 2 or above Maintainer : Andrea Rossato diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 46752c7ce..ef60e2f6c 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -1,8 +1,8 @@ {-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2010-2015 Puneeth Chaganti - Albert Krewinkel , - and John MacFarlane + 2010-2017 John MacFarlane + 2016-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 @@ -21,7 +21,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Org - Copyright : Copyright (C) 2010-2015 Puneeth Chaganti and John MacFarlane + Copyright : © 2010-2015 Puneeth Chaganti + 2010-2017 John MacFarlane + 2016-2017 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 24898d62e..d16f013c0 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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.RST - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 7aa2280dd..e9b29f97d 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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.RTF - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs index 615733a78..c33655522 100644 --- a/src/Text/Pandoc/Writers/Shared.hs +++ b/src/Text/Pandoc/Writers/Shared.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2013-2015 John MacFarlane +Copyright (C) 2013-2017 John MacFarlane 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.Shared - Copyright : Copyright (C) 2013-2015 John MacFarlane + Copyright : Copyright (C) 2013-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index 0e1a0526d..7da792c9e 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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 @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Docbook - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index da4f43ee5..9926daea1 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -1,6 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2008-2015 John MacFarlane and Peter Wang +Copyright (C) 2008-2017 John MacFarlane + 2012 Peter Wang 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 +20,8 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.Texinfo - Copyright : Copyright (C) 2008-2015 John MacFarlane and Peter Wang + Copyright : Copyright (C) 2008-2017 John MacFarlane + 2012 Peter Wang License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 0ecb746c3..d532f3ed3 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2010-2015 John MacFarlane +Copyright (C) 2010-2017 John MacFarlane 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.Writers.Textile - Copyright : Copyright (C) 2010-2015 John MacFarlane + Copyright : Copyright (C) 2010-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index da8b08de1..bc2cf8f3c 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -1,5 +1,6 @@ {- -Copyright (C) 2008-2015 John MacFarlane +Copyright (C) 2008-2017 John MacFarlane + 2017 Alex Ivkin 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 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.ZimWiki - Copyright : Copyright (C) 2008-2015 John MacFarlane, 2017 Alex Ivkin + Copyright : Copyright (C) 2008-2017 John MacFarlane, 2017 Alex Ivkin License : GNU GPL, version 2 or above Maintainer : Alex Ivkin diff --git a/src/Text/Pandoc/XML.hs b/src/Text/Pandoc/XML.hs index d7fdc4278..b6edd6be5 100644 --- a/src/Text/Pandoc/XML.hs +++ b/src/Text/Pandoc/XML.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2006-2016 John MacFarlane +Copyright (C) 2006-2017 John MacFarlane 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.XML - Copyright : Copyright (C) 2006-2016 John MacFarlane + Copyright : Copyright (C) 2006-2017 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane -- cgit v1.2.3 From 5debb0da0f94d1454d51cacede7c4844f01cc2f5 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Tue, 23 May 2017 09:48:11 +0200 Subject: Shared: Provide custom isURI that rejects unknown schemes [isURI] We also export the set of known `schemes`. The new function replaces the function of the same name from `Network.URI`, as the latter did not check whether a scheme is well-known. E.g. MediaWiki wikis frequently feature pages with names like `User:John`. These links were interpreted as URIs, thus turning internal links into global links. This is prevented by also checking whether the scheme of a URI is frequently used (i.e. is IANA registered or an otherwise well-known scheme). Fixes: #2713 Update set of well-known URIs from IANA list All official IANA schemes (as of 2017-05-22) are included in the set of known schemes. The four non-official schemes doi, isbn, javascript, and pmid are kept. --- src/Text/Pandoc/App.hs | 4 +-- src/Text/Pandoc/Parsing.hs | 27 +------------- src/Text/Pandoc/Readers/Txt2Tags.hs | 1 - src/Text/Pandoc/SelfContained.hs | 4 +-- src/Text/Pandoc/Shared.hs | 69 +++++++++++++++++++++++++++++++++++- src/Text/Pandoc/Writers/ConTeXt.hs | 2 +- src/Text/Pandoc/Writers/DokuWiki.hs | 3 +- src/Text/Pandoc/Writers/FB2.hs | 3 +- src/Text/Pandoc/Writers/Haddock.hs | 1 - src/Text/Pandoc/Writers/ICML.hs | 3 +- src/Text/Pandoc/Writers/LaTeX.hs | 2 +- src/Text/Pandoc/Writers/Markdown.hs | 1 - src/Text/Pandoc/Writers/MediaWiki.hs | 1 - src/Text/Pandoc/Writers/RST.hs | 1 - src/Text/Pandoc/Writers/Texinfo.hs | 2 +- src/Text/Pandoc/Writers/ZimWiki.hs | 5 ++- 16 files changed, 81 insertions(+), 48 deletions(-) (limited to 'src/Text/Pandoc/Shared.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 97954764a..845146f34 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -57,7 +57,7 @@ import Data.Maybe (fromMaybe, isJust, isNothing) import qualified Data.Text as T import Data.Yaml (decode) import qualified Data.Yaml as Yaml -import Network.URI (URI (..), isURI, parseURI) +import Network.URI (URI (..), parseURI) import Paths_pandoc (getDataDir) import Skylighting (Style, Syntax (..), defaultSyntaxMap, parseTheme) import Skylighting.Parser (missingIncludes, parseSyntaxDefinition, @@ -80,7 +80,7 @@ import Text.Pandoc.Lua ( runLuaFilter ) import Text.Pandoc.PDF (makePDF) import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.SelfContained (makeSelfContained, makeDataURI) -import Text.Pandoc.Shared (headerShift, openURL, readDataFile, +import Text.Pandoc.Shared (isURI, headerShift, openURL, readDataFile, readDataFileUTF8, safeRead, tabFilter) import qualified Text.Pandoc.UTF8 as UTF8 import Text.Pandoc.XML (toEntities) diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index e430c7cb5..c6be48d19 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -465,33 +465,8 @@ emailAddress = try $ toResult <$> mailbox <*> (char '@' *> domain) sepby1 p sep = (:) <$> p <*> (many (try $ sep >> p)) --- Schemes from http://www.iana.org/assignments/uri-schemes.html plus --- the unofficial schemes coap, doi, javascript, isbn, pmid -schemes :: [String] -schemes = ["coap","doi","javascript","aaa","aaas","about","acap","cap","cid", - "crid","data","dav","dict","dns","file","ftp","geo","go","gopher", - "h323","http","https","iax","icap","im","imap","info","ipp","iris", - "iris.beep","iris.xpc","iris.xpcs","iris.lwz","ldap","mailto","mid", - "msrp","msrps","mtqp","mupdate","news","nfs","ni","nih","nntp", - "opaquelocktoken","pop","pres","rtsp","service","session","shttp","sieve", - "sip","sips","sms","snmp","soap.beep","soap.beeps","tag","tel","telnet", - "tftp","thismessage","tn3270","tip","tv","urn","vemmi","ws","wss","xcon", - "xcon-userid","xmlrpc.beep","xmlrpc.beeps","xmpp","z39.50r","z39.50s", - "adiumxtra","afp","afs","aim","apt","attachment","aw","beshare","bitcoin", - "bolo","callto","chrome","chrome-extension","com-eventbrite-attendee", - "content", "cvs","dlna-playsingle","dlna-playcontainer","dtn","dvb", - "ed2k","facetime","feed","finger","fish","gg","git","gizmoproject", - "gtalk","hcp","icon","ipn","irc","irc6","ircs","itms","jar","jms", - "keyparc","lastfm","ldaps","magnet","maps","market","message","mms", - "ms-help","msnim","mumble","mvn","notes","oid","palm","paparazzi", - "platform","proxy","psyc","query","res","resource","rmi","rsync", - "rtmp","secondlife","sftp","sgn","skype","smb","soldat","spotify", - "ssh","steam","svn","teamspeak","things","udp","unreal","ut2004", - "ventrilo","view-source","webcal","wtai","wyciwyg","xfire","xri", - "ymsgr", "isbn", "pmid"] - uriScheme :: Stream s m Char => ParserT s st m String -uriScheme = oneOfStringsCI schemes +uriScheme = oneOfStringsCI (Set.toList schemes) -- | Parses a URI. Returns pair of original and URI-escaped version. uri :: Stream [Char] m Char => ParserT [Char] st m (String, String) diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index ba2b20083..05c6c9a69 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -42,7 +42,6 @@ import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (macro, space, spaces, uri) import Text.Pandoc.Shared (compactify, compactifyDL, escapeURI) ---import Network.URI (isURI) -- Not sure whether to use this function import Control.Monad (guard, void, when) import Control.Monad.Reader (Reader, asks, runReader) import Data.Default diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index f8ad43b1e..55df147b6 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -42,7 +42,7 @@ import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Lazy as L import Data.Char (isAlphaNum, isAscii, toLower) import Data.List (isPrefixOf) -import Network.URI (URI (..), escapeURIString, isURI, parseURI) +import Network.URI (URI (..), escapeURIString, parseURI) import System.FilePath (takeDirectory, takeExtension, ()) import Text.HTML.TagSoup import Text.Pandoc.Class (PandocMonad (..), fetchItem, report) @@ -50,7 +50,7 @@ import Text.Pandoc.Error import Text.Pandoc.Logging import Text.Pandoc.MIME (MimeType) import Text.Pandoc.Options (WriterOptions (..)) -import Text.Pandoc.Shared (renderTags', trim) +import Text.Pandoc.Shared (isURI, renderTags', trim) import Text.Pandoc.UTF8 (toString) import Text.Parsec (ParsecT, runParserT) import qualified Text.Parsec as P diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 3a61656e5..7a1e6f3e3 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -81,6 +81,9 @@ module Text.Pandoc.Shared ( openURL, collapseFilePath, filteredFilesFromArchive, + -- * URI handling + schemes, + isURI, -- * Error handling mapLeft, -- * for squashing blocks @@ -104,7 +107,7 @@ import Data.List ( find, stripPrefix, intercalate ) import Data.Maybe (mapMaybe) import Data.Version ( showVersion ) import qualified Data.Map as M -import Network.URI ( escapeURIString, unEscapeString ) +import Network.URI ( URI(uriScheme), escapeURIString, unEscapeString, parseURI ) import qualified Data.Set as Set import System.Directory import System.FilePath (splitDirectories, isPathSeparator) @@ -774,6 +777,70 @@ filteredFilesFromArchive zf f = fileAndBinary :: Archive -> FilePath -> Maybe (FilePath, BL.ByteString) fileAndBinary a fp = findEntryByPath fp a >>= \e -> Just (fp, fromEntry e) + +-- +-- IANA URIs +-- + +-- | Schemes from http://www.iana.org/assignments/uri-schemes.html plus +-- the unofficial schemes doi, javascript, isbn, pmid. +schemes :: Set.Set String +schemes = Set.fromList + -- Official IANA schemes + [ "aaa", "aaas", "about", "acap", "acct", "acr", "adiumxtra", "afp", "afs" + , "aim", "appdata", "apt", "attachment", "aw", "barion", "beshare", "bitcoin" + , "blob", "bolo", "browserext", "callto", "cap", "chrome", "chrome-extension" + , "cid", "coap", "coaps", "com-eventbrite-attendee", "content", "crid", "cvs" + , "data", "dav", "dict", "dis", "dlna-playcontainer", "dlna-playsingle" + , "dns", "dntp", "dtn", "dvb", "ed2k", "example", "facetime", "fax", "feed" + , "feedready", "file", "filesystem", "finger", "fish", "ftp", "geo", "gg" + , "git", "gizmoproject", "go", "gopher", "graph", "gtalk", "h323", "ham" + , "hcp", "http", "https", "hxxp", "hxxps", "hydrazone", "iax", "icap", "icon" + , "im", "imap", "info", "iotdisco", "ipn", "ipp", "ipps", "irc", "irc6" + , "ircs", "iris", "iris.beep", "iris.lwz", "iris.xpc", "iris.xpcs" + , "isostore", "itms", "jabber", "jar", "jms", "keyparc", "lastfm", "ldap" + , "ldaps", "lvlt", "magnet", "mailserver", "mailto", "maps", "market" + , "message", "mid", "mms", "modem", "mongodb", "moz", "ms-access" + , "ms-browser-extension", "ms-drive-to", "ms-enrollment", "ms-excel" + , "ms-gamebarservices", "ms-getoffice", "ms-help", "ms-infopath" + , "ms-media-stream-id", "ms-officeapp", "ms-project", "ms-powerpoint" + , "ms-publisher", "ms-search-repair", "ms-secondary-screen-controller" + , "ms-secondary-screen-setup", "ms-settings", "ms-settings-airplanemode" + , "ms-settings-bluetooth", "ms-settings-camera", "ms-settings-cellular" + , "ms-settings-cloudstorage", "ms-settings-connectabledevices" + , "ms-settings-displays-topology", "ms-settings-emailandaccounts" + , "ms-settings-language", "ms-settings-location", "ms-settings-lock" + , "ms-settings-nfctransactions", "ms-settings-notifications" + , "ms-settings-power", "ms-settings-privacy", "ms-settings-proximity" + , "ms-settings-screenrotation", "ms-settings-wifi", "ms-settings-workplace" + , "ms-spd", "ms-sttoverlay", "ms-transit-to", "ms-virtualtouchpad" + , "ms-visio", "ms-walk-to", "ms-whiteboard", "ms-whiteboard-cmd", "ms-word" + , "msnim", "msrp", "msrps", "mtqp", "mumble", "mupdate", "mvn", "news", "nfs" + , "ni", "nih", "nntp", "notes", "ocf", "oid", "onenote", "onenote-cmd" + , "opaquelocktoken", "pack", "palm", "paparazzi", "pkcs11", "platform", "pop" + , "pres", "prospero", "proxy", "pwid", "psyc", "qb", "query", "redis" + , "rediss", "reload", "res", "resource", "rmi", "rsync", "rtmfp", "rtmp" + , "rtsp", "rtsps", "rtspu", "secondlife", "service", "session", "sftp", "sgn" + , "shttp", "sieve", "sip", "sips", "skype", "smb", "sms", "smtp", "snews" + , "snmp", "soap.beep", "soap.beeps", "soldat", "spotify", "ssh", "steam" + , "stun", "stuns", "submit", "svn", "tag", "teamspeak", "tel", "teliaeid" + , "telnet", "tftp", "things", "thismessage", "tip", "tn3270", "tool", "turn" + , "turns", "tv", "udp", "unreal", "urn", "ut2004", "v-event", "vemmi" + , "ventrilo", "videotex", "vnc", "view-source", "wais", "webcal", "wpid" + , "ws", "wss", "wtai", "wyciwyg", "xcon", "xcon-userid", "xfire" + , "xmlrpc.beep", "xmlrpc.beeps", "xmpp", "xri", "ymsgr", "z39.50", "z39.50r" + , "z39.50s" + -- Inofficial schemes + , "doi", "isbn", "javascript", "pmid" + ] + +-- | Check if the string is a valid URL with a IANA or frequently used but +-- unofficial scheme (see @schemes@). +isURI :: String -> Bool +isURI = maybe False hasKnownScheme . parseURI + where + hasKnownScheme = (`Set.member` schemes) . filter (/= ':') . uriScheme + --- --- Squash blocks into inlines --- diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index eef16d3da..2d4502153 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -33,7 +33,7 @@ import Control.Monad.State import Data.Char (ord) import Data.List (intercalate, intersperse) import Data.Maybe (catMaybes) -import Network.URI (isURI, unEscapeString) +import Network.URI (unEscapeString) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 81987dc44..1d02a9c40 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -44,13 +44,12 @@ import Control.Monad.Reader (ReaderT, ask, local, runReaderT) import Control.Monad.State (StateT, evalStateT, gets, modify) import Data.Default (Default (..)) import Data.List (intercalate, intersect, isPrefixOf, transpose) -import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition import Text.Pandoc.ImageSize import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText)) -import Text.Pandoc.Shared (camelCaseToHyphenated, escapeURI, linesToPara, +import Text.Pandoc.Shared (camelCaseToHyphenated, escapeURI, isURI, linesToPara, removeFormatting, substitute, trimr) import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Writers.Shared (defField, metaToJSON) diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 0926cc331..d450513bc 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -46,7 +46,6 @@ import Data.Char (isAscii, isControl, isSpace, toLower) import Data.Either (lefts, rights) import Data.List (intercalate, intersperse, isPrefixOf, stripPrefix) import Network.HTTP (urlEncode) -import Network.URI (isURI) import Text.XML.Light import qualified Text.XML.Light as X import qualified Text.XML.Light.Cursor as XC @@ -57,7 +56,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Error import Text.Pandoc.Logging import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..), def) -import Text.Pandoc.Shared (capitalize, isHeaderBlock, linesToPara, +import Text.Pandoc.Shared (capitalize, isHeaderBlock, isURI, linesToPara, orderedListMarkers) -- | Data to be written at the end of the document: diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 812b46c30..cbbe5bdb4 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -36,7 +36,6 @@ module Text.Pandoc.Writers.Haddock (writeHaddock) where import Control.Monad.State import Data.Default import Data.List (intersperse, transpose) -import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition import Text.Pandoc.Logging diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 2f7a4889f..f36a32015 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -21,7 +21,6 @@ import Control.Monad.State import Data.List (intersperse, isInfixOf, isPrefixOf, stripPrefix) import qualified Data.Set as Set import Data.Text as Text (breakOnAll, pack) -import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P import Text.Pandoc.Definition @@ -29,7 +28,7 @@ import Text.Pandoc.ImageSize import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty -import Text.Pandoc.Shared (linesToPara, splitBy) +import Text.Pandoc.Shared (isURI, linesToPara, splitBy) import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Writers.Math (texMathToInlines) import Text.Pandoc.Writers.Shared diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 31c70e99d..2b3d7c878 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -43,7 +43,7 @@ import Data.List (foldl', intercalate, intersperse, isInfixOf, nub, nubBy, stripPrefix, (\\)) import Data.Maybe (catMaybes, fromMaybe, isJust) import qualified Data.Text as T -import Network.URI (isURI, unEscapeString) +import Network.URI (unEscapeString) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition import Text.Pandoc.Highlighting (formatLaTeXBlock, formatLaTeXInline, highlight, diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index b70716181..e858bc43f 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -49,7 +49,6 @@ import qualified Data.Text as T import qualified Data.Vector as V import Data.Yaml (Value (Array, Bool, Number, Object, String)) import Network.HTTP (urlEncode) -import Network.URI (isURI) import Text.HTML.TagSoup (Tag (..), isTagText, parseTags) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 439bbb2f9..aa5c3bc4f 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -34,7 +34,6 @@ import Control.Monad.Reader import Control.Monad.State import Data.List (intercalate) import qualified Data.Set as Set -import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 5dc2ba31a..b88fc2245 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -35,7 +35,6 @@ import Control.Monad.State import Data.Char (isSpace, toLower) import Data.List (isPrefixOf, stripPrefix) import Data.Maybe (fromMaybe) -import Network.URI (isURI) import qualified Text.Pandoc.Builder as B import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 9926daea1..710e1dea0 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -37,7 +37,7 @@ import Data.Char (chr, ord) import Data.List (maximumBy, transpose) import Data.Ord (comparing) import qualified Data.Set as Set -import Network.URI (isURI, unEscapeString) +import Network.URI (unEscapeString) import System.FilePath import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index bc2cf8f3c..4ab8bde30 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -38,14 +38,13 @@ import Data.Default (Default (..)) import Data.List (intercalate, isInfixOf, isPrefixOf, transpose) import qualified Data.Map as Map import Data.Text (breakOnAll, pack) -import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition import Text.Pandoc.ImageSize import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText)) -import Text.Pandoc.Shared (escapeURI, linesToPara, removeFormatting, substitute, - trimr) +import Text.Pandoc.Shared (isURI, escapeURI, linesToPara, removeFormatting, + substitute, trimr) import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Writers.Shared (defField, metaToJSON) -- cgit v1.2.3 From 66fa38ed1c27935fc57677d9c63ac9263958e3fd Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 23 May 2017 09:49:56 +0200 Subject: Shared.isURI: allow uppercase versions of known schemes. --- src/Text/Pandoc/Shared.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc/Shared.hs') diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 7a1e6f3e3..a6c6fb95f 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -839,7 +839,8 @@ schemes = Set.fromList isURI :: String -> Bool isURI = maybe False hasKnownScheme . parseURI where - hasKnownScheme = (`Set.member` schemes) . filter (/= ':') . uriScheme + hasKnownScheme = (`Set.member` schemes) . map toLower . + filter (/= ':') . uriScheme --- --- Squash blocks into inlines -- cgit v1.2.3 From 774075c3e22ab2ad35e2306a5b98e30da512b310 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 30 May 2017 10:22:48 +0200 Subject: Added eastAsianLineBreakFilter to Shared. This used to live in the Markdown reader. --- src/Text/Pandoc/Readers/Markdown.hs | 12 +----------- src/Text/Pandoc/Shared.hs | 12 ++++++++++++ 2 files changed, 13 insertions(+), 11 deletions(-) (limited to 'src/Text/Pandoc/Shared.hs') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 7e2bd5a4d..5694c4354 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -55,11 +55,9 @@ import qualified Text.Pandoc.Builder as B import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition import Text.Pandoc.Emoji (emojis) -import Text.Pandoc.Generic (bottomUp) import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (tableWith) -import Text.Pandoc.Pretty (charWidth) import Text.Pandoc.Readers.HTML (htmlInBalanced, htmlTag, isBlockTag, isCommentTag, isInlineTag, isTextTag) import Text.Pandoc.Readers.LaTeX (rawLaTeXBlock, rawLaTeXInline) @@ -375,15 +373,7 @@ parseMarkdown = do return $ Pandoc meta bs) st reportLogMessages (do guardEnabled Ext_east_asian_line_breaks - return $ bottomUp softBreakFilter doc) <|> return doc - -softBreakFilter :: [Inline] -> [Inline] -softBreakFilter (x:SoftBreak:y:zs) = - case (stringify x, stringify y) of - (xs@(_:_), (c:_)) - | charWidth (last xs) == 2 && charWidth c == 2 -> x:y:zs - _ -> x:SoftBreak:y:zs -softBreakFilter xs = xs + return $ eastAsianLineBreakFilter doc) <|> return doc referenceKey :: PandocMonad m => MarkdownParser m (F Blocks) referenceKey = try $ do diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index a6c6fb95f..ce2c4888a 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -70,6 +70,7 @@ module Text.Pandoc.Shared ( isTightList, addMetaField, makeMeta, + eastAsianLineBreakFilter, -- * TagSoup HTML handling renderTags', -- * File handling @@ -120,6 +121,7 @@ import qualified Control.Monad.State as S import qualified Control.Exception as E import Control.Monad (msum, unless, MonadPlus(..)) import Text.Pandoc.Pretty (charWidth) +import Text.Pandoc.Generic (bottomUp) import Text.Pandoc.Compat.Time import Data.Time.Clock.POSIX import System.IO.Error @@ -578,6 +580,16 @@ makeMeta title authors date = $ addMetaField "date" (B.fromList date) $ nullMeta +-- | Remove soft breaks between East Asian characters. +eastAsianLineBreakFilter :: Pandoc -> Pandoc +eastAsianLineBreakFilter = bottomUp go + where go (x:SoftBreak:y:zs) = + case (stringify x, stringify y) of + (xs@(_:_), (c:_)) + | charWidth (last xs) == 2 && charWidth c == 2 -> x:y:zs + _ -> x:SoftBreak:y:zs + go xs = xs + -- -- TagSoup HTML handling -- -- cgit v1.2.3 From 72b45f05ed361d9fd21c0b8625263cf69494fe7a Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 10 Jun 2017 15:22:25 +0200 Subject: Rewrote convertTabs to use Text not String. --- src/Text/Pandoc/Shared.hs | 28 +++++++++++----------------- 1 file changed, 11 insertions(+), 17 deletions(-) (limited to 'src/Text/Pandoc/Shared.hs') diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index ce2c4888a..9ee80827f 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -133,7 +133,7 @@ import qualified Data.ByteString as BS import qualified Data.ByteString.Char8 as B8 import Data.ByteString.Base64 (decodeLenient) import Data.Sequence (ViewR(..), ViewL(..), viewl, viewr) -import qualified Data.Text as T (toUpper, pack, unpack) +import qualified Data.Text as T import Data.ByteString.Lazy (toChunks, fromChunks) import qualified Data.ByteString.Lazy as BL import Paths_pandoc (version) @@ -279,26 +279,20 @@ escapeURI = escapeURIString (not . needsEscaping) where needsEscaping c = isSpace c || c `elem` ['<','>','|','"','{','}','[',']','^', '`'] - -- | Convert tabs to spaces and filter out DOS line endings. -- Tabs will be preserved if tab stop is set to 0. tabFilter :: Int -- ^ Tab stop - -> String -- ^ Input - -> String + -> T.Text -- ^ Input + -> T.Text tabFilter tabStop = - let go _ [] = "" - go _ ('\n':xs) = '\n' : go tabStop xs - go _ ('\r':'\n':xs) = '\n' : go tabStop xs - go _ ('\r':xs) = '\n' : go tabStop xs - go spsToNextStop ('\t':xs) = - if tabStop == 0 - then '\t' : go tabStop xs - else replicate spsToNextStop ' ' ++ go tabStop xs - go 1 (x:xs) = - x : go tabStop xs - go spsToNextStop (x:xs) = - x : go (spsToNextStop - 1) xs - in go tabStop + T.unlines . (if tabStop == 0 then id else map go) . T.lines + where go s = + let (s1, s2) = T.break (== '\t') s + in if T.null s2 + then s1 + else s1 <> T.replicate + (tabStop - (T.length s1 `mod` tabStop)) (T.pack " ") + <> go (T.drop 1 s2) -- -- Date/time -- cgit v1.2.3 From fa719d026464619dd51714620470998ab5d18e17 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 10 Jun 2017 23:39:49 +0200 Subject: Switched Writer types to use Text. * XML.toEntities: changed type to Text -> Text. * Shared.tabFilter -- fixed so it strips out CRs as before. * Modified writers to take Text. * Updated tests, benchmarks, trypandoc. [API change] Closes #3731. --- benchmark/benchmark-pandoc.hs | 10 +++---- benchmark/weigh-pandoc.hs | 8 +++--- src/Text/Pandoc/App.hs | 29 +++++++++++-------- src/Text/Pandoc/PDF.hs | 27 +++++++++--------- src/Text/Pandoc/Shared.hs | 4 +-- src/Text/Pandoc/Writers/AsciiDoc.hs | 11 +++++--- src/Text/Pandoc/Writers/CommonMark.hs | 13 ++++----- src/Text/Pandoc/Writers/ConTeXt.hs | 13 +++++---- src/Text/Pandoc/Writers/Custom.hs | 8 ++++-- src/Text/Pandoc/Writers/Docbook.hs | 14 +++++---- src/Text/Pandoc/Writers/DokuWiki.hs | 7 +++-- src/Text/Pandoc/Writers/EPUB.hs | 5 ++-- src/Text/Pandoc/Writers/FB2.hs | 7 +++-- src/Text/Pandoc/Writers/HTML.hs | 50 ++++++++++++++++++--------------- src/Text/Pandoc/Writers/Haddock.hs | 11 ++++---- src/Text/Pandoc/Writers/ICML.hs | 4 ++- src/Text/Pandoc/Writers/JATS.hs | 12 ++++---- src/Text/Pandoc/Writers/LaTeX.hs | 17 ++++++----- src/Text/Pandoc/Writers/Man.hs | 30 +++++++++++--------- src/Text/Pandoc/Writers/Markdown.hs | 23 ++++++++------- src/Text/Pandoc/Writers/MediaWiki.hs | 8 ++++-- src/Text/Pandoc/Writers/Ms.hs | 12 ++++---- src/Text/Pandoc/Writers/Muse.hs | 11 +++++--- src/Text/Pandoc/Writers/Native.hs | 3 +- src/Text/Pandoc/Writers/ODT.hs | 5 ++-- src/Text/Pandoc/Writers/OPML.hs | 15 ++++++---- src/Text/Pandoc/Writers/OpenDocument.hs | 10 ++++--- src/Text/Pandoc/Writers/Org.hs | 11 +++++--- src/Text/Pandoc/Writers/RST.hs | 13 +++++---- src/Text/Pandoc/Writers/RTF.hs | 7 +++-- src/Text/Pandoc/Writers/TEI.hs | 10 ++++--- src/Text/Pandoc/Writers/Texinfo.hs | 11 +++++--- src/Text/Pandoc/Writers/Textile.hs | 11 ++++---- src/Text/Pandoc/Writers/ZimWiki.hs | 8 +++--- src/Text/Pandoc/XML.hs | 11 ++++---- test/Tests/Helpers.hs | 7 +++-- test/Tests/Readers/Docx.hs | 3 +- test/Tests/Readers/LaTeX.hs | 2 +- test/Tests/Readers/Odt.hs | 4 ++- test/Tests/Writers/AsciiDoc.hs | 3 +- test/Tests/Writers/ConTeXt.hs | 5 ++-- test/Tests/Writers/Docbook.hs | 3 +- test/Tests/Writers/HTML.hs | 3 +- test/Tests/Writers/LaTeX.hs | 5 ++-- test/Tests/Writers/Markdown.hs | 5 ++-- test/Tests/Writers/Muse.hs | 3 +- test/Tests/Writers/Native.hs | 6 ++-- trypandoc/trypandoc.hs | 4 +-- 48 files changed, 292 insertions(+), 210 deletions(-) (limited to 'src/Text/Pandoc/Shared.hs') diff --git a/benchmark/benchmark-pandoc.hs b/benchmark/benchmark-pandoc.hs index be44c462f..fc1df1e9c 100644 --- a/benchmark/benchmark-pandoc.hs +++ b/benchmark/benchmark-pandoc.hs @@ -33,15 +33,15 @@ readerBench :: Pandoc -> Maybe Benchmark readerBench doc (name, reader) = case lookup name writers of - Just (StringWriter writer) -> - let inp = either (error . show) pack $ runPure + Just (TextWriter writer) -> + let inp = either (error . show) id $ runPure $ writer def{ writerWrapText = WrapAuto} doc in return $ bench (name ++ " reader") $ nf (reader def) inp _ -> trace ("\nCould not find writer for " ++ name ++ "\n") Nothing writerBench :: Pandoc - -> (String, WriterOptions -> Pandoc -> String) + -> (String, WriterOptions -> Pandoc -> Text) -> Benchmark writerBench doc (name, writer) = bench (name ++ " writer") $ nf (writer def{ writerWrapText = WrapAuto }) doc @@ -55,7 +55,7 @@ main = do [x] -> x == n (x:y:_) -> x == n && y == "reader" matchReader (_, _) = False - let matchWriter (n, StringWriter _) = + let matchWriter (n, TextWriter _) = case args of [] -> True [x] -> x == n @@ -81,7 +81,7 @@ main = do $ filter (\(n,_) -> n /="haddock") readers' let writers' = [(n, \o d -> either (error . show) id $ runPure $ setupFakeFiles >> w o d) - | (n, StringWriter w) <- matchedWriters] + | (n, TextWriter w) <- matchedWriters] let writerBs = map (writerBench doc) $ writers' defaultMainWith defaultConfig{ timeLimit = 6.0 } diff --git a/benchmark/weigh-pandoc.hs b/benchmark/weigh-pandoc.hs index 35296f925..d3cada8c0 100644 --- a/benchmark/weigh-pandoc.hs +++ b/benchmark/weigh-pandoc.hs @@ -1,6 +1,6 @@ import Weigh import Text.Pandoc -import Data.Text (Text, pack) +import Data.Text (Text) main :: IO () main = do @@ -24,14 +24,14 @@ main = do ,("commonmark", writeCommonMark) ] -weighWriter :: Pandoc -> String -> (Pandoc -> String) -> Weigh () +weighWriter :: Pandoc -> String -> (Pandoc -> Text) -> Weigh () weighWriter doc name writer = func (name ++ " writer") writer doc weighReader :: Pandoc -> String -> (Text -> Pandoc) -> Weigh () weighReader doc name reader = do case lookup name writers of - Just (StringWriter writer) -> - let inp = either (error . show) pack $ runPure $ writer def{ writerWrapText = WrapAuto} doc + Just (TextWriter writer) -> + let inp = either (error . show) id $ runPure $ writer def{ writerWrapText = WrapAuto} doc in func (name ++ " reader") reader inp _ -> return () -- no writer for reader diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index c39bda859..658266046 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -43,6 +43,7 @@ import qualified Control.Exception as E import Control.Monad import Control.Monad.Except (throwError) import Control.Monad.Trans +import Data.Monoid import Data.Aeson (FromJSON (..), ToJSON (..), defaultOptions, eitherDecode', encode, genericToEncoding) import qualified Data.ByteString as BS @@ -183,7 +184,7 @@ convertWithOpts opts = do -- disabling the custom writer for now writer <- if ".lua" `isSuffixOf` format -- note: use non-lowercased version writerName - then return (StringWriter + then return (TextWriter (\o d -> liftIO $ writeCustom writerName o d) :: Writer PandocIO) else case getWriter writerName of @@ -442,7 +443,7 @@ convertWithOpts opts = do case writer of ByteStringWriter f -> f writerOptions doc >>= writeFnBinary outputFile - StringWriter f + TextWriter f | pdfOutput -> do -- make sure writer is latex, beamer, context, html5 or ms unless (laTeXOutput || conTeXtOutput || html5Output || @@ -469,18 +470,23 @@ convertWithOpts opts = do | otherwise -> do let htmlFormat = format `elem` ["html","html4","html5","s5","slidy","slideous","dzslides","revealjs"] - selfcontain = if optSelfContained opts && htmlFormat - then makeSelfContained writerOptions - else return handleEntities = if (htmlFormat || format == "docbook4" || format == "docbook5" || format == "docbook") && optAscii opts then toEntities else id - output <- f writerOptions doc - selfcontain (output ++ ['\n' | not standalone]) >>= - writerFn eol outputFile . handleEntities + addNl = if standalone + then id + else (<> T.singleton '\n') + output <- (addNl . handleEntities) <$> f writerOptions doc + writerFn eol outputFile =<< + if optSelfContained opts && htmlFormat + -- TODO not maximally efficient; change type + -- of makeSelfContained so it works w/ Text + then T.pack <$> makeSelfContained writerOptions + (T.unpack output) + else return output type Transform = Pandoc -> Pandoc @@ -810,9 +816,10 @@ writeFnBinary :: MonadIO m => FilePath -> B.ByteString -> m () writeFnBinary "-" = liftIO . B.putStr writeFnBinary f = liftIO . B.writeFile (UTF8.encodePath f) -writerFn :: MonadIO m => IO.Newline -> FilePath -> String -> m () -writerFn eol "-" = liftIO . UTF8.putStrWith eol -writerFn eol f = liftIO . UTF8.writeFileWith eol f +writerFn :: MonadIO m => IO.Newline -> FilePath -> Text -> m () +-- TODO this implementation isn't maximally efficient: +writerFn eol "-" = liftIO . UTF8.putStrWith eol . T.unpack +writerFn eol f = liftIO . UTF8.writeFileWith eol f . T.unpack lookupHighlightStyle :: Maybe String -> IO (Maybe Style) lookupHighlightStyle Nothing = return Nothing diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index e8a826e4c..cd75d869d 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -36,12 +36,13 @@ import qualified Codec.Picture as JP import qualified Control.Exception as E import Control.Monad (unless, when) import Control.Monad.Trans (MonadIO (..)) +import qualified Data.Text as T +import Data.Text (Text) import qualified Data.ByteString as BS import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as B import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy.Char8 as BC -import Data.List (isInfixOf) import Data.Maybe (fromMaybe) import Data.Monoid ((<>)) import System.Directory @@ -74,7 +75,7 @@ changePathSeparators = intercalate "/" . splitDirectories makePDF :: String -- ^ pdf creator (pdflatex, lualatex, -- xelatex, context, wkhtmltopdf, pdfroff) - -> (WriterOptions -> Pandoc -> PandocIO String) -- ^ writer + -> (WriterOptions -> Pandoc -> PandocIO Text) -- ^ writer -> WriterOptions -- ^ options -> Verbosity -- ^ verbosity level -> MediaBag -- ^ media @@ -178,10 +179,10 @@ tex2pdf' :: Verbosity -- ^ Verbosity level -> [String] -- ^ Arguments to the latex-engine -> FilePath -- ^ temp directory for output -> String -- ^ tex program - -> String -- ^ tex source + -> Text -- ^ tex source -> IO (Either ByteString ByteString) tex2pdf' verbosity args tmpDir program source = do - let numruns = if "\\tableofcontents" `isInfixOf` source + let numruns = if "\\tableofcontents" `T.isInfixOf` source then 3 -- to get page numbers else 2 -- 1 run won't give you PDF bookmarks (exit, log', mbPdf) <- runTeXProgram verbosity program args 1 numruns tmpDir source @@ -223,11 +224,11 @@ extractConTeXtMsg log' = do -- contents of stdout, contents of produced PDF if any). Rerun -- a fixed number of times to resolve references. runTeXProgram :: Verbosity -> String -> [String] -> Int -> Int -> FilePath - -> String -> IO (ExitCode, ByteString, Maybe ByteString) + -> Text -> IO (ExitCode, ByteString, Maybe ByteString) runTeXProgram verbosity program args runNumber numRuns tmpDir source = do let file = tmpDir "input.tex" exists <- doesFileExist file - unless exists $ UTF8.writeFile file source + unless exists $ BS.writeFile file $ UTF8.fromText source #ifdef _WINDOWS -- note: we want / even on Windows, for TexLive let tmpDir' = changePathSeparators tmpDir @@ -276,7 +277,7 @@ runTeXProgram verbosity program args runNumber numRuns tmpDir source = do ms2pdf :: Verbosity -> [String] - -> String + -> Text -> IO (Either ByteString ByteString) ms2pdf verbosity args source = do env' <- getEnvironment @@ -288,10 +289,10 @@ ms2pdf verbosity args source = do mapM_ print env' putStr "\n" putStrLn $ "[makePDF] Contents:\n" - putStr source + putStr $ T.unpack source putStr "\n" (exit, out) <- pipeProcess (Just env') "pdfroff" args - (UTF8.fromStringLazy source) + (BL.fromStrict $ UTF8.fromText source) when (verbosity >= INFO) $ do B.hPutStr stdout out putStr "\n" @@ -301,12 +302,12 @@ ms2pdf verbosity args source = do html2pdf :: Verbosity -- ^ Verbosity level -> [String] -- ^ Args to wkhtmltopdf - -> String -- ^ HTML5 source + -> Text -- ^ HTML5 source -> IO (Either ByteString ByteString) html2pdf verbosity args source = do file <- withTempFile "." "html2pdf.html" $ \fp _ -> return fp pdfFile <- withTempFile "." "html2pdf.pdf" $ \fp _ -> return fp - UTF8.writeFile file source + BS.writeFile file $ UTF8.fromText source let programArgs = args ++ [file, pdfFile] env' <- getEnvironment when (verbosity >= INFO) $ do @@ -341,11 +342,11 @@ html2pdf verbosity args source = do context2pdf :: Verbosity -- ^ Verbosity level -> FilePath -- ^ temp directory for output - -> String -- ^ ConTeXt source + -> Text -- ^ ConTeXt source -> IO (Either ByteString ByteString) context2pdf verbosity tmpDir source = inDirectory tmpDir $ do let file = "input.tex" - UTF8.writeFile file source + BS.writeFile file $ UTF8.fromText source #ifdef _WINDOWS -- note: we want / even on Windows, for TexLive let tmpDir' = changePathSeparators tmpDir diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 9ee80827f..745e809d0 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -284,8 +284,8 @@ escapeURI = escapeURIString (not . needsEscaping) tabFilter :: Int -- ^ Tab stop -> T.Text -- ^ Input -> T.Text -tabFilter tabStop = - T.unlines . (if tabStop == 0 then id else map go) . T.lines +tabFilter tabStop = T.filter (/= '\r') . T.unlines . + (if tabStop == 0 then id else map go) . T.lines where go s = let (s1, s2) = T.break (== '\t') s in if T.null s2 diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index e0085fb1a..46dbe6eaf 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -43,6 +43,7 @@ import Data.Char (isPunctuation, isSpace) import Data.List (intercalate, intersperse, stripPrefix) import qualified Data.Map as M import Data.Maybe (fromMaybe) +import Data.Text (Text) import qualified Data.Text as T import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition @@ -62,7 +63,7 @@ data WriterState = WriterState { defListMarker :: String } -- | Convert Pandoc to AsciiDoc. -writeAsciiDoc :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeAsciiDoc :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeAsciiDoc opts document = evalStateT (pandocToAsciiDoc opts document) WriterState{ defListMarker = "::" @@ -74,16 +75,18 @@ writeAsciiDoc opts document = type ADW = StateT WriterState -- | Return asciidoc representation of document. -pandocToAsciiDoc :: PandocMonad m => WriterOptions -> Pandoc -> ADW m String +pandocToAsciiDoc :: PandocMonad m => WriterOptions -> Pandoc -> ADW m Text pandocToAsciiDoc opts (Pandoc meta blocks) = do let titleblock = not $ null (docTitle meta) && null (docAuthors meta) && null (docDate meta) let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing + let render' :: Doc -> Text + render' = render colwidth metadata <- metaToJSON opts - (fmap (render colwidth) . blockListToAsciiDoc opts) - (fmap (render colwidth) . inlineListToAsciiDoc opts) + (fmap render' . blockListToAsciiDoc opts) + (fmap render' . inlineListToAsciiDoc opts) meta let addTitleLine (String t) = String $ t <> "\n" <> T.replicate (T.length t) "=" diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index 5e0a06bf0..ed316ced9 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -34,6 +34,7 @@ module Text.Pandoc.Writers.CommonMark (writeCommonMark) where import CMark import Control.Monad.State (State, get, modify, runState) import Data.Foldable (foldrM) +import Data.Text (Text) import qualified Data.Text as T import Text.Pandoc.Class (PandocMonad) import Text.Pandoc.Definition @@ -45,7 +46,7 @@ import Text.Pandoc.Writers.HTML (writeHtml5String) import Text.Pandoc.Writers.Shared -- | Convert Pandoc to CommonMark. -writeCommonMark :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeCommonMark :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeCommonMark opts (Pandoc meta blocks) = do let (blocks', notes) = runState (walkM processNotes blocks) [] notes' = if null notes @@ -71,7 +72,7 @@ processNotes x = return x node :: NodeType -> [Node] -> Node node = Node Nothing -blocksToCommonMark :: PandocMonad m => WriterOptions -> [Block] -> m String +blocksToCommonMark :: PandocMonad m => WriterOptions -> [Block] -> m Text blocksToCommonMark opts bs = do let cmarkOpts = [optHardBreaks | isEnabled Ext_hard_line_breaks opts] colwidth = if writerWrapText opts == WrapAuto @@ -79,14 +80,12 @@ blocksToCommonMark opts bs = do else Nothing nodes <- blocksToNodes bs return $ - T.unpack $ nodeToCommonmark cmarkOpts colwidth $ node DOCUMENT nodes -inlinesToCommonMark :: PandocMonad m => WriterOptions -> [Inline] -> m String +inlinesToCommonMark :: PandocMonad m => WriterOptions -> [Inline] -> m Text inlinesToCommonMark opts ils = return $ - T.unpack $ nodeToCommonmark cmarkOpts colwidth - $ node PARAGRAPH (inlinesToNodes ils) + nodeToCommonmark cmarkOpts colwidth $ node PARAGRAPH (inlinesToNodes ils) where cmarkOpts = [optHardBreaks | isEnabled Ext_hard_line_breaks opts] colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts @@ -139,7 +138,7 @@ blockToNodes (DefinitionList items) ns = blockToNodes (BulletList items') ns Para term : concat xs blockToNodes t@(Table _ _ _ _ _) ns = do s <- writeHtml5String def $! Pandoc nullMeta [t] - return (node (HTML_BLOCK (T.pack $! s)) [] : ns) + return (node (HTML_BLOCK s) [] : ns) blockToNodes Null ns = return ns inlinesToNodes :: [Inline] -> [Node] diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 2d4502153..2da6a7f9a 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -33,6 +33,7 @@ import Control.Monad.State import Data.Char (ord) import Data.List (intercalate, intersperse) import Data.Maybe (catMaybes) +import Data.Text (Text) import Network.URI (unEscapeString) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging @@ -56,7 +57,7 @@ orderedListStyles :: [Char] orderedListStyles = cycle "narg" -- | Convert Pandoc to ConTeXt. -writeConTeXt :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeConTeXt :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeConTeXt options document = let defaultWriterState = WriterState { stNextRef = 1 , stOrderedListLevel = 0 @@ -66,17 +67,19 @@ writeConTeXt options document = type WM = StateT WriterState -pandocToConTeXt :: PandocMonad m => WriterOptions -> Pandoc -> WM m String +pandocToConTeXt :: PandocMonad m => WriterOptions -> Pandoc -> WM m Text pandocToConTeXt options (Pandoc meta blocks) = do let colwidth = if writerWrapText options == WrapAuto then Just $ writerColumns options else Nothing + let render' :: Doc -> Text + render' = render colwidth metadata <- metaToJSON options - (fmap (render colwidth) . blockListToConTeXt) - (fmap (render colwidth) . inlineListToConTeXt) + (fmap render' . blockListToConTeXt) + (fmap render' . inlineListToConTeXt) meta body <- mapM (elementToConTeXt options) $ hierarchicalize blocks - let main = (render colwidth . vcat) body + let main = (render' . vcat) body let layoutFromMargins = intercalate [','] $ catMaybes $ map (\(x,y) -> ((x ++ "=") ++) <$> getField y metadata) diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index b33acb17c..1314ef844 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -41,6 +41,7 @@ import Control.Monad (when) import Data.Char (toLower) import Data.List (intersperse) import qualified Data.Map as M +import Data.Text (Text, pack) import Data.Typeable import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8) import Scripting.Lua (LuaState, StackValue, callfunc) @@ -116,7 +117,7 @@ data PandocLuaException = PandocLuaException String instance Exception PandocLuaException -- | Convert Pandoc to custom markup. -writeCustom :: FilePath -> WriterOptions -> Pandoc -> IO String +writeCustom :: FilePath -> WriterOptions -> Pandoc -> IO Text writeCustom luaFile opts doc@(Pandoc meta _) = do luaScript <- UTF8.readFile luaFile enc <- getForeignEncoding @@ -139,8 +140,9 @@ writeCustom luaFile opts doc@(Pandoc meta _) = do setForeignEncoding enc let body = rendered case writerTemplate opts of - Nothing -> return body - Just tpl -> return $ renderTemplate' tpl $ setField "body" body context + Nothing -> return $ pack body + Just tpl -> return $ pack $ + renderTemplate' tpl $ setField "body" body context docToCustom :: LuaState -> WriterOptions -> Pandoc -> IO String docToCustom lua opts (Pandoc (Meta metamap) blocks) = do diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 1afdfc457..02ffbf831 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -32,6 +32,7 @@ Conversion of 'Pandoc' documents to Docbook XML. module Text.Pandoc.Writers.Docbook ( writeDocbook4, writeDocbook5 ) where import Control.Monad.Reader import Data.Char (toLower) +import Data.Text (Text) import Data.Generics (everywhere, mkT) import Data.List (intercalate, isPrefixOf, isSuffixOf, stripPrefix) import Data.Monoid (Any (..)) @@ -81,22 +82,23 @@ authorToDocbook opts name' = do in inTagsSimple "firstname" (text $ escapeStringForXML firstname) $$ inTagsSimple "surname" (text $ escapeStringForXML lastname) -writeDocbook4 :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeDocbook4 :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeDocbook4 opts d = runReaderT (writeDocbook opts d) DocBook4 -writeDocbook5 :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeDocbook5 :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeDocbook5 opts d = runReaderT (writeDocbook opts d) DocBook5 -- | Convert Pandoc document to string in Docbook format. -writeDocbook :: PandocMonad m => WriterOptions -> Pandoc -> DB m String +writeDocbook :: PandocMonad m => WriterOptions -> Pandoc -> DB m Text writeDocbook opts (Pandoc meta blocks) = do let elements = hierarchicalize blocks let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing - let render' = render colwidth + let render' :: Doc -> Text + render' = render colwidth let opts' = if (maybe False (("/book>" `isSuffixOf`) . trimr) (writerTemplate opts) && TopLevelDefault == writerTopLevelDivision opts) @@ -111,10 +113,10 @@ writeDocbook opts (Pandoc meta blocks) = do auths' <- mapM (authorToDocbook opts) $ docAuthors meta let meta' = B.setMeta "author" auths' meta metadata <- metaToJSON opts - (fmap (render colwidth . vcat) . + (fmap (render' . vcat) . (mapM (elementToDocbook opts' startLvl) . hierarchicalize)) - (fmap (render colwidth) . inlinesToDocbook opts') + (fmap render' . inlinesToDocbook opts') meta' main <- (render' . vcat) <$> (mapM (elementToDocbook opts' startLvl) elements) let context = defField "body" main diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 1d02a9c40..551a1b0b5 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -44,6 +44,7 @@ import Control.Monad.Reader (ReaderT, ask, local, runReaderT) import Control.Monad.State (StateT, evalStateT, gets, modify) import Data.Default (Default (..)) import Data.List (intercalate, intersect, isPrefixOf, transpose) +import Data.Text (Text, pack) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition @@ -75,7 +76,7 @@ instance Default WriterEnvironment where type DokuWiki m = ReaderT WriterEnvironment (StateT WriterState m) -- | Convert Pandoc to DokuWiki. -writeDokuWiki :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeDokuWiki :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeDokuWiki opts document = runDokuWiki (pandocToDokuWiki opts document) @@ -84,7 +85,7 @@ runDokuWiki = flip evalStateT def . flip runReaderT def -- | Return DokuWiki representation of document. pandocToDokuWiki :: PandocMonad m - => WriterOptions -> Pandoc -> DokuWiki m String + => WriterOptions -> Pandoc -> DokuWiki m Text pandocToDokuWiki opts (Pandoc meta blocks) = do metadata <- metaToJSON opts (fmap trimr . blockListToDokuWiki opts) @@ -96,7 +97,7 @@ pandocToDokuWiki opts (Pandoc meta blocks) = do then "" -- TODO Was "\n" Check whether I can really remove this: -- if it is definitely to do with footnotes, can remove this whole bit else "" - let main = body ++ notes + let main = pack $ body ++ notes let context = defField "body" main $ defField "toc" (writerTableOfContents opts) $ metadata diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index c8d64cf0b..d68283007 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -40,6 +40,7 @@ import Control.Monad.State (State, StateT, evalState, evalStateT, get, gets, lift, modify, put) import qualified Data.ByteString.Lazy as B import qualified Data.ByteString.Lazy.Char8 as B8 +import qualified Data.Text.Lazy as TL import Data.Char (isAlphaNum, isDigit, toLower) import Data.List (intercalate, isInfixOf, isPrefixOf) import qualified Data.Map as M @@ -373,8 +374,8 @@ pandocToEPUB :: PandocMonad m -> E m B.ByteString pandocToEPUB version opts doc@(Pandoc meta _) = do let epub3 = version == EPUB3 - let writeHtml o = fmap UTF8.fromStringLazy . - writeHtmlStringForEPUB version o + let writeHtml o = fmap (UTF8.fromTextLazy . TL.fromStrict) . + writeHtmlStringForEPUB version o epochtime <- floor <$> lift P.getPOSIXTime metadata <- getEPUBMetadata opts meta let mkEntry path content = toEntry path epochtime content diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index d450513bc..213756330 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -44,6 +44,7 @@ import Data.ByteString.Base64 (encode) import qualified Data.ByteString.Char8 as B8 import Data.Char (isAscii, isControl, isSpace, toLower) import Data.Either (lefts, rights) +import Data.Text (Text, pack) import Data.List (intercalate, intersperse, isPrefixOf, stripPrefix) import Network.HTTP (urlEncode) import Text.XML.Light @@ -86,13 +87,13 @@ instance Show ImageMode where writeFB2 :: PandocMonad m => WriterOptions -- ^ conversion options -> Pandoc -- ^ document to convert - -> m String -- ^ FictionBook2 document (not encoded yet) + -> m Text -- ^ FictionBook2 document (not encoded yet) writeFB2 opts doc = flip evalStateT newFB $ pandocToFB2 opts doc pandocToFB2 :: PandocMonad m => WriterOptions -> Pandoc - -> FBM m String + -> FBM m Text pandocToFB2 opts (Pandoc meta blocks) = do modify (\s -> s { writerOptions = opts }) desc <- description meta @@ -103,7 +104,7 @@ pandocToFB2 opts (Pandoc meta blocks) = do (imgs,missing) <- liftM imagesToFetch get >>= \s -> lift (fetchImages s) let body' = replaceImagesWithAlt missing body let fb2_xml = el "FictionBook" (fb2_attrs, [desc, body'] ++ notes ++ imgs) - return $ xml_head ++ (showContent fb2_xml) ++ "\n" + return $ pack $ xml_head ++ (showContent fb2_xml) ++ "\n" where xml_head = "\n" fb2_attrs = diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 2605a29aa..5ee8ab4ce 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -45,6 +45,8 @@ module Text.Pandoc.Writers.HTML ( ) where import Control.Monad.State import Data.Char (ord, toLower) +import Data.Text (Text) +import qualified Data.Text.Lazy as TL import Data.List (intersperse, isPrefixOf) import Data.Maybe (catMaybes, fromMaybe, isJust, isNothing) import Data.Monoid ((<>)) @@ -67,7 +69,7 @@ import Text.Pandoc.Writers.Shared import Text.Pandoc.XML (escapeStringForXML, fromEntities) #if MIN_VERSION_blaze_markup(0,6,3) #else -import Text.Blaze.Internal (preEscapedString) +import Text.Blaze.Internal (preEscapedString, preEscapedText) #endif #if MIN_VERSION_blaze_html(0,5,1) import qualified Text.Blaze.XHtml5 as H5 @@ -77,7 +79,7 @@ import qualified Text.Blaze.Html5 as H5 import Control.Monad.Except (throwError) import Data.Aeson (Value) import System.FilePath (takeExtension, takeBaseName) -import Text.Blaze.Html.Renderer.String (renderHtml) +import Text.Blaze.Html.Renderer.Text (renderHtml) import qualified Text.Blaze.XHtml1.Transitional as H import qualified Text.Blaze.XHtml1.Transitional.Attributes as A import Text.Pandoc.Class (PandocMonad, report) @@ -123,7 +125,7 @@ nl opts = if writerWrapText opts == WrapNone else preEscapedString "\n" -- | Convert Pandoc document to Html 5 string. -writeHtml5String :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeHtml5String :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeHtml5String = writeHtmlString' defaultWriterState{ stHtml5 = True } @@ -132,7 +134,7 @@ writeHtml5 :: PandocMonad m => WriterOptions -> Pandoc -> m Html writeHtml5 = writeHtml' defaultWriterState{ stHtml5 = True } -- | Convert Pandoc document to Html 4 string. -writeHtml4String :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeHtml4String :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeHtml4String = writeHtmlString' defaultWriterState{ stHtml5 = False } @@ -142,38 +144,39 @@ writeHtml4 = writeHtml' defaultWriterState{ stHtml5 = False } -- | Convert Pandoc document to Html appropriate for an epub version. writeHtmlStringForEPUB :: PandocMonad m - => EPUBVersion -> WriterOptions -> Pandoc -> m String -writeHtmlStringForEPUB version = writeHtmlString' + => EPUBVersion -> WriterOptions -> Pandoc + -> m Text +writeHtmlStringForEPUB version o = writeHtmlString' defaultWriterState{ stHtml5 = version == EPUB3, - stEPUBVersion = Just version } + stEPUBVersion = Just version } o -- | Convert Pandoc document to Reveal JS HTML slide show. writeRevealJs :: PandocMonad m - => WriterOptions -> Pandoc -> m String + => WriterOptions -> Pandoc -> m Text writeRevealJs = writeHtmlSlideShow' RevealJsSlides -- | Convert Pandoc document to S5 HTML slide show. writeS5 :: PandocMonad m - => WriterOptions -> Pandoc -> m String + => WriterOptions -> Pandoc -> m Text writeS5 = writeHtmlSlideShow' S5Slides -- | Convert Pandoc document to Slidy HTML slide show. writeSlidy :: PandocMonad m - => WriterOptions -> Pandoc -> m String + => WriterOptions -> Pandoc -> m Text writeSlidy = writeHtmlSlideShow' SlidySlides -- | Convert Pandoc document to Slideous HTML slide show. writeSlideous :: PandocMonad m - => WriterOptions -> Pandoc -> m String + => WriterOptions -> Pandoc -> m Text writeSlideous = writeHtmlSlideShow' SlideousSlides -- | Convert Pandoc document to DZSlides HTML slide show. writeDZSlides :: PandocMonad m - => WriterOptions -> Pandoc -> m String + => WriterOptions -> Pandoc -> m Text writeDZSlides = writeHtmlSlideShow' DZSlides writeHtmlSlideShow' :: PandocMonad m - => HTMLSlideVariant -> WriterOptions -> Pandoc -> m String + => HTMLSlideVariant -> WriterOptions -> Pandoc -> m Text writeHtmlSlideShow' variant = writeHtmlString' defaultWriterState{ stSlideVariant = variant , stHtml5 = case variant of @@ -185,12 +188,15 @@ writeHtmlSlideShow' variant = writeHtmlString' NoSlides -> False } +renderHtml' :: Html -> Text +renderHtml' = TL.toStrict . renderHtml + writeHtmlString' :: PandocMonad m - => WriterState -> WriterOptions -> Pandoc -> m String + => WriterState -> WriterOptions -> Pandoc -> m Text writeHtmlString' st opts d = do (body, context) <- evalStateT (pandocToHtml opts d) st case writerTemplate opts of - Nothing -> return $ renderHtml body + Nothing -> return $ renderHtml' body Just tpl -> do -- warn if empty lang when (isNothing (getField "lang" context :: Maybe String)) $ @@ -205,12 +211,12 @@ writeHtmlString' st opts d = do report $ NoTitleElement fallback return $ resetField "pagetitle" fallback context return $ renderTemplate' tpl $ - defField "body" (renderHtml body) context' + defField "body" (renderHtml' body) context' writeHtml' :: PandocMonad m => WriterState -> WriterOptions -> Pandoc -> m Html writeHtml' st opts d = do case writerTemplate opts of - Just _ -> preEscapedString <$> writeHtmlString' st opts d + Just _ -> preEscapedText <$> writeHtmlString' st opts d Nothing -> do (body, _) <- evalStateT (pandocToHtml opts d) st return body @@ -222,8 +228,8 @@ pandocToHtml :: PandocMonad m -> StateT WriterState m (Html, Value) pandocToHtml opts (Pandoc meta blocks) = do metadata <- metaToJSON opts - (fmap renderHtml . blockListToHtml opts) - (fmap renderHtml . inlineListToHtml opts) + (fmap renderHtml' . blockListToHtml opts) + (fmap renderHtml' . inlineListToHtml opts) meta let stringifyHTML = escapeStringForXML . stringify let authsMeta = map stringifyHTML $ docAuthors meta @@ -277,10 +283,10 @@ pandocToHtml opts (Pandoc meta blocks) = do Nothing -> id else id) $ (if stMath st - then defField "math" (renderHtml math) + then defField "math" (renderHtml' math) else id) $ defField "quotes" (stQuotes st) $ - maybe id (defField "toc" . renderHtml) toc $ + maybe id (defField "toc" . renderHtml') toc $ defField "author-meta" authsMeta $ maybe id (defField "date-meta") (normalizeDate dateMeta) $ defField "pagetitle" (stringifyHTML (docTitle meta)) $ @@ -463,7 +469,7 @@ parseMailto s = do obfuscateLink :: PandocMonad m => WriterOptions -> Attr -> Html -> String -> m Html obfuscateLink opts attr txt s | writerEmailObfuscation opts == NoObfuscation = return $ addAttrs opts attr $ H.a ! A.href (toValue s) $ txt -obfuscateLink opts attr (renderHtml -> txt) s = +obfuscateLink opts attr (TL.unpack . renderHtml -> txt) s = let meth = writerEmailObfuscation opts s' = map toLower (take 7 s) ++ drop 7 s in case parseMailto s' of diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index cbbe5bdb4..1ad9acd40 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -35,6 +35,7 @@ Haddock: module Text.Pandoc.Writers.Haddock (writeHaddock) where import Control.Monad.State import Data.Default +import Data.Text (Text) import Data.List (intersperse, transpose) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition @@ -52,14 +53,14 @@ instance Default WriterState where def = WriterState{ stNotes = [] } -- | Convert Pandoc to Haddock. -writeHaddock :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeHaddock :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeHaddock opts document = evalStateT (pandocToHaddock opts{ writerWrapText = writerWrapText opts } document) def -- | Return haddock representation of document. pandocToHaddock :: PandocMonad m - => WriterOptions -> Pandoc -> StateT WriterState m String + => WriterOptions -> Pandoc -> StateT WriterState m Text pandocToHaddock opts (Pandoc meta blocks) = do let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts @@ -67,13 +68,13 @@ pandocToHaddock opts (Pandoc meta blocks) = do body <- blockListToHaddock opts blocks st <- get notes' <- notesToHaddock opts (reverse $ stNotes st) - let render' :: Doc -> String + let render' :: Doc -> Text render' = render colwidth let main = render' $ body <> (if isEmpty notes' then empty else blankline <> notes') metadata <- metaToJSON opts - (fmap (render colwidth) . blockListToHaddock opts) - (fmap (render colwidth) . inlineListToHaddock opts) + (fmap render' . blockListToHaddock opts) + (fmap render' . inlineListToHaddock opts) meta let context = defField "body" main $ metadata diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index f36a32015..2884bc532 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -21,6 +21,7 @@ import Control.Monad.State import Data.List (intersperse, isInfixOf, isPrefixOf, stripPrefix) import qualified Data.Set as Set import Data.Text as Text (breakOnAll, pack) +import Data.Text (Text) import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P import Text.Pandoc.Definition @@ -127,11 +128,12 @@ footnoteName = "Footnote" citeName = "Cite" -- | Convert Pandoc document to string in ICML format. -writeICML :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeICML :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeICML opts (Pandoc meta blocks) = do let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing + render' :: Doc -> Text render' = render colwidth renderMeta f s = liftM (render' . fst) $ runStateT (f opts [] s) defaultWriterState metadata <- metaToJSON opts diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index 0b5108a79..1a8d80747 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -33,6 +33,7 @@ https://jats.nlm.nih.gov/publishing/tag-library/1.1d3/element/mml-math.html module Text.Pandoc.Writers.JATS ( writeJATS ) where import Control.Monad.Reader import Data.Char (toLower) +import Data.Text (Text) import Data.Generics (everywhere, mkT) import Data.List (intercalate, isSuffixOf, partition) import Data.Maybe (fromMaybe) @@ -81,12 +82,12 @@ authorToJATS opts name' = do in inTagsSimple "firstname" (text $ escapeStringForXML firstname) $$ inTagsSimple "surname" (text $ escapeStringForXML lastname) -writeJATS :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeJATS :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeJATS opts d = runReaderT (docToJATS opts d) JATS1_1 -- | Convert Pandoc document to string in JATS format. -docToJATS :: PandocMonad m => WriterOptions -> Pandoc -> DB m String +docToJATS :: PandocMonad m => WriterOptions -> Pandoc -> DB m Text docToJATS opts (Pandoc meta blocks) = do let isBackBlock (Div ("refs",_,_) _) = True isBackBlock _ = False @@ -96,7 +97,8 @@ docToJATS opts (Pandoc meta blocks) = do let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing - let render' = render colwidth + let render' :: Doc -> Text + render' = render colwidth let opts' = if (maybe False (("/book>" `isSuffixOf`) . trimr) (writerTemplate opts) && TopLevelDefault == writerTopLevelDivision opts) @@ -111,10 +113,10 @@ docToJATS opts (Pandoc meta blocks) = do auths' <- mapM (authorToJATS opts) $ docAuthors meta let meta' = B.setMeta "author" auths' meta metadata <- metaToJSON opts - (fmap (render colwidth . vcat) . + (fmap (render' . vcat) . (mapM (elementToJATS opts' startLvl) . hierarchicalize)) - (fmap (render colwidth) . inlinesToJATS opts') + (fmap render' . inlinesToJATS opts') meta' main <- (render' . vcat) <$> (mapM (elementToJATS opts' startLvl) elements) diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 2b3d7c878..80606d510 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -42,6 +42,7 @@ import Data.Char (isAlphaNum, isAscii, isDigit, isLetter, isPunctuation, ord, import Data.List (foldl', intercalate, intersperse, isInfixOf, nub, nubBy, stripPrefix, (\\)) import Data.Maybe (catMaybes, fromMaybe, isJust) +import Data.Text (Text) import qualified Data.Text as T import Network.URI (unEscapeString) import Text.Pandoc.Class (PandocMonad, report) @@ -114,13 +115,13 @@ startingState options = WriterState { , stEmptyLine = True } -- | Convert Pandoc to LaTeX. -writeLaTeX :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeLaTeX :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeLaTeX options document = evalStateT (pandocToLaTeX options document) $ startingState options -- | Convert Pandoc to LaTeX Beamer. -writeBeamer :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeBeamer :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeBeamer options document = evalStateT (pandocToLaTeX options document) $ (startingState options){ stBeamer = True } @@ -128,7 +129,7 @@ writeBeamer options document = type LW m = StateT WriterState m pandocToLaTeX :: PandocMonad m - => WriterOptions -> Pandoc -> LW m String + => WriterOptions -> Pandoc -> LW m Text pandocToLaTeX options (Pandoc meta blocks) = do -- Strip off final 'references' header if --natbib or --biblatex let method = writerCiteMethod options @@ -146,9 +147,11 @@ pandocToLaTeX options (Pandoc meta blocks) = do let colwidth = if writerWrapText options == WrapAuto then Just $ writerColumns options else Nothing + let render' :: Doc -> Text + render' = render colwidth metadata <- metaToJSON options - (fmap (render colwidth) . blockListToLaTeX) - (fmap (render colwidth) . inlineListToLaTeX) + (fmap render' . blockListToLaTeX) + (fmap render' . inlineListToLaTeX) meta let bookClasses = ["memoir","book","report","scrreprt","scrbook"] let documentClass = case P.parse pDocumentClass "template" template of @@ -180,8 +183,8 @@ pandocToLaTeX options (Pandoc meta blocks) = do then toSlides blocks'' else return blocks'' body <- mapM (elementToLaTeX options) $ hierarchicalize blocks''' - (biblioTitle :: String) <- liftM (render colwidth) $ inlineListToLaTeX lastHeader - let main = render colwidth $ vsep body + (biblioTitle :: Text) <- render' <$> inlineListToLaTeX lastHeader + let main = render' $ vsep body st <- get titleMeta <- stringToLaTeX TextString $ stringify $ docTitle meta authorsMeta <- mapM (stringToLaTeX TextString . stringify) $ docAuthors meta diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index f3d356de7..0fc6afbdc 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2007-2017 John MacFarlane @@ -34,6 +35,8 @@ import Control.Monad.State import Data.List (intercalate, intersperse, stripPrefix, sort) import qualified Data.Map as Map import Data.Maybe (fromMaybe) +import Data.Text (Text) +import qualified Data.Text as T import Text.Pandoc.Builder (deleteMeta) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition @@ -62,36 +65,37 @@ defaultWriterState = WriterState { stNotes = [] , stHasTables = False } -- | Convert Pandoc to Man. -writeMan :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeMan :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeMan opts document = evalStateT (pandocToMan opts document) defaultWriterState -- | Return groff man representation of document. -pandocToMan :: PandocMonad m => WriterOptions -> Pandoc -> StateT WriterState m String +pandocToMan :: PandocMonad m => WriterOptions -> Pandoc -> StateT WriterState m Text pandocToMan opts (Pandoc meta blocks) = do let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing - let render' = render colwidth + let render' :: Doc -> Text + render' = render colwidth titleText <- inlineListToMan opts $ docTitle meta let title' = render' titleText let setFieldsFromTitle = - case break (== ' ') title' of - (cmdName, rest) -> case break (=='(') cmdName of - (xs, '(':ys) | not (null ys) && - last ys == ')' -> + case T.break (== ' ') title' of + (cmdName, rest) -> case T.break (=='(') cmdName of + (xs, ys) | "(" `T.isPrefixOf` ys + && ")" `T.isSuffixOf` ys -> defField "title" xs . - defField "section" (init ys) . - case splitBy (=='|') rest of + defField "section" (T.init $ T.drop 1 ys) . + case T.splitOn "|" rest of (ft:hds) -> - defField "footer" (trim ft) . + defField "footer" (T.strip ft) . defField "header" - (trim $ concat hds) + (T.strip $ mconcat hds) [] -> id _ -> defField "title" title' metadata <- metaToJSON opts - (fmap (render colwidth) . blockListToMan opts) - (fmap (render colwidth) . inlineListToMan opts) + (fmap render' . blockListToMan opts) + (fmap render' . inlineListToMan opts) $ deleteMeta "title" meta body <- blockListToMan opts blocks notes <- gets stNotes diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 989d5af9d..69243a214 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -45,6 +45,7 @@ import Data.Maybe (fromMaybe) import Data.Monoid (Any (..)) import Data.Ord (comparing) import qualified Data.Set as Set +import Data.Text (Text) import qualified Data.Text as T import qualified Data.Vector as V import Data.Yaml (Value (Array, Bool, Number, Object, String)) @@ -106,7 +107,7 @@ instance Default WriterState } -- | Convert Pandoc to Markdown. -writeMarkdown :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeMarkdown :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeMarkdown opts document = evalMD (pandocToMarkdown opts{ writerWrapText = if isEnabled Ext_hard_line_breaks opts @@ -116,7 +117,7 @@ writeMarkdown opts document = -- | Convert Pandoc to plain text (like markdown, but without links, -- pictures, or inline formatting). -writePlain :: PandocMonad m => WriterOptions -> Pandoc -> m String +writePlain :: PandocMonad m => WriterOptions -> Pandoc -> m Text writePlain opts document = evalMD (pandocToMarkdown opts document) def{ envPlain = True } def @@ -180,15 +181,17 @@ jsonToYaml (Number n) = text $ show n jsonToYaml _ = empty -- | Return markdown representation of document. -pandocToMarkdown :: PandocMonad m => WriterOptions -> Pandoc -> MD m String +pandocToMarkdown :: PandocMonad m => WriterOptions -> Pandoc -> MD m Text pandocToMarkdown opts (Pandoc meta blocks) = do let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing isPlain <- asks envPlain + let render' :: Doc -> Text + render' = render colwidth . chomp metadata <- metaToJSON' - (fmap (render colwidth) . blockListToMarkdown opts) - (fmap (render colwidth) . blockToMarkdown opts . Plain) + (fmap render' . blockListToMarkdown opts) + (fmap render' . blockToMarkdown opts . Plain) meta let title' = maybe empty text $ getField "title" metadata let authors' = maybe [] (map text) $ getField "author" metadata @@ -216,8 +219,6 @@ pandocToMarkdown opts (Pandoc meta blocks) = do else blocks body <- blockListToMarkdown opts blocks' notesAndRefs' <- notesAndRefs opts - let render' :: Doc -> String - render' = render colwidth . chomp let main = render' $ body <> notesAndRefs' let context = defField "toc" (render' toc) $ defField "body" main @@ -571,7 +572,7 @@ blockToMarkdown' opts t@(Table caption aligns widths headers rows) = do gridTable opts blockListToMarkdown (all null headers) aligns' widths' headers rows | isEnabled Ext_raw_html opts -> fmap (id,) $ - text <$> + (text . T.unpack) <$> (writeHtml5String def $ Pandoc nullMeta [t]) | otherwise -> return $ (id, text "[TABLE]") return $ nst $ tbl $$ caption'' $$ blankline @@ -1110,7 +1111,8 @@ inlineToMarkdown opts lnk@(Link attr txt (src, tit)) | isEnabled Ext_raw_html opts && not (isEnabled Ext_link_attributes opts) && attr /= nullAttr = -- use raw HTML - (text . trim) <$> writeHtml5String def (Pandoc nullMeta [Plain [lnk]]) + (text . T.unpack . T.strip) <$> + writeHtml5String def (Pandoc nullMeta [Plain [lnk]]) | otherwise = do plain <- asks envPlain linktext <- inlineListToMarkdown opts txt @@ -1149,7 +1151,8 @@ inlineToMarkdown opts img@(Image attr alternate (source, tit)) | isEnabled Ext_raw_html opts && not (isEnabled Ext_link_attributes opts) && attr /= nullAttr = -- use raw HTML - (text . trim) <$> writeHtml5String def (Pandoc nullMeta [Plain [img]]) + (text . T.unpack . T.strip) <$> + writeHtml5String def (Pandoc nullMeta [Plain [img]]) | otherwise = do plain <- asks envPlain let txt = if null alternate || alternate == [Str source] diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index aa5c3bc4f..c70e5b786 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -34,6 +34,7 @@ import Control.Monad.Reader import Control.Monad.State import Data.List (intercalate) import qualified Data.Set as Set +import Data.Text (Text, pack) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition @@ -59,14 +60,14 @@ data WriterReader = WriterReader { type MediaWikiWriter m = ReaderT WriterReader (StateT WriterState m) -- | Convert Pandoc to MediaWiki. -writeMediaWiki :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeMediaWiki :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeMediaWiki opts document = let initialState = WriterState { stNotes = False, stOptions = opts } env = WriterReader { options = opts, listLevel = [], useTags = False } in evalStateT (runReaderT (pandocToMediaWiki document) env) initialState -- | Return MediaWiki representation of document. -pandocToMediaWiki :: PandocMonad m => Pandoc -> MediaWikiWriter m String +pandocToMediaWiki :: PandocMonad m => Pandoc -> MediaWikiWriter m Text pandocToMediaWiki (Pandoc meta blocks) = do opts <- asks options metadata <- metaToJSON opts @@ -81,7 +82,8 @@ pandocToMediaWiki (Pandoc meta blocks) = do let main = body ++ notes let context = defField "body" main $ defField "toc" (writerTableOfContents opts) metadata - return $ case writerTemplate opts of + return $ pack + $ case writerTemplate opts of Nothing -> main Just tpl -> renderTemplate' tpl context diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 5dd225e19..c5c3d9f5b 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -44,6 +44,7 @@ import Text.Pandoc.Options import Text.Pandoc.Writers.Math import Text.Printf ( printf ) import qualified Data.Text as T +import Data.Text (Text) import qualified Data.Map as Map import Data.Maybe ( catMaybes, fromMaybe ) import Data.List ( intersperse, intercalate, sort ) @@ -85,17 +86,18 @@ type Note = [Block] type MS = StateT WriterState -- | Convert Pandoc to Ms. -writeMs :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeMs :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeMs opts document = evalStateT (pandocToMs opts document) defaultWriterState -- | Return groff ms representation of document. -pandocToMs :: PandocMonad m => WriterOptions -> Pandoc -> MS m String +pandocToMs :: PandocMonad m => WriterOptions -> Pandoc -> MS m Text pandocToMs opts (Pandoc meta blocks) = do let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing - let render' = render colwidth + let render' :: Doc -> Text + render' = render colwidth metadata <- metaToJSON opts (fmap render' . blockListToMs opts) (fmap render' . inlineListToMs' opts) @@ -108,9 +110,9 @@ pandocToMs opts (Pandoc meta blocks) = do hasHighlighting <- gets stHighlighting let highlightingMacros = if hasHighlighting then case writerHighlightStyle opts of - Nothing -> "" + Nothing -> mempty Just sty -> render' $ styleToMs sty - else "" + else mempty let context = defField "body" main $ defField "has-inline-math" hasInlineMath diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index ccc6e9aef..85e0b5467 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -43,6 +43,7 @@ even though it is supported only in Emacs Muse. -} module Text.Pandoc.Writers.Muse (writeMuse) where import Control.Monad.State +import Data.Text (Text) import Data.List (intersperse, transpose, isInfixOf) import System.FilePath (takeExtension) import Text.Pandoc.Class (PandocMonad) @@ -68,7 +69,7 @@ data WriterState = writeMuse :: PandocMonad m => WriterOptions -> Pandoc - -> m String + -> m Text writeMuse opts document = let st = WriterState { stNotes = [] , stOptions = opts @@ -81,15 +82,17 @@ writeMuse opts document = -- | Return Muse representation of document. pandocToMuse :: PandocMonad m => Pandoc - -> StateT WriterState m String + -> StateT WriterState m Text pandocToMuse (Pandoc meta blocks) = do opts <- gets stOptions let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing + let render' :: Doc -> Text + render' = render Nothing metadata <- metaToJSON opts - (fmap (render Nothing) . blockListToMuse) - (fmap (render Nothing) . inlineListToMuse) + (fmap render' . blockListToMuse) + (fmap render' . inlineListToMuse) meta body <- blockListToMuse blocks notes <- liftM (reverse . stNotes) get >>= notesToMuse diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs index 653efb3ce..3ef33f05c 100644 --- a/src/Text/Pandoc/Writers/Native.hs +++ b/src/Text/Pandoc/Writers/Native.hs @@ -30,6 +30,7 @@ Conversion of a 'Pandoc' document to a string representation. -} module Text.Pandoc.Writers.Native ( writeNative ) where +import Data.Text (Text) import Data.List (intersperse) import Text.Pandoc.Class (PandocMonad) import Text.Pandoc.Definition @@ -67,7 +68,7 @@ prettyBlock (Div attr blocks) = prettyBlock block = text $ show block -- | Prettyprint Pandoc document. -writeNative :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeNative :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeNative opts (Pandoc meta blocks) = return $ let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 68e68c659..1da051380 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -35,6 +35,7 @@ import Control.Monad.State import qualified Data.ByteString.Lazy as B import Data.List (isPrefixOf) import Data.Maybe (fromMaybe) +import qualified Data.Text.Lazy as TL import System.FilePath (takeDirectory, takeExtension, (<.>)) import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P @@ -45,7 +46,7 @@ import Text.Pandoc.MIME (extensionFromMimeType, getMimeType) import Text.Pandoc.Options (WrapOption (..), WriterOptions (..)) import Text.Pandoc.Pretty import Text.Pandoc.Shared (stringify) -import Text.Pandoc.UTF8 (fromStringLazy) +import Text.Pandoc.UTF8 (fromStringLazy, fromTextLazy) import Text.Pandoc.Walk import Text.Pandoc.Writers.OpenDocument (writeOpenDocument) import Text.Pandoc.Writers.Shared (fixDisplayMath) @@ -88,7 +89,7 @@ pandocToODT opts doc@(Pandoc meta _) = do newContents <- lift $ writeOpenDocument opts{writerWrapText = WrapNone} doc' epochtime <- floor `fmap` (lift P.getPOSIXTime) let contentEntry = toEntry "content.xml" epochtime - $ fromStringLazy newContents + $ fromTextLazy $ TL.fromStrict newContents picEntries <- gets stEntries let archive = foldr addEntryToArchive refArchive $ contentEntry : picEntries diff --git a/src/Text/Pandoc/Writers/OPML.hs b/src/Text/Pandoc/Writers/OPML.hs index cdb6ab0d1..4a0a317fa 100644 --- a/src/Text/Pandoc/Writers/OPML.hs +++ b/src/Text/Pandoc/Writers/OPML.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 53c1d0c59..58295684e 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -36,6 +36,7 @@ import Control.Arrow ((***), (>>>)) import Control.Monad.State hiding (when) import Data.Char (chr) import Data.List (sortBy) +import Data.Text (Text) import qualified Data.Map as Map import Data.Ord (comparing) import qualified Data.Set as Set @@ -195,17 +196,18 @@ handleSpaces s rm [] = empty -- | Convert Pandoc document to string in OpenDocument format. -writeOpenDocument :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeOpenDocument :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeOpenDocument opts (Pandoc meta blocks) = do let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing - let render' = render colwidth + let render' :: Doc -> Text + render' = render colwidth ((body, metadata),s) <- flip runStateT defaultWriterState $ do m <- metaToJSON opts - (fmap (render colwidth) . blocksToOpenDocument opts) - (fmap (render colwidth) . inlinesToOpenDocument opts) + (fmap render' . blocksToOpenDocument opts) + (fmap render' . inlinesToOpenDocument opts) meta b <- render' `fmap` blocksToOpenDocument opts blocks return (b, m) diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 78c102db6..e8f48da00 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -37,6 +37,7 @@ Org-Mode: module Text.Pandoc.Writers.Org (writeOrg) where import Control.Monad.State import Data.Char (isAlphaNum, toLower) +import Data.Text (Text) import Data.List (intersect, intersperse, isPrefixOf, partition, transpose) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition @@ -56,7 +57,7 @@ data WriterState = type Org = StateT WriterState -- | Convert Pandoc to Org. -writeOrg :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeOrg :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeOrg opts document = do let st = WriterState { stNotes = [], stHasMath = False, @@ -64,15 +65,17 @@ writeOrg opts document = do evalStateT (pandocToOrg document) st -- | Return Org representation of document. -pandocToOrg :: PandocMonad m => Pandoc -> Org m String +pandocToOrg :: PandocMonad m => Pandoc -> Org m Text pandocToOrg (Pandoc meta blocks) = do opts <- gets stOptions let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing + let render' :: Doc -> Text + render' = render colwidth metadata <- metaToJSON opts - (fmap (render colwidth) . blockListToOrg) - (fmap (render colwidth) . inlineListToOrg) + (fmap render' . blockListToOrg) + (fmap render' . inlineListToOrg) meta body <- blockListToOrg blocks notes <- gets (reverse . stNotes) >>= notesToOrg diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index b88fc2245..59f6553e2 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -35,6 +35,7 @@ import Control.Monad.State import Data.Char (isSpace, toLower) import Data.List (isPrefixOf, stripPrefix) import Data.Maybe (fromMaybe) +import Data.Text (Text, stripEnd) import qualified Text.Pandoc.Builder as B import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging @@ -62,7 +63,7 @@ data WriterState = type RST = StateT WriterState -- | Convert Pandoc to RST. -writeRST :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeRST :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeRST opts document = do let st = WriterState { stNotes = [], stLinks = [], stImages = [], stHasMath = False, @@ -71,19 +72,21 @@ writeRST opts document = do evalStateT (pandocToRST document) st -- | Return RST representation of document. -pandocToRST :: PandocMonad m => Pandoc -> RST m String +pandocToRST :: PandocMonad m => Pandoc -> RST m Text pandocToRST (Pandoc meta blocks) = do opts <- gets stOptions let colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing + let render' :: Doc -> Text + render' = render colwidth let subtit = case lookupMeta "subtitle" meta of Just (MetaBlocks [Plain xs]) -> xs _ -> [] title <- titleToRST (docTitle meta) subtit metadata <- metaToJSON opts - (fmap (render colwidth) . blockListToRST) - (fmap (trimr . render colwidth) . inlineListToRST) + (fmap render' . blockListToRST) + (fmap (stripEnd . render') . inlineListToRST) $ B.deleteMeta "title" $ B.deleteMeta "subtitle" meta body <- blockListToRST' True $ case writerTemplate opts of Just _ -> normalizeHeadings 1 blocks @@ -94,7 +97,7 @@ pandocToRST (Pandoc meta blocks) = do pics <- gets (reverse . stImages) >>= pictRefsToRST hasMath <- gets stHasMath rawTeX <- gets stHasRawTeX - let main = render colwidth $ foldl ($+$) empty $ [body, notes, refs, pics] + let main = render' $ foldl ($+$) empty $ [body, notes, refs, pics] let context = defField "body" main $ defField "toc" (writerTableOfContents opts) $ defField "toc-depth" (show $ writerTOCDepth opts) diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index e9b29f97d..5c990f324 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -34,6 +34,8 @@ import Control.Monad.Except (catchError, throwError) import qualified Data.ByteString as B import Data.Char (chr, isDigit, ord) import Data.List (intercalate, isSuffixOf) +import Data.Text (Text) +import qualified Data.Text as T import qualified Data.Map as M import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P @@ -97,7 +99,7 @@ rtfEmbedImage opts x@(Image attr _ (src,_)) = catchError rtfEmbedImage _ x = return x -- | Convert Pandoc to a string in rich text format. -writeRTF :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeRTF :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeRTF options doc = do -- handle images Pandoc meta@(Meta metamap) blocks <- walkM (rtfEmbedImage options) doc @@ -123,7 +125,8 @@ writeRTF options doc = do then defField "toc" toc else id) $ metadata - return $ case writerTemplate options of + return $ T.pack + $ case writerTemplate options of Just tpl -> renderTemplate' tpl context Nothing -> case reverse body of ('\n':_) -> body diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index 7da792c9e..27d26c7d9 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -31,6 +31,7 @@ Conversion of 'Pandoc' documents to Docbook XML. -} module Text.Pandoc.Writers.TEI (writeTEI) where import Data.Char (toLower) +import Data.Text (Text) import Data.List (isPrefixOf, stripPrefix) import qualified Text.Pandoc.Builder as B import Text.Pandoc.Class (PandocMonad, report) @@ -56,12 +57,13 @@ authorToTEI opts name' = do inTagsSimple "author" (text $ escapeStringForXML name) -- | Convert Pandoc document to string in Docbook format. -writeTEI :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeTEI :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeTEI opts (Pandoc meta blocks) = do let elements = hierarchicalize blocks colwidth = if writerWrapText opts == WrapAuto then Just $ writerColumns opts else Nothing + render' :: Doc -> Text render' = render colwidth startLvl = case writerTopLevelDivision opts of TopLevelPart -> -1 @@ -71,9 +73,9 @@ writeTEI opts (Pandoc meta blocks) = do auths' <- mapM (authorToTEI opts) $ docAuthors meta let meta' = B.setMeta "author" auths' meta metadata <- metaToJSON opts - (fmap (render colwidth . vcat) . - (mapM (elementToTEI opts startLvl)) . hierarchicalize) - (fmap (render colwidth) . inlinesToTEI opts) + (fmap (render' . vcat) . + mapM (elementToTEI opts startLvl) . hierarchicalize) + (fmap render' . inlinesToTEI opts) meta' main <- (render' . vcat) <$> mapM (elementToTEI opts startLvl) elements let context = defField "body" main diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 710e1dea0..387e55290 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -37,6 +37,7 @@ import Data.Char (chr, ord) import Data.List (maximumBy, transpose) import Data.Ord (comparing) import qualified Data.Set as Set +import Data.Text (Text) import Network.URI (unEscapeString) import System.FilePath import Text.Pandoc.Class (PandocMonad, report) @@ -68,7 +69,7 @@ data WriterState = type TI m = StateT WriterState m -- | Convert Pandoc to Texinfo. -writeTexinfo :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeTexinfo :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeTexinfo options document = evalStateT (pandocToTexinfo options $ wrapTop document) $ WriterState { stStrikeout = False, stSuperscript = False, @@ -80,16 +81,18 @@ wrapTop :: Pandoc -> Pandoc wrapTop (Pandoc meta blocks) = Pandoc meta (Header 0 nullAttr (docTitle meta) : blocks) -pandocToTexinfo :: PandocMonad m => WriterOptions -> Pandoc -> TI m String +pandocToTexinfo :: PandocMonad m => WriterOptions -> Pandoc -> TI m Text pandocToTexinfo options (Pandoc meta blocks) = do let titlePage = not $ all null $ docTitle meta : docDate meta : docAuthors meta let colwidth = if writerWrapText options == WrapAuto then Just $ writerColumns options else Nothing + let render' :: Doc -> Text + render' = render colwidth metadata <- metaToJSON options - (fmap (render colwidth) . blockListToTexinfo) - (fmap (render colwidth) . inlineListToTexinfo) + (fmap render' . blockListToTexinfo) + (fmap render' . inlineListToTexinfo) meta main <- blockListToTexinfo blocks st <- get diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index d532f3ed3..091a5baca 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -33,6 +33,7 @@ module Text.Pandoc.Writers.Textile ( writeTextile ) where import Control.Monad.State import Data.Char (isSpace) import Data.List (intercalate) +import Data.Text (Text, pack) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition @@ -54,7 +55,7 @@ data WriterState = WriterState { type TW = StateT WriterState -- | Convert Pandoc to Textile. -writeTextile :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeTextile :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeTextile opts document = evalStateT (pandocToTextile opts document) WriterState { stNotes = [], @@ -64,17 +65,17 @@ writeTextile opts document = -- | Return Textile representation of document. pandocToTextile :: PandocMonad m - => WriterOptions -> Pandoc -> TW m String + => WriterOptions -> Pandoc -> TW m Text pandocToTextile opts (Pandoc meta blocks) = do metadata <- metaToJSON opts (blockListToTextile opts) (inlineListToTextile opts) meta body <- blockListToTextile opts blocks notes <- gets $ unlines . reverse . stNotes - let main = body ++ if null notes then "" else ("\n\n" ++ notes) + let main = pack $ body ++ if null notes then "" else ("\n\n" ++ notes) let context = defField "body" main metadata case writerTemplate opts of - Nothing -> return main - Just tpl -> return $ renderTemplate' tpl context + Nothing -> return main + Just tpl -> return $ renderTemplate' tpl context withUseTags :: PandocMonad m => TW m a -> TW m a withUseTags action = do diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index 4ab8bde30..5ee239e59 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -37,7 +37,7 @@ import Control.Monad.State (StateT, evalStateT, gets, modify) import Data.Default (Default (..)) import Data.List (intercalate, isInfixOf, isPrefixOf, transpose) import qualified Data.Map as Map -import Data.Text (breakOnAll, pack) +import Data.Text (breakOnAll, pack, Text) import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Logging import Text.Pandoc.Definition @@ -61,17 +61,17 @@ instance Default WriterState where type ZW = StateT WriterState -- | Convert Pandoc to ZimWiki. -writeZimWiki :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeZimWiki :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeZimWiki opts document = evalStateT (pandocToZimWiki opts document) def -- | Return ZimWiki representation of document. -pandocToZimWiki :: PandocMonad m => WriterOptions -> Pandoc -> ZW m String +pandocToZimWiki :: PandocMonad m => WriterOptions -> Pandoc -> ZW m Text pandocToZimWiki opts (Pandoc meta blocks) = do metadata <- metaToJSON opts (fmap trimr . blockListToZimWiki opts) (inlineListToZimWiki opts) meta - body <- blockListToZimWiki opts blocks + body <- pack <$> blockListToZimWiki opts blocks --let header = "Content-Type: text/x-zim-wiki\nWiki-Format: zim 0.4\n" let main = body let context = defField "body" main diff --git a/src/Text/Pandoc/XML.hs b/src/Text/Pandoc/XML.hs index b6edd6be5..67608fb43 100644 --- a/src/Text/Pandoc/XML.hs +++ b/src/Text/Pandoc/XML.hs @@ -37,6 +37,8 @@ module Text.Pandoc.XML ( escapeCharForXML, fromEntities ) where import Data.Char (isAscii, isSpace, ord) +import Data.Text (Text) +import qualified Data.Text as T import Text.HTML.TagSoup.Entity (lookupEntity) import Text.Pandoc.Pretty @@ -91,11 +93,10 @@ inTagsIndented :: String -> Doc -> Doc inTagsIndented tagType = inTags True tagType [] -- | Escape all non-ascii characters using numerical entities. -toEntities :: String -> String -toEntities [] = "" -toEntities (c:cs) - | isAscii c = c : toEntities cs - | otherwise = "&#" ++ show (ord c) ++ ";" ++ toEntities cs +toEntities :: Text -> Text +toEntities = T.concatMap go + where go c | isAscii c = T.singleton c + | otherwise = T.pack ("&#" ++ show (ord c) ++ ";") -- Unescapes XML entities fromEntities :: String -> String diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs index 3a82867cb..2a6543ea0 100644 --- a/test/Tests/Helpers.hs +++ b/test/Tests/Helpers.hs @@ -106,17 +106,18 @@ class ToString a where toString :: a -> String instance ToString Pandoc where - toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d + toString d = unpack $ + purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of (Pandoc (Meta m) _) | M.null m -> Nothing | otherwise -> Just "" -- need this to get meta output instance ToString Blocks where - toString = purely (writeNative def) . toPandoc + toString = unpack . purely (writeNative def) . toPandoc instance ToString Inlines where - toString = trimr . purely (writeNative def) . toPandoc + toString = trimr . unpack . purely (writeNative def) . toPandoc instance ToString String where toString = id diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs index e29f0acad..e55c3529b 100644 --- a/test/Tests/Readers/Docx.hs +++ b/test/Tests/Readers/Docx.hs @@ -3,6 +3,7 @@ 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.Text as T import qualified Data.Map as M import Test.Tasty import Test.Tasty.HUnit @@ -27,7 +28,7 @@ defopts :: ReaderOptions defopts = def{ readerExtensions = getDefaultExtensions "docx" } instance ToString NoNormPandoc where - toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d + toString d = T.unpack $ purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs index 390d80df9..afac9e8cb 100644 --- a/test/Tests/Readers/LaTeX.hs +++ b/test/Tests/Readers/LaTeX.hs @@ -6,7 +6,7 @@ import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder -import Data.Text (Text, pack) +import Data.Text (Text) import qualified Data.Text as T latex :: Text -> Pandoc diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs index 61ccc8819..eed3a33b0 100644 --- a/test/Tests/Readers/Odt.hs +++ b/test/Tests/Readers/Odt.hs @@ -5,6 +5,7 @@ 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 Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -41,7 +42,8 @@ newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} deriving ( Show ) instance ToString NoNormPandoc where - toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d + toString d = unpack $ + purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs index 02ecb08f4..6b97c0761 100644 --- a/test/Tests/Writers/AsciiDoc.hs +++ b/test/Tests/Writers/AsciiDoc.hs @@ -1,5 +1,6 @@ module Tests.Writers.AsciiDoc (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -7,7 +8,7 @@ import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder asciidoc :: (ToPandoc a) => a -> String -asciidoc = purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc +asciidoc = unpack . purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc tests :: [TestTree] tests = [ testGroup "emphasis" diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs index a5185e19f..783b601a9 100644 --- a/test/Tests/Writers/ConTeXt.hs +++ b/test/Tests/Writers/ConTeXt.hs @@ -1,6 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.ConTeXt (tests) where +import Data.Text (unpack) import Test.Tasty import Test.Tasty.QuickCheck import Tests.Helpers @@ -9,10 +10,10 @@ import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder context :: (ToPandoc a) => a -> String -context = purely (writeConTeXt def) . toPandoc +context = unpack . purely (writeConTeXt def) . toPandoc context' :: (ToPandoc a) => a -> String -context' = purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc +context' = unpack . purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc {- "my test" =: X =?> Y diff --git a/test/Tests/Writers/Docbook.hs b/test/Tests/Writers/Docbook.hs index d7da51aed..90ae073fa 100644 --- a/test/Tests/Writers/Docbook.hs +++ b/test/Tests/Writers/Docbook.hs @@ -1,6 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.Docbook (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -11,7 +12,7 @@ docbook :: (ToPandoc a) => a -> String docbook = docbookWithOpts def{ writerWrapText = WrapNone } docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String -docbookWithOpts opts = purely (writeDocbook4 opts) . toPandoc +docbookWithOpts opts = unpack . purely (writeDocbook4 opts) . toPandoc {- "my test" =: X =?> Y diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs index 4246b033d..23ff718d3 100644 --- a/test/Tests/Writers/HTML.hs +++ b/test/Tests/Writers/HTML.hs @@ -1,6 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.HTML (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -8,7 +9,7 @@ import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder html :: (ToPandoc a) => a -> String -html = purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc +html = unpack . purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc {- "my test" =: X =?> Y diff --git a/test/Tests/Writers/LaTeX.hs b/test/Tests/Writers/LaTeX.hs index 5f8aea3e0..471d9d9e7 100644 --- a/test/Tests/Writers/LaTeX.hs +++ b/test/Tests/Writers/LaTeX.hs @@ -1,6 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.LaTeX (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -14,10 +15,10 @@ latexListing :: (ToPandoc a) => a -> String latexListing = latexWithOpts def{ writerListings = True } latexWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -latexWithOpts opts = purely (writeLaTeX opts) . toPandoc +latexWithOpts opts = unpack . purely (writeLaTeX opts) . toPandoc beamerWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -beamerWithOpts opts = purely (writeBeamer opts) . toPandoc +beamerWithOpts opts = unpack . purely (writeBeamer opts) . toPandoc {- "my test" =: X =?> Y diff --git a/test/Tests/Writers/Markdown.hs b/test/Tests/Writers/Markdown.hs index 5b1e76a29..012e0888c 100644 --- a/test/Tests/Writers/Markdown.hs +++ b/test/Tests/Writers/Markdown.hs @@ -2,6 +2,7 @@ {-# OPTIONS_GHC -fno-warn-name-shadowing #-} module Tests.Writers.Markdown (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -12,10 +13,10 @@ defopts :: WriterOptions defopts = def{ writerExtensions = pandocExtensions } markdown :: (ToPandoc a) => a -> String -markdown = purely (writeMarkdown defopts) . toPandoc +markdown = unpack . purely (writeMarkdown defopts) . toPandoc markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -markdownWithOpts opts x = purely (writeMarkdown opts) $ toPandoc x +markdownWithOpts opts x = unpack . purely (writeMarkdown opts) $ toPandoc x {- "my test" =: X =?> Y diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 65bf3e99b..63fdd293c 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -1,5 +1,6 @@ module Tests.Writers.Muse (tests) where +import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -10,7 +11,7 @@ muse :: (ToPandoc a) => a -> String muse = museWithOpts def{ writerWrapText = WrapNone } museWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -museWithOpts opts = purely (writeMuse opts) . toPandoc +museWithOpts opts = unpack . purely (writeMuse opts) . toPandoc infix 4 =: (=:) :: (ToString a, ToPandoc a) diff --git a/test/Tests/Writers/Native.hs b/test/Tests/Writers/Native.hs index c92cb905c..c22185968 100644 --- a/test/Tests/Writers/Native.hs +++ b/test/Tests/Writers/Native.hs @@ -1,5 +1,6 @@ module Tests.Writers.Native (tests) where +import Data.Text (unpack) import Test.Tasty import Test.Tasty.QuickCheck import Tests.Helpers @@ -8,12 +9,11 @@ import Text.Pandoc.Arbitrary () p_write_rt :: Pandoc -> Bool p_write_rt d = - read (purely (writeNative def{ writerTemplate = Just "" }) d) == d + read (unpack $ purely (writeNative def{ writerTemplate = Just "" }) d) == d p_write_blocks_rt :: [Block] -> Bool p_write_blocks_rt bs = - read (purely (writeNative def) (Pandoc nullMeta bs)) == - bs + read (unpack $ purely (writeNative def) (Pandoc nullMeta bs)) == bs tests :: [TestTree] tests = [ testProperty "p_write_rt" p_write_rt diff --git a/trypandoc/trypandoc.hs b/trypandoc/trypandoc.hs index 0dd88a61f..d8652079a 100644 --- a/trypandoc/trypandoc.hs +++ b/trypandoc/trypandoc.hs @@ -33,11 +33,11 @@ app req respond = do _ -> error $ "could not find reader for " ++ T.unpack fromFormat let writer = case getWriter (T.unpack toFormat) of - Right (StringWriter w) -> w writerOpts + Right (TextWriter w) -> w writerOpts _ -> error $ "could not find writer for " ++ T.unpack toFormat let result = case runPure $ reader (tabFilter 4 text) >>= writer of - Right s -> T.pack s + Right s -> s Left err -> error (show err) let output = encode $ object [ T.pack "html" .= result , T.pack "name" .= -- cgit v1.2.3