Support numrange, numlist for siunitx.

See .
This commit is contained in:
John MacFarlane 2020-09-02 17:00:09 -07:00
parent 83f0acab47
commit a157e1a6e0
2 changed files with 27 additions and 9 deletions
src/Text/Pandoc/Readers

View file

@ -879,7 +879,9 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList
-- siuntix -- siuntix
, ("si", skipopts *> dosi tok) , ("si", skipopts *> dosi tok)
, ("SI", doSI tok) , ("SI", doSI tok)
, ("SIrange", doSIrange tok) , ("SIrange", doSIrange True tok)
, ("numrange", doSIrange False tok)
, ("numlist", doSInumlist)
, ("num", doSInum) , ("num", doSInum)
, ("ang", doSIang) , ("ang", doSIang)
-- hyphenat -- hyphenat

View file

@ -4,6 +4,7 @@ module Text.Pandoc.Readers.LaTeX.SIunitx
, doSI , doSI
, doSIrange , doSIrange
, doSInum , doSInum
, doSInumlist
, doSIang , doSIang
) )
where where
@ -18,6 +19,7 @@ import qualified Data.Map as M
import Data.Char (isDigit) import Data.Char (isDigit)
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import Data.List (intersperse)
dosi :: PandocMonad m => LP m Inlines -> LP m Inlines dosi :: PandocMonad m => LP m Inlines -> LP m Inlines
dosi tok = grouped (siUnit tok) <|> siUnit tok dosi tok = grouped (siUnit tok) <|> siUnit tok
@ -36,12 +38,24 @@ doSI tok = do
unit] unit]
doSInum :: PandocMonad m => LP m Inlines doSInum :: PandocMonad m => LP m Inlines
doSInum = do doSInum = skipopts *> (tonum . untokenize <$> braced)
skipopts
value <- untokenize <$> braced tonum :: Text -> Inlines
tonum value =
case runParser parseNum () "" value of case runParser parseNum () "" value of
Left _ -> return $ text value Left _ -> text value
Right num -> return num Right num -> num
doSInumlist :: PandocMonad m => LP m Inlines
doSInumlist = do
skipopts
xs <- map tonum . T.splitOn ";" . untokenize <$> braced
case xs of
[] -> return mempty
[x] -> return x
_ -> return $
mconcat (intersperse (str "," <> space) (init xs)) <>
text ", & " <> last xs
parseNum :: Parser Text () Inlines parseNum :: Parser Text () Inlines
parseNum = mconcat <$> many parseNumPart parseNum = mconcat <$> many parseNumPart
@ -78,14 +92,16 @@ doSIang = do
_ -> return mempty _ -> return mempty
-- converts e.g. \SIrange{100}{200}{\ms} to "100 ms--200 ms" -- converts e.g. \SIrange{100}{200}{\ms} to "100 ms--200 ms"
doSIrange :: PandocMonad m => LP m Inlines -> LP m Inlines doSIrange :: PandocMonad m => Bool -> LP m Inlines -> LP m Inlines
doSIrange tok = do doSIrange includeUnits tok = do
skipopts skipopts
startvalue <- doSInum startvalue <- doSInum
startvalueprefix <- option "" $ bracketed tok startvalueprefix <- option "" $ bracketed tok
stopvalue <- doSInum stopvalue <- doSInum
stopvalueprefix <- option "" $ bracketed tok stopvalueprefix <- option "" $ bracketed tok
unit <- dosi tok unit <- if includeUnits
then dosi tok
else return mempty
return . mconcat $ [startvalueprefix, return . mconcat $ [startvalueprefix,
emptyOr160 startvalueprefix, emptyOr160 startvalueprefix,
startvalue, startvalue,