aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Man.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2018-10-17 17:23:14 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2018-10-17 17:26:37 -0700
commitf48960b75fe2d7ae532ec17a060109c92b893f57 (patch)
treea63b379a0072f6727ce7d07310dd8fffee5c43d0 /src/Text/Pandoc/Writers/Man.hs
parentb3feaba6af38d621d331afb83a266e2a2ccf6ea4 (diff)
downloadpandoc-f48960b75fe2d7ae532ec17a060109c92b893f57.tar.gz
Move common groff functions to Text.Pandoc.Writers.Groff
(unexported module). These are used in both the man and ms writers. Moved groffEscape out of Text.Pandoc.Writers.Shared [cancels earlier API change from adding it, which was after last release]. This fixes strong/code combination on man (should be `\f[CB]` not `\f[BC]`), mentioned in #4973. Updated tests. Closes #4975.
Diffstat (limited to 'src/Text/Pandoc/Writers/Man.hs')
-rw-r--r--src/Text/Pandoc/Writers/Man.hs58
1 files changed, 2 insertions, 56 deletions
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index 247666b33..65aec81b3 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -33,8 +33,7 @@ Conversion of 'Pandoc' documents to groff man page format.
module Text.Pandoc.Writers.Man ( writeMan) where
import Prelude
import Control.Monad.State.Strict
-import Data.List (intercalate, intersperse, sort, stripPrefix)
-import qualified Data.Map as Map
+import Data.List (intersperse, stripPrefix)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
@@ -48,22 +47,9 @@ import Text.Pandoc.Shared
import Text.Pandoc.Templates
import Text.Pandoc.Writers.Math
import Text.Pandoc.Writers.Shared
+import Text.Pandoc.Writers.Groff
import Text.Printf (printf)
-type Notes = [[Block]]
-data WriterState = WriterState { stNotes :: Notes
- , stFontFeatures :: Map.Map Char Bool
- , stHasTables :: Bool }
-
-defaultWriterState :: WriterState
-defaultWriterState = WriterState { stNotes = []
- , stFontFeatures = Map.fromList [
- ('I',False)
- , ('B',False)
- , ('C',False)
- ]
- , stHasTables = False }
-
-- | Convert Pandoc to Man.
writeMan :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeMan opts document =
@@ -127,28 +113,6 @@ noteToMan opts num note = do
let marker = cr <> text ".SS " <> brackets (text (show num))
return $ marker $$ contents
--- | Association list of characters to escape.
-manEscapes :: [(Char, String)]
-manEscapes = [ ('\160', "\\ ")
- , ('\'', "\\[aq]")
- , ('’', "'")
- , ('\x2014', "\\[em]")
- , ('\x2013', "\\[en]")
- , ('\x2026', "\\&...")
- ] ++ backslashEscapes "-@\\"
-
--- | Escape special characters for Man.
-escapeString :: String -> String
-escapeString = escapeStringUsing manEscapes
-
--- | Escape a literal (code) section for Man.
-escapeCode :: String -> String
-escapeCode = intercalate "\n" . map escapeLine . lines where
- escapeLine codeline =
- case escapeStringUsing (manEscapes ++ backslashEscapes "\t ") codeline of
- a@('.':_) -> "\\&" ++ a
- b -> b
-
-- We split inline lists into sentences, and print one sentence per
-- line. groff/troff treats the line-ending period differently.
-- See http://code.google.com/p/pandoc/issues/detail?id=148.
@@ -373,21 +337,3 @@ inlineToMan _ (Note contents) = do
notes <- gets stNotes
let ref = show (length notes)
return $ char '[' <> text ref <> char ']'
-
-fontChange :: PandocMonad m => StateT WriterState m Doc
-fontChange = do
- features <- gets stFontFeatures
- let filling = sort [c | (c,True) <- Map.toList features]
- return $ text $ "\\f[" ++ (if null filling then "R" else filling) ++ "]"
-
-withFontFeature :: PandocMonad m
- => Char
- -> StateT WriterState m Doc
- -> StateT WriterState m Doc
-withFontFeature c action = do
- modify $ \st -> st{ stFontFeatures = Map.adjust not c $ stFontFeatures st }
- begin <- fontChange
- d <- action
- modify $ \st -> st{ stFontFeatures = Map.adjust not c $ stFontFeatures st }
- end <- fontChange
- return $ begin <> d <> end