aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlexander Krotov <ilabdsf@gmail.com>2018-11-09 14:19:17 +0300
committerAlexander Krotov <ilabdsf@gmail.com>2018-11-14 17:58:44 +0300
commitc61b67410ac9f30786dd8e5c73cf2a7bbdbcd02c (patch)
treeccfaf27480c833189b0953acb8a45846f204d0f5
parent195b3af8b63bed91d565d8745e75f07509bb595d (diff)
downloadpandoc-c61b67410ac9f30786dd8e5c73cf2a7bbdbcd02c.tar.gz
Muse reader: add grid tables support
-rw-r--r--src/Text/Pandoc/Readers/Muse.hs33
-rw-r--r--test/Tests/Readers/Muse.hs43
2 files changed, 74 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs
index e3c8392e6..2ddaffabd 100644
--- a/src/Text/Pandoc/Readers/Muse.hs
+++ b/src/Text/Pandoc/Readers/Muse.hs
@@ -32,8 +32,6 @@ Conversion of Muse text to 'Pandoc' document.
-}
{-
TODO:
-- Org tables
-- table.el tables
- <cite> tag
-}
module Text.Pandoc.Readers.Muse (readMuse) where
@@ -335,6 +333,7 @@ blockElements = (mempty <$ blankline)
<|> playTag
<|> verseTag
<|> lineBlock
+ <|> museGridTable
<|> table
<|> commentTag
@@ -681,6 +680,36 @@ elementsToTable :: [MuseTableElement] -> MuseTable
elementsToTable = foldr museAppendElement emptyTable
where emptyTable = MuseTable mempty mempty mempty mempty
+museGridPart :: PandocMonad m => MuseParser m Int
+museGridPart = try $ length <$> many1 (char '-') <* char '+'
+
+museGridTableHeader :: PandocMonad m => MuseParser m [Int]
+museGridTableHeader = try $ char '+' *> many1 museGridPart <* manyTill spaceChar eol
+
+museGridTableRow :: PandocMonad m
+ => Int
+ -> [Int]
+ -> MuseParser m (F [Blocks])
+museGridTableRow indent indices = try $ do
+ lns <- many1 $ try (indentWith indent *> museGridTableRawLine indices)
+ let cols = map unlines $ transpose lns
+ indentWith indent *> museGridTableHeader
+ sequence <$> mapM (parseFromString parseBlocks) cols
+
+museGridTableRawLine :: PandocMonad m
+ => [Int]
+ -> MuseParser m [String]
+museGridTableRawLine indices =
+ char '|' *> forM indices (\n -> count n anyChar <* char '|') <* manyTill spaceChar eol
+
+museGridTable :: PandocMonad m => MuseParser m (F Blocks)
+museGridTable = try $ do
+ indent <- getIndent
+ indices <- museGridTableHeader
+ fmap rowsToTable . sequence <$> many1 (museGridTableRow indent indices)
+ where rowsToTable rows = B.table mempty attrs [] rows
+ where attrs = const (AlignDefault, 0.0) <$> transpose rows
+
-- | Parse a table.
table :: PandocMonad m => MuseParser m (F Blocks)
table = try $ fmap (museToPandocTable . elementsToTable) <$> tableElements
diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs
index 42dec0ffd..0f9f2d92f 100644
--- a/test/Tests/Readers/Muse.hs
+++ b/test/Tests/Readers/Muse.hs
@@ -976,6 +976,49 @@ tests =
[[plain "1", plain "2", plain "3"],
[plain "4", mempty, plain "6"],
[plain "7", plain "8", plain "9"]]
+ , "Grid table" =:
+ T.unlines
+ [ "+-----+-----+"
+ , "| foo | bar |"
+ , "+-----+-----+"
+ ] =?>
+ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
+ []
+ [[para "foo", para "bar"]]
+ , "Grid table inside list" =:
+ T.unlines
+ [ " - +-----+-----+"
+ , " | foo | bar |"
+ , " +-----+-----+"
+ ] =?>
+ bulletList [table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
+ []
+ [[para "foo", para "bar"]]]
+ , "Grid table with two rows" =:
+ T.unlines
+ [ "+-----+-----+"
+ , "| foo | bar |"
+ , "+-----+-----+"
+ , "| bat | baz |"
+ , "+-----+-----+"
+ ] =?>
+ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
+ []
+ [[para "foo", para "bar"]
+ ,[para "bat", para "baz"]]
+ , "Grid table inside grid table" =:
+ T.unlines
+ [ "+-----+"
+ , "|+---+|"
+ , "||foo||"
+ , "|+---+|"
+ , "+-----+"
+ ] =?>
+ table mempty [(AlignDefault, 0.0)]
+ []
+ [[table mempty [(AlignDefault, 0.0)]
+ []
+ [[para "foo"]]]]
]
, testGroup "Lists"
[ "Bullet list" =: