{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.LaTeX.Table
( tableEnvironments )
where
import Data.Functor (($>))
import Text.Pandoc.Class
import Text.Pandoc.Readers.LaTeX.Parsing
import Text.Pandoc.Readers.LaTeX.Types
import Text.Pandoc.Builder as B
import qualified Data.Map as M
import Data.Text (Text)
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import Control.Applicative ((<|>), optional, many)
import Control.Monad (when, void)
import Text.Pandoc.Shared (safeRead, trim)
import Text.Pandoc.Logging (LogMessage(SkippedContent))
import Text.Pandoc.Walk (walkM)
import Text.Pandoc.Parsing hiding (blankline, many, mathDisplay, mathInline,
optional, space, spaces, withRaw, (<|>))
tableEnvironments :: PandocMonad m
=> LP m Blocks
-> LP m Inlines
-> M.Map Text (LP m Blocks)
tableEnvironments :: LP m Blocks -> LP m Inlines -> Map Text (LP m Blocks)
tableEnvironments LP m Blocks
blocks LP m Inlines
inline =
[(Text, LP m Blocks)] -> Map Text (LP m Blocks)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"longtable", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"longtable" (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
resetCaption LP m () -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
LP m Blocks -> LP m Inlines -> Text -> Bool -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
LP m Blocks -> LP m Inlines -> Text -> Bool -> LP m Blocks
simpTable LP m Blocks
blocks LP m Inlines
inline Text
"longtable" Bool
False LP m Blocks -> (Blocks -> LP m Blocks) -> LP m Blocks
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Blocks -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Blocks -> LP m Blocks
addTableCaption)
, (Text
"table", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"table" (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts LP m () -> LP m () -> LP m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
resetCaption LP m () -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Blocks
blocks LP m Blocks -> (Blocks -> LP m Blocks) -> LP m Blocks
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Blocks -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Blocks -> LP m Blocks
addTableCaption)
, (Text
"tabular*", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"tabular*" (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ LP m Blocks -> LP m Inlines -> Text -> Bool -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
LP m Blocks -> LP m Inlines -> Text -> Bool -> LP m Blocks
simpTable LP m Blocks
blocks LP m Inlines
inline Text
"tabular*" Bool
True)
, (Text
"tabularx", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"tabularx" (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ LP m Blocks -> LP m Inlines -> Text -> Bool -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
LP m Blocks -> LP m Inlines -> Text -> Bool -> LP m Blocks
simpTable LP m Blocks
blocks LP m Inlines
inline Text
"tabularx" Bool
True)
, (Text
"tabular", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"tabular" (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ LP m Blocks -> LP m Inlines -> Text -> Bool -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
LP m Blocks -> LP m Inlines -> Text -> Bool -> LP m Blocks
simpTable LP m Blocks
blocks LP m Inlines
inline Text
"tabular" Bool
False)
]
hline :: PandocMonad m => LP m ()
hline :: LP m ()
hline = LP m () -> LP m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m () -> LP m ()) -> LP m () -> LP m ()
forall a b. (a -> b) -> a -> b
$ do
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"hline" LP m Tok -> LP m Tok -> LP m Tok
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"toprule" LP m Tok -> LP m Tok -> LP m Tok
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"bottomrule" LP m Tok -> LP m Tok -> LP m Tok
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"midrule" LP m Tok -> LP m Tok -> LP m Tok
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"endhead" LP m Tok -> LP m Tok -> LP m Tok
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"endfirsthead"
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
ParsecT [Tok] LaTeXState m Text
-> ParsecT [Tok] LaTeXState m (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT [Tok] LaTeXState m Text
forall (m :: * -> *). PandocMonad m => LP m Text
rawopt
() -> LP m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
lbreak :: PandocMonad m => LP m Tok
lbreak :: LP m Tok
lbreak = (Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"\\" LP m Tok -> LP m Tok -> LP m Tok
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"tabularnewline")
LP m Tok -> ParsecT [Tok] LaTeXState m () -> LP m Tok
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts LP m Tok -> ParsecT [Tok] LaTeXState m () -> LP m Tok
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
amp :: PandocMonad m => LP m Tok
amp :: LP m Tok
amp = Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'&'
splitWordTok :: PandocMonad m => LP m ()
splitWordTok :: LP m ()
splitWordTok = do
[Tok]
inp <- ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
case [Tok]
inp of
(Tok SourcePos
spos TokType
Word Text
t : [Tok]
rest) ->
[Tok] -> LP m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput ([Tok] -> LP m ()) -> [Tok] -> LP m ()
forall a b. (a -> b) -> a -> b
$ (Char -> Tok) -> [Char] -> [Tok]
forall a b. (a -> b) -> [a] -> [b]
map (SourcePos -> TokType -> Text -> Tok
Tok SourcePos
spos TokType
Symbol (Text -> Tok) -> (Char -> Text) -> Char -> Tok
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton) (Text -> [Char]
T.unpack Text
t) [Tok] -> [Tok] -> [Tok]
forall a. Semigroup a => a -> a -> a
<> [Tok]
rest
[Tok]
_ -> () -> LP m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
parseAligns :: PandocMonad m => LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
parseAligns :: LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
parseAligns = LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
-> LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
-> LP m [(Alignment, ColWidth, ([Tok], [Tok]))])
-> LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
-> LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
forall a b. (a -> b) -> a -> b
$ do
let maybeBar :: ParsecT [Tok] LaTeXState m ()
maybeBar = 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 () -> ParsecT [Tok] LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (() ()
-> ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ 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 b. Functor f => a -> f b -> f a
<$ (Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'@' ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced)))
let cAlign :: ParsecT [Tok] LaTeXState m Alignment
cAlign = Alignment
AlignCenter Alignment
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'c'
let lAlign :: ParsecT [Tok] LaTeXState m Alignment
lAlign = Alignment
AlignLeft Alignment
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'l'
let rAlign :: ParsecT [Tok] LaTeXState m Alignment
rAlign = Alignment
AlignRight Alignment
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'r'
let parAlign :: ParsecT [Tok] LaTeXState m Alignment
parAlign = Alignment
AlignLeft Alignment
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'p'
let xAlign :: ParsecT [Tok] LaTeXState m Alignment
xAlign = Alignment
AlignLeft Alignment
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'X'
let mAlign :: ParsecT [Tok] LaTeXState m Alignment
mAlign = Alignment
AlignLeft Alignment
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'm'
let bAlign :: ParsecT [Tok] LaTeXState m Alignment
bAlign = Alignment
AlignLeft Alignment
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'b'
let alignChar :: ParsecT [Tok] LaTeXState m Alignment
alignChar = ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
splitWordTok ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ( ParsecT [Tok] LaTeXState m Alignment
cAlign ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tok] LaTeXState m Alignment
lAlign ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tok] LaTeXState m Alignment
rAlign ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tok] LaTeXState m Alignment
parAlign
ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tok] LaTeXState m Alignment
xAlign ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tok] LaTeXState m Alignment
mAlign ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tok] LaTeXState m Alignment
bAlign )
let alignPrefix :: ParsecT [Tok] LaTeXState m [Tok]
alignPrefix = Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'>' ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
let alignSuffix :: ParsecT [Tok] LaTeXState m [Tok]
alignSuffix = Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'<' ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
let colWidth :: ParsecT [Tok] LaTeXState m (Maybe Double)
colWidth = ParsecT [Tok] LaTeXState m (Maybe Double)
-> ParsecT [Tok] LaTeXState m (Maybe Double)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tok] LaTeXState m (Maybe Double)
-> ParsecT [Tok] LaTeXState m (Maybe Double))
-> ParsecT [Tok] LaTeXState m (Maybe Double)
-> ParsecT [Tok] LaTeXState m (Maybe Double)
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'{'
Text
ds <- Text -> Text
trim (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
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m [Tok]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok (Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"linewidth")
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'}'
Maybe Double -> ParsecT [Tok] LaTeXState m (Maybe Double)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Double -> ParsecT [Tok] LaTeXState m (Maybe Double))
-> Maybe Double -> ParsecT [Tok] LaTeXState m (Maybe Double)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Double
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead Text
ds
let alignSpec :: ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
alignSpec = do
[Tok]
pref <- [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
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 [Tok]
alignPrefix
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
Alignment
al <- ParsecT [Tok] LaTeXState m Alignment
alignChar
Maybe Double
width <- ParsecT [Tok] LaTeXState m (Maybe Double)
colWidth ParsecT [Tok] LaTeXState m (Maybe Double)
-> ParsecT [Tok] LaTeXState m (Maybe Double)
-> ParsecT [Tok] LaTeXState m (Maybe Double)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Double
-> ParsecT [Tok] LaTeXState m (Maybe Double)
-> ParsecT [Tok] LaTeXState m (Maybe Double)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Maybe Double
forall a. Maybe a
Nothing (do Text
s <- [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
SourcePos
pos <- ParsecT [Tok] LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
LogMessage -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT [Tok] LaTeXState m ())
-> LogMessage -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent Text
s SourcePos
pos
Maybe Double -> ParsecT [Tok] LaTeXState m (Maybe Double)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Double
forall a. Maybe a
Nothing)
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
[Tok]
suff <- [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
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 [Tok]
alignSuffix
(Alignment, Maybe Double, ([Tok], [Tok]))
-> ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
forall (m :: * -> *) a. Monad m => a -> m a
return (Alignment
al, Maybe Double
width, ([Tok]
pref, [Tok]
suff))
let starAlign :: ParsecT [Tok] LaTeXState m ()
starAlign = do
Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'*'
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
Text
ds <- Text -> Text
trim (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
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
[Tok]
spec <- ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
case Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead Text
ds of
Just Int
n ->
ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput ParsecT [Tok] LaTeXState m [Tok]
-> ([Tok] -> ParsecT [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Tok] -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput ([Tok] -> ParsecT [Tok] LaTeXState m ())
-> ([Tok] -> [Tok]) -> [Tok] -> ParsecT [Tok] LaTeXState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[Tok]] -> [Tok]
forall a. Monoid a => [a] -> a
mconcat (Int -> [Tok] -> [[Tok]]
forall a. Int -> a -> [a]
replicate Int
n [Tok]
spec) [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++)
Maybe Int
Nothing -> [Char] -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
Prelude.fail ([Char] -> ParsecT [Tok] LaTeXState m ())
-> [Char] -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ [Char]
"Could not parse " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Text -> [Char]
T.unpack Text
ds [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
" as number"
ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
bgroup
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
ParsecT [Tok] LaTeXState m ()
maybeBar
[(Alignment, Maybe Double, ([Tok], [Tok]))]
aligns' <- ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
-> ParsecT
[Tok] LaTeXState m [(Alignment, Maybe Double, ([Tok], [Tok]))]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
-> ParsecT
[Tok] LaTeXState m [(Alignment, Maybe Double, ([Tok], [Tok]))])
-> ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
-> ParsecT
[Tok] LaTeXState m [(Alignment, Maybe Double, ([Tok], [Tok]))]
forall a b. (a -> b) -> a -> b
$ ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
-> ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
-> ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok])))
-> ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
-> ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
forall a b. (a -> b) -> a -> b
$ ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe ())
-> ParsecT [Tok] LaTeXState m (Maybe ())
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT [Tok] LaTeXState m ()
starAlign ParsecT [Tok] LaTeXState m (Maybe ())
-> ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
-> ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
(ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
alignSpec ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
-> ParsecT [Tok] LaTeXState m ()
-> ParsecT
[Tok] LaTeXState m (Alignment, Maybe Double, ([Tok], [Tok]))
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] LaTeXState m ()
maybeBar)
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
egroup
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
[(Alignment, ColWidth, ([Tok], [Tok]))]
-> LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
forall (m :: * -> *) a. Monad m => a -> m a
return ([(Alignment, ColWidth, ([Tok], [Tok]))]
-> LP m [(Alignment, ColWidth, ([Tok], [Tok]))])
-> [(Alignment, ColWidth, ([Tok], [Tok]))]
-> LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
forall a b. (a -> b) -> a -> b
$ ((Alignment, Maybe Double, ([Tok], [Tok]))
-> (Alignment, ColWidth, ([Tok], [Tok])))
-> [(Alignment, Maybe Double, ([Tok], [Tok]))]
-> [(Alignment, ColWidth, ([Tok], [Tok]))]
forall a b. (a -> b) -> [a] -> [b]
map (Alignment, Maybe Double, ([Tok], [Tok]))
-> (Alignment, ColWidth, ([Tok], [Tok]))
forall a c. (a, Maybe Double, c) -> (a, ColWidth, c)
toSpec [(Alignment, Maybe Double, ([Tok], [Tok]))]
aligns'
where
toColWidth :: Maybe Double -> ColWidth
toColWidth (Just Double
w) | Double
w Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 = Double -> ColWidth
ColWidth Double
w
toColWidth Maybe Double
_ = ColWidth
ColWidthDefault
toSpec :: (a, Maybe Double, c) -> (a, ColWidth, c)
toSpec (a
x, Maybe Double
y, c
z) = (a
x, Maybe Double -> ColWidth
toColWidth Maybe Double
y, c
z)
parseTableRow :: PandocMonad m
=> LP m Blocks
-> LP m Inlines
-> Text
-> [([Tok], [Tok])]
-> LP m Row
parseTableRow :: LP m Blocks -> LP m Inlines -> Text -> [([Tok], [Tok])] -> LP m Row
parseTableRow LP m Blocks
blocks LP m Inlines
inline Text
envname [([Tok], [Tok])]
prefsufs = do
ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => Text -> LP m ()
end_ Text
envname)
let canContainAmp :: Tok -> Bool
canContainAmp (Tok SourcePos
_ (CtrlSeq Text
"begin") Text
_) = Bool
True
canContainAmp (Tok SourcePos
_ (CtrlSeq Text
"verb") Text
_) = Bool
True
canContainAmp (Tok SourcePos
_ (CtrlSeq Text
"Verb") Text
_) = Bool
True
canContainAmp Tok
_ = Bool
False
let celltoks :: ([Tok], [Tok]) -> ParsecT [Tok] LaTeXState m [Tok]
celltoks ([Tok]
pref, [Tok]
suff) = do
SourcePos
prefpos <- ParsecT [Tok] LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
[Tok]
contents <- [[Tok]] -> [Tok]
forall a. Monoid a => [a] -> a
mconcat ([[Tok]] -> [Tok])
-> ParsecT [Tok] LaTeXState m [[Tok]]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [[Tok]]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ( ((), [Tok]) -> [Tok]
forall a b. (a, b) -> b
snd (((), [Tok]) -> [Tok])
-> ParsecT [Tok] LaTeXState m ((), [Tok])
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m ((), [Tok])
forall (m :: * -> *) a. PandocMonad m => LP m a -> LP m (a, [Tok])
withRaw
((ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m Tok
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"parbox") ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
LP m Blocks -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void LP m Blocks
blocks)
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 Tok
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ((Tok -> Bool) -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => (Tok -> Bool) -> LP m Tok
satisfyTok Tok -> Bool
canContainAmp) ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m Inlines -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void LP m Inlines
inline)
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 Tok
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'$') ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m Inlines -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void LP m Inlines
inline))
ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(do ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy
(() ()
-> ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
amp 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 b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
lbreak ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => Text -> LP m ()
end_ Text
envname)
Int
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m [Tok]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
1 ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok) )
SourcePos
suffpos <- ParsecT [Tok] LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
[Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [] (Int
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m [Tok]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
1 ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
amp)
[Tok] -> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Tok] -> ParsecT [Tok] LaTeXState m [Tok])
-> [Tok] -> ParsecT [Tok] LaTeXState m [Tok]
forall a b. (a -> b) -> a -> b
$ (Tok -> Tok) -> [Tok] -> [Tok]
forall a b. (a -> b) -> [a] -> [b]
map (SourcePos -> Tok -> Tok
setpos SourcePos
prefpos) [Tok]
pref [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++ [Tok]
contents [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++ (Tok -> Tok) -> [Tok] -> [Tok]
forall a b. (a -> b) -> [a] -> [b]
map (SourcePos -> Tok -> Tok
setpos SourcePos
suffpos) [Tok]
suff
[[Tok]]
rawcells <- (([Tok], [Tok]) -> ParsecT [Tok] LaTeXState m [Tok])
-> [([Tok], [Tok])] -> ParsecT [Tok] LaTeXState m [[Tok]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ([Tok], [Tok]) -> ParsecT [Tok] LaTeXState m [Tok]
celltoks [([Tok], [Tok])]
prefsufs
[Cell]
cells <- ([Tok] -> ParsecT [Tok] LaTeXState m Cell)
-> [[Tok]] -> ParsecT [Tok] LaTeXState m [Cell]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (ParsecT [Tok] LaTeXState m Cell
-> [Tok] -> ParsecT [Tok] LaTeXState m Cell
forall (m :: * -> *) a. PandocMonad m => LP m a -> [Tok] -> LP m a
parseFromToks (LP m Blocks -> ParsecT [Tok] LaTeXState m Cell
forall (m :: * -> *). PandocMonad m => LP m Blocks -> LP m Cell
parseTableCell LP m Blocks
blocks)) [[Tok]]
rawcells
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
Row -> LP m Row
forall (m :: * -> *) a. Monad m => a -> m a
return (Row -> LP m Row) -> Row -> LP m Row
forall a b. (a -> b) -> a -> b
$ Attr -> [Cell] -> Row
Row Attr
nullAttr [Cell]
cells
parseTableCell :: PandocMonad m => LP m Blocks -> LP m Cell
parseTableCell :: LP m Blocks -> LP m Cell
parseTableCell LP m Blocks
blocks = do
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
(LaTeXState -> LaTeXState) -> LP m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> LP m ())
-> (LaTeXState -> LaTeXState) -> LP m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{ sInTableCell :: Bool
sInTableCell = Bool
True }
Cell
cell' <- LP m Blocks -> LP m Cell
forall (m :: * -> *). PandocMonad m => LP m Blocks -> LP m Cell
multicolumnCell LP m Blocks
blocks
LP m Cell -> LP m Cell -> LP m Cell
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Blocks -> LP m Cell
forall (m :: * -> *). PandocMonad m => LP m Blocks -> LP m Cell
multirowCell LP m Blocks
blocks
LP m Cell -> LP m Cell -> LP m Cell
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Cell
parseSimpleCell
LP m Cell -> LP m Cell -> LP m Cell
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Cell
parseEmptyCell
(LaTeXState -> LaTeXState) -> LP m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> LP m ())
-> (LaTeXState -> LaTeXState) -> LP m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{ sInTableCell :: Bool
sInTableCell = Bool
False }
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
Cell -> LP m Cell
forall (m :: * -> *) a. Monad m => a -> m a
return Cell
cell'
where
parseEmptyCell :: LP m Cell
parseEmptyCell = LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces LP m () -> Cell -> LP m Cell
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Cell
emptyCell
parseSimpleCell :: LP m Cell
parseSimpleCell = Blocks -> Cell
simpleCell (Blocks -> Cell) -> LP m Blocks -> LP m Cell
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Blocks -> Blocks
plainify (Blocks -> Blocks) -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Blocks
blocks)
cellAlignment :: PandocMonad m => LP m Alignment
cellAlignment :: LP m Alignment
cellAlignment = ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'|') ParsecT [Tok] LaTeXState m () -> LP m Alignment -> LP m Alignment
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Alignment
alignment LP m Alignment -> ParsecT [Tok] LaTeXState m () -> LP m Alignment
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'|')
where
alignment :: LP m Alignment
alignment = do
Text
c <- Tok -> Text
untoken (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
singleChar
Alignment -> LP m Alignment
forall (m :: * -> *) a. Monad m => a -> m a
return (Alignment -> LP m Alignment) -> Alignment -> LP m Alignment
forall a b. (a -> b) -> a -> b
$ case Text
c of
Text
"l" -> Alignment
AlignLeft
Text
"r" -> Alignment
AlignRight
Text
"c" -> Alignment
AlignCenter
Text
"*" -> Alignment
AlignDefault
Text
_ -> Alignment
AlignDefault
plainify :: Blocks -> Blocks
plainify :: Blocks -> Blocks
plainify Blocks
bs = case Blocks -> [Block]
forall a. Many a -> [a]
toList Blocks
bs of
[Para [Inline]
ils] -> Inlines -> Blocks
plain ([Inline] -> Inlines
forall a. [a] -> Many a
fromList [Inline]
ils)
[Block]
_ -> Blocks
bs
multirowCell :: PandocMonad m => LP m Blocks -> LP m Cell
multirowCell :: LP m Blocks -> LP m Cell
multirowCell LP m Blocks
blocks = Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"multirow" LP m Tok -> LP m Cell -> LP m Cell
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> do
Maybe Alignment
_ <- ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m (Maybe Alignment)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m (Maybe Alignment))
-> ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m (Maybe Alignment)
forall a b. (a -> b) -> a -> b
$ Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'[' LP m Tok
-> ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m Alignment
forall (m :: * -> *). PandocMonad m => LP m Alignment
cellAlignment ParsecT [Tok] LaTeXState m Alignment
-> LP m Tok -> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
']'
Int
nrows <- ([Tok] -> Int)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> ([Tok] -> Maybe Int) -> [Tok] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead (Text -> Maybe Int) -> ([Tok] -> Text) -> [Tok] -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize) ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Maybe [Tok]
_ <- ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m (Maybe [Tok])
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m (Maybe [Tok]))
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m (Maybe [Tok])
forall a b. (a -> b) -> a -> b
$ Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'[' LP m Tok
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Tok -> LP m Tok -> ParsecT [Tok] LaTeXState m [Tok]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok (Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
']')
[Tok]
_ <- Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'{' LP m Tok
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Tok -> LP m Tok -> ParsecT [Tok] LaTeXState m [Tok]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok (Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'}')
Maybe [Tok]
_ <- ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m (Maybe [Tok])
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m (Maybe [Tok]))
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m (Maybe [Tok])
forall a b. (a -> b) -> a -> b
$ Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'[' LP m Tok
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Tok -> LP m Tok -> ParsecT [Tok] LaTeXState m [Tok]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok (Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
']')
Blocks
content <- Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'{' LP m Tok -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Blocks -> Blocks
plainify (Blocks -> Blocks) -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Blocks
blocks) LP m Blocks -> LP m Tok -> LP m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'}'
Cell -> LP m Cell
forall (m :: * -> *) a. Monad m => a -> m a
return (Cell -> LP m Cell) -> Cell -> LP m Cell
forall a b. (a -> b) -> a -> b
$ Alignment -> RowSpan -> ColSpan -> Blocks -> Cell
cell Alignment
AlignDefault (Int -> RowSpan
RowSpan Int
nrows) (Int -> ColSpan
ColSpan Int
1) Blocks
content
multicolumnCell :: PandocMonad m => LP m Blocks -> LP m Cell
multicolumnCell :: LP m Blocks -> LP m Cell
multicolumnCell LP m Blocks
blocks = Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"multicolumn" LP m Tok -> LP m Cell -> LP m Cell
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> do
Int
span' <- ([Tok] -> Int)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> ([Tok] -> Maybe Int) -> [Tok] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead (Text -> Maybe Int) -> ([Tok] -> Text) -> [Tok] -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize) ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Alignment
alignment <- Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'{' LP m Tok
-> ParsecT [Tok] LaTeXState m Alignment
-> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m Alignment
forall (m :: * -> *). PandocMonad m => LP m Alignment
cellAlignment ParsecT [Tok] LaTeXState m Alignment
-> LP m Tok -> ParsecT [Tok] LaTeXState m Alignment
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'}'
let singleCell :: LP m Cell
singleCell = do
Blocks
content <- Blocks -> Blocks
plainify (Blocks -> Blocks) -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Blocks
blocks
Cell -> LP m Cell
forall (m :: * -> *) a. Monad m => a -> m a
return (Cell -> LP m Cell) -> Cell -> LP m Cell
forall a b. (a -> b) -> a -> b
$ Alignment -> RowSpan -> ColSpan -> Blocks -> Cell
cell Alignment
alignment (Int -> RowSpan
RowSpan Int
1) (Int -> ColSpan
ColSpan Int
span') Blocks
content
let nestedCell :: LP m Cell
nestedCell = do
(Cell Attr
_ Alignment
_ (RowSpan Int
rs) ColSpan
_ [Block]
bs) <- LP m Blocks -> LP m Cell
forall (m :: * -> *). PandocMonad m => LP m Blocks -> LP m Cell
multirowCell LP m Blocks
blocks
Cell -> LP m Cell
forall (m :: * -> *) a. Monad m => a -> m a
return (Cell -> LP m Cell) -> Cell -> LP m Cell
forall a b. (a -> b) -> a -> b
$ Alignment -> RowSpan -> ColSpan -> Blocks -> Cell
cell
Alignment
alignment
(Int -> RowSpan
RowSpan Int
rs)
(Int -> ColSpan
ColSpan Int
span')
([Block] -> Blocks
forall a. [a] -> Many a
fromList [Block]
bs)
Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'{' LP m Tok -> LP m Cell -> LP m Cell
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (LP m Cell
nestedCell LP m Cell -> LP m Cell -> LP m Cell
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Cell
singleCell) LP m Cell -> LP m Tok -> LP m Cell
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'}'
fixTableHead :: TableHead -> TableHead
fixTableHead :: TableHead -> TableHead
fixTableHead (TableHead Attr
attr [Row]
rows) = Attr -> [Row] -> TableHead
TableHead Attr
attr [Row]
rows'
where
rows' :: [Row]
rows' = [Row] -> [Row]
fixTableRows [Row]
rows
fixTableBody :: TableBody -> TableBody
fixTableBody :: TableBody -> TableBody
fixTableBody (TableBody Attr
attr RowHeadColumns
rhc [Row]
th [Row]
tb)
= Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
attr RowHeadColumns
rhc [Row]
th' [Row]
tb'
where
th' :: [Row]
th' = [Row] -> [Row]
fixTableRows [Row]
th
tb' :: [Row]
tb' = [Row] -> [Row]
fixTableRows [Row]
tb
fixTableRows :: [Row] -> [Row]
fixTableRows :: [Row] -> [Row]
fixTableRows = [Maybe (ColSpan, RowSpan)] -> [Row] -> [Row]
fixTableRows' ([Maybe (ColSpan, RowSpan)] -> [Row] -> [Row])
-> [Maybe (ColSpan, RowSpan)] -> [Row] -> [Row]
forall a b. (a -> b) -> a -> b
$ Maybe (ColSpan, RowSpan) -> [Maybe (ColSpan, RowSpan)]
forall a. a -> [a]
repeat Maybe (ColSpan, RowSpan)
forall a. Maybe a
Nothing
where
fixTableRows' :: [Maybe (ColSpan, RowSpan)] -> [Row] -> [Row]
fixTableRows' [Maybe (ColSpan, RowSpan)]
oldHang (Row Attr
attr [Cell]
cells : [Row]
rs)
= let ([Maybe (ColSpan, RowSpan)]
newHang, [Cell]
cells') = [Maybe (ColSpan, RowSpan)]
-> [Cell] -> ([Maybe (ColSpan, RowSpan)], [Cell])
fixTableRow [Maybe (ColSpan, RowSpan)]
oldHang [Cell]
cells
rs' :: [Row]
rs' = [Maybe (ColSpan, RowSpan)] -> [Row] -> [Row]
fixTableRows' [Maybe (ColSpan, RowSpan)]
newHang [Row]
rs
in Attr -> [Cell] -> Row
Row Attr
attr [Cell]
cells' Row -> [Row] -> [Row]
forall a. a -> [a] -> [a]
: [Row]
rs'
fixTableRows' [Maybe (ColSpan, RowSpan)]
_ [] = []
fixTableRow :: [Maybe (ColSpan, RowSpan)] -> [Cell] -> ([Maybe (ColSpan, RowSpan)], [Cell])
fixTableRow :: [Maybe (ColSpan, RowSpan)]
-> [Cell] -> ([Maybe (ColSpan, RowSpan)], [Cell])
fixTableRow [Maybe (ColSpan, RowSpan)]
oldHang [Cell]
cells
| (ColSpan
n, [Maybe (ColSpan, RowSpan)] -> [Maybe (ColSpan, RowSpan)]
prefHang, [Maybe (ColSpan, RowSpan)]
restHang) <- [Maybe (ColSpan, RowSpan)]
-> (ColSpan,
[Maybe (ColSpan, RowSpan)] -> [Maybe (ColSpan, RowSpan)],
[Maybe (ColSpan, RowSpan)])
splitHang [Maybe (ColSpan, RowSpan)]
oldHang
, ColSpan
n ColSpan -> ColSpan -> Bool
forall a. Ord a => a -> a -> Bool
> ColSpan
0
= let cells' :: [Cell]
cells' = (Cell -> ColSpan) -> ColSpan -> [Cell] -> [Cell]
forall t t. (Ord t, Num t) => (t -> t) -> t -> [t] -> [t]
dropToWidth Cell -> ColSpan
getCellW ColSpan
n [Cell]
cells
([Maybe (ColSpan, RowSpan)]
restHang', [Cell]
cells'') = [Maybe (ColSpan, RowSpan)]
-> [Cell] -> ([Maybe (ColSpan, RowSpan)], [Cell])
fixTableRow [Maybe (ColSpan, RowSpan)]
restHang [Cell]
cells'
in ([Maybe (ColSpan, RowSpan)] -> [Maybe (ColSpan, RowSpan)]
prefHang [Maybe (ColSpan, RowSpan)]
restHang', [Cell]
cells'')
| c :: Cell
c@(Cell Attr
_ Alignment
_ RowSpan
h ColSpan
w [Block]
_):[Cell]
cells' <- [Cell]
cells
= let h' :: RowSpan
h' = RowSpan -> RowSpan -> RowSpan
forall a. Ord a => a -> a -> a
max RowSpan
1 RowSpan
h
w' :: ColSpan
w' = ColSpan -> ColSpan -> ColSpan
forall a. Ord a => a -> a -> a
max ColSpan
1 ColSpan
w
oldHang' :: [Maybe (ColSpan, RowSpan)]
oldHang' = (Maybe (ColSpan, RowSpan) -> ColSpan)
-> ColSpan
-> [Maybe (ColSpan, RowSpan)]
-> [Maybe (ColSpan, RowSpan)]
forall t t. (Ord t, Num t) => (t -> t) -> t -> [t] -> [t]
dropToWidth Maybe (ColSpan, RowSpan) -> ColSpan
forall b. Maybe (ColSpan, b) -> ColSpan
getHangW ColSpan
w' [Maybe (ColSpan, RowSpan)]
oldHang
([Maybe (ColSpan, RowSpan)]
newHang, [Cell]
cells'') = [Maybe (ColSpan, RowSpan)]
-> [Cell] -> ([Maybe (ColSpan, RowSpan)], [Cell])
fixTableRow [Maybe (ColSpan, RowSpan)]
oldHang' [Cell]
cells'
in (ColSpan -> RowSpan -> [Maybe (ColSpan, RowSpan)]
forall b. (Ord b, Num b) => ColSpan -> b -> [Maybe (ColSpan, b)]
toHang ColSpan
w' RowSpan
h' [Maybe (ColSpan, RowSpan)]
-> [Maybe (ColSpan, RowSpan)] -> [Maybe (ColSpan, RowSpan)]
forall a. Semigroup a => a -> a -> a
<> [Maybe (ColSpan, RowSpan)]
newHang, Cell
c Cell -> [Cell] -> [Cell]
forall a. a -> [a] -> [a]
: [Cell]
cells'')
| Bool
otherwise
= ([Maybe (ColSpan, RowSpan)]
oldHang, [])
where
getCellW :: Cell -> ColSpan
getCellW (Cell Attr
_ Alignment
_ RowSpan
_ ColSpan
w [Block]
_) = ColSpan
w
getHangW :: Maybe (ColSpan, b) -> ColSpan
getHangW = ColSpan
-> ((ColSpan, b) -> ColSpan) -> Maybe (ColSpan, b) -> ColSpan
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ColSpan
1 (ColSpan, b) -> ColSpan
forall a b. (a, b) -> a
fst
getCS :: ColSpan -> Int
getCS (ColSpan Int
n) = Int
n
toHang :: ColSpan -> b -> [Maybe (ColSpan, b)]
toHang ColSpan
c b
r
| b
r b -> b -> Bool
forall a. Ord a => a -> a -> Bool
> b
1 = [(ColSpan, b) -> Maybe (ColSpan, b)
forall a. a -> Maybe a
Just (ColSpan
c, b
r)]
| Bool
otherwise = Int -> Maybe (ColSpan, b) -> [Maybe (ColSpan, b)]
forall a. Int -> a -> [a]
replicate (ColSpan -> Int
getCS ColSpan
c) Maybe (ColSpan, b)
forall a. Maybe a
Nothing
splitHang :: [Maybe (ColSpan, RowSpan)]
-> (ColSpan,
[Maybe (ColSpan, RowSpan)] -> [Maybe (ColSpan, RowSpan)],
[Maybe (ColSpan, RowSpan)])
splitHang = ColSpan
-> ([Maybe (ColSpan, RowSpan)] -> [Maybe (ColSpan, RowSpan)])
-> [Maybe (ColSpan, RowSpan)]
-> (ColSpan,
[Maybe (ColSpan, RowSpan)] -> [Maybe (ColSpan, RowSpan)],
[Maybe (ColSpan, RowSpan)])
forall b c.
(Ord b, Num b) =>
ColSpan
-> ([Maybe (ColSpan, b)] -> c)
-> [Maybe (ColSpan, b)]
-> (ColSpan, [Maybe (ColSpan, b)] -> c, [Maybe (ColSpan, b)])
splitHang' ColSpan
0 [Maybe (ColSpan, RowSpan)] -> [Maybe (ColSpan, RowSpan)]
forall a. a -> a
id
splitHang' :: ColSpan
-> ([Maybe (ColSpan, b)] -> c)
-> [Maybe (ColSpan, b)]
-> (ColSpan, [Maybe (ColSpan, b)] -> c, [Maybe (ColSpan, b)])
splitHang' !ColSpan
n [Maybe (ColSpan, b)] -> c
l (Just (ColSpan
c, b
r):[Maybe (ColSpan, b)]
xs)
= ColSpan
-> ([Maybe (ColSpan, b)] -> c)
-> [Maybe (ColSpan, b)]
-> (ColSpan, [Maybe (ColSpan, b)] -> c, [Maybe (ColSpan, b)])
splitHang' (ColSpan
n ColSpan -> ColSpan -> ColSpan
forall a. Num a => a -> a -> a
+ ColSpan
c) ([Maybe (ColSpan, b)] -> c
l ([Maybe (ColSpan, b)] -> c)
-> ([Maybe (ColSpan, b)] -> [Maybe (ColSpan, b)])
-> [Maybe (ColSpan, b)]
-> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ColSpan -> b -> [Maybe (ColSpan, b)]
forall b. (Ord b, Num b) => ColSpan -> b -> [Maybe (ColSpan, b)]
toHang ColSpan
c (b
rb -> b -> b
forall a. Num a => a -> a -> a
-b
1) [Maybe (ColSpan, b)]
-> [Maybe (ColSpan, b)] -> [Maybe (ColSpan, b)]
forall a. [a] -> [a] -> [a]
++)) [Maybe (ColSpan, b)]
xs
splitHang' ColSpan
n [Maybe (ColSpan, b)] -> c
l [Maybe (ColSpan, b)]
xs = (ColSpan
n, [Maybe (ColSpan, b)] -> c
l, [Maybe (ColSpan, b)]
xs)
dropToWidth :: (t -> t) -> t -> [t] -> [t]
dropToWidth t -> t
_ t
n [t]
l | t
n t -> t -> Bool
forall a. Ord a => a -> a -> Bool
< t
1 = [t]
l
dropToWidth t -> t
wproj t
n (t
c:[t]
cs) = (t -> t) -> t -> [t] -> [t]
dropToWidth t -> t
wproj (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t -> t
wproj t
c) [t]
cs
dropToWidth t -> t
_ t
_ [] = []
simpTable :: PandocMonad m
=> LP m Blocks
-> LP m Inlines
-> Text
-> Bool
-> LP m Blocks
simpTable :: LP m Blocks -> LP m Inlines -> Text -> Bool -> LP m Blocks
simpTable LP m Blocks
blocks LP m Inlines
inline Text
envname Bool
hasWidthParameter = LP m Blocks -> LP m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ do
Bool
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
hasWidthParameter (ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ () () -> LP m Inlines -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LP m Inlines -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines -> LP m Inlines
tokWith LP m Inlines
inline
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
[(Alignment, ColWidth, ([Tok], [Tok]))]
colspecs <- LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
forall (m :: * -> *).
PandocMonad m =>
LP m [(Alignment, ColWidth, ([Tok], [Tok]))]
parseAligns
let ([Alignment]
aligns, [ColWidth]
widths, [([Tok], [Tok])]
prefsufs) = [(Alignment, ColWidth, ([Tok], [Tok]))]
-> ([Alignment], [ColWidth], [([Tok], [Tok])])
forall a b c. [(a, b, c)] -> ([a], [b], [c])
unzip3 [(Alignment, ColWidth, ([Tok], [Tok]))]
colspecs
ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe ()))
-> ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe ())
forall a b. (a -> b) -> a -> b
$ Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"caption" LP m Tok
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m Inlines -> LP m ()
setCaption LP m Inlines
inline
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
label
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
LP m Tok -> ParsecT [Tok] LaTeXState m (Maybe Tok)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
lbreak
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
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 ()
forall (m :: * -> *). PandocMonad m => LP m ()
hline
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
[Row]
header' <- [Row]
-> ParsecT [Tok] LaTeXState m [Row]
-> ParsecT [Tok] LaTeXState m [Row]
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 [Row]
-> ParsecT [Tok] LaTeXState m [Row])
-> (ParsecT [Tok] LaTeXState m Row
-> ParsecT [Tok] LaTeXState m [Row])
-> ParsecT [Tok] LaTeXState m Row
-> ParsecT [Tok] LaTeXState m [Row]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT [Tok] LaTeXState m [Row]
-> ParsecT [Tok] LaTeXState m [Row]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tok] LaTeXState m [Row]
-> ParsecT [Tok] LaTeXState m [Row])
-> (ParsecT [Tok] LaTeXState m Row
-> ParsecT [Tok] LaTeXState m [Row])
-> ParsecT [Tok] LaTeXState m Row
-> ParsecT [Tok] LaTeXState m [Row]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Row -> [Row])
-> ParsecT [Tok] LaTeXState m Row
-> ParsecT [Tok] LaTeXState m [Row]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Row -> [Row] -> [Row]
forall a. a -> [a] -> [a]
:[]) (ParsecT [Tok] LaTeXState m Row
-> ParsecT [Tok] LaTeXState m [Row])
-> ParsecT [Tok] LaTeXState m Row
-> ParsecT [Tok] LaTeXState m [Row]
forall a b. (a -> b) -> a -> b
$
LP m Blocks
-> LP m Inlines
-> Text
-> [([Tok], [Tok])]
-> ParsecT [Tok] LaTeXState m Row
forall (m :: * -> *).
PandocMonad m =>
LP m Blocks -> LP m Inlines -> Text -> [([Tok], [Tok])] -> LP m Row
parseTableRow LP m Blocks
blocks LP m Inlines
inline Text
envname [([Tok], [Tok])]
prefsufs ParsecT [Tok] LaTeXState m Row
-> LP m Tok -> ParsecT [Tok] LaTeXState m Row
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
lbreak ParsecT [Tok] LaTeXState m Row
-> ParsecT [Tok] LaTeXState m [()]
-> ParsecT [Tok] LaTeXState m Row
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m [()]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
hline
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
[Row]
rows <- ParsecT [Tok] LaTeXState m Row
-> LP m Tok -> ParsecT [Tok] LaTeXState m [Row]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
sepEndBy (LP m Blocks
-> LP m Inlines
-> Text
-> [([Tok], [Tok])]
-> ParsecT [Tok] LaTeXState m Row
forall (m :: * -> *).
PandocMonad m =>
LP m Blocks -> LP m Inlines -> Text -> [([Tok], [Tok])] -> LP m Row
parseTableRow LP m Blocks
blocks LP m Inlines
inline Text
envname [([Tok], [Tok])]
prefsufs)
(LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
lbreak LP m Tok -> ParsecT [Tok] LaTeXState m (Maybe ()) -> LP m Tok
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (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 ()
forall (m :: * -> *). PandocMonad m => LP m ()
hline))
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe ()))
-> ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe ())
forall a b. (a -> b) -> a -> b
$ Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"caption" LP m Tok
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m Inlines -> LP m ()
setCaption LP m Inlines
inline
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
label
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
LP m Tok -> ParsecT [Tok] LaTeXState m (Maybe Tok)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
lbreak
ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
LP m Tok -> LP m Tok
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (LP m Tok -> LP m Tok) -> LP m Tok -> LP m Tok
forall a b. (a -> b) -> a -> b
$ Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"end"
let th :: TableHead
th = TableHead -> TableHead
fixTableHead (TableHead -> TableHead) -> TableHead -> TableHead
forall a b. (a -> b) -> a -> b
$ Attr -> [Row] -> TableHead
TableHead Attr
nullAttr [Row]
header'
let tbs :: [TableBody]
tbs = [TableBody -> TableBody
fixTableBody (TableBody -> TableBody) -> TableBody -> TableBody
forall a b. (a -> b) -> a -> b
$ Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
nullAttr RowHeadColumns
0 [] [Row]
rows]
let tf :: TableFoot
tf = Attr -> [Row] -> TableFoot
TableFoot Attr
nullAttr []
Blocks -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Caption
-> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Blocks
table Caption
emptyCaption ([Alignment] -> [ColWidth] -> [ColSpec]
forall a b. [a] -> [b] -> [(a, b)]
zip [Alignment]
aligns [ColWidth]
widths) TableHead
th [TableBody]
tbs TableFoot
tf
addTableCaption :: PandocMonad m => Blocks -> LP m Blocks
addTableCaption :: Blocks -> LP m Blocks
addTableCaption = (Block -> ParsecT [Tok] LaTeXState m Block)
-> Blocks -> LP m Blocks
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM Block -> ParsecT [Tok] LaTeXState m Block
forall (m :: * -> *).
Monad m =>
Block -> ParsecT [Tok] LaTeXState m Block
go
where go :: Block -> ParsecT [Tok] LaTeXState m Block
go (Table Attr
attr Caption
c [ColSpec]
spec TableHead
th [TableBody]
tb TableFoot
tf) = do
LaTeXState
st <- ParsecT [Tok] LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let mblabel :: Maybe Text
mblabel = LaTeXState -> Maybe Text
sLastLabel LaTeXState
st
Caption
capt <- case (LaTeXState -> Maybe Inlines
sCaption LaTeXState
st, Maybe Text
mblabel) of
(Just Inlines
ils, Maybe Text
Nothing) -> Caption -> ParsecT [Tok] LaTeXState m Caption
forall (m :: * -> *) a. Monad m => a -> m a
return (Caption -> ParsecT [Tok] LaTeXState m Caption)
-> Caption -> ParsecT [Tok] LaTeXState m Caption
forall a b. (a -> b) -> a -> b
$ Maybe [Inline] -> Blocks -> Caption
caption Maybe [Inline]
forall a. Maybe a
Nothing (Inlines -> Blocks
plain Inlines
ils)
(Just Inlines
ils, Just Text
lab) -> do
DottedNum
num <- (LaTeXState -> DottedNum) -> LP m DottedNum
forall (m :: * -> *).
Monad m =>
(LaTeXState -> DottedNum) -> LP m DottedNum
getNextNumber LaTeXState -> DottedNum
sLastTableNum
LaTeXState -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState
LaTeXState
st{ sLastTableNum :: DottedNum
sLastTableNum = DottedNum
num
, sLabels :: Map Text [Inline]
sLabels = Text -> [Inline] -> Map Text [Inline] -> Map Text [Inline]
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
lab
[Text -> Inline
Str (DottedNum -> Text
renderDottedNum DottedNum
num)]
(LaTeXState -> Map Text [Inline]
sLabels LaTeXState
st) }
Caption -> ParsecT [Tok] LaTeXState m Caption
forall (m :: * -> *) a. Monad m => a -> m a
return (Caption -> ParsecT [Tok] LaTeXState m Caption)
-> Caption -> ParsecT [Tok] LaTeXState m Caption
forall a b. (a -> b) -> a -> b
$ Maybe [Inline] -> Blocks -> Caption
caption Maybe [Inline]
forall a. Maybe a
Nothing (Inlines -> Blocks
plain Inlines
ils)
(Maybe Inlines
Nothing, Maybe Text
_) -> Caption -> ParsecT [Tok] LaTeXState m Caption
forall (m :: * -> *) a. Monad m => a -> m a
return Caption
c
let attr' :: Attr
attr' = case (Attr
attr, Maybe Text
mblabel) of
((Text
_,[Text]
classes,[(Text, Text)]
kvs), Just Text
ident) ->
(Text
ident,[Text]
classes,[(Text, Text)]
kvs)
(Attr, Maybe Text)
_ -> Attr
attr
Block -> ParsecT [Tok] LaTeXState m Block
forall (m :: * -> *) a. Monad m => a -> m a
return (Block -> ParsecT [Tok] LaTeXState m Block)
-> Block -> ParsecT [Tok] LaTeXState m Block
forall a b. (a -> b) -> a -> b
$ Attr -> Block -> Block
addAttrDiv Attr
attr' (Block -> Block) -> Block -> Block
forall a b. (a -> b) -> a -> b
$ Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
Table Attr
nullAttr Caption
capt [ColSpec]
spec TableHead
th [TableBody]
tb TableFoot
tf
go Block
x = Block -> ParsecT [Tok] LaTeXState m Block
forall (m :: * -> *) a. Monad m => a -> m a
return Block
x
addAttrDiv :: Attr -> Block -> Block
addAttrDiv :: Attr -> Block -> Block
addAttrDiv (Text
"",[],[]) Block
b = Block
b
addAttrDiv Attr
attr Block
b = Attr -> [Block] -> Block
Div Attr
attr [Block
b]