LaTeX reader: properly handle column prefixes/suffixes.

For example, in

     \begin{tabular}{>{$}l<{$}>{$}l<{$} >{$}l<{$}}

each cell will be interpreted as if it has a `$`
before its content and a `$` after (math mode).
This commit is contained in:
John MacFarlane 2017-02-13 22:39:59 +01:00
parent c4c9374526
commit cfdbe85e71
2 changed files with 57 additions and 12 deletions

View file

@ -47,7 +47,7 @@ import Text.Pandoc.Builder
import Control.Applicative ((<|>), many, optional) import Control.Applicative ((<|>), many, optional)
import Data.Maybe (fromMaybe, maybeToList) import Data.Maybe (fromMaybe, maybeToList)
import System.FilePath (replaceExtension, takeExtension, addExtension) import System.FilePath (replaceExtension, takeExtension, addExtension)
import Data.List (intercalate) import Data.List (intercalate, unzip3)
import qualified Data.Map as M import qualified Data.Map as M
import Text.Pandoc.Highlighting (fromListingsLanguage, languagesByExtension) import Text.Pandoc.Highlighting (fromListingsLanguage, languagesByExtension)
import Text.Pandoc.ImageSize (numUnit, showFl) import Text.Pandoc.ImageSize (numUnit, showFl)
@ -1324,7 +1324,7 @@ complexNatbibCitation mode = try $ do
-- tables -- tables
parseAligns :: PandocMonad m => LP m [Alignment] parseAligns :: PandocMonad m => LP m [(String, Alignment, String)]
parseAligns = try $ do parseAligns = try $ do
char '{' char '{'
let maybeBar = skipMany $ sp <|> () <$ char '|' <|> () <$ (char '@' >> braced) let maybeBar = skipMany $ sp <|> () <$ char '|' <|> () <$ (char '@' >> braced)
@ -1334,11 +1334,21 @@ parseAligns = try $ do
let rAlign = AlignRight <$ char 'r' let rAlign = AlignRight <$ char 'r'
let parAlign = AlignLeft <$ (char 'p' >> braced) let parAlign = AlignLeft <$ (char 'p' >> braced)
let alignChar = cAlign <|> lAlign <|> rAlign <|> parAlign let alignChar = cAlign <|> lAlign <|> rAlign <|> parAlign
aligns' <- sepEndBy alignChar maybeBar let alignPrefix = char '>' >> braced
let alignSuffix = char '<' >> braced
let alignSpec = do
spaces
pref <- option "" alignPrefix
spaces
ch <- alignChar
spaces
suff <- option "" alignSuffix
return (pref, ch, suff)
aligns' <- sepEndBy alignSpec maybeBar
spaces spaces
char '}' char '}'
spaces spaces
return aligns' return $ aligns'
hline :: PandocMonad m => LP m () hline :: PandocMonad m => LP m ()
hline = try $ do hline = try $ do
@ -1362,16 +1372,25 @@ lbreak = () <$ try (spaces' *>
amp :: PandocMonad m => LP m () amp :: PandocMonad m => LP m ()
amp = () <$ try (spaces' *> char '&' <* spaces') amp = () <$ try (spaces' *> char '&' <* spaces')
parseTableRow :: PandocMonad m => Int -- ^ number of columns parseTableRow :: PandocMonad m
=> Int -- ^ number of columns
-> [String] -- ^ prefixes
-> [String] -- ^ suffixes
-> LP m [Blocks] -> LP m [Blocks]
parseTableRow cols = try $ do parseTableRow cols prefixes suffixes = try $ do
let tableCellInline = notFollowedBy (amp <|> lbreak) >> inline let tableCellRaw = many (notFollowedBy
(amp <|> lbreak <|>
(() <$ try (string "\\end"))) >> anyChar)
let minipage = try $ controlSeq "begin" *> string "{minipage}" *> let minipage = try $ controlSeq "begin" *> string "{minipage}" *>
env "minipage" env "minipage"
(skipopts *> spaces' *> optional braced *> spaces' *> blocks) (skipopts *> spaces' *> optional braced *> spaces' *> blocks)
let tableCell = minipage <|> let tableCell = minipage <|>
((plain . trimInlines . mconcat) <$> many tableCellInline) ((plain . trimInlines . mconcat) <$> many inline)
cells' <- sepBy1 tableCell amp rawcells <- sepBy1 tableCellRaw amp
guard $ length rawcells == cols
let rawcells' = zipWith3 (\c p s -> p ++ trim c ++ s)
rawcells prefixes suffixes
cells' <- mapM (parseFromString tableCell) rawcells'
let numcells = length cells' let numcells = length cells'
guard $ numcells <= cols && numcells >= 1 guard $ numcells <= cols && numcells >= 1
guard $ cells' /= [mempty] guard $ cells' /= [mempty]
@ -1387,16 +1406,18 @@ simpTable :: PandocMonad m => Bool -> LP m Blocks
simpTable hasWidthParameter = try $ do simpTable hasWidthParameter = try $ do
when hasWidthParameter $ () <$ (spaces' >> tok) when hasWidthParameter $ () <$ (spaces' >> tok)
skipopts skipopts
aligns <- parseAligns (prefixes, aligns, suffixes) <- unzip3 <$> parseAligns
let cols = length aligns let cols = length aligns
optional $ controlSeq "caption" *> skipopts *> setCaption optional $ controlSeq "caption" *> skipopts *> setCaption
optional lbreak optional lbreak
spaces' spaces'
skipMany hline skipMany hline
spaces' spaces'
header' <- option [] $ try (parseTableRow cols <* lbreak <* many1 hline) header' <- option [] $ try (parseTableRow cols prefixes suffixes <*
lbreak <* many1 hline)
spaces' spaces'
rows <- sepEndBy (parseTableRow cols) (lbreak <* optional (skipMany hline)) rows <- sepEndBy (parseTableRow cols prefixes suffixes)
(lbreak <* optional (skipMany hline))
spaces' spaces'
optional $ controlSeq "caption" *> skipopts *> setCaption optional $ controlSeq "caption" *> skipopts *> setCaption
optional lbreak optional lbreak

View file

@ -0,0 +1,24 @@
See https://groups.google.com/forum/#!topic/pandoc-discuss/_VXtqihCyDU.
```
% pandoc -f latex -t native
\begin{tabular}{>{$}l<{$}>{$}l<{$} >{$}l<{$}}
\toprule
& f1 & f2 \\
\midrule
e & 0.5 & 4 \\
f & 0.5 & 5,5 \\
\bottomrule
\end{tabular}
^D
[Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
[[Plain [Math InlineMath ""]]
,[Plain [Math InlineMath "f1"]]
,[Plain [Math InlineMath "f2"]]]
[[[Plain [Math InlineMath "e"]]
,[Plain [Math InlineMath "0.5"]]
,[Plain [Math InlineMath "4"]]]
,[[Plain [Math InlineMath "f"]]
,[Plain [Math InlineMath "0.5"]]
,[Plain [Math InlineMath "5,5"]]]]]
```