2018-03-18 10:46:28 -07:00
|
|
|
|
{-# LANGUAGE NoImplicitPrelude #-}
|
2017-12-24 22:48:18 +01:00
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2019-02-04 22:52:31 +01:00
|
|
|
|
{- |
|
|
|
|
|
Module : Tests.Readers.Org.Inline
|
|
|
|
|
Copyright : © 2014-2019 Albert Krewinkel
|
|
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
|
|
|
|
|
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
|
|
|
|
|
Stability : alpha
|
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
|
|
Tests parsing of org inlines.
|
|
|
|
|
-}
|
2017-12-24 22:48:18 +01:00
|
|
|
|
module Tests.Readers.Org.Inline (tests) where
|
|
|
|
|
|
2018-03-18 10:46:28 -07:00
|
|
|
|
import Prelude
|
2017-12-24 22:48:18 +01:00
|
|
|
|
import Data.List (intersperse)
|
|
|
|
|
import Test.Tasty (TestTree, testGroup)
|
|
|
|
|
import Tests.Helpers ((=?>))
|
|
|
|
|
import Tests.Readers.Org.Shared ((=:), spcSep)
|
|
|
|
|
import Text.Pandoc.Builder
|
|
|
|
|
import Text.Pandoc.Shared (underlineSpan)
|
|
|
|
|
import qualified Data.Text as T
|
2018-02-26 21:09:51 +01:00
|
|
|
|
import qualified Tests.Readers.Org.Inline.Citation as Citation
|
2017-12-24 22:48:18 +01:00
|
|
|
|
import qualified Tests.Readers.Org.Inline.Note as Note
|
|
|
|
|
import qualified Tests.Readers.Org.Inline.Smart as Smart
|
|
|
|
|
|
|
|
|
|
tests :: [TestTree]
|
|
|
|
|
tests =
|
|
|
|
|
[ "Plain String" =:
|
|
|
|
|
"Hello, World" =?>
|
|
|
|
|
para (spcSep [ "Hello,", "World" ])
|
|
|
|
|
|
|
|
|
|
, "Emphasis" =:
|
|
|
|
|
"/Planet Punk/" =?>
|
|
|
|
|
para (emph . spcSep $ ["Planet", "Punk"])
|
|
|
|
|
|
|
|
|
|
, "Strong" =:
|
|
|
|
|
"*Cider*" =?>
|
|
|
|
|
para (strong "Cider")
|
|
|
|
|
|
|
|
|
|
, "Strong Emphasis" =:
|
|
|
|
|
"/*strength*/" =?>
|
|
|
|
|
para (emph . strong $ "strength")
|
|
|
|
|
|
|
|
|
|
, "Emphasized Strong preceded by space" =:
|
|
|
|
|
" */super/*" =?>
|
|
|
|
|
para (strong . emph $ "super")
|
|
|
|
|
|
|
|
|
|
, "Underline" =:
|
|
|
|
|
"_underline_" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (underlineSpan "underline")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Strikeout" =:
|
|
|
|
|
"+Kill Bill+" =?>
|
|
|
|
|
para (strikeout . spcSep $ [ "Kill", "Bill" ])
|
|
|
|
|
|
|
|
|
|
, "Verbatim" =:
|
|
|
|
|
"=Robot.rock()=" =?>
|
|
|
|
|
para (code "Robot.rock()")
|
|
|
|
|
|
|
|
|
|
, "Code" =:
|
|
|
|
|
"~word for word~" =?>
|
|
|
|
|
para (code "word for word")
|
|
|
|
|
|
|
|
|
|
, "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}")
|
|
|
|
|
|
|
|
|
|
, "Symbol" =:
|
|
|
|
|
"A * symbol" =?>
|
|
|
|
|
para (str "A" <> space <> str "*" <> space <> "symbol")
|
|
|
|
|
|
|
|
|
|
, "Superscript simple expression" =:
|
|
|
|
|
"2^-λ" =?>
|
|
|
|
|
para (str "2" <> superscript "-λ")
|
|
|
|
|
|
|
|
|
|
, "Superscript multi char" =:
|
|
|
|
|
"2^{n-1}" =?>
|
|
|
|
|
para (str "2" <> superscript "n-1")
|
|
|
|
|
|
|
|
|
|
, "Subscript simple expression" =:
|
|
|
|
|
"a_n" =?>
|
|
|
|
|
para (str "a" <> subscript "n")
|
|
|
|
|
|
|
|
|
|
, "Subscript multi char" =:
|
|
|
|
|
"a_{n+1}" =?>
|
|
|
|
|
para (str "a" <> subscript "n+1")
|
|
|
|
|
|
|
|
|
|
, "Linebreak" =:
|
|
|
|
|
"line \\\\ \nbreak" =?>
|
|
|
|
|
para ("line" <> linebreak <> "break")
|
|
|
|
|
|
|
|
|
|
, "Inline note" =:
|
|
|
|
|
"[fn::Schreib mir eine E-Mail]" =?>
|
|
|
|
|
para (note $ para "Schreib mir eine E-Mail")
|
|
|
|
|
|
2018-07-02 18:51:51 +03:00
|
|
|
|
, "Markup-chars not occurring on word break are symbols" =:
|
2017-12-24 22:48:18 +01:00
|
|
|
|
T.unlines [ "this+that+ +so+on"
|
|
|
|
|
, "seven*eight* nine*"
|
|
|
|
|
, "+not+funny+"
|
|
|
|
|
] =?>
|
|
|
|
|
para ("this+that+ +so+on" <> softbreak <>
|
|
|
|
|
"seven*eight* nine*" <> softbreak <>
|
|
|
|
|
strikeout "not+funny")
|
|
|
|
|
|
|
|
|
|
, "No empty markup" =:
|
|
|
|
|
"// ** __ <> == ~~ $$" =?>
|
|
|
|
|
para (spcSep [ "//", "**", "__", "<>", "==", "~~", "$$" ])
|
|
|
|
|
|
|
|
|
|
, "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" <> "."
|
|
|
|
|
])
|
|
|
|
|
|
|
|
|
|
, "Quotes are allowed border chars" =:
|
|
|
|
|
"/'yep/ *sure\"*" =?>
|
|
|
|
|
para (emph "'yep" <> space <> strong "sure\"")
|
|
|
|
|
|
|
|
|
|
, "Spaces are forbidden border chars" =:
|
|
|
|
|
"/nada /" =?>
|
|
|
|
|
para "/nada /"
|
|
|
|
|
|
|
|
|
|
, "Markup should work properly after a blank line" =:
|
|
|
|
|
T.unlines ["foo", "", "/bar/"] =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (text "foo") <>
|
|
|
|
|
para (emph $ text "bar")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Inline math must stay within three lines" =:
|
|
|
|
|
T.unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (math "a\nb\nc" <> softbreak <>
|
2017-12-24 22:48:18 +01:00
|
|
|
|
"$d" <> softbreak <> "e" <> softbreak <>
|
|
|
|
|
"f" <> softbreak <> "g$")
|
|
|
|
|
|
|
|
|
|
, "Single-character math" =:
|
|
|
|
|
"$a$ $b$! $c$?" =?>
|
|
|
|
|
para (spcSep [ math "a"
|
|
|
|
|
, "$b$!"
|
2018-01-19 21:25:24 -08:00
|
|
|
|
, math "c" <> "?"
|
2017-12-24 22:48:18 +01:00
|
|
|
|
])
|
|
|
|
|
|
|
|
|
|
, "Markup may not span more than two lines" =:
|
|
|
|
|
"/this *is +totally\nnice+ not*\nemph/" =?>
|
|
|
|
|
para ("/this" <> space <>
|
|
|
|
|
strong ("is" <> space <>
|
|
|
|
|
strikeout ("totally" <>
|
|
|
|
|
softbreak <> "nice") <>
|
|
|
|
|
space <> "not") <>
|
|
|
|
|
softbreak <> "emph/")
|
|
|
|
|
|
|
|
|
|
, "Sub- and superscript expressions" =:
|
|
|
|
|
T.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))"
|
|
|
|
|
] =?>
|
|
|
|
|
para (mconcat $ intersperse softbreak
|
|
|
|
|
[ "a" <> subscript "(a(b)(c)d)"
|
|
|
|
|
, "e" <> superscript "(f(g)h)"
|
2018-01-19 21:25:24 -08:00
|
|
|
|
, "i" <> subscript "(jk)" <> "l)"
|
|
|
|
|
, "m" <> superscript "()" <> "n"
|
2017-12-24 22:48:18 +01:00
|
|
|
|
, "o" <> subscript "p{q{}r}"
|
|
|
|
|
, "s" <> superscript "t{u}v"
|
2018-01-19 21:25:24 -08:00
|
|
|
|
, "w" <> subscript "xy" <> "z}"
|
|
|
|
|
, "1" <> superscript "" <> "2"
|
2017-12-24 22:48:18 +01:00
|
|
|
|
, "3" <> subscript "{}"
|
|
|
|
|
, "4" <> superscript ("(a(" <> strong "b(c" <> ")d))")
|
|
|
|
|
])
|
|
|
|
|
, "Verbatim text can contain equal signes (=)" =:
|
|
|
|
|
"=is_subst = True=" =?>
|
|
|
|
|
para (code "is_subst = True")
|
|
|
|
|
|
|
|
|
|
, testGroup "Images"
|
|
|
|
|
[ "Image" =:
|
2019-01-01 20:53:52 +01:00
|
|
|
|
"[[./sunset.jpg]]" =?>
|
|
|
|
|
para (image "./sunset.jpg" "" "")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Image with explicit file: prefix" =:
|
2019-01-01 20:53:52 +01:00
|
|
|
|
"[[file:sunrise.jpg]]" =?>
|
|
|
|
|
para (image "sunrise.jpg" "" "")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Multiple images within a paragraph" =:
|
2019-01-01 20:53:52 +01:00
|
|
|
|
T.unlines [ "[[file:sunrise.jpg]]"
|
|
|
|
|
, "[[file:sunset.jpg]]"
|
|
|
|
|
] =?>
|
|
|
|
|
para (image "sunrise.jpg" "" ""
|
2017-12-24 22:48:18 +01:00
|
|
|
|
<> softbreak
|
2019-01-01 20:53:52 +01:00
|
|
|
|
<> image "sunset.jpg" "" "")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Image with html attributes" =:
|
2019-01-01 20:53:52 +01:00
|
|
|
|
T.unlines [ "#+ATTR_HTML: :width 50%"
|
|
|
|
|
, "[[file:guinea-pig.gif]]"
|
|
|
|
|
] =?>
|
|
|
|
|
para (imageWith ("", [], [("width", "50%")]) "guinea-pig.gif" "" "")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
, "Explicit link" =:
|
|
|
|
|
"[[http://zeitlens.com/][pseudo-random /nonsense/]]" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (link "http://zeitlens.com/" ""
|
2017-12-24 22:48:18 +01:00
|
|
|
|
("pseudo-random" <> space <> emph "nonsense"))
|
|
|
|
|
|
|
|
|
|
, "Self-link" =:
|
|
|
|
|
"[[http://zeitlens.com/]]" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (link "http://zeitlens.com/" "" "http://zeitlens.com/")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
2019-01-01 22:06:44 +01:00
|
|
|
|
, "Internal self-link (reference)" =:
|
|
|
|
|
"[[#rabbit]]" =?>
|
|
|
|
|
para (link "#rabbit" "" "#rabbit")
|
|
|
|
|
|
2017-12-24 22:48:18 +01:00
|
|
|
|
, "Absolute file link" =:
|
|
|
|
|
"[[/url][hi]]" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (link "file:///url" "" "hi")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Link to file in parent directory" =:
|
|
|
|
|
"[[../file.txt][moin]]" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (link "../file.txt" "" "moin")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Empty link (for gitit interop)" =:
|
|
|
|
|
"[[][New Link]]" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (link "" "" "New Link")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Image link" =:
|
|
|
|
|
"[[sunset.png][file:dusk.svg]]" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (link "sunset.png" "" (image "dusk.svg" "" ""))
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Image link with non-image target" =:
|
|
|
|
|
"[[http://example.com][./logo.png]]" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (link "http://example.com" "" (image "./logo.png" "" ""))
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
2019-01-01 20:53:52 +01:00
|
|
|
|
, "Link to image" =:
|
|
|
|
|
"[[https://example.com/image.jpg][Look!]]" =?>
|
|
|
|
|
para (link "https://example.com/image.jpg" "" (str "Look!"))
|
|
|
|
|
|
2017-12-24 22:48:18 +01:00
|
|
|
|
, "Plain link" =:
|
|
|
|
|
"Posts on http://zeitlens.com/ can be funny at times." =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (spcSep [ "Posts", "on"
|
2017-12-24 22:48:18 +01:00
|
|
|
|
, link "http://zeitlens.com/" "" "http://zeitlens.com/"
|
|
|
|
|
, "can", "be", "funny", "at", "times."
|
|
|
|
|
])
|
|
|
|
|
|
|
|
|
|
, "Angle link" =:
|
|
|
|
|
"Look at <http://moltkeplatz.de> for fnords." =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (spcSep [ "Look", "at"
|
2017-12-24 22:48:18 +01:00
|
|
|
|
, link "http://moltkeplatz.de" "" "http://moltkeplatz.de"
|
|
|
|
|
, "for", "fnords."
|
|
|
|
|
])
|
|
|
|
|
|
|
|
|
|
, "Absolute file link" =:
|
|
|
|
|
"[[file:///etc/passwd][passwd]]" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (link "file:///etc/passwd" "" "passwd")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "File link" =:
|
|
|
|
|
"[[file:target][title]]" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (link "target" "" "title")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Anchor" =:
|
|
|
|
|
"<<anchor>> Link here later." =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (spanWith ("anchor", [], []) mempty <>
|
2017-12-24 22:48:18 +01:00
|
|
|
|
"Link" <> space <> "here" <> space <> "later.")
|
|
|
|
|
|
|
|
|
|
, "Inline code block" =:
|
|
|
|
|
"src_emacs-lisp{(message \"Hello\")}" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (codeWith ( ""
|
2017-12-24 22:48:18 +01:00
|
|
|
|
, [ "commonlisp" ]
|
|
|
|
|
, [ ("org-language", "emacs-lisp") ])
|
|
|
|
|
"(message \"Hello\")")
|
|
|
|
|
|
|
|
|
|
, "Inline code block with arguments" =:
|
|
|
|
|
"src_sh[:export both :results output]{echo 'Hello, World'}" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (codeWith ( ""
|
2017-12-24 22:48:18 +01:00
|
|
|
|
, [ "bash" ]
|
|
|
|
|
, [ ("org-language", "sh")
|
|
|
|
|
, ("export", "both")
|
|
|
|
|
, ("results", "output")
|
|
|
|
|
]
|
|
|
|
|
)
|
|
|
|
|
"echo 'Hello, World'")
|
2018-09-27 15:04:56 -07:00
|
|
|
|
|
|
|
|
|
, "Inline code block with a blank argument array" =:
|
|
|
|
|
"src_sh[]{echo 'Hello, World'}" =?>
|
|
|
|
|
para (codeWith ( ""
|
|
|
|
|
, [ "bash" ]
|
|
|
|
|
, [ ("org-language", "sh") ])
|
|
|
|
|
"echo 'Hello, World'")
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Inline code block with toggle" =:
|
|
|
|
|
"src_sh[:toggle]{echo $HOME}" =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para (codeWith ( ""
|
2017-12-24 22:48:18 +01:00
|
|
|
|
, [ "bash" ]
|
|
|
|
|
, [ ("org-language", "sh")
|
|
|
|
|
, ("toggle", "yes")
|
|
|
|
|
]
|
|
|
|
|
)
|
|
|
|
|
"echo $HOME")
|
|
|
|
|
|
|
|
|
|
, "Inline LaTeX symbol" =:
|
|
|
|
|
"\\dots" =?>
|
|
|
|
|
para "…"
|
|
|
|
|
|
|
|
|
|
, "Inline LaTeX command" =:
|
|
|
|
|
"\\textit{Emphasised}" =?>
|
|
|
|
|
para (emph "Emphasised")
|
|
|
|
|
|
|
|
|
|
, "Inline LaTeX command with spaces" =:
|
|
|
|
|
"\\emph{Emphasis mine}" =?>
|
|
|
|
|
para (emph "Emphasis mine")
|
|
|
|
|
|
2019-05-05 14:48:37 +02:00
|
|
|
|
, "Inline math symbols" =:
|
|
|
|
|
"\\tau \\oplus \\alpha" =?>
|
|
|
|
|
para "τ ⊕ α"
|
|
|
|
|
|
|
|
|
|
, "Inline LaTeX math command" =:
|
|
|
|
|
"\\crarr" =?>
|
|
|
|
|
para "↵"
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "Unknown inline LaTeX command" =:
|
|
|
|
|
"\\notacommand{foo}" =?>
|
|
|
|
|
para (rawInline "latex" "\\notacommand{foo}")
|
|
|
|
|
|
|
|
|
|
, "Export snippet" =:
|
|
|
|
|
"@@html:<kbd>M-x org-agenda</kbd>@@" =?>
|
|
|
|
|
para (rawInline "html" "<kbd>M-x org-agenda</kbd>")
|
|
|
|
|
|
|
|
|
|
, "MathML symbol in LaTeX-style" =:
|
|
|
|
|
"There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: '\\nbsp')." =?>
|
2018-01-19 21:25:24 -08:00
|
|
|
|
para "There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: ' ')."
|
2017-12-24 22:48:18 +01:00
|
|
|
|
|
|
|
|
|
, "MathML symbol in LaTeX-style, including braces" =:
|
|
|
|
|
"\\Aacute{}stor" =?>
|
|
|
|
|
para "Ástor"
|
|
|
|
|
|
|
|
|
|
, "MathML copy sign" =:
|
|
|
|
|
"\\copy" =?>
|
|
|
|
|
para "©"
|
|
|
|
|
|
|
|
|
|
, "MathML symbols, space separated" =:
|
|
|
|
|
"\\ForAll \\Auml" =?>
|
|
|
|
|
para "∀ Ä"
|
|
|
|
|
|
|
|
|
|
, "Macro" =:
|
|
|
|
|
T.unlines [ "#+MACRO: HELLO /Hello, $1/"
|
|
|
|
|
, "{{{HELLO(World)}}}"
|
|
|
|
|
] =?>
|
|
|
|
|
para (emph "Hello, World")
|
|
|
|
|
|
|
|
|
|
, "Macro repeting its argument" =:
|
|
|
|
|
T.unlines [ "#+MACRO: HELLO $1$1"
|
|
|
|
|
, "{{{HELLO(moin)}}}"
|
|
|
|
|
] =?>
|
|
|
|
|
para "moinmoin"
|
|
|
|
|
|
|
|
|
|
, "Macro called with too few arguments" =:
|
|
|
|
|
T.unlines [ "#+MACRO: HELLO Foo $1 $2 Bar"
|
|
|
|
|
, "{{{HELLO()}}}"
|
|
|
|
|
] =?>
|
|
|
|
|
para "Foo Bar"
|
|
|
|
|
|
2018-02-26 21:09:51 +01:00
|
|
|
|
, testGroup "Citations" Citation.tests
|
2017-12-24 22:48:18 +01:00
|
|
|
|
, testGroup "Footnotes" Note.tests
|
|
|
|
|
, testGroup "Smart punctuation" Smart.tests
|
|
|
|
|
]
|