diff options
| author | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2009-12-31 01:17:27 +0000 | 
|---|---|---|
| committer | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2009-12-31 01:17:27 +0000 | 
| commit | 87537c3ff829d7cbcd56d34d03da7ce559e2898d (patch) | |
| tree | d78c33df3fa0a5fbf5b485c874de9d35599fd7dd | |
| parent | bf42fa1f54d8cff0c13f834252b87dd58fd3139d (diff) | |
| download | pandoc-87537c3ff829d7cbcd56d34d03da7ce559e2898d.tar.gz | |
Revised man writer to use new templates.
Note that now the "--after-body" will come after the "AUTHORS"
section, whereas before it would come before it.  This is a
slight break from backwards compatibility.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@1733 788f1e2b-df1e-0410-8736-df70ead52e1b
| -rw-r--r-- | src/Text/Pandoc/Writers/Man.hs | 79 | ||||
| -rw-r--r-- | templates/man.template | 87 | ||||
| -rw-r--r-- | tests/writer.man | 3 | 
3 files changed, 51 insertions, 118 deletions
| diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 64fd24ad0..937d10b25 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -30,62 +30,56 @@ Conversion of 'Pandoc' documents to groff man page format.  -}  module Text.Pandoc.Writers.Man ( writeMan) where  import Text.Pandoc.Definition +import Text.Pandoc.Templates  import Text.Pandoc.Shared  import Text.Printf ( printf ) -import Data.List ( isPrefixOf, drop, nub, intersperse, intercalate ) +import Data.List ( isPrefixOf, drop, intersperse, intercalate )  import Text.PrettyPrint.HughesPJ hiding ( Str )  import Control.Monad.State  import Control.Monad ( liftM )  type Notes = [[Block]] -type Preprocessors = [String] -- e.g. "t" for tbl -type WriterState = (Notes, Preprocessors) +data WriterState = WriterState { stNotes  :: Notes +                               , stHasTables :: Bool }  -- | Convert Pandoc to Man.  writeMan :: WriterOptions -> Pandoc -> String -writeMan opts document = render $ evalState (pandocToMan opts document) ([],[])  +writeMan opts document = evalState (pandocToMan opts document) (WriterState [] False)   -- | Return groff man representation of document. -pandocToMan :: WriterOptions -> Pandoc -> State WriterState Doc -pandocToMan opts (Pandoc meta blocks) = do -  return empty -- TODO ---  let before  = writerIncludeBefore opts ---  let after   = writerIncludeAfter opts ---  let before' = if null before then empty else text before ---  let after'  = if null after then empty else text after ---  (head', foot) <- metaToMan opts meta ---  body <- blockListToMan opts blocks ---  (notes, preprocessors) <- get ---  let preamble = if null preprocessors || not (writerStandalone opts) ---                    then empty ---                    else text $ ".\\\" " ++ concat (nub preprocessors) ---  notes' <- notesToMan opts (reverse notes) ---  return $ preamble $$ head' $$ before' $$ body $$ notes' $$ foot $$ after' - --- | Insert bibliographic information into Man header and footer. -metaToMan :: WriterOptions -- ^ Options, including Man header -          -> Meta          -- ^ Meta with bibliographic information -          -> State WriterState (Doc, Doc) -metaToMan options (Meta title authors date) = do -  titleText <- inlineListToMan options title -  authorsText <- mapM (inlineListToMan options) authors -  dateText <- inlineListToMan options date  +pandocToMan :: WriterOptions -> Pandoc -> State WriterState String +pandocToMan opts (Pandoc (Meta title authors date) blocks) = do +  let before  = writerIncludeBefore opts +  let after   = writerIncludeAfter opts +  let before' = if null before then empty else text before +  let after'  = if null after then empty else text after +  titleText <- inlineListToMan opts title +  authors' <- mapM (inlineListToMan opts) authors +  date' <- inlineListToMan opts date     let (cmdName, rest) = break (== ' ') $ render titleText    let (title', section) = case reverse cmdName of                              (')':d:'(':xs) | d `elem` ['0'..'9'] ->                                     (text (reverse xs), char d)                              xs -> (text (reverse xs), doubleQuotes empty)                     -  let extras = map (doubleQuotes . text . removeLeadingTrailingSpace) $ -               splitBy '|' rest -  let head' = (text ".TH") <+> title' <+> section <+>  -             doubleQuotes dateText <+> hsep extras -  let foot = case length authorsText of -                0 -> empty -                1 -> text ".SH AUTHOR" $$ (hcat $ intersperse (text ", ") authorsText) -                _ -> text ".SH AUTHORS" $$ (hcat $ intersperse (text ", ") authorsText) -  return $ if writerStandalone options -              then (head', foot) -              else (empty, empty) +  let description = hsep $ +                    map (doubleQuotes . text . removeLeadingTrailingSpace) $ +                    splitBy '|' rest +  body <- blockListToMan opts blocks +  notes <- liftM stNotes get +  notes' <- notesToMan opts (reverse notes) +  let main = render $ before' $$ body $$ notes' $$ after' +  hasTables <- liftM stHasTables get +  let context  = writerVariables opts ++ +                 [ ("body", main) +                 , ("title", render title') +                 , ("section", render section) +                 , ("date", render date') +                 , ("description", render description) ] ++ +                 [ ("has-tables", "yes") | hasTables ] ++ +                 [ ("author", render a) | a <- authors' ] +  if writerStandalone opts +     then return $ renderTemplate context $ writerTemplate opts +     else return main  -- | Return man representation of notes.  notesToMan :: WriterOptions -> [[Block]] -> State WriterState Doc @@ -173,7 +167,7 @@ blockToMan opts (Table caption alignments widths headers rows) =        aligncode AlignDefault = "l"    in do    caption' <- inlineListToMan opts caption -  modify (\(notes, preprocessors) -> (notes, "t":preprocessors)) +  modify $ \st -> st{ stHasTables = True }    let iwidths = if all (== 0) widths                     then repeat ""                     else map (printf "w(%0.2fn)" . (70 *)) widths @@ -332,8 +326,9 @@ inlineToMan opts (Image alternate (source, tit)) = do    linkPart <- inlineToMan opts (Link txt (source, tit))     return $ char '[' <> text "IMAGE: " <> linkPart <> char ']'  inlineToMan _ (Note contents) = do  -  modify (\(notes, prep) -> (contents:notes, prep)) -- add to notes in state -  (notes, _) <- get +  -- add to notes in state +  modify $ \st -> st{ stNotes = contents : stNotes st } +  notes <- liftM stNotes get    let ref = show $ (length notes)    return $ char '[' <> text ref <> char ']' diff --git a/templates/man.template b/templates/man.template index 993115ab9..586724395 100644 --- a/templates/man.template +++ b/templates/man.template @@ -1,75 +1,12 @@ -<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> -<html xmlns="http://www.w3.org/1999/xhtml" -><head -  ><title -    >title</title -    ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" -     /><meta name="generator" content="pandoc" -     /><meta name="author" content="$authors$" -     /><meta name="date" content="$date$" -     />$header-includes$ -</head -  ><body -  > -<h1 class="title" -    ><span class="math" -      ><em -	>title</em -	></span -      ></h1 -    ><div id="TOC" -    ><ul -      ><li -	><a href="#section-oen" -	  >section oen</a -	  ></li -	></ul -      ></div -    ><div id="section-oen" -    ><h1 -      ><a href="#TOC" -	>section oen</a -	></h1 -      ><ol style="list-style-type: decimal;" -      ><li -	>one<ol style="list-style-type: lower-alpha;" -	  ><li -	    >two<ol start="3" style="list-style-type: lower-roman;" -	      ><li -		>three</li -		></ol -	      ></li -	    ></ol -	  ></li -	></ol -      ><pre class="haskell" -      ><code -	>hi -</code -	></pre -      ><p -      >footnote<a href="#fn1" class="footnoteRef" id="fnref1" -	><sup -	  >1</sup -	  ></a -	></p -      ></div -    ><div class="footnotes" -    ><hr -       /><ol -      ><li id="fn1" -	><p -	  >with code</p -	  ><pre -	  ><code -	    >code -</code -	    ></pre -	  > <a href="#fnref1" class="footnoteBackLink" title="Jump back to footnote 1">↩</a></li -	></ol -      ></div -    > -</body -  ></html -> - +$if(has-tables)$ +.\"t +$endif$ +.TH $title$ $section$ "$date$" $description$ +$for(header-includes)$ +$header-includes$ +$endfor$ +$body$ +$if(author)$ +.SH AUTHORS +$for(author)$$author$$sep$; $endfor$. +$endif$ diff --git a/tests/writer.man b/tests/writer.man index 692f8f036..1048bc701 100644 --- a/tests/writer.man +++ b/tests/writer.man @@ -776,4 +776,5 @@ In quote.  .PP  In list.  .SH AUTHORS -John MacFarlane, Anonymous +John MacFarlane; Anonymous. + | 
