Removed Shared.compactify.
Changed signatures on Parsing.tableWith and Parsing.gridTableWith.
This commit is contained in:
parent
86b9a51ee3
commit
56f74cb0ab
3 changed files with 25 additions and 37 deletions
|
@ -740,11 +740,11 @@ lineBlockLines = try $ do
|
||||||
-- | Parse a table using 'headerParser', 'rowParser',
|
-- | Parse a table using 'headerParser', 'rowParser',
|
||||||
-- 'lineParser', and 'footerParser'.
|
-- 'lineParser', and 'footerParser'.
|
||||||
tableWith :: Stream s m Char
|
tableWith :: Stream s m Char
|
||||||
=> ParserT s ParserState m ([[Block]], [Alignment], [Int])
|
=> ParserT s ParserState m ([Blocks], [Alignment], [Int])
|
||||||
-> ([Int] -> ParserT s ParserState m [[Block]])
|
-> ([Int] -> ParserT s ParserState m [Blocks])
|
||||||
-> ParserT s ParserState m sep
|
-> ParserT s ParserState m sep
|
||||||
-> ParserT s ParserState m end
|
-> ParserT s ParserState m end
|
||||||
-> ParserT s ParserState m Block
|
-> ParserT s ParserState m Blocks
|
||||||
tableWith headerParser rowParser lineParser footerParser = try $ do
|
tableWith headerParser rowParser lineParser footerParser = try $ do
|
||||||
(heads, aligns, indices) <- headerParser
|
(heads, aligns, indices) <- headerParser
|
||||||
lines' <- rowParser indices `sepEndBy1` lineParser
|
lines' <- rowParser indices `sepEndBy1` lineParser
|
||||||
|
@ -753,7 +753,7 @@ tableWith headerParser rowParser lineParser footerParser = try $ do
|
||||||
let widths = if (indices == [])
|
let widths = if (indices == [])
|
||||||
then replicate (length aligns) 0.0
|
then replicate (length aligns) 0.0
|
||||||
else widthsFromIndices numColumns indices
|
else widthsFromIndices numColumns indices
|
||||||
return $ Table [] aligns widths heads lines'
|
return $ B.table mempty (zip aligns widths) heads lines'
|
||||||
|
|
||||||
-- Calculate relative widths of table columns, based on indices
|
-- Calculate relative widths of table columns, based on indices
|
||||||
widthsFromIndices :: Int -- Number of columns on terminal
|
widthsFromIndices :: Int -- Number of columns on terminal
|
||||||
|
@ -787,9 +787,9 @@ widthsFromIndices numColumns' indices =
|
||||||
-- which may be grid, separated by blank lines, and
|
-- which may be grid, separated by blank lines, and
|
||||||
-- ending with a footer (dashed line followed by blank line).
|
-- ending with a footer (dashed line followed by blank line).
|
||||||
gridTableWith :: Stream [Char] m Char
|
gridTableWith :: Stream [Char] m Char
|
||||||
=> ParserT [Char] ParserState m [Block] -- ^ Block list parser
|
=> ParserT [Char] ParserState m Blocks -- ^ Block list parser
|
||||||
-> Bool -- ^ Headerless table
|
-> Bool -- ^ Headerless table
|
||||||
-> ParserT [Char] ParserState m Block
|
-> ParserT [Char] ParserState m Blocks
|
||||||
gridTableWith blocks headless =
|
gridTableWith blocks headless =
|
||||||
tableWith (gridTableHeader headless blocks) (gridTableRow blocks)
|
tableWith (gridTableHeader headless blocks) (gridTableRow blocks)
|
||||||
(gridTableSep '-') gridTableFooter
|
(gridTableSep '-') gridTableFooter
|
||||||
|
@ -818,8 +818,8 @@ gridTableSep ch = try $ gridDashedLines ch >> return '\n'
|
||||||
-- | Parse header for a grid table.
|
-- | Parse header for a grid table.
|
||||||
gridTableHeader :: Stream [Char] m Char
|
gridTableHeader :: Stream [Char] m Char
|
||||||
=> Bool -- ^ Headerless table
|
=> Bool -- ^ Headerless table
|
||||||
-> ParserT [Char] ParserState m [Block]
|
-> ParserT [Char] ParserState m Blocks
|
||||||
-> ParserT [Char] ParserState m ([[Block]], [Alignment], [Int])
|
-> ParserT [Char] ParserState m ([Blocks], [Alignment], [Int])
|
||||||
gridTableHeader headless blocks = try $ do
|
gridTableHeader headless blocks = try $ do
|
||||||
optional blanklines
|
optional blanklines
|
||||||
dashes <- gridDashedLines '-'
|
dashes <- gridDashedLines '-'
|
||||||
|
@ -850,9 +850,9 @@ gridTableRawLine indices = do
|
||||||
|
|
||||||
-- | Parse row of grid table.
|
-- | Parse row of grid table.
|
||||||
gridTableRow :: Stream [Char] m Char
|
gridTableRow :: Stream [Char] m Char
|
||||||
=> ParserT [Char] ParserState m [Block]
|
=> ParserT [Char] ParserState m Blocks
|
||||||
-> [Int]
|
-> [Int]
|
||||||
-> ParserT [Char] ParserState m [[Block]]
|
-> ParserT [Char] ParserState m [Blocks]
|
||||||
gridTableRow blocks indices = do
|
gridTableRow blocks indices = do
|
||||||
colLines <- many1 (gridTableRawLine indices)
|
colLines <- many1 (gridTableRawLine indices)
|
||||||
let cols = map ((++ "\n") . unlines . removeOneLeadingSpace) $
|
let cols = map ((++ "\n") . unlines . removeOneLeadingSpace) $
|
||||||
|
@ -867,8 +867,8 @@ removeOneLeadingSpace xs =
|
||||||
where startsWithSpace "" = True
|
where startsWithSpace "" = True
|
||||||
startsWithSpace (y:_) = y == ' '
|
startsWithSpace (y:_) = y == ' '
|
||||||
|
|
||||||
compactifyCell :: [Block] -> [Block]
|
compactifyCell :: Blocks -> Blocks
|
||||||
compactifyCell bs = head $ compactify [bs]
|
compactifyCell bs = head $ compactify' [bs]
|
||||||
|
|
||||||
-- | Parse footer for a grid table.
|
-- | Parse footer for a grid table.
|
||||||
gridTableFooter :: Stream s m Char => ParserT s ParserState m [Char]
|
gridTableFooter :: Stream s m Char => ParserT s ParserState m [Char]
|
||||||
|
|
|
@ -973,13 +973,13 @@ simpleTableRawLine indices = do
|
||||||
return (simpleTableSplitLine indices line)
|
return (simpleTableSplitLine indices line)
|
||||||
|
|
||||||
-- Parse a table row and return a list of blocks (columns).
|
-- Parse a table row and return a list of blocks (columns).
|
||||||
simpleTableRow :: PandocMonad m => [Int] -> RSTParser m [[Block]]
|
simpleTableRow :: PandocMonad m => [Int] -> RSTParser m [Blocks]
|
||||||
simpleTableRow indices = do
|
simpleTableRow indices = do
|
||||||
notFollowedBy' simpleTableFooter
|
notFollowedBy' simpleTableFooter
|
||||||
firstLine <- simpleTableRawLine indices
|
firstLine <- simpleTableRawLine indices
|
||||||
colLines <- return [] -- TODO
|
colLines <- return [] -- TODO
|
||||||
let cols = map unlines . transpose $ firstLine : colLines
|
let cols = map unlines . transpose $ firstLine : colLines
|
||||||
mapM (parseFromString (B.toList . mconcat <$> many plain)) cols
|
mapM (parseFromString (mconcat <$> many plain)) cols
|
||||||
|
|
||||||
simpleTableSplitLine :: [Int] -> String -> [String]
|
simpleTableSplitLine :: [Int] -> String -> [String]
|
||||||
simpleTableSplitLine indices line =
|
simpleTableSplitLine indices line =
|
||||||
|
@ -988,7 +988,7 @@ simpleTableSplitLine indices line =
|
||||||
|
|
||||||
simpleTableHeader :: PandocMonad m
|
simpleTableHeader :: PandocMonad m
|
||||||
=> Bool -- ^ Headerless table
|
=> Bool -- ^ Headerless table
|
||||||
-> RSTParser m ([[Block]], [Alignment], [Int])
|
-> RSTParser m ([Blocks], [Alignment], [Int])
|
||||||
simpleTableHeader headless = try $ do
|
simpleTableHeader headless = try $ do
|
||||||
optional blanklines
|
optional blanklines
|
||||||
rawContent <- if headless
|
rawContent <- if headless
|
||||||
|
@ -1002,7 +1002,7 @@ simpleTableHeader headless = try $ do
|
||||||
let rawHeads = if headless
|
let rawHeads = if headless
|
||||||
then replicate (length dashes) ""
|
then replicate (length dashes) ""
|
||||||
else simpleTableSplitLine indices rawContent
|
else simpleTableSplitLine indices rawContent
|
||||||
heads <- mapM (parseFromString (B.toList . mconcat <$> many plain)) $
|
heads <- mapM (parseFromString (mconcat <$> many plain)) $
|
||||||
map trim rawHeads
|
map trim rawHeads
|
||||||
return (heads, aligns, indices)
|
return (heads, aligns, indices)
|
||||||
|
|
||||||
|
@ -1011,17 +1011,22 @@ simpleTable :: PandocMonad m
|
||||||
=> Bool -- ^ Headerless table
|
=> Bool -- ^ Headerless table
|
||||||
-> RSTParser m Blocks
|
-> RSTParser m Blocks
|
||||||
simpleTable headless = do
|
simpleTable headless = do
|
||||||
Table c a _w h l <- tableWith (simpleTableHeader headless) simpleTableRow sep simpleTableFooter
|
tbl <- tableWith (simpleTableHeader headless) simpleTableRow
|
||||||
|
sep simpleTableFooter
|
||||||
-- Simple tables get 0s for relative column widths (i.e., use default)
|
-- Simple tables get 0s for relative column widths (i.e., use default)
|
||||||
return $ B.singleton $ Table c a (replicate (length a) 0) h l
|
case B.toList tbl of
|
||||||
|
[Table c a _w h l] -> return $ B.singleton $
|
||||||
|
Table c a (replicate (length a) 0) h l
|
||||||
|
_ -> do
|
||||||
|
warning "tableWith returned something unexpected"
|
||||||
|
return tbl -- TODO error?
|
||||||
where
|
where
|
||||||
sep = return () -- optional (simpleTableSep '-')
|
sep = return () -- optional (simpleTableSep '-')
|
||||||
|
|
||||||
gridTable :: PandocMonad m
|
gridTable :: PandocMonad m
|
||||||
=> Bool -- ^ Headerless table
|
=> Bool -- ^ Headerless table
|
||||||
-> RSTParser m Blocks
|
-> RSTParser m Blocks
|
||||||
gridTable headerless = B.singleton
|
gridTable headerless = gridTableWith parseBlocks headerless
|
||||||
<$> gridTableWith (B.toList <$> parseBlocks) headerless
|
|
||||||
|
|
||||||
table :: PandocMonad m => RSTParser m Blocks
|
table :: PandocMonad m => RSTParser m Blocks
|
||||||
table = gridTable False <|> simpleTable False <|>
|
table = gridTable False <|> simpleTable False <|>
|
||||||
|
|
|
@ -59,7 +59,6 @@ module Text.Pandoc.Shared (
|
||||||
deNote,
|
deNote,
|
||||||
stringify,
|
stringify,
|
||||||
capitalize,
|
capitalize,
|
||||||
compactify,
|
|
||||||
compactify',
|
compactify',
|
||||||
compactify'DL,
|
compactify'DL,
|
||||||
linesToPara,
|
linesToPara,
|
||||||
|
@ -432,22 +431,6 @@ capitalize = walk go
|
||||||
go (Str s) = Str (T.unpack $ T.toUpper $ T.pack s)
|
go (Str s) = Str (T.unpack $ T.toUpper $ T.pack s)
|
||||||
go x = x
|
go x = x
|
||||||
|
|
||||||
-- | Change final list item from @Para@ to @Plain@ if the list contains
|
|
||||||
-- no other @Para@ blocks.
|
|
||||||
compactify :: [[Block]] -- ^ List of list items (each a list of blocks)
|
|
||||||
-> [[Block]]
|
|
||||||
compactify [] = []
|
|
||||||
compactify items =
|
|
||||||
case (init items, last items) of
|
|
||||||
(_,[]) -> items
|
|
||||||
(others, final) ->
|
|
||||||
case last final of
|
|
||||||
Para a -> case (filter isPara $ concat items) of
|
|
||||||
-- if this is only Para, change to Plain
|
|
||||||
[_] -> others ++ [init final ++ [Plain a]]
|
|
||||||
_ -> items
|
|
||||||
_ -> items
|
|
||||||
|
|
||||||
-- | Change final list item from @Para@ to @Plain@ if the list contains
|
-- | Change final list item from @Para@ to @Plain@ if the list contains
|
||||||
-- no other @Para@ blocks. Like compactify, but operates on @Blocks@ rather
|
-- no other @Para@ blocks. Like compactify, but operates on @Blocks@ rather
|
||||||
-- than @[Block]@.
|
-- than @[Block]@.
|
||||||
|
|
Loading…
Add table
Reference in a new issue