2014-03-04 00:33:25 +01:00
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
module Tests.Readers.Org (tests) where
|
|
|
|
|
|
|
|
|
|
import Text.Pandoc.Definition
|
|
|
|
|
import Test.Framework
|
|
|
|
|
import Tests.Helpers
|
|
|
|
|
import Text.Pandoc.Builder
|
|
|
|
|
import Text.Pandoc
|
|
|
|
|
import Data.List (intersperse)
|
2015-02-18 20:57:48 +01:00
|
|
|
|
import Text.Pandoc.Error
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
|
|
|
|
org :: String -> Pandoc
|
2015-02-18 20:57:48 +01:00
|
|
|
|
org = handleError . readOrg def
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
2015-03-09 13:11:53 +01:00
|
|
|
|
orgSmart :: String -> Pandoc
|
2015-03-28 20:12:48 +01:00
|
|
|
|
orgSmart = handleError . readOrg def { readerSmart = True }
|
2015-03-09 13:11:53 +01:00
|
|
|
|
|
2014-03-04 00:33:25 +01:00
|
|
|
|
infix 4 =:
|
|
|
|
|
(=:) :: ToString c
|
|
|
|
|
=> String -> (String, c) -> Test
|
|
|
|
|
(=:) = test org
|
|
|
|
|
|
|
|
|
|
spcSep :: [Inlines] -> Inlines
|
|
|
|
|
spcSep = mconcat . intersperse space
|
|
|
|
|
|
|
|
|
|
simpleTable' :: Int
|
|
|
|
|
-> [Blocks]
|
|
|
|
|
-> [[Blocks]]
|
|
|
|
|
-> Blocks
|
|
|
|
|
simpleTable' n = table "" (take n $ repeat (AlignDefault, 0.0))
|
|
|
|
|
|
|
|
|
|
tests :: [Test]
|
|
|
|
|
tests =
|
|
|
|
|
[ testGroup "Inlines" $
|
|
|
|
|
[ "Plain String" =:
|
|
|
|
|
"Hello, World" =?>
|
|
|
|
|
para (spcSep [ "Hello,", "World" ])
|
|
|
|
|
|
|
|
|
|
, "Emphasis" =:
|
|
|
|
|
"/Planet Punk/" =?>
|
|
|
|
|
para (emph . spcSep $ ["Planet", "Punk"])
|
|
|
|
|
|
|
|
|
|
, "Strong" =:
|
|
|
|
|
"*Cider*" =?>
|
|
|
|
|
para (strong "Cider")
|
|
|
|
|
|
2014-04-05 09:37:46 +02:00
|
|
|
|
, "Strong Emphasis" =:
|
2014-04-06 14:49:57 +02:00
|
|
|
|
"/*strength*/" =?>
|
|
|
|
|
para (emph . strong $ "strength")
|
2014-04-05 09:37:46 +02:00
|
|
|
|
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, "Strikeout" =:
|
|
|
|
|
"+Kill Bill+" =?>
|
|
|
|
|
para (strikeout . spcSep $ [ "Kill", "Bill" ])
|
|
|
|
|
|
2014-06-17 07:03:26 +02:00
|
|
|
|
, "Verbatim" =:
|
2014-03-04 00:33:25 +01:00
|
|
|
|
"=Robot.rock()=" =?>
|
|
|
|
|
para (code "Robot.rock()")
|
|
|
|
|
|
2014-06-17 07:03:26 +02:00
|
|
|
|
, "Code" =:
|
2014-03-04 00:33:25 +01:00
|
|
|
|
"~word for word~" =?>
|
2014-06-17 07:03:26 +02:00
|
|
|
|
para (code "word for word")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
2014-04-10 15:11:03 +02:00
|
|
|
|
, "Math $..$" =:
|
|
|
|
|
"$E=mc^2$" =?>
|
|
|
|
|
para (math "E=mc^2")
|
|
|
|
|
|
|
|
|
|
, "Math $$..$$" =:
|
|
|
|
|
"$$E=mc^2$$" =?>
|
|
|
|
|
para (displayMath "E=mc^2")
|
|
|
|
|
|
|
|
|
|
, "Math \\[..\\]" =:
|
|
|
|
|
"\\[E=ℎν\\]" =?>
|
|
|
|
|
para (displayMath "E=ℎν")
|
|
|
|
|
|
|
|
|
|
, "Math \\(..\\)" =:
|
|
|
|
|
"\\(σ_x σ_p ≥ \\frac{ℏ}{2}\\)" =?>
|
|
|
|
|
para (math "σ_x σ_p ≥ \\frac{ℏ}{2}")
|
|
|
|
|
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, "Symbol" =:
|
|
|
|
|
"A * symbol" =?>
|
|
|
|
|
para (str "A" <> space <> str "*" <> space <> "symbol")
|
|
|
|
|
|
2014-04-11 11:05:42 +02:00
|
|
|
|
, "Superscript simple expression" =:
|
|
|
|
|
"2^-λ" =?>
|
|
|
|
|
para (str "2" <> superscript "-λ")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
|
|
|
|
, "Superscript multi char" =:
|
|
|
|
|
"2^{n-1}" =?>
|
|
|
|
|
para (str "2" <> superscript "n-1")
|
|
|
|
|
|
2014-04-11 11:05:42 +02:00
|
|
|
|
, "Subscript simple expression" =:
|
2014-03-04 00:33:25 +01:00
|
|
|
|
"a_n" =?>
|
|
|
|
|
para (str "a" <> subscript "n")
|
|
|
|
|
|
|
|
|
|
, "Subscript multi char" =:
|
|
|
|
|
"a_{n+1}" =?>
|
|
|
|
|
para (str "a" <> subscript "n+1")
|
|
|
|
|
|
2014-04-12 11:07:38 +02:00
|
|
|
|
, "Linebreak" =:
|
|
|
|
|
"line \\\\ \nbreak" =?>
|
|
|
|
|
para ("line" <> linebreak <> "break")
|
|
|
|
|
|
2014-04-06 18:43:49 +02:00
|
|
|
|
, "Inline note" =:
|
|
|
|
|
"[fn::Schreib mir eine E-Mail]" =?>
|
|
|
|
|
para (note $ para "Schreib mir eine E-Mail")
|
|
|
|
|
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, "Markup-chars not occuring on word break are symbols" =:
|
|
|
|
|
unlines [ "this+that+ +so+on"
|
|
|
|
|
, "seven*eight* nine*"
|
|
|
|
|
, "+not+funny+"
|
|
|
|
|
] =?>
|
2015-12-12 21:21:36 +01:00
|
|
|
|
para ("this+that+ +so+on" <> softbreak <>
|
|
|
|
|
"seven*eight* nine*" <> softbreak <>
|
|
|
|
|
strikeout "not+funny")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
2014-04-10 15:11:03 +02:00
|
|
|
|
, "No empty markup" =:
|
2014-04-11 11:05:42 +02:00
|
|
|
|
"// ** __ ++ == ~~ $$" =?>
|
|
|
|
|
para (spcSep [ "//", "**", "__", "++", "==", "~~", "$$" ])
|
2014-04-10 15:11:03 +02:00
|
|
|
|
|
2014-04-08 22:39:25 +02:00
|
|
|
|
, "Adherence to Org's rules for markup borders" =:
|
|
|
|
|
"/t/& a/ / ./r/ (*l*) /e/! /b/." =?>
|
|
|
|
|
para (spcSep [ emph $ "t/&" <> space <> "a"
|
|
|
|
|
, "/"
|
|
|
|
|
, "./r/"
|
|
|
|
|
, "(" <> (strong "l") <> ")"
|
|
|
|
|
, (emph "e") <> "!"
|
|
|
|
|
, (emph "b") <> "."
|
|
|
|
|
])
|
|
|
|
|
|
2014-10-18 10:38:39 +02:00
|
|
|
|
, "Quotes are forbidden border chars" =:
|
|
|
|
|
"/'nope/ *nope\"*" =?>
|
|
|
|
|
para ("/'nope/" <> space <> "*nope\"*")
|
|
|
|
|
|
|
|
|
|
, "Commata are forbidden border chars" =:
|
|
|
|
|
"/nada,/" =?>
|
|
|
|
|
para "/nada,/"
|
|
|
|
|
|
2014-09-04 18:14:31 +02:00
|
|
|
|
, "Markup should work properly after a blank line" =:
|
|
|
|
|
unlines ["foo", "", "/bar/"] =?>
|
|
|
|
|
(para $ text "foo") <> (para $ emph $ text "bar")
|
|
|
|
|
|
2014-04-08 22:39:25 +02:00
|
|
|
|
, "Inline math must stay within three lines" =:
|
|
|
|
|
unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?>
|
2015-12-12 21:21:36 +01:00
|
|
|
|
para ((math "a\nb\nc") <> softbreak <>
|
|
|
|
|
"$d" <> softbreak <> "e" <> softbreak <>
|
|
|
|
|
"f" <> softbreak <> "g$")
|
2014-04-08 22:39:25 +02:00
|
|
|
|
|
2014-04-10 15:11:03 +02:00
|
|
|
|
, "Single-character math" =:
|
|
|
|
|
"$a$ $b$! $c$?" =?>
|
|
|
|
|
para (spcSep [ math "a"
|
|
|
|
|
, "$b$!"
|
|
|
|
|
, (math "c") <> "?"
|
|
|
|
|
])
|
|
|
|
|
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, "Markup may not span more than two lines" =:
|
2015-12-12 21:21:36 +01:00
|
|
|
|
"/this *is +totally\nnice+ not*\nemph/" =?>
|
|
|
|
|
para ("/this" <> space <>
|
|
|
|
|
strong ("is" <> space <>
|
|
|
|
|
strikeout ("totally" <>
|
|
|
|
|
softbreak <> "nice") <>
|
|
|
|
|
space <> "not") <>
|
|
|
|
|
softbreak <> "emph/")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
2014-04-11 11:05:42 +02:00
|
|
|
|
, "Sub- and superscript expressions" =:
|
|
|
|
|
unlines [ "a_(a(b)(c)d)"
|
|
|
|
|
, "e^(f(g)h)"
|
|
|
|
|
, "i_(jk)l)"
|
|
|
|
|
, "m^()n"
|
|
|
|
|
, "o_{p{q{}r}}"
|
|
|
|
|
, "s^{t{u}v}"
|
|
|
|
|
, "w_{xy}z}"
|
|
|
|
|
, "1^{}2"
|
|
|
|
|
, "3_{{}}"
|
|
|
|
|
, "4^(a(*b(c*)d))"
|
|
|
|
|
] =?>
|
2015-12-12 21:21:36 +01:00
|
|
|
|
para (mconcat $ intersperse softbreak
|
|
|
|
|
[ "a" <> subscript "(a(b)(c)d)"
|
2014-04-11 11:05:42 +02:00
|
|
|
|
, "e" <> superscript "(f(g)h)"
|
|
|
|
|
, "i" <> (subscript "(jk)") <> "l)"
|
|
|
|
|
, "m" <> (superscript "()") <> "n"
|
|
|
|
|
, "o" <> subscript "p{q{}r}"
|
|
|
|
|
, "s" <> superscript "t{u}v"
|
|
|
|
|
, "w" <> (subscript "xy") <> "z}"
|
|
|
|
|
, "1" <> (superscript "") <> "2"
|
|
|
|
|
, "3" <> subscript "{}"
|
|
|
|
|
, "4" <> superscript ("(a(" <> strong "b(c" <> ")d))")
|
|
|
|
|
])
|
|
|
|
|
|
2014-04-05 16:10:52 +02:00
|
|
|
|
, "Image" =:
|
|
|
|
|
"[[./sunset.jpg]]" =?>
|
|
|
|
|
(para $ image "./sunset.jpg" "" "")
|
|
|
|
|
|
2016-01-31 19:44:45 +01:00
|
|
|
|
, "Image with explicit file: prefix" =:
|
|
|
|
|
"[[file:sunrise.jpg]]" =?>
|
|
|
|
|
(para $ image "sunrise.jpg" "" "")
|
|
|
|
|
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, "Explicit link" =:
|
2014-04-05 16:10:52 +02:00
|
|
|
|
"[[http://zeitlens.com/][pseudo-random /nonsense/]]" =?>
|
2014-03-04 00:33:25 +01:00
|
|
|
|
(para $ link "http://zeitlens.com/" ""
|
2014-04-05 16:10:52 +02:00
|
|
|
|
("pseudo-random" <> space <> emph "nonsense"))
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
|
|
|
|
, "Self-link" =:
|
|
|
|
|
"[[http://zeitlens.com/]]" =?>
|
|
|
|
|
(para $ link "http://zeitlens.com/" "" "http://zeitlens.com/")
|
2014-04-05 16:10:52 +02:00
|
|
|
|
|
2014-11-05 22:27:25 +01:00
|
|
|
|
, "Absolute file link" =:
|
|
|
|
|
"[[/url][hi]]" =?>
|
|
|
|
|
(para $ link "file:///url" "" "hi")
|
|
|
|
|
|
|
|
|
|
, "Link to file in parent directory" =:
|
|
|
|
|
"[[../file.txt][moin]]" =?>
|
|
|
|
|
(para $ link "../file.txt" "" "moin")
|
|
|
|
|
|
2014-11-05 22:49:17 +01:00
|
|
|
|
, "Empty link (for gitit interop)" =:
|
|
|
|
|
"[[][New Link]]" =?>
|
|
|
|
|
(para $ link "" "" "New Link")
|
|
|
|
|
|
2014-04-05 16:10:52 +02:00
|
|
|
|
, "Image link" =:
|
|
|
|
|
"[[sunset.png][dusk.svg]]" =?>
|
|
|
|
|
(para $ link "sunset.png" "" (image "dusk.svg" "" ""))
|
2014-04-24 17:42:01 +02:00
|
|
|
|
|
2015-02-26 13:11:50 +01:00
|
|
|
|
, "Image link with non-image target" =:
|
|
|
|
|
"[[http://example.com][logo.png]]" =?>
|
|
|
|
|
(para $ link "http://example.com" "" (image "logo.png" "" ""))
|
|
|
|
|
|
2014-04-24 17:42:01 +02:00
|
|
|
|
, "Plain link" =:
|
|
|
|
|
"Posts on http://zeitlens.com/ can be funny at times." =?>
|
|
|
|
|
(para $ spcSep [ "Posts", "on"
|
|
|
|
|
, link "http://zeitlens.com/" "" "http://zeitlens.com/"
|
|
|
|
|
, "can", "be", "funny", "at", "times."
|
|
|
|
|
])
|
|
|
|
|
|
|
|
|
|
, "Angle link" =:
|
|
|
|
|
"Look at <http://moltkeplatz.de> for fnords." =?>
|
|
|
|
|
(para $ spcSep [ "Look", "at"
|
|
|
|
|
, link "http://moltkeplatz.de" "" "http://moltkeplatz.de"
|
|
|
|
|
, "for", "fnords."
|
|
|
|
|
])
|
2014-04-25 15:29:28 +02:00
|
|
|
|
|
2014-12-14 18:25:31 +01:00
|
|
|
|
, "Absolute file link" =:
|
|
|
|
|
"[[file:///etc/passwd][passwd]]" =?>
|
|
|
|
|
(para $ link "file:///etc/passwd" "" "passwd")
|
|
|
|
|
|
|
|
|
|
, "File link" =:
|
|
|
|
|
"[[file:target][title]]" =?>
|
|
|
|
|
(para $ link "target" "" "title")
|
|
|
|
|
|
2014-04-25 15:29:28 +02:00
|
|
|
|
, "Anchor" =:
|
|
|
|
|
"<<anchor>> Link here later." =?>
|
|
|
|
|
(para $ spanWith ("anchor", [], []) mempty <>
|
|
|
|
|
"Link" <> space <> "here" <> space <> "later.")
|
2014-05-05 14:39:25 +02:00
|
|
|
|
|
|
|
|
|
, "Inline code block" =:
|
|
|
|
|
"src_emacs-lisp{(message \"Hello\")}" =?>
|
|
|
|
|
(para $ codeWith ( ""
|
|
|
|
|
, [ "commonlisp", "rundoc-block" ]
|
|
|
|
|
, [ ("rundoc-language", "emacs-lisp") ])
|
|
|
|
|
"(message \"Hello\")")
|
|
|
|
|
|
|
|
|
|
, "Inline code block with arguments" =:
|
|
|
|
|
"src_sh[:export both :results output]{echo 'Hello, World'}" =?>
|
|
|
|
|
(para $ codeWith ( ""
|
|
|
|
|
, [ "bash", "rundoc-block" ]
|
|
|
|
|
, [ ("rundoc-language", "sh")
|
|
|
|
|
, ("rundoc-export", "both")
|
|
|
|
|
, ("rundoc-results", "output")
|
|
|
|
|
]
|
|
|
|
|
)
|
|
|
|
|
"echo 'Hello, World'")
|
2014-05-14 14:49:30 +02:00
|
|
|
|
|
2015-10-25 08:51:53 +01:00
|
|
|
|
, "Inline code block with toggle" =:
|
|
|
|
|
"src_sh[:toggle]{echo $HOME}" =?>
|
|
|
|
|
(para $ codeWith ( ""
|
|
|
|
|
, [ "bash", "rundoc-block" ]
|
|
|
|
|
, [ ("rundoc-language", "sh")
|
|
|
|
|
, ("rundoc-toggle", "yes")
|
|
|
|
|
]
|
|
|
|
|
)
|
|
|
|
|
"echo $HOME")
|
|
|
|
|
|
2014-05-14 14:49:30 +02:00
|
|
|
|
, "Citation" =:
|
|
|
|
|
"[@nonexistent]" =?>
|
|
|
|
|
let citation = Citation
|
|
|
|
|
{ citationId = "nonexistent"
|
|
|
|
|
, citationPrefix = []
|
|
|
|
|
, citationSuffix = []
|
|
|
|
|
, citationMode = NormalCitation
|
|
|
|
|
, citationNoteNum = 0
|
|
|
|
|
, citationHash = 0}
|
|
|
|
|
in (para $ cite [citation] "[@nonexistent]")
|
|
|
|
|
|
|
|
|
|
, "Citation containing text" =:
|
|
|
|
|
"[see @item1 p. 34-35]" =?>
|
|
|
|
|
let citation = Citation
|
|
|
|
|
{ citationId = "item1"
|
|
|
|
|
, citationPrefix = [Str "see"]
|
|
|
|
|
, citationSuffix = [Space ,Str "p.",Space,Str "34-35"]
|
|
|
|
|
, citationMode = NormalCitation
|
|
|
|
|
, citationNoteNum = 0
|
|
|
|
|
, citationHash = 0}
|
|
|
|
|
in (para $ cite [citation] "[see @item1 p. 34-35]")
|
2014-05-20 22:29:21 +02:00
|
|
|
|
|
|
|
|
|
, "Inline LaTeX symbol" =:
|
|
|
|
|
"\\dots" =?>
|
|
|
|
|
para "…"
|
|
|
|
|
|
|
|
|
|
, "Inline LaTeX command" =:
|
|
|
|
|
"\\textit{Emphasised}" =?>
|
|
|
|
|
para (emph "Emphasised")
|
|
|
|
|
|
|
|
|
|
, "Inline LaTeX math symbol" =:
|
|
|
|
|
"\\tau" =?>
|
|
|
|
|
para (emph "τ")
|
|
|
|
|
|
|
|
|
|
, "Unknown inline LaTeX command" =:
|
|
|
|
|
"\\notacommand{foo}" =?>
|
|
|
|
|
para (rawInline "latex" "\\notacommand{foo}")
|
|
|
|
|
|
2014-10-20 19:54:21 +02:00
|
|
|
|
, "MathML symbol in LaTeX-style" =:
|
|
|
|
|
"There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: '\\nbsp')." =?>
|
|
|
|
|
para ("There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: ' ').")
|
|
|
|
|
|
|
|
|
|
, "MathML symbol in LaTeX-style, including braces" =:
|
|
|
|
|
"\\Aacute{}stor" =?>
|
|
|
|
|
para "Ástor"
|
|
|
|
|
|
|
|
|
|
, "MathML copy sign" =:
|
|
|
|
|
"\\copy" =?>
|
|
|
|
|
para "©"
|
|
|
|
|
|
2014-05-20 22:29:21 +02:00
|
|
|
|
, "LaTeX citation" =:
|
|
|
|
|
"\\cite{Coffee}" =?>
|
|
|
|
|
let citation = Citation
|
|
|
|
|
{ citationId = "Coffee"
|
|
|
|
|
, citationPrefix = []
|
|
|
|
|
, citationSuffix = []
|
|
|
|
|
, citationMode = AuthorInText
|
|
|
|
|
, citationNoteNum = 0
|
|
|
|
|
, citationHash = 0}
|
|
|
|
|
in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, testGroup "Meta Information" $
|
|
|
|
|
[ "Comment" =:
|
|
|
|
|
"# Nothing to see here" =?>
|
|
|
|
|
(mempty::Blocks)
|
|
|
|
|
|
|
|
|
|
, "Not a comment" =:
|
|
|
|
|
"#-tag" =?>
|
|
|
|
|
para "#-tag"
|
|
|
|
|
|
|
|
|
|
, "Comment surrounded by Text" =:
|
|
|
|
|
unlines [ "Before"
|
|
|
|
|
, "# Comment"
|
|
|
|
|
, "After"
|
|
|
|
|
] =?>
|
|
|
|
|
mconcat [ para "Before"
|
|
|
|
|
, para "After"
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Title" =:
|
|
|
|
|
"#+TITLE: Hello, World" =?>
|
|
|
|
|
let titleInline = toList $ "Hello," <> space <> "World"
|
|
|
|
|
meta = setMeta "title" (MetaInlines titleInline) $ nullMeta
|
|
|
|
|
in Pandoc meta mempty
|
|
|
|
|
|
|
|
|
|
, "Author" =:
|
|
|
|
|
"#+author: Albert /Emacs-Fanboy/ Krewinkel" =?>
|
|
|
|
|
let author = toList . spcSep $ [ "Albert", emph "Emacs-Fanboy", "Krewinkel" ]
|
|
|
|
|
meta = setMeta "author" (MetaInlines author) $ nullMeta
|
|
|
|
|
in Pandoc meta mempty
|
|
|
|
|
|
|
|
|
|
, "Date" =:
|
|
|
|
|
"#+Date: Feb. *28*, 2014" =?>
|
|
|
|
|
let date = toList . spcSep $ [ "Feb.", (strong "28") <> ",", "2014" ]
|
|
|
|
|
meta = setMeta "date" (MetaInlines date) $ nullMeta
|
|
|
|
|
in Pandoc meta mempty
|
|
|
|
|
|
|
|
|
|
, "Description" =:
|
|
|
|
|
"#+DESCRIPTION: Explanatory text" =?>
|
|
|
|
|
let description = toList . spcSep $ [ "Explanatory", "text" ]
|
|
|
|
|
meta = setMeta "description" (MetaInlines description) $ nullMeta
|
|
|
|
|
in Pandoc meta mempty
|
|
|
|
|
|
|
|
|
|
, "Properties drawer" =:
|
|
|
|
|
unlines [ " :PROPERTIES:"
|
|
|
|
|
, " :setting: foo"
|
|
|
|
|
, " :END:"
|
|
|
|
|
] =?>
|
|
|
|
|
(mempty::Blocks)
|
|
|
|
|
|
|
|
|
|
, "Logbook drawer" =:
|
|
|
|
|
unlines [ " :LogBook:"
|
|
|
|
|
, " - State \"DONE\" from \"TODO\" [2014-03-03 Mon 11:00]"
|
|
|
|
|
, " :END:"
|
|
|
|
|
] =?>
|
|
|
|
|
(mempty::Blocks)
|
|
|
|
|
|
|
|
|
|
, "Drawer surrounded by text" =:
|
|
|
|
|
unlines [ "Before"
|
|
|
|
|
, ":PROPERTIES:"
|
|
|
|
|
, ":END:"
|
|
|
|
|
, "After"
|
|
|
|
|
] =?>
|
|
|
|
|
para "Before" <> para "After"
|
|
|
|
|
|
|
|
|
|
, "Drawer start is the only text in first line of a drawer" =:
|
|
|
|
|
unlines [ " :LOGBOOK: foo"
|
|
|
|
|
, " :END:"
|
|
|
|
|
] =?>
|
2015-12-12 21:21:36 +01:00
|
|
|
|
para (":LOGBOOK:" <> space <> "foo" <> softbreak <> ":END:")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
|
|
|
|
, "Drawers with unknown names are just text" =:
|
|
|
|
|
unlines [ ":FOO:"
|
|
|
|
|
, ":END:"
|
|
|
|
|
] =?>
|
2015-12-12 21:21:36 +01:00
|
|
|
|
para (":FOO:" <> softbreak <> ":END:")
|
2014-04-25 15:29:28 +02:00
|
|
|
|
|
|
|
|
|
, "Anchor reference" =:
|
|
|
|
|
unlines [ "<<link-here>> Target."
|
|
|
|
|
, ""
|
|
|
|
|
, "[[link-here][See here!]]"
|
|
|
|
|
] =?>
|
|
|
|
|
(para (spanWith ("link-here", [], []) mempty <> "Target.") <>
|
|
|
|
|
para (link "#link-here" "" ("See" <> space <> "here!")))
|
|
|
|
|
|
|
|
|
|
, "Search links are read as emph" =:
|
|
|
|
|
"[[Wally][Where's Wally?]]" =?>
|
|
|
|
|
(para (emph $ "Where's" <> space <> "Wally?"))
|
|
|
|
|
|
|
|
|
|
, "Link to nonexistent anchor" =:
|
|
|
|
|
unlines [ "<<link-here>> Target."
|
|
|
|
|
, ""
|
|
|
|
|
, "[[link$here][See here!]]"
|
|
|
|
|
] =?>
|
|
|
|
|
(para (spanWith ("link-here", [], []) mempty <> "Target.") <>
|
|
|
|
|
para (emph ("See" <> space <> "here!")))
|
2014-04-30 11:16:01 +02:00
|
|
|
|
|
|
|
|
|
, "Link abbreviation" =:
|
|
|
|
|
unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s"
|
|
|
|
|
, "[[wp:Org_mode][Wikipedia on Org-mode]]"
|
|
|
|
|
] =?>
|
|
|
|
|
(para (link "https://en.wikipedia.org/wiki/Org_mode" ""
|
|
|
|
|
("Wikipedia" <> space <> "on" <> space <> "Org-mode")))
|
|
|
|
|
|
|
|
|
|
, "Link abbreviation, defined after first use" =:
|
|
|
|
|
unlines [ "[[zl:non-sense][Non-sense articles]]"
|
|
|
|
|
, "#+LINK: zl http://zeitlens.com/tags/%s.html"
|
|
|
|
|
] =?>
|
|
|
|
|
(para (link "http://zeitlens.com/tags/non-sense.html" ""
|
|
|
|
|
("Non-sense" <> space <> "articles")))
|
|
|
|
|
|
|
|
|
|
, "Link abbreviation, URL encoded arguments" =:
|
|
|
|
|
unlines [ "#+link: expl http://example.com/%h/foo"
|
|
|
|
|
, "[[expl:Hello, World!][Moin!]]"
|
|
|
|
|
] =?>
|
|
|
|
|
(para (link "http://example.com/Hello%2C%20World%21/foo" "" "Moin!"))
|
|
|
|
|
|
|
|
|
|
, "Link abbreviation, append arguments" =:
|
|
|
|
|
unlines [ "#+link: expl http://example.com/"
|
|
|
|
|
, "[[expl:foo][bar]]"
|
|
|
|
|
] =?>
|
|
|
|
|
(para (link "http://example.com/foo" "" "bar"))
|
2014-03-04 00:33:25 +01:00
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, testGroup "Basic Blocks" $
|
|
|
|
|
[ "Paragraph" =:
|
|
|
|
|
"Paragraph\n" =?>
|
|
|
|
|
para "Paragraph"
|
|
|
|
|
|
|
|
|
|
, "First Level Header" =:
|
|
|
|
|
"* Headline\n" =?>
|
2015-08-15 07:54:38 +02:00
|
|
|
|
headerWith ("headline", [], []) 1 "Headline"
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
|
|
|
|
, "Third Level Header" =:
|
|
|
|
|
"*** Third Level Headline\n" =?>
|
2015-08-15 07:54:38 +02:00
|
|
|
|
headerWith ("third-level-headline", [], [])
|
|
|
|
|
3
|
|
|
|
|
("Third" <> space <> "Level" <> space <> "Headline")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
|
|
|
|
, "Compact Headers with Paragraph" =:
|
|
|
|
|
unlines [ "* First Level"
|
|
|
|
|
, "** Second Level"
|
|
|
|
|
, " Text"
|
|
|
|
|
] =?>
|
2015-08-15 07:54:38 +02:00
|
|
|
|
mconcat [ headerWith ("first-level", [], [])
|
|
|
|
|
1
|
|
|
|
|
("First" <> space <> "Level")
|
|
|
|
|
, headerWith ("second-level", [], [])
|
|
|
|
|
2
|
|
|
|
|
("Second" <> space <> "Level")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, para "Text"
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Separated Headers with Paragraph" =:
|
|
|
|
|
unlines [ "* First Level"
|
|
|
|
|
, ""
|
|
|
|
|
, "** Second Level"
|
|
|
|
|
, ""
|
|
|
|
|
, " Text"
|
|
|
|
|
] =?>
|
2015-08-15 07:54:38 +02:00
|
|
|
|
mconcat [ headerWith ("first-level", [], [])
|
|
|
|
|
1
|
|
|
|
|
("First" <> space <> "Level")
|
|
|
|
|
, headerWith ("second-level", [], [])
|
|
|
|
|
2
|
|
|
|
|
("Second" <> space <> "Level")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, para "Text"
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Headers not preceded by a blank line" =:
|
|
|
|
|
unlines [ "** eat dinner"
|
|
|
|
|
, "Spaghetti and meatballs tonight."
|
|
|
|
|
, "** walk dog"
|
|
|
|
|
] =?>
|
2015-08-15 07:54:38 +02:00
|
|
|
|
mconcat [ headerWith ("eat-dinner", [], [])
|
|
|
|
|
2
|
|
|
|
|
("eat" <> space <> "dinner")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, para $ spcSep [ "Spaghetti", "and", "meatballs", "tonight." ]
|
2015-08-15 07:54:38 +02:00
|
|
|
|
, headerWith ("walk-dog", [], [])
|
|
|
|
|
2
|
|
|
|
|
("walk" <> space <> "dog")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
]
|
|
|
|
|
|
2015-05-20 18:01:03 +02:00
|
|
|
|
, "Tagged headers" =:
|
|
|
|
|
unlines [ "* Personal :PERSONAL:"
|
|
|
|
|
, "** Call Mom :@PHONE:"
|
|
|
|
|
, "** Call John :@PHONE:JOHN: "
|
|
|
|
|
] =?>
|
|
|
|
|
let tagSpan t = spanWith ("", ["tag"], [("data-tag-name", t)]) mempty
|
2015-08-15 07:54:38 +02:00
|
|
|
|
in mconcat [ headerWith ("personal", [], [])
|
|
|
|
|
1
|
|
|
|
|
("Personal" <> tagSpan "PERSONAL")
|
|
|
|
|
, headerWith ("call-mom", [], [])
|
|
|
|
|
2
|
|
|
|
|
("Call Mom" <> tagSpan "@PHONE")
|
|
|
|
|
, headerWith ("call-john", [], [])
|
|
|
|
|
2
|
|
|
|
|
("Call John" <> tagSpan "@PHONE" <> tagSpan "JOHN")
|
2015-05-20 18:01:03 +02:00
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Untagged header containing colons" =:
|
|
|
|
|
"* This: is not: tagged" =?>
|
2015-08-15 07:54:38 +02:00
|
|
|
|
headerWith ("this-is-not-tagged", [], []) 1 "This: is not: tagged"
|
2015-05-20 18:01:03 +02:00
|
|
|
|
|
2015-11-08 22:23:47 +01:00
|
|
|
|
, "Header starting with strokeout text" =:
|
|
|
|
|
unlines [ "foo"
|
|
|
|
|
, ""
|
|
|
|
|
, "* +thing+ other thing"
|
|
|
|
|
] =?>
|
|
|
|
|
mconcat [ para "foo"
|
|
|
|
|
, headerWith ("thing-other-thing", [], [])
|
|
|
|
|
1
|
|
|
|
|
((strikeout "thing") <> " other thing")
|
|
|
|
|
]
|
|
|
|
|
|
2014-10-18 21:59:44 +02:00
|
|
|
|
, "Comment Trees" =:
|
|
|
|
|
unlines [ "* COMMENT A comment tree"
|
|
|
|
|
, " Not much going on here"
|
|
|
|
|
, "** This will be dropped"
|
|
|
|
|
, "* Comment tree above"
|
|
|
|
|
] =?>
|
2015-08-15 07:54:38 +02:00
|
|
|
|
headerWith ("comment-tree-above", [], []) 1 "Comment tree above"
|
2014-10-18 21:59:44 +02:00
|
|
|
|
|
|
|
|
|
, "Nothing but a COMMENT header" =:
|
|
|
|
|
"* COMMENT Test" =?>
|
|
|
|
|
(mempty::Blocks)
|
|
|
|
|
|
2015-05-23 14:20:17 +02:00
|
|
|
|
, "Tree with :noexport:" =:
|
|
|
|
|
unlines [ "* Should be ignored :archive:noexport:old:"
|
|
|
|
|
, "** Old stuff"
|
|
|
|
|
, " This is not going to be exported"
|
|
|
|
|
] =?>
|
|
|
|
|
(mempty::Blocks)
|
|
|
|
|
|
2016-01-07 19:56:44 +01:00
|
|
|
|
, "Subtree with :noexport:" =:
|
|
|
|
|
unlines [ "* Exported"
|
|
|
|
|
, "** This isn't exported :noexport:"
|
|
|
|
|
, "*** This neither"
|
|
|
|
|
, "** But this is"
|
|
|
|
|
] =?>
|
|
|
|
|
mconcat [ headerWith ("exported", [], []) 1 "Exported"
|
|
|
|
|
, headerWith ("but-this-is", [], []) 2 "But this is"
|
|
|
|
|
]
|
|
|
|
|
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, "Paragraph starting with an asterisk" =:
|
|
|
|
|
"*five" =?>
|
|
|
|
|
para "*five"
|
|
|
|
|
|
|
|
|
|
, "Paragraph containing asterisk at beginning of line" =:
|
|
|
|
|
unlines [ "lucky"
|
|
|
|
|
, "*star"
|
|
|
|
|
] =?>
|
2015-12-12 21:21:36 +01:00
|
|
|
|
para ("lucky" <> softbreak <> "*star")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
|
|
|
|
, "Example block" =:
|
|
|
|
|
unlines [ ": echo hello"
|
|
|
|
|
, ": echo dear tester"
|
|
|
|
|
] =?>
|
|
|
|
|
codeBlockWith ("", ["example"], []) "echo hello\necho dear tester\n"
|
|
|
|
|
|
|
|
|
|
, "Example block surrounded by text" =:
|
|
|
|
|
unlines [ "Greetings"
|
|
|
|
|
, ": echo hello"
|
|
|
|
|
, ": echo dear tester"
|
|
|
|
|
, "Bye"
|
|
|
|
|
] =?>
|
|
|
|
|
mconcat [ para "Greetings"
|
|
|
|
|
, codeBlockWith ("", ["example"], [])
|
|
|
|
|
"echo hello\necho dear tester\n"
|
|
|
|
|
, para "Bye"
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Horizontal Rule" =:
|
|
|
|
|
unlines [ "before"
|
|
|
|
|
, "-----"
|
|
|
|
|
, "after"
|
|
|
|
|
] =?>
|
|
|
|
|
mconcat [ para "before"
|
|
|
|
|
, horizontalRule
|
|
|
|
|
, para "after"
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Not a Horizontal Rule" =:
|
|
|
|
|
"----- five dashes" =?>
|
|
|
|
|
(para $ spcSep [ "-----", "five", "dashes" ])
|
|
|
|
|
|
|
|
|
|
, "Comment Block" =:
|
|
|
|
|
unlines [ "#+BEGIN_COMMENT"
|
|
|
|
|
, "stuff"
|
|
|
|
|
, "bla"
|
|
|
|
|
, "#+END_COMMENT"] =?>
|
|
|
|
|
(mempty::Blocks)
|
|
|
|
|
|
2014-04-12 00:17:46 +02:00
|
|
|
|
, "Figure" =:
|
|
|
|
|
unlines [ "#+caption: A very courageous man."
|
|
|
|
|
, "#+name: goodguy"
|
|
|
|
|
, "[[edward.jpg]]"
|
|
|
|
|
] =?>
|
|
|
|
|
para (image "edward.jpg" "fig:goodguy" "A very courageous man.")
|
|
|
|
|
|
2016-01-11 22:18:04 +01:00
|
|
|
|
, "Figure with no name" =:
|
|
|
|
|
unlines [ "#+caption: I've been through the desert on this"
|
|
|
|
|
, "[[horse.png]]"
|
2014-04-12 00:17:46 +02:00
|
|
|
|
] =?>
|
2016-01-11 22:18:04 +01:00
|
|
|
|
para (image "horse.png" "fig:" "I've been through the desert on this")
|
2014-04-12 00:17:46 +02:00
|
|
|
|
|
|
|
|
|
, "Figure with `fig:` prefix in name" =:
|
|
|
|
|
unlines [ "#+caption: Used as a metapher in evolutionary biology."
|
|
|
|
|
, "#+name: fig:redqueen"
|
|
|
|
|
, "[[the-red-queen.jpg]]"
|
|
|
|
|
] =?>
|
|
|
|
|
para (image "the-red-queen.jpg" "fig:redqueen"
|
|
|
|
|
"Used as a metapher in evolutionary biology.")
|
2014-04-19 13:15:47 +02:00
|
|
|
|
|
|
|
|
|
, "Footnote" =:
|
|
|
|
|
unlines [ "A footnote[1]"
|
|
|
|
|
, ""
|
|
|
|
|
, "[1] First paragraph"
|
|
|
|
|
, ""
|
|
|
|
|
, "second paragraph"
|
|
|
|
|
] =?>
|
|
|
|
|
para (mconcat
|
|
|
|
|
[ "A", space, "footnote"
|
|
|
|
|
, note $ mconcat [ para ("First" <> space <> "paragraph")
|
|
|
|
|
, para ("second" <> space <> "paragraph")
|
|
|
|
|
]
|
|
|
|
|
])
|
|
|
|
|
|
|
|
|
|
, "Two footnotes" =:
|
|
|
|
|
unlines [ "Footnotes[fn:1][fn:2]"
|
|
|
|
|
, ""
|
|
|
|
|
, "[fn:1] First note."
|
|
|
|
|
, ""
|
|
|
|
|
, "[fn:2] Second note."
|
|
|
|
|
] =?>
|
|
|
|
|
para (mconcat
|
|
|
|
|
[ "Footnotes"
|
|
|
|
|
, note $ para ("First" <> space <> "note.")
|
|
|
|
|
, note $ para ("Second" <> space <> "note.")
|
|
|
|
|
])
|
|
|
|
|
|
|
|
|
|
, "Footnote followed by header" =:
|
|
|
|
|
unlines [ "Another note[fn:yay]"
|
|
|
|
|
, ""
|
|
|
|
|
, "[fn:yay] This is great!"
|
|
|
|
|
, ""
|
|
|
|
|
, "** Headline"
|
|
|
|
|
] =?>
|
|
|
|
|
mconcat
|
|
|
|
|
[ para (mconcat
|
|
|
|
|
[ "Another", space, "note"
|
|
|
|
|
, note $ para ("This" <> space <> "is" <> space <> "great!")
|
|
|
|
|
])
|
2015-08-15 07:54:38 +02:00
|
|
|
|
, headerWith ("headline", [], []) 2 "Headline"
|
2014-04-19 13:15:47 +02:00
|
|
|
|
]
|
2014-03-04 00:33:25 +01:00
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, testGroup "Lists" $
|
|
|
|
|
[ "Simple Bullet Lists" =:
|
|
|
|
|
("- Item1\n" ++
|
|
|
|
|
"- Item2\n") =?>
|
|
|
|
|
bulletList [ plain "Item1"
|
|
|
|
|
, plain "Item2"
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Indented Bullet Lists" =:
|
|
|
|
|
(" - Item1\n" ++
|
|
|
|
|
" - Item2\n") =?>
|
|
|
|
|
bulletList [ plain "Item1"
|
|
|
|
|
, plain "Item2"
|
|
|
|
|
]
|
|
|
|
|
|
2014-11-14 08:40:18 +01:00
|
|
|
|
, "Unindented *" =:
|
|
|
|
|
("- Item1\n" ++
|
|
|
|
|
"* Item2\n") =?>
|
|
|
|
|
bulletList [ plain "Item1"
|
|
|
|
|
] <>
|
2015-08-15 07:54:38 +02:00
|
|
|
|
headerWith ("item2", [], []) 1 "Item2"
|
2014-11-14 08:40:18 +01:00
|
|
|
|
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, "Multi-line Bullet Lists" =:
|
|
|
|
|
("- *Fat\n" ++
|
|
|
|
|
" Tony*\n" ++
|
|
|
|
|
"- /Sideshow\n" ++
|
|
|
|
|
" Bob/") =?>
|
2015-12-12 21:21:36 +01:00
|
|
|
|
bulletList [ plain $ strong ("Fat" <> softbreak <> "Tony")
|
|
|
|
|
, plain $ emph ("Sideshow" <> softbreak <> "Bob")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Nested Bullet Lists" =:
|
|
|
|
|
("- Discovery\n" ++
|
|
|
|
|
" + One More Time\n" ++
|
|
|
|
|
" + Harder, Better, Faster, Stronger\n" ++
|
|
|
|
|
"- Homework\n" ++
|
|
|
|
|
" + Around the World\n"++
|
|
|
|
|
"- Human After All\n" ++
|
|
|
|
|
" + Technologic\n" ++
|
|
|
|
|
" + Robot Rock\n") =?>
|
|
|
|
|
bulletList [ mconcat
|
2014-07-20 21:56:01 +02:00
|
|
|
|
[ plain "Discovery"
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, bulletList [ plain ("One" <> space <>
|
|
|
|
|
"More" <> space <>
|
|
|
|
|
"Time")
|
|
|
|
|
, plain ("Harder," <> space <>
|
|
|
|
|
"Better," <> space <>
|
|
|
|
|
"Faster," <> space <>
|
|
|
|
|
"Stronger")
|
|
|
|
|
]
|
|
|
|
|
]
|
|
|
|
|
, mconcat
|
2014-07-20 21:56:01 +02:00
|
|
|
|
[ plain "Homework"
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, bulletList [ plain ("Around" <> space <>
|
|
|
|
|
"the" <> space <>
|
|
|
|
|
"World")
|
|
|
|
|
]
|
|
|
|
|
]
|
|
|
|
|
, mconcat
|
2014-07-20 21:56:01 +02:00
|
|
|
|
[ plain ("Human" <> space <> "After" <> space <> "All")
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, bulletList [ plain "Technologic"
|
|
|
|
|
, plain ("Robot" <> space <> "Rock")
|
|
|
|
|
]
|
|
|
|
|
]
|
|
|
|
|
]
|
|
|
|
|
|
2014-10-12 09:18:36 +02:00
|
|
|
|
, "Bullet List with Decreasing Indent" =:
|
|
|
|
|
(" - Discovery\n\
|
|
|
|
|
\ - Human After All\n") =?>
|
|
|
|
|
mconcat [ bulletList [ plain "Discovery" ]
|
|
|
|
|
, bulletList [ plain ("Human" <> space <> "After" <> space <> "All")]
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Header follows Bullet List" =:
|
|
|
|
|
(" - Discovery\n\
|
|
|
|
|
\ - Human After All\n\
|
|
|
|
|
\* Homework") =?>
|
|
|
|
|
mconcat [ bulletList [ plain "Discovery"
|
|
|
|
|
, plain ("Human" <> space <> "After" <> space <> "All")
|
|
|
|
|
]
|
2015-08-15 07:54:38 +02:00
|
|
|
|
, headerWith ("homework", [], []) 1 "Homework"
|
2014-10-12 09:18:36 +02:00
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Bullet List Unindented with trailing Header" =:
|
|
|
|
|
("- Discovery\n\
|
|
|
|
|
\- Homework\n\
|
|
|
|
|
\* NotValidListItem") =?>
|
|
|
|
|
mconcat [ bulletList [ plain "Discovery"
|
|
|
|
|
, plain "Homework"
|
|
|
|
|
]
|
2015-08-15 07:54:38 +02:00
|
|
|
|
, headerWith ("notvalidlistitem", [], []) 1 "NotValidListItem"
|
2014-10-12 09:18:36 +02:00
|
|
|
|
]
|
2014-03-04 00:33:25 +01:00
|
|
|
|
|
|
|
|
|
, "Simple Ordered List" =:
|
|
|
|
|
("1. Item1\n" ++
|
|
|
|
|
"2. Item2\n") =?>
|
|
|
|
|
let listStyle = (1, DefaultStyle, DefaultDelim)
|
|
|
|
|
listStructure = [ plain "Item1"
|
|
|
|
|
, plain "Item2"
|
|
|
|
|
]
|
|
|
|
|
in orderedListWith listStyle listStructure
|
|
|
|
|
|
|
|
|
|
, "Simple Ordered List with Parens" =:
|
|
|
|
|
("1) Item1\n" ++
|
|
|
|
|
"2) Item2\n") =?>
|
|
|
|
|
let listStyle = (1, DefaultStyle, DefaultDelim)
|
|
|
|
|
listStructure = [ plain "Item1"
|
|
|
|
|
, plain "Item2"
|
|
|
|
|
]
|
|
|
|
|
in orderedListWith listStyle listStructure
|
|
|
|
|
|
|
|
|
|
, "Indented Ordered List" =:
|
|
|
|
|
(" 1. Item1\n" ++
|
|
|
|
|
" 2. Item2\n") =?>
|
|
|
|
|
let listStyle = (1, DefaultStyle, DefaultDelim)
|
|
|
|
|
listStructure = [ plain "Item1"
|
|
|
|
|
, plain "Item2"
|
|
|
|
|
]
|
|
|
|
|
in orderedListWith listStyle listStructure
|
|
|
|
|
|
|
|
|
|
, "Nested Ordered Lists" =:
|
|
|
|
|
("1. One\n" ++
|
|
|
|
|
" 1. One-One\n" ++
|
|
|
|
|
" 2. One-Two\n" ++
|
|
|
|
|
"2. Two\n" ++
|
|
|
|
|
" 1. Two-One\n"++
|
|
|
|
|
" 2. Two-Two\n") =?>
|
|
|
|
|
let listStyle = (1, DefaultStyle, DefaultDelim)
|
|
|
|
|
listStructure = [ mconcat
|
2014-07-20 21:56:01 +02:00
|
|
|
|
[ plain "One"
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, orderedList [ plain "One-One"
|
|
|
|
|
, plain "One-Two"
|
|
|
|
|
]
|
|
|
|
|
]
|
|
|
|
|
, mconcat
|
2014-07-20 21:56:01 +02:00
|
|
|
|
[ plain "Two"
|
2014-03-04 00:33:25 +01:00
|
|
|
|
, orderedList [ plain "Two-One"
|
|
|
|
|
, plain "Two-Two"
|
|
|
|
|
]
|
|
|
|
|
]
|
|
|
|
|
]
|
|
|
|
|
in orderedListWith listStyle listStructure
|
|
|
|
|
|
|
|
|
|
, "Ordered List in Bullet List" =:
|
|
|
|
|
("- Emacs\n" ++
|
|
|
|
|
" 1. Org\n") =?>
|
2014-07-20 21:56:01 +02:00
|
|
|
|
bulletList [ (plain "Emacs") <>
|
2014-03-04 00:33:25 +01:00
|
|
|
|
(orderedList [ plain "Org"])
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Bullet List in Ordered List" =:
|
|
|
|
|
("1. GNU\n" ++
|
|
|
|
|
" - Freedom\n") =?>
|
2014-07-20 21:56:01 +02:00
|
|
|
|
orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ]
|
2014-04-06 14:49:57 +02:00
|
|
|
|
|
|
|
|
|
, "Definition List" =:
|
|
|
|
|
unlines [ "- PLL :: phase-locked loop"
|
|
|
|
|
, "- TTL ::"
|
|
|
|
|
, " transistor-transistor logic"
|
2015-11-13 21:25:11 +01:00
|
|
|
|
, "- PSK :: phase-shift keying"
|
2014-04-06 14:49:57 +02:00
|
|
|
|
, ""
|
|
|
|
|
, " a digital modulation scheme"
|
|
|
|
|
] =?>
|
|
|
|
|
definitionList [ ("PLL", [ plain $ "phase-locked" <> space <> "loop" ])
|
|
|
|
|
, ("TTL", [ plain $ "transistor-transistor" <> space <>
|
|
|
|
|
"logic" ])
|
|
|
|
|
, ("PSK", [ mconcat
|
2014-04-18 08:33:25 +02:00
|
|
|
|
[ para $ "phase-shift" <> space <> "keying"
|
|
|
|
|
, para $ spcSep [ "a", "digital"
|
|
|
|
|
, "modulation", "scheme" ]
|
2014-04-06 14:49:57 +02:00
|
|
|
|
]
|
2014-04-18 08:33:25 +02:00
|
|
|
|
])
|
2014-04-06 14:49:57 +02:00
|
|
|
|
]
|
2014-09-27 23:38:58 +02:00
|
|
|
|
, "Definition list with multi-word term" =:
|
|
|
|
|
" - Elijah Wood :: He plays Frodo" =?>
|
|
|
|
|
definitionList [ ("Elijah" <> space <> "Wood", [plain $ "He" <> space <> "plays" <> space <> "Frodo"])]
|
2014-04-19 15:05:03 +02:00
|
|
|
|
, "Compact definition list" =:
|
|
|
|
|
unlines [ "- ATP :: adenosine 5' triphosphate"
|
|
|
|
|
, "- DNA :: deoxyribonucleic acid"
|
|
|
|
|
, "- PCR :: polymerase chain reaction"
|
|
|
|
|
, ""
|
|
|
|
|
] =?>
|
|
|
|
|
definitionList
|
|
|
|
|
[ ("ATP", [ plain $ spcSep [ "adenosine", "5'", "triphosphate" ] ])
|
|
|
|
|
, ("DNA", [ plain $ spcSep [ "deoxyribonucleic", "acid" ] ])
|
|
|
|
|
, ("PCR", [ plain $ spcSep [ "polymerase", "chain", "reaction" ] ])
|
|
|
|
|
]
|
|
|
|
|
|
2014-10-18 02:06:25 +02:00
|
|
|
|
, "Definition List With Trailing Header" =:
|
|
|
|
|
"- definition :: list\n\
|
|
|
|
|
\- cool :: defs\n\
|
|
|
|
|
\* header" =?>
|
|
|
|
|
mconcat [ definitionList [ ("definition", [plain "list"])
|
|
|
|
|
, ("cool", [plain "defs"])
|
|
|
|
|
]
|
2015-08-15 07:54:38 +02:00
|
|
|
|
, headerWith ("header", [], []) 1 "header"
|
2014-10-18 02:06:25 +02:00
|
|
|
|
]
|
|
|
|
|
|
2015-11-13 21:25:11 +01:00
|
|
|
|
, "Definition lists double-colon markers must be surrounded by whitespace" =:
|
|
|
|
|
"- std::cout" =?>
|
|
|
|
|
bulletList [ plain "std::cout" ]
|
|
|
|
|
|
2014-04-18 08:33:25 +02:00
|
|
|
|
, "Loose bullet list" =:
|
|
|
|
|
unlines [ "- apple"
|
|
|
|
|
, ""
|
|
|
|
|
, "- orange"
|
|
|
|
|
, ""
|
|
|
|
|
, "- peach"
|
|
|
|
|
] =?>
|
|
|
|
|
bulletList [ para "apple"
|
|
|
|
|
, para "orange"
|
|
|
|
|
, para "peach"
|
|
|
|
|
]
|
2015-10-24 18:04:29 +02:00
|
|
|
|
|
|
|
|
|
, "Recognize preceding paragraphs in non-list contexts" =:
|
|
|
|
|
unlines [ "CLOSED: [2015-10-19 Mon 15:03]"
|
|
|
|
|
, "- Note taken on [2015-10-19 Mon 13:24]"
|
|
|
|
|
] =?>
|
|
|
|
|
mconcat [ para "CLOSED: [2015-10-19 Mon 15:03]"
|
|
|
|
|
, bulletList [ plain "Note taken on [2015-10-19 Mon 13:24]" ]
|
|
|
|
|
]
|
2014-03-04 00:33:25 +01:00
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, testGroup "Tables"
|
|
|
|
|
[ "Single cell table" =:
|
|
|
|
|
"|Test|" =?>
|
|
|
|
|
simpleTable' 1 mempty [[plain "Test"]]
|
|
|
|
|
|
|
|
|
|
, "Multi cell table" =:
|
|
|
|
|
"| One | Two |" =?>
|
|
|
|
|
simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ]
|
|
|
|
|
|
|
|
|
|
, "Multi line table" =:
|
|
|
|
|
unlines [ "| One |"
|
|
|
|
|
, "| Two |"
|
|
|
|
|
, "| Three |"
|
|
|
|
|
] =?>
|
|
|
|
|
simpleTable' 1 mempty
|
|
|
|
|
[ [ plain "One" ]
|
|
|
|
|
, [ plain "Two" ]
|
|
|
|
|
, [ plain "Three" ]
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Empty table" =:
|
|
|
|
|
"||" =?>
|
|
|
|
|
simpleTable' 1 mempty mempty
|
|
|
|
|
|
|
|
|
|
, "Glider Table" =:
|
|
|
|
|
unlines [ "| 1 | 0 | 0 |"
|
|
|
|
|
, "| 0 | 1 | 1 |"
|
|
|
|
|
, "| 1 | 1 | 0 |"
|
|
|
|
|
] =?>
|
|
|
|
|
simpleTable' 3 mempty
|
|
|
|
|
[ [ plain "1", plain "0", plain "0" ]
|
|
|
|
|
, [ plain "0", plain "1", plain "1" ]
|
|
|
|
|
, [ plain "1", plain "1", plain "0" ]
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Table between Paragraphs" =:
|
|
|
|
|
unlines [ "Before"
|
|
|
|
|
, "| One | Two |"
|
|
|
|
|
, "After"
|
|
|
|
|
] =?>
|
|
|
|
|
mconcat [ para "Before"
|
|
|
|
|
, simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ]
|
|
|
|
|
, para "After"
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Table with Header" =:
|
|
|
|
|
unlines [ "| Species | Status |"
|
|
|
|
|
, "|--------------+--------------|"
|
|
|
|
|
, "| cervisiae | domesticated |"
|
|
|
|
|
, "| paradoxus | wild |"
|
|
|
|
|
] =?>
|
|
|
|
|
simpleTable [ plain "Species", plain "Status" ]
|
|
|
|
|
[ [ plain "cervisiae", plain "domesticated" ]
|
|
|
|
|
, [ plain "paradoxus", plain "wild" ]
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Table with final hline" =:
|
|
|
|
|
unlines [ "| cervisiae | domesticated |"
|
|
|
|
|
, "| paradoxus | wild |"
|
|
|
|
|
, "|--------------+--------------|"
|
|
|
|
|
] =?>
|
|
|
|
|
simpleTable' 2 mempty
|
|
|
|
|
[ [ plain "cervisiae", plain "domesticated" ]
|
|
|
|
|
, [ plain "paradoxus", plain "wild" ]
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Table in a box" =:
|
|
|
|
|
unlines [ "|---------|---------|"
|
|
|
|
|
, "| static | Haskell |"
|
|
|
|
|
, "| dynamic | Lisp |"
|
|
|
|
|
, "|---------+---------|"
|
|
|
|
|
] =?>
|
|
|
|
|
simpleTable' 2 mempty
|
|
|
|
|
[ [ plain "static", plain "Haskell" ]
|
|
|
|
|
, [ plain "dynamic", plain "Lisp" ]
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Table with alignment row" =:
|
|
|
|
|
unlines [ "| Numbers | Text | More |"
|
|
|
|
|
, "| <c> | <r> | |"
|
|
|
|
|
, "| 1 | One | foo |"
|
|
|
|
|
, "| 2 | Two | bar |"
|
|
|
|
|
] =?>
|
|
|
|
|
table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0])
|
|
|
|
|
[]
|
|
|
|
|
[ [ plain "Numbers", plain "Text", plain "More" ]
|
|
|
|
|
, [ plain "1" , plain "One" , plain "foo" ]
|
|
|
|
|
, [ plain "2" , plain "Two" , plain "bar" ]
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Pipe within text doesn't start a table" =:
|
|
|
|
|
"Ceci n'est pas une | pipe " =?>
|
|
|
|
|
para (spcSep [ "Ceci", "n'est", "pas", "une", "|", "pipe" ])
|
|
|
|
|
|
|
|
|
|
, "Missing pipe at end of row" =:
|
|
|
|
|
"|incomplete-but-valid" =?>
|
|
|
|
|
simpleTable' 1 mempty [ [ plain "incomplete-but-valid" ] ]
|
|
|
|
|
|
|
|
|
|
, "Table with differing row lengths" =:
|
|
|
|
|
unlines [ "| Numbers | Text "
|
|
|
|
|
, "|-"
|
|
|
|
|
, "| <c> | <r> |"
|
|
|
|
|
, "| 1 | One | foo |"
|
|
|
|
|
, "| 2"
|
|
|
|
|
] =?>
|
|
|
|
|
table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0])
|
|
|
|
|
[ plain "Numbers", plain "Text" , plain mempty ]
|
|
|
|
|
[ [ plain "1" , plain "One" , plain "foo" ]
|
|
|
|
|
, [ plain "2" , plain mempty , plain mempty ]
|
|
|
|
|
]
|
2014-04-18 20:47:50 +02:00
|
|
|
|
|
|
|
|
|
, "Table with caption" =:
|
|
|
|
|
unlines [ "#+CAPTION: Hitchhiker's Multiplication Table"
|
|
|
|
|
, "| x | 6 |"
|
|
|
|
|
, "| 9 | 42 |"
|
|
|
|
|
] =?>
|
|
|
|
|
table "Hitchhiker's Multiplication Table"
|
|
|
|
|
[(AlignDefault, 0), (AlignDefault, 0)]
|
|
|
|
|
[]
|
|
|
|
|
[ [ plain "x", plain "6" ]
|
|
|
|
|
, [ plain "9", plain "42" ]
|
|
|
|
|
]
|
2014-03-04 00:33:25 +01:00
|
|
|
|
]
|
2014-04-17 18:09:27 +02:00
|
|
|
|
|
2014-04-18 10:15:58 +02:00
|
|
|
|
, testGroup "Blocks and fragments"
|
2014-04-17 18:09:27 +02:00
|
|
|
|
[ "Source block" =:
|
|
|
|
|
unlines [ " #+BEGIN_SRC haskell"
|
|
|
|
|
, " main = putStrLn greeting"
|
|
|
|
|
, " where greeting = \"moin\""
|
|
|
|
|
, " #+END_SRC" ] =?>
|
|
|
|
|
let attr' = ("", ["haskell"], [])
|
|
|
|
|
code' = "main = putStrLn greeting\n" ++
|
|
|
|
|
" where greeting = \"moin\"\n"
|
|
|
|
|
in codeBlockWith attr' code'
|
|
|
|
|
|
|
|
|
|
, "Source block between paragraphs" =:
|
|
|
|
|
unlines [ "Low German greeting"
|
|
|
|
|
, " #+BEGIN_SRC haskell"
|
|
|
|
|
, " main = putStrLn greeting"
|
|
|
|
|
, " where greeting = \"Moin!\""
|
|
|
|
|
, " #+END_SRC" ] =?>
|
|
|
|
|
let attr' = ("", ["haskell"], [])
|
|
|
|
|
code' = "main = putStrLn greeting\n" ++
|
|
|
|
|
" where greeting = \"Moin!\"\n"
|
|
|
|
|
in mconcat [ para $ spcSep [ "Low", "German", "greeting" ]
|
|
|
|
|
, codeBlockWith attr' code'
|
|
|
|
|
]
|
2014-05-09 18:07:37 +02:00
|
|
|
|
, "Source block with rundoc/babel arguments" =:
|
|
|
|
|
unlines [ "#+BEGIN_SRC emacs-lisp :exports both"
|
|
|
|
|
, "(progn (message \"Hello, World!\")"
|
|
|
|
|
, " (+ 23 42))"
|
|
|
|
|
, "#+END_SRC" ] =?>
|
|
|
|
|
let classes = [ "commonlisp" -- as kate doesn't know emacs-lisp syntax
|
|
|
|
|
, "rundoc-block"
|
|
|
|
|
]
|
|
|
|
|
params = [ ("rundoc-language", "emacs-lisp")
|
|
|
|
|
, ("rundoc-exports", "both")
|
|
|
|
|
]
|
|
|
|
|
code' = unlines [ "(progn (message \"Hello, World!\")"
|
|
|
|
|
, " (+ 23 42))" ]
|
|
|
|
|
in codeBlockWith ("", classes, params) code'
|
2014-04-17 18:09:27 +02:00
|
|
|
|
|
2014-07-15 02:14:46 +02:00
|
|
|
|
, "Source block with results and :exports both" =:
|
|
|
|
|
unlines [ "#+BEGIN_SRC emacs-lisp :exports both"
|
|
|
|
|
, "(progn (message \"Hello, World!\")"
|
|
|
|
|
, " (+ 23 42))"
|
|
|
|
|
, "#+END_SRC"
|
|
|
|
|
, ""
|
|
|
|
|
, "#+RESULTS:"
|
|
|
|
|
, ": 65"] =?>
|
|
|
|
|
let classes = [ "commonlisp" -- as kate doesn't know emacs-lisp syntax
|
|
|
|
|
, "rundoc-block"
|
|
|
|
|
]
|
|
|
|
|
params = [ ("rundoc-language", "emacs-lisp")
|
|
|
|
|
, ("rundoc-exports", "both")
|
|
|
|
|
]
|
|
|
|
|
code' = unlines [ "(progn (message \"Hello, World!\")"
|
|
|
|
|
, " (+ 23 42))" ]
|
|
|
|
|
results' = "65\n"
|
|
|
|
|
in codeBlockWith ("", classes, params) code'
|
|
|
|
|
<>
|
|
|
|
|
codeBlockWith ("", ["example"], []) results'
|
|
|
|
|
|
|
|
|
|
, "Source block with results and :exports code" =:
|
|
|
|
|
unlines [ "#+BEGIN_SRC emacs-lisp :exports code"
|
|
|
|
|
, "(progn (message \"Hello, World!\")"
|
|
|
|
|
, " (+ 23 42))"
|
|
|
|
|
, "#+END_SRC"
|
|
|
|
|
, ""
|
|
|
|
|
, "#+RESULTS:"
|
|
|
|
|
, ": 65" ] =?>
|
|
|
|
|
let classes = [ "commonlisp" -- as kate doesn't know emacs-lisp syntax
|
|
|
|
|
, "rundoc-block"
|
|
|
|
|
]
|
|
|
|
|
params = [ ("rundoc-language", "emacs-lisp")
|
|
|
|
|
, ("rundoc-exports", "code")
|
|
|
|
|
]
|
|
|
|
|
code' = unlines [ "(progn (message \"Hello, World!\")"
|
|
|
|
|
, " (+ 23 42))" ]
|
|
|
|
|
in codeBlockWith ("", classes, params) code'
|
|
|
|
|
|
|
|
|
|
, "Source block with results and :exports results" =:
|
|
|
|
|
unlines [ "#+BEGIN_SRC emacs-lisp :exports results"
|
|
|
|
|
, "(progn (message \"Hello, World!\")"
|
|
|
|
|
, " (+ 23 42))"
|
|
|
|
|
, "#+END_SRC"
|
|
|
|
|
, ""
|
|
|
|
|
, "#+RESULTS:"
|
|
|
|
|
, ": 65" ] =?>
|
|
|
|
|
let results' = "65\n"
|
|
|
|
|
in codeBlockWith ("", ["example"], []) results'
|
|
|
|
|
|
|
|
|
|
, "Source block with results and :exports none" =:
|
|
|
|
|
unlines [ "#+BEGIN_SRC emacs-lisp :exports none"
|
|
|
|
|
, "(progn (message \"Hello, World!\")"
|
|
|
|
|
, " (+ 23 42))"
|
|
|
|
|
, "#+END_SRC"
|
|
|
|
|
, ""
|
|
|
|
|
, "#+RESULTS:"
|
|
|
|
|
, ": 65" ] =?>
|
2014-09-04 18:14:31 +02:00
|
|
|
|
rawBlock "html" ""
|
2014-07-15 02:14:46 +02:00
|
|
|
|
|
2015-10-25 08:51:53 +01:00
|
|
|
|
, "Source block with toggling header arguments" =:
|
|
|
|
|
unlines [ "#+BEGIN_SRC sh :noeval"
|
|
|
|
|
, "echo $HOME"
|
|
|
|
|
, "#+END_SRC"
|
|
|
|
|
] =?>
|
|
|
|
|
let classes = [ "bash", "rundoc-block" ]
|
|
|
|
|
params = [ ("rundoc-language", "sh"), ("rundoc-noeval", "yes") ]
|
|
|
|
|
in codeBlockWith ("", classes, params) "echo $HOME\n"
|
|
|
|
|
|
2014-04-17 18:09:27 +02:00
|
|
|
|
, "Example block" =:
|
|
|
|
|
unlines [ "#+begin_example"
|
|
|
|
|
, "A chosen representation of"
|
|
|
|
|
, "a rule."
|
|
|
|
|
, "#+eND_exAMPle"
|
|
|
|
|
] =?>
|
|
|
|
|
codeBlockWith ("", ["example"], [])
|
|
|
|
|
"A chosen representation of\na rule.\n"
|
|
|
|
|
|
|
|
|
|
, "HTML block" =:
|
|
|
|
|
unlines [ "#+BEGIN_HTML"
|
|
|
|
|
, "<aside>HTML5 is pretty nice.</aside>"
|
|
|
|
|
, "#+END_HTML"
|
|
|
|
|
] =?>
|
|
|
|
|
rawBlock "html" "<aside>HTML5 is pretty nice.</aside>\n"
|
|
|
|
|
|
|
|
|
|
, "Quote block" =:
|
|
|
|
|
unlines [ "#+BEGIN_QUOTE"
|
|
|
|
|
, "/Niemand/ hat die Absicht, eine Mauer zu errichten!"
|
|
|
|
|
, "#+END_QUOTE"
|
|
|
|
|
] =?>
|
|
|
|
|
blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht,"
|
|
|
|
|
, "eine", "Mauer", "zu", "errichten!"
|
|
|
|
|
]))
|
|
|
|
|
|
|
|
|
|
, "Verse block" =:
|
|
|
|
|
unlines [ "The first lines of Goethe's /Faust/:"
|
|
|
|
|
, "#+begin_verse"
|
|
|
|
|
, "Habe nun, ach! Philosophie,"
|
|
|
|
|
, "Juristerei und Medizin,"
|
|
|
|
|
, "Und leider auch Theologie!"
|
|
|
|
|
, "Durchaus studiert, mit heißem Bemühn."
|
|
|
|
|
, "#+end_verse"
|
|
|
|
|
] =?>
|
|
|
|
|
mconcat
|
|
|
|
|
[ para $ spcSep [ "The", "first", "lines", "of"
|
|
|
|
|
, "Goethe's", emph "Faust" <> ":"]
|
|
|
|
|
, para $ mconcat
|
|
|
|
|
[ spcSep [ "Habe", "nun,", "ach!", "Philosophie," ]
|
|
|
|
|
, linebreak
|
|
|
|
|
, spcSep [ "Juristerei", "und", "Medizin," ]
|
|
|
|
|
, linebreak
|
|
|
|
|
, spcSep [ "Und", "leider", "auch", "Theologie!" ]
|
|
|
|
|
, linebreak
|
|
|
|
|
, spcSep [ "Durchaus", "studiert,", "mit", "heißem", "Bemühn." ]
|
|
|
|
|
]
|
|
|
|
|
]
|
|
|
|
|
|
2015-09-19 21:54:44 +02:00
|
|
|
|
, "Verse block with newlines" =:
|
|
|
|
|
unlines [ "#+BEGIN_VERSE"
|
|
|
|
|
, "foo"
|
|
|
|
|
, ""
|
|
|
|
|
, "bar"
|
|
|
|
|
, "#+END_VERSE"
|
|
|
|
|
] =?>
|
|
|
|
|
para ("foo" <> linebreak <> linebreak <> "bar")
|
|
|
|
|
|
2014-04-18 10:15:58 +02:00
|
|
|
|
, "LaTeX fragment" =:
|
|
|
|
|
unlines [ "\\begin{equation}"
|
|
|
|
|
, "X_i = \\begin{cases}"
|
|
|
|
|
, " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\"
|
|
|
|
|
, " C_{\\alpha(i)} & \\text{otherwise}"
|
|
|
|
|
, " \\end{cases}"
|
|
|
|
|
, "\\end{equation}"
|
|
|
|
|
] =?>
|
|
|
|
|
rawBlock "latex"
|
|
|
|
|
(unlines [ "\\begin{equation}"
|
|
|
|
|
, "X_i = \\begin{cases}"
|
|
|
|
|
, " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" ++
|
|
|
|
|
" \\alpha(i)\\\\"
|
|
|
|
|
, " C_{\\alpha(i)} & \\text{otherwise}"
|
|
|
|
|
, " \\end{cases}"
|
|
|
|
|
, "\\end{equation}"
|
|
|
|
|
])
|
|
|
|
|
|
2014-04-18 20:47:50 +02:00
|
|
|
|
, "Code block with caption" =:
|
|
|
|
|
unlines [ "#+CAPTION: Functor laws in Haskell"
|
|
|
|
|
, "#+NAME: functor-laws"
|
|
|
|
|
, "#+BEGIN_SRC haskell"
|
|
|
|
|
, "fmap id = id"
|
|
|
|
|
, "fmap (p . q) = (fmap p) . (fmap q)"
|
|
|
|
|
, "#+END_SRC"
|
|
|
|
|
] =?>
|
|
|
|
|
divWith
|
|
|
|
|
nullAttr
|
|
|
|
|
(mappend
|
|
|
|
|
(plain $ spanWith ("", ["label"], [])
|
|
|
|
|
(spcSep [ "Functor", "laws", "in", "Haskell" ]))
|
|
|
|
|
(codeBlockWith ("functor-laws", ["haskell"], [])
|
|
|
|
|
(unlines [ "fmap id = id"
|
|
|
|
|
, "fmap (p . q) = (fmap p) . (fmap q)"
|
|
|
|
|
])))
|
2014-05-09 18:23:23 +02:00
|
|
|
|
|
|
|
|
|
, "Convert blank lines in blocks to single newlines" =:
|
|
|
|
|
unlines [ "#+begin_html"
|
|
|
|
|
, ""
|
|
|
|
|
, "<span>boring</span>"
|
|
|
|
|
, ""
|
|
|
|
|
, "#+end_html"
|
|
|
|
|
] =?>
|
|
|
|
|
rawBlock "html" "\n<span>boring</span>\n\n"
|
2014-05-10 11:25:20 +02:00
|
|
|
|
|
|
|
|
|
, "Non-letter chars in source block parameters" =:
|
|
|
|
|
unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich"
|
|
|
|
|
, "code body"
|
|
|
|
|
, "#+END_SRC"
|
|
|
|
|
] =?>
|
|
|
|
|
let classes = [ "c", "rundoc-block" ]
|
|
|
|
|
params = [ ("rundoc-language", "C")
|
|
|
|
|
, ("rundoc-tangle", "xxxx.c")
|
|
|
|
|
, ("rundoc-city", "Zürich")
|
|
|
|
|
]
|
|
|
|
|
in codeBlockWith ( "", classes, params) "code body\n"
|
2014-04-17 18:09:27 +02:00
|
|
|
|
]
|
2015-11-13 20:32:36 +01:00
|
|
|
|
|
2015-03-09 13:11:53 +01:00
|
|
|
|
, testGroup "Smart punctuation"
|
|
|
|
|
[ test orgSmart "quote before ellipses"
|
|
|
|
|
("'...hi'"
|
|
|
|
|
=?> para (singleQuoted "…hi"))
|
2015-05-20 18:01:03 +02:00
|
|
|
|
|
2015-03-09 13:11:53 +01:00
|
|
|
|
, test orgSmart "apostrophe before emph"
|
|
|
|
|
("D'oh! A l'/aide/!"
|
|
|
|
|
=?> para ("D’oh! A l’" <> emph "aide" <> "!"))
|
2015-05-20 18:01:03 +02:00
|
|
|
|
|
2015-03-09 13:11:53 +01:00
|
|
|
|
, test orgSmart "apostrophe in French"
|
|
|
|
|
("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
|
|
|
|
|
=?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»")
|
2015-05-20 18:01:03 +02:00
|
|
|
|
|
2015-03-09 13:11:53 +01:00
|
|
|
|
, test orgSmart "Quotes cannot occur at the end of emphasized text"
|
|
|
|
|
("/say \"yes\"/" =?>
|
|
|
|
|
para ("/say" <> space <> doubleQuoted "yes" <> "/"))
|
2015-05-20 18:01:03 +02:00
|
|
|
|
|
2015-03-09 13:11:53 +01:00
|
|
|
|
, test orgSmart "Dashes are allowed at the borders of emphasis'"
|
|
|
|
|
("/foo---/" =?>
|
|
|
|
|
para (emph "foo—"))
|
2015-11-13 20:32:36 +01:00
|
|
|
|
|
|
|
|
|
, test orgSmart "Single quotes can be followed by emphasized text"
|
|
|
|
|
("Singles on the '/meat market/'" =?>
|
|
|
|
|
para ("Singles on the " <> (singleQuoted $ emph "meat market")))
|
|
|
|
|
|
|
|
|
|
, test orgSmart "Double quotes can be followed by emphasized text"
|
|
|
|
|
("Double income, no kids: \"/DINK/\"" =?>
|
|
|
|
|
para ("Double income, no kids: " <> (doubleQuoted $ emph "DINK")))
|
2015-03-09 13:11:53 +01:00
|
|
|
|
]
|
2014-03-04 00:33:25 +01:00
|
|
|
|
]
|