From 0cb7362f62410f58e2356381bbf2c1fe85abe2a5 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 9 Aug 2012 20:19:06 -0700 Subject: Removed `--strict`, added extensions to writer/reader names. * The `--strict` option has been removed. * Instead of using `--strict`, one can now use `strict` instead of `markdown` as an input or output format name. * The `--enable` and `--disable` optinos have been removed. * It is now possible to enable or disable specific extensions by appending them (with '+' or '-') to the writer or reader name. For example `pandoc -f markdown-footnotes+hard_line_breaks`. * The lhs extensions are now implemented this way, too; you can use either `+lhs` or `+literate_haskell`. --- src/pandoc.hs | 73 ++++++++++++++++++++++++++--------------------------------- 1 file changed, 32 insertions(+), 41 deletions(-) (limited to 'src/pandoc.hs') diff --git a/src/pandoc.hs b/src/pandoc.hs index 13e3e2021..12d7d74a2 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -44,7 +44,7 @@ import System.Exit ( exitWith, ExitCode (..) ) import System.FilePath import System.Console.GetOpt import Data.Char ( toLower ) -import Data.List ( intercalate, isSuffixOf, isPrefixOf ) +import Data.List ( intercalate, isPrefixOf ) import System.Directory ( getAppUserDataDirectory, doesFileExist, findExecutable ) import System.IO ( stdout ) import System.IO.Error ( isDoesNotExistError ) @@ -58,7 +58,6 @@ import Network.HTTP (simpleHTTP, mkRequest, getResponseBody, RequestMethod(..)) import Network.URI (parseURI, isURI, URI(..)) import qualified Data.ByteString.Lazy as B import Data.ByteString.Lazy.UTF8 (toString) -import qualified Data.Set as Set import Text.CSL.Reference (Reference(..)) #if MIN_VERSION_base(4,4,0) #else @@ -99,8 +98,8 @@ wrapWords indent c = wrap' (c - indent) (c - indent) then ",\n" ++ replicate indent ' ' ++ x ++ wrap' cols (cols - length x) xs else ", " ++ x ++ wrap' cols (remaining - (length x + 2)) xs -nonTextFormats :: [String] -nonTextFormats = ["odt","docx","epub"] +isTextFormat :: String -> Bool +isTextFormat s = takeWhile (`notElem` "+-") s `notElem` ["odt","docx","epub"] -- | Data structure for command line options. data Opt = Opt @@ -133,7 +132,6 @@ data Opt = Opt , optEPUBFonts :: [FilePath] -- ^ EPUB fonts to embed , optDumpArgs :: Bool -- ^ Output command-line arguments , optIgnoreArgs :: Bool -- ^ Ignore command-line arguments - , optStrict :: Bool -- ^ Use strict markdown syntax , optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst , optWrapText :: Bool -- ^ Wrap text , optColumns :: Int -- ^ Line length in characters @@ -186,7 +184,6 @@ defaultOpts = Opt , optEPUBFonts = [] , optDumpArgs = False , optIgnoreArgs = False - , optStrict = False , optReferenceLinks = False , optWrapText = True , optColumns = 72 @@ -237,7 +234,10 @@ options = , Option "" ["strict"] (NoArg - (\opt -> return opt { optStrict = True } )) + (\opt -> do + err 59 $ "The --strict option has been removed.\n" ++ + "Use `strict' input or output format instead." + return opt )) "" -- "Disable markdown syntax extensions" , Option "R" ["parse-raw"] @@ -702,7 +702,7 @@ usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String usageMessage programName = usageInfo (programName ++ " [OPTIONS] [FILES]" ++ "\nInput formats: " ++ (wrapWords 16 78 $ readers'names) ++ "\nOutput formats: " ++ - (wrapWords 16 78 $ writers'names ++ nonTextFormats) ++ "\nOptions:") + (wrapWords 16 78 $ writers'names) ++ "\nOptions:") where writers'names = map fst writers readers'names = map fst readers @@ -782,9 +782,10 @@ main = do ["Try " ++ prg ++ " --help for more information."] let defaultOpts' = if compatMode - then defaultOpts { optReader = "markdown" + then defaultOpts { optReader = "strict" , optWriter = "html" - , optStrict = True } + , optEmailObfuscation = + ReferenceObfuscation } else defaultOpts -- thread option data structure through all supplied option actions @@ -819,7 +820,6 @@ main = do , optEPUBFonts = epubFonts , optDumpArgs = dumpArgs , optIgnoreArgs = ignoreArgs - , optStrict = strict , optReferenceLinks = referenceLinks , optWrapText = wrap , optColumns = columns @@ -867,8 +867,8 @@ main = do let pdfOutput = map toLower (takeExtension outputFile) == ".pdf" - let laTeXOutput = writerName' == "latex" || writerName' == "beamer" || - writerName' == "latex+lhs" || writerName' == "beamer+lhs" + let laTeXOutput = "latex" `isPrefixOf` writerName' || + "beamer" `isPrefixOf` writerName' when pdfOutput $ do -- make sure writer is latex or beamer @@ -882,11 +882,11 @@ main = do latexEngine ++ " is needed for pdf output." Just _ -> return () - reader <- case (lookup readerName' readers) of - Just r -> return r - Nothing -> err 7 ("Unknown reader: " ++ readerName') + reader <- case getReader readerName' of + Right r -> return r + Left e -> err 7 e - let standalone' = standalone || writerName' `elem` nonTextFormats || pdfOutput + let standalone' = standalone || not (isTextFormat writerName') || pdfOutput templ <- case templatePath of _ | not standalone' -> return "" @@ -896,8 +896,8 @@ main = do Left e -> throwIO e Right t -> return t Just tp -> do - -- strip off "+lhs" if present - let format = takeWhile (/='+') writerName' + -- strip off extensions + let format = takeWhile (`notElem` "+-") writerName' let tp' = case takeExtension tp of "" -> tp <.> format _ -> tp @@ -919,13 +919,13 @@ main = do return $ ("mathml-script", s) : variables _ -> return variables - variables'' <- case writerName' of - "dzslides" -> do + variables'' <- if "dzslides" `isPrefixOf` writerName' + then do dztempl <- readDataFile datadir $ "dzslides" "template.html" let dzcore = unlines $ dropWhile (not . isPrefixOf "