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