aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/App/CommandLineOptions.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2021-03-11 15:49:27 -0800
committerJohn MacFarlane <[email protected]>2021-03-13 15:05:37 -0800
commit8be95ad8e5150d5cab66c4abdf59baaf4670c6c8 (patch)
tree9655036efbaabda6a2a7802dc971c7fba5a987ca /src/Text/Pandoc/App/CommandLineOptions.hs
parent35b66a76718205c303f416bf0afc01c098e8a171 (diff)
Use custom Prelude based on relude.relude
The Prelude now longer exports partial functions, so a large number of uses of these functions in the code base have been rewritten. A .ghci file has been added; this is necessary for ghci to work properly with the custom Prelude. Currently there are lots of compiler warnings. We should either fix these or go to using a custom Prelude that changes less than relude.
Diffstat (limited to 'src/Text/Pandoc/App/CommandLineOptions.hs')
-rw-r--r--src/Text/Pandoc/App/CommandLineOptions.hs21
1 files changed, 11 insertions, 10 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index b4483f756..a2739e6af 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -43,7 +43,6 @@ import Safe (tailDef)
import Skylighting (Style, Syntax (..), defaultSyntaxMap, parseTheme)
import System.Console.GetOpt
import System.Environment (getArgs, getProgName)
-import System.Exit (exitSuccess)
import System.FilePath
import System.IO (stdout)
import Text.DocTemplates (Context (..), ToContext (toVal), Val (..))
@@ -71,6 +70,8 @@ import qualified Data.Map as M
import qualified Data.Text as T
import qualified Text.Pandoc.UTF8 as UTF8
+import Prelude hiding (Option, Reader)
+
parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt
parseOptions options' defaults = do
rawArgs <- map UTF8.decodeArg <$> getArgs
@@ -88,12 +89,12 @@ parseOptionsFromArgs options' defaults prg rawArgs = do
unrecognizedOpts
unless (null errors && null unknownOptionErrors) $
- E.throwIO $ PandocOptionError $ T.pack $
- concat errors ++ unlines unknownOptionErrors ++
- ("Try " ++ prg ++ " --help for more information.")
+ E.throwIO $ PandocOptionError $ T.pack (concat errors) <>
+ T.unlines unknownOptionErrors <>
+ ("Try " <> T.pack prg <> " --help for more information.")
-- thread option data structure through all supplied option actions
- opts <- foldl (>>=) (return defaults) actions
+ opts <- foldl' (>>=) (return defaults) actions
let mbArgs = case args of
[] -> Nothing
xs -> Just xs
@@ -813,12 +814,12 @@ options =
let optnames (Option shorts longs _ _) =
map (\c -> ['-',c]) shorts ++
map ("--" ++) longs
- let allopts = unwords (concatMap optnames options)
+ let allopts = intercalate " " (concatMap optnames options)
UTF8.hPutStrLn stdout $ T.pack $ printf tpl allopts
(T.unpack $ T.unwords readersNames)
(T.unpack $ T.unwords writersNames)
(T.unpack $ T.unwords $ map fst highlightingStyles)
- (unwords datafiles)
+ (intercalate " " datafiles)
exitSuccess ))
"" -- "Print bash completion script"
@@ -987,9 +988,9 @@ compileInfo =
VERSION_skylighting ++ ",\nciteproc " ++ VERSION_citeproc ++
", ipynb " ++ VERSION_ipynb
-handleUnrecognizedOption :: String -> [String] -> [String]
+handleUnrecognizedOption :: String -> [Text] -> [Text]
handleUnrecognizedOption "--smart" =
- (("--smart/-S has been removed. Use +smart or -smart extension instead.\n" ++
+ (("--smart/-S has been removed. Use +smart or -smart extension instead.\n" <>
"For example: pandoc -f markdown+smart -t markdown-smart.") :)
handleUnrecognizedOption "--normalize" =
("--normalize has been removed. Normalization is now automatic." :)
@@ -1014,7 +1015,7 @@ handleUnrecognizedOption "--epub-stylesheet" =
("--epub-stylesheet has been removed. Use --css instead.\n" :)
handleUnrecognizedOption "-R" = handleUnrecognizedOption "--parse-raw"
handleUnrecognizedOption x =
- (("Unknown option " ++ x ++ ".") :)
+ (("Unknown option " <> T.pack x <> ".") :)
readersNames :: [Text]
readersNames = sort (map fst (readers :: [(Text, Reader PandocIO)]))