diff options
| -rw-r--r-- | src/Text/Pandoc/Writers/Man.hs | 40 | ||||
| -rw-r--r-- | tests/tables.man | 2 | ||||
| -rw-r--r-- | tests/writer.man | 46 | 
3 files changed, 42 insertions, 46 deletions
| diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 3c6be434b..0fd78dadf 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -35,7 +35,7 @@ import Text.Pandoc.Shared  import Text.Pandoc.Readers.TeXMath  import Text.Printf ( printf )  import Data.List ( isPrefixOf, intersperse, intercalate ) -import Text.PrettyPrint.HughesPJ hiding ( Str ) +import Text.Pandoc.Pretty  import Control.Monad.State  type Notes = [[Block]] @@ -52,27 +52,31 @@ pandocToMan opts (Pandoc (Meta title authors date) blocks) = do    titleText <- inlineListToMan opts title    authors' <- mapM (inlineListToMan opts) authors    date' <- inlineListToMan opts date  -  let (cmdName, rest) = break (== ' ') $ render titleText +  let colwidth = if writerWrapText opts +                    then Just $ writerColumns opts +                    else Nothing +  let render' = render colwidth +  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)                     +                            xs -> (text (reverse xs), doubleQuotes 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 $ body $$ notes' $$ text "" +  let main = render' $ body $$ notes' $$ text ""    hasTables <- liftM stHasTables get    let context  = writerVariables opts ++                   [ ("body", main) -                 , ("title", render title') -                 , ("section", render section) -                 , ("date", render date') -                 , ("description", render description) ] ++ +                 , ("title", render' title') +                 , ("section", render' section) +                 , ("date", render' date') +                 , ("description", render' description) ] ++                   [ ("has-tables", "yes") | hasTables ] ++ -                 [ ("author", render a) | a <- authors' ] +                 [ ("author", render' a) | a <- authors' ]    if writerStandalone opts       then return $ renderTemplate context $ writerTemplate opts       else return main @@ -89,7 +93,7 @@ notesToMan opts notes =  noteToMan :: WriterOptions -> Int -> [Block] -> State WriterState Doc  noteToMan opts num note = do    contents <- blockListToMan opts note -  let marker = text "\n.SS [" <> text (show num) <> char ']' +  let marker = cr <> text ".SS " <> brackets (text (show num))    return $ marker $$ contents   -- | Association list of characters to escape. @@ -136,14 +140,13 @@ blockToMan :: WriterOptions -- ^ Options                  -> State WriterState Doc   blockToMan _ Null = return empty  blockToMan opts (Plain inlines) =  -  liftM vcat $ mapM (wrapIfNeeded opts (inlineListToMan opts)) $ -    splitSentences inlines +  liftM vcat $ mapM (inlineListToMan opts) $ splitSentences inlines  blockToMan opts (Para inlines) = do -  contents <- liftM vcat $ mapM (wrapIfNeeded opts (inlineListToMan opts)) $ +  contents <- liftM vcat $ mapM (inlineListToMan opts) $      splitSentences inlines    return $ text ".PP" $$ contents   blockToMan _ (RawHtml _) = return empty -blockToMan _ HorizontalRule = return $ text $ ".PP\n   *   *   *   *   *" +blockToMan _ HorizontalRule = return $ text ".PP" $$ text "   *   *   *   *   *"  blockToMan opts (Header level inlines) = do    contents <- inlineListToMan opts inlines    let heading = case level of @@ -256,7 +259,7 @@ definitionListItemToMan opts (label, defs) = do                                    mapM (\item -> blockToMan opts item) rest                          first' <- blockToMan opts first                          return $ first' $$ text ".RS" $$ rest' $$ text ".RE" -  return $ text ".TP\n.B " <> labelText $+$ contents +  return $ text ".TP" $$ text ".B " <> labelText $$ contents  -- | Convert list of Pandoc block elements to man.  blockListToMan :: WriterOptions -- ^ Options @@ -309,11 +312,12 @@ inlineToMan _ (Str str) = return $ text $ escapeString str  inlineToMan opts (Math InlineMath str) = inlineListToMan opts $ readTeXMath str  inlineToMan opts (Math DisplayMath str) = do    contents <- inlineListToMan opts $ readTeXMath str -  return $ text ".RS" $$ contents $$ text ".RE" +  return $ cr <> text ".RS" $$ contents $$ text ".RE"  inlineToMan _ (TeX _) = return empty  inlineToMan _ (HtmlInline _) = return empty -inlineToMan _ (LineBreak) = return $ text "\n.PD 0\n.P\n.PD\n" -inlineToMan _ Space = return $ char ' ' +inlineToMan _ (LineBreak) = return $ +  cr <> text ".PD 0" $$ text ".P" $$ text ".PD" <> cr +inlineToMan _ Space = return space  inlineToMan opts (Link txt (src, _)) = do    linktext <- inlineListToMan opts txt    let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src diff --git a/tests/tables.man b/tests/tables.man index 35922b4df..5f57ae5a7 100644 --- a/tests/tables.man +++ b/tests/tables.man @@ -264,4 +264,4 @@ T}@T{  Here\[aq]s another one.  Note the blank line between rows.  T} -.TE +.TE
\ No newline at end of file diff --git a/tests/writer.man b/tests/writer.man index e4dc0c7de..80897f252 100644 --- a/tests/writer.man +++ b/tests/writer.man @@ -26,8 +26,8 @@ Here's a regular paragraph.  In Markdown 1.0.0 and earlier.  Version 8.  This line turns into a list item. -Because a hard-wrapped line in the middle of a paragraph looked -like a list item. +Because a hard-wrapped line in the middle of a paragraph looked like a list +item.  .PP  Here's one with a bullet.  * criminey. @@ -531,8 +531,8 @@ Superscripts: a^bc^d a^\f[I]hello\f[]^ a^hello\ there^.  .PP  Subscripts: H~2~O, H~23~O, H~many\ of\ them~O.  .PP -These should not be superscripts or subscripts, because of the -unescaped spaces: a^b c^d, a~b c~d. +These should not be superscripts or subscripts, because of the unescaped +spaces: a^b c^d, a~b c~d.  .PP     *   *   *   *   *  .SH Smart quotes, ellipses, dashes @@ -547,8 +547,8 @@ So is `pine.'  .PP  `He said, \[lq]I want to go.\[rq]' Were you alive in the 70's?  .PP -Here is some quoted `\f[C]code\f[]' and a -\[lq]quoted link (http://example.com/?foo=1&bar=2)\[rq]. +Here is some quoted `\f[C]code\f[]' and a \[lq]quoted +link (http://example.com/?foo=1&bar=2)\[rq].  .PP  Some dashes: one\[em]two \[em] three\[em]four \[em] five.  .PP @@ -641,7 +641,7 @@ Greater-than: >  .PP  Hash: #  .PP -Period: \&. +Period: .  .PP  Bang: !  .PP @@ -701,11 +701,9 @@ Foo bar (/url/).  Foo biz (/url/).  .SS With ampersands  .PP -Here's a -link with an ampersand in the URL (http://example.com/?foo=1&bar=2). +Here's a link with an ampersand in the URL (http://example.com/?foo=1&bar=2).  .PP -Here's a link with an amersand in the link text: -AT&T (http://att.com/). +Here's a link with an amersand in the link text: AT&T (http://att.com/).  .PP  Here's an inline link (/script?foo=1&bar=2).  .PP @@ -746,9 +744,9 @@ Here is a movie [IMAGE: movie (movie.jpg)] icon.     *   *   *   *   *  .SH Footnotes  .PP -Here is a footnote reference,[1] and another.[2] This should -\f[I]not\f[] be a footnote reference, because it contains a -space.[^my note] Here is an inline note.[3] +Here is a footnote reference,[1] and another.[2] This should \f[I]not\f[] be a +footnote reference, because it contains a space.[^my note] Here is an inline +note.[3]  .RS  .PP  Notes can go in quotes.[4] @@ -756,23 +754,20 @@ Notes can go in quotes.[4]  .IP "1." 3  And in list items.[5]  .PP -This paragraph should not be part of the note, as it is not -indented. +This paragraph should not be part of the note, as it is not indented.  .SH NOTES -  .SS [1]  .PP  Here is the footnote.  It can go anywhere after the footnote reference.  It need not be placed at the end of the document. -  .SS [2]  .PP  Here's the long note.  This one contains multiple blocks.  .PP -Subsequent blocks are indented to show that they belong to the -footnote (as with list items). +Subsequent blocks are indented to show that they belong to the footnote (as +with list items).  .IP  .nf  \f[C] @@ -780,19 +775,16 @@ footnote (as with list items).  \f[]  .fi  .PP -If you want, you can indent every line, but you can also be lazy -and just indent the first line of each block. - +If you want, you can indent every line, but you can also be lazy and just +indent the first line of each block.  .SS [3]  .PP  This is \f[I]easier\f[] to type. -Inline notes may contain links (http://google.com) and \f[C]]\f[] -verbatim characters, as well as [bracketed text]. - +Inline notes may contain links (http://google.com) and \f[C]]\f[] verbatim +characters, as well as [bracketed text].  .SS [4]  .PP  In quote. -  .SS [5]  .PP  In list. | 
