Let --eol
take native
as an argument.
Add `Native` to the `LineEnding` type. Make `optEol` a `Native` rather than `Maybe Native`.
This commit is contained in:
parent
30a3deadcc
commit
4d1e9b8e41
2 changed files with 18 additions and 16 deletions
|
@ -593,11 +593,12 @@ General writer options
|
||||||
: Print a system default data file. Files in the user data directory
|
: Print a system default data file. Files in the user data directory
|
||||||
are ignored.
|
are ignored.
|
||||||
|
|
||||||
`--eol=crlf`|`lf`
|
`--eol=crlf`|`lf`|`native`
|
||||||
|
|
||||||
: Manually specify line endings: `crlf` (Windows) or `lf`
|
: Manually specify line endings: `crlf` (Windows), `lf`
|
||||||
(MacOS/linux/unix). The default is to use the line endings
|
(MacOS/linux/unix), or `native` (line endings appropriate
|
||||||
appropriate for the OS.
|
to the OS on which pandoc is being run). The default is
|
||||||
|
`native`.
|
||||||
|
|
||||||
`--dpi`=*NUMBER*
|
`--dpi`=*NUMBER*
|
||||||
|
|
||||||
|
|
|
@ -90,11 +90,11 @@ import System.Posix.IO (stdOutput)
|
||||||
import System.Posix.Terminal (queryTerminal)
|
import System.Posix.Terminal (queryTerminal)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
data Newline = LF | CRLF deriving (Show, Generic)
|
data LineEnding = LF | CRLF | Native deriving (Show, Generic)
|
||||||
|
|
||||||
instance ToJSON Newline where
|
instance ToJSON LineEnding where
|
||||||
toEncoding = genericToEncoding defaultOptions
|
toEncoding = genericToEncoding defaultOptions
|
||||||
instance FromJSON Newline
|
instance FromJSON LineEnding
|
||||||
|
|
||||||
parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt
|
parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt
|
||||||
parseOptions options' defaults = do
|
parseOptions options' defaults = do
|
||||||
|
@ -422,9 +422,9 @@ convertWithOpts opts = do
|
||||||
else return $ optMetadata opts
|
else return $ optMetadata opts
|
||||||
|
|
||||||
let eol = case optEol opts of
|
let eol = case optEol opts of
|
||||||
Just CRLF -> IO.CRLF
|
CRLF -> IO.CRLF
|
||||||
Just LF -> IO.LF
|
LF -> IO.LF
|
||||||
Nothing -> nativeNewline
|
Native -> nativeNewline
|
||||||
|
|
||||||
runIO' $ do
|
runIO' $ do
|
||||||
setResourcePath (optResourcePath opts)
|
setResourcePath (optResourcePath opts)
|
||||||
|
@ -584,7 +584,7 @@ data Opt = Opt
|
||||||
, optIncludeAfterBody :: [FilePath] -- ^ Files to include after body
|
, optIncludeAfterBody :: [FilePath] -- ^ Files to include after body
|
||||||
, optIncludeInHeader :: [FilePath] -- ^ Files to include in header
|
, optIncludeInHeader :: [FilePath] -- ^ Files to include in header
|
||||||
, optResourcePath :: [FilePath] -- ^ Path to search for images etc
|
, optResourcePath :: [FilePath] -- ^ Path to search for images etc
|
||||||
, optEol :: Maybe Newline -- ^ Enforce line-endings
|
, optEol :: LineEnding -- ^ Style of line-endings to use
|
||||||
} deriving (Generic, Show)
|
} deriving (Generic, Show)
|
||||||
|
|
||||||
instance ToJSON Opt where
|
instance ToJSON Opt where
|
||||||
|
@ -658,7 +658,7 @@ defaultOpts = Opt
|
||||||
, optIncludeAfterBody = []
|
, optIncludeAfterBody = []
|
||||||
, optIncludeInHeader = []
|
, optIncludeInHeader = []
|
||||||
, optResourcePath = ["."]
|
, optResourcePath = ["."]
|
||||||
, optEol = Nothing
|
, optEol = Native
|
||||||
}
|
}
|
||||||
|
|
||||||
addMetadata :: (String, String) -> Pandoc -> Pandoc
|
addMetadata :: (String, String) -> Pandoc -> Pandoc
|
||||||
|
@ -986,12 +986,13 @@ options =
|
||||||
(ReqArg
|
(ReqArg
|
||||||
(\arg opt ->
|
(\arg opt ->
|
||||||
case toLower <$> arg of
|
case toLower <$> arg of
|
||||||
"crlf" -> return opt { optEol = Just CRLF }
|
"crlf" -> return opt { optEol = CRLF }
|
||||||
"lf" -> return opt { optEol = Just LF }
|
"lf" -> return opt { optEol = LF }
|
||||||
|
"native" -> return opt { optEol = Native }
|
||||||
-- mac-syntax (cr) is not supported in ghc-base.
|
-- mac-syntax (cr) is not supported in ghc-base.
|
||||||
_ -> E.throwIO $ PandocOptionError
|
_ -> E.throwIO $ PandocOptionError
|
||||||
"--eol must be one of crlf (Windows), lf (Unix)")
|
"--eol must be crlf, lf, or native")
|
||||||
"crlf|lf")
|
"crlf|lf|native")
|
||||||
"" -- "EOL (default OS-dependent)"
|
"" -- "EOL (default OS-dependent)"
|
||||||
|
|
||||||
, Option "" ["wrap"]
|
, Option "" ["wrap"]
|
||||||
|
|
Loading…
Add table
Reference in a new issue