Refactored man pages.

* Markdown syntax description from README now goes in pandoc_markdown.5.
* Refactored man page construction functions, putting more of
  the work in MakeManPages.hs.
This commit is contained in:
John MacFarlane 2011-01-28 11:55:11 -08:00
parent 5ba5373ec6
commit 8c435578d6
6 changed files with 110 additions and 64 deletions

View file

@ -5,20 +5,65 @@ import Data.Char (toUpper)
import qualified Data.ByteString as B
import Control.Monad
import System.FilePath
import System.Environment (getArgs)
import Text.Pandoc.Shared (normalize)
import System.Directory (getModificationTime)
import System.IO.Error (isDoesNotExistError)
import System.Time (ClockTime(..))
import Data.Maybe (catMaybes)
main = do
rmContents <- liftM toString $ B.readFile "README"
let (Pandoc meta blocks) = readMarkdown defaultParserState rmContents
let newBlocks = removeWrapperSect blocks
manTemplate <- liftM toString $ B.readFile
$ "man" </> "man1" </> "pandoc.1.template"
let manBlocks = removeSect [Str "Wrappers"]
$ removeSect [Str "Pandoc's",Space,Str "markdown"] blocks
let syntaxBlocks = extractSect [Str "Pandoc's",Space,Str "markdown"] blocks
args <- getArgs
let verbose = "--verbose" `elem` args
makeManPage verbose ("man" </> "man1" </> "pandoc.1")
meta manBlocks
makeManPage verbose ("man" </> "man5" </> "pandoc_markdown.5")
meta syntaxBlocks
let markdown2pdfpage = "man" </> "man1" </> "markdown2pdf.1"
modDeps <- modifiedDependencies markdown2pdfpage [markdown2pdfpage <.> "md"]
unless (null modDeps) $ do
mpdfContents <- liftM toString $ B.readFile $ markdown2pdfpage <.> "md"
templ <- liftM toString $ B.readFile $ "templates" </> "man.template"
let doc = readMarkdown defaultParserState{ stateStandalone = True }
mpdfContents
writeManPage markdown2pdfpage templ doc
when verbose $
putStrLn $ "Created " ++ markdown2pdfpage
makeManPage :: Bool -> FilePath -> Meta -> [Block] -> IO ()
makeManPage verbose page meta blocks = do
let templ = page <.> "template"
modDeps <- modifiedDependencies page ["README", templ]
unless (null modDeps) $ do
manTemplate <- liftM toString $ B.readFile templ
writeManPage page manTemplate (Pandoc meta blocks)
when verbose $
putStrLn $ "Created " ++ page
writeManPage :: FilePath -> String -> Pandoc -> IO ()
writeManPage page templ doc = do
let opts = defaultWriterOptions{ writerStandalone = True
, writerTemplate = manTemplate }
, writerTemplate = templ }
let manPage = writeMan opts $
bottomUp (concatMap removeLinks) $
bottomUp capitalizeHeaders $
Pandoc meta newBlocks
B.writeFile ("man" </> "man1" </> "pandoc.1") $ fromString manPage
bottomUp (concatMap removeLinks) $
bottomUp capitalizeHeaders doc
B.writeFile page $ fromString manPage
-- | Returns a list of 'dependencies' that have been modified after 'file'.
modifiedDependencies :: FilePath -> [FilePath] -> IO [FilePath]
modifiedDependencies file dependencies = do
fileModTime <- catch (getModificationTime file) $
\e -> if isDoesNotExistError e
then return (TOD 0 0) -- the minimum ClockTime
else ioError e
depModTimes <- mapM getModificationTime dependencies
let modified = zipWith (\dep time -> if time > fileModTime then Just dep else Nothing) dependencies depModTimes
return $ catMaybes modified
removeLinks :: Inline -> [Inline]
removeLinks (Link l _) = l
@ -32,10 +77,19 @@ capitalize :: Inline -> Inline
capitalize (Str xs) = Str $ map toUpper xs
capitalize x = x
removeWrapperSect :: [Block] -> [Block]
removeWrapperSect (Header 1 [Str "Wrappers"]:xs) =
removeSect :: [Inline] -> [Block] -> [Block]
removeSect ils (Header 1 x:xs) | normalize x == normalize ils =
dropWhile notLevelOneHeader xs
where notLevelOneHeader (Header 1 _) = False
notLevelOneHeader _ = True
removeWrapperSect (x:xs) = x : removeWrapperSect xs
removeWrapperSect [] = []
removeSect ils (x:xs) = x : removeSect ils xs
removeSect _ [] = []
extractSect :: [Inline] -> [Block] -> [Block]
extractSect ils (Header 1 x:xs) | normalize x == normalize ils =
bottomUp promoteHeader xs
where promoteHeader (Header n x) = Header (n-1) x
promoteHeader x = x
extractSect ils (x:xs) = extractSect ils xs
extractSect _ [] = []

21
README
View file

@ -22,9 +22,9 @@ Pandoc's enhanced version of markdown includes syntax for footnotes,
tables, flexible ordered lists, definition lists, delimited code blocks,
superscript, subscript, strikeout, title blocks, automatic tables of
contents, embedded LaTeX math, citations, and markdown inside HTML block
elements. (These enhancements, described below under [Pandoc's markdown
vs. standard markdown](#pandocs-markdown-vs.-standard-markdown),
can be disabled using the `--strict` option.)
elements. (These enhancements, described below under
[Pandoc's markdown](#pandocs-markdown), can be disabled using the `--strict`
option.)
In contrast to most existing tools for converting markdown to HTML, which
use regex substitutions, Pandoc has a modular design: it consists of a
@ -549,15 +549,14 @@ consecutive items:
$for(author)$$author$$sep$, $endfor$
Pandoc's markdown vs. standard markdown
=======================================
Pandoc's markdown
=================
In parsing markdown, Pandoc departs from and extends [standard markdown]
in a few respects. Except where noted, these differences can
be suppressed by specifying the `--strict` command-line option.
[standard markdown]: http://daringfireball.net/projects/markdown/syntax
"Markdown syntax description"
Pandoc understands an extended and slightly revised version of
John Gruber's [markdown] syntax. This document explains the syntax,
noting differences from standard markdown. Except where noted, these
differences can be suppressed by specifying the `--strict` command-line
option.
Backslash escapes
-----------------

View file

@ -9,11 +9,9 @@ import Distribution.Verbosity ( Verbosity, silent )
import Distribution.Simple.InstallDirs (mandir, bindir, CopyDest (NoCopyDest))
import Distribution.Simple.Utils (copyFiles)
import Control.Exception ( bracket_ )
import Control.Monad ( unless )
import System.Process ( rawSystem, runCommand, runProcess, waitForProcess )
import System.FilePath ( (</>), (<.>) )
import System.Process ( rawSystem, runCommand, waitForProcess )
import System.FilePath ( (</>) )
import System.Directory
import System.IO ( stderr )
import System.Exit
import System.Time
import System.IO.Error ( isDoesNotExistError )
@ -48,46 +46,23 @@ runTestSuite args _ pkg lbi = do
putStrLn "Build pandoc with the 'tests' flag to run tests"
exitWith $ ExitFailure 3
-- | Build man pages from markdown sources in man/man1/.
-- | Build man pages from markdown sources in man/
makeManPages :: Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()
makeManPages _ flags _ bi = do
let pandocPath = (buildDir bi) </> "pandoc" </> "pandoc"
makeManPages _ flags _ _ = do
let verbosity = fromFlag $ buildVerbosity flags
-- make markdown2pdf.1 from markdown2pdf.1.md
makeManPage pandocPath verbosity "markdown2pdf.1"
-- make pandoc.1 from README
let pandocpage = manDir </> "pandoc.1"
modifiedDeps <- modifiedDependencies pandocpage ["README"]
unless (null modifiedDeps) $ do
let cmd = "runghc -package-conf=dist/package.conf.inplace MakeManPage.hs"
ec <- runCommand cmd >>= waitForProcess
case ec of
ExitSuccess -> unless (verbosity == silent) $
putStrLn $ "Created " ++ pandocpage
ExitFailure n -> putStrLn ("Error creating " ++ pandocpage ++
". Exit code = " ++ show n) >> exitWith ec
let cmd = "runghc -package-conf=dist/package.conf.inplace MakeManPage.hs"
let cmd' = if verbosity == silent
then cmd
else cmd ++ " --verbose"
runCommand cmd' >>= waitForProcess >>= exitWith
manpages :: [FilePath]
manpages = ["pandoc.1", "markdown2pdf.1"]
manpages = ["man1" </> "pandoc.1"
,"man1" </> "markdown2pdf.1"
,"man5" </> "pandoc_markdown.5"]
manDir :: FilePath
manDir = "man" </> "man1"
-- | Build a man page from markdown source in man/man1.
makeManPage :: FilePath -> Verbosity -> FilePath -> IO ()
makeManPage pandoc verbosity manpage = do
let page = manDir </> manpage
let source = page <.> "md"
modifiedDeps <- modifiedDependencies page [source]
unless (null modifiedDeps) $ do
ec <- runProcess pandoc ["-s", "-S", "-r", "markdown", "-w", "man",
"--template=templates/man.template", "-o", page, source]
Nothing Nothing Nothing Nothing (Just stderr) >>= waitForProcess
case ec of
ExitSuccess -> unless (verbosity == silent) $
putStrLn $ "Created " ++ page
ExitFailure n -> putStrLn ("Error creating " ++ page ++
". Exit code = " ++ show n) >> exitWith ec
manDir = "man"
installScripts :: PackageDescription -> LocalBuildInfo
-> Verbosity -> CopyDest -> IO ()
@ -101,7 +76,7 @@ installScripts pkg lbi verbosity copy =
installManpages :: PackageDescription -> LocalBuildInfo
-> Verbosity -> CopyDest -> IO ()
installManpages pkg lbi verbosity copy =
copyFiles verbosity (mandir (absoluteInstallDirs pkg lbi copy) </> "man1")
copyFiles verbosity (mandir (absoluteInstallDirs pkg lbi copy))
(zip (repeat manDir) manpages)
-- | Returns a list of 'dependencies' that have been modified after 'file'.

View file

@ -5,9 +5,12 @@ $endif$
.SH NAME
pandoc - general markup converter
$body$
.SH PANDOC'S MARKDOWN
For a complete description of pandoc's extensions to standard markdown,
see \f[C]pandoc_markdown\f[] (5).
.SH SEE ALSO
.PP
\f[C]markdown2pdf\f[] (1).
\f[C]markdown2pdf\f[] (1), \f[C]pandoc_markdown\f[] (5).
.PP
The Pandoc source code and all documentation may be downloaded
from <http://johnmacfarlane.net/pandoc/>.

View file

@ -0,0 +1,11 @@
$if(has-tables)$
.\"t
$endif$
.TH PANDOC_MARKDOWN 5 "$date$" "$title$"
.SH NAME
pandoc_markdown - markdown syntax for pandoc(1)
.SH DESCRIPTION
$body$
.SH SEE ALSO
.PP
\f[C]pandoc\f[] (1).

View file

@ -74,9 +74,11 @@ Extra-Source-Files:
-- code to create pandoc.1 man page
MakeManPage.hs,
man/man1/pandoc.1.template,
man/man5/pandoc_markdown.5.template,
-- generated man pages (produced post-build)
man/man1/markdown2pdf.1,
man/man1/pandoc.1,
man/man5/pandoc_markdown.5,
-- benchmarks
Benchmark.hs,
-- tests
@ -156,7 +158,9 @@ Extra-Source-Files:
tests/lhs-test.nohl.html,
tests/lhs-test.nohl.html+lhs,
tests/lhs-test.fragment.html+lhs
Extra-Tmp-Files: man/man1/pandoc.1, man/man1/markdown2pdf.1
Extra-Tmp-Files: man/man1/pandoc.1,
man/man1/markdown2pdf.1,
man/man5/pandoc_markdown.5
Flag threaded
Description: Compile markdown2pdf with -threaded option.