From 6b8240fc2f45ced4f16403316cab76df15ceaf7a Mon Sep 17 00:00:00 2001
From: Stefan Dresselhaus <sdressel@techfak.uni-bielefeld.de>
Date: Wed, 17 May 2017 15:13:35 +0200
Subject: [PATCH] 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(-)

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