diff --git a/pandoc.cabal b/pandoc.cabal index 3d0efb31b..b05e00ef2 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -218,7 +218,7 @@ Library random >= 1 && < 1.1, extensible-exceptions >= 0.1 && < 0.2, citeproc-hs >= 0.3.4 && < 0.4, - pandoc-types == 1.8.*, + pandoc-types == 1.9.*, json >= 0.4 && < 0.6, dlist >= 0.4 && < 0.6, tagsoup >= 0.12.5 && < 0.13, @@ -306,7 +306,7 @@ Executable pandoc random >= 1 && < 1.1, extensible-exceptions >= 0.1 && < 0.2, citeproc-hs >= 0.3.4 && < 0.4, - pandoc-types == 1.8.*, + pandoc-types == 1.9.*, json >= 0.4 && < 0.6, dlist >= 0.4 && < 0.6, tagsoup >= 0.12.5 && < 0.13, diff --git a/src/Tests/Arbitrary.hs b/src/Tests/Arbitrary.hs index 3ad90020d..986e3e4d5 100644 --- a/src/Tests/Arbitrary.hs +++ b/src/Tests/Arbitrary.hs @@ -1,5 +1,5 @@ {-# OPTIONS_GHC -fno-warn-orphans #-} -{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-} +{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, ScopedTypeVariables #-} -- provides Arbitrary instance for Pandoc types module Tests.Arbitrary () where @@ -22,10 +22,10 @@ arbAttr = do return (id',classes,keyvals) instance Arbitrary Inlines where - arbitrary = liftM fromList arbitrary + arbitrary = liftM (fromList :: [Inline] -> Inlines) arbitrary instance Arbitrary Blocks where - arbitrary = liftM fromList arbitrary + arbitrary = liftM (fromList :: [Block] -> Blocks) arbitrary instance Arbitrary Inline where arbitrary = resize 3 $ arbInline 2 diff --git a/src/Tests/Readers/LaTeX.hs b/src/Tests/Readers/LaTeX.hs index 6d28441f8..781867597 100644 --- a/src/Tests/Readers/LaTeX.hs +++ b/src/Tests/Readers/LaTeX.hs @@ -7,6 +7,7 @@ import Tests.Helpers import Tests.Arbitrary() import Text.Pandoc.Builder import Text.Pandoc +import Data.Monoid (mempty) latex :: String -> Pandoc latex = readLaTeX defaultParserState @@ -35,10 +36,10 @@ tests = [ testGroup "basic" "\\subsubsection{header}" =?> header 3 "header" , "emph" =: "\\section{text \\emph{emph}}" =?> - header 1 ("text" +++ space +++ emph "emph") + header 1 ("text" <> space <> emph "emph") , "link" =: "\\section{text \\href{/url}{link}}" =?> - header 1 ("text" +++ space +++ link "/url" "" "link") + header 1 ("text" <> space <> link "/url" "" "link") ] , testGroup "space and comments" @@ -67,13 +68,13 @@ baseCitation = Citation{ citationId = "item1" natbibCitations :: Test natbibCitations = testGroup "natbib" [ "citet" =: "\\citet{item1}" - =?> para (cite [baseCitation] empty) + =?> para (cite [baseCitation] mempty) , "suffix" =: "\\citet[p.~30]{item1}" =?> para - (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] empty) + (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] mempty) , "suffix long" =: "\\citet[p.~30, with suffix]{item1}" =?> para (cite [baseCitation{ citationSuffix = - toList $ text "p.\160\&30, with suffix" }] empty) + toList $ text "p.\160\&30, with suffix" }] mempty) , "multiple" =: "\\citeauthor{item1} \\citetext{\\citeyear{item1}; \\citeyear[p.~30]{item2}; \\citealp[see also][]{item3}}" =?> para (cite [baseCitation{ citationMode = AuthorInText } ,baseCitation{ citationMode = SuppressAuthor @@ -82,7 +83,7 @@ natbibCitations = testGroup "natbib" ,baseCitation{ citationId = "item3" , citationPrefix = [Str "see",Space,Str "also"] , citationMode = NormalCitation } - ] empty) + ] mempty) , "group" =: "\\citetext{\\citealp[see][p.~34--35]{item1}; \\citealp[also][chap. 3]{item3}}" =?> para (cite [baseCitation{ citationMode = NormalCitation , citationPrefix = [Str "see"] @@ -91,36 +92,36 @@ natbibCitations = testGroup "natbib" , citationId = "item3" , citationPrefix = [Str "also"] , citationSuffix = [Str "chap.",Space,Str "3"] } - ] empty) + ] mempty) , "suffix and locator" =: "\\citep[pp.~33, 35--37, and nowhere else]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation - , citationSuffix = [Str "pp.\160\&33,",Space,Str "35",EnDash,Str "37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] empty) + , citationSuffix = [Str "pp.\160\&33,",Space,Str "35",EnDash,Str "37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] mempty) , "suffix only" =: "\\citep[and nowhere else]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation - , citationSuffix = toList $ text "and nowhere else" }] empty) + , citationSuffix = toList $ text "and nowhere else" }] mempty) , "no author" =: "\\citeyearpar{item1}, and now Doe with a locator \\citeyearpar[p.~44]{item2}" - =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] empty +++ - text ", and now Doe with a locator " +++ + =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] mempty <> + text ", and now Doe with a locator " <> cite [baseCitation{ citationMode = SuppressAuthor , citationSuffix = [Str "p.\160\&44"] - , citationId = "item2" }] empty) + , citationId = "item2" }] mempty) , "markup" =: "\\citep[\\emph{see}][p. \\textbf{32}]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation , citationPrefix = [Emph [Str "see"]] , citationSuffix = [Str "p.",Space, - Strong [Str "32"]] }] empty) + Strong [Str "32"]] }] mempty) ] biblatexCitations :: Test biblatexCitations = testGroup "biblatex" [ "textcite" =: "\\textcite{item1}" - =?> para (cite [baseCitation] empty) + =?> para (cite [baseCitation] mempty) , "suffix" =: "\\textcite[p.~30]{item1}" =?> para - (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] empty) + (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] mempty) , "suffix long" =: "\\textcite[p.~30, with suffix]{item1}" =?> para (cite [baseCitation{ citationSuffix = - toList $ text "p.\160\&30, with suffix" }] empty) + toList $ text "p.\160\&30, with suffix" }] mempty) , "multiple" =: "\\textcites{item1}[p.~30]{item2}[see also][]{item3}" =?> para (cite [baseCitation{ citationMode = AuthorInText } ,baseCitation{ citationMode = NormalCitation @@ -129,7 +130,7 @@ biblatexCitations = testGroup "biblatex" ,baseCitation{ citationId = "item3" , citationPrefix = [Str "see",Space,Str "also"] , citationMode = NormalCitation } - ] empty) + ] mempty) , "group" =: "\\autocites[see][p.~34--35]{item1}[also][chap. 3]{item3}" =?> para (cite [baseCitation{ citationMode = NormalCitation , citationPrefix = [Str "see"] @@ -138,24 +139,24 @@ biblatexCitations = testGroup "biblatex" , citationId = "item3" , citationPrefix = [Str "also"] , citationSuffix = [Str "chap.",Space,Str "3"] } - ] empty) + ] mempty) , "suffix and locator" =: "\\autocite[pp.~33, 35--37, and nowhere else]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation - , citationSuffix = [Str "pp.\160\&33,",Space,Str "35",EnDash,Str "37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] empty) + , citationSuffix = [Str "pp.\160\&33,",Space,Str "35",EnDash,Str "37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] mempty) , "suffix only" =: "\\autocite[and nowhere else]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation - , citationSuffix = toList $ text "and nowhere else" }] empty) + , citationSuffix = toList $ text "and nowhere else" }] mempty) , "no author" =: "\\autocite*{item1}, and now Doe with a locator \\autocite*[p.~44]{item2}" - =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] empty +++ - text ", and now Doe with a locator " +++ + =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] mempty <> + text ", and now Doe with a locator " <> cite [baseCitation{ citationMode = SuppressAuthor , citationSuffix = [Str "p.\160\&44"] - , citationId = "item2" }] empty) + , citationId = "item2" }] mempty) , "markup" =: "\\autocite[\\emph{see}][p. \\textbf{32}]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation , citationPrefix = [Emph [Str "see"]] , citationSuffix = [Str "p.",Space, - Strong [Str "32"]] }] empty) + Strong [Str "32"]] }] mempty) , "parencite" =: "\\parencite{item1}" - =?> para (cite [baseCitation{ citationMode = NormalCitation }] empty) + =?> para (cite [baseCitation{ citationMode = NormalCitation }] mempty) ] diff --git a/src/Tests/Readers/Markdown.hs b/src/Tests/Readers/Markdown.hs index 61bd3a107..3c0cb9a3a 100644 --- a/src/Tests/Readers/Markdown.hs +++ b/src/Tests/Readers/Markdown.hs @@ -8,7 +8,6 @@ import Tests.Arbitrary() import Text.Pandoc.Builder -- import Text.Pandoc.Shared ( normalize ) import Text.Pandoc -import Data.Sequence (singleton) markdown :: String -> Pandoc markdown = readMarkdown defaultParserState{ stateStandalone = True } @@ -61,26 +60,26 @@ tests = [ testGroup "inline code" , testGroup "smart punctuation" [ test markdownSmart "quote before ellipses" ("'...hi'" - =?> para (singleQuoted (singleton Ellipses +++ "hi"))) + =?> para (singleQuoted (singleton Ellipses <> "hi"))) ] , testGroup "mixed emphasis and strong" [ "emph and strong emph alternating" =: "*xxx* ***xxx*** xxx\n*xxx* ***xxx*** xxx" - =?> para (emph "xxx" +++ space +++ strong (emph "xxx") +++ - space +++ "xxx" +++ space +++ - emph "xxx" +++ space +++ strong (emph "xxx") +++ - space +++ "xxx") + =?> para (emph "xxx" <> space <> strong (emph "xxx") <> + space <> "xxx" <> space <> + emph "xxx" <> space <> strong (emph "xxx") <> + space <> "xxx") , "emph with spaced strong" =: "*x **xx** x*" - =?> para (emph ("x" +++ space +++ strong "xx" +++ space +++ "x")) + =?> para (emph ("x" <> space <> strong "xx" <> space <> "x")) ] , testGroup "footnotes" [ "indent followed by newline and flush-left text" =: "[^1]\n\n[^1]: my note\n\n \nnot in note\n" - =?> para (note (para "my note")) +++ para "not in note" + =?> para (note (para "my note")) <> para "not in note" , "indent followed by newline and indented text" =: "[^1]\n\n[^1]: my note\n \n in note\n" - =?> para (note (para "my note" +++ para "in note")) + =?> para (note (para "my note" <> para "in note")) , "recursive note" =: "[^1]\n\n[^1]: See [^1]\n" =?> para (note (para "See [^1]")) @@ -90,9 +89,9 @@ tests = [ testGroup "inline code" "inverse bird tracks and html" $ "> a\n\n< b\n\n