\n"
              =?> codeBlockWith ("",["sourceCode","literate","haskell"],[]) "a"
                  <>
                  codeBlockWith ("",["sourceCode","haskell"],[]) "b"
                  <>
                  rawBlock "html" "
\n\n"
          ]
-- the round-trip properties frequently fail
--        , testGroup "round trip"
--          [ property "p_markdown_round_trip" p_markdown_round_trip
--          ]
        , testGroup "definition lists"
          [ "no blank space" =:
            "foo1\n  :  bar\n\nfoo2\n  : bar2\n  : bar3\n" =?>
            definitionList [ (text "foo1", [plain (text "bar")])
                           , (text "foo2", [plain (text "bar2"),
                                            plain (text "bar3")])
                           ]
          , "blank space before first def" =:
            "foo1\n\n  :  bar\n\nfoo2\n\n  : bar2\n  : bar3\n" =?>
            definitionList [ (text "foo1", [para (text "bar")])
                           , (text "foo2", [para (text "bar2"),
                                            plain (text "bar3")])
                           ]
          , "blank space before second def" =:
            "foo1\n  :  bar\n\nfoo2\n  : bar2\n\n  : bar3\n" =?>
            definitionList [ (text "foo1", [plain (text "bar")])
                           , (text "foo2", [plain (text "bar2"),
                                            para (text "bar3")])
                           ]
          , "laziness" =:
            "foo1\n  :  bar\nbaz\n  : bar2\n" =?>
            definitionList [ (text "foo1", [plain (text "bar" <>
                                                 softbreak <> text "baz"),
                                            plain (text "bar2")])
                           ]
          , "no blank space before first of two paragraphs" =:
            "foo1\n  : bar\n\n    baz\n" =?>
            definitionList [ (text "foo1", [para (text "bar") <>
                                            para (text "baz")])
                           ]
          , "first line not indented" =:
            "foo\n: bar\n" =?>
            definitionList [ (text "foo", [plain (text "bar")]) ]
          , "list in definition" =:
            "foo\n:   - bar\n" =?>
            definitionList [ (text "foo", [bulletList [plain (text "bar")]]) ]
          , "in div" =:
            "
foo\n:   - bar\n
" =?>
            divWith nullAttr (definitionList
              [ (text "foo", [bulletList [plain (text "bar")]]) ])
          ]
        , testGroup "+compact_definition_lists"
          [ test markdownCDL "basic compact list" $
            "foo1\n:   bar\n    baz\nfoo2\n:   bar2\n" =?>
            definitionList [ (text "foo1", [plain (text "bar" <> softbreak <>
                                                     text "baz")])
                           , (text "foo2", [plain (text "bar2")])
                           ]
          ]
        , testGroup "lists"
          [ "issue #1154" =:
              " -  
\n    first div breaks\n    
\n\n    
\n\n    
\n    with this div too.\n    
\n"
              =?> bulletList [divWith nullAttr (para $ text "first div breaks") <>
                              rawBlock "html" "
" <>
                              divWith nullAttr (para $ text "with this div too.")]
          , test markdownGH "issue #1636" $
              unlines [ "* a"
                      , "* b"
                      , "* c"
                      , "    * d" ]
              =?>
              bulletList [ plain "a"
                         , plain "b"
                         , plain "c" <> bulletList [plain "d"] ]
          ]
        , testGroup "entities"
          [ "character references" =:
            "〈 ö" =?> para (text "\10216 ö")
          , "numeric" =:
            ",DD" =?> para (text ",DD")
          , "in link title" =:
            "[link](/url \"title 〈 ö ,\")" =?>
               para (link "/url" "title \10216 ö ," (text "link"))
          ]
        , testGroup "citations"
          [ "simple" =:
            "@item1" =?> para (cite [
                Citation{ citationId      = "item1"
                        , citationPrefix  = []
                        , citationSuffix  = []
                        , citationMode    = AuthorInText
                        , citationNoteNum = 0
                        , citationHash    = 0
                        }
                ] "@item1")
          , "key starts with digit" =:
            "@1657:huyghens" =?> para (cite [
                Citation{ citationId      = "1657:huyghens"
                        , citationPrefix  = []
                        , citationSuffix  = []
                        , citationMode    = AuthorInText
                        , citationNoteNum = 0
                        , citationHash    = 0
                        }
                ] "@1657:huyghens")
          ]
        , let citation = cite [Citation "cita" [] [] AuthorInText 0 0] (str "@cita")
          in testGroup "footnote/link following citation" -- issue #2083
          [ "footnote" =:
              unlines [ "@cita[^note]"
                      , ""
                      , "[^note]: note" ] =?>
              para (
                citation <> note (para $ str "note")
              )
          , "normal link" =:
              "@cita [link](http://www.com)" =?>
              para (
                citation <> space <> link "http://www.com" "" (str "link")
              )
          , "reference link" =:
              unlines [ "@cita [link][link]"
                      , ""
                      , "[link]: http://www.com" ] =?>
              para (
                citation <> space <> link "http://www.com" "" (str "link")
              )
          , "short reference link" =:
              unlines [ "@cita [link]"
                      , ""
                      , "[link]: http://www.com" ] =?>
              para (
                citation <> space <> link "http://www.com" "" (str "link")
              )
          , "implicit header link" =:
              unlines [ "# Header"
                      , "@cita [Header]" ] =?>
              headerWith ("header",[],[]) 1 (str "Header") <> para (
                citation <> space <> link "#header" "" (str "Header")
              )
          , "regular citation" =:
              "@cita [foo]" =?>
              para (
                cite [Citation "cita" [] [Str "foo"] AuthorInText 0 0]
                  (str "@cita" <> space <> str "[foo]")
              )
          ]
        ]