{-# LANGUAGE Rank2Types, OverloadedStrings, FlexibleContexts, RecordWildCards #-}
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
ReplaceEqn{[Inline]
[Block]
replaceEqnEq :: [Block]
replaceEqnIdx :: [Inline]
replaceEqnEq :: forall a. ReplaceEqn a -> [a]
replaceEqnIdx :: forall a. ReplaceEqn a -> [Inline]
..} <- (Options -> BlockTemplate) -> Attr -> Text -> WS (ReplaceEqn Block)
forall a t.
MkTemplate a t =>
(Options -> t) -> Attr -> Text -> WS (ReplaceEqn a)
replaceEqn Options -> BlockTemplate
eqnBlockTemplate (Text
label, [Text]
cls, [(Text, Text)]
attrs) Text
eq
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]
replaceEqnIdx [(Text, Text)]
attrs) [Block]
replaceEqnEq
else WS (ReplacedResult Block)
forall (m :: * -> *) a. Monad m => m (ReplacedResult a)
noReplaceRecurse
data ReplaceEqn a = ReplaceEqn
{ forall a. ReplaceEqn a -> [a]
replaceEqnEq :: [a]
, forall a. ReplaceEqn a -> [Inline]
replaceEqnIdx :: [Inline]
}
replaceEqn :: MkTemplate a t => (Options -> t) -> Attr -> T.Text -> WS (ReplaceEqn a)
replaceEqn :: forall a t.
MkTemplate a t =>
(Options -> t) -> Attr -> Text -> WS (ReplaceEqn a)
replaceEqn Options -> t
eqTemplate (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 :: [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
$
if Options -> Bool
tableEqns Options
opts
then Options -> Template
eqnInlineTableTemplate Options
opts
else Options -> Template
eqnInlineTemplate Options
opts
wrapMath :: a -> [Inline]
wrapMath a
x = [MathType -> Text -> Inline
Math MathType
mathfmt (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ a -> Text
forall a. Walkable Inline a => a -> Text
stringify a
x]
commonVars :: [Inline] -> Map k [Inline]
commonVars [Inline]
eqn = [(k, [Inline])] -> Map k [Inline]
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(k, [Inline])] -> Map k [Inline])
-> [(k, [Inline])] -> Map k [Inline]
forall a b. (a -> b) -> a -> b
$
[ (k
"e", [Inline]
eqn)
, (k
"t", [Inline]
eqn)
, (k
"i", [Inline] -> [Inline]
forall {a}. Walkable Inline a => a -> [Inline]
wrapMath [Inline]
idxStr)
, (k
"ri", [Inline] -> [Inline]
forall {a}. Walkable Inline a => a -> [Inline]
wrapMath [Inline]
idxStrRaw)
, (k
"nmi", [Inline]
idxStr)
, (k
"nmri", [Inline]
idxStrRaw)
]
eqTxtVars :: Map Text [Inline]
eqTxtVars = [Inline] -> Map Text [Inline]
forall {k}. (Ord k, IsString k) => [Inline] -> Map k [Inline]
commonVars [Text -> Inline
Str Text
eq]
eqInline :: [a]
eqInline = Map Text [Inline] -> t -> [a]
forall a b. MkTemplate a b => Map Text [Inline] -> b -> [a]
applyTemplate' Map Text [Inline]
eqInlineVars (t -> [a]) -> t -> [a]
forall a b. (a -> b) -> a -> b
$ Options -> t
eqTemplate Options
opts
mathfmt :: MathType
mathfmt = if Options -> Bool
eqnBlockInlineMath Options
opts then MathType
InlineMath else MathType
DisplayMath
eqInlineVars :: Map Text [Inline]
eqInlineVars = [Inline] -> Map Text [Inline]
forall {k}. (Ord k, IsString k) => [Inline] -> Map k [Inline]
commonVars ([Inline] -> Map Text [Inline]) -> [Inline] -> Map Text [Inline]
forall a b. (a -> b) -> a -> b
$ [Inline] -> [Inline]
forall {a}. Walkable Inline a => a -> [Inline]
wrapMath [Inline]
eqTxt
ReplaceEqn a -> WS (ReplaceEqn a)
forall a. a -> WS a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ReplaceEqn a -> WS (ReplaceEqn a))
-> ReplaceEqn a -> WS (ReplaceEqn a)
forall a b. (a -> b) -> a -> b
$ ReplaceEqn
{ replaceEqnEq :: [a]
replaceEqnEq = [a]
eqInline
, replaceEqnIdx :: [Inline]
replaceEqnIdx = [Inline]
idxStr
}
splitMath :: [Block] -> [Block]
splitMath :: [Block] -> [Block]
splitMath (Para [Inline]
ils:[Block]
xs)
| Inline
_:Inline
_:[Inline]
_ <- [Inline]
ils
= ([Inline] -> Block) -> [[Inline]] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
map [Inline] -> Block
Para ([Inline] -> [[Inline]]
split [Inline]
ils) [Block] -> [Block] -> [Block]
forall a. Semigroup a => a -> a -> a
<> [Block]
xs
where
split :: [Inline] -> [[Inline]]
split [Inline]
ys =
let ([Inline]
before, [Inline]
after) = (Inline -> Bool) -> [Inline] -> ([Inline], [Inline])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Inline -> Bool
isMath [Inline]
ys
beforeEl :: [[Inline]] -> [[Inline]]
beforeEl
| [Inline] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
before = [[Inline]] -> [[Inline]]
forall a. a -> a
id
| Bool
otherwise = ([Inline]
before [Inline] -> [[Inline]] -> [[Inline]]
forall a. a -> [a] -> [a]
:)
in [[Inline]] -> [[Inline]]
beforeEl ([[Inline]] -> [[Inline]]) -> [[Inline]] -> [[Inline]]
forall a b. (a -> b) -> a -> b
$ case [Inline]
after of
Inline
z:[Inline]
zs -> [Inline
z] [Inline] -> [[Inline]] -> [[Inline]]
forall a. a -> [a] -> [a]
: [Inline] -> [[Inline]]
split ([Inline] -> [Inline]
dropSpaces [Inline]
zs)
[] -> []
dropSpaces :: [Inline] -> [Inline]
dropSpaces = (Inline -> Bool) -> [Inline] -> [Inline]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Inline -> Bool
isSpace
isMath :: Inline -> Bool
isMath (Span Attr
_ [Math MathType
DisplayMath Text
_]) = Bool
True
isMath Inline
_ = Bool
False
splitMath [Block]
xs = [Block]
xs