aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorTEC <tec@tecosaur.com>2020-11-18 02:06:30 +0800
committerAlbert Krewinkel <albert+github@zeitkraut.de>2020-11-18 14:48:56 +0100
commit0306eec5fa3591fc864d9e2e3c0b84a1229509e6 (patch)
treecb2e769efb85b4a51be1b572c478117a7d1529ac
parent224a501b29248a56bfb05f8092ea6db81b838f59 (diff)
downloadpandoc-0306eec5fa3591fc864d9e2e3c0b84a1229509e6.tar.gz
Replace org #+KEYWORDS with #+keywords
As of ~2 years ago, lower case keywords became the standard (though they are handled case insensitive, as always): https://code.orgmode.org/bzg/org-mode/commit/13424336a6f30c50952d291e7a82906c1210daf0 Upper case keywords are exclusive to the manual: - https://orgmode.org/list/871s50zn6p.fsf@nicolasgoaziou.fr/ - https://orgmode.org/list/87tuuw3n15.fsf@nicolasgoaziou.fr/
-rw-r--r--data/templates/default.org6
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs22
-rw-r--r--src/Text/Pandoc/Writers/Org.hs32
-rw-r--r--test/Tests/Readers/Org/Block.hs42
-rw-r--r--test/Tests/Readers/Org/Block/CodeBlock.hs64
-rw-r--r--test/Tests/Readers/Org/Block/Figure.hs16
-rw-r--r--test/Tests/Readers/Org/Block/Header.hs6
-rw-r--r--test/Tests/Readers/Org/Block/Table.hs4
-rw-r--r--test/Tests/Readers/Org/Inline.hs2
-rw-r--r--test/Tests/Readers/Org/Meta.hs50
-rw-r--r--test/command/3706.md16
-rw-r--r--test/command/4186.md16
-rw-r--r--test/command/5178.md20
-rw-r--r--test/org-select-tags.org4
-rw-r--r--test/tables.org6
-rw-r--r--test/writer.org168
16 files changed, 237 insertions, 237 deletions
diff --git a/data/templates/default.org b/data/templates/default.org
index 860342ea6..a7daef7df 100644
--- a/data/templates/default.org
+++ b/data/templates/default.org
@@ -1,12 +1,12 @@
$if(title)$
-#+TITLE: $title$
+#+title: $title$
$endif$
$if(author)$
-#+AUTHOR: $for(author)$$author$$sep$; $endfor$
+#+author: $for(author)$$author$$sep$; $endfor$
$endif$
$if(date)$
-#+DATE: $date$
+#+date: $date$
$endif$
$for(header-includes)$
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index cd91e9ecc..f2e8b1ab6 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -111,23 +111,23 @@ attrFromBlockAttributes BlockAttributes{..} =
stringyMetaAttribute :: Monad m => OrgParser m (Text, Text)
stringyMetaAttribute = try $ do
metaLineStart
- attrName <- T.toUpper <$> many1TillChar nonspaceChar (char ':')
+ attrName <- T.toLower <$> many1TillChar nonspaceChar (char ':')
skipSpaces
attrValue <- anyLine <|> ("" <$ newline)
return (attrName, attrValue)
-- | Parse a set of block attributes. Block attributes are given through
--- lines like @#+CAPTION: block caption@ or @#+ATTR_HTML: :width 20@.
+-- lines like @#+caption: block caption@ or @#+attr_html: :width 20@.
-- Parsing will fail if any line contains an attribute different from
-- those attributes known to work on blocks.
blockAttributes :: PandocMonad m => OrgParser m BlockAttributes
blockAttributes = try $ do
kv <- many stringyMetaAttribute
guard $ all (isBlockAttr . fst) kv
- let caption = foldl' (appendValues "CAPTION") Nothing kv
- let kvAttrs = foldl' (appendValues "ATTR_HTML") Nothing kv
- let name = lookup "NAME" kv
- let label = lookup "LABEL" kv
+ let caption = foldl' (appendValues "caption") Nothing kv
+ let kvAttrs = foldl' (appendValues "attr_html") Nothing kv
+ let name = lookup "name" kv
+ let label = lookup "label" kv
caption' <- traverse (parseFromString inlines . (<> "\n")) caption
kvAttrs' <- parseFromString keyValues . (<> "\n") $ fromMaybe mempty kvAttrs
return BlockAttributes
@@ -139,9 +139,9 @@ blockAttributes = try $ do
where
isBlockAttr :: Text -> Bool
isBlockAttr = flip elem
- [ "NAME", "LABEL", "CAPTION"
- , "ATTR_HTML", "ATTR_LATEX"
- , "RESULTS"
+ [ "name", "label", "caption"
+ , "attr_html", "attr_latex"
+ , "results"
]
appendValues :: Text -> Maybe Text -> (Text, Text) -> Maybe Text
@@ -170,10 +170,10 @@ keyValues = try $
--
--- Org Blocks (#+BEGIN_... / #+END_...)
+-- Org Blocks (#+begin_... / #+end_...)
--
--- | Read an org-mode block delimited by #+BEGIN_TYPE and #+END_TYPE.
+-- | Read an org-mode block delimited by #+begin_type and #+end_type.
orgBlock :: PandocMonad m => OrgParser m (F Blocks)
orgBlock = try $ do
blockAttrs <- blockAttributes
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 41d48b44b..2af93017d 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -106,7 +106,7 @@ blockToOrg (Para [Image attr txt (src,tgt)])
| Just tit <- T.stripPrefix "fig:" tgt = do
capt <- if null txt
then return empty
- else ("#+CAPTION: " <>) `fmap` inlineListToOrg txt
+ else ("#+caption: " <>) `fmap` inlineListToOrg txt
img <- inlineToOrg (Image attr txt (src,tit))
return $ capt $$ img $$ blankline
blockToOrg (Para inlines) = do
@@ -121,11 +121,11 @@ blockToOrg (LineBlock lns) = do
let joinWithBlankLines = mconcat . intersperse blankline
let prettifyStanza ls = joinWithLinefeeds <$> mapM inlineListToOrg ls
contents <- joinWithBlankLines <$> mapM prettifyStanza (splitStanza lns)
- return $ blankline $$ "#+BEGIN_VERSE" $$
- nest 2 contents $$ "#+END_VERSE" <> blankline
+ return $ blankline $$ "#+begin_verse" $$
+ nest 2 contents $$ "#+end_verse" <> blankline
blockToOrg (RawBlock "html" str) =
- return $ blankline $$ "#+BEGIN_HTML" $$
- nest 2 (literal str) $$ "#+END_HTML" $$ blankline
+ return $ blankline $$ "#+begin_html" $$
+ nest 2 (literal str) $$ "#+end_html" $$ blankline
blockToOrg b@(RawBlock f str)
| isRawFormat f = return $ literal str
| otherwise = do
@@ -148,19 +148,19 @@ blockToOrg (CodeBlock (_,classes,kvs) str) = do
else ""
let at = map pandocLangToOrg classes `intersect` orgLangIdentifiers
let (beg, end) = case at of
- [] -> ("#+BEGIN_EXAMPLE" <> numberlines, "#+END_EXAMPLE")
- (x:_) -> ("#+BEGIN_SRC " <> x <> numberlines, "#+END_SRC")
+ [] -> ("#+begin_example" <> numberlines, "#+end_example")
+ (x:_) -> ("#+begin_src " <> x <> numberlines, "#+end_src")
return $ literal beg $$ nest 2 (literal str) $$ text end $$ blankline
blockToOrg (BlockQuote blocks) = do
contents <- blockListToOrg blocks
- return $ blankline $$ "#+BEGIN_QUOTE" $$
- nest 2 contents $$ "#+END_QUOTE" $$ blankline
+ return $ blankline $$ "#+begin_quote" $$
+ nest 2 contents $$ "#+end_quote" $$ blankline
blockToOrg (Table _ blkCapt specs thead tbody tfoot) = do
let (caption', _, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
caption'' <- inlineListToOrg caption'
let caption = if null caption'
then empty
- else "#+CAPTION: " <> caption''
+ else "#+caption: " <> caption''
headers' <- mapM blockListToOrg headers
rawRows <- mapM (mapM blockListToOrg) rows
let numChars = maximum . map offset
@@ -292,12 +292,12 @@ divToOrg attr bs = do
case divBlockType attr of
GreaterBlock blockName attr' ->
-- Write as greater block. The ID, if present, is added via
- -- the #+NAME keyword; other classes and key-value pairs
- -- are kept as #+ATTR_HTML attributes.
+ -- the #+name keyword; other classes and key-value pairs
+ -- are kept as #+attr_html attributes.
return $ blankline $$ attrHtml attr'
- $$ "#+BEGIN_" <> literal blockName
+ $$ "#+begin_" <> literal blockName
$$ contents
- $$ "#+END_" <> literal blockName $$ blankline
+ $$ "#+end_" <> literal blockName $$ blankline
Drawer drawerName (_,_,kvs) -> do
-- Write as drawer. Only key-value pairs are retained.
let keys = vcat $ map (\(k,v) ->
@@ -320,8 +320,8 @@ attrHtml :: Attr -> Doc Text
attrHtml ("" , [] , []) = mempty
attrHtml (ident, classes, kvs) =
let
- name = if T.null ident then mempty else "#+NAME: " <> literal ident <> cr
- keyword = "#+ATTR_HTML"
+ name = if T.null ident then mempty else "#+name: " <> literal ident <> cr
+ keyword = "#+attr_html"
classKv = ("class", T.unwords classes)
kvStrings = map (\(k,v) -> ":" <> k <> " " <> v) (classKv:kvs)
in name <> keyword <> ": " <> literal (T.unwords kvStrings) <> cr
diff --git a/test/Tests/Readers/Org/Block.hs b/test/Tests/Readers/Org/Block.hs
index 895e3f05b..995bd0316 100644
--- a/test/Tests/Readers/Org/Block.hs
+++ b/test/Tests/Readers/Org/Block.hs
@@ -75,10 +75,10 @@ tests =
, testGroup "Comments"
[ "Comment Block" =:
- T.unlines [ "#+BEGIN_COMMENT"
+ T.unlines [ "#+begin_comment"
, "stuff"
, "bla"
- , "#+END_COMMENT"] =?>
+ , "#+end_comment"] =?>
(mempty::Blocks)
, "Comment line" =:
@@ -92,16 +92,16 @@ tests =
, testGroup "Blocks and fragments"
[ "HTML block" =:
- T.unlines [ "#+BEGIN_HTML"
+ T.unlines [ "#+begin_html"
, "<aside>HTML5 is pretty nice.</aside>"
- , "#+END_HTML"
+ , "#+end_html"
] =?>
rawBlock "html" "<aside>HTML5 is pretty nice.</aside>\n"
, "Quote block" =:
- T.unlines [ "#+BEGIN_QUOTE"
+ T.unlines [ "#+begin_quote"
, "/Niemand/ hat die Absicht, eine Mauer zu errichten!"
- , "#+END_QUOTE"
+ , "#+end_quote"
] =?>
blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht,"
, "eine", "Mauer", "zu", "errichten!"
@@ -128,31 +128,31 @@ tests =
]
, "Verse block with blank lines" =:
- T.unlines [ "#+BEGIN_VERSE"
+ T.unlines [ "#+begin_verse"
, "foo"
, ""
, "bar"
- , "#+END_VERSE"
+ , "#+end_verse"
] =?>
lineBlock [ "foo", mempty, "bar" ]
, "Verse block with varying indentation" =:
- T.unlines [ "#+BEGIN_VERSE"
+ T.unlines [ "#+begin_verse"
, " hello darkness"
, "my old friend"
- , "#+END_VERSE"
+ , "#+end_verse"
] =?>
lineBlock [ "\160\160hello darkness", "my old friend" ]
, "Raw block LaTeX" =:
- T.unlines [ "#+BEGIN_LaTeX"
+ T.unlines [ "#+begin_latex"
, "The category $\\cat{Set}$ is adhesive."
- , "#+END_LaTeX"
+ , "#+end_latex"
] =?>
rawBlock "latex" "The category $\\cat{Set}$ is adhesive.\n"
, "Raw LaTeX line" =:
- "#+LATEX: \\let\\foo\\bar" =?>
+ "#+latex: \\let\\foo\\bar" =?>
rawBlock "latex" "\\let\\foo\\bar"
, "Raw Beamer line" =:
@@ -160,13 +160,13 @@ tests =
rawBlock "beamer" "\\pause"
, "Raw HTML line" =:
- "#+HTML: <aside>not important</aside>" =?>
+ "#+html: <aside>not important</aside>" =?>
rawBlock "html" "<aside>not important</aside>"
, "Export block HTML" =:
- T.unlines [ "#+BEGIN_export html"
+ T.unlines [ "#+begin_export html"
, "<samp>Hello, World!</samp>"
- , "#+END_export"
+ , "#+end_export"
] =?>
rawBlock "html" "<samp>Hello, World!</samp>\n"
@@ -197,13 +197,13 @@ tests =
] =?>
rawBlock "html" "\n<span>boring</span>\n\n"
- , "Accept `ATTR_HTML` attributes for generic block" =:
- T.unlines [ "#+ATTR_HTML: :title hello, world :id test :class fun code"
- , "#+BEGIN_TEST"
+ , "Accept `attr_html` attributes for generic block" =:
+ T.unlines [ "#+attr_html: :title hello, world :id test :class fun code"
+ , "#+begin_test"
, "nonsense"
- , "#+END_TEST"
+ , "#+end_test"
] =?>
- let attr = ("test", ["fun", "code", "TEST"], [("title", "hello, world")])
+ let attr = ("test", ["fun", "code", "test"], [("title", "hello, world")])
in divWith attr (para "nonsense")
]
diff --git a/test/Tests/Readers/Org/Block/CodeBlock.hs b/test/Tests/Readers/Org/Block/CodeBlock.hs
index 42ad09d86..adf6661ca 100644
--- a/test/Tests/Readers/Org/Block/CodeBlock.hs
+++ b/test/Tests/Readers/Org/Block/CodeBlock.hs
@@ -23,48 +23,48 @@ import qualified Data.Text as T
tests :: [TestTree]
tests =
[ "Source block" =:
- T.unlines [ " #+BEGIN_SRC haskell"
+ T.unlines [ " #+begin_src haskell"
, " main = putStrLn greeting"
, " where greeting = \"moin\""
- , " #+END_SRC" ] =?>
+ , " #+end_src" ] =?>
let attr' = ("", ["haskell"], [])
code' = "main = putStrLn greeting\n" <>
" where greeting = \"moin\"\n"
in codeBlockWith attr' code'
, "Source block with indented code" =:
- T.unlines [ " #+BEGIN_SRC haskell"
+ T.unlines [ " #+begin_src haskell"
, " main = putStrLn greeting"
, " where greeting = \"moin\""
- , " #+END_SRC" ] =?>
+ , " #+end_src" ] =?>
let attr' = ("", ["haskell"], [])
code' = "main = putStrLn greeting\n" <>
" where greeting = \"moin\"\n"
in codeBlockWith attr' code'
, "Source block with tab-indented code" =:
- T.unlines [ "\t#+BEGIN_SRC haskell"
+ T.unlines [ "\t#+begin_src haskell"
, "\tmain = putStrLn greeting"
, "\t where greeting = \"moin\""
- , "\t#+END_SRC" ] =?>
+ , "\t#+end_src" ] =?>
let attr' = ("", ["haskell"], [])
code' = "main = putStrLn greeting\n" <>
" where greeting = \"moin\"\n"
in codeBlockWith attr' code'
, "Empty source block" =:
- T.unlines [ " #+BEGIN_SRC haskell"
- , " #+END_SRC" ] =?>
+ T.unlines [ " #+begin_src haskell"
+ , " #+end_src" ] =?>
let attr' = ("", ["haskell"], [])
code' = ""
in codeBlockWith attr' code'
, "Source block between paragraphs" =:
T.unlines [ "Low German greeting"
- , " #+BEGIN_SRC haskell"
+ , " #+begin_src haskell"
, " main = putStrLn greeting"
, " where greeting = \"Moin!\""
- , " #+END_SRC" ] =?>
+ , " #+end_src" ] =?>
let attr' = ("", ["haskell"], [])
code' = "main = putStrLn greeting\n" <>
" where greeting = \"Moin!\"\n"
@@ -72,10 +72,10 @@ tests =
, codeBlockWith attr' code'
]
, "Source block with babel arguments" =:
- T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both"
+ T.unlines [ "#+begin_src emacs-lisp :exports both"
, "(progn (message \"Hello, World!\")"
, " (+ 23 42))"
- , "#+END_SRC" ] =?>
+ , "#+end_src" ] =?>
let classes = [ "commonlisp" ] -- as kate doesn't know emacs-lisp syntax
params = [ ("org-language", "emacs-lisp")
, ("exports", "both")
@@ -85,10 +85,10 @@ tests =
in codeBlockWith ("", classes, params) code'
, "Source block with results and :exports both" =:
- T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both"
+ T.unlines [ "#+begin_src emacs-lisp :exports both"
, "(progn (message \"Hello, World!\")"
, " (+ 23 42))"
- , "#+END_SRC"
+ , "#+end_src"
, ""
, "#+RESULTS:"
, ": 65"] =?>
@@ -104,10 +104,10 @@ tests =
codeBlockWith ("", ["example"], []) results'
, "Source block with results and :exports code" =:
- T.unlines [ "#+BEGIN_SRC emacs-lisp :exports code"
+ T.unlines [ "#+begin_src emacs-lisp :exports code"
, "(progn (message \"Hello, World!\")"
, " (+ 23 42))"
- , "#+END_SRC"
+ , "#+end_src"
, ""
, "#+RESULTS:"
, ": 65" ] =?>
@@ -120,10 +120,10 @@ tests =
in codeBlockWith ("", classes, params) code'
, "Source block with results and :exports results" =:
- T.unlines [ "#+BEGIN_SRC emacs-lisp :exports results"
+ T.unlines [ "#+begin_src emacs-lisp :exports results"
, "(progn (message \"Hello, World!\")"
, " (+ 23 42))"
- , "#+END_SRC"
+ , "#+end_src"
, ""
, "#+RESULTS:"
, ": 65" ] =?>
@@ -131,37 +131,37 @@ tests =
in codeBlockWith ("", ["example"], []) results'
, "Source block with results and :exports none" =:
- T.unlines [ "#+BEGIN_SRC emacs-lisp :exports none"
+ T.unlines [ "#+begin_src emacs-lisp :exports none"
, "(progn (message \"Hello, World!\")"
, " (+ 23 42))"
- , "#+END_SRC"
+ , "#+end_src"
, ""
, "#+RESULTS:"
, ": 65" ] =?>
(mempty :: Blocks)
, "Source block with toggling header arguments" =:
- T.unlines [ "#+BEGIN_SRC sh :noeval"
+ T.unlines [ "#+begin_src sh :noeval"
, "echo $HOME"
- , "#+END_SRC"
+ , "#+end_src"
] =?>
let classes = [ "bash" ]
params = [ ("org-language", "sh"), ("noeval", "yes") ]
in codeBlockWith ("", classes, params) "echo $HOME\n"
, "Source block with line number switch" =:
- T.unlines [ "#+BEGIN_SRC sh -n 10"
+ T.unlines [ "#+begin_src sh -n 10"
, ":() { :|:& };:"
- , "#+END_SRC"
+ , "#+end_src"
] =?>
let classes = [ "bash", "numberLines" ]
params = [ ("org-language", "sh"), ("startFrom", "10") ]
in codeBlockWith ("", classes, params) ":() { :|:& };:\n"
, "Source block with multi-word parameter values" =:
- T.unlines [ "#+BEGIN_SRC dot :cmdline -Kdot -Tpng "
+ T.unlines [ "#+begin_src dot :cmdline -Kdot -Tpng "
, "digraph { id [label=\"ID\"] }"
- , "#+END_SRC"
+ , "#+end_src"
] =?>
let classes = [ "dot" ]
params = [ ("cmdline", "-Kdot -Tpng") ]
@@ -177,12 +177,12 @@ tests =
"A chosen representation of\na rule.\n"
, "Code block with caption" =:
- T.unlines [ "#+CAPTION: Functor laws in Haskell"
- , "#+NAME: functor-laws"
- , "#+BEGIN_SRC haskell"
+ T.unlines [ "#+caption: Functor laws in Haskell"
+ , "#+name: functor-laws"
+ , "#+begin_src haskell"
, "fmap id = id"
, "fmap (p . q) = (fmap p) . (fmap q)"
- , "#+END_SRC"
+ , "#+end_src"
] =?>
divWith
nullAttr
@@ -195,9 +195,9 @@ tests =
])))
, "Non-letter chars in source block parameters" =:
- T.unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich"
+ T.unlines [ "#+begin_src C :tangle xxxx.c :city Zürich"
, "code body"
- , "#+END_SRC"
+ , "#+end_src"
] =?>
let params = [ ("org-language", "C")
, ("tangle", "xxxx.c")
diff --git a/test/Tests/Readers/Org/Block/Figure.hs b/test/Tests/Readers/Org/Block/Figure.hs
index 829ef0496..56ddde9d8 100644
--- a/test/Tests/Readers/Org/Block/Figure.hs
+++ b/test/Tests/Readers/Org/Block/Figure.hs
@@ -44,9 +44,9 @@ tests =
"Used as a metapher in evolutionary biology.")
, "Figure with HTML attributes" =:
- T.unlines [ "#+CAPTION: mah brain just explodid"
- , "#+NAME: lambdacat"
- , "#+ATTR_HTML: :style color: blue :role button"
+ T.unlines [ "#+caption: mah brain just explodid"
+ , "#+name: lambdacat"
+ , "#+attr_html: :style color: blue :role button"
, "[[file:lambdacat.jpg]]"
] =?>
let kv = [("style", "color: blue"), ("role", "button")]
@@ -55,22 +55,22 @@ tests =
in para (imageWith (mempty, mempty, kv) "lambdacat.jpg" name caption)
, "LaTeX attributes are ignored" =:
- T.unlines [ "#+CAPTION: Attribute after caption"
- , "#+ATTR_LATEX: :float nil"
+ T.unlines [ "#+caption: Attribute after caption"
+ , "#+attr_latex: :float nil"
, "[[file:test.png]]"
] =?>
para (image "test.png" "fig:" "Attribute after caption")
, "Labelled figure" =:
- T.unlines [ "#+CAPTION: My figure"
- , "#+LABEL: fig:myfig"
+ T.unlines [ "#+caption: My figure"
+ , "#+label: fig:myfig"
, "[[file:blub.png]]"
] =?>
let attr = ("fig:myfig", mempty, mempty)
in para (imageWith attr "blub.png" "fig:" "My figure")
, "Figure with empty caption" =:
- T.unlines [ "#+CAPTION:"
+ T.unlines [ "#+caption:"
, "[[file:guess.jpg]]"
] =?>
para (image "guess.jpg" "fig:" "")
diff --git a/test/Tests/Readers/Org/Block/Header.hs b/test/Tests/Readers/Org/Block/Header.hs
index 31056b5b5..d38d26efb 100644
--- a/test/Tests/Readers/Org/Block/Header.hs
+++ b/test/Tests/Readers/Org/Block/Header.hs
@@ -99,7 +99,7 @@ tests =
headerWith ("waiting-header", [], []) 1 "WAITING header"
, "Custom todo keywords" =:
- T.unlines [ "#+TODO: WAITING CANCELLED"
+ T.unlines [ "#+todo: WAITING CANCELLED"
, "* WAITING compile"
, "* CANCELLED lunch"
] =?>
@@ -109,7 +109,7 @@ tests =
<> headerWith ("lunch", [], []) 1 (doneSpan <> space <> "lunch")
, "Custom todo keywords with multiple done-states" =:
- T.unlines [ "#+TODO: WAITING | DONE CANCELLED "
+ T.unlines [ "#+todo: WAITING | DONE CANCELLED "
, "* WAITING compile"
, "* CANCELLED lunch"
, "* DONE todo-feature"
@@ -248,7 +248,7 @@ tests =
headerWith ("look", [], []) 1 "important"
, "third and forth level headers" =:
- T.unlines [ "#+OPTIONS: p:t h:3"
+ T.unlines [ "#+options: p:t h:3"
, "*** Third"
, " CLOSED: [2018-09-05 Wed 13:58]"
, " Text 3"
diff --git a/test/Tests/Readers/Org/Block/Table.hs b/test/Tests/Readers/Org/Block/Table.hs
index ab404648e..31c994d3f 100644
--- a/test/Tests/Readers/Org/Block/Table.hs
+++ b/test/Tests/Readers/Org/Block/Table.hs
@@ -167,7 +167,7 @@ tests =
]
, "Table with caption" =:
- T.unlines [ "#+CAPTION: Hitchhiker's Multiplication Table"
+ T.unlines [ "#+caption: Hitchhiker's Multiplication Table"
, "| x | 6 |"
, "| 9 | 42 |"
] =?>
@@ -180,7 +180,7 @@ tests =
]
, "named table" =:
- T.unlines [ "#+NAME: x-marks-the-spot"
+ T.unlines [ "#+name: x-marks-the-spot"
, "| x |"
] =?>
divWith ("x-marks-the-spot", mempty, mempty)
diff --git a/test/Tests/Readers/Org/Inline.hs b/test/Tests/Readers/Org/Inline.hs
index 7c8a4496c..9edd328c3 100644
--- a/test/Tests/Readers/Org/Inline.hs
+++ b/test/Tests/Readers/Org/Inline.hs
@@ -210,7 +210,7 @@ tests =
<> image "sunset.jpg" "" "")
, "Image with html attributes" =:
- T.unlines [ "#+ATTR_HTML: :width 50%"
+ T.unlines [ "#+attr_html: :width 50%"
, "[[file:guinea-pig.gif]]"
] =?>
para (imageWith ("", [], [("width", "50%")]) "guinea-pig.gif" "" "")
diff --git a/test/Tests/Readers/Org/Meta.hs b/test/Tests/Readers/Org/Meta.hs
index 0bd63b15d..3290e718b 100644
--- a/test/Tests/Readers/Org/Meta.hs
+++ b/test/Tests/Readers/Org/Meta.hs
@@ -44,7 +44,7 @@ tests =
, testGroup "Export settings"
[ "Title" =:
- "#+TITLE: Hello, World" =?>
+ "#+title: Hello, World" =?>
let titleInline = toList $ "Hello," <> space <> "World"
meta = setMeta "title" (MetaInlines titleInline) nullMeta
in Pandoc meta mempty
@@ -69,21 +69,21 @@ tests =
]
, "Date" =:
- "#+Date: Feb. *28*, 2014" =?>
+ "#+date: Feb. *28*, 2014" =?>
let date = toList . spcSep $ [ "Feb.", strong "28" <> ",", "2014" ]
meta = setMeta "date" (MetaInlines date) nullMeta
in Pandoc meta mempty
, testGroup "Description"
[ "Single line" =:
- "#+DESCRIPTION: Explanatory text" =?>
+ "#+description: Explanatory text" =?>
let description = [Str "Explanatory", Space, Str "text"]
meta = setMeta "description" (MetaInlines description) nullMeta
in Pandoc meta mempty
, "Multiline" =:
- T.unlines [ "#+DESCRIPTION: /Short/ introduction"
- , "#+DESCRIPTION: to Org-mode"
+ T.unlines [ "#+description: /Short/ introduction"
+ , "#+description: to Org-mode"
] =?>
let description = [ Emph [Str "Short"], Space, Str "introduction"
, SoftBreak
@@ -94,54 +94,54 @@ tests =
]
, "Subtitle" =:
- T.unlines [ "#+SUBTITLE: Your Life in"
- , "#+SUBTITLE: /Plain/ Text"
+ T.unlines [ "#+subtitle: Your Life in"
+ , "#+subtitle: /Plain/ Text"
] =?>
let subtitle = "Your Life in" <> softbreak <> emph "Plain" <> " Text"
in Pandoc (setMeta "subtitle" (toMetaValue subtitle) nullMeta) mempty
, "Keywords" =:
- T.unlines [ "#+KEYWORDS: pandoc, testing,"
- , "#+KEYWORDS: Org"
+ T.unlines [ "#+keywords: pandoc, testing,"
+ , "#+keywords: Org"
] =?>
let keywords = toList $ "pandoc, testing," <> softbreak <> "Org"
meta = setMeta "keywords" (MetaInlines keywords) nullMeta
in Pandoc meta mempty
, "Institute" =:
- "#+INSTITUTE: ACME Inc." =?>
+ "#+institute: ACME Inc." =?>
Pandoc (setMeta "institute" ("ACME Inc." :: Inlines) nullMeta) mempty
, testGroup "LaTeX"
[ "LATEX_HEADER" =:
- "#+LaTeX_header: \\usepackage{tikz}" =?>
+ "#+latex_header: \\usepackage{tikz}" =?>
let latexInlines = rawInline "latex" "\\usepackage{tikz}"
inclList = MetaList [MetaInlines (toList latexInlines)]
meta = setMeta "header-includes" inclList nullMeta
in Pandoc meta mempty
, "LATEX_HEADER_EXTRA" =:
- "#+LATEX_HEADER_EXTRA: \\usepackage{calc}" =?>
+ "#+latex_header_extra: \\usepackage{calc}" =?>
let latexInlines = rawInline "latex" "\\usepackage{calc}"
inclList = toMetaValue [latexInlines]
in Pandoc (setMeta "header-includes" inclList nullMeta) mempty
, testGroup "LaTeX_CLASS"
[ "stored as documentclass" =:
- "#+LATEX_CLASS: article" =?>
+ "#+latex_class: article" =?>
let meta = setMeta "documentclass" (MetaString "article") nullMeta
in Pandoc meta mempty
, "last definition takes precedence" =:
- T.unlines [ "#+LATEX_CLASS: this will not be used"
- , "#+LATEX_CLASS: report"
+ T.unlines [ "#+latex_class: this will not be used"
+ , "#+latex_class: report"
] =?>
let meta = setMeta "documentclass" (MetaString "report") nullMeta
in Pandoc meta mempty
]
, "LATEX_CLASS_OPTIONS as classoption" =:
- "#+LATEX_CLASS_OPTIONS: [a4paper]" =?>
+ "#+latex_class_options: [a4paper]" =?>
let meta = setMeta "classoption" (MetaString "a4paper") nullMeta
in Pandoc meta mempty
]
@@ -155,8 +155,8 @@ tests =
in Pandoc meta mempty
, "HTML_HEAD_EXTRA behaves like HTML_HEAD" =:
- T.unlines [ "#+HTML_HEAD: <meta name=\"generator\" content=\"pandoc\">"
- , "#+HTML_HEAD_EXTRA: <meta charset=\"utf-8\">"
+ T.unlines [ "#+html_head: <meta name=\"generator\" content=\"pandoc\">"
+ , "#+html_head_extra: <meta charset=\"utf-8\">"
] =?>
let generator = rawInline "html"
"<meta name=\"generator\" content=\"pandoc\">"
@@ -167,9 +167,9 @@ tests =
]
, testGroup "Non-export keywords"
- [ testGroup "#+LINK"
+ [ testGroup "#+link"
[ "Link abbreviation" =:
- T.unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s"
+ T.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" ""
@@ -177,7 +177,7 @@ tests =
, "Link abbreviation, defined after first use" =:
T.unlines [ "[[zl:non-sense][Non-sense articles]]"
- , "#+LINK: zl http://zeitlens.com/tags/%s.html"
+ , "#+link: zl http://zeitlens.com/tags/%s.html"
] =?>
para (link "http://zeitlens.com/tags/non-sense.html" ""
("Non-sense" <> space <> "articles"))
@@ -214,11 +214,11 @@ tests =
]
, "Unknown keyword" =:
- T.unlines [ "#+UNKNOWN_KEYWORD: Chumbawamba"
- , "#+ANOTHER_UNKNOWN: Blur"
+ T.unlines [ "#+unknown_keyword: Chumbawamba"
+ , "#+another_unknown: Blur"
] =?>
- rawBlock "org" "#+UNKNOWN_KEYWORD: Chumbawamba" <>
- rawBlock "org" "#+ANOTHER_UNKNOWN: Blur"
+ rawBlock "org" "#+unknown_keyword: Chumbawamba" <>
+ rawBlock "org" "#+another_unknown: Blur"
]
, "Properties drawer" =:
diff --git a/test/command/3706.md b/test/command/3706.md
index db50f8f68..b6c2c6db1 100644
--- a/test/command/3706.md
+++ b/test/command/3706.md
@@ -2,12 +2,12 @@ Results marker can be hidden in block attributes (#3706)
```
pandoc -f org -t native
-#+BEGIN_SRC R :exports results :colnames yes
+#+begin_src r :exports results :colnames yes
data.frame(Id = 1:3, Desc = rep("La",3))
-#+END_SRC
+#+end_src
-#+CAPTION: Lalelu.
-#+LABEL: tab
+#+caption: Lalelu.
+#+label: tab
#+RESULTS:
| Id | Desc |
|----+------|
@@ -49,12 +49,12 @@ pandoc -f org -t native
```
pandoc -f org -t native
-#+BEGIN_SRC R :exports none :colnames yes
+#+begin_src R :exports none :colnames yes
data.frame(Id = 1:2, Desc = rep("La",2))
-#+END_SRC
+#+end_src
-#+CAPTION: Lalelu.
-#+LABEL: tab
+#+caption: Lalelu.
+#+label: tab
#+RESULTS:
| Id | Desc |
|----+------|
diff --git a/test/command/4186.md b/test/command/4186.md
index 2345b0350..8c0d04a31 100644
--- a/test/command/4186.md
+++ b/test/command/4186.md
@@ -1,8 +1,8 @@
```
% pandoc -f org -t native
-#+BEGIN_EXAMPLE -i
+#+begin_example -i
This should retain the four leading spaces
-#+END_EXAMPLE
+#+end_example
^D
[CodeBlock ("",["example"],[]) " This should retain the four leading spaces\n"]
```
@@ -10,10 +10,10 @@
```
% pandoc -f org -t html
- depth 1
- #+NAME: bob
- #+BEGIN_EXAMPLE -i
+ #+name: bob
+ #+begin_example -i
Vertical alignment is four spaces beyond the appearance of the word "depth".
- #+END_EXAMPLE
+ #+end_example
- depth 2
#+begin_example
Vertically aligned with the second appearance of the word "depth".
@@ -27,10 +27,10 @@
inner list element.
#+end_example
Still inside the inner list element
- #+NAME: carrie
- #+BEGIN_EXAMPLE
+ #+name: carrie
+ #+begin_example
This belongs to the outer list element, and is aligned accordingly, since the NAME attribute is not indented deeply enough. It is not enough for the BEGIN alone to be aligned deeply if the block is meant to have a NAME.
- #+END_EXAMPLE
+ #+end_example
Still in the shallower list element since the preceding example
block forced the deeper list element to terminate.
Outside all lists.
diff --git a/test/command/5178.md b/test/command/5178.md
index 57aace945..856f86abc 100644
--- a/test/command/5178.md
+++ b/test/command/5178.md
@@ -6,21 +6,21 @@
main = putStrLn "Hello World!"
unsafePerformIO main
^D
-#+BEGIN_SRC haskell -n 42
+#+begin_src haskell -n 42
main = putStrLn "Hello World!"
unsafePerformIO main
-#+END_SRC
+#+end_src
```
```
% pandoc -f org -t native
-#+BEGIN_SRC lisp -n 20
+#+begin_src lisp -n 20
(+ 1 1)
-#+END_SRC
+#+end_src
-#+BEGIN_SRC lisp +n 10
+#+begin_src lisp +n 10
(+ 2 2)
-#+END_SRC
+#+end_src
^D
[CodeBlock ("",["commonlisp","numberLines"],[("org-language","lisp"),("startFrom","20")]) "(+ 1 1)\n"
,CodeBlock ("",["commonlisp","numberLines","continuedSourceBlock"],[("org-language","lisp"),("startFrom","10")]) "(+ 2 2)\n"]
@@ -31,11 +31,11 @@
[CodeBlock ("",["commonlisp","numberLines"],[("org-language","lisp"),("startFrom","20")]) "(+ 1 1)\n"
,CodeBlock ("",["commonlisp","numberLines","continuedSourceBlock"],[("org-language","lisp"),("startFrom","10")]) "(+ 2 2)\n"]
^D
-#+BEGIN_SRC lisp -n 20
+#+begin_src lisp -n 20
(+ 1 1)
-#+END_SRC
+#+end_src
-#+BEGIN_SRC lisp +n 10
+#+begin_src lisp +n 10
(+ 2 2)
-#+END_SRC
+#+end_src
```
diff --git a/test/org-select-tags.org b/test/org-select-tags.org
index 8f0ebfdbd..ca41a48b2 100644
--- a/test/org-select-tags.org
+++ b/test/org-select-tags.org
@@ -1,5 +1,5 @@
-#+SELECT_TAGS: yes no
-#+EXCLUDE_TAGS: no
+#+select_tags: yes no
+#+exclude_tags: no
In a document containing one or more trees containing a tag
listed in SELECT_TAGS, only those trees and their ancestor nodes will appear;
diff --git a/test/tables.org b/test/tables.org
index c4f7c994b..f58495a34 100644
--- a/test/tables.org
+++ b/test/tables.org
@@ -5,7 +5,7 @@ Simple table with caption:
| 12 | 12 | 12 | 12 |
| 123 | 123 | 123 | 123 |
| 1 | 1 | 1 | 1 |
-#+CAPTION: Demonstration of simple table syntax.
+#+caption: Demonstration of simple table syntax.
Simple table without caption:
@@ -22,7 +22,7 @@ Simple table indented two spaces:
| 12 | 12 | 12 | 12 |
| 123 | 123 | 123 | 123 |
| 1 | 1 | 1 | 1 |
-#+CAPTION: Demonstration of simple table syntax.
+#+caption: Demonstration of simple table syntax.
Multiline table with caption:
@@ -30,7 +30,7 @@ Multiline table with caption:
|-----------------+--------------+---------------+-------------------------------------------------------|
| First | row | 12.0 | Example of a row that spans multiple lines. |
| Second | row | 5.0 | Here's another one. Note the blank line between rows. |
-#+CAPTION: Here's the caption. It may span multiple lines.
+#+caption: Here's the caption. It may span multiple lines.
Multiline table without caption:
diff --git a/test/writer.org b/test/writer.org
index 7fa6b8a43..34dd51f43 100644
--- a/test/writer.org
+++ b/test/writer.org
@@ -1,7 +1,7 @@
-#+TITLE: Pandoc Test Suite
+#+title: Pandoc Test Suite
-#+AUTHOR: John MacFarlane; Anonymous
-#+DATE: July 17, 2006
+#+author: John MacFarlane; Anonymous
+#+date: July 17, 2006
This is a set of tests for pandoc. Most of them are adapted from John Gruber's
markdown test suite.
@@ -73,18 +73,18 @@ here.
:END:
E-mail style:
-#+BEGIN_QUOTE
+#+begin_quote
This is a block quote. It is pretty short.
-#+END_QUOTE
+#+end_quote
-#+BEGIN_QUOTE
+#+begin_quote
Code in a block quote:
- #+BEGIN_EXAMPLE
+ #+begin_example
sub status {
print "working";
}
- #+END_EXAMPLE
+ #+end_example
A list:
@@ -93,14 +93,14 @@ E-mail style:
Nested block quotes:
- #+BEGIN_QUOTE
+ #+begin_quote
nested
- #+END_QUOTE
+ #+end_quote
- #+BEGIN_QUOTE
+ #+begin_quote
nested
- #+END_QUOTE
-#+END_QUOTE
+ #+end_quote
+#+end_quote
This should not be a block quote: 2 > 1.
@@ -114,7 +114,7 @@ And a following paragraph.
:END:
Code:
-#+BEGIN_EXAMPLE
+#+begin_example
---- (should be four hyphens)
sub status {
@@ -122,15 +122,15 @@ Code:
}
this code block is indented by one tab
-#+END_EXAMPLE
+#+end_example
And:
-#+BEGIN_EXAMPLE
+#+begin_example
this code block is indented by two tabs
These should not be escaped: \$ \\ \> \[ \{
-#+END_EXAMPLE
+#+end_example
--------------
@@ -347,13 +347,13 @@ Multiple blocks with italics:
- /orange/ :: orange fruit
- #+BEGIN_EXAMPLE
+ #+begin_example
{ orange code block }
- #+END_EXAMPLE
+ #+end_example
- #+BEGIN_QUOTE
+ #+begin_quote
orange block quote
- #+END_QUOTE
+ #+end_quote
Multiple definitions, tight:
@@ -399,45 +399,45 @@ bar
Interpreted markdown in a table:
-#+BEGIN_HTML
+#+begin_html
<table>
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<tr>
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<td>
-#+END_HTML
+#+end_html
This is /emphasized/
-#+BEGIN_HTML
+#+begin_html
</td>
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<td>
-#+END_HTML
+#+end_html
And this is *strong*
-#+BEGIN_HTML
+#+begin_html
</td>
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
</tr>
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
</table>
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script>
-#+END_HTML
+#+end_html
Here's a simple block:
@@ -445,17 +445,17 @@ foo
This should be a code block, though:
-#+BEGIN_EXAMPLE
+#+begin_example
<div>
foo
</div>
-#+END_EXAMPLE
+#+end_example
As should this:
-#+BEGIN_EXAMPLE
+#+begin_example
<div>foo</div>
-#+END_EXAMPLE
+#+end_example
Now, nested:
@@ -463,80 +463,80 @@ foo
This should just be an HTML comment:
-#+BEGIN_HTML
+#+begin_html
<!-- Comment -->
-#+END_HTML
+#+end_html
Multiline:
-#+BEGIN_HTML
+#+begin_html
<!--
Blah
Blah
-->
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<!--
This is another comment.
-->
-#+END_HTML
+#+end_html
Code block:
-#+BEGIN_EXAMPLE
+#+begin_example
<!-- Comment -->
-#+END_EXAMPLE
+#+end_example
Just plain comment, with trailing spaces on the line:
-#+BEGIN_HTML
+#+begin_html
<!-- foo -->
-#+END_HTML
+#+end_html
Code:
-#+BEGIN_EXAMPLE
+#+begin_example
<hr />
-#+END_EXAMPLE
+#+end_example
Hr's:
-#+BEGIN_HTML
+#+begin_html
<hr>
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<hr />
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<hr />
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<hr>
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<hr />
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<hr />
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<hr class="foo" id="bar" />
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<hr class="foo" id="bar" />
-#+END_HTML
+#+end_html
-#+BEGIN_HTML
+#+begin_html
<hr class="foo" id="bar">
-#+END_HTML
+#+end_html
--------------
@@ -727,9 +727,9 @@ Indented [[/url][thrice]].
This should [not][] be a link.
-#+BEGIN_EXAMPLE
+#+begin_example
[not]: /url
-#+END_EXAMPLE
+#+end_example
Foo [[/url/][bar]].
@@ -760,15 +760,15 @@ With an ampersand: [[http://example.com/?foo=1&bar=2]]
An e-mail address: [[mailto:nobody@nowhere.net][nobody@nowhere.net]]
-#+BEGIN_QUOTE
+#+begin_quote
Blockquoted: [[http://example.com/]]
-#+END_QUOTE
+#+end_quote
Auto-links should not occur here: =<http://example.com/>=
-#+BEGIN_EXAMPLE
+#+begin_example
or here: <http://example.com/>
-#+END_EXAMPLE
+#+end_example
--------------
@@ -778,7 +778,7 @@ Auto-links should not occur here: =<http://example.com/>=
:END:
From "Voyage dans la Lune" by Georges Melies (1902):
-#+CAPTION: lalune
+#+caption: lalune
[[file:lalune.jpg]]
Here is a movie [[file:movie.jpg]] icon.
@@ -793,9 +793,9 @@ Here is a footnote reference,[fn:1] and another.[fn:2] This should /not/ be a
footnote reference, because it contains a space.[^my note] Here is an inline
note.[fn:3]
-#+BEGIN_QUOTE
+#+begin_quote
Notes can go in quotes.[fn:4]
-#+END_QUOTE
+#+end_quote
1. And in list items.[fn:5]
@@ -809,9 +809,9 @@ This paragraph should not be part of the note, as it is not indented.
Subsequent blocks are indented to show that they belong to the footnote
(as with list items).
- #+BEGIN_EXAMPLE
+ #+begin_example
{ <code> }
- #+END_EXAMPLE
+ #+end_example
If you want, you can indent every line, but you can also be lazy and
just indent the first line of each block.