aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs8
-rw-r--r--src/Text/Pandoc/Shared.hs10
-rw-r--r--src/Text/Pandoc/Writers/Man.hs2
3 files changed, 16 insertions, 4 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index ed0291051..0e144dd0d 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -234,7 +234,9 @@ blocks = mconcat <$> many block
getRawCommand :: String -> LP String
getRawCommand name' = do
- rawargs <- withRaw (skipopts *> option "" dimenarg *> many braced)
+ rawargs <- withRaw (many (try (optional sp *> opt)) *>
+ option "" (try (optional sp *> dimenarg)) *>
+ many braced)
return $ '\\' : name' ++ snd rawargs
lookupListDefault :: (Ord k) => v -> [k] -> M.Map k v -> v
@@ -816,10 +818,10 @@ tok :: LP Inlines
tok = try $ grouped inline <|> inlineCommand <|> str <$> count 1 inlineChar
opt :: LP Inlines
-opt = bracketed inline <* optional sp
+opt = bracketed inline
skipopts :: LP ()
-skipopts = skipMany opt
+skipopts = skipMany (opt *> optional sp)
inlineText :: LP Inlines
inlineText = str <$> many1 inlineChar
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 9bea0a65e..1fe3db5f7 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -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
--
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index f91367eb9..6b1e42394 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -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