category feedMarkdownSpecialised needseditdelete







Markdown is a popular text markup format, used on Stackoverflow, Github, and in many other places (including this guide). Markdown doesn't have a strict specification, and all libraries implement it differently; to see how listed libraries (well, some of them) work on various outputs, use Babelmark.

Code highlighting

Unless noted otherwise, all libraries support code blocks with attributes, which makes code highlighting possible if used like this:

~~~ haskell
import Control.Monad
~~~

Some libraries (e.g. cheapskate) actually let you highlight the code in generated HTML, while others simply use the name of the language as a <div> class (and then you have to use a library like highlight.js to highlight code blocks at the client side).

Recommendations

pandoc is very often used as a standalone Markdown converter (in Hakyll, for instance). It's very customisable and has tons of features. However, it's slower than other libraries, and shouldn't be used on untrustworthy input (because there are some inputs that take exponential time).

cheapskate is a smaller library, is often used for sites, and has a small ecosystem around it. cmark is another small library that implements a standardised version of Markdown – it's newer and thus used less often, but likely to become the standard Markdown library in the future, and so you might just as well start using it now. Anyway, both cheapskate and cmark are fine.

markdown can actually be fine too. It suffers from the same problem as pandoc (takes exponential time on some inputs), but it has a more customisable parser than cheapskate or cmark and sometimes it's useful.

If you want non-HTML output (e.g. LaTeX), then cmark and pandoc are your only options. If you want a really fast library, use cmark. If you want to modify the parser to suit your own needs, fork cheapskate or markdown.

edit description
or press Ctrl+Enter to savemarkdown supported
#
other
move item up move item down edit item info delete item
Summary edit summary

A document converter that supports about 15 input formats (including Markdown). Has the most feature-rich Markdown dialect and can convert to the most number of formats. Not recommended for web (when Markdown is written by users and not by you), but very good for blogs, articles, slides/presentations, generating documentation, and so on.

Summary quit editing summary
Prosedit prosquit editing pros
  • Can convert to the most number of formats (including EPUB, docx, ODT, LaTeX, and other markup formats like Haddock, DocBook, MediaWiki markup, etc).
    move trait up move trait down edit trait delete trait
  • Has the most number of features – superscript/subscript/strikethrough, footnotes, tables, definition lists, math rendering, citations, code highlighting, table of contents generation, and so on.
    move trait up move trait down edit trait delete trait
  • The implementation doesn't use advanced Haskell features and can easily be modified (if you want to add features to your dialect of Markdown).
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Consedit consquit editing cons
  • Quite heavy if the only thing you want is rendering Markdown to HTML.
    move trait up move trait down edit trait delete trait
  • Doesn't handle pathological inputs well (e.g. parsing [[[[[[[[[[[[[[[[[ foo ]]]]]]]]]]]]]]]]] takes 40s on my machine).
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Ecosystemedit ecosystem
Ecosystemquit editing ecosystemor press Ctrl+Enter to savemarkdown supported
Notes
collapse notesedit notes

Links

Imports

import Text.Pandoc

Usage

Markdown to HTML

Here's a program that reads Markdown input and outputs rendered HTML:

import Text.Pandoc

main = do
  s <- getContents
  parsed <- case readMarkdown def s of
    Left  err -> error (show err)
    Right doc -> return doc
  putStrLn (writeHtmlString def parsed)

We might also generate a full HTML document instead of simply some markup. To do that, we'll use writerStandalone = True and load a template:

import Text.Pandoc

main = do
  s <- getContents
  template <- either (error . show) id <$>
                getDefaultTemplate Nothing "html"
  parsed <- case readMarkdown def s of
    Left  err -> error (show err)
    Right doc -> return doc
  let writerOpts = def {
        writerStandalone = True,
        writerTemplate   = template }
  putStr (writeHtmlString writerOpts parsed)

Working with parsed Markdown

For transforming Markdown, use functions from Text.Pandoc.Walk (from pandoc-types). There are some examples available in the docs.

You can construct your own documents by using functions from Text.Pandoc.Builder.

There are some helper functions (such as stringify or capitalize) in Text.Pandoc.Shared.

collapse notesedit notes
#
other
move item up move item down edit item info delete item
Summary edit summary

A lightweight Markdown library from the author of Pandoc, implementing the CommonMark standard (which is just a more precisely specified version of Markdown). Can parse Markdown and convert it to various formats (including HTML).

Binds to a C library (libcmark), but doesn't require it to be installed – the sources are shipped with the Haskell package.

Summary quit editing summary
Prosedit prosquit editing pros
  • Very fast (the author's benchmarks: 82× faster than cheapskate, 59× faster than markdown, 105× faster than pandoc, 3× faster than discount).
    move trait up move trait down edit trait delete trait
  • Can deal with any input, including garbage, with linear performance. (Some Markdown parsers have quadratic complexity on some inputs, which gives an attacker an opportunity to slow down your site.)
    move trait up move trait down edit trait delete trait
  • Can render to several formats: apart from HTML, it also supports LaTeX, groff man, and a custom XML format.
    move trait up move trait down edit trait delete trait
  • The only library here that lets you get position info for parsed blocks.
    move trait up move trait down edit trait delete trait
  • Has a sibling Javascript library that implements the same specification (so that the results of client-side and server-side rendering would fully match).
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Consedit consquit editing cons
  • Can't automatically recognise links (i.e. if you write go to https://google.com, the link won't be highlighted).
    move trait up move trait down edit trait delete trait
  • Doesn't sanitize HTML output by default (you have to use xss-sanitize if you want that).
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Ecosystemedit ecosystem

cmark-highlight (highlights code blocks)

Ecosystemquit editing ecosystemor press Ctrl+Enter to savemarkdown supported
Notes
collapse notesedit notes

Links

Imports

import CMark

Usage

In the simplest case you just use commonmarkToHtml (or commonmarkToLaTeX, etc) which takes text, parses it, and renders it. You can also parse Markdown with commonmarkToNode, transform it, and then render with nodeToHtml.

collapse notesedit notes
#
other
move item up move item down edit item info delete item
Summary edit summary

Another lightweight Markdown library from the author of Pandoc. Unlike cmark, it's implemented in pure Haskell. Can parse Markdown and convert it to HTML.

Summary quit editing summary
Prosedit prosquit editing pros
  • Can deal with any input with linear performance.
    move trait up move trait down edit trait delete trait
  • HTML output is sanitized by default (to protect against XSS attacks).
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Consedit consquit editing cons

    press Ctrl+Enter or Enter to addmarkdown supportededit off
    Ecosystemedit ecosystem

    cheapskate-terminal (renders to console), cheapskate-highlight (highlights code blocks), cheapskate-lucid

    Ecosystemquit editing ecosystemor press Ctrl+Enter to savemarkdown supported
    Notes
    collapse notesedit notes

    Imports

    import Cheapskate
    import Cheapskate.Html

    And these are imports from blaze-html that you'll need if you want to render HTML:

    import Text.Blaze.Html (Html)
    
    -- for rendering to ByteString
    import Text.Blaze.Html.Renderer.Utf8 (renderHtml)
    
    -- or for rendering to Text
    import Text.Blaze.Html.Renderer.Text (renderHtml)

    Usage

    First of all, you should know what options cheapskate will use. By default, sanitize and allowRawHtml are enabled:

    data Options = Options {
      sanitize           :: Bool,   -- ^ Sanitize raw HTML, link/image attributes
      allowRawHtml       :: Bool,   -- ^ Allow raw HTML (if false it gets escaped)
      preserveHardBreaks :: Bool,   -- ^ Preserve hard line breaks in the source
      debug              :: Bool }  -- ^ Print container structure for debugging

    There are 2 functions we'll primarily use: markdown :: Options -> Text -> Doc parses Markdown, and renderDoc :: Doc -> Html renders it to HTML. Doc is a type that consists of Blocks, and blocks usually have Inlines inside, or other blocks. You can traverse and transform those structures manually, or you can use walk and friends.

    Rendering Markdown to HTML

    Here's a program that reads Markdown input, outputs rendered HTML, and doesn't allow raw HTML. renderHtml is a function that takes Html and produces Text from it, and it comes from blaze-html.

    import Cheapskate
    import Cheapskate.Html
    
    import Text.Blaze.Html (Html)
    import Text.Blaze.Html.Renderer.Text (renderHtml)
    
    import qualified Data.Text.Lazy    as TL
    import qualified Data.Text.Lazy.IO as TL
    
    -- Type signatures are added for clarity.
    main = do
      md <- TL.getContents
      let parsed :: Doc
          parsed = markdown def{allowRawHtml = False} (TL.toStrict md)
      let rendered :: Html
          rendered = renderDoc parsed
      TL.putStr (renderHtml rendered)

    If you were outputting it to a file, you'd want to use renderHtml from Text.Blaze.Html.Renderer.Utf8 instead. And if you want pretty indented HTML, use Text.Blaze.Html.Renderer.Pretty.

    Working with parsed Markdown

    The Inline and Block types are defined like this:

    data Block = Para Inlines
               | Header Int Inlines
               | Blockquote Blocks
               | List Bool ListType [Blocks]
               | CodeBlock CodeAttr Text
               | HtmlBlock Text
               | HRule
    
    data Inline = Str Text
                | Space
                | SoftBreak
                | LineBreak
                | Emph Inlines
                | Strong Inlines
                | Code Text
                | Link Inlines Text {- URL -} Text {- title -}
                | Image Inlines Text {- URL -} Text {- title -}
                | Entity Text
                | RawHtml Text

    Inlines is defined as Seq Inline, BlocksSeq Block. You can use for_ or fmap if you want to traverse them.

    There are two functions for traversing Markdown – walk and walkM. The general signature is walk :: (Data a, Data b) => (a -> a) -> b -> b, so it can traverse all Inlines in a Doc, or all Blocks in a Block, or any other combination. walkM is more powerful, as it allows monadic functions – you can use it if your transforming function uses IO, for instance, or you can do gathering with it. For instance, here's how to turn some Markdown into plain text, using the Writer monad:

    -- Using a DList Text instead of Text might be faster
    
    stringify :: Inlines -> Text
    stringify = execWriter . walkM go
      where
        go :: Inline -> Writer Text Inline
        go i = do
          case i of
            Str x     -> tell x
            Code x    -> tell x
            Space     -> tell " "
            SoftBreak -> tell " "
            LineBreak -> tell " "
            -- We should've handled the case for Entity as well
            -- (by converting it to a character), but let's ignore it
            -- for the sake of simplicity.
            _other    -> return ()
          return i

    Highlighting code blocks

    To highlight code in blocks, use cheapskate-highlight:

    import Cheapskate.Highlight

    In the basic case you can just apply highlightDoc to the parsed Doc before rendering it. You'd also have to include CSS into your page – you can get the CSS to include by applying styleToCss :: Style -> String to one of the styles defined in Text.Highlighting.Kate.Styles (reexported by Cheapskate.Highlight), for instance pygments.

    collapse notesedit notes
    #
    markdown (Hackage)
    other
    move item up move item down edit item info delete item
    Summary edit summary

    A library from Michael Snoyman (the author of Yesod). Can parse Markdown and convert it to HTML. Has additional features that make it good for publishing (you can customise the parser, for instance) but simultaneously can get stuck on some inputs and that's pretty bad (unless you explicitly implement a timeout or something like that).

    Summary quit editing summary
    Prosedit prosquit editing pros
    • Sanitizes input by default.
      move trait up move trait down edit trait delete trait
    • The parser can be customised to add new kinds of fencing in addition to ``` and ~~~ – for instance, @@@. Moreover, the contents can be parsed as Markdown as well (so you could set it up so that e.g. @@@ would mean “spoiler” or “important note”).
      move trait up move trait down edit trait delete trait
    • Has an option for adding target=_blank to all links so that they'd open in new tabs.
      move trait up move trait down edit trait delete trait

    press Ctrl+Enter or Enter to addmarkdown supportededit off
    Consedit consquit editing cons
    • Doesn't handle pathological inputs well (e.g. parsing [[[[[[[[[[[[[[[[[[[[[[[ foo ]]]]]]]]]]]]]]]]]]]]]]] takes 46s on my machine), which makes it unsuitable for e.g. sites with user-submitted content.
      move trait up move trait down edit trait delete trait

    press Ctrl+Enter or Enter to addmarkdown supportededit off
    Ecosystemquit editing ecosystemor press Ctrl+Enter to savemarkdown supported
    Notes
    collapse notesedit notes

    <notes are empty>

    add something!

    #
    other
    move item up move item down edit item info delete item
    Summary edit summary

    Bindings to Github's (former) Markdown library, sundown. (The sources are bundled with the package, so the library doesn't need to be installed separately.) Can convert Markdown to HTML, but doesn't give access to parsed Markdown.

    Summary quit editing summary
    Prosedit prosquit editing pros
    • Very fast (since it's a C library). Can deal with any input with linear performance, and has been battle-tested extensively (since it's been used on Github).
      move trait up move trait down edit trait delete trait
    • Supports automatic link recognition.
      move trait up move trait down edit trait delete trait
    • Has support for tables, superscripts, strikethrough.
      move trait up move trait down edit trait delete trait
    • Can generate a table of contents.
      move trait up move trait down edit trait delete trait

    press Ctrl+Enter or Enter to addmarkdown supportededit off
    Consedit consquit editing cons
    • The underlying library (sundown) has been deprecated.
      move trait up move trait down edit trait delete trait
    • Doesn't provide a Haskell type for parsed Markdown (so you can't inspect or modify it).
      move trait up move trait down edit trait delete trait

    press Ctrl+Enter or Enter to addmarkdown supportededit off
    Ecosystemedit ecosystem
    Ecosystemquit editing ecosystemor press Ctrl+Enter to savemarkdown supported
    Notes
    collapse notesedit notes

    <notes are empty>

    add something!

    #
    other
    move item up move item down edit item info delete item
    Summary edit summary

    Bindings to another Markdown library, discount. Can convert Markdown to HTML, but doesn't give access to parsed Markdown.

    The documentation for Markdown extensions it supports can be found here.

    Summary quit editing summary
    Prosedit prosquit editing pros
    • Supports tables, superscripts, strikethrough, footnotes.
      move trait up move trait down edit trait delete trait
    • Has some non-standard extensions too: definition lists, paragraph centering, specifying image sizes, and styling text (e.g. [foo](class:bar) would wrap “foo” into a <span> tag with class="bar" and then you could apply CSS styling to it).
      move trait up move trait down edit trait delete trait
    • Seems to be able to deal with any input with linear performance (since it renders this stress-test just fine).
      move trait up move trait down edit trait delete trait
    • Supports math in pages (with MathJax).
      move trait up move trait down edit trait delete trait
    • Can generate table of contents.
      move trait up move trait down edit trait delete trait

    press Ctrl+Enter or Enter to addmarkdown supportededit off
    Consedit consquit editing cons
    • The library has to be installed separately.
      move trait up move trait down edit trait delete trait
    • Its dialect of Markdown is rather non-standard.
      move trait up move trait down edit trait delete trait
    • Doesn't have code blocks with attributes (so, no code highlighting).
      move trait up move trait down edit trait delete trait
    • Doesn't provide a Haskell type for parsed Markdown (so you can't inspect or modify it).
      move trait up move trait down edit trait delete trait

    press Ctrl+Enter or Enter to addmarkdown supportededit off
    Ecosystemedit ecosystem
    Ecosystemquit editing ecosystemor press Ctrl+Enter to savemarkdown supported
    Notes
    collapse notesedit notes

    <notes are empty>

    add something!