From e15a4badff82a62afd2356c1e1e3211ef4c6eb71 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 10:34:04 +0200 Subject: Simplify plumbing for document transformation. --- src/Text/Pandoc/App.hs | 46 +++++++++++++++++++++------------------------- 1 file changed, 21 insertions(+), 25 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index c38ebdd84..b8a3c6613 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -68,10 +68,10 @@ import System.IO (stdout) import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) -import Text.Pandoc.Class (PandocIO, getLog, withMediaBag) +import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, getMediaBag) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) -import Text.Pandoc.MediaBag (MediaBag, extractMediaBag, mediaDirectory) +import Text.Pandoc.MediaBag (extractMediaBag, mediaDirectory) import Text.Pandoc.PDF (makePDF) import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.SelfContained (makeSelfContained, makeDataURI) @@ -391,20 +391,16 @@ convertWithOpts opts = do E.throwIO PandocFailOnWarningError return res - let sourceToDoc :: [FilePath] -> PandocIO (Pandoc, MediaBag) + let sourceToDoc :: [FilePath] -> PandocIO Pandoc sourceToDoc sources' = case reader of StringReader r - | optFileScope opts || readerName == "json" -> do - pairs <- mapM - (readSource >=> withMediaBag . r readerOpts) sources - return (mconcat (map fst pairs), mconcat (map snd pairs)) + | optFileScope opts || readerName == "json" -> + mconcat <$> mapM (readSource >=> r readerOpts) sources | otherwise -> - readSources sources' >>= withMediaBag . r readerOpts - ByteStringReader r -> do - pairs <- mapM (readFile' >=> - withMediaBag . r readerOpts) sources - return (mconcat (map fst pairs), mconcat (map snd pairs)) + readSources sources' >>= r readerOpts + ByteStringReader r -> + mconcat <$> mapM (readFile' >=> r readerOpts) sources metadata <- if format == "jats" && lookup "csl" (optMetadata opts) == Nothing && @@ -416,16 +412,15 @@ convertWithOpts opts = do else return $ optMetadata opts runIO' $ do - (doc, media) <- sourceToDoc sources - doc' <- (maybe return (extractMedia media) (optExtractMedia opts) >=> - return . flip (foldr addMetadata) metadata >=> - applyTransforms transforms >=> - applyLuaFilters datadir (optLuaFilters opts) [format] >=> - applyFilters datadir filters' [format]) doc + (doc, media) <- withMediaBag $ sourceToDoc sources >>= + (maybe return extractMedia (optExtractMedia opts) + >=> return . flip (foldr addMetadata) metadata + >=> applyTransforms transforms + >=> applyLuaFilters datadir (optLuaFilters opts) [format] + >=> applyFilters datadir filters' [format]) case writer of - -- StringWriter f -> f writerOptions doc' >>= writerFn outputFile - ByteStringWriter f -> f writerOptions doc' >>= writeFnBinary outputFile + ByteStringWriter f -> f writerOptions doc >>= writeFnBinary outputFile StringWriter f | pdfOutput -> do -- make sure writer is latex, beamer, context, html5 or ms @@ -445,7 +440,7 @@ convertWithOpts opts = do when (isNothing mbPdfProg) $ liftIO $ E.throwIO $ PandocPDFProgramNotFoundError pdfprog - res <- makePDF pdfprog f writerOptions verbosity media doc' + res <- makePDF pdfprog f writerOptions verbosity media doc case res of Right pdf -> writeFnBinary outputFile pdf Left err' -> liftIO $ @@ -462,7 +457,7 @@ convertWithOpts opts = do format == "docbook") && optAscii opts then toEntities else id - output <- f writerOptions doc' + output <- f writerOptions doc selfcontain (output ++ ['\n' | not standalone]) >>= writerFn outputFile . handleEntities @@ -728,12 +723,13 @@ defaultWriterName x = -- Transformations of a Pandoc document post-parsing: -extractMedia :: MonadIO m => MediaBag -> FilePath -> Pandoc -> m Pandoc -extractMedia media dir d = +extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc +extractMedia dir d = do + media <- getMediaBag case [fp | (fp, _, _) <- mediaDirectory media] of [] -> return d fps -> do - extractMediaBag True dir media + liftIO $ extractMediaBag True dir media return $ walk (adjustImagePath dir fps) d adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline -- cgit v1.2.3 From 400fe3188e3f5a3e48700ae114a0da05ae6e599a Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 11:45:33 +0200 Subject: Allow `--extract-media` to work with non-binary input formats. If `--extract-media` is supplied with a non-binary input format, pandoc will attempt to extract the contents of all linked images, whether in local files, data: uris, or external uris. They will be named based on the sha1 hash of the contents. Closes #1583, #2289. Notes: - One thing that is slightly subideal with this commit is that identical resources will be downloaded multiple times. To improve this we could have mediabag store an original filename/url + a new name. - We might think about reusing some of this code, since more or less the same thing is done in the Docx, EPUB, PDF writers (with slight variations). --- src/Text/Pandoc/App.hs | 30 ++++++++++++++++++++++++++---- 1 file changed, 26 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index b8a3c6613..212ae7fe2 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -45,6 +45,7 @@ import Data.Aeson (eitherDecode', encode) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as B import Data.Char (toLower, toUpper) +import Data.Digest.Pure.SHA (sha1, showDigest) import qualified Data.Set as Set import Data.Foldable (foldrM) import Data.List (intercalate, isPrefixOf, isSuffixOf, sort) @@ -68,17 +69,19 @@ import System.IO (stdout) import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) -import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, getMediaBag) +import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, getMediaBag, + fetchItem, insertMedia) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) import Text.Pandoc.MediaBag (extractMediaBag, mediaDirectory) +import Text.Pandoc.MIME (extensionFromMimeType) import Text.Pandoc.PDF (makePDF) import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.SelfContained (makeSelfContained, makeDataURI) import Text.Pandoc.Shared (headerShift, openURL, readDataFile, readDataFileUTF8, safeRead, tabFilter) import qualified Text.Pandoc.UTF8 as UTF8 -import Text.Pandoc.Walk (walk) +import Text.Pandoc.Walk (walkM, walk) import Text.Pandoc.XML (toEntities) import Text.Printf #ifndef _WINDOWS @@ -413,11 +416,15 @@ convertWithOpts opts = do runIO' $ do (doc, media) <- withMediaBag $ sourceToDoc sources >>= - (maybe return extractMedia (optExtractMedia opts) + ( (if isJust (optExtractMedia opts) + then fillMedia (writerSourceURL writerOptions) + else return) + >=> maybe return extractMedia (optExtractMedia opts) >=> return . flip (foldr addMetadata) metadata >=> applyTransforms transforms >=> applyLuaFilters datadir (optLuaFilters opts) [format] - >=> applyFilters datadir filters' [format]) + >=> applyFilters datadir filters' [format] + ) case writer of ByteStringWriter f -> f writerOptions doc >>= writeFnBinary outputFile @@ -723,6 +730,21 @@ defaultWriterName x = -- Transformations of a Pandoc document post-parsing: +-- | Traverse tree, filling media bag. +fillMedia :: Maybe String -> Pandoc -> PandocIO Pandoc +fillMedia sourceURL d = walkM handleImage d + where handleImage :: Inline -> PandocIO Inline + handleImage (Image attr lab (src, tit)) = do + (bs, mt) <- fetchItem sourceURL src + let ext = fromMaybe (takeExtension src) + (mt >>= extensionFromMimeType) + let bs' = B.fromChunks [bs] + let basename = showDigest $ sha1 bs' + let fname = basename <.> ext + insertMedia fname mt bs' + return $ Image attr lab (fname, tit) + handleImage x = return x + extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc extractMedia dir d = do media <- getMediaBag -- cgit v1.2.3 From f8e125f42d8568b9f2926c2d1a3eb37acba2b3d1 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 12:16:14 +0200 Subject: fillMediaBag: don't cause fatal error if resource not found. Report warning instead and change image to its alt text. --- src/Text/Pandoc/App.hs | 29 +++++++++++++++++++---------- 1 file changed, 19 insertions(+), 10 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 212ae7fe2..2efa69944 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -39,6 +39,7 @@ module Text.Pandoc.App ( ) where import Control.Applicative ((<|>)) import qualified Control.Exception as E +import Control.Monad.Except (catchError, throwError) import Control.Monad import Control.Monad.Trans import Data.Aeson (eitherDecode', encode) @@ -70,7 +71,7 @@ import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, getMediaBag, - fetchItem, insertMedia) + fetchItem, insertMedia, report) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) import Text.Pandoc.MediaBag (extractMediaBag, mediaDirectory) @@ -734,15 +735,23 @@ defaultWriterName x = fillMedia :: Maybe String -> Pandoc -> PandocIO Pandoc fillMedia sourceURL d = walkM handleImage d where handleImage :: Inline -> PandocIO Inline - handleImage (Image attr lab (src, tit)) = do - (bs, mt) <- fetchItem sourceURL src - let ext = fromMaybe (takeExtension src) - (mt >>= extensionFromMimeType) - let bs' = B.fromChunks [bs] - let basename = showDigest $ sha1 bs' - let fname = basename <.> ext - insertMedia fname mt bs' - return $ Image attr lab (fname, tit) + handleImage (Image attr lab (src, tit)) = catchError + (do (bs, mt) <- fetchItem sourceURL src + let ext = fromMaybe (takeExtension src) + (mt >>= extensionFromMimeType) + let bs' = B.fromChunks [bs] + let basename = showDigest $ sha1 bs' + let fname = basename <.> ext + insertMedia fname mt bs' + return $ Image attr lab (fname, tit)) + (\e -> do + case e of + PandocResourceNotFound _ -> do + report $ CouldNotFetchResource src + "replacing image with description" + -- emit alt text + return $ Span ("",["image"],[]) lab + _ -> throwError e) handleImage x = return x extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc -- 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/App.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 af7215a048a490a7c69eb6ea906bf4ca5d09c1b1 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 20:42:32 +0200 Subject: Moved fillMedia, extractMedia from App to Class. Also generalized type of fillMedia to any instance of PandocMonad. --- src/Text/Pandoc/App.hs | 52 +++----------------------------------------- src/Text/Pandoc/Class.hs | 56 +++++++++++++++++++++++++++++++++++++++++++++--- 2 files changed, 56 insertions(+), 52 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index a1691c5e2..6bc345d73 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -39,14 +39,13 @@ module Text.Pandoc.App ( ) where import Control.Applicative ((<|>)) import qualified Control.Exception as E -import Control.Monad.Except (catchError, throwError) +import Control.Monad.Except (throwError) import Control.Monad import Control.Monad.Trans import Data.Aeson (eitherDecode', encode) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as B import Data.Char (toLower, toUpper) -import Data.Digest.Pure.SHA (sha1, showDigest) import qualified Data.Set as Set import Data.Foldable (foldrM) import Data.List (intercalate, isPrefixOf, isSuffixOf, sort) @@ -70,19 +69,16 @@ import System.IO (stdout) import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) -import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, getMediaBag, - fetchItem, insertMedia, report) +import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, + extractMedia, fillMedia) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) -import Text.Pandoc.MediaBag (extractMediaBag, mediaDirectory) -import Text.Pandoc.MIME (extensionFromMimeType) import Text.Pandoc.PDF (makePDF) import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.SelfContained (makeSelfContained, makeDataURI) import Text.Pandoc.Shared (headerShift, openURL, readDataFile, readDataFileUTF8, safeRead, tabFilter) import qualified Text.Pandoc.UTF8 as UTF8 -import Text.Pandoc.Walk (walkM, walk) import Text.Pandoc.XML (toEntities) import Text.Printf #ifndef _WINDOWS @@ -731,48 +727,6 @@ defaultWriterName x = -- Transformations of a Pandoc document post-parsing: --- | Traverse tree, filling media bag. -fillMedia :: Maybe String -> Pandoc -> PandocIO Pandoc -fillMedia sourceURL d = walkM handleImage d - where handleImage :: Inline -> PandocIO Inline - handleImage (Image attr lab (src, tit)) = catchError - (do (bs, mt) <- fetchItem sourceURL src - let ext = fromMaybe (takeExtension src) - (mt >>= extensionFromMimeType) - let bs' = B.fromChunks [bs] - let basename = showDigest $ sha1 bs' - let fname = basename <.> ext - insertMedia fname mt bs' - return $ Image attr lab (fname, tit)) - (\e -> do - case e of - PandocResourceNotFound _ -> do - report $ CouldNotFetchResource src - "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 - -extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc -extractMedia dir d = do - media <- getMediaBag - case [fp | (fp, _, _) <- mediaDirectory media] of - [] -> return d - fps -> do - liftIO $ extractMediaBag True dir media - return $ walk (adjustImagePath dir fps) d - -adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline -adjustImagePath dir paths (Image attr lab (src, tit)) - | src `elem` paths = Image attr lab (dir ++ "/" ++ src, tit) -adjustImagePath _ _ x = x - applyTransforms :: Monad m => [Transform] -> Pandoc -> m Pandoc applyTransforms transforms d = return $ foldr ($) d transforms diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 939e0bd18..7407d0799 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -61,6 +61,8 @@ module Text.Pandoc.Class ( PandocMonad(..) , runIOorExplode , runPure , withMediaBag + , fillMedia + , extractMedia ) where import Prelude hiding (readFile) @@ -76,8 +78,11 @@ import Text.Pandoc.Compat.Time (UTCTime) import Text.Pandoc.Logging import Text.Parsec (ParsecT) import qualified Text.Pandoc.Compat.Time as IO (getCurrentTime) -import Text.Pandoc.MIME (MimeType, getMimeType) +import Text.Pandoc.MIME (MimeType, getMimeType, extensionFromMimeType) +import Text.Pandoc.Definition import Data.Char (toLower) +import Data.Digest.Pure.SHA (sha1, showDigest) +import Data.Maybe (fromMaybe) import Data.Time.Clock.POSIX ( utcTimeToPOSIXSeconds , posixSecondsToUTCTime , POSIXTime ) @@ -86,13 +91,15 @@ import Network.URI ( escapeURIString, nonStrictRelativeTo, unEscapeString, parseURIReference, isAllowedInURI, parseURI, URI(..) ) import qualified Data.Time.LocalTime as IO (getCurrentTimeZone) -import Text.Pandoc.MediaBag (MediaBag, lookupMedia) +import Text.Pandoc.MediaBag (MediaBag, lookupMedia, extractMediaBag, + mediaDirectory) +import Text.Pandoc.Walk (walkM, walk) import qualified Text.Pandoc.MediaBag as MB import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL import qualified System.Environment as IO (lookupEnv) import System.FilePath.Glob (match, compile) -import System.FilePath ((), takeExtension, dropExtension, isRelative) +import System.FilePath ((), (<.>), takeExtension, dropExtension, isRelative) import qualified System.FilePath.Glob as IO (glob) import qualified System.Directory as IO (getModificationTime) import Control.Monad as M (fail) @@ -338,6 +345,49 @@ withPaths (p:ps) action fp = catchError (action (p fp)) (\_ -> withPaths ps action fp) +-- | Traverse tree, filling media bag. +fillMedia :: PandocMonad m => Maybe String -> Pandoc -> m Pandoc +fillMedia sourceURL d = walkM handleImage d + where handleImage :: PandocMonad m => Inline -> m Inline + handleImage (Image attr lab (src, tit)) = catchError + (do (bs, mt) <- fetchItem sourceURL src + let ext = fromMaybe (takeExtension src) + (mt >>= extensionFromMimeType) + let bs' = BL.fromChunks [bs] + let basename = showDigest $ sha1 bs' + let fname = basename <.> ext + insertMedia fname mt bs' + return $ Image attr lab (fname, tit)) + (\e -> do + case e of + PandocResourceNotFound _ -> do + report $ CouldNotFetchResource src + "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 + +-- | Extract media from the mediabag into a directory. +extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc +extractMedia dir d = do + media <- getMediaBag + case [fp | (fp, _, _) <- mediaDirectory media] of + [] -> return d + fps -> do + liftIO $ extractMediaBag True dir media + return $ walk (adjustImagePath dir fps) d + +adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline +adjustImagePath dir paths (Image attr lab (src, tit)) + | src `elem` paths = Image attr lab (dir ++ "/" ++ src, tit) +adjustImagePath _ _ x = x + data PureState = PureState { stStdGen :: StdGen , stWord8Store :: [Word8] -- should be -- inifinite, -- cgit v1.2.3 From 6b086acae8f20ad46ca92139e47e516302280e94 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 7 May 2017 21:03:18 +0200 Subject: Rename fillMedia -> fillMediaBag. --- src/Text/Pandoc/App.hs | 4 ++-- src/Text/Pandoc/Class.hs | 6 +++--- src/Text/Pandoc/PDF.hs | 5 +++-- 3 files changed, 8 insertions(+), 7 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 6bc345d73..f340259f3 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -70,7 +70,7 @@ import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, - extractMedia, fillMedia) + extractMedia, fillMediaBag) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) import Text.Pandoc.PDF (makePDF) @@ -414,7 +414,7 @@ convertWithOpts opts = do runIO' $ do (doc, media) <- withMediaBag $ sourceToDoc sources >>= ( (if isJust (optExtractMedia opts) - then fillMedia (writerSourceURL writerOptions) + then fillMediaBag (writerSourceURL writerOptions) else return) >=> maybe return extractMedia (optExtractMedia opts) >=> return . flip (foldr addMetadata) metadata diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 7407d0799..4ef56ec33 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -61,7 +61,7 @@ module Text.Pandoc.Class ( PandocMonad(..) , runIOorExplode , runPure , withMediaBag - , fillMedia + , fillMediaBag , extractMedia ) where @@ -346,8 +346,8 @@ withPaths (p:ps) action fp = (\_ -> withPaths ps action fp) -- | Traverse tree, filling media bag. -fillMedia :: PandocMonad m => Maybe String -> Pandoc -> m Pandoc -fillMedia sourceURL d = walkM handleImage d +fillMediaBag :: PandocMonad m => Maybe String -> Pandoc -> m Pandoc +fillMediaBag sourceURL d = walkM handleImage d where handleImage :: PandocMonad m => Inline -> m Inline handleImage (Image attr lab (src, tit)) = catchError (do (bs, mt) <- fetchItem sourceURL src diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 240da3ef0..7097337e2 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -63,7 +63,8 @@ import Text.Pandoc.Writers.Shared (getField, metaToJSON) import Data.List (intercalate) #endif import Text.Pandoc.Class (PandocIO, report, runIO, runIOorExplode, - setMediaBag, setVerbosity, fillMedia, extractMedia) + setMediaBag, setVerbosity, + fillMediaBag, extractMedia) import Text.Pandoc.Logging #ifdef _WINDOWS @@ -138,7 +139,7 @@ handleImages verbosity opts mediabag tmpdir doc = do doc' <- runIOorExplode $ do setVerbosity verbosity setMediaBag mediabag - fillMedia (writerSourceURL opts) doc >>= + fillMediaBag (writerSourceURL opts) doc >>= extractMedia tmpdir walkM (convertImages verbosity tmpdir) doc' -- 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/App.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 6b8240fc2f45ced4f16403316cab76df15ceaf7a Mon Sep 17 00:00:00 2001 From: Stefan Dresselhaus Date: Wed, 17 May 2017 15:13:35 +0200 Subject: Add `--eol` flag and writer option to control line endings. * Add `--eol=crlf|lf` CLI option. * Add `optEol` to `WriterOptions` [API change] * In `Text.Pandoc.UTF8`, add new functions parameterized on `Newline`: `writeFileWith`, `putStrWith`, `putStrLnWith`, `hPutStrWith`, `hPutStrLnWith`. [API change] * Document option in MANUAL.txt. Closes #3663. Closes #2097. --- MANUAL.txt | 7 +++++++ src/Text/Pandoc/App.hs | 26 +++++++++++++++++++++----- src/Text/Pandoc/UTF8.hs | 41 +++++++++++++++++++++++++++++++++-------- 3 files changed, 61 insertions(+), 13 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/MANUAL.txt b/MANUAL.txt index f41d96ffa..d99cd0600 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -593,7 +593,14 @@ General writer options : Print a system default data file. Files in the user data directory are ignored. +`--eol=crlf`|`lf` + +: Manually specify line endings: `crlf` (Windows) or `lf` + (MacOS/linux/unix). The default is to use the line endings + appropriate for the OS. + `--dpi`=*NUMBER* + : Specify the dpi (dots per inch) value for conversion from pixels to inch/centimeters and vice versa. The default is 96dpi. Technically, the correct term would be ppi (pixels per inch). diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 157100507..9c8e1bde4 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -65,7 +65,7 @@ import System.Directory (Permissions (..), doesFileExist, findExecutable, import System.Environment (getArgs, getEnvironment, getProgName) import System.Exit (ExitCode (..), exitSuccess) import System.FilePath -import System.IO (stdout) +import System.IO (stdout, nativeNewline, Newline(..)) import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) @@ -411,6 +411,8 @@ convertWithOpts opts = do return $ ("csl", jatsEncoded) : optMetadata opts else return $ optMetadata opts + let eol = fromMaybe nativeNewline $ optEol opts + runIO' $ do (doc, media) <- withMediaBag $ sourceToDoc sources >>= ( (if isJust (optExtractMedia opts) @@ -463,7 +465,7 @@ convertWithOpts opts = do else id output <- f writerOptions doc selfcontain (output ++ ['\n' | not standalone]) >>= - writerFn outputFile . handleEntities + writerFn eol outputFile . handleEntities type Transform = Pandoc -> Pandoc @@ -567,6 +569,7 @@ data Opt = Opt , optIncludeBeforeBody :: [FilePath] -- ^ Files to include before , optIncludeAfterBody :: [FilePath] -- ^ Files to include after body , optIncludeInHeader :: [FilePath] -- ^ Files to include in header + , optEol :: Maybe Newline -- ^ Enforce line-endings } -- | Defaults for command-line options. @@ -635,6 +638,7 @@ defaultOpts = Opt , optIncludeBeforeBody = [] , optIncludeAfterBody = [] , optIncludeInHeader = [] + , optEol = Nothing } addMetadata :: (String, String) -> Pandoc -> Pandoc @@ -783,9 +787,9 @@ writeFnBinary :: MonadIO m => FilePath -> B.ByteString -> m () writeFnBinary "-" = liftIO . B.putStr writeFnBinary f = liftIO . B.writeFile (UTF8.encodePath f) -writerFn :: MonadIO m => FilePath -> String -> m () -writerFn "-" = liftIO . UTF8.putStr -writerFn f = liftIO . UTF8.writeFile f +writerFn :: MonadIO m => Newline -> FilePath -> String -> m () +writerFn eol "-" = liftIO . UTF8.putStrWith eol +writerFn eol f = liftIO . UTF8.writeFileWith eol f lookupHighlightStyle :: Maybe String -> IO (Maybe Style) lookupHighlightStyle Nothing = return Nothing @@ -958,6 +962,18 @@ options = "NUMBER") "" -- "Dpi (default 96)" + , Option "" ["eol"] + (ReqArg + (\arg opt -> + case toLower <$> arg of + "crlf" -> return opt { optEol = Just CRLF } + "lf" -> return opt { optEol = Just LF } + -- mac-syntax (cr) is not supported in ghc-base. + _ -> E.throwIO $ PandocOptionError + "--eol must be one of crlf (Windows), lf (Unix)") + "crlf|lf") + "" -- "EOL (default OS-dependent)" + , Option "" ["wrap"] (ReqArg (\arg opt -> diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs index e27a24e63..84043d4cb 100644 --- a/src/Text/Pandoc/UTF8.hs +++ b/src/Text/Pandoc/UTF8.hs @@ -28,11 +28,16 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA UTF-8 aware string IO functions that will work with GHC 6.10, 6.12, or 7. -} module Text.Pandoc.UTF8 ( readFile - , writeFile , getContents + , writeFileWith + , writeFile + , putStrWith , putStr + , putStrLnWith , putStrLn + , hPutStrWith , hPutStr + , hPutStrLnWith , hPutStrLn , hGetContents , toString @@ -61,23 +66,43 @@ readFile f = do h <- openFile (encodePath f) ReadMode hGetContents h -writeFile :: FilePath -> String -> IO () -writeFile f s = withFile (encodePath f) WriteMode $ \h -> hPutStr h s - getContents :: IO String getContents = hGetContents stdin +writeFileWith :: Newline -> FilePath -> String -> IO () +writeFileWith eol f s = + withFile (encodePath f) WriteMode $ \h -> hPutStrWith eol h s + +writeFile :: FilePath -> String -> IO () +writeFile = writeFileWith nativeNewline + +putStrWith :: Newline -> String -> IO () +putStrWith eol s = hPutStrWith eol stdout s + putStr :: String -> IO () -putStr s = hPutStr stdout s +putStr = putStrWith nativeNewline + +putStrLnWith :: Newline -> String -> IO () +putStrLnWith eol s = hPutStrLnWith eol stdout s putStrLn :: String -> IO () -putStrLn s = hPutStrLn stdout s +putStrLn = putStrLnWith nativeNewline + +hPutStrWith :: Newline -> Handle -> String -> IO () +hPutStrWith eol h s = + hSetNewlineMode h (NewlineMode eol eol) >> + hSetEncoding h utf8 >> IO.hPutStr h s hPutStr :: Handle -> String -> IO () -hPutStr h s = hSetEncoding h utf8 >> IO.hPutStr h s +hPutStr = hPutStrWith nativeNewline + +hPutStrLnWith :: Newline -> Handle -> String -> IO () +hPutStrLnWith eol h s = + hSetNewlineMode h (NewlineMode eol eol) >> + hSetEncoding h utf8 >> IO.hPutStrLn h s hPutStrLn :: Handle -> String -> IO () -hPutStrLn h s = hSetEncoding h utf8 >> IO.hPutStrLn h s +hPutStrLn = hPutStrLnWith nativeNewline hGetContents :: Handle -> IO String hGetContents = fmap toString . B.hGetContents -- cgit v1.2.3 From fd6e65b00ffc628488c27171f7dd9ab833c436c6 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 20 May 2017 21:43:53 +0200 Subject: Added `--resource-path=SEARCHPATH` command line option. SEARCHPATH is separated by the usual character, depending on OS (: on unix, ; on windows). Note: This does not yet work for PDF output, because the routine that creates PDFs runs outside PandocMonad. (This has to do with its use of inTemporaryDirectory and its interaction with our exceptions.) The best solution would be to figure out how to move the PDF creation routines into PandocMonad. Second-best, just pass an extra parameter in? See #852. --- MANUAL.txt | 6 ++++++ src/Text/Pandoc/App.hs | 13 ++++++++++++- 2 files changed, 18 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/MANUAL.txt b/MANUAL.txt index 51b324817..8c65789b9 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -690,6 +690,12 @@ General writer options repeatedly to include multiple files. They will be included in the order specified. Implies `--standalone`. +`--resource-path=`*SEARCHPATH* + +: List of paths to search for images and other resources. + The paths should be separated by `:` on linux, unix, and + MacOS systems, and by `;` on Windows. + Options affecting specific writers ---------------------------------- diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 9c8e1bde4..a4967e5d1 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -70,7 +70,7 @@ import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, - extractMedia, fillMediaBag) + extractMedia, fillMediaBag, setResourcePath) import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.Lua ( runLuaFilter ) import Text.Pandoc.PDF (makePDF) @@ -414,6 +414,7 @@ convertWithOpts opts = do let eol = fromMaybe nativeNewline $ optEol opts runIO' $ do + setResourcePath $ "." : (optResourcePath opts) (doc, media) <- withMediaBag $ sourceToDoc sources >>= ( (if isJust (optExtractMedia opts) then fillMediaBag (writerSourceURL writerOptions) @@ -569,6 +570,7 @@ data Opt = Opt , optIncludeBeforeBody :: [FilePath] -- ^ Files to include before , optIncludeAfterBody :: [FilePath] -- ^ Files to include after body , optIncludeInHeader :: [FilePath] -- ^ Files to include in header + , optResourcePath :: [FilePath] -- ^ Path to search for images etc , optEol :: Maybe Newline -- ^ Enforce line-endings } @@ -638,6 +640,7 @@ defaultOpts = Opt , optIncludeBeforeBody = [] , optIncludeAfterBody = [] , optIncludeInHeader = [] + , optResourcePath = [] , optEol = Nothing } @@ -1052,6 +1055,14 @@ options = "FILE") "" -- "File to include after document body" + , Option "" ["resource-path"] + (ReqArg + (\arg opt -> return opt { optResourcePath = + splitSearchPath arg }) + "SEARCHPATH") + "" -- "Paths to search for images and other resources" + + , Option "" ["self-contained"] (NoArg (\opt -> return opt { optSelfContained = True, -- cgit v1.2.3 From 8c1b81bbef7125a9a2fde9d6894578f06bf4cedd Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 21 May 2017 08:59:06 +0200 Subject: Finished implemtation of `--resource-path`. * Default is just working directory. * Working directory must be explicitly specifide if `--resource-path` option is used. --- MANUAL.txt | 8 +++++++- src/Text/Pandoc/App.hs | 4 ++-- src/Text/Pandoc/Readers/LaTeX.hs | 4 ++-- 3 files changed, 11 insertions(+), 5 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/MANUAL.txt b/MANUAL.txt index 8c65789b9..c7aa299c4 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -694,7 +694,13 @@ General writer options : List of paths to search for images and other resources. The paths should be separated by `:` on linux, unix, and - MacOS systems, and by `;` on Windows. + MacOS systems, and by `;` on Windows. If `--resource-path` + is not specified, the default resource path is the working + directory. Note that, if `--resource-path` is specified, + the working directory must be explicitly listed or it + will not be searched. For example: + `--resource-path=.:test` will search the working directory + and the `test` subdirectory, in that order. Options affecting specific writers ---------------------------------- diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index a4967e5d1..c874a2cde 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -414,7 +414,7 @@ convertWithOpts opts = do let eol = fromMaybe nativeNewline $ optEol opts runIO' $ do - setResourcePath $ "." : (optResourcePath opts) + setResourcePath (optResourcePath opts) (doc, media) <- withMediaBag $ sourceToDoc sources >>= ( (if isJust (optExtractMedia opts) then fillMediaBag (writerSourceURL writerOptions) @@ -640,7 +640,7 @@ defaultOpts = Opt , optIncludeBeforeBody = [] , optIncludeAfterBody = [] , optIncludeInHeader = [] - , optResourcePath = [] + , optResourcePath = ["."] , optEol = Nothing } diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 30c788666..84758d309 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -46,7 +46,7 @@ import Safe (minimumDef) import System.FilePath (addExtension, replaceExtension, takeExtension) import Text.Pandoc.Builder import Text.Pandoc.Class (PandocMonad, PandocPure, lookupEnv, readFileFromDirs, - report, setResourcePath) + report, setResourcePath, getResourcePath) import Text.Pandoc.Highlighting (fromListingsLanguage, languagesByExtension) import Text.Pandoc.ImageSize (numUnit, showFl) import Text.Pandoc.Logging @@ -417,7 +417,7 @@ blockCommands = M.fromList $ graphicsPath :: PandocMonad m => LP m Blocks graphicsPath = do ps <- bgroup *> (manyTill braced egroup) - setResourcePath (".":ps) + getResourcePath >>= setResourcePath . (++ ps) return mempty addMeta :: PandocMonad m => ToMetaValue a => String -> a -> LP m () -- cgit v1.2.3 From aa1e39858dd0ad25fd5e0cf0e2e19182bd4f157b Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 21 May 2017 11:42:50 +0200 Subject: Text.Pandoc.App: ToJSON and FromJSON instances for Opts. This can be used e.g. to pass options via web interface, such as trypandoc. --- src/Text/Pandoc/App.hs | 27 ++++++++++++++++++++++----- src/Text/Pandoc/Logging.hs | 10 ++++++++++ src/Text/Pandoc/Options.hs | 34 ++++++++++++++++++++++++++++++++++ 3 files changed, 66 insertions(+), 5 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index c874a2cde..eee72fd3c 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -1,6 +1,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} +{-# LANGUAGE DeriveGeneric #-} {- Copyright (C) 2006-2017 John MacFarlane @@ -42,12 +43,14 @@ import qualified Control.Exception as E import Control.Monad.Except (throwError) import Control.Monad import Control.Monad.Trans -import Data.Aeson (eitherDecode', encode) +import Data.Aeson (eitherDecode', encode, ToJSON(..), FromJSON(..), + genericToEncoding, defaultOptions) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as B import Data.Char (toLower, toUpper) import qualified Data.Set as Set import Data.Foldable (foldrM) +import GHC.Generics import Data.List (intercalate, isPrefixOf, isSuffixOf, sort) import qualified Data.Map as M import Data.Maybe (fromMaybe, isJust, isNothing) @@ -65,7 +68,8 @@ import System.Directory (Permissions (..), doesFileExist, findExecutable, import System.Environment (getArgs, getEnvironment, getProgName) import System.Exit (ExitCode (..), exitSuccess) import System.FilePath -import System.IO (stdout, nativeNewline, Newline(..)) +import System.IO (stdout, nativeNewline) +import qualified System.IO as IO (Newline(..)) import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) @@ -86,6 +90,12 @@ import System.Posix.IO (stdOutput) import System.Posix.Terminal (queryTerminal) #endif +data Newline = LF | CRLF deriving (Show, Generic) + +instance ToJSON Newline where + toEncoding = genericToEncoding defaultOptions +instance FromJSON Newline + parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt parseOptions options' defaults = do rawArgs <- map UTF8.decodeArg <$> getArgs @@ -411,7 +421,10 @@ convertWithOpts opts = do return $ ("csl", jatsEncoded) : optMetadata opts else return $ optMetadata opts - let eol = fromMaybe nativeNewline $ optEol opts + let eol = case optEol opts of + Just CRLF -> IO.CRLF + Just LF -> IO.LF + Nothing -> nativeNewline runIO' $ do setResourcePath (optResourcePath opts) @@ -572,7 +585,11 @@ data Opt = Opt , optIncludeInHeader :: [FilePath] -- ^ Files to include in header , optResourcePath :: [FilePath] -- ^ Path to search for images etc , optEol :: Maybe Newline -- ^ Enforce line-endings - } + } deriving (Generic, Show) + +instance ToJSON Opt where + toEncoding = genericToEncoding defaultOptions +instance FromJSON Opt -- | Defaults for command-line options. defaultOpts :: Opt @@ -790,7 +807,7 @@ writeFnBinary :: MonadIO m => FilePath -> B.ByteString -> m () writeFnBinary "-" = liftIO . B.putStr writeFnBinary f = liftIO . B.writeFile (UTF8.encodePath f) -writerFn :: MonadIO m => Newline -> FilePath -> String -> m () +writerFn :: MonadIO m => IO.Newline -> FilePath -> String -> m () writerFn eol "-" = liftIO . UTF8.putStrWith eol writerFn eol f = liftIO . UTF8.writeFileWith eol f diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index 2cca4b7d3..bf7f33d29 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -39,6 +39,7 @@ module Text.Pandoc.Logging ( , messageVerbosity ) where +import Control.Monad (mzero) import Data.Aeson import Data.Aeson.Encode.Pretty (Config (..), defConfig, encodePretty', keyOrder) @@ -56,6 +57,15 @@ data Verbosity = ERROR | WARNING | INFO | DEBUG instance ToJSON Verbosity where toJSON x = toJSON (show x) +instance FromJSON Verbosity where + parseJSON (String t) = + case t of + "ERROR" -> return ERROR + "WARNING" -> return WARNING + "INFO" -> return INFO + "DEBUG" -> return DEBUG + _ -> mzero + parseJSON _ = mzero data LogMessage = SkippedContent String SourcePos diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 6757c6782..c7211c86e 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -45,6 +45,8 @@ module Text.Pandoc.Options ( module Text.Pandoc.Extensions , def , isEnabled ) where +import Data.Aeson (ToJSON(..), FromJSON(..), + genericToEncoding, defaultOptions) import Data.Data (Data) import Data.Default import qualified Data.Set as Set @@ -104,17 +106,29 @@ data HTMLMathMethod = PlainMath | KaTeX String String -- url of stylesheet and katex.js deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON HTMLMathMethod where + toEncoding = genericToEncoding defaultOptions +instance FromJSON HTMLMathMethod + data CiteMethod = Citeproc -- use citeproc to render them | Natbib -- output natbib cite commands | Biblatex -- output biblatex cite commands deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON CiteMethod where + toEncoding = genericToEncoding defaultOptions +instance FromJSON CiteMethod + -- | Methods for obfuscating email addresses in HTML. data ObfuscationMethod = NoObfuscation | ReferenceObfuscation | JavascriptObfuscation deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON ObfuscationMethod where + toEncoding = genericToEncoding defaultOptions +instance FromJSON ObfuscationMethod + -- | Varieties of HTML slide shows. data HTMLSlideVariant = S5Slides | SlidySlides @@ -124,18 +138,30 @@ data HTMLSlideVariant = S5Slides | NoSlides deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON HTMLSlideVariant where + toEncoding = genericToEncoding defaultOptions +instance FromJSON HTMLSlideVariant + -- | Options for accepting or rejecting MS Word track-changes. data TrackChanges = AcceptChanges | RejectChanges | AllChanges deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON TrackChanges where + toEncoding = genericToEncoding defaultOptions +instance FromJSON TrackChanges + -- | Options for wrapping text in the output. data WrapOption = WrapAuto -- ^ Automatically wrap to width | WrapNone -- ^ No non-semantic newlines | WrapPreserve -- ^ Preserve wrapping of input source deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON WrapOption where + toEncoding = genericToEncoding defaultOptions +instance FromJSON WrapOption + -- | Options defining the type of top-level headers. data TopLevelDivision = TopLevelPart -- ^ Top-level headers become parts | TopLevelChapter -- ^ Top-level headers become chapters @@ -144,12 +170,20 @@ data TopLevelDivision = TopLevelPart -- ^ Top-level headers become parts -- heuristics deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON TopLevelDivision where + toEncoding = genericToEncoding defaultOptions +instance FromJSON TopLevelDivision + -- | Locations for footnotes and references in markdown output data ReferenceLocation = EndOfBlock -- ^ End of block | EndOfSection -- ^ prior to next section header (or end of document) | EndOfDocument -- ^ at end of document deriving (Show, Read, Eq, Data, Typeable, Generic) +instance ToJSON ReferenceLocation where + toEncoding = genericToEncoding defaultOptions +instance FromJSON ReferenceLocation + -- | Options for writers data WriterOptions = WriterOptions { writerTemplate :: Maybe String -- ^ Template to use -- cgit v1.2.3 From 4d1e9b8e4198990e515185fd3a0d6047f7999a61 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Mon, 22 May 2017 10:10:04 +0200 Subject: Let `--eol` take `native` as an argument. Add `Native` to the `LineEnding` type. Make `optEol` a `Native` rather than `Maybe Native`. --- MANUAL.txt | 9 +++++---- src/Text/Pandoc/App.hs | 25 +++++++++++++------------ 2 files changed, 18 insertions(+), 16 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/MANUAL.txt b/MANUAL.txt index c7aa299c4..ae518054d 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -593,11 +593,12 @@ General writer options : Print a system default data file. Files in the user data directory are ignored. -`--eol=crlf`|`lf` +`--eol=crlf`|`lf`|`native` -: Manually specify line endings: `crlf` (Windows) or `lf` - (MacOS/linux/unix). The default is to use the line endings - appropriate for the OS. +: Manually specify line endings: `crlf` (Windows), `lf` + (MacOS/linux/unix), or `native` (line endings appropriate + to the OS on which pandoc is being run). The default is + `native`. `--dpi`=*NUMBER* diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index eee72fd3c..97954764a 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -90,11 +90,11 @@ import System.Posix.IO (stdOutput) import System.Posix.Terminal (queryTerminal) #endif -data Newline = LF | CRLF deriving (Show, Generic) +data LineEnding = LF | CRLF | Native deriving (Show, Generic) -instance ToJSON Newline where +instance ToJSON LineEnding where toEncoding = genericToEncoding defaultOptions -instance FromJSON Newline +instance FromJSON LineEnding parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt parseOptions options' defaults = do @@ -422,9 +422,9 @@ convertWithOpts opts = do else return $ optMetadata opts let eol = case optEol opts of - Just CRLF -> IO.CRLF - Just LF -> IO.LF - Nothing -> nativeNewline + CRLF -> IO.CRLF + LF -> IO.LF + Native -> nativeNewline runIO' $ do setResourcePath (optResourcePath opts) @@ -584,7 +584,7 @@ data Opt = Opt , optIncludeAfterBody :: [FilePath] -- ^ Files to include after body , optIncludeInHeader :: [FilePath] -- ^ Files to include in header , optResourcePath :: [FilePath] -- ^ Path to search for images etc - , optEol :: Maybe Newline -- ^ Enforce line-endings + , optEol :: LineEnding -- ^ Style of line-endings to use } deriving (Generic, Show) instance ToJSON Opt where @@ -658,7 +658,7 @@ defaultOpts = Opt , optIncludeAfterBody = [] , optIncludeInHeader = [] , optResourcePath = ["."] - , optEol = Nothing + , optEol = Native } addMetadata :: (String, String) -> Pandoc -> Pandoc @@ -986,12 +986,13 @@ options = (ReqArg (\arg opt -> case toLower <$> arg of - "crlf" -> return opt { optEol = Just CRLF } - "lf" -> return opt { optEol = Just LF } + "crlf" -> return opt { optEol = CRLF } + "lf" -> return opt { optEol = LF } + "native" -> return opt { optEol = Native } -- mac-syntax (cr) is not supported in ghc-base. _ -> E.throwIO $ PandocOptionError - "--eol must be one of crlf (Windows), lf (Unix)") - "crlf|lf") + "--eol must be crlf, lf, or native") + "crlf|lf|native") "" -- "EOL (default OS-dependent)" , Option "" ["wrap"] -- 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/App.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 00d8585d8f6cfafea536c59912f3de9d53ef3193 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 1 Jun 2017 14:14:42 +0200 Subject: Trivial renaming. --- src/Text/Pandoc/App.hs | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 845146f34..d8409a00f 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -1423,8 +1423,8 @@ options = map ("--" ++) longs let allopts = unwords (concatMap optnames options) UTF8.hPutStrLn stdout $ printf tpl allopts - (unwords readers'names) - (unwords writers'names) + (unwords readersNames) + (unwords writersNames) (unwords $ map fst highlightingStyles) ddir exitSuccess )) @@ -1433,14 +1433,14 @@ options = , Option "" ["list-input-formats"] (NoArg (\_ -> do - mapM_ (UTF8.hPutStrLn stdout) readers'names + mapM_ (UTF8.hPutStrLn stdout) readersNames exitSuccess )) "" , Option "" ["list-output-formats"] (NoArg (\_ -> do - mapM_ (UTF8.hPutStrLn stdout) writers'names + mapM_ (UTF8.hPutStrLn stdout) writersNames exitSuccess )) "" @@ -1544,11 +1544,11 @@ uppercaseFirstLetter :: String -> String uppercaseFirstLetter (c:cs) = toUpper c : cs uppercaseFirstLetter [] = [] -readers'names :: [String] -readers'names = sort (map fst (readers :: [(String, Reader PandocIO)])) +readersNames :: [String] +readersNames = sort (map fst (readers :: [(String, Reader PandocIO)])) -writers'names :: [String] -writers'names = sort (map fst (writers :: [(String, Writer PandocIO)])) +writersNames :: [String] +writersNames = sort (map fst (writers :: [(String, Writer PandocIO)])) splitField :: String -> (String, String) splitField s = -- cgit v1.2.3 From c2eb7d085743b8a78d4580d5a07baa899fa9b64e Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 1 Jun 2017 14:16:17 +0200 Subject: Use isNothing. --- src/Text/Pandoc/App.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index d8409a00f..bc1d4ce18 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -413,8 +413,8 @@ convertWithOpts opts = do mconcat <$> mapM (readFile' >=> r readerOpts) sources metadata <- if format == "jats" && - lookup "csl" (optMetadata opts) == Nothing && - lookup "citation-style" (optMetadata opts) == Nothing + isNothing (lookup "csl" (optMetadata opts)) && + isNothing (lookup "citation-style" (optMetadata opts)) then do jatsCSL <- readDataFile datadir "jats.csl" let jatsEncoded = makeDataURI ("application/xml", jatsCSL) -- cgit v1.2.3 From 0cf6511f16388fc2bb71cffc733a704d20cfe3e3 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 1 Jun 2017 15:09:38 +0200 Subject: Some hlint refactoring. --- pandoc.hs | 6 +++--- src/Text/Pandoc/App.hs | 37 ++++++++++++++++++------------------- src/Text/Pandoc/Class.hs | 29 +++++++++++++---------------- 3 files changed, 34 insertions(+), 38 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/pandoc.hs b/pandoc.hs index 6135aec03..970fc8778 100644 --- a/pandoc.hs +++ b/pandoc.hs @@ -1,5 +1,5 @@ {-# LANGUAGE CPP #-} -{-# LANGUAGE PatternGuards #-} + {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {- @@ -33,9 +33,9 @@ Parses command-line options and calls the appropriate readers and writers. -} module Main where -import Text.Pandoc.App (convertWithOpts, defaultOpts, options, parseOptions) -import Text.Pandoc.Error (handleError, PandocError) import qualified Control.Exception as E +import Text.Pandoc.App (convertWithOpts, defaultOpts, options, parseOptions) +import Text.Pandoc.Error (PandocError, handleError) main :: IO () main = E.catch (parseOptions options defaultOpts >>= convertWithOpts) diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index bc1d4ce18..58044860b 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -1,7 +1,7 @@ {-# LANGUAGE CPP #-} +{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} -{-# LANGUAGE DeriveGeneric #-} {- Copyright (C) 2006-2017 John MacFarlane @@ -40,47 +40,47 @@ module Text.Pandoc.App ( ) where import Control.Applicative ((<|>)) import qualified Control.Exception as E -import Control.Monad.Except (throwError) import Control.Monad +import Control.Monad.Except (throwError) import Control.Monad.Trans -import Data.Aeson (eitherDecode', encode, ToJSON(..), FromJSON(..), - genericToEncoding, defaultOptions) +import Data.Aeson (FromJSON (..), ToJSON (..), defaultOptions, eitherDecode', + encode, genericToEncoding) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as B import Data.Char (toLower, toUpper) -import qualified Data.Set as Set import Data.Foldable (foldrM) -import GHC.Generics import Data.List (intercalate, isPrefixOf, isSuffixOf, sort) import qualified Data.Map as M import Data.Maybe (fromMaybe, isJust, isNothing) +import qualified Data.Set as Set import qualified Data.Text as T import Data.Yaml (decode) import qualified Data.Yaml as Yaml +import GHC.Generics import Network.URI (URI (..), parseURI) import Paths_pandoc (getDataDir) import Skylighting (Style, Syntax (..), defaultSyntaxMap, parseTheme) -import Skylighting.Parser (missingIncludes, parseSyntaxDefinition, - addSyntaxDefinition) +import Skylighting.Parser (addSyntaxDefinition, missingIncludes, + parseSyntaxDefinition) import System.Console.GetOpt import System.Directory (Permissions (..), doesFileExist, findExecutable, getAppUserDataDirectory, getPermissions) import System.Environment (getArgs, getEnvironment, getProgName) import System.Exit (ExitCode (..), exitSuccess) import System.FilePath -import System.IO (stdout, nativeNewline) -import qualified System.IO as IO (Newline(..)) +import System.IO (nativeNewline, stdout) +import qualified System.IO as IO (Newline (..)) import System.IO.Error (isDoesNotExistError) import Text.Pandoc import Text.Pandoc.Builder (setMeta) -import Text.Pandoc.Class (PandocIO, getLog, withMediaBag, - extractMedia, fillMediaBag, setResourcePath) +import Text.Pandoc.Class (PandocIO, extractMedia, fillMediaBag, getLog, + setResourcePath, withMediaBag) import Text.Pandoc.Highlighting (highlightingStyles) -import Text.Pandoc.Lua ( runLuaFilter ) +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 (isURI, headerShift, openURL, readDataFile, +import Text.Pandoc.SelfContained (makeDataURI, makeSelfContained) +import Text.Pandoc.Shared (headerShift, isURI, openURL, readDataFile, readDataFileUTF8, safeRead, tabFilter) import qualified Text.Pandoc.UTF8 as UTF8 import Text.Pandoc.XML (toEntities) @@ -243,10 +243,9 @@ convertWithOpts opts = do withList f (x:xs) vars = f x vars >>= withList f xs variables <- - return (("outputfile", optOutputFile opts) : optVariables opts) - >>= + withList (addStringAsVariable "sourcefile") - (reverse $ optInputFiles opts) + (reverse $ optInputFiles opts) (("outputfile", optOutputFile opts) : optVariables opts) -- we reverse this list because, unlike -- the other option lists here, it is -- not reversed when parsed from CLI arguments. @@ -796,7 +795,7 @@ readURI :: FilePath -> PandocIO String readURI src = do res <- liftIO $ openURL src case res of - Left e -> throwError $ PandocHttpError src e + Left e -> throwError $ PandocHttpError src e Right (contents, _) -> return $ UTF8.toString contents readFile' :: MonadIO m => FilePath -> m B.ByteString diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index f47efb2aa..49b20bd30 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -1,10 +1,8 @@ {-# LANGUAGE DeriveFunctor #-} -{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE StandaloneDeriving #-} {- Copyright (C) 2016 Jesse Rosenthal @@ -156,7 +154,7 @@ report :: PandocMonad m => LogMessage -> m () report msg = do verbosity <- getsCommonState stVerbosity let level = messageVerbosity msg - when (level <= verbosity) $ do + when (level <= verbosity) $ logOutput msg unless (level == DEBUG) $ modifyCommonState $ \st -> st{ stLog = msg : stLog st } @@ -224,7 +222,7 @@ runIO :: PandocIO a -> IO (Either PandocError a) runIO ma = flip evalStateT def $ runExceptT $ unPandocIO ma withMediaBag :: PandocMonad m => m a -> m (a, MediaBag) -withMediaBag ma = ((,)) <$> ma <*> getMediaBag +withMediaBag ma = (,) <$> ma <*> getMediaBag runIOorExplode :: PandocIO a -> IO a runIOorExplode ma = runIO ma >>= handleError @@ -250,7 +248,7 @@ instance PandocMonad PandocIO where getCurrentTime = liftIO IO.getCurrentTime getCurrentTimeZone = liftIO IO.getCurrentTimeZone newStdGen = liftIO IO.newStdGen - newUniqueHash = hashUnique <$> (liftIO IO.newUnique) + newUniqueHash = hashUnique <$> liftIO IO.newUnique openURL u = do report $ Fetching u res <- liftIO (IO.openURL u) @@ -266,7 +264,7 @@ instance PandocMonad PandocIO where putCommonState x = PandocIO $ lift $ put x logOutput msg = liftIO $ do UTF8.hPutStr stderr $ "[" ++ - (map toLower $ show (messageVerbosity msg)) ++ "] " + map toLower (show (messageVerbosity msg)) ++ "] " alertIndent $ lines $ showLogMessage msg alertIndent :: [String] -> IO () @@ -297,14 +295,14 @@ fetchItem :: PandocMonad m fetchItem sourceURL s = do mediabag <- getMediaBag case lookupMedia s mediabag of - Just (mime, bs) -> return $ (BL.toStrict bs, Just mime) + Just (mime, bs) -> return (BL.toStrict bs, Just mime) Nothing -> downloadOrRead sourceURL s downloadOrRead :: PandocMonad m => Maybe String -> String -> m (B.ByteString, Maybe MimeType) -downloadOrRead sourceURL s = do +downloadOrRead sourceURL s = case (sourceURL >>= parseURIReference' . ensureEscaped, ensureEscaped s) of (Just u, s') -> -- try fetching from relative path at source @@ -367,7 +365,7 @@ fillMediaBag sourceURL d = walkM handleImage d let fname = basename <.> ext insertMedia fname mt bs' return $ Image attr lab (fname, tit)) - (\e -> do + (\e -> case e of PandocResourceNotFound _ -> do report $ CouldNotFetchResource src @@ -434,7 +432,7 @@ instance Default PureState where getPureState :: PandocPure PureState -getPureState = PandocPure $ lift $ lift $ get +getPureState = PandocPure $ lift $ lift get getsPureState :: (PureState -> a) -> PandocPure a getsPureState f = f <$> getPureState @@ -505,16 +503,16 @@ instance PandocMonad PandocPure where case infoFileContents <$> getFileInfo fp fps of Just bs -> return bs Nothing -> throwError $ PandocResourceNotFound fp - readDataFile Nothing "reference.docx" = do + readDataFile Nothing "reference.docx" = (B.concat . BL.toChunks . fromArchive) <$> getsPureState stReferenceDocx - readDataFile Nothing "reference.odt" = do + readDataFile Nothing "reference.odt" = (B.concat . BL.toChunks . fromArchive) <$> getsPureState stReferenceODT readDataFile Nothing fname = do let fname' = if fname == "MANUAL.txt" then fname else "data" fname readFileStrict fname' readDataFile (Just userDir) fname = do userDirFiles <- getsPureState stUserDataDir - case infoFileContents <$> (getFileInfo (userDir fname) userDirFiles) of + case infoFileContents <$> getFileInfo (userDir fname) userDirFiles of Just bs -> return bs Nothing -> readDataFile Nothing fname @@ -524,12 +522,12 @@ instance PandocMonad PandocPure where getModificationTime fp = do fps <- getsPureState stFiles - case infoFileMTime <$> (getFileInfo fp fps) of + case infoFileMTime <$> getFileInfo fp fps of Just tm -> return tm Nothing -> throwError $ PandocIOError fp (userError "Can't get modification time") - getCommonState = PandocPure $ lift $ get + getCommonState = PandocPure $ lift get putCommonState x = PandocPure $ lift $ put x logOutput _msg = return () @@ -613,4 +611,3 @@ instance PandocMonad m => PandocMonad (StateT st m) where getCommonState = lift getCommonState putCommonState = lift . putCommonState logOutput = lift . logOutput - -- cgit v1.2.3 From b61a51ee1551c62558369d9bcdaff32de7f3e2eb Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 2 Jun 2017 15:06:14 +0200 Subject: hlint suggestions. --- pandoc.hs | 1 + src/Text/Pandoc/App.hs | 1 + src/Text/Pandoc/CSS.hs | 2 +- src/Text/Pandoc/Class.hs | 2 +- src/Text/Pandoc/Compat/Time.hs | 2 +- src/Text/Pandoc/Error.hs | 2 +- src/Text/Pandoc/Highlighting.hs | 6 ++--- src/Text/Pandoc/ImageSize.hs | 57 ++++++++++++++++++++--------------------- 8 files changed, 37 insertions(+), 36 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/pandoc.hs b/pandoc.hs index 970fc8778..7b749229c 100644 --- a/pandoc.hs +++ b/pandoc.hs @@ -40,3 +40,4 @@ import Text.Pandoc.Error (PandocError, handleError) main :: IO () main = E.catch (parseOptions options defaultOpts >>= convertWithOpts) (\(e :: PandocError) -> handleError (Left e)) + diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 58044860b..4d42b2f2b 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -1554,3 +1554,4 @@ splitField s = case break (`elem` ":=") s of (k,_:v) -> (k,v) (k,[]) -> (k,"true") + diff --git a/src/Text/Pandoc/CSS.hs b/src/Text/Pandoc/CSS.hs index 3e2fd6309..41be1ea13 100644 --- a/src/Text/Pandoc/CSS.hs +++ b/src/Text/Pandoc/CSS.hs @@ -11,7 +11,7 @@ import Text.Parsec.String ruleParser :: Parser (String, String) ruleParser = do p <- many1 (noneOf ":") <* char ':' - v <- many1 (noneOf ":;") <* (optional $ char ';') <* spaces + v <- many1 (noneOf ":;") <* optional (char ';') <* spaces return (trim p, trim v) styleAttrParser :: Parser [(String, String)] diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 49b20bd30..91731d396 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -365,7 +365,7 @@ fillMediaBag sourceURL d = walkM handleImage d let fname = basename <.> ext insertMedia fname mt bs' return $ Image attr lab (fname, tit)) - (\e -> + (\e -> case e of PandocResourceNotFound _ -> do report $ CouldNotFetchResource src diff --git a/src/Text/Pandoc/Compat/Time.hs b/src/Text/Pandoc/Compat/Time.hs index b1cde82a4..1de197801 100644 --- a/src/Text/Pandoc/Compat/Time.hs +++ b/src/Text/Pandoc/Compat/Time.hs @@ -27,4 +27,4 @@ where import Data.Time import System.Locale ( defaultTimeLocale ) -#endif +#endif \ No newline at end of file diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index 077413056..3cf381168 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -83,7 +83,7 @@ handleError (Left e) = errColumn = sourceColumn errPos ls = lines input ++ [""] errorInFile = if length ls > errLine - 1 - then concat ["\n", (ls !! (errLine - 1)) + then concat ["\n", ls !! (errLine - 1) ,"\n", replicate (errColumn - 1) ' ' ,"^"] else "" diff --git a/src/Text/Pandoc/Highlighting.hs b/src/Text/Pandoc/Highlighting.hs index 183155d5b..0754aae4c 100644 --- a/src/Text/Pandoc/Highlighting.hs +++ b/src/Text/Pandoc/Highlighting.hs @@ -91,7 +91,7 @@ highlight syntaxmap formatter (_, classes, keyvals) rawCode = , traceOutput = False } classes' = map T.pack classes rawCode' = T.pack rawCode - in case msum (map (\l -> lookupSyntax l syntaxmap) classes') of + in case msum (map ((`lookupSyntax` syntaxmap)) classes') of Nothing | numberLines fmtOpts -> Right $ formatter fmtOpts{ codeClasses = [], @@ -100,9 +100,9 @@ highlight syntaxmap formatter (_, classes, keyvals) rawCode = $ T.lines rawCode' | otherwise -> Left "" Just syntax -> - (formatter fmtOpts{ codeClasses = + formatter fmtOpts{ codeClasses = [T.toLower (sShortname syntax)], - containerClasses = classes' }) <$> + containerClasses = classes' } <$> tokenize tokenizeOpts syntax rawCode' -- Functions for correlating latex listings package's language names diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs index eec8658c5..61ff006cf 100644 --- a/src/Text/Pandoc/ImageSize.hs +++ b/src/Text/Pandoc/ImageSize.hs @@ -120,7 +120,7 @@ imageType img = case B.take 4 img of | findSvgTag img -> return Svg "%!PS" - | (B.take 4 $ B.drop 1 $ B.dropWhile (/=' ') img) == "EPSF" + | B.take 4 (B.drop 1 $ B.dropWhile (/=' ') img) == "EPSF" -> return Eps _ -> mzero @@ -168,7 +168,7 @@ desiredSizeInPoints opts attr s = (Nothing, Nothing) -> sizeInPoints s where ratio = fromIntegral (pxX s) / fromIntegral (pxY s) - getDim dir = case (dimension dir attr) of + getDim dir = case dimension dir attr of Just (Percent _) -> Nothing Just dim -> Just $ inPoints opts dim Nothing -> Nothing @@ -182,7 +182,7 @@ inEm opts dim = (64/11) * inInch opts dim inInch :: WriterOptions -> Dimension -> Double inInch opts dim = case dim of - (Pixel a) -> fromIntegral a / (fromIntegral $ writerDpi opts) + (Pixel a) -> fromIntegral a / fromIntegral (writerDpi opts) (Centimeter a) -> a * 0.3937007874 (Inch a) -> a (Percent _) -> 0 @@ -261,7 +261,7 @@ epsSize img = do case ls' of [] -> mzero (x:_) -> case B.words x of - (_:_:_:ux:uy:[]) -> do + [_, _, _, ux, uy] -> do ux' <- safeRead $ B.unpack ux uy' <- safeRead $ B.unpack uy return ImageSize{ @@ -279,27 +279,26 @@ pngSize img = do let (i, rest') = B.splitAt 4 $ B.drop 4 rest guard $ i == "MHDR" || i == "IHDR" let (sizes, rest'') = B.splitAt 8 rest' - (x,y) <- case map fromIntegral $ unpack $ sizes of + (x,y) <- case map fromIntegral $unpack sizes of ([w1,w2,w3,w4,h1,h2,h3,h4] :: [Integer]) -> return - ((shift w1 24) + (shift w2 16) + (shift w3 8) + w4, - (shift h1 24) + (shift h2 16) + (shift h3 8) + h4) + (shift w1 24 + shift w2 16 + shift w3 8 + w4, + shift h1 24 + shift h2 16 + shift h3 8 + h4) _ -> Nothing -- "PNG parse error" let (dpix, dpiy) = findpHYs rest'' - return $ ImageSize { pxX = x, pxY = y, dpiX = dpix, dpiY = dpiy } + return ImageSize { pxX = x, pxY = y, dpiX = dpix, dpiY = dpiy } findpHYs :: ByteString -> (Integer, Integer) -findpHYs x = - if B.null x || "IDAT" `B.isPrefixOf` x - then (72,72) -- default, no pHYs - else if "pHYs" `B.isPrefixOf` x - then let [x1,x2,x3,x4,y1,y2,y3,y4,u] = map fromIntegral - $ unpack $ B.take 9 $ B.drop 4 x - factor = if u == 1 -- dots per meter - then \z -> z * 254 `div` 10000 - else const 72 - in ( factor $ (shift x1 24) + (shift x2 16) + (shift x3 8) + x4, - factor $ (shift y1 24) + (shift y2 16) + (shift y3 8) + y4 ) - else findpHYs $ B.drop 1 x -- read another byte +findpHYs x + | B.null x || "IDAT" `B.isPrefixOf` x = (72,72) + | "pHYs" `B.isPrefixOf` x = + let [x1,x2,x3,x4,y1,y2,y3,y4,u] = + map fromIntegral $ unpack $ B.take 9 $ B.drop 4 x + factor = if u == 1 -- dots per meter + then \z -> z * 254 `div` 10000 + else const 72 + in ( factor $ (shift x1 24) + (shift x2 16) + (shift x3 8) + x4, + factor $ (shift y1 24) + (shift y2 16) + (shift y3 8) + y4 ) + | otherwise = findpHYs $ B.drop 1 x -- read another byte gifSize :: ByteString -> Maybe ImageSize gifSize img = do @@ -343,16 +342,16 @@ jpegSize img = jfifSize :: ByteString -> Either String ImageSize jfifSize rest = let [dpiDensity,dpix1,dpix2,dpiy1,dpiy2] = map fromIntegral - $ unpack $ B.take 5 $ B.drop 9 $ rest + $ unpack $ B.take 5 $B.drop 9 rest factor = case dpiDensity of 1 -> id - 2 -> \x -> (x * 254 `div` 10) + 2 -> \x -> x * 254 `div` 10 _ -> const 72 dpix = factor (shift dpix1 8 + dpix2) dpiy = factor (shift dpiy1 8 + dpiy2) in case findJfifSize rest of Left msg -> Left msg - Right (w,h) -> Right $ ImageSize { pxX = w + Right (w,h) ->Right ImageSize { pxX = w , pxY = h , dpiX = dpix , dpiY = dpiy } @@ -386,7 +385,7 @@ runGet' p bl = exifSize :: ByteString -> Either String ImageSize -exifSize bs = runGet' header $ bl +exifSize bs =runGet' header bl where bl = BL.fromChunks [bs] header = runExceptT $ exifHeader bl -- NOTE: It would be nicer to do @@ -456,14 +455,13 @@ exifHeader hdr = do Left msg -> throwError msg Right x -> return x return (tag, payload) - entries <- sequence $ replicate (fromIntegral numentries) ifdEntry + entries <- replicateM (fromIntegral numentries) ifdEntry subentries <- case lookup ExifOffset entries of Just (UnsignedLong offset') -> do pos <- lift bytesRead lift $ skip (fromIntegral offset' - (fromIntegral pos - 8)) numsubentries <- lift getWord16 - sequence $ - replicate (fromIntegral numsubentries) ifdEntry + replicateM (fromIntegral numsubentries) ifdEntry _ -> return [] let allentries = entries ++ subentries (wdth, hght) <- case (lookup ExifImageWidth allentries, @@ -474,13 +472,13 @@ exifHeader hdr = do -- we return a default width and height when -- the exif header doesn't contain these let resfactor = case lookup ResolutionUnit allentries of - Just (UnsignedShort 1) -> (100 / 254) + Just (UnsignedShort 1) -> 100 / 254 _ -> 1 let xres = maybe 72 (\(UnsignedRational x) -> floor $ x * resfactor) $ lookup XResolution allentries let yres = maybe 72 (\(UnsignedRational x) -> floor $ x * resfactor) $ lookup YResolution allentries - return $ ImageSize{ + return ImageSize{ pxX = wdth , pxY = hght , dpiX = xres @@ -604,3 +602,4 @@ tagTypeTable = M.fromList , (0xa300, FileSource) , (0xa301, SceneType) ] + -- cgit v1.2.3 From 627e27fc1e3800e71cac0d0b0ae7f1e687772aea Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 10 Jun 2017 15:55:18 +0200 Subject: App: change readSource(s) to use Text instead of String. --- src/Text/Pandoc/App.hs | 24 ++++++++++++++---------- 1 file changed, 14 insertions(+), 10 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 4d42b2f2b..1d42e4854 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -53,7 +53,9 @@ import Data.List (intercalate, isPrefixOf, isSuffixOf, sort) import qualified Data.Map as M import Data.Maybe (fromMaybe, isJust, isNothing) import qualified Data.Set as Set +import Data.Text (Text) import qualified Data.Text as T +import qualified Data.Text.IO as T import Data.Yaml (decode) import qualified Data.Yaml as Yaml import GHC.Generics @@ -381,8 +383,8 @@ convertWithOpts opts = do then 0 else optTabStop opts) - readSources :: [FilePath] -> PandocIO String - readSources srcs = convertTabs . intercalate "\n" <$> + readSources :: [FilePath] -> PandocIO Text + readSources srcs = convertTabs . T.intercalate (T.pack "\n") <$> mapM readSource srcs let runIO' :: PandocIO a -> IO a @@ -405,9 +407,9 @@ convertWithOpts opts = do case reader of StringReader r | optFileScope opts || readerName == "json" -> - mconcat <$> mapM (readSource >=> r readerOpts) sources + mconcat <$> mapM (readSource >=> r readerOpts . T.unpack) sources | otherwise -> - readSources sources' >>= r readerOpts + readSources sources' >>= r readerOpts . T.unpack ByteStringReader r -> mconcat <$> mapM (readFile' >=> r readerOpts) sources @@ -782,21 +784,23 @@ applyFilters mbDatadir filters args d = do expandedFilters <- mapM (expandFilterPath mbDatadir) filters foldrM ($) d $ map (flip externalFilter args) expandedFilters -readSource :: FilePath -> PandocIO String -readSource "-" = liftIO UTF8.getContents +readSource :: FilePath -> PandocIO Text +readSource "-" = liftIO T.getContents readSource src = case parseURI src of Just u | uriScheme u `elem` ["http:","https:"] -> readURI src | uriScheme u == "file:" -> - liftIO $ UTF8.readFile (uriPath u) - _ -> liftIO $ UTF8.readFile src + liftIO $ UTF8.toText <$> + BS.readFile (uriPath u) + _ -> liftIO $ UTF8.toText <$> + BS.readFile src -readURI :: FilePath -> PandocIO String +readURI :: FilePath -> PandocIO Text readURI src = do res <- liftIO $ openURL src case res of Left e -> throwError $ PandocHttpError src e - Right (contents, _) -> return $ UTF8.toString contents + Right (contents, _) -> return $ UTF8.toText contents readFile' :: MonadIO m => FilePath -> m B.ByteString readFile' "-" = liftIO B.getContents -- cgit v1.2.3 From 94b3dacb4ea7e5e99ab62286b13877b92f9391b3 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 10 Jun 2017 18:26:44 +0200 Subject: Changed all readers to take Text instead of String. Readers: Renamed StringReader -> TextReader. Updated tests. API change. --- src/Text/Pandoc/App.hs | 6 +- src/Text/Pandoc/Lua/PandocModule.hs | 5 +- src/Text/Pandoc/Readers.hs | 1 - src/Text/Pandoc/Readers/CommonMark.hs | 6 +- src/Text/Pandoc/Readers/DocBook.hs | 8 +- src/Text/Pandoc/Readers/EPUB.hs | 4 +- src/Text/Pandoc/Readers/HTML.hs | 6 +- src/Text/Pandoc/Readers/Haddock.hs | 5 +- src/Text/Pandoc/Readers/LaTeX.hs | 5 +- src/Text/Pandoc/Readers/Markdown.hs | 5 +- src/Text/Pandoc/Readers/MediaWiki.hs | 5 +- src/Text/Pandoc/Readers/Native.hs | 21 +- src/Text/Pandoc/Readers/OPML.hs | 10 +- src/Text/Pandoc/Readers/Org.hs | 7 +- src/Text/Pandoc/Readers/RST.hs | 7 +- src/Text/Pandoc/Readers/TWiki.hs | 7 +- src/Text/Pandoc/Readers/Textile.hs | 7 +- src/Text/Pandoc/Readers/Txt2Tags.hs | 7 +- test/Tests/Command.hs | 3 +- test/Tests/Helpers.hs | 4 + test/Tests/Readers/Docx.hs | 4 +- test/Tests/Readers/HTML.hs | 3 +- test/Tests/Readers/LaTeX.hs | 14 +- test/Tests/Readers/Markdown.hs | 48 +- test/Tests/Readers/Odt.hs | 6 +- test/Tests/Readers/Org.hs | 984 +++++++++++++++++----------------- test/Tests/Readers/RST.hs | 24 +- test/Tests/Readers/Txt2Tags.hs | 78 +-- test/Tests/Writers/Docx.hs | 6 +- 29 files changed, 672 insertions(+), 624 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 1d42e4854..c39bda859 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -405,11 +405,11 @@ convertWithOpts opts = do let sourceToDoc :: [FilePath] -> PandocIO Pandoc sourceToDoc sources' = case reader of - StringReader r + TextReader r | optFileScope opts || readerName == "json" -> - mconcat <$> mapM (readSource >=> r readerOpts . T.unpack) sources + mconcat <$> mapM (readSource >=> r readerOpts) sources | otherwise -> - readSources sources' >>= r readerOpts . T.unpack + readSources sources' >>= r readerOpts ByteStringReader r -> mconcat <$> mapM (readFile' >=> r readerOpts) sources diff --git a/src/Text/Pandoc/Lua/PandocModule.hs b/src/Text/Pandoc/Lua/PandocModule.hs index 8e0f3a5b4..27c19d4f0 100644 --- a/src/Text/Pandoc/Lua/PandocModule.hs +++ b/src/Text/Pandoc/Lua/PandocModule.hs @@ -30,6 +30,7 @@ module Text.Pandoc.Lua.PandocModule ( pushPandocModule ) where import Control.Monad (unless) import Data.ByteString.Char8 (unpack) import Data.Default (Default (..)) +import Data.Text (pack) import Scripting.Lua (LuaState, call, push, pushhsfunction, rawset) import Text.Pandoc.Class hiding (readDataFile) import Text.Pandoc.Definition (Pandoc) @@ -58,8 +59,8 @@ read_doc formatSpec content = do Left s -> return $ Left s Right reader -> case reader of - StringReader r -> do - res <- runIO $ r def content + TextReader r -> do + res <- runIO $ r def (pack content) case res of Left s -> return . Left $ show s Right pd -> return $ Right pd diff --git a/src/Text/Pandoc/Readers.hs b/src/Text/Pandoc/Readers.hs index 5cc37cd72..004fefe25 100644 --- a/src/Text/Pandoc/Readers.hs +++ b/src/Text/Pandoc/Readers.hs @@ -94,7 +94,6 @@ import Text.Parsec.Error import qualified Text.Pandoc.UTF8 as UTF8 import qualified Data.ByteString.Lazy as BL import Data.Text (Text) -import qualified Data.Text.Lazy as TL data Reader m = TextReader (ReaderOptions -> Text -> m Pandoc) | ByteStringReader (ReaderOptions -> BL.ByteString -> m Pandoc) diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs index e98ee066e..3c62f8db5 100644 --- a/src/Text/Pandoc/Readers/CommonMark.hs +++ b/src/Text/Pandoc/Readers/CommonMark.hs @@ -34,15 +34,15 @@ where import CMark import Data.List (groupBy) -import Data.Text (pack, unpack) +import Data.Text (Text, unpack) import Text.Pandoc.Class (PandocMonad) import Text.Pandoc.Definition import Text.Pandoc.Options -- | Parse a CommonMark formatted string into a 'Pandoc' structure. -readCommonMark :: PandocMonad m => ReaderOptions -> String -> m Pandoc +readCommonMark :: PandocMonad m => ReaderOptions -> Text -> m Pandoc readCommonMark opts s = return $ - nodeToPandoc $ commonmarkToNode opts' $ pack s + nodeToPandoc $ commonmarkToNode opts' s where opts' = if extensionEnabled Ext_smart (readerExtensions opts) then [optNormalize, optSmart] else [optNormalize] diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index bef256a93..bd3c7c356 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -16,6 +16,8 @@ import Text.TeXMath (readMathML, writeTeX) import Data.Default import Data.Foldable (asum) import Text.Pandoc.Class (PandocMonad) +import Data.Text (Text) +import qualified Data.Text as T {- @@ -522,11 +524,11 @@ instance Default DBState where , dbContent = [] } -readDocBook :: PandocMonad m => ReaderOptions -> String -> m Pandoc +readDocBook :: PandocMonad m => ReaderOptions -> Text -> m Pandoc readDocBook _ inp = do - let tree = normalizeTree . parseXML . handleInstructions $ inp + let tree = normalizeTree . parseXML . handleInstructions $ T.unpack inp (bs, st') <- flip runStateT (def{ dbContent = tree }) $ mapM parseBlock $ tree - return $ Pandoc (dbMeta st') (toList . mconcat $ bs) + return $ Pandoc (dbMeta st') (toList . mconcat $ bs) -- We treat specially (issue #1236), converting it -- to
, since xml-light doesn't parse the instruction correctly. diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index db58e9654..c0d8029dc 100644 --- a/src/Text/Pandoc/Readers/EPUB.hs +++ b/src/Text/Pandoc/Readers/EPUB.hs @@ -13,6 +13,8 @@ import Control.DeepSeq (NFData, deepseq) import Control.Monad (guard, liftM) import Control.Monad.Except (throwError) import qualified Data.ByteString.Lazy as BL (ByteString) +import qualified Data.Text.Lazy.Encoding as TL +import qualified Data.Text.Lazy as TL import Data.List (isInfixOf, isPrefixOf) import qualified Data.Map as M (Map, elems, fromList, lookup) import Data.Maybe (fromMaybe, mapMaybe) @@ -73,7 +75,7 @@ archiveToEPUB os archive = do mimeToReader "application/xhtml+xml" (unEscapeString -> root) (unEscapeString -> path) = do fname <- findEntryByPathE (root path) archive - html <- readHtml os' . UTF8.toStringLazy $ fromEntry fname + html <- readHtml os' . TL.toStrict . TL.decodeUtf8 $ fromEntry fname return $ fixInternalReferences path html mimeToReader s _ (unEscapeString -> path) | s `elem` imageMimes = return $ imageToPandoc path diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index c1bdb4d09..3bccf89fb 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -59,6 +59,7 @@ import Control.Monad ( guard, mzero, void, unless ) import Control.Arrow ((***)) import Control.Applicative ( (<|>) ) import Data.Monoid (First (..)) +import Data.Text (Text, unpack) import Text.TeXMath (readMathML, writeTeX) import Data.Default (Default (..), def) import Control.Monad.Reader (ask, asks, local, ReaderT, runReaderT, lift) @@ -74,11 +75,12 @@ import Control.Monad.Except (throwError) -- | Convert HTML-formatted string to 'Pandoc' document. readHtml :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assumes @'\n'@ line endings) + -> Text -- ^ String to parse (assumes @'\n'@ line endings) -> m Pandoc readHtml opts inp = do let tags = stripPrefixes . canonicalizeTags $ - parseTagsOptions parseOptions{ optTagPosition = True } inp + parseTagsOptions parseOptions{ optTagPosition = True } + (unpack inp) parseDoc = do blocks <- (fixPlains False) . mconcat <$> manyTill block eof meta <- stateMeta . parserState <$> getState diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs index 28caa528e..b22b71b96 100644 --- a/src/Text/Pandoc/Readers/Haddock.hs +++ b/src/Text/Pandoc/Readers/Haddock.hs @@ -16,6 +16,7 @@ module Text.Pandoc.Readers.Haddock import Control.Monad.Except (throwError) import Data.List (intersperse, stripPrefix) +import Data.Text (Text, unpack) import Data.Maybe (fromMaybe) import Data.Monoid ((<>)) import Documentation.Haddock.Parser @@ -32,9 +33,9 @@ import Text.Pandoc.Shared (splitBy, trim) -- | Parse Haddock markup and return a 'Pandoc' document. readHaddock :: PandocMonad m => ReaderOptions - -> String + -> Text -> m Pandoc -readHaddock opts s = case readHaddockEither opts s of +readHaddock opts s = case readHaddockEither opts (unpack s) of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index b65ae15ad..796d2789e 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -39,6 +39,7 @@ import Control.Applicative (many, optional, (<|>)) import Control.Monad import Control.Monad.Except (throwError) import Data.Char (chr, isAlphaNum, isLetter, ord) +import Data.Text (Text, unpack) import Data.List (intercalate, isPrefixOf) import qualified Data.Map as M import Data.Maybe (fromMaybe, maybeToList) @@ -59,10 +60,10 @@ import Text.Pandoc.Walk -- | Parse LaTeX from string and return 'Pandoc' document. readLaTeX :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assumes @'\n'@ line endings) + -> Text -- ^ String to parse (assumes @'\n'@ line endings) -> m Pandoc readLaTeX opts ltx = do - parsed <- readWithM parseLaTeX def{ stateOptions = opts } ltx + parsed <- readWithM parseLaTeX def{ stateOptions = opts } (unpack ltx) case parsed of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 5694c4354..5e966a17e 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -70,10 +70,11 @@ type MarkdownParser m = ParserT [Char] ParserState m -- | Read markdown from an input string and return a Pandoc document. readMarkdown :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readMarkdown opts s = do - parsed <- (readWithM parseMarkdown) def{ stateOptions = opts } (s ++ "\n\n") + parsed <- (readWithM parseMarkdown) def{ stateOptions = opts } + (T.unpack s ++ "\n\n") case parsed of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index 3f6142f00..a3ff60c14 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -41,6 +41,7 @@ module Text.Pandoc.Readers.MediaWiki ( readMediaWiki ) where import Control.Monad import Control.Monad.Except (throwError) import Data.Char (isDigit, isSpace) +import Data.Text (Text, unpack) import qualified Data.Foldable as F import Data.List (intercalate, intersperse, isPrefixOf) import qualified Data.Map as M @@ -64,7 +65,7 @@ import Text.Pandoc.XML (fromEntities) -- | Read mediawiki from an input string and return a Pandoc document. readMediaWiki :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readMediaWiki opts s = do parsed <- readWithM parseMediaWiki MWState{ mwOptions = opts @@ -76,7 +77,7 @@ readMediaWiki opts s = do , mwLogMessages = [] , mwInTT = False } - (s ++ "\n") + (unpack s ++ "\n") case parsed of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs index 8f42a45de..abc2ed38a 100644 --- a/src/Text/Pandoc/Readers/Native.hs +++ b/src/Text/Pandoc/Readers/Native.hs @@ -37,6 +37,7 @@ import Text.Pandoc.Shared (safeRead) import Control.Monad.Except (throwError) import Text.Pandoc.Class import Text.Pandoc.Error +import Data.Text (Text, unpack) -- | Read native formatted text and return a Pandoc document. -- The input may be a full pandoc document, a block list, a block, @@ -50,22 +51,22 @@ import Text.Pandoc.Error -- readNative :: PandocMonad m => ReaderOptions - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readNative _ s = - case maybe (Pandoc nullMeta <$> readBlocks s) Right (safeRead s) of + case maybe (Pandoc nullMeta <$> readBlocks s) Right (safeRead (unpack s)) of Right doc -> return doc Left _ -> throwError $ PandocParseError "couldn't read native" -readBlocks :: String -> Either PandocError [Block] -readBlocks s = maybe ((:[]) <$> readBlock s) Right (safeRead s) +readBlocks :: Text -> Either PandocError [Block] +readBlocks s = maybe ((:[]) <$> readBlock s) Right (safeRead (unpack s)) -readBlock :: String -> Either PandocError Block -readBlock s = maybe (Plain <$> readInlines s) Right (safeRead s) +readBlock :: Text -> Either PandocError Block +readBlock s = maybe (Plain <$> readInlines s) Right (safeRead (unpack s)) -readInlines :: String -> Either PandocError [Inline] -readInlines s = maybe ((:[]) <$> readInline s) Right (safeRead s) +readInlines :: Text -> Either PandocError [Inline] +readInlines s = maybe ((:[]) <$> readInline s) Right (safeRead (unpack s)) -readInline :: String -> Either PandocError Inline -readInline s = maybe (Left . PandocParseError $ "Could not read: " ++ s) Right (safeRead s) +readInline :: Text -> Either PandocError Inline +readInline s = maybe (Left . PandocParseError $ "Could not read: " ++ unpack s) Right (safeRead (unpack s)) diff --git a/src/Text/Pandoc/Readers/OPML.hs b/src/Text/Pandoc/Readers/OPML.hs index cf1c8f479..591d7590e 100644 --- a/src/Text/Pandoc/Readers/OPML.hs +++ b/src/Text/Pandoc/Readers/OPML.hs @@ -2,6 +2,7 @@ module Text.Pandoc.Readers.OPML ( readOPML ) where import Control.Monad.State import Data.Char (toUpper) +import Data.Text (Text, unpack, pack) import Data.Default import Data.Generics import Text.HTML.TagSoup.Entity (lookupEntity) @@ -28,9 +29,10 @@ instance Default OPMLState where , opmlDocDate = mempty } -readOPML :: PandocMonad m => ReaderOptions -> String -> m Pandoc +readOPML :: PandocMonad m => ReaderOptions -> Text -> m Pandoc readOPML _ inp = do - (bs, st') <- flip runStateT def (mapM parseBlock $ normalizeTree $ parseXML inp) + (bs, st') <- flip runStateT def + (mapM parseBlock $ normalizeTree $ parseXML (unpack inp)) return $ setTitle (opmlDocTitle st') $ setAuthors (opmlDocAuthors st') $ @@ -69,10 +71,10 @@ asHtml :: PandocMonad m => String -> OPML m Inlines asHtml s = (\(Pandoc _ bs) -> case bs of [Plain ils] -> fromList ils - _ -> mempty) <$> (lift $ readHtml def s) + _ -> mempty) <$> (lift $ readHtml def (pack s)) asMarkdown :: PandocMonad m => String -> OPML m Blocks -asMarkdown s = (\(Pandoc _ bs) -> fromList bs) <$> (lift $ readMarkdown def s) +asMarkdown s = (\(Pandoc _ bs) -> fromList bs) <$> (lift $ readMarkdown def (pack s)) getBlocks :: PandocMonad m => Element -> OPML m Blocks getBlocks e = mconcat <$> (mapM parseBlock $ elContent e) diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index 2b29bcfda..5e0d67d10 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -40,15 +40,18 @@ import Text.Pandoc.Parsing (reportLogMessages) import Control.Monad.Except (throwError) import Control.Monad.Reader (runReaderT) +import Data.Text (Text) +import qualified Data.Text as T -- | Parse org-mode string and return a Pandoc document. readOrg :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readOrg opts s = do parsed <- flip runReaderT def $ - readWithM parseOrg (optionsToParserState opts) (s ++ "\n\n") + readWithM parseOrg (optionsToParserState opts) + (T.unpack s ++ "\n\n") case parsed of Right result -> return result Left _ -> throwError $ PandocParseError "problem parsing org" diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index b242d6428..fb5f6f2d4 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -53,6 +53,8 @@ import Text.Pandoc.Options import Text.Pandoc.Parsing import Text.Pandoc.Shared import Text.Printf (printf) +import Data.Text (Text) +import qualified Data.Text as T -- TODO: -- [ ] .. parsed-literal @@ -62,10 +64,11 @@ import Text.Printf (printf) -- | Parse reStructuredText string and return Pandoc document. readRST :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readRST opts s = do - parsed <- (readWithM parseRST) def{ stateOptions = opts } (s ++ "\n\n") + parsed <- (readWithM parseRST) def{ stateOptions = opts } + (T.unpack s ++ "\n\n") case parsed of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs index fcb95fc35..9e544c4ac 100644 --- a/src/Text/Pandoc/Readers/TWiki.hs +++ b/src/Text/Pandoc/Readers/TWiki.hs @@ -49,14 +49,17 @@ import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (enclosed, macro, nested) import Text.Pandoc.Readers.HTML (htmlTag, isCommentTag) import Text.Pandoc.XML (fromEntities) +import Data.Text (Text) +import qualified Data.Text as T -- | Read twiki from an input string and return a Pandoc document. readTWiki :: PandocMonad m => ReaderOptions - -> String + -> Text -> m Pandoc readTWiki opts s = do - res <- readWithM parseTWiki def{ stateOptions = opts } (s ++ "\n\n") + res <- readWithM parseTWiki def{ stateOptions = opts } + (T.unpack s ++ "\n\n") case res of Left e -> throwError e Right d -> return d diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index 0b964dd63..1669e3e51 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -70,14 +70,17 @@ import Text.Pandoc.Parsing import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isInlineTag) import Text.Pandoc.Readers.LaTeX (rawLaTeXBlock, rawLaTeXInline) import Text.Pandoc.Shared (trim) +import Data.Text (Text) +import qualified Data.Text as T -- | Parse a Textile text and return a Pandoc document. readTextile :: PandocMonad m => ReaderOptions -- ^ Reader options - -> String -- ^ String to parse (assuming @'\n'@ line endings) + -> Text -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc readTextile opts s = do - parsed <- readWithM parseTextile def{ stateOptions = opts } (s ++ "\n\n") + parsed <- readWithM parseTextile def{ stateOptions = opts } + (T.unpack s ++ "\n\n") case parsed of Right result -> return result Left e -> throwError e diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index d8791869d..260bb7fff 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -45,7 +45,8 @@ import Text.Pandoc.Shared (compactify, compactifyDL, escapeURI) import Control.Monad (guard, void, when) import Control.Monad.Reader (Reader, asks, runReader) import Data.Default - +import Data.Text (Text) +import qualified Data.Text as T import Control.Monad.Except (catchError, throwError) import Data.Time.Format (formatTime) import Text.Pandoc.Class (PandocMonad) @@ -90,11 +91,11 @@ getT2TMeta = do -- | Read Txt2Tags from an input string returning a Pandoc document readTxt2Tags :: PandocMonad m => ReaderOptions - -> String + -> Text -> m Pandoc readTxt2Tags opts s = do meta <- getT2TMeta - let parsed = flip runReader meta $ readWithM parseT2T (def {stateOptions = opts}) (s ++ "\n\n") + let parsed = flip runReader meta $ readWithM parseT2T (def {stateOptions = opts}) (T.unpack s ++ "\n\n") case parsed of Right result -> return $ result Left e -> throwError e diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs index 588c0c06c..1f3694f60 100644 --- a/test/Tests/Command.hs +++ b/test/Tests/Command.hs @@ -13,6 +13,7 @@ import Test.Tasty.HUnit import Tests.Helpers import Text.Pandoc import Text.Pandoc.Shared (trimr) +import qualified Data.ByteString as BS import qualified Text.Pandoc.UTF8 as UTF8 import System.IO.Unsafe (unsafePerformIO) -- TODO temporary @@ -83,7 +84,7 @@ runCommandTest pandocpath (num, code) = extractCommandTest :: FilePath -> FilePath -> TestTree extractCommandTest pandocpath fp = unsafePerformIO $ do - contents <- UTF8.readFile ("command" fp) + contents <- UTF8.toText <$> BS.readFile ("command" fp) Pandoc _ blocks <- runIOorExplode (readMarkdown def{ readerExtensions = pandocExtensions } contents) let codeblocks = map extractCode $ filter isCodeBlock $ blocks diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs index 7e8ebb01a..3a82867cb 100644 --- a/test/Tests/Helpers.hs +++ b/test/Tests/Helpers.hs @@ -15,6 +15,7 @@ module Tests.Helpers ( test import Data.Algorithm.Diff import qualified Data.Map as M +import Data.Text (Text, unpack) import System.Directory import System.Environment.Executable (getExecutablePath) import System.Exit @@ -120,6 +121,9 @@ instance ToString Inlines where instance ToString String where toString = id +instance ToString Text where + toString = unpack + class ToPandoc a where toPandoc :: a -> Pandoc diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs index 028a4ff2f..e29f0acad 100644 --- a/test/Tests/Readers/Docx.hs +++ b/test/Tests/Readers/Docx.hs @@ -2,11 +2,13 @@ module Tests.Readers.Docx (tests) where import Codec.Archive.Zip import qualified Data.ByteString.Lazy as B +import qualified Data.ByteString as BS import qualified Data.Map as M import Test.Tasty import Test.Tasty.HUnit import Tests.Helpers import Text.Pandoc +import Text.Pandoc.UTF8 as UTF8 import qualified Text.Pandoc.Class as P import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory) import System.IO.Unsafe -- TODO temporary @@ -40,7 +42,7 @@ compareOutput :: ReaderOptions -> IO (NoNormPandoc, NoNormPandoc) compareOutput opts docxFile nativeFile = do df <- B.readFile docxFile - nf <- Prelude.readFile nativeFile + nf <- UTF8.toText <$> BS.readFile nativeFile p <- runIOorExplode $ readDocx opts df df' <- runIOorExplode $ readNative def nf return $ (noNorm p, noNorm df') diff --git a/test/Tests/Readers/HTML.hs b/test/Tests/Readers/HTML.hs index e2262d131..8647540b6 100644 --- a/test/Tests/Readers/HTML.hs +++ b/test/Tests/Readers/HTML.hs @@ -6,8 +6,9 @@ import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder +import Data.Text (Text) -html :: String -> Pandoc +html :: Text -> Pandoc html = purely $ readHtml def tests :: [TestTree] diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs index 75547ed6b..390d80df9 100644 --- a/test/Tests/Readers/LaTeX.hs +++ b/test/Tests/Readers/LaTeX.hs @@ -6,14 +6,16 @@ import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder +import Data.Text (Text, pack) +import qualified Data.Text as T -latex :: String -> Pandoc +latex :: Text -> Pandoc latex = purely $ readLaTeX def{ readerExtensions = getDefaultExtensions "latex" } infix 4 =: (=:) :: ToString c - => String -> (String, c) -> TestTree + => String -> (Text, c) -> TestTree (=:) = test latex simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks @@ -74,7 +76,7 @@ tests = [ testGroup "basic" "\\begin{tabular}{|rl|}One & Two\\\\ \\end{tabular}" =?> simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] , "Multi line table" =: - unlines [ "\\begin{tabular}{|c|}" + T.unlines [ "\\begin{tabular}{|c|}" , "One\\\\" , "Two\\\\" , "Three\\\\" @@ -91,7 +93,7 @@ tests = [ testGroup "basic" "\\begin{tabular}{@{}r@{}l}One & Two\\\\ \\end{tabular}" =?> simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] , "Table with custom column separators" =: - unlines [ "\\begin{tabular}{@{($\\to$)}r@{\\hspace{2cm}}l}" + T.unlines [ "\\begin{tabular}{@{($\\to$)}r@{\\hspace{2cm}}l}" , "One&Two\\\\" , "\\end{tabular}" ] =?> simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] @@ -108,10 +110,10 @@ tests = [ testGroup "basic" , let hex = ['0'..'9']++['a'..'f'] in testGroup "Character Escapes" [ "Two-character escapes" =: - concat ["^^"++[i,j] | i <- hex, j <- hex] =?> + mconcat ["^^" <> T.pack [i,j] | i <- hex, j <- hex] =?> para (str ['\0'..'\255']) , "One-character escapes" =: - concat ["^^"++[i] | i <- hex] =?> + mconcat ["^^" <> T.pack [i] | i <- hex] =?> para (str $ ['p'..'y']++['!'..'&']) ] ] diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs index e1d0c8e1f..1cd32b87d 100644 --- a/test/Tests/Readers/Markdown.hs +++ b/test/Tests/Readers/Markdown.hs @@ -1,38 +1,40 @@ {-# LANGUAGE OverloadedStrings #-} module Tests.Readers.Markdown (tests) where +import Data.Text (Text, unpack) +import qualified Data.Text as T import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder -markdown :: String -> Pandoc +markdown :: Text -> Pandoc markdown = purely $ readMarkdown def { readerExtensions = disableExtension Ext_smart pandocExtensions } -markdownSmart :: String -> Pandoc +markdownSmart :: Text -> Pandoc markdownSmart = purely $ readMarkdown def { readerExtensions = enableExtension Ext_smart pandocExtensions } -markdownCDL :: String -> Pandoc +markdownCDL :: Text -> Pandoc markdownCDL = purely $ readMarkdown def { readerExtensions = enableExtension Ext_compact_definition_lists pandocExtensions } -markdownGH :: String -> Pandoc +markdownGH :: Text -> Pandoc markdownGH = purely $ readMarkdown def { readerExtensions = githubMarkdownExtensions } infix 4 =: (=:) :: ToString c - => String -> (String, c) -> TestTree + => String -> (Text, c) -> TestTree (=:) = test markdown -testBareLink :: (String, Inlines) -> TestTree +testBareLink :: (Text, Inlines) -> TestTree testBareLink (inp, ils) = test (purely $ readMarkdown def{ readerExtensions = extensionsFromList [Ext_autolink_bare_uris, Ext_raw_html] }) - inp (inp, doc $ para ils) + (unpack inp) (inp, doc $ para ils) autolink :: String -> Inlines autolink = autolinkWith nullAttr @@ -40,7 +42,7 @@ autolink = autolinkWith nullAttr autolinkWith :: Attr -> String -> Inlines autolinkWith attr s = linkWith attr s "" (str s) -bareLinkTests :: [(String, Inlines)] +bareLinkTests :: [(Text, Inlines)] bareLinkTests = [ ("http://google.com is a search engine.", autolink "http://google.com" <> " is a search engine.") @@ -376,10 +378,10 @@ tests = [ testGroup "inline code" rawBlock "html" "" <> divWith nullAttr (para $ text "with this div too.")] , test markdownGH "issue #1636" $ - unlines [ "* a" - , "* b" - , "* c" - , " * d" ] + T.unlines [ "* a" + , "* b" + , "* c" + , " * d" ] =?> bulletList [ plain "a" , plain "b" @@ -419,9 +421,9 @@ tests = [ testGroup "inline code" , let citation = cite [Citation "cita" [] [] AuthorInText 0 0] (str "@cita") in testGroup "footnote/link following citation" -- issue #2083 [ "footnote" =: - unlines [ "@cita[^note]" - , "" - , "[^note]: note" ] =?> + T.unlines [ "@cita[^note]" + , "" + , "[^note]: note" ] =?> para ( citation <> note (para $ str "note") ) @@ -431,22 +433,22 @@ tests = [ testGroup "inline code" citation <> space <> link "http://www.com" "" (str "link") ) , "reference link" =: - unlines [ "@cita [link][link]" - , "" - , "[link]: http://www.com" ] =?> + T.unlines [ "@cita [link][link]" + , "" + , "[link]: http://www.com" ] =?> para ( citation <> space <> link "http://www.com" "" (str "link") ) , "short reference link" =: - unlines [ "@cita [link]" - , "" - , "[link]: http://www.com" ] =?> + T.unlines [ "@cita [link]" + , "" + , "[link]: http://www.com" ] =?> para ( citation <> space <> link "http://www.com" "" (str "link") ) , "implicit header link" =: - unlines [ "# Header" - , "@cita [Header]" ] =?> + T.unlines [ "# Header" + , "@cita [Header]" ] =?> headerWith ("header",[],[]) 1 (str "Header") <> para ( citation <> space <> link "#header" "" (str "Header") ) diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs index 6fc062158..61ccc8819 100644 --- a/test/Tests/Readers/Odt.hs +++ b/test/Tests/Readers/Odt.hs @@ -2,6 +2,8 @@ module Tests.Readers.Odt (tests) where import Control.Monad (liftM) import qualified Data.ByteString.Lazy as B +import qualified Data.ByteString as BS +import qualified Text.Pandoc.UTF8 as UTF8 import qualified Data.Map as M import Test.Tasty import Tests.Helpers @@ -58,7 +60,7 @@ type TestCreator = ReaderOptions compareOdtToNative :: TestCreator compareOdtToNative opts odtPath nativePath = do - nativeFile <- Prelude.readFile nativePath + nativeFile <- UTF8.toText <$> BS.readFile nativePath odtFile <- B.readFile odtPath native <- getNoNormVia id "native" <$> runIO (readNative def nativeFile) odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile) @@ -66,7 +68,7 @@ compareOdtToNative opts odtPath nativePath = do compareOdtToMarkdown :: TestCreator compareOdtToMarkdown opts odtPath markdownPath = do - markdownFile <- Prelude.readFile markdownPath + markdownFile <- UTF8.toText <$> BS.readFile markdownPath odtFile <- B.readFile odtPath markdown <- getNoNormVia id "markdown" <$> runIO (readMarkdown def{ readerExtensions = pandocExtensions } diff --git a/test/Tests/Readers/Org.hs b/test/Tests/Readers/Org.hs index 4644d13a0..45b10da42 100644 --- a/test/Tests/Readers/Org.hs +++ b/test/Tests/Readers/Org.hs @@ -2,21 +2,23 @@ module Tests.Readers.Org (tests) where import Data.List (intersperse) +import Data.Text (Text) +import qualified Data.Text as T import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Builder -org :: String -> Pandoc +org :: Text -> Pandoc org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" } -orgSmart :: String -> Pandoc +orgSmart :: Text -> Pandoc orgSmart = purely $ readOrg def { readerExtensions = enableExtension Ext_smart $ getDefaultExtensions "org" } infix 4 =: (=:) :: ToString c - => String -> (String, c) -> TestTree + => String -> (Text, c) -> TestTree (=:) = test org spcSep :: [Inlines] -> Inlines @@ -112,17 +114,17 @@ tests = para (note $ para "Schreib mir eine E-Mail") , "Markup-chars not occuring on word break are symbols" =: - unlines [ "this+that+ +so+on" - , "seven*eight* nine*" - , "+not+funny+" - ] =?> + T.unlines [ "this+that+ +so+on" + , "seven*eight* nine*" + , "+not+funny+" + ] =?> para ("this+that+ +so+on" <> softbreak <> "seven*eight* nine*" <> softbreak <> strikeout "not+funny") , "No empty markup" =: - "// ** __ ++ == ~~ $$" =?> - para (spcSep [ "//", "**", "__", "++", "==", "~~", "$$" ]) + "// ** __ <> == ~~ $$" =?> + para (spcSep [ "//", "**", "__", "<>", "==", "~~", "$$" ]) , "Adherence to Org's rules for markup borders" =: "/t/& a/ / ./r/ (*l*) /e/! /b/." =?> @@ -143,11 +145,11 @@ tests = para "/nada,/" , "Markup should work properly after a blank line" =: - unlines ["foo", "", "/bar/"] =?> + T.unlines ["foo", "", "/bar/"] =?> (para $ text "foo") <> (para $ emph $ text "bar") , "Inline math must stay within three lines" =: - unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?> + T.unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?> para ((math "a\nb\nc") <> softbreak <> "$d" <> softbreak <> "e" <> softbreak <> "f" <> softbreak <> "g$") @@ -169,17 +171,17 @@ tests = softbreak <> "emph/") , "Sub- and superscript expressions" =: - unlines [ "a_(a(b)(c)d)" - , "e^(f(g)h)" - , "i_(jk)l)" - , "m^()n" - , "o_{p{q{}r}}" - , "s^{t{u}v}" - , "w_{xy}z}" - , "1^{}2" - , "3_{{}}" - , "4^(a(*b(c*)d))" - ] =?> + T.unlines [ "a_(a(b)(c)d)" + , "e^(f(g)h)" + , "i_(jk)l)" + , "m^()n" + , "o_{p{q{}r}}" + , "s^{t{u}v}" + , "w_{xy}z}" + , "1^{}2" + , "3_{{}}" + , "4^(a(*b(c*)d))" + ] =?> para (mconcat $ intersperse softbreak [ "a" <> subscript "(a(b)(c)d)" , "e" <> superscript "(f(g)h)" @@ -206,17 +208,17 @@ tests = (para $ image "sunrise.jpg" "" "") , "Multiple images within a paragraph" =: - unlines [ "[[file:sunrise.jpg]]" - , "[[file:sunset.jpg]]" - ] =?> + T.unlines [ "[[file:sunrise.jpg]]" + , "[[file:sunset.jpg]]" + ] =?> (para $ (image "sunrise.jpg" "" "") <> softbreak <> (image "sunset.jpg" "" "")) , "Image with html attributes" =: - unlines [ "#+ATTR_HTML: :width 50%" - , "[[file:guinea-pig.gif]]" - ] =?> + T.unlines [ "#+ATTR_HTML: :width 50%" + , "[[file:guinea-pig.gif]]" + ] =?> (para $ imageWith ("", [], [("width", "50%")]) "guinea-pig.gif" "" "") ] @@ -511,21 +513,21 @@ tests = in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}") , "Macro" =: - unlines [ "#+MACRO: HELLO /Hello, $1/" - , "{{{HELLO(World)}}}" - ] =?> + T.unlines [ "#+MACRO: HELLO /Hello, $1/" + , "{{{HELLO(World)}}}" + ] =?> para (emph "Hello, World") , "Macro repeting its argument" =: - unlines [ "#+MACRO: HELLO $1$1" - , "{{{HELLO(moin)}}}" - ] =?> + T.unlines [ "#+MACRO: HELLO $1$1" + , "{{{HELLO(moin)}}}" + ] =?> para "moinmoin" , "Macro called with too few arguments" =: - unlines [ "#+MACRO: HELLO Foo $1 $2 Bar" - , "{{{HELLO()}}}" - ] =?> + T.unlines [ "#+MACRO: HELLO Foo $1 $2 Bar" + , "{{{HELLO()}}}" + ] =?> para "Foo Bar" ] @@ -539,10 +541,10 @@ tests = para "#-tag" , "Comment surrounded by Text" =: - unlines [ "Before" - , "# Comment" - , "After" - ] =?> + T.unlines [ "Before" + , "# Comment" + , "After" + ] =?> mconcat [ para "Before" , para "After" ] @@ -579,10 +581,10 @@ tests = in Pandoc meta mempty , "Properties drawer" =: - unlines [ " :PROPERTIES:" - , " :setting: foo" - , " :END:" - ] =?> + T.unlines [ " :PROPERTIES:" + , " :setting: foo" + , " :END:" + ] =?> (mempty::Blocks) , "LaTeX_headers options are translated to header-includes" =: @@ -610,46 +612,46 @@ tests = in Pandoc meta mempty , "later meta definitions take precedence" =: - unlines [ "#+AUTHOR: this will not be used" - , "#+author: Max" - ] =?> + T.unlines [ "#+AUTHOR: this will not be used" + , "#+author: Max" + ] =?> let author = MetaInlines [Str "Max"] meta = setMeta "author" (MetaList [author]) $ nullMeta in Pandoc meta mempty , "Logbook drawer" =: - unlines [ " :LogBook:" - , " - State \"DONE\" from \"TODO\" [2014-03-03 Mon 11:00]" - , " :END:" - ] =?> + T.unlines [ " :LogBook:" + , " - State \"DONE\" from \"TODO\" [2014-03-03 Mon 11:00]" + , " :END:" + ] =?> (mempty::Blocks) , "Drawer surrounded by text" =: - unlines [ "Before" - , ":PROPERTIES:" - , ":END:" - , "After" - ] =?> + T.unlines [ "Before" + , ":PROPERTIES:" + , ":END:" + , "After" + ] =?> para "Before" <> para "After" , "Drawer markers must be the only text in the line" =: - unlines [ " :LOGBOOK: foo" - , " :END: bar" - ] =?> + T.unlines [ " :LOGBOOK: foo" + , " :END: bar" + ] =?> para (":LOGBOOK: foo" <> softbreak <> ":END: bar") , "Drawers can be arbitrary" =: - unlines [ ":FOO:" - , "/bar/" - , ":END:" - ] =?> + T.unlines [ ":FOO:" + , "/bar/" + , ":END:" + ] =?> divWith (mempty, ["FOO", "drawer"], mempty) (para $ emph "bar") , "Anchor reference" =: - unlines [ "<> Target." - , "" - , "[[link-here][See here!]]" - ] =?> + T.unlines [ "<> Target." + , "" + , "[[link-here][See here!]]" + ] =?> (para (spanWith ("link-here", [], []) mempty <> "Target.") <> para (link "#link-here" "" ("See" <> space <> "here!"))) @@ -658,112 +660,112 @@ tests = (para (emph $ "Where's" <> space <> "Wally?")) , "Link to nonexistent anchor" =: - unlines [ "<> Target." - , "" - , "[[link$here][See here!]]" - ] =?> + T.unlines [ "<> Target." + , "" + , "[[link$here][See here!]]" + ] =?> (para (spanWith ("link-here", [], []) mempty <> "Target.") <> para (emph ("See" <> space <> "here!"))) , "Link abbreviation" =: - unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s" - , "[[wp:Org_mode][Wikipedia on Org-mode]]" - ] =?> + T.unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s" + , "[[wp:Org_mode][Wikipedia on Org-mode]]" + ] =?> (para (link "https://en.wikipedia.org/wiki/Org_mode" "" ("Wikipedia" <> space <> "on" <> space <> "Org-mode"))) , "Link abbreviation, defined after first use" =: - unlines [ "[[zl:non-sense][Non-sense articles]]" - , "#+LINK: zl http://zeitlens.com/tags/%s.html" - ] =?> + T.unlines [ "[[zl:non-sense][Non-sense articles]]" + , "#+LINK: zl http://zeitlens.com/tags/%s.html" + ] =?> (para (link "http://zeitlens.com/tags/non-sense.html" "" ("Non-sense" <> space <> "articles"))) , "Link abbreviation, URL encoded arguments" =: - unlines [ "#+link: expl http://example.com/%h/foo" - , "[[expl:Hello, World!][Moin!]]" - ] =?> + T.unlines [ "#+link: expl http://example.com/%h/foo" + , "[[expl:Hello, World!][Moin!]]" + ] =?> (para (link "http://example.com/Hello%2C%20World%21/foo" "" "Moin!")) , "Link abbreviation, append arguments" =: - unlines [ "#+link: expl http://example.com/" - , "[[expl:foo][bar]]" - ] =?> + T.unlines [ "#+link: expl http://example.com/" + , "[[expl:foo][bar]]" + ] =?> (para (link "http://example.com/foo" "" "bar")) , testGroup "export options" [ "disable simple sub/superscript syntax" =: - unlines [ "#+OPTIONS: ^:nil" - , "a^b" - ] =?> + T.unlines [ "#+OPTIONS: ^:nil" + , "a^b" + ] =?> para "a^b" , "directly select drawers to be exported" =: - unlines [ "#+OPTIONS: d:(\"IMPORTANT\")" - , ":IMPORTANT:" - , "23" - , ":END:" - , ":BORING:" - , "very boring" - , ":END:" - ] =?> + T.unlines [ "#+OPTIONS: d:(\"IMPORTANT\")" + , ":IMPORTANT:" + , "23" + , ":END:" + , ":BORING:" + , "very boring" + , ":END:" + ] =?> divWith (mempty, ["IMPORTANT", "drawer"], mempty) (para "23") , "exclude drawers from being exported" =: - unlines [ "#+OPTIONS: d:(not \"BORING\")" - , ":IMPORTANT:" - , "5" - , ":END:" - , ":BORING:" - , "very boring" - , ":END:" - ] =?> + T.unlines [ "#+OPTIONS: d:(not \"BORING\")" + , ":IMPORTANT:" + , "5" + , ":END:" + , ":BORING:" + , "very boring" + , ":END:" + ] =?> divWith (mempty, ["IMPORTANT", "drawer"], mempty) (para "5") , "don't include archive trees" =: - unlines [ "#+OPTIONS: arch:nil" - , "* old :ARCHIVE:" - ] =?> + T.unlines [ "#+OPTIONS: arch:nil" + , "* old :ARCHIVE:" + ] =?> (mempty ::Blocks) , "include complete archive trees" =: - unlines [ "#+OPTIONS: arch:t" - , "* old :ARCHIVE:" - , " boring" - ] =?> + T.unlines [ "#+OPTIONS: arch:t" + , "* old :ARCHIVE:" + , " boring" + ] =?> mconcat [ headerWith ("old", [], mempty) 1 ("old" <> space <> tagSpan "ARCHIVE") , para "boring" ] , "include archive tree header only" =: - unlines [ "#+OPTIONS: arch:headline" - , "* old :ARCHIVE:" - , " boring" - ] =?> + T.unlines [ "#+OPTIONS: arch:headline" + , "* old :ARCHIVE:" + , " boring" + ] =?> headerWith ("old", [], mempty) 1 ("old" <> space <> tagSpan "ARCHIVE") , "limit headline depth" =: - unlines [ "#+OPTIONS: H:2" - , "* top-level section" - , "** subsection" - , "*** list item 1" - , "*** list item 2" - ] =?> + T.unlines [ "#+OPTIONS: H:2" + , "* top-level section" + , "** subsection" + , "*** list item 1" + , "*** list item 2" + ] =?> mconcat [ headerWith ("top-level-section", [], []) 1 "top-level section" , headerWith ("subsection", [], []) 2 "subsection" , orderedList [ para "list item 1", para "list item 2" ] ] , "turn all headlines into lists" =: - unlines [ "#+OPTIONS: H:0" - , "first block" - , "* top-level section 1" - , "** subsection" - , "* top-level section 2" - ] =?> + T.unlines [ "#+OPTIONS: H:0" + , "first block" + , "* top-level section 1" + , "** subsection" + , "* top-level section 2" + ] =?> mconcat [ para "first block" , orderedList [ (para "top-level section 1" <> @@ -772,33 +774,33 @@ tests = ] , "disable author export" =: - unlines [ "#+OPTIONS: author:nil" - , "#+AUTHOR: ShyGuy" - ] =?> + T.unlines [ "#+OPTIONS: author:nil" + , "#+AUTHOR: ShyGuy" + ] =?> Pandoc nullMeta mempty , "disable creator export" =: - unlines [ "#+OPTIONS: creator:nil" - , "#+creator: The Architect" - ] =?> + T.unlines [ "#+OPTIONS: creator:nil" + , "#+creator: The Architect" + ] =?> Pandoc nullMeta mempty , "disable email export" =: - unlines [ "#+OPTIONS: email:nil" - , "#+email: no-mail-please@example.com" - ] =?> + T.unlines [ "#+OPTIONS: email:nil" + , "#+email: no-mail-please@example.com" + ] =?> Pandoc nullMeta mempty , "disable inclusion of todo keywords" =: - unlines [ "#+OPTIONS: todo:nil" - , "** DONE todo export" - ] =?> + T.unlines [ "#+OPTIONS: todo:nil" + , "** DONE todo export" + ] =?> headerWith ("todo-export", [], []) 2 "todo export" , "remove tags from headlines" =: - unlines [ "#+OPTIONS: tags:nil" - , "* Headline :hello:world:" - ] =?> + T.unlines [ "#+OPTIONS: tags:nil" + , "* Headline :hello:world:" + ] =?> headerWith ("headline", [], mempty) 1 "Headline" ] ] @@ -820,10 +822,10 @@ tests = ("Third" <> space <> "Level" <> space <> "Headline") , "Compact Headers with Paragraph" =: - unlines [ "* First Level" - , "** Second Level" - , " Text" - ] =?> + T.unlines [ "* First Level" + , "** Second Level" + , " Text" + ] =?> mconcat [ headerWith ("first-level", [], []) 1 ("First" <> space <> "Level") @@ -834,12 +836,12 @@ tests = ] , "Separated Headers with Paragraph" =: - unlines [ "* First Level" - , "" - , "** Second Level" - , "" - , " Text" - ] =?> + T.unlines [ "* First Level" + , "" + , "** Second Level" + , "" + , " Text" + ] =?> mconcat [ headerWith ("first-level", [], []) 1 ("First" <> space <> "Level") @@ -850,10 +852,10 @@ tests = ] , "Headers not preceded by a blank line" =: - unlines [ "** eat dinner" - , "Spaghetti and meatballs tonight." - , "** walk dog" - ] =?> + T.unlines [ "** eat dinner" + , "Spaghetti and meatballs tonight." + , "** walk dog" + ] =?> mconcat [ headerWith ("eat-dinner", [], []) 2 ("eat" <> space <> "dinner") @@ -879,21 +881,21 @@ tests = headerWith ("waiting-header", [], []) 1 "WAITING header" , "Custom todo keywords" =: - unlines [ "#+TODO: WAITING CANCELLED" - , "* WAITING compile" - , "* CANCELLED lunch" - ] =?> + T.unlines [ "#+TODO: WAITING CANCELLED" + , "* WAITING compile" + , "* CANCELLED lunch" + ] =?> let todoSpan = spanWith ("", ["todo", "WAITING"], []) "WAITING" doneSpan = spanWith ("", ["done", "CANCELLED"], []) "CANCELLED" in headerWith ("compile", [], []) 1 (todoSpan <> space <> "compile") <> headerWith ("lunch", [], []) 1 (doneSpan <> space <> "lunch") , "Custom todo keywords with multiple done-states" =: - unlines [ "#+TODO: WAITING | DONE CANCELLED " - , "* WAITING compile" - , "* CANCELLED lunch" - , "* DONE todo-feature" - ] =?> + T.unlines [ "#+TODO: WAITING | DONE CANCELLED " + , "* WAITING compile" + , "* CANCELLED lunch" + , "* DONE todo-feature" + ] =?> let waiting = spanWith ("", ["todo", "WAITING"], []) "WAITING" cancelled = spanWith ("", ["done", "CANCELLED"], []) "CANCELLED" done = spanWith ("", ["done", "DONE"], []) "DONE" @@ -903,10 +905,10 @@ tests = ] , "Tagged headers" =: - unlines [ "* Personal :PERSONAL:" - , "** Call Mom :@PHONE:" - , "** Call John :@PHONE:JOHN: " - ] =?> + T.unlines [ "* Personal :PERSONAL:" + , "** Call Mom :@PHONE:" + , "** Call John :@PHONE:JOHN: " + ] =?> mconcat [ headerWith ("personal", [], []) 1 ("Personal " <> tagSpan "PERSONAL") @@ -923,10 +925,10 @@ tests = headerWith ("this-is-not-tagged", [], []) 1 "This: is not: tagged" , "Header starting with strokeout text" =: - unlines [ "foo" - , "" - , "* +thing+ other thing" - ] =?> + T.unlines [ "foo" + , "" + , "* +thing+ other thing" + ] =?> mconcat [ para "foo" , headerWith ("thing-other-thing", [], []) 1 @@ -934,11 +936,11 @@ tests = ] , "Comment Trees" =: - unlines [ "* COMMENT A comment tree" - , " Not much going on here" - , "** This will be dropped" - , "* Comment tree above" - ] =?> + T.unlines [ "* COMMENT A comment tree" + , " Not much going on here" + , "** This will be dropped" + , "* Comment tree above" + ] =?> headerWith ("comment-tree-above", [], []) 1 "Comment tree above" , "Nothing but a COMMENT header" =: @@ -946,38 +948,38 @@ tests = (mempty::Blocks) , "Tree with :noexport:" =: - unlines [ "* Should be ignored :archive:noexport:old:" - , "** Old stuff" - , " This is not going to be exported" - ] =?> + T.unlines [ "* Should be ignored :archive:noexport:old:" + , "** Old stuff" + , " This is not going to be exported" + ] =?> (mempty::Blocks) , "Subtree with :noexport:" =: - unlines [ "* Exported" - , "** This isn't exported :noexport:" - , "*** This neither" - , "** But this is" - ] =?> + T.unlines [ "* Exported" + , "** This isn't exported :noexport:" + , "*** This neither" + , "** But this is" + ] =?> mconcat [ headerWith ("exported", [], []) 1 "Exported" , headerWith ("but-this-is", [], []) 2 "But this is" ] , "Preferences are treated as header attributes" =: - unlines [ "* foo" - , " :PROPERTIES:" - , " :custom_id: fubar" - , " :bar: baz" - , " :END:" - ] =?> + T.unlines [ "* foo" + , " :PROPERTIES:" + , " :custom_id: fubar" + , " :bar: baz" + , " :END:" + ] =?> headerWith ("fubar", [], [("bar", "baz")]) 1 "foo" , "Headers marked with a unnumbered property get a class of the same name" =: - unlines [ "* Not numbered" - , " :PROPERTIES:" - , " :UNNUMBERED: t" - , " :END:" - ] =?> + T.unlines [ "* Not numbered" + , " :PROPERTIES:" + , " :UNNUMBERED: t" + , " :END:" + ] =?> headerWith ("not-numbered", ["unnumbered"], []) 1 "Not numbered" ] , "Paragraph starting with an asterisk" =: @@ -985,23 +987,23 @@ tests = para "*five" , "Paragraph containing asterisk at beginning of line" =: - unlines [ "lucky" - , "*star" - ] =?> + T.unlines [ "lucky" + , "*star" + ] =?> para ("lucky" <> softbreak <> "*star") , "Example block" =: - unlines [ ": echo hello" - , ": echo dear tester" - ] =?> + T.unlines [ ": echo hello" + , ": echo dear tester" + ] =?> codeBlockWith ("", ["example"], []) "echo hello\necho dear tester\n" , "Example block surrounded by text" =: - unlines [ "Greetings" - , ": echo hello" - , ": echo dear tester" - , "Bye" - ] =?> + T.unlines [ "Greetings" + , ": echo hello" + , ": echo dear tester" + , "Bye" + ] =?> mconcat [ para "Greetings" , codeBlockWith ("", ["example"], []) "echo hello\necho dear tester\n" @@ -1009,10 +1011,10 @@ tests = ] , "Horizontal Rule" =: - unlines [ "before" - , "-----" - , "after" - ] =?> + T.unlines [ "before" + , "-----" + , "after" + ] =?> mconcat [ para "before" , horizontalRule , para "after" @@ -1023,67 +1025,67 @@ tests = para "\8212\8211 em and en dash" , "Comment Block" =: - unlines [ "#+BEGIN_COMMENT" - , "stuff" - , "bla" - , "#+END_COMMENT"] =?> + T.unlines [ "#+BEGIN_COMMENT" + , "stuff" + , "bla" + , "#+END_COMMENT"] =?> (mempty::Blocks) , testGroup "Figures" $ [ "Figure" =: - unlines [ "#+caption: A very courageous man." - , "#+name: goodguy" - , "[[file:edward.jpg]]" - ] =?> + T.unlines [ "#+caption: A very courageous man." + , "#+name: goodguy" + , "[[file:edward.jpg]]" + ] =?> para (image "edward.jpg" "fig:goodguy" "A very courageous man.") , "Figure with no name" =: - unlines [ "#+caption: I've been through the desert on this" - , "[[file:horse.png]]" - ] =?> + T.unlines [ "#+caption: I've been through the desert on this" + , "[[file:horse.png]]" + ] =?> para (image "horse.png" "fig:" "I've been through the desert on this") , "Figure with `fig:` prefix in name" =: - unlines [ "#+caption: Used as a metapher in evolutionary biology." - , "#+name: fig:redqueen" - , "[[./the-red-queen.jpg]]" - ] =?> + T.unlines [ "#+caption: Used as a metapher in evolutionary biology." + , "#+name: fig:redqueen" + , "[[./the-red-queen.jpg]]" + ] =?> para (image "./the-red-queen.jpg" "fig:redqueen" "Used as a metapher in evolutionary biology.") , "Figure with HTML attributes" =: - unlines [ "#+CAPTION: mah brain just explodid" - , "#+NAME: lambdacat" - , "#+ATTR_HTML: :style color: blue :role button" - , "[[file:lambdacat.jpg]]" - ] =?> + T.unlines [ "#+CAPTION: mah brain just explodid" + , "#+NAME: lambdacat" + , "#+ATTR_HTML: :style color: blue :role button" + , "[[file:lambdacat.jpg]]" + ] =?> let kv = [("style", "color: blue"), ("role", "button")] name = "fig:lambdacat" caption = "mah brain just explodid" in para (imageWith (mempty, mempty, kv) "lambdacat.jpg" name caption) , "Labelled figure" =: - unlines [ "#+CAPTION: My figure" - , "#+LABEL: fig:myfig" - , "[[file:blub.png]]" - ] =?> + T.unlines [ "#+CAPTION: My figure" + , "#+LABEL: fig:myfig" + , "[[file:blub.png]]" + ] =?> let attr = ("fig:myfig", mempty, mempty) in para (imageWith attr "blub.png" "fig:" "My figure") , "Figure with empty caption" =: - unlines [ "#+CAPTION:" - , "[[file:guess.jpg]]" - ] =?> + T.unlines [ "#+CAPTION:" + , "[[file:guess.jpg]]" + ] =?> para (image "guess.jpg" "fig:" "") ] , "Footnote" =: - unlines [ "A footnote[1]" - , "" - , "[1] First paragraph" - , "" - , "second paragraph" - ] =?> + T.unlines [ "A footnote[1]" + , "" + , "[1] First paragraph" + , "" + , "second paragraph" + ] =?> para (mconcat [ "A", space, "footnote" , note $ mconcat [ para ("First" <> space <> "paragraph") @@ -1092,12 +1094,12 @@ tests = ]) , "Two footnotes" =: - unlines [ "Footnotes[fn:1][fn:2]" - , "" - , "[fn:1] First note." - , "" - , "[fn:2] Second note." - ] =?> + T.unlines [ "Footnotes[fn:1][fn:2]" + , "" + , "[fn:1] First note." + , "" + , "[fn:2] Second note." + ] =?> para (mconcat [ "Footnotes" , note $ para ("First" <> space <> "note.") @@ -1105,32 +1107,32 @@ tests = ]) , "Emphasized text before footnote" =: - unlines [ "/text/[fn:1]" - , "" - , "[fn:1] unicorn" - ] =?> + T.unlines [ "/text/[fn:1]" + , "" + , "[fn:1] unicorn" + ] =?> para (mconcat [ emph "text" , note . para $ "unicorn" ]) , "Footnote that starts with emphasized text" =: - unlines [ "text[fn:1]" - , "" - , "[fn:1] /emphasized/" - ] =?> + T.unlines [ "text[fn:1]" + , "" + , "[fn:1] /emphasized/" + ] =?> para (mconcat [ "text" , note . para $ emph "emphasized" ]) , "Footnote followed by header" =: - unlines [ "Another note[fn:yay]" - , "" - , "[fn:yay] This is great!" - , "" - , "** Headline" - ] =?> + T.unlines [ "Another note[fn:yay]" + , "" + , "[fn:yay] This is great!" + , "" + , "** Headline" + ] =?> mconcat [ para (mconcat [ "Another", space, "note" @@ -1142,43 +1144,43 @@ tests = , testGroup "Lists" $ [ "Simple Bullet Lists" =: - ("- Item1\n" ++ + ("- Item1\n" <> "- Item2\n") =?> bulletList [ plain "Item1" , plain "Item2" ] , "Indented Bullet Lists" =: - (" - Item1\n" ++ + (" - Item1\n" <> " - Item2\n") =?> bulletList [ plain "Item1" , plain "Item2" ] , "Unindented *" =: - ("- Item1\n" ++ + ("- Item1\n" <> "* Item2\n") =?> bulletList [ plain "Item1" ] <> headerWith ("item2", [], []) 1 "Item2" , "Multi-line Bullet Lists" =: - ("- *Fat\n" ++ - " Tony*\n" ++ - "- /Sideshow\n" ++ + ("- *Fat\n" <> + " Tony*\n" <> + "- /Sideshow\n" <> " Bob/") =?> bulletList [ plain $ strong ("Fat" <> softbreak <> "Tony") , plain $ emph ("Sideshow" <> softbreak <> "Bob") ] , "Nested Bullet Lists" =: - ("- Discovery\n" ++ - " + One More Time\n" ++ - " + Harder, Better, Faster, Stronger\n" ++ - "- Homework\n" ++ - " + Around the World\n"++ - "- Human After All\n" ++ - " + Technologic\n" ++ + ("- Discovery\n" <> + " + One More Time\n" <> + " + Harder, Better, Faster, Stronger\n" <> + "- Homework\n" <> + " + Around the World\n"<> + "- Human After All\n" <> + " + Technologic\n" <> " + Robot Rock\n") =?> bulletList [ mconcat [ plain "Discovery" @@ -1234,7 +1236,7 @@ tests = ] , "Simple Ordered List" =: - ("1. Item1\n" ++ + ("1. Item1\n" <> "2. Item2\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ plain "Item1" @@ -1243,7 +1245,7 @@ tests = in orderedListWith listStyle listStructure , "Simple Ordered List with Parens" =: - ("1) Item1\n" ++ + ("1) Item1\n" <> "2) Item2\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ plain "Item1" @@ -1252,7 +1254,7 @@ tests = in orderedListWith listStyle listStructure , "Indented Ordered List" =: - (" 1. Item1\n" ++ + (" 1. Item1\n" <> " 2. Item2\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ plain "Item1" @@ -1261,11 +1263,11 @@ tests = in orderedListWith listStyle listStructure , "Nested Ordered Lists" =: - ("1. One\n" ++ - " 1. One-One\n" ++ - " 2. One-Two\n" ++ - "2. Two\n" ++ - " 1. Two-One\n"++ + ("1. One\n" <> + " 1. One-One\n" <> + " 2. One-Two\n" <> + "2. Two\n" <> + " 1. Two-One\n"<> " 2. Two-Two\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ mconcat @@ -1284,25 +1286,25 @@ tests = in orderedListWith listStyle listStructure , "Ordered List in Bullet List" =: - ("- Emacs\n" ++ + ("- Emacs\n" <> " 1. Org\n") =?> bulletList [ (plain "Emacs") <> (orderedList [ plain "Org"]) ] , "Bullet List in Ordered List" =: - ("1. GNU\n" ++ + ("1. GNU\n" <> " - Freedom\n") =?> orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ] , "Definition List" =: - unlines [ "- PLL :: phase-locked loop" - , "- TTL ::" - , " transistor-transistor logic" - , "- PSK :: phase-shift keying" - , "" - , " a digital modulation scheme" - ] =?> + T.unlines [ "- PLL :: phase-locked loop" + , "- TTL ::" + , " transistor-transistor logic" + , "- PSK :: phase-shift keying" + , "" + , " a digital modulation scheme" + ] =?> definitionList [ ("PLL", [ plain $ "phase-locked" <> space <> "loop" ]) , ("TTL", [ plain $ "transistor-transistor" <> space <> "logic" ]) @@ -1317,11 +1319,11 @@ tests = " - Elijah Wood :: He plays Frodo" =?> definitionList [ ("Elijah" <> space <> "Wood", [plain $ "He" <> space <> "plays" <> space <> "Frodo"])] , "Compact definition list" =: - unlines [ "- ATP :: adenosine 5' triphosphate" - , "- DNA :: deoxyribonucleic acid" - , "- PCR :: polymerase chain reaction" - , "" - ] =?> + T.unlines [ "- ATP :: adenosine 5' triphosphate" + , "- DNA :: deoxyribonucleic acid" + , "- PCR :: polymerase chain reaction" + , "" + ] =?> definitionList [ ("ATP", [ plain $ spcSep [ "adenosine", "5'", "triphosphate" ] ]) , ("DNA", [ plain $ spcSep [ "deoxyribonucleic", "acid" ] ]) @@ -1343,21 +1345,21 @@ tests = bulletList [ plain "std::cout" ] , "Loose bullet list" =: - unlines [ "- apple" - , "" - , "- orange" - , "" - , "- peach" - ] =?> + T.unlines [ "- apple" + , "" + , "- orange" + , "" + , "- peach" + ] =?> bulletList [ para "apple" , para "orange" , para "peach" ] , "Recognize preceding paragraphs in non-list contexts" =: - unlines [ "CLOSED: [2015-10-19 Mon 15:03]" - , "- Note taken on [2015-10-19 Mon 13:24]" - ] =?> + T.unlines [ "CLOSED: [2015-10-19 Mon 15:03]" + , "- Note taken on [2015-10-19 Mon 13:24]" + ] =?> mconcat [ para "CLOSED: [2015-10-19 Mon 15:03]" , bulletList [ plain "Note taken on [2015-10-19 Mon 13:24]" ] ] @@ -1373,10 +1375,10 @@ tests = simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] , "Multi line table" =: - unlines [ "| One |" - , "| Two |" - , "| Three |" - ] =?> + T.unlines [ "| One |" + , "| Two |" + , "| Three |" + ] =?> simpleTable' 1 mempty [ [ plain "One" ] , [ plain "Two" ] @@ -1388,10 +1390,10 @@ tests = simpleTable' 1 mempty [[mempty]] , "Glider Table" =: - unlines [ "| 1 | 0 | 0 |" - , "| 0 | 1 | 1 |" - , "| 1 | 1 | 0 |" - ] =?> + T.unlines [ "| 1 | 0 | 0 |" + , "| 0 | 1 | 1 |" + , "| 1 | 1 | 0 |" + ] =?> simpleTable' 3 mempty [ [ plain "1", plain "0", plain "0" ] , [ plain "0", plain "1", plain "1" ] @@ -1399,42 +1401,42 @@ tests = ] , "Table between Paragraphs" =: - unlines [ "Before" - , "| One | Two |" - , "After" - ] =?> + T.unlines [ "Before" + , "| One | Two |" + , "After" + ] =?> mconcat [ para "Before" , simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] , para "After" ] , "Table with Header" =: - unlines [ "| Species | Status |" - , "|--------------+--------------|" - , "| cervisiae | domesticated |" - , "| paradoxus | wild |" - ] =?> + T.unlines [ "| Species | Status |" + , "|--------------+--------------|" + , "| cervisiae | domesticated |" + , "| paradoxus | wild |" + ] =?> simpleTable [ plain "Species", plain "Status" ] [ [ plain "cervisiae", plain "domesticated" ] , [ plain "paradoxus", plain "wild" ] ] , "Table with final hline" =: - unlines [ "| cervisiae | domesticated |" - , "| paradoxus | wild |" - , "|--------------+--------------|" - ] =?> + T.unlines [ "| cervisiae | domesticated |" + , "| paradoxus | wild |" + , "|--------------+--------------|" + ] =?> simpleTable' 2 mempty [ [ plain "cervisiae", plain "domesticated" ] , [ plain "paradoxus", plain "wild" ] ] , "Table in a box" =: - unlines [ "|---------|---------|" - , "| static | Haskell |" - , "| dynamic | Lisp |" - , "|---------+---------|" - ] =?> + T.unlines [ "|---------|---------|" + , "| static | Haskell |" + , "| dynamic | Lisp |" + , "|---------+---------|" + ] =?> simpleTable' 2 mempty [ [ plain "static", plain "Haskell" ] , [ plain "dynamic", plain "Lisp" ] @@ -1445,18 +1447,18 @@ tests = simpleTable' 3 mempty [[mempty, mempty, plain "c"]] , "Table with empty rows" =: - unlines [ "| first |" - , "| |" - , "| third |" - ] =?> + T.unlines [ "| first |" + , "| |" + , "| third |" + ] =?> simpleTable' 1 mempty [[plain "first"], [mempty], [plain "third"]] , "Table with alignment row" =: - unlines [ "| Numbers | Text | More |" - , "| | | |" - , "| 1 | One | foo |" - , "| 2 | Two | bar |" - ] =?> + T.unlines [ "| Numbers | Text | More |" + , "| | | |" + , "| 1 | One | foo |" + , "| 2 | Two | bar |" + ] =?> table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0]) [] [ [ plain "Numbers", plain "Text", plain "More" ] @@ -1473,12 +1475,12 @@ tests = simpleTable' 1 mempty [ [ plain "incomplete-but-valid" ] ] , "Table with differing row lengths" =: - unlines [ "| Numbers | Text " - , "|-" - , "| | |" - , "| 1 | One | foo |" - , "| 2" - ] =?> + T.unlines [ "| Numbers | Text " + , "|-" + , "| | |" + , "| 1 | One | foo |" + , "| 2" + ] =?> table "" (zip [AlignCenter, AlignRight] [0, 0]) [ plain "Numbers", plain "Text" ] [ [ plain "1" , plain "One" , plain "foo" ] @@ -1486,10 +1488,10 @@ tests = ] , "Table with caption" =: - unlines [ "#+CAPTION: Hitchhiker's Multiplication Table" - , "| x | 6 |" - , "| 9 | 42 |" - ] =?> + T.unlines [ "#+CAPTION: Hitchhiker's Multiplication Table" + , "| x | 6 |" + , "| 9 | 42 |" + ] =?> table "Hitchhiker's Multiplication Table" [(AlignDefault, 0), (AlignDefault, 0)] [] @@ -1500,59 +1502,59 @@ tests = , testGroup "Blocks and fragments" [ "Source block" =: - unlines [ " #+BEGIN_SRC haskell" - , " main = putStrLn greeting" - , " where greeting = \"moin\"" - , " #+END_SRC" ] =?> + T.unlines [ " #+BEGIN_SRC haskell" + , " main = putStrLn greeting" + , " where greeting = \"moin\"" + , " #+END_SRC" ] =?> let attr' = ("", ["haskell"], []) - code' = "main = putStrLn greeting\n" ++ + code' = "main = putStrLn greeting\n" <> " where greeting = \"moin\"\n" in codeBlockWith attr' code' , "Source block with indented code" =: - unlines [ " #+BEGIN_SRC haskell" - , " main = putStrLn greeting" - , " where greeting = \"moin\"" - , " #+END_SRC" ] =?> + T.unlines [ " #+BEGIN_SRC haskell" + , " main = putStrLn greeting" + , " where greeting = \"moin\"" + , " #+END_SRC" ] =?> let attr' = ("", ["haskell"], []) - code' = "main = putStrLn greeting\n" ++ + code' = "main = putStrLn greeting\n" <> " where greeting = \"moin\"\n" in codeBlockWith attr' code' , "Source block with tab-indented code" =: - unlines [ "\t#+BEGIN_SRC haskell" - , "\tmain = putStrLn greeting" - , "\t where greeting = \"moin\"" - , "\t#+END_SRC" ] =?> + T.unlines [ "\t#+BEGIN_SRC haskell" + , "\tmain = putStrLn greeting" + , "\t where greeting = \"moin\"" + , "\t#+END_SRC" ] =?> let attr' = ("", ["haskell"], []) - code' = "main = putStrLn greeting\n" ++ + code' = "main = putStrLn greeting\n" <> " where greeting = \"moin\"\n" in codeBlockWith attr' code' , "Empty source block" =: - unlines [ " #+BEGIN_SRC haskell" - , " #+END_SRC" ] =?> + T.unlines [ " #+BEGIN_SRC haskell" + , " #+END_SRC" ] =?> let attr' = ("", ["haskell"], []) code' = "" in codeBlockWith attr' code' , "Source block between paragraphs" =: - unlines [ "Low German greeting" - , " #+BEGIN_SRC haskell" - , " main = putStrLn greeting" - , " where greeting = \"Moin!\"" - , " #+END_SRC" ] =?> + T.unlines [ "Low German greeting" + , " #+BEGIN_SRC haskell" + , " main = putStrLn greeting" + , " where greeting = \"Moin!\"" + , " #+END_SRC" ] =?> let attr' = ("", ["haskell"], []) - code' = "main = putStrLn greeting\n" ++ + code' = "main = putStrLn greeting\n" <> " where greeting = \"Moin!\"\n" in mconcat [ para $ spcSep [ "Low", "German", "greeting" ] , codeBlockWith attr' code' ] , "Source block with babel arguments" =: - unlines [ "#+BEGIN_SRC emacs-lisp :exports both" - , "(progn (message \"Hello, World!\")" - , " (+ 23 42))" - , "#+END_SRC" ] =?> + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" ] =?> let classes = [ "commonlisp" ] -- as kate doesn't know emacs-lisp syntax params = [ ("data-org-language", "emacs-lisp") , ("exports", "both") @@ -1562,13 +1564,13 @@ tests = in codeBlockWith ("", classes, params) code' , "Source block with results and :exports both" =: - unlines [ "#+BEGIN_SRC emacs-lisp :exports both" - , "(progn (message \"Hello, World!\")" - , " (+ 23 42))" - , "#+END_SRC" - , "" - , "#+RESULTS:" - , ": 65"] =?> + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65"] =?> let classes = [ "commonlisp" ] params = [ ("data-org-language", "emacs-lisp") , ("exports", "both") @@ -1581,13 +1583,13 @@ tests = codeBlockWith ("", ["example"], []) results' , "Source block with results and :exports code" =: - unlines [ "#+BEGIN_SRC emacs-lisp :exports code" - , "(progn (message \"Hello, World!\")" - , " (+ 23 42))" - , "#+END_SRC" - , "" - , "#+RESULTS:" - , ": 65" ] =?> + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports code" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65" ] =?> let classes = [ "commonlisp" ] params = [ ("data-org-language", "emacs-lisp") , ("exports", "code") @@ -1597,87 +1599,87 @@ tests = in codeBlockWith ("", classes, params) code' , "Source block with results and :exports results" =: - unlines [ "#+BEGIN_SRC emacs-lisp :exports results" - , "(progn (message \"Hello, World!\")" - , " (+ 23 42))" - , "#+END_SRC" - , "" - , "#+RESULTS:" - , ": 65" ] =?> + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports results" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65" ] =?> let results' = "65\n" in codeBlockWith ("", ["example"], []) results' , "Source block with results and :exports none" =: - unlines [ "#+BEGIN_SRC emacs-lisp :exports none" - , "(progn (message \"Hello, World!\")" - , " (+ 23 42))" - , "#+END_SRC" - , "" - , "#+RESULTS:" - , ": 65" ] =?> + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports none" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65" ] =?> (mempty :: Blocks) , "Source block with toggling header arguments" =: - unlines [ "#+BEGIN_SRC sh :noeval" - , "echo $HOME" - , "#+END_SRC" - ] =?> + T.unlines [ "#+BEGIN_SRC sh :noeval" + , "echo $HOME" + , "#+END_SRC" + ] =?> let classes = [ "bash" ] params = [ ("data-org-language", "sh"), ("noeval", "yes") ] in codeBlockWith ("", classes, params) "echo $HOME\n" , "Source block with line number switch" =: - unlines [ "#+BEGIN_SRC sh -n 10" - , ":() { :|:& };:" - , "#+END_SRC" - ] =?> + T.unlines [ "#+BEGIN_SRC sh -n 10" + , ":() { :|:& };:" + , "#+END_SRC" + ] =?> let classes = [ "bash", "numberLines" ] params = [ ("data-org-language", "sh"), ("startFrom", "10") ] in codeBlockWith ("", classes, params) ":() { :|:& };:\n" , "Source block with multi-word parameter values" =: - unlines [ "#+BEGIN_SRC dot :cmdline -Kdot -Tpng " - , "digraph { id [label=\"ID\"] }" - , "#+END_SRC" - ] =?> + T.unlines [ "#+BEGIN_SRC dot :cmdline -Kdot -Tpng " + , "digraph { id [label=\"ID\"] }" + , "#+END_SRC" + ] =?> let classes = [ "dot" ] params = [ ("cmdline", "-Kdot -Tpng") ] in codeBlockWith ("", classes, params) "digraph { id [label=\"ID\"] }\n" , "Example block" =: - unlines [ "#+begin_example" - , "A chosen representation of" - , "a rule." - , "#+eND_exAMPle" - ] =?> + T.unlines [ "#+begin_example" + , "A chosen representation of" + , "a rule." + , "#+eND_exAMPle" + ] =?> codeBlockWith ("", ["example"], []) "A chosen representation of\na rule.\n" , "HTML block" =: - unlines [ "#+BEGIN_HTML" - , "" - , "#+END_HTML" - ] =?> + T.unlines [ "#+BEGIN_HTML" + , "" + , "#+END_HTML" + ] =?> rawBlock "html" "\n" , "Quote block" =: - unlines [ "#+BEGIN_QUOTE" - , "/Niemand/ hat die Absicht, eine Mauer zu errichten!" - , "#+END_QUOTE" - ] =?> + T.unlines [ "#+BEGIN_QUOTE" + , "/Niemand/ hat die Absicht, eine Mauer zu errichten!" + , "#+END_QUOTE" + ] =?> blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht," , "eine", "Mauer", "zu", "errichten!" ])) , "Verse block" =: - unlines [ "The first lines of Goethe's /Faust/:" - , "#+begin_verse" - , "Habe nun, ach! Philosophie," - , "Juristerei und Medizin," - , "Und leider auch Theologie!" - , "Durchaus studiert, mit heißem Bemühn." - , "#+end_verse" - ] =?> + T.unlines [ "The first lines of Goethe's /Faust/:" + , "#+begin_verse" + , "Habe nun, ach! Philosophie," + , "Juristerei und Medizin," + , "Und leider auch Theologie!" + , "Durchaus studiert, mit heißem Bemühn." + , "#+end_verse" + ] =?> mconcat [ para $ spcSep [ "The", "first", "lines", "of" , "Goethe's", emph "Faust" <> ":"] @@ -1690,27 +1692,27 @@ tests = ] , "Verse block with blank lines" =: - unlines [ "#+BEGIN_VERSE" - , "foo" - , "" - , "bar" - , "#+END_VERSE" - ] =?> + T.unlines [ "#+BEGIN_VERSE" + , "foo" + , "" + , "bar" + , "#+END_VERSE" + ] =?> lineBlock [ "foo", mempty, "bar" ] , "Verse block with varying indentation" =: - unlines [ "#+BEGIN_VERSE" - , " hello darkness" - , "my old friend" - , "#+END_VERSE" - ] =?> + T.unlines [ "#+BEGIN_VERSE" + , " hello darkness" + , "my old friend" + , "#+END_VERSE" + ] =?> lineBlock [ "\160\160hello darkness", "my old friend" ] , "Raw block LaTeX" =: - unlines [ "#+BEGIN_LaTeX" - , "The category $\\cat{Set}$ is adhesive." - , "#+END_LaTeX" - ] =?> + T.unlines [ "#+BEGIN_LaTeX" + , "The category $\\cat{Set}$ is adhesive." + , "#+END_LaTeX" + ] =?> rawBlock "latex" "The category $\\cat{Set}$ is adhesive.\n" , "Raw LaTeX line" =: @@ -1726,24 +1728,24 @@ tests = rawBlock "html" "" , "Export block HTML" =: - unlines [ "#+BEGIN_export html" - , "Hello, World!" - , "#+END_export" - ] =?> + T.unlines [ "#+BEGIN_export html" + , "Hello, World!" + , "#+END_export" + ] =?> rawBlock "html" "Hello, World!\n" , "LaTeX fragment" =: - unlines [ "\\begin{equation}" - , "X_i = \\begin{cases}" - , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\" - , " C_{\\alpha(i)} & \\text{otherwise}" - , " \\end{cases}" - , "\\end{equation}" - ] =?> + T.unlines [ "\\begin{equation}" + , "X_i = \\begin{cases}" + , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\" + , " C_{\\alpha(i)} & \\text{otherwise}" + , " \\end{cases}" + , "\\end{equation}" + ] =?> rawBlock "latex" (unlines [ "\\begin{equation}" , "X_i = \\begin{cases}" - , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" ++ + , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" <> " \\alpha(i)\\\\" , " C_{\\alpha(i)} & \\text{otherwise}" , " \\end{cases}" @@ -1751,13 +1753,13 @@ tests = ]) , "Code block with caption" =: - unlines [ "#+CAPTION: Functor laws in Haskell" - , "#+NAME: functor-laws" - , "#+BEGIN_SRC haskell" - , "fmap id = id" - , "fmap (p . q) = (fmap p) . (fmap q)" - , "#+END_SRC" - ] =?> + T.unlines [ "#+CAPTION: Functor laws in Haskell" + , "#+NAME: functor-laws" + , "#+BEGIN_SRC haskell" + , "fmap id = id" + , "fmap (p . q) = (fmap p) . (fmap q)" + , "#+END_SRC" + ] =?> divWith nullAttr (mappend @@ -1769,28 +1771,28 @@ tests = ]))) , "Convert blank lines in blocks to single newlines" =: - unlines [ "#+begin_html" - , "" - , "boring" - , "" - , "#+end_html" - ] =?> + T.unlines [ "#+begin_html" + , "" + , "boring" + , "" + , "#+end_html" + ] =?> rawBlock "html" "\nboring\n\n" , "Accept `ATTR_HTML` attributes for generic block" =: - unlines [ "#+ATTR_HTML: :title hello, world :id test :class fun code" - , "#+BEGIN_TEST" - , "nonsense" - , "#+END_TEST" - ] =?> + T.unlines [ "#+ATTR_HTML: :title hello, world :id test :class fun code" + , "#+BEGIN_TEST" + , "nonsense" + , "#+END_TEST" + ] =?> let attr = ("test", ["fun", "code", "TEST"], [("title", "hello, world")]) in divWith attr (para "nonsense") , "Non-letter chars in source block parameters" =: - unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich" - , "code body" - , "#+END_SRC" - ] =?> + T.unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich" + , "code body" + , "#+END_SRC" + ] =?> let params = [ ("data-org-language", "C") , ("tangle", "xxxx.c") , ("city", "Zürich") diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs index 7f67ee742..cbca1564f 100644 --- a/test/Tests/Readers/RST.hs +++ b/test/Tests/Readers/RST.hs @@ -2,25 +2,27 @@ {-# LANGUAGE ScopedTypeVariables #-} module Tests.Readers.RST (tests) where +import Data.Text (Text) +import qualified Data.Text as T import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder -rst :: String -> Pandoc +rst :: Text -> Pandoc rst = purely $ readRST def{ readerStandalone = True } infix 4 =: (=:) :: ToString c - => String -> (String, c) -> TestTree + => String -> (Text, c) -> TestTree (=:) = test rst tests :: [TestTree] tests = [ "line block with blank line" =: "| a\n|\n| b" =?> lineBlock [ "a", mempty, "\160b" ] , testGroup "field list" - [ "general" =: unlines + [ "general" =: T.unlines [ "para" , "" , ":Hostname: media08" @@ -44,7 +46,7 @@ tests = [ "line block with blank line" =: , (text "Parameter i", [para "integer"]) , (str "Final", [para "item\non two lines"]) ]) - , "metadata" =: unlines + , "metadata" =: T.unlines [ "=====" , "Title" , "=====" @@ -58,7 +60,7 @@ tests = [ "line block with blank line" =: $ setMeta "title" ("Title" :: Inlines) $ setMeta "subtitle" ("Subtitle" :: Inlines) $ doc mempty ) - , "with inline markup" =: unlines + , "with inline markup" =: T.unlines [ ":*Date*: today" , "" , ".." @@ -80,7 +82,7 @@ tests = [ "line block with blank line" =: ]) ] , "URLs with following punctuation" =: - ("http://google.com, http://yahoo.com; http://foo.bar.baz.\n" ++ + ("http://google.com, http://yahoo.com; http://foo.bar.baz.\n" <> "http://foo.bar/baz_(bam) (http://foo.bar)") =?> para (link "http://google.com" "" "http://google.com" <> ", " <> link "http://yahoo.com" "" "http://yahoo.com" <> "; " <> @@ -89,10 +91,10 @@ tests = [ "line block with blank line" =: link "http://foo.bar/baz_(bam)" "" "http://foo.bar/baz_(bam)" <> " (" <> link "http://foo.bar" "" "http://foo.bar" <> ")") , "Reference names with special characters" =: - ("A-1-B_2_C:3:D+4+E.5.F_\n\n" ++ + ("A-1-B_2_C:3:D+4+E.5.F_\n\n" <> ".. _A-1-B_2_C:3:D+4+E.5.F: https://example.com\n") =?> para (link "https://example.com" "" "A-1-B_2_C:3:D+4+E.5.F") - , "Code directive with class and number-lines" =: unlines + , "Code directive with class and number-lines" =: T.unlines [ ".. code::python" , " :number-lines: 34" , " :class: class1 class2 class3" @@ -107,7 +109,7 @@ tests = [ "line block with blank line" =: ) "def func(x):\n return y" ) - , "Code directive with number-lines, no line specified" =: unlines + , "Code directive with number-lines, no line specified" =: T.unlines [ ".. code::python" , " :number-lines: " , "" @@ -122,7 +124,7 @@ tests = [ "line block with blank line" =: "def func(x):\n return y" ) , testGroup "literal / line / code blocks" - [ "indented literal block" =: unlines + [ "indented literal block" =: T.unlines [ "::" , "" , " block quotes" @@ -163,7 +165,7 @@ tests = [ "line block with blank line" =: , "unknown role" =: ":unknown:`text`" =?> para (str "text") ] , testGroup "footnotes" - [ "remove space before note" =: unlines + [ "remove space before note" =: T.unlines [ "foo [1]_" , "" , ".. [1]" diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs index f6fa4f989..580815279 100644 --- a/test/Tests/Readers/Txt2Tags.hs +++ b/test/Tests/Readers/Txt2Tags.hs @@ -2,6 +2,8 @@ module Tests.Readers.Txt2Tags (tests) where import Data.List (intersperse) +import Data.Text (Text) +import qualified Data.Text as T import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -9,7 +11,7 @@ import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder import Text.Pandoc.Class -t2t :: String -> Pandoc +t2t :: Text -> Pandoc -- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def t2t = purely $ \s -> do putCommonState @@ -20,7 +22,7 @@ t2t = purely $ \s -> do infix 4 =: (=:) :: ToString c - => String -> (String, c) -> TestTree + => String -> (Text, c) -> TestTree (=:) = test t2t spcSep :: [Inlines] -> Inlines @@ -154,7 +156,7 @@ tests = "== header ==[lab/el]" =?> para (text "== header ==[lab/el]") , "Headers not preceded by a blank line" =: - unlines [ "++ eat dinner ++" + T.unlines [ "++ eat dinner ++" , "Spaghetti and meatballs tonight." , "== walk dog ==" ] =?> @@ -168,16 +170,16 @@ tests = para "=five" , "Paragraph containing asterisk at beginning of line" =: - unlines [ "lucky" + T.unlines [ "lucky" , "*star" ] =?> para ("lucky" <> softbreak <> "*star") , "Horizontal Rule" =: - unlines [ "before" - , replicate 20 '-' - , replicate 20 '=' - , replicate 20 '_' + T.unlines [ "before" + , T.replicate 20 "-" + , T.replicate 20 "=" + , T.replicate 20 "_" , "after" ] =?> mconcat [ para "before" @@ -188,7 +190,7 @@ tests = ] , "Comment Block" =: - unlines [ "%%%" + T.unlines [ "%%%" , "stuff" , "bla" , "%%%"] =?> @@ -199,14 +201,14 @@ tests = , testGroup "Lists" $ [ "Simple Bullet Lists" =: - ("- Item1\n" ++ + ("- Item1\n" <> "- Item2\n") =?> bulletList [ plain "Item1" , plain "Item2" ] , "Indented Bullet Lists" =: - (" - Item1\n" ++ + (" - Item1\n" <> " - Item2\n") =?> bulletList [ plain "Item1" , plain "Item2" @@ -215,13 +217,13 @@ tests = , "Nested Bullet Lists" =: - ("- Discovery\n" ++ - " + One More Time\n" ++ - " + Harder, Better, Faster, Stronger\n" ++ - "- Homework\n" ++ - " + Around the World\n"++ - "- Human After All\n" ++ - " + Technologic\n" ++ + ("- Discovery\n" <> + " + One More Time\n" <> + " + Harder, Better, Faster, Stronger\n" <> + "- Homework\n" <> + " + Around the World\n"<> + "- Human After All\n" <> + " + Technologic\n" <> " + Robot Rock\n") =?> bulletList [ mconcat [ plain "Discovery" @@ -250,7 +252,7 @@ tests = ] , "Simple Ordered List" =: - ("+ Item1\n" ++ + ("+ Item1\n" <> "+ Item2\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ plain "Item1" @@ -260,7 +262,7 @@ tests = , "Indented Ordered List" =: - (" + Item1\n" ++ + (" + Item1\n" <> " + Item2\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ plain "Item1" @@ -269,11 +271,11 @@ tests = in orderedListWith listStyle listStructure , "Nested Ordered Lists" =: - ("+ One\n" ++ - " + One-One\n" ++ - " + One-Two\n" ++ - "+ Two\n" ++ - " + Two-One\n"++ + ("+ One\n" <> + " + One-One\n" <> + " + One-Two\n" <> + "+ Two\n" <> + " + Two-One\n"<> " + Two-Two\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ mconcat @@ -292,19 +294,19 @@ tests = in orderedListWith listStyle listStructure , "Ordered List in Bullet List" =: - ("- Emacs\n" ++ + ("- Emacs\n" <> " + Org\n") =?> bulletList [ (plain "Emacs") <> (orderedList [ plain "Org"]) ] , "Bullet List in Ordered List" =: - ("+ GNU\n" ++ + ("+ GNU\n" <> " - Freedom\n") =?> orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ] , "Definition List" =: - unlines [ ": PLL" + T.unlines [ ": PLL" , " phase-locked loop" , ": TTL" , " transistor-transistor logic" @@ -318,7 +320,7 @@ tests = , "Loose bullet list" =: - unlines [ "- apple" + T.unlines [ "- apple" , "" , "- orange" , "" @@ -340,7 +342,7 @@ tests = simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] , "Multi line table" =: - unlines [ "| One |" + T.unlines [ "| One |" , "| Two |" , "| Three |" ] =?> @@ -355,7 +357,7 @@ tests = simpleTable' 1 mempty [[mempty]] , "Glider Table" =: - unlines [ "| 1 | 0 | 0 |" + T.unlines [ "| 1 | 0 | 0 |" , "| 0 | 1 | 1 |" , "| 1 | 1 | 0 |" ] =?> @@ -367,7 +369,7 @@ tests = , "Table with Header" =: - unlines [ "|| Species | Status |" + T.unlines [ "|| Species | Status |" , "| cervisiae | domesticated |" , "| paradoxus | wild |" ] =?> @@ -377,7 +379,7 @@ tests = ] , "Table alignment determined by spacing" =: - unlines [ "| Numbers | Text | More |" + T.unlines [ "| Numbers | Text | More |" , "| 1 | One | foo |" , "| 2 | Two | bar |" ] =?> @@ -394,7 +396,7 @@ tests = , "Table with differing row lengths" =: - unlines [ "|| Numbers | Text " + T.unlines [ "|| Numbers | Text " , "| 1 | One | foo |" , "| 2 " ] =?> @@ -408,23 +410,23 @@ tests = , testGroup "Blocks and fragments" [ "Source block" =: - unlines [ "```" + T.unlines [ "```" , "main = putStrLn greeting" , " where greeting = \"moin\"" , "```" ] =?> - let code' = "main = putStrLn greeting\n" ++ + let code' = "main = putStrLn greeting\n" <> " where greeting = \"moin\"\n" in codeBlock code' , "tagged block" =: - unlines [ "'''" + T.unlines [ "'''" , "" , "'''" ] =?> rawBlock "html" "\n" , "Quote block" =: - unlines ["\t//Niemand// hat die Absicht, eine Mauer zu errichten!" + T.unlines ["\t//Niemand// hat die Absicht, eine Mauer zu errichten!" ] =?> blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht," , "eine", "Mauer", "zu", "errichten!" diff --git a/test/Tests/Writers/Docx.hs b/test/Tests/Writers/Docx.hs index 2d7179199..215952893 100644 --- a/test/Tests/Writers/Docx.hs +++ b/test/Tests/Writers/Docx.hs @@ -10,6 +10,8 @@ import Text.Pandoc.Readers.Docx import Text.Pandoc.Readers.Native import Text.Pandoc.Writers.Docx import System.IO.Unsafe (unsafePerformIO) -- TODO temporary +import qualified Data.ByteString as BS +import qualified Text.Pandoc.UTF8 as UTF8 type Options = (WriterOptions, ReaderOptions) @@ -18,8 +20,8 @@ compareOutput :: Options -> FilePath -> IO (Pandoc, Pandoc) compareOutput opts nativeFileIn nativeFileOut = do - nf <- Prelude.readFile nativeFileIn - nf' <- Prelude.readFile nativeFileOut + nf <- UTF8.toText <$> BS.readFile nativeFileIn + nf' <- UTF8.toText <$> BS.readFile nativeFileOut let wopts = fst opts df <- runIOorExplode $ do d <- readNative def nf -- cgit v1.2.3 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/App.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 From d1da54a4c3138df6781dfe1d67a4d83d2f8adc61 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 11 Jun 2017 21:22:44 +0200 Subject: Properly decode source from stdin. This should fix the appveyor failures. --- src/Text/Pandoc/App.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) (limited to 'src/Text/Pandoc/App.hs') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 658266046..19066e8b7 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -56,7 +56,6 @@ import Data.Maybe (fromMaybe, isJust, isNothing) import qualified Data.Set as Set import Data.Text (Text) import qualified Data.Text as T -import qualified Data.Text.IO as T import Data.Yaml (decode) import qualified Data.Yaml as Yaml import GHC.Generics @@ -791,7 +790,7 @@ applyFilters mbDatadir filters args d = do foldrM ($) d $ map (flip externalFilter args) expandedFilters readSource :: FilePath -> PandocIO Text -readSource "-" = liftIO T.getContents +readSource "-" = liftIO (UTF8.toText <$> BS.getContents) readSource src = case parseURI src of Just u | uriScheme u `elem` ["http:","https:"] -> readURI src -- cgit v1.2.3