Merge pull request #2426 from alexvong1995/better-man-writer
Better man writer (revised)
This commit is contained in:
commit
4aabcf3d4e
4 changed files with 12 additions and 10 deletions
|
@ -37,7 +37,7 @@ import Text.Pandoc.Walk (walk)
|
|||
import Text.Pandoc.Readers.LaTeX (handleIncludes)
|
||||
import Text.Pandoc.Shared ( tabFilter, readDataFileUTF8, readDataFile,
|
||||
safeRead, headerShift, normalize, err, warn,
|
||||
openURL )
|
||||
openURL, pandocVersion )
|
||||
import Text.Pandoc.MediaBag ( mediaDirectory, extractMediaBag, MediaBag )
|
||||
import Text.Pandoc.XML ( toEntities )
|
||||
import Text.Pandoc.SelfContained ( makeSelfContained )
|
||||
|
|
|
@ -117,8 +117,6 @@ module Text.Pandoc
|
|||
, writeCustom
|
||||
-- * Rendering templates and default templates
|
||||
, module Text.Pandoc.Templates
|
||||
-- * Version
|
||||
, pandocVersion
|
||||
-- * Miscellaneous
|
||||
, getReader
|
||||
, getWriter
|
||||
|
@ -178,17 +176,11 @@ import Text.Pandoc.Error
|
|||
import Data.Aeson
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import Data.List (intercalate)
|
||||
import Data.Version (showVersion)
|
||||
import Data.Set (Set)
|
||||
import qualified Data.Set as Set
|
||||
import Text.Parsec
|
||||
import Text.Parsec.Error
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
import Paths_pandoc (version)
|
||||
|
||||
-- | Version number of pandoc library.
|
||||
pandocVersion :: String
|
||||
pandocVersion = showVersion version
|
||||
|
||||
parseFormatSpec :: String
|
||||
-> Either ParseError (String, Set Extension -> Set Extension)
|
||||
|
|
|
@ -92,7 +92,9 @@ module Text.Pandoc.Shared (
|
|||
-- * Safe read
|
||||
safeRead,
|
||||
-- * Temp directory
|
||||
withTempDir
|
||||
withTempDir,
|
||||
-- * Version
|
||||
pandocVersion
|
||||
) where
|
||||
|
||||
import Text.Pandoc.Definition
|
||||
|
@ -106,6 +108,7 @@ import System.Exit (exitWith, ExitCode(..))
|
|||
import Data.Char ( toLower, isLower, isUpper, isAlpha,
|
||||
isLetter, isDigit, isSpace )
|
||||
import Data.List ( find, stripPrefix, intercalate )
|
||||
import Data.Version ( showVersion )
|
||||
import qualified Data.Map as M
|
||||
import Network.URI ( escapeURIString, isURI, nonStrictRelativeTo,
|
||||
unEscapeString, parseURIReference, isAllowedInURI )
|
||||
|
@ -136,6 +139,7 @@ import Data.Sequence (ViewR(..), ViewL(..), viewl, viewr)
|
|||
import qualified Data.Text as T (toUpper, pack, unpack)
|
||||
import Data.ByteString.Lazy (toChunks, fromChunks)
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import Paths_pandoc (version)
|
||||
|
||||
import Codec.Archive.Zip
|
||||
|
||||
|
@ -165,6 +169,10 @@ import Network.HTTP (findHeader, rspBody,
|
|||
import Network.Browser (browse, setAllowRedirects, setOutHandler, request)
|
||||
#endif
|
||||
|
||||
-- | Version number of pandoc library.
|
||||
pandocVersion :: String
|
||||
pandocVersion = showVersion version
|
||||
|
||||
--
|
||||
-- List processing
|
||||
--
|
||||
|
|
|
@ -85,6 +85,8 @@ pandocToMan opts (Pandoc meta blocks) = do
|
|||
let context = defField "body" main
|
||||
$ setFieldsFromTitle
|
||||
$ defField "has-tables" hasTables
|
||||
$ defField "hyphenate" True
|
||||
$ defField "pandoc-version" pandocVersion
|
||||
$ metadata
|
||||
if writerStandalone opts
|
||||
then return $ renderTemplate' (writerTemplate opts) context
|
||||
|
|
Loading…
Reference in a new issue