aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/App.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2017-08-16 09:45:12 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2017-08-16 09:45:12 -0700
commit61cf3affa98f8331a2f2d55eedf56fc2a2a529e2 (patch)
tree40310ec042502fb98f14bfc2d79b3bf787be48a6 /src/Text/Pandoc/App.hs
parent7a40f4865fb635ff4e126697895da956300e7e35 (diff)
downloadpandoc-61cf3affa98f8331a2f2d55eedf56fc2a2a529e2.tar.gz
Change behavior with binary format output to stdout.
Previously, for binary formats, output to stdout was disabled unless we could detect that the output was being piped (and not sent to the terminal). Unfortunately, such detection is not possible on Windows, leaving windows users no way to pipe binary output. So we have changed the behavior in the following way: * If the -o option is not used, binary output is never sent to stdout by default; instead, an error is raised. * IF '-o -' is used, binary output is sent to stdout, regardless of whether it is being piped. This works on Windows too.
Diffstat (limited to 'src/Text/Pandoc/App.hs')
-rw-r--r--src/Text/Pandoc/App.hs31
1 files changed, 12 insertions, 19 deletions
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 521f5e275..c7f8bbb89 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -91,10 +91,6 @@ import Text.Pandoc.Shared (headerShift, isURI, openURL,
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.XML (toEntities)
import Text.Printf
-#ifndef _WINDOWS
-import System.Posix.IO (stdOutput)
-import System.Posix.Terminal (queryTerminal)
-#endif
data LineEnding = LF | CRLF | Native deriving (Show, Generic)
@@ -124,7 +120,7 @@ parseOptions options' defaults = do
convertWithOpts :: Opt -> IO ()
convertWithOpts opts = do
let args = optInputFiles opts
- let outputFile = optOutputFile opts
+ let outputFile = fromMaybe "-" (optOutputFile opts)
let filters = optFilters opts
let verbosity = optVerbosity opts
@@ -245,18 +241,14 @@ convertWithOpts opts = do
(\(syn,dep) -> (T.unpack syn ++ " requires " ++
T.unpack dep ++ " through IncludeRules.")) xs)
-
-
-#ifdef _WINDOWS
- let istty = True
-#else
- istty <- queryTerminal stdOutput
-#endif
- when (istty && not (isTextFormat format) && outputFile == "-") $
+ -- We don't want to send output to the terminal if the user
+ -- does 'pandoc -t docx input.txt'; though we allow them to
+ -- force this with '-o -'.
+ when (not (isTextFormat format) && optOutputFile opts == Nothing) $
E.throwIO $ PandocAppError $
"Cannot write " ++ format ++ " output to stdout.\n" ++
- "Specify an output file using the -o option."
-
+ "Specify an output file using the -o option, or " ++
+ "use '-o -' to force output to stdout."
let convertTabs = tabFilter (if optPreserveTabs opts || readerName == "t2t"
then 0
@@ -303,7 +295,8 @@ convertWithOpts opts = do
variables <-
withList (addStringAsVariable "sourcefile")
(reverse $ optInputFiles opts)
- (("outputfile", optOutputFile opts) : optVariables opts)
+ (("outputfile", fromMaybe "-" (optOutputFile opts))
+ : optVariables opts)
-- we reverse this list because, unlike
-- the other option lists here, it is
-- not reversed when parsed from CLI arguments.
@@ -562,7 +555,7 @@ data Opt = Opt
, optTemplate :: Maybe FilePath -- ^ Custom template
, optVariables :: [(String,String)] -- ^ Template variables to set
, optMetadata :: [(String, String)] -- ^ Metadata fields to set
- , optOutputFile :: FilePath -- ^ Name of output file
+ , optOutputFile :: Maybe FilePath -- ^ Name of output file
, optInputFiles :: [FilePath] -- ^ Names of input files
, optNumberSections :: Bool -- ^ Number sections in LaTeX
, optNumberOffset :: [Int] -- ^ Starting number for sections
@@ -638,7 +631,7 @@ defaultOpts = Opt
, optTemplate = Nothing
, optVariables = []
, optMetadata = []
- , optOutputFile = "-" -- "-" means stdout
+ , optOutputFile = Nothing
, optInputFiles = []
, optNumberSections = False
, optNumberOffset = [0,0,0,0,0,0]
@@ -889,7 +882,7 @@ options =
, Option "o" ["output"]
(ReqArg
- (\arg opt -> return opt { optOutputFile = arg })
+ (\arg opt -> return opt { optOutputFile = Just arg })
"FILE")
"" -- "Name of output file"