{-# LANGUAGE Rank2Types, OverloadedStrings, FlexibleContexts #-}
module Text.Pandoc.CrossRef.References.Blocks.Math where
import Control.Monad.Reader.Class
import qualified Data.Map as M
import qualified Data.Text as T
import Text.Pandoc.Definition
import Text.Pandoc.Shared (stringify)
import Text.Pandoc.CrossRef.References.Monad
import Text.Pandoc.CrossRef.References.Blocks.Util
import Text.Pandoc.CrossRef.Util.Options
import Text.Pandoc.CrossRef.Util.Template
import Text.Pandoc.CrossRef.Util.Util
runBlockMath :: Attr -> T.Text -> WS (ReplacedResult Block)
runBlockMath :: Attr -> Text -> WS (ReplacedResult Block)
runBlockMath (Text
label, [Text]
cls, [(Text, Text)]
attrs) Text
eq = do
Options
opts <- WS Options
forall r (m :: * -> *). MonadReader r m => m r
ask
if Options -> Bool
tableEqns Options
opts Bool -> Bool -> Bool
&& Bool -> Bool
not (Options -> Bool
isLatexFormat Options
opts)
then do
(Text
eq', [Inline]
idxStr) <- Attr -> Text -> WS (Text, [Inline])
replaceEqn (Text
label, [Text]
cls, [(Text, Text)]
attrs) Text
eq
let mathfmt :: MathType
mathfmt = if Options -> Bool
eqnBlockInlineMath Options
opts then MathType
InlineMath else MathType
DisplayMath
Block -> WS (ReplacedResult Block)
forall (m :: * -> *) a. Monad m => a -> m (ReplacedResult a)
replaceNoRecurse (Block -> WS (ReplacedResult Block))
-> Block -> WS (ReplacedResult Block)
forall a b. (a -> b) -> a -> b
$ Attr -> [Block] -> Block
Div (Text
label,[Text]
cls,Options -> [Inline] -> [(Text, Text)] -> [(Text, Text)]
setLabel Options
opts [Inline]
idxStr [(Text, Text)]
attrs) ([Block] -> Block) -> [Block] -> Block
forall a b. (a -> b) -> a -> b
$
[Inline] -> [Inline] -> BlockTemplate -> [Block]
forall a b. MkTemplate a b => [Inline] -> [Inline] -> b -> [a]
applyTemplate [MathType -> Text -> Inline
Math MathType
mathfmt (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ [Inline] -> Text
forall a. Walkable Inline a => a -> Text
stringify [Inline]
idxStr] [MathType -> Text -> Inline
Math MathType
mathfmt Text
eq']
(BlockTemplate -> [Block]) -> BlockTemplate -> [Block]
forall a b. (a -> b) -> a -> b
$ Options -> BlockTemplate
eqnBlockTemplate Options
opts
else WS (ReplacedResult Block)
forall (m :: * -> *) a. Monad m => m (ReplacedResult a)
noReplaceRecurse
replaceEqn :: Attr -> T.Text -> WS (T.Text, [Inline])
replaceEqn :: Attr -> Text -> WS (Text, [Inline])
replaceEqn (Text
label, [Text]
_, [(Text, Text)]
attrs) Text
eq = do
Options
opts <- WS Options
forall r (m :: * -> *). MonadReader r m => m r
ask
let label' :: Either Text Text
label' | Text -> Bool
T.null Text
label = Text -> Either Text Text
forall a b. a -> Either a b
Left Text
"eq"
| Bool
otherwise = Text -> Either Text Text
forall a b. b -> Either a b
Right Text
label
[Inline]
idxStrRaw <- Either Text Text
-> [(Text, Text)] -> [Inline] -> SPrefix -> WS [Inline]
replaceAttr Either Text Text
label' [(Text, Text)]
attrs [] SPrefix
SPfxEqn
let idxStr :: [Inline]
idxStr = Map Text [Inline] -> Template -> [Inline]
forall a b. MkTemplate a b => Map Text [Inline] -> b -> [a]
applyTemplate' ([(Text, [Inline])] -> Map Text [Inline]
forall k a. [(k, a)] -> Map k a
M.fromDistinctAscList [(Text
"i", [Inline]
idxStrRaw)]) (Template -> [Inline]) -> Template -> [Inline]
forall a b. (a -> b) -> a -> b
$ Options -> Template
eqnIndexTemplate Options
opts
eqTxt :: [Inline]
eqTxt = Map Text [Inline] -> Template -> [Inline]
forall a b. MkTemplate a b => Map Text [Inline] -> b -> [a]
applyTemplate' Map Text [Inline]
eqTxtVars (Template -> [Inline]) -> Template -> [Inline]
forall a b. (a -> b) -> a -> b
$ Options -> Template
eqnInlineTemplate Options
opts :: [Inline]
eqTxtVars :: Map Text [Inline]
eqTxtVars = [(Text, [Inline])] -> Map Text [Inline]
forall k a. [(k, a)] -> Map k a
M.fromDistinctAscList
[ (Text
"e", [Text -> Inline
Str Text
eq])
, (Text
"i", [Inline]
idxStr)
, (Text
"ri", [Inline]
idxStrRaw)
]
eq' :: Text
eq' | Options -> Bool
tableEqns Options
opts = Text
eq
| Bool
otherwise = [Inline] -> Text
forall a. Walkable Inline a => a -> Text
stringify [Inline]
eqTxt
(Text, [Inline]) -> WS (Text, [Inline])
forall a. a -> WS a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
eq', [Inline]
idxStr)
splitMath :: [Block] -> [Block]
splitMath :: [Block] -> [Block]
splitMath (Para [Inline]
ils:[Block]
xs)
| [Inline] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Inline]
ils Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 = ([Inline] -> Block) -> [[Inline]] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
map [Inline] -> Block
Para ([[Inline]] -> [Inline] -> [Inline] -> [[Inline]]
split [] [] [Inline]
ils) [Block] -> [Block] -> [Block]
forall a. Semigroup a => a -> a -> a
<> [Block]
xs
where
split :: [[Inline]] -> [Inline] -> [Inline] -> [[Inline]]
split [[Inline]]
res [Inline]
acc [] = [[Inline]] -> [[Inline]]
forall a. [a] -> [a]
reverse ([Inline] -> [Inline]
forall a. [a] -> [a]
reverse [Inline]
acc [Inline] -> [[Inline]] -> [[Inline]]
forall a. a -> [a] -> [a]
: [[Inline]]
res)
split [[Inline]]
res [Inline]
acc (x :: Inline
x@(Span Attr
_ [Math MathType
DisplayMath Text
_]):[Inline]
ys) =
[[Inline]] -> [Inline] -> [Inline] -> [[Inline]]
split ([Inline
x] [Inline] -> [[Inline]] -> [[Inline]]
forall a. a -> [a] -> [a]
: [Inline] -> [Inline]
forall a. [a] -> [a]
reverse ([Inline] -> [Inline]
dropSpaces [Inline]
acc) [Inline] -> [[Inline]] -> [[Inline]]
forall a. a -> [a] -> [a]
: [[Inline]]
res)
[] ([Inline] -> [Inline]
dropSpaces [Inline]
ys)
split [[Inline]]
res [Inline]
acc (Inline
y:[Inline]
ys) = [[Inline]] -> [Inline] -> [Inline] -> [[Inline]]
split [[Inline]]
res (Inline
yInline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
:[Inline]
acc) [Inline]
ys
dropSpaces :: [Inline] -> [Inline]
dropSpaces = (Inline -> Bool) -> [Inline] -> [Inline]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Inline -> Bool
isSpace
splitMath [Block]
xs = [Block]
xs