From f659644fccc5ee2eb21338ba0059da52a94fccbf Mon Sep 17 00:00:00 2001 From: Artyom Kazak Date: Sun, 3 Aug 2014 19:23:16 +0400 Subject: Use `mapM_` instead of `() <$ mapM` in one place. --- src/Text/Pandoc/Readers/Org.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index 34e98380e..003902b9b 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -274,7 +274,7 @@ optionalAttributes parser = try $ parseBlockAttributes :: OrgParser () parseBlockAttributes = do attrs <- many attribute - () <$ mapM (uncurry parseAndAddAttribute) attrs + mapM_ (uncurry parseAndAddAttribute) attrs where attribute :: OrgParser (String, String) attribute = try $ do -- cgit v1.2.3 From feebab97408d7322272e4453a60d0605c8d36772 Mon Sep 17 00:00:00 2001 From: Artyom Kazak Date: Sun, 3 Aug 2014 15:01:24 +0400 Subject: Clean up `mediaTypeOf` a bit. --- src/Text/Pandoc/Writers/EPUB.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 34a6dcb2f..4ec68879f 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -32,7 +32,7 @@ module Text.Pandoc.Writers.EPUB ( writeEPUB ) where import Data.IORef import qualified Data.Map as M import Data.Maybe ( fromMaybe ) -import Data.List ( isInfixOf, intercalate ) +import Data.List ( isPrefixOf, isInfixOf, intercalate ) import System.Environment ( getEnv ) import Text.Printf (printf) import System.FilePath ( (), takeExtension, takeFileName ) @@ -825,11 +825,11 @@ ppTopElement = ("\n" ++) . unEntity . unEntity (x:xs) = x : unEntity xs mediaTypeOf :: FilePath -> Maybe String -mediaTypeOf x = case getMimeType x of - Just y@('i':'m':'a':'g':'e':_) -> Just y - Just y@('v':'i':'d':'e':'o':_) -> Just y - Just y@('a':'u':'d':'i':'o':_) -> Just y - _ -> Nothing +mediaTypeOf x = + let mediaPrefixes = ["image", "video", "audio"] in + case getMimeType x of + Just y | any (`isPrefixOf` y) mediaPrefixes -> Just y + _ -> Nothing data IdentState = IdentState{ chapterNumber :: Int, -- cgit v1.2.3 From 82118b332899a90a60a0e95e8ae416d7f5398071 Mon Sep 17 00:00:00 2001 From: Artyom Kazak Date: Sun, 3 Aug 2014 14:44:39 +0400 Subject: Use `stripPrefix` where appropriate. --- src/Text/Pandoc/Readers/Docx.hs | 14 +++++++------- src/Text/Pandoc/Shared.hs | 14 +++++++------- src/Text/Pandoc/Writers/AsciiDoc.hs | 5 +++-- src/Text/Pandoc/Writers/Docbook.hs | 28 ++++++++++++++-------------- src/Text/Pandoc/Writers/FB2.hs | 29 ++++++++++++++--------------- src/Text/Pandoc/Writers/LaTeX.hs | 6 +++--- src/Text/Pandoc/Writers/Man.hs | 5 +++-- src/Text/Pandoc/Writers/Markdown.hs | 5 +++-- src/Text/Pandoc/Writers/RST.hs | 5 +++-- 9 files changed, 57 insertions(+), 54 deletions(-) diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index 86ce62ced..be486c83f 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -86,7 +86,7 @@ import Text.Pandoc.Readers.Docx.TexChar import Text.Pandoc.Shared import Text.Pandoc.MediaBag (insertMedia, MediaBag) import Data.Maybe (mapMaybe, fromMaybe) -import Data.List (delete, isPrefixOf, (\\), intercalate, intersect) +import Data.List (delete, stripPrefix, (\\), intercalate, intersect) import Data.Monoid import qualified Data.ByteString.Lazy as B import qualified Data.Map as M @@ -455,8 +455,8 @@ oMathElemToTexString (LowerLimit base limElems) = do -- we want to make sure to replace the `\rightarrow` with `\to` let arrowToTo :: String -> String arrowToTo "" = "" - arrowToTo s | "\\rightarrow" `isPrefixOf` s = - "\\to" ++ (arrowToTo $ drop (length "\\rightarrow") s) + arrowToTo s | Just s' <- stripPrefix "\\rightarrow" s = + "\\to" ++ arrowToTo s' arrowToTo (c:cs) = c : arrowToTo cs lim' = arrowToTo lim return $ case baseString of @@ -470,8 +470,8 @@ oMathElemToTexString (UpperLimit base limElems) = do -- we want to make sure to replace the `\rightarrow` with `\to` let arrowToTo :: String -> String arrowToTo "" = "" - arrowToTo s | "\\rightarrow" `isPrefixOf` s = - "\\to" ++ (arrowToTo $ drop (length "\\rightarrow") s) + arrowToTo s | Just s' <- stripPrefix "\\rightarrow" s = + "\\to" ++ arrowToTo s' arrowToTo (c:cs) = c : arrowToTo cs lim' = arrowToTo lim return $ case baseString of @@ -698,8 +698,8 @@ ilToCode Space = " " ilToCode _ = "" isHeaderClass :: String -> Maybe Int -isHeaderClass s | "Heading" `isPrefixOf` s = - case reads (drop (length "Heading") s) :: [(Int, String)] of +isHeaderClass s | Just s' <- stripPrefix "Heading" s = + case reads s' :: [(Int, String)] of [] -> Nothing ((n, "") : []) -> Just n _ -> Nothing diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index f0e5bbe5d..93a575809 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -99,7 +99,7 @@ import System.Environment (getProgName) import System.Exit (exitWith, ExitCode(..)) import Data.Char ( toLower, isLower, isUpper, isAlpha, isLetter, isDigit, isSpace ) -import Data.List ( find, isPrefixOf, intercalate ) +import Data.List ( find, stripPrefix, intercalate ) import qualified Data.Map as M import Network.URI ( escapeURIString, isURI, nonStrictRelativeTo, unEscapeString, parseURIReference, isAllowedInURI ) @@ -183,9 +183,9 @@ substitute :: (Eq a) => [a] -> [a] -> [a] -> [a] substitute _ _ [] = [] substitute [] _ xs = xs substitute target replacement lst@(x:xs) = - if target `isPrefixOf` lst - then replacement ++ substitute target replacement (drop (length target) lst) - else x : substitute target replacement xs + case stripPrefix target lst of + Just lst' -> replacement ++ substitute target replacement lst' + Nothing -> x : substitute target replacement xs ordNub :: (Ord a) => [a] -> [a] ordNub l = go Set.empty l @@ -808,9 +808,9 @@ fetchItem' media sourceURL s = do -- | Read from a URL and return raw data and maybe mime type. openURL :: String -> IO (Either E.SomeException (BS.ByteString, Maybe String)) openURL u - | "data:" `isPrefixOf` u = - let mime = takeWhile (/=',') $ drop 5 u - contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u + | Just u' <- stripPrefix "data:" u = + let mime = takeWhile (/=',') u' + contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u' in return $ Right (decodeLenient contents, Just mime) #ifdef HTTP_CLIENT | otherwise = withSocketsDo $ E.try $ do diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index ffcce7990..e5b8c5167 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -43,7 +43,8 @@ import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (blankline, space) -import Data.List ( isPrefixOf, intersperse, intercalate ) +import Data.Maybe (fromMaybe) +import Data.List ( stripPrefix, intersperse, intercalate ) import Text.Pandoc.Pretty import Control.Monad.State import qualified Data.Map as M @@ -401,7 +402,7 @@ inlineToAsciiDoc opts (Link txt (src, _tit)) = do let prefix = if isRelative then text "link:" else empty - let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src + let srcSuffix = fromMaybe src (stripPrefix "mailto:" src) let useAuto = case txt of [Str s] | escapeURI s == srcSuffix -> True _ -> False diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 25c1e156e..bc4732d7f 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -37,7 +37,7 @@ import Text.Pandoc.Writers.Shared import Text.Pandoc.Options import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Readers.TeXMath -import Data.List ( isPrefixOf, intercalate, isSuffixOf ) +import Data.List ( stripPrefix, isPrefixOf, intercalate, isSuffixOf ) import Data.Char ( toLower ) import Data.Monoid ( Any(..) ) import Text.Pandoc.Highlighting ( languages, languagesByExtension ) @@ -312,19 +312,19 @@ inlineToDocbook _ (RawInline f x) | f == "html" || f == "docbook" = text x | otherwise = empty inlineToDocbook _ LineBreak = text "\n" inlineToDocbook _ Space = space -inlineToDocbook opts (Link txt (src, _)) = - if isPrefixOf "mailto:" src - then let src' = drop 7 src - emailLink = inTagsSimple "email" $ text $ - escapeStringForXML $ src' - in case txt of - [Str s] | escapeURI s == src' -> emailLink - _ -> inlinesToDocbook opts txt <+> - char '(' <> emailLink <> char ')' - else (if isPrefixOf "#" src - then inTags False "link" [("linkend", drop 1 src)] - else inTags False "ulink" [("url", src)]) $ - inlinesToDocbook opts txt +inlineToDocbook opts (Link txt (src, _)) + | Just email <- stripPrefix "mailto:" src = + let emailLink = inTagsSimple "email" $ text $ + escapeStringForXML $ email + in case txt of + [Str s] | escapeURI s == email -> emailLink + _ -> inlinesToDocbook opts txt <+> + char '(' <> emailLink <> char ')' + | otherwise = + (if isPrefixOf "#" src + then inTags False "link" [("linkend", drop 1 src)] + else inTags False "ulink" [("url", src)]) $ + inlinesToDocbook opts txt inlineToDocbook _ (Image _ (src, tit)) = let titleDoc = if null tit then empty diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 7a9bff4fe..930076c9e 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -29,7 +29,7 @@ import Control.Monad.State (StateT, evalStateT, get, modify) import Control.Monad.State (liftM, liftM2, liftIO) import Data.ByteString.Base64 (encode) import Data.Char (toLower, isSpace, isAscii, isControl) -import Data.List (intersperse, intercalate, isPrefixOf) +import Data.List (intersperse, intercalate, isPrefixOf, stripPrefix) import Data.Either (lefts, rights) import Network.Browser (browse, request, setAllowRedirects, setOutHandler) import Network.HTTP (catchIO_, getRequest, getHeaders, getResponseBody) @@ -252,22 +252,21 @@ readDataURI :: String -- ^ URI -> Maybe (String,String,Bool,String) -- ^ Maybe (mime,charset,isBase64,data) readDataURI uri = - let prefix = "data:" - in if not (prefix `isPrefixOf` uri) - then Nothing - else - let rest = drop (length prefix) uri - meta = takeWhile (/= ',') rest -- without trailing ',' - uridata = drop (length meta + 1) rest - parts = split (== ';') meta - (mime,cs,enc)=foldr upd ("text/plain","US-ASCII",False) parts - in Just (mime,cs,enc,uridata) + case stripPrefix "data:" uri of + Nothing -> Nothing + Just rest -> + let meta = takeWhile (/= ',') rest -- without trailing ',' + uridata = drop (length meta + 1) rest + parts = split (== ';') meta + (mime,cs,enc)=foldr upd ("text/plain","US-ASCII",False) parts + in Just (mime,cs,enc,uridata) + where upd str m@(mime,cs,enc) - | isMimeType str = (str,cs,enc) - | "charset=" `isPrefixOf` str = (mime,drop (length "charset=") str,enc) - | str == "base64" = (mime,cs,True) - | otherwise = m + | isMimeType str = (str,cs,enc) + | Just str' <- stripPrefix "charset=" str = (mime,str',enc) + | str == "base64" = (mime,cs,True) + | otherwise = m -- Without parameters like ;charset=...; see RFC 2045, 5.1 isMimeType :: String -> Bool diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index ea704c91d..3ea070ee7 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -37,7 +37,7 @@ import Text.Pandoc.Options import Text.Pandoc.Templates import Text.Printf ( printf ) import Network.URI ( isURI, unEscapeString ) -import Data.List ( (\\), isSuffixOf, isInfixOf, +import Data.List ( (\\), isSuffixOf, isInfixOf, stripPrefix, isPrefixOf, intercalate, intersperse ) import Data.Char ( toLower, isPunctuation, isAscii, isLetter, isDigit, ord ) import Data.Maybe ( fromMaybe ) @@ -761,8 +761,8 @@ inlineToLaTeX (Link txt (src, _)) = do modify $ \s -> s{ stUrl = True } src' <- stringToLaTeX URLString src return $ text $ "\\url{" ++ src' ++ "}" - [Str x] | "mailto:" `isPrefixOf` src && - escapeURI x == drop 7 src -> -- email autolink + [Str x] | Just rest <- stripPrefix "mailto:" src, + escapeURI x == rest -> -- email autolink do modify $ \s -> s{ stUrl = True } src' <- stringToLaTeX URLString src contents <- inlineListToLaTeX txt diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 2af7c0e31..6b2c4c200 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -36,7 +36,8 @@ import Text.Pandoc.Writers.Shared import Text.Pandoc.Options import Text.Pandoc.Readers.TeXMath import Text.Printf ( printf ) -import Data.List ( isPrefixOf, intersperse, intercalate ) +import Data.List ( stripPrefix, intersperse, intercalate ) +import Data.Maybe (fromMaybe) import Text.Pandoc.Pretty import Text.Pandoc.Builder (deleteMeta) import Control.Monad.State @@ -343,7 +344,7 @@ inlineToMan _ (LineBreak) = return $ inlineToMan _ Space = return space inlineToMan opts (Link txt (src, _)) = do linktext <- inlineListToMan opts txt - let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src + let srcSuffix = fromMaybe src (stripPrefix "mailto:" src) return $ case txt of [Str s] | escapeURI s == srcSuffix -> diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index a859267cc..211d793dd 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -38,7 +38,8 @@ import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (blankline, blanklines, char, space) -import Data.List ( group, isPrefixOf, find, intersperse, transpose, sortBy ) +import Data.Maybe (fromMaybe) +import Data.List ( group, stripPrefix, find, intersperse, transpose, sortBy ) import Data.Char ( isSpace, isPunctuation ) import Data.Ord ( comparing ) import Text.Pandoc.Pretty @@ -815,7 +816,7 @@ inlineToMarkdown opts (Link txt (src, tit)) = do let linktitle = if null tit then empty else text $ " \"" ++ tit ++ "\"" - let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src + let srcSuffix = fromMaybe src (stripPrefix "mailto:" src) let useAuto = isURI src && case txt of [Str s] | escapeURI s == srcSuffix -> True diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 5e97d2ac3..57ebfc360 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -37,7 +37,8 @@ import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Builder (deleteMeta) -import Data.List ( isPrefixOf, intersperse, transpose ) +import Data.Maybe (fromMaybe) +import Data.List ( isPrefixOf, stripPrefix, intersperse, transpose ) import Network.URI (isURI) import Text.Pandoc.Pretty import Control.Monad.State @@ -401,7 +402,7 @@ inlineToRST (Link [Str str] (src, _)) if "mailto:" `isPrefixOf` src then src == escapeURI ("mailto:" ++ str) else src == escapeURI str = do - let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src + let srcSuffix = fromMaybe src (stripPrefix "mailto:" src) return $ text srcSuffix inlineToRST (Link [Image alt (imgsrc,imgtit)] (src, _tit)) = do label <- registerImage alt (imgsrc,imgtit) (Just src) -- cgit v1.2.3 From e51a2cedf9c46bd45143c4d896ac61d317cf0ebf Mon Sep 17 00:00:00 2001 From: Artyom Kazak Date: Sun, 3 Aug 2014 13:45:28 +0400 Subject: Remove dangling `where` from one function. --- src/Text/Pandoc/Writers/FB2.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 930076c9e..ddbb976ef 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -294,7 +294,6 @@ fetchURL url = do let content_type = lookupHeader HdrContentType (getHeaders r) content <- liftM (Just . toStr . encode . toBS) . getResponseBody $ Right r return $ liftM2 (,) content_type content - where toBS :: String -> B.ByteString toBS = B.pack . map (toEnum . fromEnum) -- cgit v1.2.3 From eb88444452c763b059cc83dcc2a691652d8eb842 Mon Sep 17 00:00:00 2001 From: Artyom Kazak Date: Sun, 3 Aug 2014 13:25:11 +0400 Subject: Remove redundant isHexDigit function. --- src/Text/Pandoc/Readers/RST.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index b7bc83e86..e5eccb116 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -47,7 +47,7 @@ import Text.Pandoc.Builder (Inlines, Blocks, trimInlines, (<>)) import qualified Text.Pandoc.Builder as B import Data.Monoid (mconcat, mempty) import Data.Sequence (viewr, ViewR(..)) -import Data.Char (toLower) +import Data.Char (toLower, isHexDigit) -- | Parse reStructuredText string and return Pandoc document. readRST :: ReaderOptions -- ^ Reader options @@ -656,9 +656,6 @@ extractUnicodeChar s = maybe Nothing (\c -> Just (c,rest)) mbc where (ds,rest) = span isHexDigit s mbc = safeRead ('\'':'\\':'x':ds ++ "'") -isHexDigit :: Char -> Bool -isHexDigit c = c `elem` "0123456789ABCDEFabcdef" - extractCaption :: RSTParser (Inlines, Blocks) extractCaption = do capt <- trimInlines . mconcat <$> many inline -- cgit v1.2.3 From 141fdf944a8b635934615368468362e6bbd073de Mon Sep 17 00:00:00 2001 From: Artyom Kazak Date: Sun, 3 Aug 2014 19:41:33 +0400 Subject: Add PatternGuards pragmas. --- src/Text/Pandoc/Shared.hs | 2 +- src/Text/Pandoc/Writers/Docbook.hs | 2 +- src/Text/Pandoc/Writers/FB2.hs | 2 ++ src/Text/Pandoc/Writers/LaTeX.hs | 3 ++- 4 files changed, 6 insertions(+), 3 deletions(-) diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 93a575809..51da34e79 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DeriveDataTypeable, CPP, MultiParamTypeClasses, - FlexibleContexts, ScopedTypeVariables #-} + FlexibleContexts, ScopedTypeVariables, PatternGuards #-} {- Copyright (C) 2006-2014 John MacFarlane diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index bc4732d7f..367193116 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE OverloadedStrings, PatternGuards #-} {- Copyright (C) 2006-2014 John MacFarlane diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index ddbb976ef..233b8b32b 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE PatternGuards #-} + {- Copyright (c) 2011-2012, Sergey Astanin All rights reserved. diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 3ea070ee7..d140932a7 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -1,4 +1,5 @@ -{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-} +{-# LANGUAGE OverloadedStrings, ScopedTypeVariables, + PatternGuards #-} {- Copyright (C) 2006-2014 John MacFarlane -- cgit v1.2.3 From 675b15458a03371ef4d72d52218319a4cf09216d Mon Sep 17 00:00:00 2001 From: Artyom Kazak Date: Mon, 4 Aug 2014 18:08:12 +0400 Subject: Slightly fix readability of main program file. --- pandoc.hs | 89 +++++++++++++++++++++++++++++++++++++-------------------------- 1 file changed, 52 insertions(+), 37 deletions(-) diff --git a/pandoc.hs b/pandoc.hs index 48f4dee55..0c4543d7a 100644 --- a/pandoc.hs +++ b/pandoc.hs @@ -57,7 +57,8 @@ import System.IO.Error ( isDoesNotExistError ) import qualified Control.Exception as E import Control.Exception.Extensible ( throwIO ) import qualified Text.Pandoc.UTF8 as UTF8 -import Control.Monad (when, unless, liftM, (>=>)) +import Control.Monad (when, unless, (>=>)) +import Data.Maybe (isJust) import Data.Foldable (foldrM) import Network.URI (parseURI, isURI, URI(..)) import qualified Data.ByteString.Lazy as B @@ -74,10 +75,13 @@ import Data.Monoid type Transform = Pandoc -> Pandoc copyrightMessage :: String -copyrightMessage = "\nCopyright (C) 2006-2014 John MacFarlane\n" ++ - "Web: http://johnmacfarlane.net/pandoc\n" ++ - "This is free software; see the source for copying conditions. There is no\n" ++ - "warranty, not even for merchantability or fitness for a particular purpose." +copyrightMessage = unlines [ + "", + "Copyright (C) 2006-2014 John MacFarlane", + "Web: http://johnmacfarlane.net/pandoc", + "This is free software; see the source for copying conditions.", + "There is no warranty, not even for merchantability or fitness", + "for a particular purpose." ] compileInfo :: String compileInfo = @@ -91,15 +95,21 @@ compileInfo = -- comma separated words in lines with a maximum line length. wrapWords :: Int -> Int -> [String] -> String wrapWords indent c = wrap' (c - indent) (c - indent) - where wrap' _ _ [] = "" - wrap' cols remaining (x:xs) = if remaining == cols - then x ++ wrap' cols (remaining - length x) xs - else if (length x + 1) > remaining - then ",\n" ++ replicate indent ' ' ++ x ++ wrap' cols (cols - length x) xs - else ", " ++ x ++ wrap' cols (remaining - (length x + 2)) xs + where + wrap' _ _ [] = "" + wrap' cols remaining (x:xs) + | remaining == cols = + x ++ wrap' cols (remaining - length x) xs + | (length x + 1) > remaining = + ",\n" ++ replicate indent ' ' ++ x ++ + wrap' cols (cols - length x) xs + | otherwise = + ", " ++ x ++ + wrap' cols (remaining - length x - 2) xs isTextFormat :: String -> Bool -isTextFormat s = takeWhile (`notElem` "+-") s `notElem` ["odt","docx","epub","epub3"] +isTextFormat s = takeWhile (`notElem` "+-") s `notElem` binaries + where binaries = ["odt","docx","epub","epub3"] externalFilter :: FilePath -> [String] -> Pandoc -> IO Pandoc externalFilter f args' d = do @@ -937,7 +947,7 @@ defaultWriterName x = ".fb2" -> "fb2" ".opml" -> "opml" ['.',y] | y `elem` ['1'..'9'] -> "man" - _ -> "html" + _ -> "html" -- Transformations of a Pandoc document post-parsing: @@ -967,7 +977,7 @@ applyFilters filters args d = main :: IO () main = do - rawArgs <- liftM (map UTF8.decodeArg) getArgs + rawArgs <- map UTF8.decodeArg <$> getArgs prg <- getProgName let compatMode = (prg == "hsmarkdown") @@ -1002,7 +1012,7 @@ main = do , optTemplate = templatePath , optOutputFile = outputFile , optNumberSections = numberSections - , optNumberOffset = numberFrom + , optNumberOffset = numberFrom , optSectionDivs = sectionDivs , optIncremental = incremental , optSelfContained = selfContained @@ -1050,18 +1060,17 @@ main = do exitWith ExitSuccess -- --bibliography implies -F pandoc-citeproc for backwards compatibility: - let filters' = case M.lookup "bibliography" metadata of - Just _ | optCiteMethod opts /= Natbib && - optCiteMethod opts /= Biblatex && - all (\f -> takeBaseName f /= "pandoc-citeproc") - filters -> "pandoc-citeproc" : filters - _ -> filters + let needsCiteproc = isJust (M.lookup "bibliography" metadata) && + optCiteMethod opts `notElem` [Natbib, Biblatex] && + "pandoc-citeproc" `notElem` map takeBaseName filters + let filters' = if needsCiteproc then "pandoc-citeproc" : filters + else filters let sources = if ignoreArgs then [] else args datadir <- case mbDataDir of Nothing -> E.catch - (liftM Just $ getAppUserDataDirectory "pandoc") + (Just <$> getAppUserDataDirectory "pandoc") (\e -> let _ = (e :: E.SomeException) in return Nothing) Just _ -> return mbDataDir @@ -1092,7 +1101,8 @@ main = do else case getWriter writerName' of Left e -> err 9 $ if writerName' == "pdf" - then e ++ "\nTo create a pdf with pandoc, use " ++ + then e ++ + "\nTo create a pdf with pandoc, use " ++ "the latex or beamer writer and specify\n" ++ "an output file with .pdf extension " ++ "(pandoc -t latex -o filename.pdf)." @@ -1144,20 +1154,22 @@ main = do then do dztempl <- readDataFileUTF8 datadir ("dzslides" "template.html") - let dzcore = unlines $ dropWhile (not . isPrefixOf "