2006-12-20 21:54:23 +01:00
{-
Copyright ( C ) 2006 John MacFarlane < jgm at berkeley dot edu >
This program is free software ; you can redistribute it and / or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation ; either version 2 of the License , or
( at your option ) any later version .
This program is distributed in the hope that it will be useful ,
but WITHOUT ANY WARRANTY ; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE . See the
GNU General Public License for more details .
You should have received a copy of the GNU General Public License
along with this program ; if not , write to the Free Software
Foundation , Inc . , 59 Temple Place , Suite 330 , Boston , MA 02111 - 1307 USA
- }
2006-12-20 07:50:14 +01:00
{- |
Module : Main
Copyright : Copyright ( C ) 2006 John MacFarlane
License : GNU GPL , version 2 or above
Maintainer : John MacFarlane < jgm at berkeley dot edu >
2006-12-20 21:20:10 +01:00
Stability : alpha
2006-12-20 07:50:14 +01:00
Portability : portable
Parses command - line options and calls the appropriate readers and
writers .
- }
2006-10-17 16:22:29 +02:00
module Main where
import Text.Pandoc.UTF8 ( decodeUTF8 , encodeUTF8 )
import Text.Pandoc.Readers.Markdown ( readMarkdown )
import Text.Pandoc.Readers.HTML ( readHtml )
import Text.Pandoc.Writers.S5 ( s5CSS , s5Javascript , writeS5 )
import Text.Pandoc.Writers.RST ( writeRST )
import Text.Pandoc.Readers.RST ( readRST )
import Text.Pandoc.ASCIIMathML ( asciiMathMLScript )
import Text.Pandoc.Writers.HTML ( writeHtml )
2007-01-01 22:08:12 +01:00
import Text.Pandoc.Writers.Docbook ( writeDocbook )
2006-10-17 16:22:29 +02:00
import Text.Pandoc.Writers.LaTeX ( writeLaTeX )
import Text.Pandoc.Readers.LaTeX ( readLaTeX )
import Text.Pandoc.Writers.RTF ( writeRTF )
import Text.Pandoc.Writers.Markdown ( writeMarkdown )
2006-12-20 07:50:14 +01:00
import Text.Pandoc.Writers.DefaultHeaders ( defaultHtmlHeader ,
2007-01-01 22:08:12 +01:00
defaultRTFHeader , defaultS5Header , defaultLaTeXHeader ,
defaultDocbookHeader )
2006-10-17 16:22:29 +02:00
import Text.Pandoc.Definition
import Text.Pandoc.Shared
2006-12-28 03:20:09 +01:00
import Text.Regex ( mkRegex , matchRegex )
2007-01-08 17:29:29 +01:00
import System.Environment ( getArgs , getProgName )
import System.Exit ( exitWith , ExitCode ( .. ) )
2006-10-17 16:22:29 +02:00
import System.Console.GetOpt
2006-12-16 06:05:02 +01:00
import System.IO
2006-10-17 16:22:29 +02:00
import Data.Maybe ( fromMaybe )
import Data.List ( isPrefixOf )
import Char ( toLower )
import Control.Monad ( ( >>= ) )
version :: String
2006-12-14 00:14:55 +01:00
version = " 0.3 "
2006-10-17 16:22:29 +02:00
2006-12-22 21:16:03 +01:00
copyrightMessage :: String
copyrightMessage = " \ n Copyright (C) 2006 John MacFarlane \ n Web: http://sophos.berkeley.edu/macfarlane/pandoc \ n This is free software; see the source for copying conditions. There is no \ n warranty, not even for merchantability or fitness for a particular purpose. "
2006-10-17 16:22:29 +02:00
-- | Association list of formats and readers.
readers :: [ ( String , ParserState -> String -> Pandoc ) ]
readers = [ ( " native " , readPandoc )
, ( " markdown " , readMarkdown )
, ( " rst " , readRST )
, ( " html " , readHtml )
, ( " latex " , readLaTeX )
]
-- | Reader for native Pandoc format.
readPandoc :: ParserState -> String -> Pandoc
readPandoc state input = read input
-- | Association list of formats and pairs of writers and default headers.
writers :: [ ( String , ( WriterOptions -> Pandoc -> String , String ) ) ]
writers = [ ( " native " , ( writeDoc , " " ) )
, ( " html " , ( writeHtml , defaultHtmlHeader ) )
, ( " s5 " , ( writeS5 , defaultS5Header ) )
2007-01-01 22:08:12 +01:00
, ( " docbook " , ( writeDocbook , defaultDocbookHeader ) )
2006-10-17 16:22:29 +02:00
, ( " latex " , ( writeLaTeX , defaultLaTeXHeader ) )
, ( " markdown " , ( writeMarkdown , " " ) )
, ( " rst " , ( writeRST , " " ) )
, ( " rtf " , ( writeRTF , defaultRTFHeader ) )
]
-- | Writer for Pandoc native format.
writeDoc :: WriterOptions -> Pandoc -> String
writeDoc options = prettyPandoc
-- | Data structure for command line options.
data Opt = Opt
2006-12-30 23:51:49 +01:00
{ optPreserveTabs :: Bool -- ^ Convert tabs to spaces
2006-12-20 07:50:14 +01:00
, optTabStop :: Int -- ^ Number of spaces per tab
2006-12-30 23:51:49 +01:00
, optStandalone :: Bool -- ^ Include header, footer
2006-12-28 03:20:09 +01:00
, optReader :: String -- ^ Reader format
, optWriter :: String -- ^ Writer format
2006-12-30 23:51:49 +01:00
, optParseRaw :: Bool -- ^ Parse unconvertable HTML and TeX
2006-12-20 07:50:14 +01:00
, optCSS :: String -- ^ CSS file to link to
, optIncludeInHeader :: String -- ^ File to include in header
, optIncludeBeforeBody :: String -- ^ File to include at top of body
, optIncludeAfterBody :: String -- ^ File to include at end of body
, optCustomHeader :: String -- ^ Custom header to use, or "DEFAULT"
, optTitlePrefix :: String -- ^ Optional prefix for HTML title
2006-12-22 21:16:03 +01:00
, optOutputFile :: String -- ^ Name of output file
2006-12-30 23:51:49 +01:00
, optNumberSections :: Bool -- ^ Number sections in LaTeX
, optIncremental :: Bool -- ^ Use incremental lists in S5
, optSmart :: Bool -- ^ Use smart typography
, optASCIIMathML :: Bool -- ^ Use ASCIIMathML in HTML
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
, optDumpArgs :: Bool -- ^ Output command-line arguments
, optIgnoreArgs :: Bool -- ^ Ignore command-line arguments
2006-12-30 23:51:49 +01:00
, optStrict :: Bool -- ^ Use strict markdown syntax
2006-10-17 16:22:29 +02:00
}
-- | Defaults for command-line options.
2006-12-28 03:20:09 +01:00
defaultOpts :: Opt
defaultOpts = Opt
2006-10-17 16:22:29 +02:00
{ optPreserveTabs = False
, optTabStop = 4
, optStandalone = False
2006-12-28 03:20:09 +01:00
, optReader = " " -- null for default reader
, optWriter = " " -- null for default writer
2006-10-17 16:22:29 +02:00
, optParseRaw = False
, optCSS = " "
, optIncludeInHeader = " "
, optIncludeBeforeBody = " "
, optIncludeAfterBody = " "
, optCustomHeader = " DEFAULT "
, optTitlePrefix = " "
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
, optOutputFile = " - " -- "-" means stdout
2006-10-17 16:22:29 +02:00
, optNumberSections = False
, optIncremental = False
2006-12-18 23:02:39 +01:00
, optSmart = False
2006-10-17 16:22:29 +02:00
, optASCIIMathML = False
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
, optDumpArgs = False
, optIgnoreArgs = False
2006-12-30 23:51:49 +01:00
, optStrict = False
2006-10-17 16:22:29 +02:00
}
2006-12-28 03:20:09 +01:00
-- | A list of functions, each transforming the options data structure
-- in response to a command-line option.
options :: [ OptDescr ( Opt -> IO Opt ) ]
options =
2006-12-22 21:16:03 +01:00
[ Option " fr " [ " from " , " read " ]
2006-10-17 16:22:29 +02:00
( ReqArg
2006-12-28 03:20:09 +01:00
( \ arg opt -> return opt { optReader = map toLower arg } )
2006-10-17 16:22:29 +02:00
" FORMAT " )
2006-12-31 02:12:01 +01:00
" " -- ("(" ++ (joinWithSep ", " (map fst readers)) ++ ")")
2006-10-17 16:22:29 +02:00
, Option " tw " [ " to " , " write " ]
( ReqArg
2006-12-28 03:20:09 +01:00
( \ arg opt -> return opt { optWriter = map toLower arg } )
2006-10-17 16:22:29 +02:00
" FORMAT " )
2006-12-31 02:12:01 +01:00
" " -- ("(" ++ (joinWithSep ", " (map fst writers)) ++ ")")
2006-10-17 16:22:29 +02:00
, Option " s " [ " standalone " ]
( NoArg
( \ opt -> return opt { optStandalone = True } ) )
2006-12-31 02:12:01 +01:00
" " -- "Include needed header and footer on output"
2006-10-17 16:22:29 +02:00
2006-12-22 21:16:03 +01:00
, Option " o " [ " output " ]
( ReqArg
2006-12-28 03:20:09 +01:00
( \ arg opt -> return opt { optOutputFile = arg } )
2006-12-22 21:16:03 +01:00
" FILENAME " )
2006-12-31 02:12:01 +01:00
" " -- "Name of output file"
2006-12-22 21:16:03 +01:00
2006-10-17 16:22:29 +02:00
, Option " p " [ " preserve-tabs " ]
( NoArg
( \ opt -> return opt { optPreserveTabs = True } ) )
2006-12-31 02:12:01 +01:00
" " -- "Preserve tabs instead of converting to spaces"
2006-10-17 16:22:29 +02:00
, Option " " [ " tab-stop " ]
( ReqArg
( \ arg opt -> return opt { optTabStop = ( read arg ) } )
" TABSTOP " )
2006-12-31 02:12:01 +01:00
" " -- "Tab stop (default 4)"
2006-10-17 16:22:29 +02:00
2006-12-30 23:51:49 +01:00
, Option " " [ " strict " ]
( NoArg
( \ opt -> return opt { optStrict = True } ) )
2006-12-31 02:12:01 +01:00
" " -- "Use strict markdown syntax with no extensions"
2006-12-30 23:51:49 +01:00
2006-10-17 16:22:29 +02:00
, Option " R " [ " parse-raw " ]
( NoArg
( \ opt -> return opt { optParseRaw = True } ) )
2006-12-31 02:12:01 +01:00
" " -- "Parse untranslatable HTML codes and LaTeX environments as raw"
2006-10-17 16:22:29 +02:00
2006-12-18 23:02:39 +01:00
, Option " S " [ " smart " ]
2006-10-17 16:22:29 +02:00
( NoArg
2006-12-18 23:02:39 +01:00
( \ opt -> return opt { optSmart = True } ) )
2007-01-06 10:54:58 +01:00
" " -- "Use smart quotes, dashes, and ellipses"
2006-10-17 16:22:29 +02:00
, Option " m " [ " asciimathml " ]
( NoArg
2006-12-20 07:50:14 +01:00
( \ opt -> return opt { optASCIIMathML = True ,
optStandalone = True } ) )
2006-12-31 02:12:01 +01:00
" " -- "Use ASCIIMathML script in html output"
2006-10-17 16:22:29 +02:00
, Option " i " [ " incremental " ]
( NoArg
( \ opt -> return opt { optIncremental = True } ) )
2006-12-31 02:12:01 +01:00
" " -- "Make list items display incrementally in S5"
2006-10-17 16:22:29 +02:00
, Option " N " [ " number-sections " ]
( NoArg
( \ opt -> return opt { optNumberSections = True } ) )
2006-12-31 02:12:01 +01:00
" " -- "Number sections in LaTeX"
2006-10-17 16:22:29 +02:00
, Option " c " [ " css " ]
( ReqArg
2006-12-20 07:50:14 +01:00
( \ arg opt -> return opt { optCSS = arg ,
optStandalone = True } )
2006-10-17 16:22:29 +02:00
" CSS " )
2006-12-31 02:12:01 +01:00
" " -- "Link to CSS style sheet"
2006-10-17 16:22:29 +02:00
, Option " H " [ " include-in-header " ]
( ReqArg
( \ arg opt -> do
text <- readFile arg
2006-12-20 07:50:14 +01:00
return opt { optIncludeInHeader = text ,
optStandalone = True } )
2006-10-17 16:22:29 +02:00
" FILENAME " )
2006-12-31 02:12:01 +01:00
" " -- "File to include at end of header (implies -s)"
2006-10-17 16:22:29 +02:00
, Option " B " [ " include-before-body " ]
( ReqArg
( \ arg opt -> do
text <- readFile arg
return opt { optIncludeBeforeBody = text } )
" FILENAME " )
2006-12-31 02:12:01 +01:00
" " -- "File to include before document body"
2006-10-17 16:22:29 +02:00
, Option " A " [ " include-after-body " ]
( ReqArg
( \ arg opt -> do
text <- readFile arg
return opt { optIncludeAfterBody = text } )
" FILENAME " )
2006-12-31 02:12:01 +01:00
" " -- "File to include after document body"
2006-10-17 16:22:29 +02:00
2006-12-22 21:16:03 +01:00
, Option " C " [ " custom-header " ]
2006-10-17 16:22:29 +02:00
( ReqArg
( \ arg opt -> do
text <- readFile arg
2006-12-20 07:50:14 +01:00
return opt { optCustomHeader = text ,
optStandalone = True } )
2006-10-17 16:22:29 +02:00
" FILENAME " )
2006-12-31 02:12:01 +01:00
" " -- "File to use for custom header (implies -s)"
2006-10-17 16:22:29 +02:00
, Option " T " [ " title-prefix " ]
( ReqArg
2006-12-20 07:50:14 +01:00
( \ arg opt -> return opt { optTitlePrefix = arg ,
optStandalone = True } )
2006-10-17 16:22:29 +02:00
" STRING " )
2006-12-31 02:12:01 +01:00
" " -- "String to prefix to HTML window title"
2006-10-17 16:22:29 +02:00
, Option " D " [ " print-default-header " ]
( ReqArg
( \ arg opt -> do
let header = case ( lookup arg writers ) of
2006-12-20 07:50:14 +01:00
Just ( writer , head ) -> head
Nothing -> error ( " Unknown reader: " ++ arg )
2006-12-22 21:16:03 +01:00
hPutStr stdout header
2006-10-17 16:22:29 +02:00
exitWith ExitSuccess )
" FORMAT " )
2006-12-31 02:12:01 +01:00
" " -- "Print default header for FORMAT"
2006-12-22 21:16:03 +01:00
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
, Option " " [ " dump-args " ]
2006-12-22 21:16:03 +01:00
( NoArg
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
( \ opt -> return opt { optDumpArgs = True } ) )
" " -- "Print output filename and arguments to stdout."
, Option " " [ " ignore-args " ]
( NoArg
( \ opt -> return opt { optIgnoreArgs = True } ) )
" " -- "Ignore command-line arguments."
2006-12-22 21:16:03 +01:00
, Option " v " [ " version " ]
( NoArg
( \ _ -> do
prg <- getProgName
hPutStrLn stderr ( prg ++ " " ++ version ++
copyrightMessage )
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
exitWith $ ExitFailure 4 ) )
2006-12-31 02:12:01 +01:00
" " -- "Print version"
2006-12-22 21:16:03 +01:00
, Option " h " [ " help " ]
( NoArg
2006-12-28 03:20:09 +01:00
( \ _ -> do
prg <- getProgName
2006-12-31 02:12:01 +01:00
hPutStr stderr ( usageMessage prg options )
2006-12-28 03:20:09 +01:00
exitWith $ ExitFailure 2 ) )
2006-12-31 02:12:01 +01:00
" " -- "Show help"
2006-10-17 16:22:29 +02:00
]
2006-12-22 21:16:03 +01:00
2006-12-31 02:12:01 +01:00
-- Returns usage message
usageMessage :: String -> [ OptDescr ( Opt -> IO Opt ) ] -> String
usageMessage programName options = usageInfo
( programName ++ " [OPTIONS] [FILES] " ++ " \ n Input formats: " ++
joinWithSep " , " ( map fst readers ) ++ " \ n Output formats: " ++
joinWithSep " , " ( map fst writers ) ++ " \ n Options: " )
options
2006-12-28 03:20:09 +01:00
-- Determine default reader based on source file extensions
defaultReaderName :: [ String ] -> String
defaultReaderName [] = " markdown "
defaultReaderName ( x : xs ) =
let x' = map toLower x in
case ( matchRegex ( mkRegex " .* \ \ .(.*) " ) x' ) of
Nothing -> defaultReaderName xs -- no extension
Just [ " xhtml " ] -> " html "
Just [ " html " ] -> " html "
Just [ " htm " ] -> " html "
Just [ " tex " ] -> " latex "
Just [ " latex " ] -> " latex "
Just [ " ltx " ] -> " latex "
Just [ " rst " ] -> " rst "
Just [ " native " ] -> " native "
Just _ -> " markdown "
-- Determine default writer based on output file extension
defaultWriterName :: String -> String
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
defaultWriterName " - " = " html " -- no output file
2006-12-28 03:20:09 +01:00
defaultWriterName x =
let x' = map toLower x in
case ( matchRegex ( mkRegex " .* \ \ .(.*) " ) x' ) of
Nothing -> " markdown " -- no extension
Just [ " " ] -> " markdown " -- empty extension
Just [ " tex " ] -> " latex "
Just [ " latex " ] -> " latex "
Just [ " ltx " ] -> " latex "
Just [ " rtf " ] -> " rtf "
Just [ " rst " ] -> " rst "
Just [ " s5 " ] -> " s5 "
Just [ " native " ] -> " native "
Just [ " txt " ] -> " markdown "
Just [ " text " ] -> " markdown "
Just [ " md " ] -> " markdown "
Just [ " markdown " ] -> " markdown "
2007-01-01 22:08:12 +01:00
Just [ " db " ] -> " docbook "
Just [ " xml " ] -> " docbook "
2007-01-02 01:40:12 +01:00
Just [ " sgml " ] -> " docbook "
2006-12-28 03:20:09 +01:00
Just _ -> " html "
2006-12-22 21:16:03 +01:00
2006-12-28 03:20:09 +01:00
main = do
2006-12-22 21:16:03 +01:00
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
rawArgs <- getArgs
2007-01-02 08:37:42 +01:00
prg <- getProgName
let compatMode = ( prg == " hsmarkdown " )
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
let ( actions , args , errors ) = if compatMode
then ( [] , rawArgs , [] )
else getOpt Permute options rawArgs
2006-12-22 21:16:03 +01:00
if ( not ( null errors ) )
then do
2006-12-28 03:20:09 +01:00
name <- getProgName
2006-12-22 21:16:03 +01:00
mapM ( \ e -> hPutStrLn stderr e ) errors
2006-12-31 02:12:01 +01:00
hPutStr stderr ( usageMessage name options )
2007-01-08 17:29:29 +01:00
exitWith $ ExitFailure 2
2006-12-22 21:16:03 +01:00
else
return ()
2006-10-17 16:22:29 +02:00
2007-01-02 08:37:42 +01:00
let defaultOpts' = if compatMode
then defaultOpts { optReader = " markdown "
, optWriter = " html "
, optStrict = True }
else defaultOpts
2006-10-17 16:22:29 +02:00
-- thread option data structure through all supplied option actions
2007-01-02 08:37:42 +01:00
opts <- foldl ( >>= ) ( return defaultOpts' ) actions
2006-10-17 16:22:29 +02:00
let Opt { optPreserveTabs = preserveTabs
, optTabStop = tabStop
, optStandalone = standalone
2006-12-28 03:20:09 +01:00
, optReader = readerName
, optWriter = writerName
2006-10-17 16:22:29 +02:00
, optParseRaw = parseRaw
, optCSS = css
, optIncludeInHeader = includeHeader
, optIncludeBeforeBody = includeBefore
, optIncludeAfterBody = includeAfter
, optCustomHeader = customHeader
, optTitlePrefix = titlePrefix
2006-12-22 21:16:03 +01:00
, optOutputFile = outputFile
2006-10-17 16:22:29 +02:00
, optNumberSections = numberSections
, optIncremental = incremental
2006-12-18 23:02:39 +01:00
, optSmart = smart
2006-10-17 16:22:29 +02:00
, optASCIIMathML = asciiMathML
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
, optDumpArgs = dumpArgs
, optIgnoreArgs = ignoreArgs
2006-12-30 23:51:49 +01:00
, optStrict = strict
2006-10-17 16:22:29 +02:00
} = opts
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
let sources = if ignoreArgs then [] else args
2006-12-28 03:20:09 +01:00
-- assign reader and writer based on options and filenames
let readerName' = if null readerName
then defaultReaderName sources
else readerName
let writerName' = if null writerName
then defaultWriterName outputFile
else writerName
reader <- case ( lookup readerName' readers ) of
Just r -> return r
Nothing -> error ( " Unknown reader: " ++ readerName' )
( writer , defaultHeader ) <- case ( lookup writerName' writers ) of
Just ( w , h ) -> return ( w , h )
Nothing -> error ( " Unknown writer: " ++ writerName' )
2006-12-22 21:16:03 +01:00
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
output <- if ( outputFile == " - " )
2006-12-22 21:16:03 +01:00
then return stdout
else openFile outputFile WriteMode
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
if dumpArgs
then do
hPutStrLn stdout outputFile
mapM ( \ arg -> hPutStrLn stdout arg ) args
exitWith $ ExitSuccess
2006-12-22 21:16:03 +01:00
else return ()
2006-10-17 16:22:29 +02:00
let tabFilter = if preserveTabs then id else ( tabsToSpaces tabStop )
let addBlank str = str ++ " \ n \ n "
let removeCRs str = filter ( /= '\ r' ) str -- remove DOS-style line endings
let filter = tabFilter . addBlank . removeCRs
2007-01-02 08:37:42 +01:00
let startParserState =
defaultParserState { stateParseRaw = parseRaw ,
stateTabStop = tabStop ,
stateStandalone = standalone && ( not strict ) ,
2007-01-06 19:46:32 +01:00
stateSmart = smart || writerName' == " latex " ,
2007-01-02 08:37:42 +01:00
stateStrict = strict }
2006-12-20 07:50:14 +01:00
let csslink = if ( css == " " )
then " "
else " <link rel= \ " stylesheet \ " href= \ " " ++ css ++
" \ " type= \ " text/css \ " media= \ " all \ " /> \ n "
2006-10-17 16:22:29 +02:00
let asciiMathMLLink = if asciiMathML then asciiMathMLScript else " "
2006-12-20 07:50:14 +01:00
let header = ( if ( customHeader == " DEFAULT " )
then defaultHeader
else customHeader ) ++
2006-10-17 16:22:29 +02:00
csslink ++ asciiMathMLLink ++ includeHeader
2006-12-30 23:51:49 +01:00
let writerOptions = WriterOptions { writerStandalone = standalone &&
( not strict ) ,
2006-10-17 16:22:29 +02:00
writerHeader = header ,
writerTitlePrefix = titlePrefix ,
writerTabStop = tabStop ,
2007-01-01 22:08:12 +01:00
writerNotes = [] ,
2006-12-28 03:20:09 +01:00
writerS5 = ( writerName == " s5 " ) ,
2006-10-17 16:22:29 +02:00
writerIncremental = incremental ,
writerNumberSections = numberSections ,
writerIncludeBefore = includeBefore ,
2006-12-30 23:51:49 +01:00
writerIncludeAfter = includeAfter ,
writerStrictMarkdown = strict }
2006-10-17 16:22:29 +02:00
2006-12-22 21:16:03 +01:00
( readSources sources ) >>= ( hPutStr output . encodeUTF8 .
( writer writerOptions ) .
2006-10-17 16:22:29 +02:00
( reader startParserState ) . filter .
2006-12-22 21:16:03 +01:00
decodeUTF8 . ( joinWithSep " \ n " ) ) >> hClose output
2006-10-17 16:22:29 +02:00
where
readSources [] = mapM readSource [ " - " ]
readSources sources = mapM readSource sources
2006-12-22 21:16:03 +01:00
readSource " - " = getContents
2006-10-17 16:22:29 +02:00
readSource source = readFile source