我尝试使用 Markdown 编写器读取 Markdown 文件后重新生成该文件。我已经测试过了
`pandoc -s -t markdown input.md -o output.md`
生成一个带有 YAML 标头的文件。在源代码中我看到必须设置扩展名
Ext_yaml_metadata_block
。
不幸的是,在我的 Haskell 代码中,作者只生成内容,而不生成 YAML 标头,尽管我在读取和写入中设置了扩展名。我的代码中还需要什么或者还有什么问题?谢谢您的帮助!
我的最小但不太现实的 MWE:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module MarkdownYAMLquestion where
import qualified Text.Pandoc as Pandoc
import Text.Pandoc.Definition as Pandoc(Pandoc(..))
import Uniform.PandocImports(unPandocM)
import UniformBase(s2t,putIOwords, runErr, ErrIO, Text, showT)
smallMD :: Text
smallMD = s2t $ unlines
["---"
, "keywords: somewords"
, "showframe: False"
, "---"
, ""
, "some content text"
]
testyaml :: IO ()
-- a minimal example
testyaml = do
res <- runErr $ do
pan1 <- readMarkdown3 smallMD
putIOwords ["the pandoc", showT pan1] -- the YAML header is parsed!
mdRes <- writeToMarkdown3 pan1
putIOwords ["\n\nthe file reproduced\n", mdRes]
putIOwords ["testyaml end res", showT res]
writeToMarkdown3 :: Pandoc -> ErrIO Text
-- write with yaml header
writeToMarkdown3 pan1= unPandocM $ Pandoc.writeMarkdown
markdownWriterOptionsx pan1
markdownWriterOptionsx :: Pandoc.WriterOptions
markdownWriterOptionsx = Pandoc.def {Pandoc.writerExtensions = exts}
where
exts = mconcat [ Pandoc.extensionsFromList
[Pandoc.Ext_yaml_metadata_block]
]
readMarkdown3 :: Text -> ErrIO Pandoc
-- | reads the markdown text and produces a pandoc structure
-- the filename is only used for the error message
readMarkdown3 text1 = unPandocM $ Pandoc.readMarkdown markdownOptions text1
markdownOptions :: Pandoc.ReaderOptions
markdownOptions = Pandoc.def { Pandoc.readerExtensions = exts }
where
exts = mconcat
[ Pandoc.extensionsFromList
[ Pandoc.Ext_yaml_metadata_block
-- , Pandoc.Ext_fenced_code-block -- code blocks with ~
, Pandoc.Ext_backtick_code_blocks
, Pandoc.Ext_fenced_code_attributes -- eg for haskell code snippets
, Pandoc.Ext_auto_identifiers
-- , Pandoc.Ext_raw_html -- three extension give markdown_strict
, Pandoc.Ext_raw_tex --Allow raw TeX (other than math)
, Pandoc.Ext_latex_macros -- allow tex for math
, Pandoc.Ext_tex_math_dollars
, Pandoc.Ext_shortcut_reference_links
, Pandoc.Ext_spaced_reference_links
, Pandoc.Ext_footnotes -- all footnotes
, Pandoc.Ext_inline_notes
, Pandoc.Ext_citations -- <-- this is the important extension for bibTex
, Pandoc.Ext_implicit_figures -- a figure alone in a para will have a caption
, Pandoc.Ext_header_attributes -- for {.unnumbered}
, Pandoc.Ext_lists_without_preceding_blankline
, Pandoc.Ext_superscript -- start and closing ^
, Pandoc.Ext_subscript -- start and closing ~
-- , Pandoc.Ext_short_subsuperscripts -- only start ^ and ~
, Pandoc.Ext_strikeout -- require ~~ two! before and after
, Pandoc.Ext_smart -- Smart quotes, apostrophes, ellipses, dashes
]
, Pandoc.githubMarkdownExtensions
]
问题在于
markdownWriter
(特别是 pandocToMarkdown
中的 Text.Pandoc.Writers.Markdown
),它需要扩展 Pandoc.Ext_yaml_metadata_block
和 writerTemplate
,必须首先下载并编译它们。可以编译默认的 markdown
模板,然后加载到 writerTemplate
选项中。
使用此选项和扩展集,可以正确再现带有 YAML 块和内容的 Markdown 文件。在应用程序中,读取和写入的目的是更改元数据,从而拥有一个添加了默认值的 YAML 块。
所有更改都在
writeToMarkdown3
中,它替换了原始问题中的代码。
writeToMarkdown3 :: Pandoc -> ErrIO Text
-- write with yaml header
writeToMarkdown3 pan1 = do
template <- unPandocM $ getDefaultTemplate "markdown"
compTpl :: (Template Text) <- unPandocM $ compileDefaultTemplate "markdown"
unPandocM $ Pandoc.writeMarkdown
(markdownWriterOptions compTpl) pan1
markdownWriterOptions :: Template Text -> Pandoc.WriterOptions
markdownWriterOptions tpl =
Pandoc.def {Pandoc.writerTemplate = (Just ( tpl) )
, Pandoc.writerExtensions = exts}
where
exts = Pandoc.extensionsFromList
[Pandoc.Ext_yaml_metadata_block]