aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2020-12-09 21:05:40 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2020-12-10 08:59:55 -0800
commit8c9010864cd818031d7eff161a57459709751517 (patch)
treeb4ecb84312641884f5fb883a91b9311e2f94f0ba
parentb15191aece326b54db08c737808cf7a01e1df1ad (diff)
downloadpandoc-8c9010864cd818031d7eff161a57459709751517.tar.gz
Commonmark reader: refactor specFor, set input name to "".
-rw-r--r--src/Text/Pandoc/Readers/CommonMark.hs10
1 files changed, 8 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs
index c1773eaab..d32a38342 100644
--- a/src/Text/Pandoc/Readers/CommonMark.hs
+++ b/src/Text/Pandoc/Readers/CommonMark.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{- |
Module : Text.Pandoc.Readers.CommonMark
@@ -27,15 +28,20 @@ import Text.Pandoc.Options
import Text.Pandoc.Error
import Control.Monad.Except
import Data.Functor.Identity (runIdentity)
+import Data.Typeable
-- | Parse a CommonMark formatted string into a 'Pandoc' structure.
readCommonMark :: PandocMonad m => ReaderOptions -> Text -> m Pandoc
readCommonMark opts s = do
- let res = runIdentity $
- commonmarkWith (foldr ($) defaultSyntaxSpec exts) "input" s
+ let res = runIdentity $ commonmarkWith (specFor opts) "" s
case res of
Left err -> throwError $ PandocParsecError s err
Right (Cm bls :: Cm () Blocks) -> return $ B.doc bls
+
+specFor :: (Monad m, Typeable m, Typeable a,
+ Rangeable (Cm a Inlines), Rangeable (Cm a Blocks))
+ => ReaderOptions -> SyntaxSpec m (Cm a Inlines) (Cm a Blocks)
+specFor opts = foldr ($) defaultSyntaxSpec exts
where
exts = [ (hardLineBreaksSpec <>) | isEnabled Ext_hard_line_breaks opts ] ++
[ (smartPunctuationSpec <>) | isEnabled Ext_smart opts ] ++