{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.LaTeX.SIunitx
  ( siunitxCommands )
where
import Text.Pandoc.Builder
import Text.Pandoc.Readers.LaTeX.Parsing
import Text.Pandoc.Readers.LaTeX.Types
import Text.Pandoc.Class
import Text.Pandoc.Parsing hiding (blankline, mathDisplay, mathInline,
                            optional, space, spaces, withRaw, (<|>))
import Control.Applicative ((<|>))
import Control.Monad (void)
import qualified Data.Map as M
import Data.Char (isDigit)
import Data.Text (Text)
import qualified Data.Text as T
import Data.List (intersperse)
import qualified Data.Sequence as Seq
import Text.Pandoc.Walk (walk)

siunitxCommands :: PandocMonad m
                 => LP m Inlines -> M.Map Text (LP m Inlines)
siunitxCommands :: LP m Inlines -> Map Text (LP m Inlines)
siunitxCommands LP m Inlines
tok = [(Text, LP m Inlines)] -> Map Text (LP m Inlines)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
  [ (Text
"si", LP m Inlines -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines -> LP m Inlines
dosi LP m Inlines
tok)
  , (Text
"SI", LP m Inlines -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines -> LP m Inlines
doSI LP m Inlines
tok)
  , (Text
"SIrange", Bool -> LP m Inlines -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
Bool -> LP m Inlines -> LP m Inlines
doSIrange Bool
True LP m Inlines
tok)
  , (Text
"numrange", Bool -> LP m Inlines -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
Bool -> LP m Inlines -> LP m Inlines
doSIrange Bool
False LP m Inlines
tok)
  , (Text
"numlist", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doSInumlist)
  , (Text
"SIlist", LP m Inlines -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines -> LP m Inlines
doSIlist LP m Inlines
tok)
  , (Text
"num", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doSInum)
  , (Text
"ang", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doSIang)
  ]

dosi :: PandocMonad m => LP m Inlines -> LP m Inlines
dosi :: LP m Inlines -> LP m Inlines
dosi LP m Inlines
tok = do
  [(Text, Text)]
options <- [(Text, Text)]
-> ParsecT [Tok] LaTeXState m [(Text, Text)]
-> ParsecT [Tok] LaTeXState m [(Text, Text)]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [] ParsecT [Tok] LaTeXState m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => LP m [(Text, Text)]
keyvals
  LP m Inlines -> LP m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped ([(Text, Text)] -> LP m Inlines -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
[(Text, Text)] -> LP m Inlines -> LP m Inlines
siUnit [(Text, Text)]
options LP m Inlines
tok) LP m Inlines -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [(Text, Text)] -> LP m Inlines -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
[(Text, Text)] -> LP m Inlines -> LP m Inlines
siUnit [(Text, Text)]
options LP m Inlines
tok

-- converts e.g. \SI{1}[\$]{} to "$ 1" or \SI{1}{\euro} to "1 €"
doSI :: PandocMonad m => LP m Inlines -> LP m Inlines
doSI :: LP m Inlines -> LP m Inlines
doSI LP m Inlines
tok = do
  LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
  Inlines
value <- LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doSInum
  Inlines
valueprefix <- Inlines -> LP m Inlines -> LP m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
"" (LP m Inlines -> LP m Inlines) -> LP m Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ LP m Inlines -> LP m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
bracketed LP m Inlines
tok
  Inlines
unit <- LP m Inlines -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines -> LP m Inlines
dosi LP m Inlines
tok
  Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> LP m Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> LP m Inlines) -> [Inlines] -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ [Inlines
valueprefix,
                      Inlines -> Inlines
emptyOr160 Inlines
valueprefix,
                      Inlines
value,
                      Inlines -> Inlines
emptyOr160 Inlines
unit,
                      Inlines
unit]

doSInum :: PandocMonad m => LP m Inlines
doSInum :: LP m Inlines
doSInum = LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts LP m () -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Text -> Inlines
tonum (Text -> Inlines) -> ([Tok] -> Text) -> [Tok] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> Inlines)
-> ParsecT [Tok] LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced)

tonum :: Text -> Inlines
tonum :: Text -> Inlines
tonum Text
value =
  case Parsec Text () Inlines
-> () -> SourceName -> Text -> Either ParseError Inlines
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> SourceName -> s -> Either ParseError a
runParser Parsec Text () Inlines
parseNum () SourceName
"" Text
value of
    Left ParseError
_    -> Text -> Inlines
text Text
value
    Right Inlines
num -> Inlines
num

doSInumlist :: PandocMonad m => LP m Inlines
doSInumlist :: LP m Inlines
doSInumlist = do
  LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
  [Inlines]
xs <- (Text -> Inlines) -> [Text] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Inlines
tonum ([Text] -> [Inlines]) -> ([Tok] -> [Text]) -> [Tok] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
T.splitOn Text
";" (Text -> [Text]) -> ([Tok] -> Text) -> [Tok] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> [Inlines])
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Inlines]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  case [Inlines]
xs of
    []  -> Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
    [Inlines
x] -> Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
x
    [Inlines]
_   -> Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines) -> Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$
             [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat (Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Text -> Inlines
str Text
"," Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
space) ([Inlines] -> [Inlines]
forall a. [a] -> [a]
init [Inlines]
xs)) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>
             Text -> Inlines
text Text
", & " Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> [Inlines] -> Inlines
forall a. [a] -> a
last [Inlines]
xs

doSIlist :: PandocMonad m => LP m Inlines -> LP m Inlines
doSIlist :: LP m Inlines -> LP m Inlines
doSIlist LP m Inlines
tok = do
  [(Text, Text)]
options <- [(Text, Text)]
-> ParsecT [Tok] LaTeXState m [(Text, Text)]
-> ParsecT [Tok] LaTeXState m [(Text, Text)]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [] ParsecT [Tok] LaTeXState m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => LP m [(Text, Text)]
keyvals
  [Inlines]
nums <- (Text -> Inlines) -> [Text] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Inlines
tonum ([Text] -> [Inlines]) -> ([Tok] -> [Text]) -> [Tok] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
T.splitOn Text
";" (Text -> [Text]) -> ([Tok] -> Text) -> [Tok] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> [Inlines])
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Inlines]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  Inlines
unit <- LP m Inlines -> LP m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped ([(Text, Text)] -> LP m Inlines -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
[(Text, Text)] -> LP m Inlines -> LP m Inlines
siUnit [(Text, Text)]
options LP m Inlines
tok) LP m Inlines -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [(Text, Text)] -> LP m Inlines -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
[(Text, Text)] -> LP m Inlines -> LP m Inlines
siUnit [(Text, Text)]
options LP m Inlines
tok
  let xs :: [Inlines]
xs = (Inlines -> Inlines) -> [Inlines] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map (Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> (Text -> Inlines
str Text
"\xa0" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
unit)) [Inlines]
nums
  case [Inlines]
xs of
    []  -> Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
    [Inlines
x] -> Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
x
    [Inlines]
_   -> Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines) -> Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$
             [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat (Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Text -> Inlines
str Text
"," Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
space) ([Inlines] -> [Inlines]
forall a. [a] -> [a]
init [Inlines]
xs)) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>
             Text -> Inlines
text Text
", & " Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> [Inlines] -> Inlines
forall a. [a] -> a
last [Inlines]
xs

parseNum :: Parser Text () Inlines
parseNum :: Parsec Text () Inlines
parseNum = ([Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT Text () Identity [Inlines] -> Parsec Text () Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parsec Text () Inlines -> ParsecT Text () Identity [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many Parsec Text () Inlines
parseNumPart) Parsec Text () Inlines
-> ParsecT Text () Identity () -> Parsec Text () Inlines
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof

minus :: Text
minus :: Text
minus = Text
"\x2212"

hyphenToMinus :: Inline -> Inline
hyphenToMinus :: Inline -> Inline
hyphenToMinus (Str Text
t) = Text -> Inline
Str (Text -> Text -> Text -> Text
T.replace Text
"-" Text
minus Text
t)
hyphenToMinus Inline
x = Inline
x

parseNumPart :: Parser Text () Inlines
parseNumPart :: Parsec Text () Inlines
parseNumPart =
  Parsec Text () Inlines
parseDecimalNum Parsec Text () Inlines
-> Parsec Text () Inlines -> Parsec Text () Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
  Parsec Text () Inlines
parseComma Parsec Text () Inlines
-> Parsec Text () Inlines -> Parsec Text () Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
  Parsec Text () Inlines
parsePlusMinus Parsec Text () Inlines
-> Parsec Text () Inlines -> Parsec Text () Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
  Parsec Text () Inlines
parsePM Parsec Text () Inlines
-> Parsec Text () Inlines -> Parsec Text () Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
  Parsec Text () Inlines
parseI Parsec Text () Inlines
-> Parsec Text () Inlines -> Parsec Text () Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
  Parsec Text () Inlines
parseExp Parsec Text () Inlines
-> Parsec Text () Inlines -> Parsec Text () Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
  Parsec Text () Inlines
parseX Parsec Text () Inlines
-> Parsec Text () Inlines -> Parsec Text () Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
  Parsec Text () Inlines
parseSpace
 where
  parseDecimalNum, parsePlusMinus, parsePM,
    parseComma, parseI, parseX,
    parseExp, parseSpace :: Parser Text () Inlines
  parseDecimalNum :: Parsec Text () Inlines
parseDecimalNum = Parsec Text () Inlines -> Parsec Text () Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parsec Text () Inlines -> Parsec Text () Inlines)
-> Parsec Text () Inlines -> Parsec Text () Inlines
forall a b. (a -> b) -> a -> b
$ do
    Text
pref <- Text
-> ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
forall a. Monoid a => a
mempty (ParsecT Text () Identity Text -> ParsecT Text () Identity Text)
-> ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall a b. (a -> b) -> a -> b
$ (Text
forall a. Monoid a => a
mempty Text
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'+') ParsecT Text () Identity Text
-> ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Text
minus Text
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-')
    SourceName
basenum' <- ParsecT Text () Identity Char
-> ParsecT Text () Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ((Char -> Bool) -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (\Char
c -> Char -> Bool
isDigit Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.'))
    let basenum :: Text
basenum = Text
pref Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName -> Text
T.pack
                    (case SourceName
basenum' of
                      Char
'.':SourceName
_ -> Char
'0'Char -> SourceName -> SourceName
forall a. a -> [a] -> [a]
:SourceName
basenum'
                      SourceName
_ -> SourceName
basenum')
    Text
uncertainty <- Text
-> ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
forall a. Monoid a => a
mempty (ParsecT Text () Identity Text -> ParsecT Text () Identity Text)
-> ParsecT Text () Identity Text -> ParsecT Text () Identity Text
forall a b. (a -> b) -> a -> b
$ SourceName -> Text
T.pack (SourceName -> Text)
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity SourceName
forall u. ParsecT Text u Identity SourceName
parseParens
    if Text -> Bool
T.null Text
uncertainty
       then Inlines -> Parsec Text () Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Parsec Text () Inlines)
-> Inlines -> Parsec Text () Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
str Text
basenum
       else Inlines -> Parsec Text () Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Parsec Text () Inlines)
-> Inlines -> Parsec Text () Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
basenum Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\xa0\xb1\xa0" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
             let (Text
_,Text
ys) = (Char -> Bool) -> Text -> (Text, Text)
T.break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'.') Text
basenum
              in case (Text -> Int
T.length Text
ys Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1, Text -> Int
T.length Text
uncertainty) of
                   (Int
0,Int
_) -> Text
uncertainty
                   (Int
x,Int
y)
                     | Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
y  -> Text
"0." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.replicate (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
y) Text
"0" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
                                      (Char -> Bool) -> Text -> Text
T.dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'0') Text
uncertainty
                     | Bool
otherwise -> Int -> Text -> Text
T.take (Int
y Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
x) Text
uncertainty Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
                                      case (Char -> Bool) -> Text -> Text
T.dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'0')
                                             (Int -> Text -> Text
T.drop (Int
y Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
x) Text
uncertainty) of
                                             Text
t | Text -> Bool
T.null Text
t -> Text
forall a. Monoid a => a
mempty
                                               | Bool
otherwise -> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
  parseComma :: Parsec Text () Inlines
parseComma = Text -> Inlines
str Text
"." Inlines -> ParsecT Text () Identity Char -> Parsec Text () Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
','
  parsePlusMinus :: Parsec Text () Inlines
parsePlusMinus = Text -> Inlines
str Text
"\xa0\xb1\xa0" Inlines
-> ParsecT Text () Identity SourceName -> Parsec Text () Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (SourceName -> ParsecT Text () Identity SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"+-")
  parsePM :: Parsec Text () Inlines
parsePM = Text -> Inlines
str Text
"\xa0\xb1\xa0" Inlines
-> ParsecT Text () Identity SourceName -> Parsec Text () Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (SourceName -> ParsecT Text () Identity SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\pm")
  parseParens :: ParsecT Text u Identity SourceName
parseParens =
    Char -> ParsecT Text u Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'(' ParsecT Text u Identity Char
-> ParsecT Text u Identity SourceName
-> ParsecT Text u Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text u Identity Char -> ParsecT Text u Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ((Char -> Bool) -> ParsecT Text u Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (\Char
c -> Char -> Bool
isDigit Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.')) ParsecT Text u Identity SourceName
-> ParsecT Text u Identity Char
-> ParsecT Text u Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Text u Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
')'
  parseI :: Parsec Text () Inlines
parseI = Text -> Inlines
str Text
"i" Inlines -> ParsecT Text () Identity Char -> Parsec Text () Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'i'
  parseX :: Parsec Text () Inlines
parseX = Text -> Inlines
str Text
"\xa0\xd7\xa0" Inlines -> ParsecT Text () Identity Char -> Parsec Text () Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'x'
  parseExp :: Parsec Text () Inlines
parseExp = (\Inlines
n -> Text -> Inlines
str (Text
"\xa0\xd7\xa0" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"10") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
superscript Inlines
n)
               (Inlines -> Inlines)
-> Parsec Text () Inlines -> Parsec Text () Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'e' ParsecT Text () Identity Char
-> Parsec Text () Inlines -> Parsec Text () Inlines
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec Text () Inlines
parseDecimalNum)
  parseSpace :: Parsec Text () Inlines
parseSpace = Inlines
forall a. Monoid a => a
mempty Inlines -> ParsecT Text () Identity () -> Parsec Text () Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 (Char -> ParsecT Text () Identity Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' ')

doSIang :: PandocMonad m => LP m Inlines
doSIang :: LP m Inlines
doSIang = do
  LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
  [Text]
ps <- Text -> Text -> [Text]
T.splitOn Text
";" (Text -> [Text]) -> ([Tok] -> Text) -> [Tok] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> [Text])
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  let dropPlus :: Text -> Text
dropPlus Text
t = case Text -> Maybe (Char, Text)
T.uncons Text
t of
                     Just (Char
'+',Text
t') -> Text
t'
                     Maybe (Char, Text)
_ -> Text
t
  case [Text]
ps [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ Text -> [Text]
forall a. a -> [a]
repeat Text
"" of
    (Text
d:Text
m:Text
s:[Text]
_) -> Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines) -> Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$
      (if Text -> Bool
T.null Text
d then Inlines
forall a. Monoid a => a
mempty else Text -> Inlines
str (Text -> Text
dropPlus Text
d) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
"\xb0") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>
      (if Text -> Bool
T.null Text
m then Inlines
forall a. Monoid a => a
mempty else Text -> Inlines
str (Text -> Text
dropPlus Text
m) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
"\x2032") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>
      (if Text -> Bool
T.null Text
s then Inlines
forall a. Monoid a => a
mempty else Text -> Inlines
str (Text -> Text
dropPlus Text
s) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
"\x2033")
    [Text]
_ -> Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty

-- converts e.g. \SIrange{100}{200}{\ms} to "100 ms--200 ms"
doSIrange :: PandocMonad m => Bool -> LP m Inlines -> LP m Inlines
doSIrange :: Bool -> LP m Inlines -> LP m Inlines
doSIrange Bool
includeUnits LP m Inlines
tok = do
  LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
  Inlines
startvalue <- LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doSInum
  Inlines
startvalueprefix <- Inlines -> LP m Inlines -> LP m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
"" (LP m Inlines -> LP m Inlines) -> LP m Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ LP m Inlines -> LP m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
bracketed LP m Inlines
tok
  Inlines
stopvalue <- LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doSInum
  Inlines
stopvalueprefix <- Inlines -> LP m Inlines -> LP m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
"" (LP m Inlines -> LP m Inlines) -> LP m Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ LP m Inlines -> LP m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
bracketed LP m Inlines
tok
  Inlines
unit <- if Bool
includeUnits
             then LP m Inlines -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines -> LP m Inlines
dosi LP m Inlines
tok
             else Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
  Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> LP m Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> LP m Inlines) -> [Inlines] -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ [Inlines
startvalueprefix,
                      Inlines -> Inlines
emptyOr160 Inlines
startvalueprefix,
                      Inlines
startvalue,
                      Inlines -> Inlines
emptyOr160 Inlines
unit,
                      Inlines
unit,
                      Inlines
"\8211", -- An en-dash
                      Inlines
stopvalueprefix,
                      Inlines -> Inlines
emptyOr160 Inlines
stopvalueprefix,
                      Inlines
stopvalue,
                      Inlines -> Inlines
emptyOr160 Inlines
unit,
                      Inlines
unit]

emptyOr160 :: Inlines -> Inlines
emptyOr160 :: Inlines -> Inlines
emptyOr160 Inlines
x = if Inlines
x Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
forall a. Monoid a => a
mempty then Inlines
x else Text -> Inlines
str Text
"\160"

siUnit :: forall m. PandocMonad m => [(Text,Text)] -> LP m Inlines -> LP m Inlines
siUnit :: [(Text, Text)] -> LP m Inlines -> LP m Inlines
siUnit [(Text, Text)]
options LP m Inlines
tok = [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ([Inlines] -> [Inlines]) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Text -> Inlines
str Text
"\xa0") ([Inlines] -> Inlines)
-> ParsecT [Tok] LaTeXState m [Inlines] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines -> ParsecT [Tok] LaTeXState m [Inlines]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 LP m Inlines
siUnitPart
 where
  siUnitPart :: LP m Inlines
  siUnitPart :: LP m Inlines
siUnitPart = LP m Inlines -> LP m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m Inlines -> LP m Inlines) -> LP m Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ do
    ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'.') ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'~') ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces1)
    Inlines
x <- ((LP m (Inlines -> Inlines)
siPrefix LP m (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> LP m Inlines
siBase)
            LP m Inlines -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (do Inlines
u <- LP m Inlines
siBase LP m Inlines -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
tok
                    Inlines -> LP m Inlines -> LP m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
u (LP m Inlines -> LP m Inlines) -> LP m Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ LP m (Inlines -> Inlines)
siSuffix LP m (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Inlines -> LP m Inlines
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inlines
u))
    Inlines -> LP m Inlines -> LP m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
x (Inlines -> LP m Inlines
siInfix Inlines
x)
  siInfix :: Inlines -> LP m Inlines
  siInfix :: Inlines -> LP m Inlines
siInfix Inlines
u1 = LP m Inlines -> LP m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m Inlines -> LP m Inlines) -> LP m Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$
       (do Tok
_ <- Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"per"
           Inlines
u2 <- LP m Inlines
siUnitPart
           let useSlash :: Bool
useSlash = Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"per-mode" [(Text, Text)]
options Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"symbol"
           if Bool
useSlash
              then Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
u1 Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
"/" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
u2)
              else Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
u1 Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
"\xa0" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
negateExponent Inlines
u2))
   LP m Inlines -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (do Tok
_ <- Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'/'
           Inlines
u2 <- LP m Inlines
siUnitPart
           Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
u1 Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
"/" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
u2))
  siPrefix :: LP m (Inlines -> Inlines)
  siPrefix :: LP m (Inlines -> Inlines)
siPrefix =
       (do Tok
_ <- Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"square"
           ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
           (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
superscript Inlines
"2"))
   LP m (Inlines -> Inlines)
-> LP m (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (do Tok
_ <- Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"cubic"
           ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
           (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
superscript Inlines
"3"))
   LP m (Inlines -> Inlines)
-> LP m (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (do Tok
_ <- Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"raisetothe"
           ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
           Inlines
n <- (Inline -> Inline) -> Inlines -> Inlines
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
hyphenToMinus (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
tok
           (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
superscript Inlines
n))
  siSuffix :: LP m (Inlines -> Inlines)
  siSuffix :: LP m (Inlines -> Inlines)
siSuffix =
       (do Tok
_ <- Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"squared"
           ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
           (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
superscript Inlines
"2"))
   LP m (Inlines -> Inlines)
-> LP m (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (do Tok
_ <- Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"cubed"
           ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
           (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
superscript Inlines
"3"))
   LP m (Inlines -> Inlines)
-> LP m (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (do Tok
_ <- Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"tothe"
           ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
           Inlines
n <- (Inline -> Inline) -> Inlines -> Inlines
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
hyphenToMinus (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
tok
           (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
superscript Inlines
n))
   LP m (Inlines -> Inlines)
-> LP m (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'^' ParsecT [Tok] LaTeXState m Tok
-> LP m (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (do Inlines
n <- (Inline -> Inline) -> Inlines -> Inlines
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
hyphenToMinus (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
tok
                          (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
superscript Inlines
n)))
   LP m (Inlines -> Inlines)
-> LP m (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'_' ParsecT [Tok] LaTeXState m Tok
-> LP m (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (do Inlines
n <- (Inline -> Inline) -> Inlines -> Inlines
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
hyphenToMinus (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
tok
                          (Inlines -> Inlines) -> LP m (Inlines -> Inlines)
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
subscript Inlines
n)))
  negateExponent :: Inlines -> Inlines
  negateExponent :: Inlines -> Inlines
negateExponent Inlines
ils =
    case Seq Inline -> ViewR Inline
forall a. Seq a -> ViewR a
Seq.viewr (Inlines -> Seq Inline
forall a. Many a -> Seq a
unMany Inlines
ils) of
      Seq Inline
xs Seq.:> Superscript [Inline]
ss -> (Seq Inline -> Inlines
forall a. Seq a -> Many a
Many Seq Inline
xs) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>
                                     Inlines -> Inlines
superscript (Text -> Inlines
str Text
minus Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> [Inline] -> Inlines
forall a. [a] -> Many a
fromList [Inline]
ss)
      ViewR Inline
_ -> Inlines
ils Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
superscript (Text -> Inlines
str (Text
minus Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"1"))
  siBase :: LP m Inlines
  siBase :: LP m Inlines
siBase =
    ((LP m Inlines -> LP m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try
       (do Tok SourcePos
_ (CtrlSeq Text
name) Text
_ <- ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyControlSeq
           case Text -> Map Text Inlines -> Maybe Inlines
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
name Map Text Inlines
siUnitModifierMap of
              Just Inlines
il -> (Inlines
il Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>) (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
siBase
              Maybe Inlines
Nothing ->
                case Text -> Map Text Inlines -> Maybe Inlines
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
name Map Text Inlines
siUnitMap of
                   Just Inlines
il -> Inlines -> LP m Inlines
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inlines
il
                   Maybe Inlines
Nothing -> SourceName -> LP m Inlines
forall (m :: * -> *) a. MonadFail m => SourceName -> m a
fail SourceName
"not a unit command"))
    LP m Inlines -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (do Tok SourcePos
_ TokType
Word Text
t <- (Tok -> Bool) -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => (Tok -> Bool) -> LP m Tok
satisfyTok Tok -> Bool
isWordTok
            Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines) -> Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
str Text
t)
     )

siUnitModifierMap :: M.Map Text Inlines
siUnitModifierMap :: Map Text Inlines
siUnitModifierMap = [(Text, Inlines)] -> Map Text Inlines
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
  [ (Text
"atto", Text -> Inlines
str Text
"a")
  , (Text
"centi", Text -> Inlines
str Text
"c")
  , (Text
"deca", Text -> Inlines
str Text
"d")
  , (Text
"deci", Text -> Inlines
str Text
"d")
  , (Text
"deka", Text -> Inlines
str Text
"d")
  , (Text
"exa", Text -> Inlines
str Text
"E")
  , (Text
"femto", Text -> Inlines
str Text
"f")
  , (Text
"giga", Text -> Inlines
str Text
"G")
  , (Text
"hecto", Text -> Inlines
str Text
"h")
  , (Text
"kilo", Text -> Inlines
str Text
"k")
  , (Text
"mega", Text -> Inlines
str Text
"M")
  , (Text
"micro", Text -> Inlines
str Text
"μ")
  , (Text
"milli", Text -> Inlines
str Text
"m")
  , (Text
"nano", Text -> Inlines
str Text
"n")
  , (Text
"peta", Text -> Inlines
str Text
"P")
  , (Text
"pico", Text -> Inlines
str Text
"p")
  , (Text
"tera", Text -> Inlines
str Text
"T")
  , (Text
"yocto", Text -> Inlines
str Text
"y")
  , (Text
"yotta", Text -> Inlines
str Text
"Y")
  , (Text
"zepto", Text -> Inlines
str Text
"z")
  , (Text
"zetta", Text -> Inlines
str Text
"Z")
  ]

siUnitMap :: M.Map Text Inlines
siUnitMap :: Map Text Inlines
siUnitMap = [(Text, Inlines)] -> Map Text Inlines
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
  [ (Text
"fg", Text -> Inlines
str Text
"fg")
  , (Text
"pg", Text -> Inlines
str Text
"pg")
  , (Text
"ng", Text -> Inlines
str Text
"ng")
  , (Text
"ug", Text -> Inlines
str Text
"μg")
  , (Text
"mg", Text -> Inlines
str Text
"mg")
  , (Text
"g", Text -> Inlines
str Text
"g")
  , (Text
"kg", Text -> Inlines
str Text
"kg")
  , (Text
"amu", Text -> Inlines
str Text
"u")
  , (Text
"pm", Text -> Inlines
str Text
"pm")
  , (Text
"nm", Text -> Inlines
str Text
"nm")
  , (Text
"um", Text -> Inlines
str Text
"μm")
  , (Text
"mm", Text -> Inlines
str Text
"mm")
  , (Text
"cm", Text -> Inlines
str Text
"cm")
  , (Text
"dm", Text -> Inlines
str Text
"dm")
  , (Text
"m", Text -> Inlines
str Text
"m")
  , (Text
"km", Text -> Inlines
str Text
"km")
  , (Text
"as", Text -> Inlines
str Text
"as")
  , (Text
"fs", Text -> Inlines
str Text
"fs")
  , (Text
"ps", Text -> Inlines
str Text
"ps")
  , (Text
"ns", Text -> Inlines
str Text
"ns")
  , (Text
"us", Text -> Inlines
str Text
"μs")
  , (Text
"ms", Text -> Inlines
str Text
"ms")
  , (Text
"s", Text -> Inlines
str Text
"s")
  , (Text
"fmol", Text -> Inlines
str Text
"fmol")
  , (Text
"pmol", Text -> Inlines
str Text
"pmol")
  , (Text
"nmol", Text -> Inlines
str Text
"nmol")
  , (Text
"umol", Text -> Inlines
str Text
"μmol")
  , (Text
"mmol", Text -> Inlines
str Text
"mmol")
  , (Text
"mol", Text -> Inlines
str Text
"mol")
  , (Text
"kmol", Text -> Inlines
str Text
"kmol")
  , (Text
"pA", Text -> Inlines
str Text
"pA")
  , (Text
"nA", Text -> Inlines
str Text
"nA")
  , (Text
"uA", Text -> Inlines
str Text
"μA")
  , (Text
"mA", Text -> Inlines
str Text
"mA")
  , (Text
"A", Text -> Inlines
str Text
"A")
  , (Text
"kA", Text -> Inlines
str Text
"kA")
  , (Text
"ul", Text -> Inlines
str Text
"μl")
  , (Text
"ml", Text -> Inlines
str Text
"ml")
  , (Text
"l", Text -> Inlines
str Text
"l")
  , (Text
"hl", Text -> Inlines
str Text
"hl")
  , (Text
"uL", Text -> Inlines
str Text
"μL")
  , (Text
"mL", Text -> Inlines
str Text
"mL")
  , (Text
"L", Text -> Inlines
str Text
"L")
  , (Text
"hL", Text -> Inlines
str Text
"hL")
  , (Text
"mHz", Text -> Inlines
str Text
"mHz")
  , (Text
"Hz", Text -> Inlines
str Text
"Hz")
  , (Text
"kHz", Text -> Inlines
str Text
"kHz")
  , (Text
"MHz", Text -> Inlines
str Text
"MHz")
  , (Text
"GHz", Text -> Inlines
str Text
"GHz")
  , (Text
"THz", Text -> Inlines
str Text
"THz")
  , (Text
"mN", Text -> Inlines
str Text
"mN")
  , (Text
"N", Text -> Inlines
str Text
"N")
  , (Text
"kN", Text -> Inlines
str Text
"kN")
  , (Text
"MN", Text -> Inlines
str Text
"MN")
  , (Text
"Pa", Text -> Inlines
str Text
"Pa")
  , (Text
"kPa", Text -> Inlines
str Text
"kPa")
  , (Text
"MPa", Text -> Inlines
str Text
"MPa")
  , (Text
"GPa", Text -> Inlines
str Text
"GPa")
  , (Text
"mohm", Text -> Inlines
str Text
"mΩ")
  , (Text
"kohm", Text -> Inlines
str Text
"kΩ")
  , (Text
"Mohm", Text -> Inlines
str Text
"MΩ")
  , (Text
"pV", Text -> Inlines
str Text
"pV")
  , (Text
"nV", Text -> Inlines
str Text
"nV")
  , (Text
"uV", Text -> Inlines
str Text
"μV")
  , (Text
"mV", Text -> Inlines
str Text
"mV")
  , (Text
"V", Text -> Inlines
str Text
"V")
  , (Text
"kV", Text -> Inlines
str Text
"kV")
  , (Text
"W", Text -> Inlines
str Text
"W")
  , (Text
"uW", Text -> Inlines
str Text
"μW")
  , (Text
"mW", Text -> Inlines
str Text
"mW")
  , (Text
"kW", Text -> Inlines
str Text
"kW")
  , (Text
"MW", Text -> Inlines
str Text
"MW")
  , (Text
"GW", Text -> Inlines
str Text
"GW")
  , (Text
"J", Text -> Inlines
str Text
"J")
  , (Text
"uJ", Text -> Inlines
str Text
"μJ")
  , (Text
"mJ", Text -> Inlines
str Text
"mJ")
  , (Text
"kJ", Text -> Inlines
str Text
"kJ")
  , (Text
"eV", Text -> Inlines
str Text
"eV")
  , (Text
"meV", Text -> Inlines
str Text
"meV")
  , (Text
"keV", Text -> Inlines
str Text
"keV")
  , (Text
"MeV", Text -> Inlines
str Text
"MeV")
  , (Text
"GeV", Text -> Inlines
str Text
"GeV")
  , (Text
"TeV", Text -> Inlines
str Text
"TeV")
  , (Text
"kWh", Text -> Inlines
str Text
"kWh")
  , (Text
"F", Text -> Inlines
str Text
"F")
  , (Text
"fF", Text -> Inlines
str Text
"fF")
  , (Text
"pF", Text -> Inlines
str Text
"pF")
  , (Text
"K", Text -> Inlines
str Text
"K")
  , (Text
"dB", Text -> Inlines
str Text
"dB")
  , (Text
"ampere", Text -> Inlines
str Text
"A")
  , (Text
"angstrom", Text -> Inlines
str Text
"Å")
  , (Text
"arcmin", Text -> Inlines
str Text
"′")
  , (Text
"arcminute", Text -> Inlines
str Text
"′")
  , (Text
"arcsecond", Text -> Inlines
str Text
"″")
  , (Text
"astronomicalunit", Text -> Inlines
str Text
"ua")
  , (Text
"atomicmassunit", Text -> Inlines
str Text
"u")
  , (Text
"bar", Text -> Inlines
str Text
"bar")
  , (Text
"barn", Text -> Inlines
str Text
"b")
  , (Text
"becquerel", Text -> Inlines
str Text
"Bq")
  , (Text
"bel", Text -> Inlines
str Text
"B")
  , (Text
"bohr", Inlines -> Inlines
emph (Text -> Inlines
str Text
"a") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
subscript (Text -> Inlines
str Text
"0"))
  , (Text
"candela", Text -> Inlines
str Text
"cd")
  , (Text
"celsius", Text -> Inlines
str Text
"°C")
  , (Text
"clight", Inlines -> Inlines
emph (Text -> Inlines
str Text
"c") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
subscript (Text -> Inlines
str Text
"0"))
  , (Text
"coulomb", Text -> Inlines
str Text
"C")
  , (Text
"dalton", Text -> Inlines
str Text
"Da")
  , (Text
"day", Text -> Inlines
str Text
"d")
  , (Text
"decibel", Text -> Inlines
str Text
"db")
  , (Text
"degreeCelsius",Text -> Inlines
str Text
"°C")
  , (Text
"degree", Text -> Inlines
str Text
"°")
  , (Text
"electronmass", Inlines -> Inlines
emph (Text -> Inlines
str Text
"m") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
subscript (Text -> Inlines
str Text
"e"))
  , (Text
"electronvolt", Text -> Inlines
str Text
"eV")
  , (Text
"elementarycharge", Inlines -> Inlines
emph (Text -> Inlines
str Text
"e"))
  , (Text
"farad", Text -> Inlines
str Text
"F")
  , (Text
"gram", Text -> Inlines
str Text
"g")
  , (Text
"gray", Text -> Inlines
str Text
"Gy")
  , (Text
"hartree", Inlines -> Inlines
emph (Text -> Inlines
str Text
"E") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
subscript (Text -> Inlines
str Text
"h"))
  , (Text
"hectare", Text -> Inlines
str Text
"ha")
  , (Text
"henry", Text -> Inlines
str Text
"H")
  , (Text
"hertz", Text -> Inlines
str Text
"Hz")
  , (Text
"hour", Text -> Inlines
str Text
"h")
  , (Text
"joule", Text -> Inlines
str Text
"J")
  , (Text
"katal", Text -> Inlines
str Text
"kat")
  , (Text
"kelvin", Text -> Inlines
str Text
"K")
  , (Text
"kilogram", Text -> Inlines
str Text
"kg")
  , (Text
"knot", Text -> Inlines
str Text
"kn")
  , (Text
"liter", Text -> Inlines
str Text
"L")
  , (Text
"litre", Text -> Inlines
str Text
"l")
  , (Text
"lumen", Text -> Inlines
str Text
"lm")
  , (Text
"lux", Text -> Inlines
str Text
"lx")
  , (Text
"meter", Text -> Inlines
str Text
"m")
  , (Text
"metre", Text -> Inlines
str Text
"m")
  , (Text
"minute", Text -> Inlines
str Text
"min")
  , (Text
"mmHg", Text -> Inlines
str Text
"mmHg")
  , (Text
"mole", Text -> Inlines
str Text
"mol")
  , (Text
"nauticalmile", Text -> Inlines
str Text
"M")
  , (Text
"neper", Text -> Inlines
str Text
"Np")
  , (Text
"newton", Text -> Inlines
str Text
"N")
  , (Text
"ohm", Text -> Inlines
str Text
"Ω")
  , (Text
"Pa", Text -> Inlines
str Text
"Pa")
  , (Text
"pascal", Text -> Inlines
str Text
"Pa")
  , (Text
"percent", Text -> Inlines
str Text
"%")
  , (Text
"planckbar", Inlines -> Inlines
emph (Text -> Inlines
str Text
"\x210f"))
  , (Text
"radian", Text -> Inlines
str Text
"rad")
  , (Text
"second", Text -> Inlines
str Text
"s")
  , (Text
"siemens", Text -> Inlines
str Text
"S")
  , (Text
"sievert", Text -> Inlines
str Text
"Sv")
  , (Text
"steradian", Text -> Inlines
str Text
"sr")
  , (Text
"tesla", Text -> Inlines
str Text
"T")
  , (Text
"tonne", Text -> Inlines
str Text
"t")
  , (Text
"volt", Text -> Inlines
str Text
"V")
  , (Text
"watt", Text -> Inlines
str Text
"W")
  , (Text
"weber", Text -> Inlines
str Text
"Wb")
  ]