2013-01-23 17:47:43 +01:00
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2019-02-04 22:52:31 +01:00
|
|
|
|
{- |
|
|
|
|
|
Module : Tests.Readers.Markdown
|
2022-01-01 20:02:31 +01:00
|
|
|
|
Copyright : © 2006-2022 John MacFarlane
|
2019-02-04 22:52:31 +01:00
|
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
|
Stability : alpha
|
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
|
|
Tests for the Markdown reader.
|
|
|
|
|
-}
|
2011-01-27 07:09:09 +01:00
|
|
|
|
module Tests.Readers.Markdown (tests) where
|
|
|
|
|
|
2017-06-10 18:26:44 +02:00
|
|
|
|
import Data.Text (Text, unpack)
|
|
|
|
|
import qualified Data.Text as T
|
2017-03-14 17:05:36 +01:00
|
|
|
|
import Test.Tasty
|
2011-01-27 07:09:09 +01:00
|
|
|
|
import Tests.Helpers
|
|
|
|
|
import Text.Pandoc
|
2017-03-04 13:03:41 +01:00
|
|
|
|
import Text.Pandoc.Arbitrary ()
|
|
|
|
|
import Text.Pandoc.Builder
|
2011-01-27 07:09:09 +01:00
|
|
|
|
|
2017-06-10 18:26:44 +02:00
|
|
|
|
markdown :: Text -> Pandoc
|
2017-01-15 20:42:00 +01:00
|
|
|
|
markdown = purely $ readMarkdown def { readerExtensions =
|
|
|
|
|
disableExtension Ext_smart pandocExtensions }
|
2011-01-27 07:09:09 +01:00
|
|
|
|
|
2017-06-10 18:26:44 +02:00
|
|
|
|
markdownSmart :: Text -> Pandoc
|
2017-01-14 18:27:06 +01:00
|
|
|
|
markdownSmart = purely $ readMarkdown def { readerExtensions =
|
2017-01-15 20:42:00 +01:00
|
|
|
|
enableExtension Ext_smart pandocExtensions }
|
2011-07-26 08:49:45 +02:00
|
|
|
|
|
2017-06-10 18:26:44 +02:00
|
|
|
|
markdownCDL :: Text -> Pandoc
|
2017-01-14 13:06:27 +01:00
|
|
|
|
markdownCDL = purely $ readMarkdown def { readerExtensions = enableExtension
|
2017-01-15 20:42:00 +01:00
|
|
|
|
Ext_compact_definition_lists pandocExtensions }
|
2014-07-21 01:33:59 +02:00
|
|
|
|
|
2017-06-10 18:26:44 +02:00
|
|
|
|
markdownGH :: Text -> Pandoc
|
2017-01-15 20:42:00 +01:00
|
|
|
|
markdownGH = purely $ readMarkdown def {
|
|
|
|
|
readerExtensions = githubMarkdownExtensions }
|
2014-09-26 11:32:08 +02:00
|
|
|
|
|
2021-08-16 06:57:57 +02:00
|
|
|
|
markdownMMD :: Text -> Pandoc
|
|
|
|
|
markdownMMD = purely $ readMarkdown def {
|
|
|
|
|
readerExtensions = multimarkdownExtensions }
|
2012-02-05 22:23:06 +01:00
|
|
|
|
infix 4 =:
|
2011-01-27 07:09:09 +01:00
|
|
|
|
(=:) :: ToString c
|
2017-06-10 18:26:44 +02:00
|
|
|
|
=> String -> (Text, c) -> TestTree
|
2011-01-27 07:09:09 +01:00
|
|
|
|
(=:) = test markdown
|
|
|
|
|
|
2017-06-10 18:26:44 +02:00
|
|
|
|
testBareLink :: (Text, Inlines) -> TestTree
|
2013-01-15 21:28:31 +01:00
|
|
|
|
testBareLink (inp, ils) =
|
2016-12-01 18:47:05 +01:00
|
|
|
|
test (purely $ readMarkdown def{ readerExtensions =
|
2017-01-14 13:06:27 +01:00
|
|
|
|
extensionsFromList [Ext_autolink_bare_uris, Ext_raw_html] })
|
2017-06-10 18:26:44 +02:00
|
|
|
|
(unpack inp) (inp, doc $ para ils)
|
2013-01-15 21:28:31 +01:00
|
|
|
|
|
|
|
|
|
autolink :: String -> Inlines
|
2018-09-19 23:49:46 +02:00
|
|
|
|
autolink = autolinkWith ("",["uri"],[])
|
2016-10-26 12:18:58 +02:00
|
|
|
|
|
|
|
|
|
autolinkWith :: Attr -> String -> Inlines
|
Switch to new pandoc-types and use Text instead of String [API change].
PR #5884.
+ Use pandoc-types 1.20 and texmath 0.12.
+ Text is now used instead of String, with a few exceptions.
+ In the MediaBag module, some of the types using Strings
were switched to use FilePath instead (not Text).
+ In the Parsing module, new parsers `manyChar`, `many1Char`,
`manyTillChar`, `many1TillChar`, `many1Till`, `manyUntil`,
`mantyUntilChar` have been added: these are like their
unsuffixed counterparts but pack some or all of their output.
+ `glob` in Text.Pandoc.Class still takes String since it seems
to be intended as an interface to Glob, which uses strings.
It seems to be used only once in the package, in the EPUB writer,
so that is not hard to change.
2019-11-04 22:12:37 +01:00
|
|
|
|
autolinkWith attr s = linkWith attr s' "" (str s')
|
|
|
|
|
where s' = T.pack s
|
2013-01-15 21:28:31 +01:00
|
|
|
|
|
2017-06-10 18:26:44 +02:00
|
|
|
|
bareLinkTests :: [(Text, Inlines)]
|
2013-01-15 21:28:31 +01:00
|
|
|
|
bareLinkTests =
|
|
|
|
|
[ ("http://google.com is a search engine.",
|
|
|
|
|
autolink "http://google.com" <> " is a search engine.")
|
2013-09-02 00:18:56 +02:00
|
|
|
|
, ("<a href=\"http://foo.bar.baz\">http://foo.bar.baz</a>",
|
|
|
|
|
rawInline "html" "<a href=\"http://foo.bar.baz\">" <>
|
|
|
|
|
"http://foo.bar.baz" <> rawInline "html" "</a>")
|
2013-01-15 21:28:31 +01:00
|
|
|
|
, ("Try this query: http://google.com?search=fish&time=hour.",
|
|
|
|
|
"Try this query: " <> autolink "http://google.com?search=fish&time=hour" <> ".")
|
|
|
|
|
, ("HTTPS://GOOGLE.COM,",
|
|
|
|
|
autolink "HTTPS://GOOGLE.COM" <> ",")
|
|
|
|
|
, ("http://el.wikipedia.org/wiki/Τεχνολογία,",
|
|
|
|
|
autolink "http://el.wikipedia.org/wiki/Τεχνολογία" <> ",")
|
|
|
|
|
, ("doi:10.1000/182,",
|
|
|
|
|
autolink "doi:10.1000/182" <> ",")
|
|
|
|
|
, ("git://github.com/foo/bar.git,",
|
|
|
|
|
autolink "git://github.com/foo/bar.git" <> ",")
|
|
|
|
|
, ("file:///Users/joe/joe.txt, and",
|
|
|
|
|
autolink "file:///Users/joe/joe.txt" <> ", and")
|
|
|
|
|
, ("mailto:someone@somedomain.com.",
|
|
|
|
|
autolink "mailto:someone@somedomain.com" <> ".")
|
|
|
|
|
, ("Use http: this is not a link!",
|
|
|
|
|
"Use http: this is not a link!")
|
|
|
|
|
, ("(http://google.com).",
|
|
|
|
|
"(" <> autolink "http://google.com" <> ").")
|
|
|
|
|
, ("http://en.wikipedia.org/wiki/Sprite_(computer_graphics)",
|
|
|
|
|
autolink "http://en.wikipedia.org/wiki/Sprite_(computer_graphics)")
|
|
|
|
|
, ("http://en.wikipedia.org/wiki/Sprite_[computer_graphics]",
|
2018-09-19 23:49:46 +02:00
|
|
|
|
linkWith ("",["uri"],[])
|
|
|
|
|
"http://en.wikipedia.org/wiki/Sprite_%5Bcomputer_graphics%5D" ""
|
Percent-encode more special characters in URLs.
HTML, LaTeX writers adjusted.
The special characters are '<','>','|','"','{','}','[',']','^', '`'.
Closes #1640, #2377.
2015-10-12 02:06:26 +02:00
|
|
|
|
(str "http://en.wikipedia.org/wiki/Sprite_[computer_graphics]"))
|
2013-01-15 21:28:31 +01:00
|
|
|
|
, ("http://en.wikipedia.org/wiki/Sprite_{computer_graphics}",
|
2018-09-19 23:49:46 +02:00
|
|
|
|
linkWith ("",["uri"],[])
|
|
|
|
|
"http://en.wikipedia.org/wiki/Sprite_%7Bcomputer_graphics%7D" ""
|
Percent-encode more special characters in URLs.
HTML, LaTeX writers adjusted.
The special characters are '<','>','|','"','{','}','[',']','^', '`'.
Closes #1640, #2377.
2015-10-12 02:06:26 +02:00
|
|
|
|
(str "http://en.wikipedia.org/wiki/Sprite_{computer_graphics}"))
|
2013-01-15 21:28:31 +01:00
|
|
|
|
, ("http://example.com/Notification_Center-GitHub-20101108-140050.jpg",
|
|
|
|
|
autolink "http://example.com/Notification_Center-GitHub-20101108-140050.jpg")
|
|
|
|
|
, ("https://github.com/github/hubot/blob/master/scripts/cream.js#L20-20",
|
|
|
|
|
autolink "https://github.com/github/hubot/blob/master/scripts/cream.js#L20-20")
|
|
|
|
|
, ("http://www.rubyonrails.com",
|
|
|
|
|
autolink "http://www.rubyonrails.com")
|
|
|
|
|
, ("http://www.rubyonrails.com:80",
|
|
|
|
|
autolink "http://www.rubyonrails.com:80")
|
|
|
|
|
, ("http://www.rubyonrails.com/~minam",
|
|
|
|
|
autolink "http://www.rubyonrails.com/~minam")
|
|
|
|
|
, ("https://www.rubyonrails.com/~minam",
|
|
|
|
|
autolink "https://www.rubyonrails.com/~minam")
|
|
|
|
|
, ("http://www.rubyonrails.com/~minam/url%20with%20spaces",
|
|
|
|
|
autolink "http://www.rubyonrails.com/~minam/url%20with%20spaces")
|
|
|
|
|
, ("http://www.rubyonrails.com/foo.cgi?something=here",
|
|
|
|
|
autolink "http://www.rubyonrails.com/foo.cgi?something=here")
|
|
|
|
|
, ("http://www.rubyonrails.com/foo.cgi?something=here&and=here",
|
|
|
|
|
autolink "http://www.rubyonrails.com/foo.cgi?something=here&and=here")
|
|
|
|
|
, ("http://www.rubyonrails.com/contact;new",
|
|
|
|
|
autolink "http://www.rubyonrails.com/contact;new")
|
|
|
|
|
, ("http://www.rubyonrails.com/contact;new%20with%20spaces",
|
|
|
|
|
autolink "http://www.rubyonrails.com/contact;new%20with%20spaces")
|
|
|
|
|
, ("http://www.rubyonrails.com/contact;new?with=query&string=params",
|
|
|
|
|
autolink "http://www.rubyonrails.com/contact;new?with=query&string=params")
|
|
|
|
|
, ("http://www.rubyonrails.com/~minam/contact;new?with=query&string=params",
|
|
|
|
|
autolink "http://www.rubyonrails.com/~minam/contact;new?with=query&string=params")
|
|
|
|
|
, ("http://en.wikipedia.org/wiki/Wikipedia:Today%27s_featured_picture_%28animation%29/January_20%2C_2007",
|
|
|
|
|
autolink "http://en.wikipedia.org/wiki/Wikipedia:Today%27s_featured_picture_%28animation%29/January_20%2C_2007")
|
|
|
|
|
, ("http://www.mail-archive.com/rails@lists.rubyonrails.org/",
|
|
|
|
|
autolink "http://www.mail-archive.com/rails@lists.rubyonrails.org/")
|
|
|
|
|
, ("http://www.amazon.com/Testing-Equal-Sign-In-Path/ref=pd_bbs_sr_1?ie=UTF8&s=books&qid=1198861734&sr=8-1",
|
|
|
|
|
autolink "http://www.amazon.com/Testing-Equal-Sign-In-Path/ref=pd_bbs_sr_1?ie=UTF8&s=books&qid=1198861734&sr=8-1")
|
|
|
|
|
, ("http://en.wikipedia.org/wiki/Texas_hold%27em",
|
|
|
|
|
autolink "http://en.wikipedia.org/wiki/Texas_hold%27em")
|
|
|
|
|
, ("https://www.google.com/doku.php?id=gps:resource:scs:start",
|
|
|
|
|
autolink "https://www.google.com/doku.php?id=gps:resource:scs:start")
|
|
|
|
|
, ("http://www.rubyonrails.com",
|
|
|
|
|
autolink "http://www.rubyonrails.com")
|
|
|
|
|
, ("http://manuals.ruby-on-rails.com/read/chapter.need_a-period/103#page281",
|
|
|
|
|
autolink "http://manuals.ruby-on-rails.com/read/chapter.need_a-period/103#page281")
|
|
|
|
|
, ("http://foo.example.com/controller/action?parm=value&p2=v2#anchor123",
|
|
|
|
|
autolink "http://foo.example.com/controller/action?parm=value&p2=v2#anchor123")
|
|
|
|
|
, ("http://foo.example.com:3000/controller/action",
|
|
|
|
|
autolink "http://foo.example.com:3000/controller/action")
|
|
|
|
|
, ("http://foo.example.com:3000/controller/action+pack",
|
|
|
|
|
autolink "http://foo.example.com:3000/controller/action+pack")
|
|
|
|
|
, ("http://business.timesonline.co.uk/article/0,,9065-2473189,00.html",
|
|
|
|
|
autolink "http://business.timesonline.co.uk/article/0,,9065-2473189,00.html")
|
|
|
|
|
, ("http://www.mail-archive.com/ruby-talk@ruby-lang.org/",
|
|
|
|
|
autolink "http://www.mail-archive.com/ruby-talk@ruby-lang.org/")
|
2015-07-14 19:20:09 +02:00
|
|
|
|
, ("https://example.org/?anchor=lala-",
|
|
|
|
|
autolink "https://example.org/?anchor=lala-")
|
|
|
|
|
, ("https://example.org/?anchor=-lala",
|
|
|
|
|
autolink "https://example.org/?anchor=-lala")
|
2013-01-15 21:28:31 +01:00
|
|
|
|
]
|
|
|
|
|
|
2011-02-05 03:33:08 +01:00
|
|
|
|
{-
|
|
|
|
|
p_markdown_round_trip :: Block -> Bool
|
|
|
|
|
p_markdown_round_trip b = matches d' d''
|
|
|
|
|
where d' = normalize $ Pandoc (Meta [] [] []) [b]
|
|
|
|
|
d'' = normalize
|
2012-07-26 07:35:41 +02:00
|
|
|
|
$ readMarkdown def { readerSmart = True }
|
2012-07-27 07:59:56 +02:00
|
|
|
|
$ writeMarkdown def d'
|
2011-02-05 03:33:08 +01:00
|
|
|
|
matches (Pandoc _ [Plain []]) (Pandoc _ []) = True
|
|
|
|
|
matches (Pandoc _ [Para []]) (Pandoc _ []) = True
|
|
|
|
|
matches (Pandoc _ [Plain xs]) (Pandoc _ [Para xs']) = xs == xs'
|
|
|
|
|
matches x y = x == y
|
|
|
|
|
-}
|
|
|
|
|
|
2017-03-14 17:05:36 +01:00
|
|
|
|
tests :: [TestTree]
|
2011-01-27 07:09:09 +01:00
|
|
|
|
tests = [ testGroup "inline code"
|
|
|
|
|
[ "with attribute" =:
|
|
|
|
|
"`document.write(\"Hello\");`{.javascript}"
|
|
|
|
|
=?> para
|
|
|
|
|
(codeWith ("",["javascript"],[]) "document.write(\"Hello\");")
|
|
|
|
|
, "with attribute space" =:
|
|
|
|
|
"`*` {.haskell .special x=\"7\"}"
|
2016-12-24 15:34:07 +01:00
|
|
|
|
=?> para (code "*" <> space <> str "{.haskell" <> space <>
|
|
|
|
|
str ".special" <> space <> str "x=\"7\"}")
|
2011-01-27 07:09:09 +01:00
|
|
|
|
]
|
2020-04-16 01:20:01 +02:00
|
|
|
|
, testGroup "inline code in lists (regression tests for #6284)" $
|
|
|
|
|
let lists = [("ordered", "1. ", ol), ("bullet", "- ", ul)]
|
|
|
|
|
ol = orderedListWith (1, Decimal, Period)
|
|
|
|
|
ul = bulletList
|
|
|
|
|
items =
|
|
|
|
|
[ ("in text" , ["If `(1) x`, then `2`"], [text "If " <> code "(1) x" <> text ", then " <> code "2"])
|
|
|
|
|
, ("at start" , ["`#. x`" ], [code "#. x" ])
|
|
|
|
|
, ("at start" , ["`- x`" ], [code "- x" ])
|
|
|
|
|
, ("after literal backticks", ["`x``#. x`" ], [code "x``#. x" ])
|
|
|
|
|
, ("after literal backticks", ["`x``- x`" ], [code "x``- x" ])
|
|
|
|
|
]
|
|
|
|
|
lis = ["`text","y","x`"]
|
|
|
|
|
lis' = ["text","y","x"]
|
|
|
|
|
bldLsts w lsts txts
|
|
|
|
|
= let (res, res', f) =
|
|
|
|
|
foldr (\((_, _, lt), lc) (acc, tacc, t) ->
|
|
|
|
|
if lt [] == t []
|
|
|
|
|
then (acc, lc : tacc, lt)
|
|
|
|
|
else (join t tacc acc, [lc], lt))
|
|
|
|
|
(mempty, [], mconcat)
|
|
|
|
|
(zip lsts (map text txts))
|
|
|
|
|
join t tacc acc = case tacc of
|
|
|
|
|
[] -> acc
|
|
|
|
|
[x] -> t [plain x] <> acc
|
|
|
|
|
xs -> t (map w xs) <> acc
|
|
|
|
|
in join f res' res
|
|
|
|
|
in ["code with list marker "<>mp<>" in " <> ln <> " list" =:
|
|
|
|
|
T.intercalate "\n" (map (lstr <>) istrs) =?> lbld (map plain iblds)
|
|
|
|
|
| (ln, lstr, lbld) <- lists, (mp, istrs, iblds) <- items]
|
|
|
|
|
<> [ "lists with newlines in backticks" =:
|
|
|
|
|
T.intercalate "\n" (zipWith (\i (_, lt, _) -> lt <> i) lis lsts)
|
|
|
|
|
=?> bldLsts plain lsts lis
|
|
|
|
|
| lsts <- [ [i, j, k] | i <- lists, j <- lists, k <- lists]
|
|
|
|
|
]
|
|
|
|
|
<> [ "lists with newlines and indent in backticks" =:
|
|
|
|
|
T.intercalate ("\n" <> T.replicate 4 " ") (zipWith (\i (_, lt, _) -> lt <> i) lis lsts)
|
|
|
|
|
=?> let (_, _, f) = head lsts
|
|
|
|
|
in f [plain $ code $ T.intercalate (T.replicate 5 " ") $ head lis' : zipWith (\i (_, lt, _) -> lt <> i) (tail lis') (tail lsts)]
|
|
|
|
|
| lsts <- [ [i, j, k] | i <- lists, j <- lists, k <- lists]
|
|
|
|
|
]
|
|
|
|
|
<> [ "lists with blank lines and indent in backticks" =:
|
|
|
|
|
T.intercalate ("\n\n" <> T.replicate 4 " ") (zipWith (\i (_, lt, _) -> lt <> i) lis lsts)
|
|
|
|
|
<> "\n"
|
|
|
|
|
=?> let (_, _, f) = head lsts
|
|
|
|
|
in f . pure $ (para . text $ head lis) <> bldLsts para (tail lsts) (tail lis)
|
|
|
|
|
| lsts <- [ [i, j, k] | i <- lists, j <- lists, k <- lists]
|
|
|
|
|
]
|
2013-11-23 04:41:08 +01:00
|
|
|
|
, testGroup "emph and strong"
|
|
|
|
|
[ "two strongs in emph" =:
|
|
|
|
|
"***a**b **c**d*" =?> para (emph (strong (str "a") <> str "b" <> space
|
|
|
|
|
<> strong (str "c") <> str "d"))
|
2014-07-08 06:21:04 +02:00
|
|
|
|
, "emph and strong emph alternating" =:
|
|
|
|
|
"*xxx* ***xxx*** xxx\n*xxx* ***xxx*** xxx"
|
|
|
|
|
=?> para (emph "xxx" <> space <> strong (emph "xxx") <>
|
2015-12-12 00:58:11 +01:00
|
|
|
|
space <> "xxx" <> softbreak <>
|
2014-07-08 06:21:04 +02:00
|
|
|
|
emph "xxx" <> space <> strong (emph "xxx") <>
|
|
|
|
|
space <> "xxx")
|
|
|
|
|
, "emph with spaced strong" =:
|
|
|
|
|
"*x **xx** x*"
|
|
|
|
|
=?> para (emph ("x" <> space <> strong "xx" <> space <> "x"))
|
2014-07-10 23:23:20 +02:00
|
|
|
|
, "intraword underscore with opening underscore (#1121)" =:
|
|
|
|
|
"_foot_ball_" =?> para (emph (text "foot_ball"))
|
2013-11-23 04:41:08 +01:00
|
|
|
|
]
|
2012-09-22 22:00:59 +02:00
|
|
|
|
, testGroup "raw LaTeX"
|
|
|
|
|
[ "in URL" =:
|
|
|
|
|
"\\begin\n" =?> para (text "\\begin")
|
|
|
|
|
]
|
2014-07-08 06:27:28 +02:00
|
|
|
|
, testGroup "raw HTML"
|
|
|
|
|
[ "nesting (issue #1330)" =:
|
|
|
|
|
"<del>test</del>" =?>
|
|
|
|
|
rawBlock "html" "<del>" <> plain (str "test") <>
|
|
|
|
|
rawBlock "html" "</del>"
|
2015-04-18 07:55:39 +02:00
|
|
|
|
, "invalid tag (issue #1820" =:
|
|
|
|
|
"</ div></.div>" =?>
|
|
|
|
|
para (text "</ div></.div>")
|
2015-07-22 07:44:18 +02:00
|
|
|
|
, "technically invalid comment" =:
|
|
|
|
|
"<!-- pandoc --help -->" =?>
|
|
|
|
|
rawBlock "html" "<!-- pandoc --help -->"
|
2015-10-23 06:18:06 +02:00
|
|
|
|
, test markdownGH "issue 2469" $
|
|
|
|
|
"<\n\na>" =?>
|
|
|
|
|
para (text "<") <> para (text "a>")
|
2014-07-08 06:27:28 +02:00
|
|
|
|
]
|
2016-10-23 23:12:36 +02:00
|
|
|
|
, testGroup "raw email addresses"
|
|
|
|
|
[ test markdownGH "issue 2940" $
|
|
|
|
|
"**@user**" =?>
|
|
|
|
|
para (strong (text "@user"))
|
|
|
|
|
]
|
2015-11-13 21:06:39 +01:00
|
|
|
|
, testGroup "emoji"
|
|
|
|
|
[ test markdownGH "emoji symbols" $
|
2018-07-16 00:14:40 +02:00
|
|
|
|
":smile: and :+1:" =?> para (spanWith ("", ["emoji"], [("data-emoji", "smile")]) "😄" <>
|
|
|
|
|
space <> str "and" <> space <>
|
|
|
|
|
spanWith ("", ["emoji"], [("data-emoji", "+1")]) "👍")
|
2015-11-13 21:06:39 +01:00
|
|
|
|
]
|
2012-09-22 22:59:30 +02:00
|
|
|
|
, "unbalanced brackets" =:
|
2018-01-14 21:23:16 +01:00
|
|
|
|
"[[[[[[[[[[[[hi" =?> para (text "[[[[[[[[[[[[hi")
|
2011-12-02 04:47:25 +01:00
|
|
|
|
, testGroup "backslash escapes"
|
|
|
|
|
[ "in URL" =:
|
|
|
|
|
"[hi](/there\\))"
|
2011-12-06 06:13:06 +01:00
|
|
|
|
=?> para (link "/there)" "" "hi")
|
2011-12-05 07:37:28 +01:00
|
|
|
|
, "in title" =:
|
2011-12-06 06:16:30 +01:00
|
|
|
|
"[hi](/there \"a\\\"a\")"
|
2011-12-06 06:13:06 +01:00
|
|
|
|
=?> para (link "/there" "a\"a" "hi")
|
2011-12-06 04:07:17 +01:00
|
|
|
|
, "in reference link title" =:
|
|
|
|
|
"[hi]\n\n[hi]: /there (a\\)a)"
|
2011-12-06 06:13:06 +01:00
|
|
|
|
=?> para (link "/there" "a)a" "hi")
|
2011-12-06 04:07:17 +01:00
|
|
|
|
, "in reference link URL" =:
|
2011-12-06 06:16:30 +01:00
|
|
|
|
"[hi]\n\n[hi]: /there\\.0"
|
|
|
|
|
=?> para (link "/there.0" "" "hi")
|
2011-12-02 04:47:25 +01:00
|
|
|
|
]
|
2013-01-15 21:28:31 +01:00
|
|
|
|
, testGroup "bare URIs"
|
2015-07-14 22:16:20 +02:00
|
|
|
|
(map testBareLink bareLinkTests)
|
2014-12-14 21:20:33 +01:00
|
|
|
|
, testGroup "autolinks"
|
|
|
|
|
[ "with unicode dash following" =:
|
|
|
|
|
"<http://foo.bar>\8212" =?> para (autolink "http://foo.bar" <>
|
|
|
|
|
str "\8212")
|
2015-07-10 19:28:39 +02:00
|
|
|
|
, "a partial URL (#2277)" =:
|
|
|
|
|
"<www.boe.es/buscar/act.php?id=BOE-A-1996-8930#a66>" =?>
|
|
|
|
|
para (text "<www.boe.es/buscar/act.php?id=BOE-A-1996-8930#a66>")
|
2016-10-26 12:18:58 +02:00
|
|
|
|
, "with some attributes" =:
|
|
|
|
|
"<http://foo.bar>{#i .j .z k=v}" =?>
|
|
|
|
|
para (autolinkWith ("i", ["j", "z"], [("k", "v")]) "http://foo.bar")
|
|
|
|
|
, "with some attributes and spaces" =:
|
|
|
|
|
"<http://foo.bar> {#i .j .z k=v}" =?>
|
|
|
|
|
para (autolink "http://foo.bar" <> space <> text "{#i .j .z k=v}")
|
2014-12-14 21:20:33 +01:00
|
|
|
|
]
|
2015-07-14 22:16:20 +02:00
|
|
|
|
, testGroup "links"
|
|
|
|
|
[ "no autolink inside link" =:
|
|
|
|
|
"[<https://example.org>](url)" =?>
|
|
|
|
|
para (link "url" "" (text "<https://example.org>"))
|
|
|
|
|
, "no inline link inside link" =:
|
|
|
|
|
"[[a](url2)](url)" =?>
|
|
|
|
|
para (link "url" "" (text "[a](url2)"))
|
|
|
|
|
, "no bare URI inside link" =:
|
|
|
|
|
"[https://example.org(](url)" =?>
|
|
|
|
|
para (link "url" "" (text "https://example.org("))
|
|
|
|
|
]
|
2013-06-19 18:27:11 +02:00
|
|
|
|
, testGroup "Headers"
|
|
|
|
|
[ "blank line before header" =:
|
|
|
|
|
"\n# Header\n"
|
|
|
|
|
=?> headerWith ("header",[],[]) 1 "Header"
|
2015-04-19 03:59:29 +02:00
|
|
|
|
, "bracketed text (#2062)" =:
|
|
|
|
|
"# [hi]\n"
|
|
|
|
|
=?> headerWith ("hi",[],[]) 1 "[hi]"
|
2015-07-23 08:31:24 +02:00
|
|
|
|
, "ATX header without trailing #s" =:
|
|
|
|
|
"# Foo bar\n\n" =?>
|
|
|
|
|
headerWith ("foo-bar",[],[]) 1 "Foo bar"
|
|
|
|
|
, "ATX header without trailing #s" =:
|
|
|
|
|
"# Foo bar with # #" =?>
|
|
|
|
|
headerWith ("foo-bar-with",[],[]) 1 "Foo bar with #"
|
|
|
|
|
, "setext header" =:
|
|
|
|
|
"Foo bar\n=\n\n Foo bar 2 \n=" =?>
|
|
|
|
|
headerWith ("foo-bar",[],[]) 1 "Foo bar"
|
|
|
|
|
<> headerWith ("foo-bar-2",[],[]) 1 "Foo bar 2"
|
2013-06-19 18:27:11 +02:00
|
|
|
|
]
|
2015-07-23 08:31:03 +02:00
|
|
|
|
, testGroup "Implicit header references"
|
|
|
|
|
[ "ATX header without trailing #s" =:
|
|
|
|
|
"# Header\n[header]\n\n[header ]\n\n[ header]" =?>
|
|
|
|
|
headerWith ("header",[],[]) 1 "Header"
|
|
|
|
|
<> para (link "#header" "" (text "header"))
|
2015-07-24 00:35:18 +02:00
|
|
|
|
<> para (link "#header" "" (text "header"))
|
|
|
|
|
<> para (link "#header" "" (text "header"))
|
2015-07-23 08:31:03 +02:00
|
|
|
|
, "ATX header with trailing #s" =:
|
|
|
|
|
"# Foo bar #\n[foo bar]\n\n[foo bar ]\n\n[ foo bar]" =?>
|
|
|
|
|
headerWith ("foo-bar",[],[]) 1 "Foo bar"
|
|
|
|
|
<> para (link "#foo-bar" "" (text "foo bar"))
|
2015-07-24 00:35:18 +02:00
|
|
|
|
<> para (link "#foo-bar" "" (text "foo bar"))
|
|
|
|
|
<> para (link "#foo-bar" "" (text "foo bar"))
|
2015-07-23 08:31:03 +02:00
|
|
|
|
, "setext header" =:
|
|
|
|
|
" Header \n=\n\n[header]\n\n[header ]\n\n[ header]" =?>
|
|
|
|
|
headerWith ("header",[],[]) 1 "Header"
|
|
|
|
|
<> para (link "#header" "" (text "header"))
|
2015-07-24 00:35:18 +02:00
|
|
|
|
<> para (link "#header" "" (text "header"))
|
|
|
|
|
<> para (link "#header" "" (text "header"))
|
2015-07-23 08:31:03 +02:00
|
|
|
|
]
|
2011-07-26 08:49:45 +02:00
|
|
|
|
, testGroup "smart punctuation"
|
|
|
|
|
[ test markdownSmart "quote before ellipses"
|
|
|
|
|
("'...hi'"
|
2013-12-20 02:43:25 +01:00
|
|
|
|
=?> para (singleQuoted "…hi"))
|
2011-12-27 08:03:20 +01:00
|
|
|
|
, test markdownSmart "apostrophe before emph"
|
|
|
|
|
("D'oh! A l'*aide*!"
|
|
|
|
|
=?> para ("D’oh! A l’" <> emph "aide" <> "!"))
|
|
|
|
|
, test markdownSmart "apostrophe in French"
|
|
|
|
|
("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
|
2013-12-20 02:43:25 +01:00
|
|
|
|
=?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»")
|
2015-04-17 23:53:20 +02:00
|
|
|
|
, test markdownSmart "apostrophe after math" $ -- issue #1909
|
|
|
|
|
"The value of the $x$'s and the systems' condition." =?>
|
|
|
|
|
para (text "The value of the " <> math "x" <> text "\8217s and the systems\8217 condition.")
|
2018-04-17 10:55:37 +02:00
|
|
|
|
, test markdownSmart "unclosed double quote"
|
|
|
|
|
("**this should \"be bold**"
|
2021-04-29 08:30:16 +02:00
|
|
|
|
=?> para (strong "this should \8220be bold"))
|
2011-07-26 08:49:45 +02:00
|
|
|
|
]
|
2021-08-16 06:57:57 +02:00
|
|
|
|
, testGroup "sub- and superscripts"
|
|
|
|
|
[
|
|
|
|
|
test markdownMMD "normal subscript"
|
|
|
|
|
("H~2~"
|
|
|
|
|
=?> para ("H" <> subscript "2"))
|
|
|
|
|
, test markdownMMD "normal superscript"
|
|
|
|
|
("x^3^"
|
|
|
|
|
=?> para ("x" <> superscript "3"))
|
2022-02-22 18:05:39 +01:00
|
|
|
|
, test markdownMMD "short subscript delimited by space"
|
2021-08-16 06:57:57 +02:00
|
|
|
|
("O~2 is dangerous"
|
|
|
|
|
=?> para ("O" <> subscript "2" <> space <> "is dangerous"))
|
2022-02-22 18:05:39 +01:00
|
|
|
|
, test markdownMMD "short subscript delimited by newline"
|
2021-08-16 06:57:57 +02:00
|
|
|
|
("O~2\n"
|
|
|
|
|
=?> para ("O" <> subscript "2"))
|
2022-02-22 18:05:39 +01:00
|
|
|
|
, test markdownMMD "short subscript delimited by EOF"
|
2021-08-16 06:57:57 +02:00
|
|
|
|
("O~2"
|
|
|
|
|
=?> para ("O" <> subscript "2"))
|
|
|
|
|
, test markdownMMD "short subscript delimited by punctuation"
|
|
|
|
|
("O~2."
|
|
|
|
|
=?> para ("O" <> subscript "2" <> "."))
|
|
|
|
|
, test markdownMMD "short subscript delimited by emph"
|
|
|
|
|
("O~2*combustible!*"
|
|
|
|
|
=?> para ("O" <> subscript "2" <> emph "combustible!"))
|
|
|
|
|
, test markdownMMD "no nesting in short subscripts"
|
|
|
|
|
("y~*2*"
|
|
|
|
|
=?> para ("y~" <> emph "2"))
|
2022-02-22 18:05:39 +01:00
|
|
|
|
, test markdownMMD "short superscript delimited by space"
|
2021-08-16 06:57:57 +02:00
|
|
|
|
("x^2 = y"
|
|
|
|
|
=?> para ("x" <> superscript "2" <> space <> "= y"))
|
2022-02-22 18:05:39 +01:00
|
|
|
|
, test markdownMMD "short superscript delimited by newline"
|
2021-08-16 06:57:57 +02:00
|
|
|
|
("x^2\n"
|
|
|
|
|
=?> para ("x" <> superscript "2"))
|
2022-02-22 18:05:39 +01:00
|
|
|
|
, test markdownMMD "short superscript delimited by ExF"
|
2021-08-16 06:57:57 +02:00
|
|
|
|
("x^2"
|
|
|
|
|
=?> para ("x" <> superscript "2"))
|
|
|
|
|
, test markdownMMD "short superscript delimited by punctuation"
|
|
|
|
|
("x^2."
|
|
|
|
|
=?> para ("x" <> superscript "2" <> "."))
|
|
|
|
|
, test markdownMMD "short superscript delimited by emph"
|
|
|
|
|
("x^2*combustible!*"
|
|
|
|
|
=?> para ("x" <> superscript "2" <> emph "combustible!"))
|
|
|
|
|
, test markdownMMD "no nesting in short superscripts"
|
|
|
|
|
("y^*2*"
|
|
|
|
|
=?> para ("y^" <> emph "2"))
|
|
|
|
|
]
|
2011-02-01 05:05:11 +01:00
|
|
|
|
, testGroup "footnotes"
|
2011-02-01 16:37:22 +01:00
|
|
|
|
[ "indent followed by newline and flush-left text" =:
|
2011-02-01 05:42:49 +01:00
|
|
|
|
"[^1]\n\n[^1]: my note\n\n \nnot in note\n"
|
2011-12-13 23:29:07 +01:00
|
|
|
|
=?> para (note (para "my note")) <> para "not in note"
|
2011-02-01 16:37:22 +01:00
|
|
|
|
, "indent followed by newline and indented text" =:
|
2011-02-02 07:35:27 +01:00
|
|
|
|
"[^1]\n\n[^1]: my note\n \n in note\n"
|
2011-12-13 23:29:07 +01:00
|
|
|
|
=?> para (note (para "my note" <> para "in note"))
|
2011-04-20 20:42:27 +02:00
|
|
|
|
, "recursive note" =:
|
|
|
|
|
"[^1]\n\n[^1]: See [^1]\n"
|
|
|
|
|
=?> para (note (para "See [^1]"))
|
2011-02-01 05:05:11 +01:00
|
|
|
|
]
|
2011-03-02 20:18:38 +01:00
|
|
|
|
, testGroup "lhs"
|
2017-01-14 13:06:27 +01:00
|
|
|
|
[ test (purely $ readMarkdown def{ readerExtensions = enableExtension
|
2017-01-15 20:42:00 +01:00
|
|
|
|
Ext_literate_haskell pandocExtensions })
|
Change reader types, allowing better tracking of source positions.
Previously, when multiple file arguments were provided, pandoc
simply concatenated them and passed the contents to the readers,
which took a Text argument.
As a result, the readers had no way of knowing which file
was the source of any particular bit of text. This meant that
we couldn't report accurate source positions on errors or
include accurate source positions as attributes in the AST.
More seriously, it meant that we couldn't resolve resource
paths relative to the files containing them
(see e.g. #5501, #6632, #6384, #3752).
Add Text.Pandoc.Sources (exported module), with a `Sources` type
and a `ToSources` class. A `Sources` wraps a list of `(SourcePos,
Text)` pairs. [API change] A parsec `Stream` instance is provided for
`Sources`. The module also exports versions of parsec's `satisfy` and
other Char parsers that track source positions accurately from a
`Sources` stream (or any instance of the new `UpdateSourcePos` class).
Text.Pandoc.Parsing now exports these modified Char parsers instead of
the ones parsec provides. Modified parsers to use a `Sources` as stream
[API change].
The readers that previously took a `Text` argument have been
modified to take any instance of `ToSources`. So, they may still
be used with a `Text`, but they can also be used with a `Sources`
object.
In Text.Pandoc.Error, modified the constructor PandocParsecError
to take a `Sources` rather than a `Text` as first argument,
so parse error locations can be accurately reported.
T.P.Error: showPos, do not print "-" as source name.
2021-05-01 22:17:45 +02:00
|
|
|
|
"inverse bird tracks and html"
|
|
|
|
|
$ ("> a\n\n< b\n\n<div>\n" :: Text)
|
2019-01-08 20:36:33 +01:00
|
|
|
|
=?> codeBlockWith ("",["haskell","literate"],[]) "a"
|
2011-12-13 23:29:07 +01:00
|
|
|
|
<>
|
2019-01-08 20:36:33 +01:00
|
|
|
|
codeBlockWith ("",["haskell"],[]) "b"
|
2011-12-13 23:29:07 +01:00
|
|
|
|
<>
|
2011-03-02 20:18:38 +01:00
|
|
|
|
rawBlock "html" "<div>\n\n"
|
|
|
|
|
]
|
2011-02-05 03:33:08 +01:00
|
|
|
|
-- the round-trip properties frequently fail
|
|
|
|
|
-- , testGroup "round trip"
|
|
|
|
|
-- [ property "p_markdown_round_trip" p_markdown_round_trip
|
|
|
|
|
-- ]
|
2014-07-21 01:33:59 +02:00
|
|
|
|
, 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" =?>
|
2015-12-12 00:58:11 +01:00
|
|
|
|
definitionList [ (text "foo1", [plain (text "bar" <>
|
|
|
|
|
softbreak <> text "baz"),
|
2014-07-21 01:33:59 +02:00
|
|
|
|
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")])
|
|
|
|
|
]
|
2015-04-18 19:13:32 +02:00
|
|
|
|
, "first line not indented" =:
|
|
|
|
|
"foo\n: bar\n" =?>
|
|
|
|
|
definitionList [ (text "foo", [plain (text "bar")]) ]
|
2015-04-26 20:20:53 +02:00
|
|
|
|
, "list in definition" =:
|
|
|
|
|
"foo\n: - bar\n" =?>
|
|
|
|
|
definitionList [ (text "foo", [bulletList [plain (text "bar")]]) ]
|
2015-05-04 00:06:40 +02:00
|
|
|
|
, "in div" =:
|
|
|
|
|
"<div>foo\n: - bar\n</div>" =?>
|
|
|
|
|
divWith nullAttr (definitionList
|
|
|
|
|
[ (text "foo", [bulletList [plain (text "bar")]]) ])
|
2014-07-21 01:33:59 +02:00
|
|
|
|
]
|
|
|
|
|
, testGroup "+compact_definition_lists"
|
|
|
|
|
[ test markdownCDL "basic compact list" $
|
|
|
|
|
"foo1\n: bar\n baz\nfoo2\n: bar2\n" =?>
|
2015-12-12 00:58:11 +01:00
|
|
|
|
definitionList [ (text "foo1", [plain (text "bar" <> softbreak <>
|
|
|
|
|
text "baz")])
|
2014-07-21 01:33:59 +02:00
|
|
|
|
, (text "foo2", [plain (text "bar2")])
|
|
|
|
|
]
|
|
|
|
|
]
|
2014-05-04 17:19:48 +02:00
|
|
|
|
, testGroup "lists"
|
|
|
|
|
[ "issue #1154" =:
|
|
|
|
|
" - <div>\n first div breaks\n </div>\n\n <button>if this button exists</button>\n\n <div>\n with this div too.\n </div>\n"
|
2014-08-31 21:55:47 +02:00
|
|
|
|
=?> bulletList [divWith nullAttr (para $ text "first div breaks") <>
|
2014-05-04 17:19:48 +02:00
|
|
|
|
rawBlock "html" "<button>" <>
|
|
|
|
|
plain (text "if this button exists") <>
|
2014-07-07 23:47:51 +02:00
|
|
|
|
rawBlock "html" "</button>" <>
|
2014-08-31 21:55:47 +02:00
|
|
|
|
divWith nullAttr (para $ text "with this div too.")]
|
2014-09-26 11:32:08 +02:00
|
|
|
|
, test markdownGH "issue #1636" $
|
2017-06-10 18:26:44 +02:00
|
|
|
|
T.unlines [ "* a"
|
|
|
|
|
, "* b"
|
|
|
|
|
, "* c"
|
|
|
|
|
, " * d" ]
|
2014-09-26 11:32:08 +02:00
|
|
|
|
=?>
|
|
|
|
|
bulletList [ plain "a"
|
|
|
|
|
, plain "b"
|
|
|
|
|
, plain "c" <> bulletList [plain "d"] ]
|
2014-05-04 17:19:48 +02:00
|
|
|
|
]
|
2016-01-09 02:33:37 +01:00
|
|
|
|
, 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"))
|
|
|
|
|
]
|
2015-02-18 14:54:25 +01:00
|
|
|
|
, testGroup "citations"
|
|
|
|
|
[ "simple" =:
|
|
|
|
|
"@item1" =?> para (cite [
|
|
|
|
|
Citation{ citationId = "item1"
|
|
|
|
|
, citationPrefix = []
|
|
|
|
|
, citationSuffix = []
|
|
|
|
|
, citationMode = AuthorInText
|
2020-09-09 06:56:12 +02:00
|
|
|
|
, citationNoteNum = 1
|
2015-02-18 14:54:25 +01:00
|
|
|
|
, citationHash = 0
|
|
|
|
|
}
|
|
|
|
|
] "@item1")
|
|
|
|
|
, "key starts with digit" =:
|
|
|
|
|
"@1657:huyghens" =?> para (cite [
|
|
|
|
|
Citation{ citationId = "1657:huyghens"
|
|
|
|
|
, citationPrefix = []
|
|
|
|
|
, citationSuffix = []
|
|
|
|
|
, citationMode = AuthorInText
|
2020-09-09 06:56:12 +02:00
|
|
|
|
, citationNoteNum = 1
|
2015-02-18 14:54:25 +01:00
|
|
|
|
, citationHash = 0
|
|
|
|
|
}
|
|
|
|
|
] "@1657:huyghens")
|
|
|
|
|
]
|
2020-09-09 06:56:12 +02:00
|
|
|
|
, let citation = cite [Citation "cita" [] [] AuthorInText 1 0] (str "@cita")
|
2015-04-17 16:30:55 +02:00
|
|
|
|
in testGroup "footnote/link following citation" -- issue #2083
|
|
|
|
|
[ "footnote" =:
|
2017-06-10 18:26:44 +02:00
|
|
|
|
T.unlines [ "@cita[^note]"
|
|
|
|
|
, ""
|
|
|
|
|
, "[^note]: note" ] =?>
|
2015-04-17 16:30:55 +02:00
|
|
|
|
para (
|
|
|
|
|
citation <> note (para $ str "note")
|
|
|
|
|
)
|
|
|
|
|
, "normal link" =:
|
|
|
|
|
"@cita [link](http://www.com)" =?>
|
|
|
|
|
para (
|
|
|
|
|
citation <> space <> link "http://www.com" "" (str "link")
|
|
|
|
|
)
|
|
|
|
|
, "reference link" =:
|
2017-06-10 18:26:44 +02:00
|
|
|
|
T.unlines [ "@cita [link][link]"
|
|
|
|
|
, ""
|
|
|
|
|
, "[link]: http://www.com" ] =?>
|
2015-04-17 16:30:55 +02:00
|
|
|
|
para (
|
|
|
|
|
citation <> space <> link "http://www.com" "" (str "link")
|
|
|
|
|
)
|
|
|
|
|
, "short reference link" =:
|
2017-06-10 18:26:44 +02:00
|
|
|
|
T.unlines [ "@cita [link]"
|
|
|
|
|
, ""
|
|
|
|
|
, "[link]: http://www.com" ] =?>
|
2015-04-17 16:30:55 +02:00
|
|
|
|
para (
|
|
|
|
|
citation <> space <> link "http://www.com" "" (str "link")
|
|
|
|
|
)
|
|
|
|
|
, "implicit header link" =:
|
2017-06-10 18:26:44 +02:00
|
|
|
|
T.unlines [ "# Header"
|
|
|
|
|
, "@cita [Header]" ] =?>
|
2015-04-17 16:30:55 +02:00
|
|
|
|
headerWith ("header",[],[]) 1 (str "Header") <> para (
|
|
|
|
|
citation <> space <> link "#header" "" (str "Header")
|
|
|
|
|
)
|
|
|
|
|
, "regular citation" =:
|
|
|
|
|
"@cita [foo]" =?>
|
|
|
|
|
para (
|
2020-09-09 06:56:12 +02:00
|
|
|
|
cite [Citation "cita" [] [Str "foo"] AuthorInText 1 0]
|
2015-04-17 16:30:55 +02:00
|
|
|
|
(str "@cita" <> space <> str "[foo]")
|
|
|
|
|
)
|
|
|
|
|
]
|
2011-01-27 07:09:09 +01:00
|
|
|
|
]
|