aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-09-22 10:15:42 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2019-09-22 10:38:15 -0700
commitb64410ff9ce64d6a2c7e09b43694b6f4245f9129 (patch)
tree85c567dabf7f3fd5da679bf7b2e06eacf585c129 /src/Text/Pandoc/Readers
parentfc443712d311270af8f7698275849be446469836 (diff)
downloadpandoc-b64410ff9ce64d6a2c7e09b43694b6f4245f9129.tar.gz
Use HsYAML-0.2.0.0
Most of this is due to @vijayphoenix (#5704), but it needed some revisions to integrate with current master, and to use the released HsYAML. Closes #5704.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs23
1 files changed, 12 insertions, 11 deletions
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index e626321e6..316dfc9d0 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -28,6 +28,7 @@ import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.YAML as YAML
+import qualified Data.YAML.Event as YE
import System.FilePath (addExtension, takeExtension)
import Text.HTML.TagSoup
import Text.Pandoc.Builder (Blocks, Inlines)
@@ -244,22 +245,22 @@ yamlBsToMeta :: PandocMonad m => BS.ByteString -> MarkdownParser m (F Meta)
yamlBsToMeta bstr = do
pos <- getPosition
case YAML.decodeNode' YAML.failsafeSchemaResolver False False bstr of
- Right ((YAML.Doc (YAML.Mapping _ o)):_) -> (fmap Meta) <$> yamlMap o
+ Right ((YAML.Doc (YAML.Mapping _ _ o)):_) -> (fmap Meta) <$> yamlMap o
Right [] -> return . return $ mempty
- Right [YAML.Doc (YAML.Scalar YAML.SNull)] -> return . return $ mempty
+ Right [YAML.Doc (YAML.Scalar _ YAML.SNull)] -> return . return $ mempty
Right _ -> do
logMessage $
CouldNotParseYamlMetadata "not an object"
pos
return . return $ mempty
- Left err' -> do
+ Left (_pos, err') -> do
logMessage $ CouldNotParseYamlMetadata
err' pos
return . return $ mempty
-nodeToKey :: Monad m => YAML.Node -> m Text
-nodeToKey (YAML.Scalar (YAML.SStr t)) = return t
-nodeToKey (YAML.Scalar (YAML.SUnknown _ t)) = return t
+nodeToKey :: Monad m => YAML.Node YE.Pos -> m Text
+nodeToKey (YAML.Scalar _ (YAML.SStr t)) = return t
+nodeToKey (YAML.Scalar _ (YAML.SUnknown _ t)) = return t
nodeToKey _ = fail "Non-string key in YAML mapping"
toMetaValue :: PandocMonad m
@@ -291,8 +292,8 @@ checkBoolean t =
else Nothing
yamlToMetaValue :: PandocMonad m
- => YAML.Node -> MarkdownParser m (F MetaValue)
-yamlToMetaValue (YAML.Scalar x) =
+ => YAML.Node YE.Pos-> MarkdownParser m (F MetaValue)
+yamlToMetaValue (YAML.Scalar _ x) =
case x of
YAML.SStr t -> toMetaValue t
YAML.SBool b -> return $ return $ MetaBool b
@@ -303,16 +304,16 @@ yamlToMetaValue (YAML.Scalar x) =
Just b -> return $ return $ MetaBool b
Nothing -> toMetaValue t
YAML.SNull -> return $ return $ MetaString ""
-yamlToMetaValue (YAML.Sequence _ xs) = do
+yamlToMetaValue (YAML.Sequence _ _ xs) = do
xs' <- mapM yamlToMetaValue xs
return $ do
xs'' <- sequence xs'
return $ B.toMetaValue xs''
-yamlToMetaValue (YAML.Mapping _ o) = fmap B.toMetaValue <$> yamlMap o
+yamlToMetaValue (YAML.Mapping _ _ o) = fmap B.toMetaValue <$> yamlMap o
yamlToMetaValue _ = return $ return $ MetaString ""
yamlMap :: PandocMonad m
- => M.Map YAML.Node YAML.Node
+ => M.Map (YAML.Node YE.Pos) (YAML.Node YE.Pos)
-> MarkdownParser m (F (M.Map String MetaValue))
yamlMap o = do
kvs <- forM (M.toList o) $ \(key, v) -> do