{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Text.TeXMath.Writers.Pandoc (writePandoc)
where
import Text.Pandoc.Definition
import qualified Data.Text as T
import Text.TeXMath.Unicode.ToUnicode
import Text.TeXMath.Types
import Text.TeXMath.Shared (getSpaceChars)
writePandoc :: DisplayType
-> [Exp]
-> Maybe [Inline]
writePandoc :: DisplayType -> [Exp] -> Maybe [Inline]
writePandoc DisplayType
_ [Exp]
exps = TextType -> [Exp] -> Maybe [Inline]
expsToInlines TextType
TextNormal [Exp]
exps
expsToInlines :: TextType -> [Exp] -> Maybe [Inline]
expsToInlines :: TextType -> [Exp] -> Maybe [Inline]
expsToInlines TextType
tt [Exp]
xs = do
[[Inline]]
res <- (Exp -> Maybe [Inline]) -> [Exp] -> Maybe [[Inline]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt) ([Exp] -> [Exp]
addSpaces [Exp]
xs)
[Inline] -> Maybe [Inline]
forall (m :: * -> *) a. Monad m => a -> m a
return ([[Inline]] -> [Inline]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Inline]]
res)
addSpaces :: [Exp] -> [Exp]
addSpaces :: [Exp] -> [Exp]
addSpaces (ESymbol TeXSymbolType
t1 Text
s1 : ESpace Rational
r : [Exp]
xs)
= TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
t1 Text
s1 Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
: Rational -> Exp
ESpace Rational
r Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
: [Exp] -> [Exp]
addSpaces [Exp]
xs
addSpaces (ESymbol TeXSymbolType
t1 Text
s1 : [Exp]
xs)
| TeXSymbolType
t1 TeXSymbolType -> [TeXSymbolType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [TeXSymbolType
Bin, TeXSymbolType
Op, TeXSymbolType
Rel, TeXSymbolType
Open, TeXSymbolType
Pun]
= TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
t1 Text
s1 Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
: [Exp] -> [Exp]
addSpaces [Exp]
xs
addSpaces (ESymbol TeXSymbolType
t1 Text
s1 : ESymbol TeXSymbolType
Pun Text
s2 : [Exp]
xs)
= TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
t1 Text
s1 Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
: TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
s2 Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
: [Exp] -> [Exp]
addSpaces [Exp]
xs
addSpaces (ESymbol TeXSymbolType
t2 Text
s2 : [Exp]
xs)
| Bool -> Bool
not ([Exp] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Exp]
xs)
= TeXSymbolType -> Exp -> [Exp]
addSpace TeXSymbolType
t2 (TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
t2 Text
s2) [Exp] -> [Exp] -> [Exp]
forall a. [a] -> [a] -> [a]
++ [Exp] -> [Exp]
addSpaces [Exp]
xs
addSpaces (EMathOperator Text
s : [Exp]
xs) =
Text -> Exp
EMathOperator Text
s Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
: Exp
thinspace Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
: [Exp] -> [Exp]
addSpaces [Exp]
xs
addSpaces (Exp
x:[Exp]
xs) = Exp
x Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
: [Exp] -> [Exp]
addSpaces [Exp]
xs
addSpaces [] = []
addSpace :: TeXSymbolType -> Exp -> [Exp]
addSpace :: TeXSymbolType -> Exp -> [Exp]
addSpace TeXSymbolType
t Exp
x =
case TeXSymbolType
t of
TeXSymbolType
Bin -> [Exp
medspace, Exp
x, Exp
medspace]
TeXSymbolType
Rel -> [Exp
widespace, Exp
x, Exp
widespace]
TeXSymbolType
Pun -> [Exp
x, Exp
thinspace]
TeXSymbolType
_ -> [Exp
x]
thinspace, medspace, widespace :: Exp
thinspace :: Exp
thinspace = TextType -> Text -> Exp
EText TextType
TextNormal Text
"\x2006"
medspace :: Exp
medspace = TextType -> Text -> Exp
EText TextType
TextNormal Text
"\x2005"
widespace :: Exp
widespace = TextType -> Text -> Exp
EText TextType
TextNormal Text
"\x2004"
renderStr :: TextType -> T.Text -> [Inline]
renderStr :: TextType -> Text -> [Inline]
renderStr TextType
_ Text
"" = []
renderStr TextType
tt Text
s =
case TextType
tt of
TextType
TextNormal -> [Text -> Inline
Str Text
s]
TextType
TextBold -> [[Inline] -> Inline
Strong [Text -> Inline
Str Text
s]]
TextType
TextItalic -> [[Inline] -> Inline
Emph [Text -> Inline
Str Text
s]]
TextType
TextMonospace -> [Attr -> Text -> Inline
Code Attr
nullAttr Text
s]
TextType
TextSansSerif -> [Text -> Inline
Str Text
s]
TextType
TextDoubleStruck -> [Text -> Inline
Str (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> Text
toUnicode TextType
tt Text
s]
TextType
TextScript -> [Text -> Inline
Str (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> Text
toUnicode TextType
tt Text
s]
TextType
TextFraktur -> [Text -> Inline
Str (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> Text
toUnicode TextType
tt Text
s]
TextType
TextBoldItalic -> [[Inline] -> Inline
Strong [[Inline] -> Inline
Emph [Text -> Inline
Str Text
s]]]
TextType
TextSansSerifBold -> [[Inline] -> Inline
Strong [Text -> Inline
Str Text
s]]
TextType
TextBoldScript -> [[Inline] -> Inline
Strong [Text -> Inline
Str (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> Text
toUnicode TextType
tt Text
s]]
TextType
TextBoldFraktur -> [[Inline] -> Inline
Strong [Text -> Inline
Str (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> Text
toUnicode TextType
tt Text
s]]
TextType
TextSansSerifItalic -> [[Inline] -> Inline
Emph [Text -> Inline
Str Text
s]]
TextType
TextSansSerifBoldItalic -> [[Inline] -> Inline
Strong [[Inline] -> Inline
Emph [Text -> Inline
Str Text
s]]]
expToInlines :: TextType -> Exp -> Maybe [Inline]
expToInlines :: TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt (ENumber Text
s) = [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt Text
s
expToInlines TextType
TextNormal (EIdentifier Text
s) = [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
TextItalic Text
s
expToInlines TextType
tt (EIdentifier Text
s) = [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt Text
s
expToInlines TextType
tt (EMathOperator Text
s) = [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt Text
s
expToInlines TextType
tt (ESymbol TeXSymbolType
_ Text
s) = [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt Text
s
expToInlines TextType
tt (EDelimited Text
start Text
end [InEDelimited]
xs) = do
[[Inline]]
xs' <- (InEDelimited -> Maybe [Inline])
-> [InEDelimited] -> Maybe [[Inline]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((Text -> Maybe [Inline])
-> (Exp -> Maybe [Inline]) -> InEDelimited -> Maybe [Inline]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Inline] -> Maybe [Inline]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Inline] -> Maybe [Inline])
-> (Text -> [Inline]) -> Text -> Maybe [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextType -> Text -> [Inline]
renderStr TextType
tt) (TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt)) [InEDelimited]
xs
[Inline] -> Maybe [Inline]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt Text
start [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [[Inline]] -> [Inline]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Inline]]
xs' [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ TextType -> Text -> [Inline]
renderStr TextType
tt Text
end
expToInlines TextType
tt (EGrouped [Exp]
xs) = TextType -> [Exp] -> Maybe [Inline]
expsToInlines TextType
tt [Exp]
xs
expToInlines TextType
_ (EStyled TextType
tt' [Exp]
xs) = TextType -> [Exp] -> Maybe [Inline]
expsToInlines TextType
tt' [Exp]
xs
expToInlines TextType
_ (ESpace Rational
n) = [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just [Text -> Inline
Str (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ Rational -> Text
getSpaceChars Rational
n]
expToInlines TextType
_ (ESqrt Exp
_) = Maybe [Inline]
forall a. Maybe a
Nothing
expToInlines TextType
_ (ERoot Exp
_ Exp
_) = Maybe [Inline]
forall a. Maybe a
Nothing
expToInlines TextType
_ (EFraction FractionType
_ Exp
_ Exp
_) = Maybe [Inline]
forall a. Maybe a
Nothing
expToInlines TextType
tt (ESub Exp
x Exp
y) = do
[Inline]
x' <- TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt Exp
x
[Inline]
y' <- TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt Exp
y
[Inline] -> Maybe [Inline]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ [Inline]
x' [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [[Inline] -> Inline
Subscript [Inline]
y']
expToInlines TextType
tt (ESuper Exp
x Exp
y) = do
[Inline]
x' <- TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt Exp
x
[Inline]
y' <- TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt Exp
y
[Inline] -> Maybe [Inline]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ [Inline]
x' [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [[Inline] -> Inline
Superscript [Inline]
y']
expToInlines TextType
tt (ESubsup Exp
x Exp
y Exp
z) = do
[Inline]
x' <- TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt Exp
x
[Inline]
y' <- TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt Exp
y
[Inline]
z' <- TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt Exp
z
[Inline] -> Maybe [Inline]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ [Inline]
x' [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [[Inline] -> Inline
Subscript [Inline]
y'] [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [[Inline] -> Inline
Superscript [Inline]
z']
expToInlines TextType
_ (EText TextType
tt' Text
x) = [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' Text
x
expToInlines TextType
tt (EOver Bool
b (EGrouped [EIdentifier (Text -> String
T.unpack -> [Char
c])]) (ESymbol TeXSymbolType
Accent (Text -> String
T.unpack -> [Char
accent]))) = TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt (Bool -> Exp -> Exp -> Exp
EOver Bool
b (Text -> Exp
EIdentifier (Text -> Exp) -> Text -> Exp
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
c) (TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent (Text -> Exp) -> Text -> Exp
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
accent))
expToInlines TextType
tt (EOver Bool
_ (EIdentifier (Text -> String
T.unpack -> [Char
c])) (ESymbol TeXSymbolType
Accent (Text -> String
T.unpack -> [Char
accent]))) =
case Char
accent of
Char
'\x203E' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0304']
Char
'\x0304' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0304']
Char
'\x00B4' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0301']
Char
'\x0301' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0301']
Char
'\x0060' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0300']
Char
'\x0300' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0300']
Char
'\x02D8' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0306']
Char
'\x0306' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0306']
Char
'\x02C7' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x030C']
Char
'\x030C' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x030C']
Char
'.' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0307']
Char
'\x0307' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0307']
Char
'\x00B0' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x030A']
Char
'\x030A' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x030A']
Char
'\x20D7' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x20D7']
Char
'\x20D6' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x20D6']
Char
'\x005E' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0302']
Char
'\x0302' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0302']
Char
'~' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0303']
Char
'\x0303' -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline]) -> [Inline] -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> [Inline]
renderStr TextType
tt' (Text -> [Inline]) -> Text -> [Inline]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack [Char
c,Char
'\x0303']
Char
_ -> Maybe [Inline]
forall a. Maybe a
Nothing
where tt' :: TextType
tt' = if TextType
tt TextType -> TextType -> Bool
forall a. Eq a => a -> a -> Bool
== TextType
TextNormal then TextType
TextItalic else TextType
tt
expToInlines TextType
tt (EScaled Rational
_ Exp
e) = TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt Exp
e
expToInlines TextType
tt (EUnder Bool
convertible Exp
b Exp
e)
| Bool
convertible = TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt (Exp -> Exp -> Exp
ESub Exp
b Exp
e)
| Bool
otherwise = Maybe [Inline]
forall a. Maybe a
Nothing
expToInlines TextType
tt (EOver Bool
convertible Exp
b Exp
e)
| Bool
convertible = TextType -> Exp -> Maybe [Inline]
expToInlines TextType
tt (Exp -> Exp -> Exp
ESuper Exp
b Exp
e)
| Bool
otherwise = Maybe [Inline]
forall a. Maybe a
Nothing
expToInlines TextType
_ (EUnderover Bool
_ Exp
_ Exp
_ Exp
_) = Maybe [Inline]
forall a. Maybe a
Nothing
expToInlines TextType
_ (EPhantom Exp
_) = Maybe [Inline]
forall a. Maybe a
Nothing
expToInlines TextType
_ (EBoxed Exp
_) = Maybe [Inline]
forall a. Maybe a
Nothing
expToInlines TextType
_ (EArray [Alignment]
_ [ArrayLine]
_) = Maybe [Inline]
forall a. Maybe a
Nothing