Fixed table parsing with wide or combining characters.

Closes #348.  Closes #108.
This commit is contained in:
John MacFarlane 2012-01-27 00:39:00 -08:00
parent 4321e27bfd
commit ff93a8e789
2 changed files with 5 additions and 5 deletions

View file

@ -502,7 +502,7 @@ gridTableWith block tableCaption headless =
gridTableSplitLine :: [Int] -> String -> [String] gridTableSplitLine :: [Int] -> String -> [String]
gridTableSplitLine indices line = map removeFinalBar $ tail $ gridTableSplitLine indices line = map removeFinalBar $ tail $
splitByIndices (init indices) $ removeTrailingSpace line splitStringByIndices (init indices) $ removeTrailingSpace line
gridPart :: Char -> GenParser Char st (Int, Int) gridPart :: Char -> GenParser Char st (Int, Int)
gridPart ch = do gridPart ch = do

View file

@ -773,7 +773,7 @@ simpleTableHeader headless = try $ do
let (lengths, lines') = unzip dashes let (lengths, lines') = unzip dashes
let indices = scanl (+) (length initSp) lines' let indices = scanl (+) (length initSp) lines'
-- If no header, calculate alignment on basis of first row of text -- If no header, calculate alignment on basis of first row of text
rawHeads <- liftM (tail . splitByIndices (init indices)) $ rawHeads <- liftM (tail . splitStringByIndices (init indices)) $
if headless if headless
then lookAhead anyLine then lookAhead anyLine
else return rawContent else return rawContent
@ -800,7 +800,7 @@ rawTableLine indices = do
notFollowedBy' (blanklines <|> tableFooter) notFollowedBy' (blanklines <|> tableFooter)
line <- many1Till anyChar newline line <- many1Till anyChar newline
return $ map removeLeadingTrailingSpace $ tail $ return $ map removeLeadingTrailingSpace $ tail $
splitByIndices (init indices) line splitStringByIndices (init indices) line
-- Parse a table line and return a list of lists of blocks (columns). -- Parse a table line and return a list of lists of blocks (columns).
tableLine :: [Int] tableLine :: [Int]
@ -862,9 +862,9 @@ multilineTableHeader headless = try $ do
let indices = scanl (+) (length initSp) lines' let indices = scanl (+) (length initSp) lines'
rawHeadsList <- if headless rawHeadsList <- if headless
then liftM (map (:[]) . tail . then liftM (map (:[]) . tail .
splitByIndices (init indices)) $ lookAhead anyLine splitStringByIndices (init indices)) $ lookAhead anyLine
else return $ transpose $ map else return $ transpose $ map
(\ln -> tail $ splitByIndices (init indices) ln) (\ln -> tail $ splitStringByIndices (init indices) ln)
rawContent rawContent
let aligns = zipWith alignType rawHeadsList lengths let aligns = zipWith alignType rawHeadsList lengths
let rawHeads = if headless let rawHeads = if headless