From e3e66ba47f8fa5f06008db2aa998dcb8c80a6e3f Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Wed, 2 Sep 2020 15:44:36 -0700
Subject: LaTeX reader: support `\si` and improve other siunitx commands.

---
 src/Text/Pandoc/Readers/LaTeX.hs         |  1 +
 src/Text/Pandoc/Readers/LaTeX/SIunitx.hs | 30 ++++++++++++++++++++++--------
 2 files changed, 23 insertions(+), 8 deletions(-)

(limited to 'src')

diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 689b88a33..47c00c934 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -877,6 +877,7 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList
   , ("acfp", doAcronymPlural "full")
   , ("acsp", doAcronymPlural "abbrv")
   -- siuntix
+  , ("si", dosi tok)
   , ("SI", doSI tok)
   , ("SIrange", doSIrange tok)
   , ("num", doSInum)
diff --git a/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs b/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs
index 03375f224..f2b88f88b 100644
--- a/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs
@@ -1,6 +1,7 @@
 {-# LANGUAGE OverloadedStrings #-}
 module Text.Pandoc.Readers.LaTeX.SIunitx
-  ( doSI
+  ( dosi
+  , doSI
   , doSIrange
   , doSInum
   )
@@ -17,13 +18,16 @@ import Data.Char (isDigit)
 import Data.Text (Text)
 import qualified Data.Text as T
 
+dosi :: PandocMonad m => LP m Inlines -> LP m Inlines
+dosi tok = grouped (siUnit tok) <|> siUnit tok
+
 -- converts e.g. \SI{1}[\$]{} to "$ 1" or \SI{1}{\euro} to "1 €"
 doSI :: PandocMonad m => LP m Inlines -> LP m Inlines
 doSI tok = do
   skipopts
-  value <- tok
+  value <- doSInum
   valueprefix <- option "" $ bracketed tok
-  unit <- grouped (siUnit tok) <|> tok
+  unit <- dosi tok
   return . mconcat $ [valueprefix,
                       emptyOr160 valueprefix,
                       value,
@@ -65,11 +69,11 @@ parseNumPart =
 doSIrange :: PandocMonad m => LP m Inlines -> LP m Inlines
 doSIrange tok = do
   skipopts
-  startvalue <- tok
+  startvalue <- doSInum
   startvalueprefix <- option "" $ bracketed tok
-  stopvalue <- tok
+  stopvalue <- doSInum
   stopvalueprefix <- option "" $ bracketed tok
-  unit <- grouped (siUnit tok) <|> tok
+  unit <- dosi tok
   return . mconcat $ [startvalueprefix,
                       emptyOr160 startvalueprefix,
                       startvalue,
@@ -86,7 +90,7 @@ emptyOr160 :: Inlines -> Inlines
 emptyOr160 x = if x == mempty then x else str "\160"
 
 siUnit :: PandocMonad m => LP m Inlines -> LP m Inlines
-siUnit tok = do
+siUnit tok = try (do
   Tok _ (CtrlSeq name) _ <- anyControlSeq
   case name of
     "square" -> do
@@ -108,7 +112,17 @@ siUnit tok = do
                  , (il <> superscript "3") <$ controlSeq "cubed"
                  , (\n -> il <> superscript n) <$> (controlSeq "tothe" *> tok)
                  ]
-            Nothing -> tok
+            Nothing -> fail "not an siunit unit command")
+ <|> (lookAhead anyControlSeq >> tok)
+ <|> (do Tok _ Word t <- satisfyTok isWordTok
+         return $ str t)
+ <|> (symbol '^' *> (superscript <$> tok))
+ <|> (symbol '_' *> (subscript <$> tok))
+ <|> ("\xa0" <$ symbol '.')
+ <|> ("\xa0" <$ symbol '~')
+ <|> tok
+ <|> (do Tok _ _ t <- anyTok
+         return (str t))
 
 siUnitMap :: M.Map Text Inlines
 siUnitMap = M.fromList
-- 
cgit v1.2.3