summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Man.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/Man.hs')
-rw-r--r--src/Text/Pandoc/Writers/Man.hs78
1 files changed, 39 insertions, 39 deletions
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index c481e6c87..f6f570042 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -17,9 +17,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{- |
- Module : Text.Pandoc.Writers.Man
+ Module : Text.Pandoc.Writers.Man
Copyright : Copyright (C) 2007-2010 John MacFarlane
- License : GNU GPL, version 2 or above
+ License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
Stability : alpha
@@ -44,21 +44,21 @@ data WriterState = WriterState { stNotes :: Notes
-- | Convert Pandoc to Man.
writeMan :: WriterOptions -> Pandoc -> String
-writeMan opts document = evalState (pandocToMan opts document) (WriterState [] False)
+writeMan opts document = evalState (pandocToMan opts document) (WriterState [] False)
-- | Return groff man representation of document.
pandocToMan :: WriterOptions -> Pandoc -> State WriterState String
pandocToMan opts (Pandoc (Meta title authors date) blocks) = do
titleText <- inlineListToMan opts title
authors' <- mapM (inlineListToMan opts) authors
- date' <- inlineListToMan opts date
+ date' <- inlineListToMan opts date
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'] ->
+ (')':d:'(':xs) | d `elem` ['0'..'9'] ->
(text (reverse xs), char d)
xs -> (text (reverse xs), doubleQuotes empty)
let description = hsep $
@@ -86,7 +86,7 @@ notesToMan :: WriterOptions -> [[Block]] -> State WriterState Doc
notesToMan opts notes =
if null notes
then return empty
- else mapM (\(num, note) -> noteToMan opts num note) (zip [1..] notes) >>=
+ else mapM (\(num, note) -> noteToMan opts num note) (zip [1..] notes) >>=
return . (text ".SH NOTES" $$) . vcat
-- | Return man representation of a note.
@@ -94,7 +94,7 @@ noteToMan :: WriterOptions -> Int -> [Block] -> State WriterState Doc
noteToMan opts num note = do
contents <- blockListToMan opts note
let marker = cr <> text ".SS " <> brackets (text (show num))
- return $ marker $$ contents
+ return $ marker $$ contents
-- | Association list of characters to escape.
manEscapes :: [(Char, String)]
@@ -113,7 +113,7 @@ escapeString = escapeStringUsing manEscapes
-- | Escape a literal (code) section for Man.
escapeCode :: String -> String
escapeCode = concat . intersperse "\n" . map escapeLine . lines where
- escapeLine codeline =
+ escapeLine codeline =
case escapeStringUsing (manEscapes ++ backslashEscapes "\t ") codeline of
a@('.':_) -> "\\&" ++ a
b -> b
@@ -150,14 +150,14 @@ splitSentences xs =
-- | Convert Pandoc block element to man.
blockToMan :: WriterOptions -- ^ Options
-> Block -- ^ Block element
- -> State WriterState Doc
+ -> State WriterState Doc
blockToMan _ Null = return empty
-blockToMan opts (Plain inlines) =
+blockToMan opts (Plain inlines) =
liftM vcat $ mapM (inlineListToMan opts) $ splitSentences inlines
blockToMan opts (Para inlines) = do
contents <- liftM vcat $ mapM (inlineListToMan opts) $
splitSentences inlines
- return $ text ".PP" $$ contents
+ return $ text ".PP" $$ contents
blockToMan _ (RawBlock "man" str) = return $ text str
blockToMan _ (RawBlock _ _) = return empty
blockToMan _ HorizontalRule = return $ text ".PP" $$ text " * * * * *"
@@ -166,7 +166,7 @@ blockToMan opts (Header level inlines) = do
let heading = case level of
1 -> ".SH "
_ -> ".SS "
- return $ text heading <> contents
+ return $ text heading <> contents
blockToMan _ (CodeBlock _ str) = return $
text ".IP" $$
text ".nf" $$
@@ -174,10 +174,10 @@ blockToMan _ (CodeBlock _ str) = return $
text (escapeCode str) $$
text "\\f[]" $$
text ".fi"
-blockToMan opts (BlockQuote blocks) = do
+blockToMan opts (BlockQuote blocks) = do
contents <- blockListToMan opts blocks
return $ text ".RS" $$ contents $$ text ".RE"
-blockToMan opts (Table caption alignments widths headers rows) =
+blockToMan opts (Table caption alignments widths headers rows) =
let aligncode AlignLeft = "l"
aligncode AlignRight = "r"
aligncode AlignCenter = "c"
@@ -190,53 +190,53 @@ blockToMan opts (Table caption alignments widths headers rows) =
else map (printf "w(%0.2fn)" . (70 *)) widths
-- 78n default width - 8n indent = 70n
let coldescriptions = text $ intercalate " "
- (zipWith (\align width -> aligncode align ++ width)
+ (zipWith (\align width -> aligncode align ++ width)
alignments iwidths) ++ "."
colheadings <- mapM (blockListToMan opts) headers
- let makeRow cols = text "T{" $$
- (vcat $ intersperse (text "T}@T{") cols) $$
+ let makeRow cols = text "T{" $$
+ (vcat $ intersperse (text "T}@T{") cols) $$
text "T}"
let colheadings' = if all null headers
then empty
else makeRow colheadings $$ char '_'
- body <- mapM (\row -> do
+ body <- mapM (\row -> do
cols <- mapM (blockListToMan opts) row
return $ makeRow cols) rows
- return $ text ".PP" $$ caption' $$
- text ".TS" $$ text "tab(@);" $$ coldescriptions $$
+ return $ text ".PP" $$ caption' $$
+ text ".TS" $$ text "tab(@);" $$ coldescriptions $$
colheadings' $$ vcat body $$ text ".TE"
blockToMan opts (BulletList items) = do
contents <- mapM (bulletListItemToMan opts) items
- return (vcat contents)
+ return (vcat contents)
blockToMan opts (OrderedList attribs items) = do
- let markers = take (length items) $ orderedListMarkers attribs
+ let markers = take (length items) $ orderedListMarkers attribs
let indent = 1 + (maximum $ map length markers)
contents <- mapM (\(num, item) -> orderedListItemToMan opts num indent item) $
- zip markers items
+ zip markers items
return (vcat contents)
-blockToMan opts (DefinitionList items) = do
+blockToMan opts (DefinitionList items) = do
contents <- mapM (definitionListItemToMan opts) items
return (vcat contents)
-- | Convert bullet list item (list of blocks) to man.
bulletListItemToMan :: WriterOptions -> [Block] -> State WriterState Doc
bulletListItemToMan _ [] = return empty
-bulletListItemToMan opts ((Para first):rest) =
+bulletListItemToMan opts ((Para first):rest) =
bulletListItemToMan opts ((Plain first):rest)
bulletListItemToMan opts ((Plain first):rest) = do
- first' <- blockToMan opts (Plain first)
+ first' <- blockToMan opts (Plain first)
rest' <- blockListToMan opts rest
let first'' = text ".IP \\[bu] 2" $$ first'
let rest'' = if null rest
then empty
else text ".RS 2" $$ rest' $$ text ".RE"
- return (first'' $$ rest'')
+ return (first'' $$ rest'')
bulletListItemToMan opts (first:rest) = do
first' <- blockToMan opts first
rest' <- blockListToMan opts rest
return $ text "\\[bu] .RS 2" $$ first' $$ rest' $$ text ".RE"
-
+
-- | Convert ordered list item (a list of blocks) to man.
orderedListItemToMan :: WriterOptions -- ^ options
-> String -- ^ order marker for list item
@@ -244,7 +244,7 @@ orderedListItemToMan :: WriterOptions -- ^ options
-> [Block] -- ^ list item (list of blocks)
-> State WriterState Doc
orderedListItemToMan _ _ _ [] = return empty
-orderedListItemToMan opts num indent ((Para first):rest) =
+orderedListItemToMan opts num indent ((Para first):rest) =
orderedListItemToMan opts num indent ((Plain first):rest)
orderedListItemToMan opts num indent (first:rest) = do
first' <- blockToMan opts first
@@ -254,17 +254,17 @@ orderedListItemToMan opts num indent (first:rest) = do
let rest'' = if null rest
then empty
else text ".RS 4" $$ rest' $$ text ".RE"
- return $ first'' $$ rest''
+ return $ first'' $$ rest''
-- | Convert definition list item (label, list of blocks) to man.
definitionListItemToMan :: WriterOptions
- -> ([Inline],[[Block]])
+ -> ([Inline],[[Block]])
-> State WriterState Doc
definitionListItemToMan opts (label, defs) = do
labelText <- inlineListToMan opts label
- contents <- if null defs
+ contents <- if null defs
then return empty
- else liftM vcat $ forM defs $ \blocks -> do
+ else liftM vcat $ forM defs $ \blocks -> do
let (first, rest) = case blocks of
((Para x):y) -> (Plain x,y)
(x:y) -> (x,y)
@@ -278,7 +278,7 @@ definitionListItemToMan opts (label, defs) = do
-- | Convert list of Pandoc block elements to man.
blockListToMan :: WriterOptions -- ^ Options
-> [Block] -- ^ List of block elements
- -> State WriterState Doc
+ -> State WriterState Doc
blockListToMan opts blocks =
mapM (blockToMan opts) blocks >>= (return . vcat)
@@ -292,7 +292,7 @@ inlineListToMan opts lst = mapM (inlineToMan opts) lst >>= (return . hcat)
-- | Convert Pandoc inline element to man.
inlineToMan :: WriterOptions -> Inline -> State WriterState Doc
-inlineToMan opts (Emph lst) = do
+inlineToMan opts (Emph lst) = do
contents <- inlineListToMan opts lst
return $ text "\\f[I]" <> contents <> text "\\f[]"
inlineToMan opts (Strong lst) = do
@@ -333,16 +333,16 @@ inlineToMan opts (Link txt (src, _)) = do
let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src
return $ case txt of
[Code _ s]
- | s == srcSuffix -> char '<' <> text srcSuffix <> char '>'
+ | s == srcSuffix -> char '<' <> text srcSuffix <> char '>'
_ -> linktext <> text " (" <> text src <> char ')'
inlineToMan opts (Image alternate (source, tit)) = do
- let txt = if (null alternate) || (alternate == [Str ""]) ||
+ let txt = if (null alternate) || (alternate == [Str ""]) ||
(alternate == [Str source]) -- to prevent autolinks
then [Str "image"]
else alternate
- linkPart <- inlineToMan opts (Link txt (source, tit))
+ linkPart <- inlineToMan opts (Link txt (source, tit))
return $ char '[' <> text "IMAGE: " <> linkPart <> char ']'
-inlineToMan _ (Note contents) = do
+inlineToMan _ (Note contents) = do
-- add to notes in state
modify $ \st -> st{ stNotes = contents : stNotes st }
notes <- liftM stNotes get