aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/CommonMark.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2017-08-07 23:10:17 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2017-08-07 23:11:14 -0700
commit91c989d6221991a47b1f0a9d180ccf3ce96b3f02 (patch)
tree0ae78b62dee006d93821ac909eaca4c12159c302 /src/Text/Pandoc/Readers/CommonMark.hs
parent6a9db1fde3b592a843b5fa6ce843a46cb3163968 (diff)
downloadpandoc-91c989d6221991a47b1f0a9d180ccf3ce96b3f02.tar.gz
Remove GFM modules; use CMarkGFM for both gfm and commonmark.
We no longer have a separate readGFM and writeGFM; instead, we'll use readCommonMark and writeCommonMark with githubExtensions. It remains to implement these extensions conditionally. Closes #3841.
Diffstat (limited to 'src/Text/Pandoc/Readers/CommonMark.hs')
-rw-r--r--src/Text/Pandoc/Readers/CommonMark.hs69
1 files changed, 63 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs
index a0ea9f3e8..9a67c8597 100644
--- a/src/Text/Pandoc/Readers/CommonMark.hs
+++ b/src/Text/Pandoc/Readers/CommonMark.hs
@@ -32,7 +32,7 @@ CommonMark is a strongly specified variant of Markdown: http://commonmark.org.
module Text.Pandoc.Readers.CommonMark (readCommonMark)
where
-import CMark
+import CMarkGFM
import Data.List (groupBy)
import Data.Text (Text, unpack)
import Text.Pandoc.Class (PandocMonad)
@@ -42,10 +42,10 @@ import Text.Pandoc.Options
-- | Parse a CommonMark formatted string into a 'Pandoc' structure.
readCommonMark :: PandocMonad m => ReaderOptions -> Text -> m Pandoc
readCommonMark opts s = return $
- nodeToPandoc $ commonmarkToNode opts' s
- where opts' = if extensionEnabled Ext_smart (readerExtensions opts)
- then [optSmart]
- else []
+ nodeToPandoc $ commonmarkToNode opts' exts s
+ where opts' = [optSmart | enabled Ext_smart]
+ exts = [extStrikethrough, extTable, extAutolink]
+ enabled x = extensionEnabled x (readerExtensions opts)
nodeToPandoc :: Node -> Pandoc
nodeToPandoc (Node _ DOCUMENT nodes) =
@@ -88,9 +88,64 @@ addBlock (Node _ (LIST listAttrs) nodes) =
delim = case listDelim listAttrs of
PERIOD_DELIM -> Period
PAREN_DELIM -> OneParen
-addBlock (Node _ ITEM _) = id -- handled in LIST
+addBlock (Node _ (TABLE alignments) nodes) = do
+ (Table [] aligns widths headers rows :)
+ where aligns = map fromTableCellAlignment alignments
+ fromTableCellAlignment NoAlignment = AlignDefault
+ fromTableCellAlignment LeftAligned = AlignLeft
+ fromTableCellAlignment RightAligned = AlignRight
+ fromTableCellAlignment CenterAligned = AlignCenter
+ widths = replicate numcols 0.0
+ numcols = if null rows'
+ then 0
+ else maximum $ map length rows'
+ rows' = map toRow $ filter isRow nodes
+ (headers, rows) = case rows' of
+ (h:rs) -> (h, rs)
+ [] -> ([], [])
+ isRow (Node _ TABLE_ROW _) = True
+ isRow _ = False
+ isCell (Node _ TABLE_CELL _) = True
+ isCell _ = False
+ toRow (Node _ TABLE_ROW ns) = map toCell $ filter isCell ns
+ toRow (Node _ t _) = error $ "toRow encountered non-row " ++ show t
+ toCell (Node _ TABLE_CELL []) = []
+ toCell (Node _ TABLE_CELL (n:ns))
+ | isBlockNode n = addBlocks (n:ns)
+ | otherwise = [Plain (addInlines (n:ns))]
+ toCell (Node _ t _) = error $ "toCell encountered non-cell " ++ show t
+addBlock (Node _ TABLE_ROW _) = id -- handled in TABLE
+addBlock (Node _ TABLE_CELL _) = id -- handled in TABLE
addBlock _ = id
+isBlockNode :: Node -> Bool
+isBlockNode (Node _ nodetype _) =
+ case nodetype of
+ DOCUMENT -> True
+ THEMATIC_BREAK -> True
+ PARAGRAPH -> True
+ BLOCK_QUOTE -> True
+ HTML_BLOCK _ -> True
+ CUSTOM_BLOCK _ _ -> True
+ CODE_BLOCK _ _ -> True
+ HEADING _ -> True
+ LIST _ -> True
+ ITEM -> True
+ TEXT _ -> False
+ SOFTBREAK -> False
+ LINEBREAK -> False
+ HTML_INLINE _ -> False
+ CUSTOM_INLINE _ _ -> False
+ CODE _ -> False
+ EMPH -> False
+ STRONG -> False
+ LINK _ _ -> False
+ IMAGE _ _ -> False
+ STRIKETHROUGH -> False
+ TABLE _ -> False
+ TABLE_ROW -> False
+ TABLE_CELL -> False
+
children :: Node -> [Node]
children (Node _ _ ns) = ns
@@ -121,6 +176,8 @@ addInline (Node _ EMPH nodes) =
(Emph (addInlines nodes) :)
addInline (Node _ STRONG nodes) =
(Strong (addInlines nodes) :)
+addInline (Node _ STRIKETHROUGH nodes) =
+ (Strikeout (addInlines nodes) :)
addInline (Node _ (LINK url title) nodes) =
(Link nullAttr (addInlines nodes) (unpack url, unpack title) :)
addInline (Node _ (IMAGE url title) nodes) =