aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt1
-rw-r--r--pandoc.cabal4
-rw-r--r--src/Text/Pandoc/Readers.hs3
-rw-r--r--src/Text/Pandoc/Readers/Jira.hs173
-rw-r--r--stack.yaml1
-rw-r--r--test/Tests/Old.hs2
-rw-r--r--test/Tests/Readers/Jira.hs114
-rw-r--r--test/jira-reader.jira284
-rw-r--r--test/jira-reader.native185
-rw-r--r--test/test-pandoc.hs2
10 files changed, 769 insertions, 0 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index 18a9078c4..c92b46482 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -240,6 +240,7 @@ header when requesting a document from a URL:
- `html` ([HTML])
- `ipynb` ([Jupyter notebook])
- `jats` ([JATS] XML)
+ - `jira` ([Jira] wiki markup)
- `json` (JSON version of native AST)
- `latex` ([LaTeX])
- `markdown` ([Pandoc's Markdown])
diff --git a/pandoc.cabal b/pandoc.cabal
index 209a2f276..432b81eb3 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -246,6 +246,7 @@ extra-source-files:
test/creole-reader.native
test/rst-reader.rst
test/jats-reader.xml
+ test/jira-reader.jira
test/s5-basic.html
test/s5-fancy.html
test/s5-fragment.html
@@ -405,6 +406,7 @@ library
blaze-html >= 0.9 && < 0.10,
blaze-markup >= 0.8 && < 0.9,
vector >= 0.10 && < 0.13,
+ jira-wiki-markup >= 1.0 && < 1.1,
hslua >= 1.0.1 && < 1.1,
hslua-module-system >= 0.2 && < 0.3,
hslua-module-text >= 0.2 && < 0.3,
@@ -487,6 +489,7 @@ library
Text.Pandoc.Readers.Org,
Text.Pandoc.Readers.DocBook,
Text.Pandoc.Readers.JATS,
+ Text.Pandoc.Readers.Jira,
Text.Pandoc.Readers.OPML,
Text.Pandoc.Readers.Textile,
Text.Pandoc.Readers.Native,
@@ -750,6 +753,7 @@ test-suite test-pandoc
Tests.Readers.LaTeX
Tests.Readers.HTML
Tests.Readers.JATS
+ Tests.Readers.Jira
Tests.Readers.Markdown
Tests.Readers.Org
Tests.Readers.Org.Block
diff --git a/src/Text/Pandoc/Readers.hs b/src/Text/Pandoc/Readers.hs
index 36a0e6daa..990e78f35 100644
--- a/src/Text/Pandoc/Readers.hs
+++ b/src/Text/Pandoc/Readers.hs
@@ -37,6 +37,7 @@ module Text.Pandoc.Readers
, readLaTeX
, readHtml
, readJATS
+ , readJira
, readTextile
, readDocBook
, readOPML
@@ -78,6 +79,7 @@ import Text.Pandoc.Readers.Ipynb
import Text.Pandoc.Readers.Haddock
import Text.Pandoc.Readers.HTML (readHtml)
import Text.Pandoc.Readers.JATS (readJATS)
+import Text.Pandoc.Readers.Jira (readJira)
import Text.Pandoc.Readers.LaTeX
import Text.Pandoc.Readers.Markdown
import Text.Pandoc.Readers.MediaWiki
@@ -121,6 +123,7 @@ readers = [ ("native" , TextReader readNative)
,("textile" , TextReader readTextile) -- TODO : textile+lhs
,("html" , TextReader readHtml)
,("jats" , TextReader readJATS)
+ ,("jira" , TextReader readJira)
,("latex" , TextReader readLaTeX)
,("haddock" , TextReader readHaddock)
,("twiki" , TextReader readTWiki)
diff --git a/src/Text/Pandoc/Readers/Jira.hs b/src/Text/Pandoc/Readers/Jira.hs
new file mode 100644
index 000000000..362693af9
--- /dev/null
+++ b/src/Text/Pandoc/Readers/Jira.hs
@@ -0,0 +1,173 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
+{- |
+ Module : Text.Pandoc.Readers.Org
+ Copyright : © 2019 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+
+Conversion of jira wiki formatted plain text to 'Pandoc' document.
+-}
+module Text.Pandoc.Readers.Jira ( readJira ) where
+
+import Prelude
+import Control.Monad.Except (throwError)
+import Data.Text (Text, append, pack, singleton, unpack)
+import Text.HTML.TagSoup.Entity (lookupEntity)
+import Text.Jira.Parser (parse)
+import Text.Pandoc.Class (PandocMonad (..))
+import Text.Pandoc.Builder
+import Text.Pandoc.Error (PandocError (PandocParseError))
+import Text.Pandoc.Options (ReaderOptions)
+import Text.Pandoc.Shared (stringify)
+
+import qualified Text.Jira.Markup as Jira
+
+-- | Read Jira wiki markup.
+readJira :: PandocMonad m
+ => ReaderOptions
+ -> Text
+ -> m Pandoc
+readJira _opts s = case parse s of
+ Right d -> return $ jiraToPandoc d
+ Left e -> throwError . PandocParseError $
+ "Jira parse error" `append` pack (show e)
+
+jiraToPandoc :: Jira.Doc -> Pandoc
+jiraToPandoc (Jira.Doc blks) = doc $ foldMap jiraToPandocBlocks blks
+
+--
+-- Blocks
+--
+
+-- | Converts a Jira block to a Pandoc block.
+jiraToPandocBlocks :: Jira.Block -> Blocks
+jiraToPandocBlocks = \case
+ Jira.BlockQuote blcks -> blockQuote $ foldMap jiraToPandocBlocks blcks
+ Jira.Code lang ps txt -> toPandocCodeBlocks (Just lang) ps txt
+ Jira.Color c blcks -> divWith (mempty, mempty, [("color", colorName c)]) $
+ foldMap jiraToPandocBlocks blcks
+ Jira.Header lvl inlns -> header lvl $ foldMap jiraToPandocInlines inlns
+ Jira.HorizontalRule -> horizontalRule
+ Jira.List style items -> toPandocList style items
+ Jira.NoFormat ps txt -> toPandocCodeBlocks Nothing ps txt
+ Jira.Panel ps blcks -> toPandocDiv ps blcks
+ Jira.Para inlns -> para $ foldMap jiraToPandocInlines inlns
+ Jira.Table rows -> toPandocTable rows
+
+-- | Create a pandoc list – either to a @'BulletList'@ or an @'OrderedList'@.
+toPandocList :: Jira.ListStyle -> [[Jira.Block]] -> Blocks
+toPandocList style items =
+ let items' = map (foldMap jiraToPandocBlocks) items
+ in if style == Jira.Enumeration
+ then orderedList items'
+ else bulletList items'
+
+-- | Create a pandoc @'CodeBlock'@
+toPandocCodeBlocks :: Maybe Jira.Language -> [Jira.Parameter] -> Text -> Blocks
+toPandocCodeBlocks langMay params txt =
+ let classes = case langMay of
+ Just (Jira.Language lang) -> [lang]
+ Nothing -> []
+ in codeBlockWith ("", classes, map paramToPair params) txt
+
+-- | Create a pandoc @'Div'@
+toPandocDiv :: [Jira.Parameter] -> [Jira.Block] -> Blocks
+toPandocDiv params =
+ divWith ("", [], map paramToPair params) . foldMap jiraToPandocBlocks
+
+paramToPair :: Jira.Parameter -> (Text, Text)
+paramToPair (Jira.Parameter key value) = (key, value)
+
+-- | Give textual representation of a color.
+colorName :: Jira.ColorName -> Text
+colorName (Jira.ColorName name) = name
+
+-- | Create a pandoc @'Table'@.
+-- This relies on 'simpleTable' to sanitize the table.
+toPandocTable :: [Jira.Row] -> Blocks
+toPandocTable rows =
+ let (headerRow, bodyRows) = splitIntoHeaderAndBody rows
+ in simpleTable
+ (rowToBlocksList headerRow)
+ (map rowToBlocksList bodyRows)
+
+rowToBlocksList :: Jira.Row -> [Blocks]
+rowToBlocksList (Jira.Row cells) =
+ map cellContent cells
+ where
+ cellContent cell = let content = case cell of
+ Jira.HeaderCell x -> x
+ Jira.BodyCell x -> x
+ in foldMap jiraToPandocBlocks content
+
+splitIntoHeaderAndBody :: [Jira.Row] -> (Jira.Row, [Jira.Row])
+splitIntoHeaderAndBody [] = (Jira.Row [], [])
+splitIntoHeaderAndBody rows@(first@(Jira.Row cells) : rest) =
+ let isHeaderCell (Jira.HeaderCell{}) = True
+ isHeaderCell (Jira.BodyCell{}) = False
+ in if all isHeaderCell cells
+ then (first, rest)
+ else (Jira.Row [], rows)
+
+--
+-- Inlines
+--
+
+-- | Converts a Jira inline to a Pandoc block.
+jiraToPandocInlines :: Jira.Inline -> Inlines
+jiraToPandocInlines = \case
+ Jira.Anchor t -> spanWith (t, [], []) mempty
+ Jira.AutoLink url -> link (Jira.fromURL url) "" (str (Jira.fromURL url))
+ Jira.Emoji icon -> str . iconUnicode $ icon
+ Jira.Entity entity -> str . fromEntity $ entity
+ Jira.Image _ url -> image (Jira.fromURL url) "" mempty
+ Jira.Link alias url -> link (Jira.fromURL url) "" (fromInlines alias)
+ Jira.Linebreak -> linebreak
+ Jira.Monospaced inlns -> code . stringify . toList . fromInlines $ inlns
+ Jira.Space -> space
+ Jira.SpecialChar c -> str (Data.Text.singleton c)
+ Jira.Str t -> str t
+ Jira.Styled style inlns -> fromStyle style $ fromInlines inlns
+ where
+ fromInlines = foldMap jiraToPandocInlines
+ fromEntity e = case lookupEntity (unpack e ++ ";") of
+ Nothing -> "&" `append` e `append` ";"
+ Just cs -> pack cs
+
+ fromStyle = \case
+ Jira.Emphasis -> emph
+ Jira.Insert -> spanWith ("", ["inserted"], [])
+ Jira.Strikeout -> strikeout
+ Jira.Strong -> strong
+ Jira.Subscript -> subscript
+ Jira.Superscript -> superscript
+
+-- | Get unicode representation of a Jira icon.
+iconUnicode :: Jira.Icon -> Text
+iconUnicode = \case
+ Jira.IconSlightlySmiling -> "🙂"
+ Jira.IconFrowning -> "🙁"
+ Jira.IconTongue -> "😛"
+ Jira.IconSmiling -> "😃"
+ Jira.IconWinking -> "😉"
+ Jira.IconThumbsUp -> "👍"
+ Jira.IconThumbsDown -> "👎"
+ Jira.IconInfo -> "ℹ"
+ Jira.IconCheckmark -> "✓"
+ Jira.IconX -> "🅇"
+ Jira.IconAttention -> "⚠"
+ Jira.IconPlus -> "⊞"
+ Jira.IconMinus -> "⊟"
+ Jira.IconQuestionmark -> "?"
+ Jira.IconOn -> "💡"
+ Jira.IconOff -> "💡"
+ Jira.IconStar -> "★"
+ Jira.IconStarRed -> "★"
+ Jira.IconStarGreen -> "★"
+ Jira.IconStarBlue -> "★"
+ Jira.IconStarYellow -> "★"
+ Jira.IconFlag -> "⚑"
+ Jira.IconFlagOff -> "⚐"
diff --git a/stack.yaml b/stack.yaml
index 6f2ac1c11..8356b126f 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -20,6 +20,7 @@ extra-deps:
- regex-pcre-builtin-0.95.0.8.8.35
- doclayout-0.2.0.1
- emojis-0.1
+- jira-wiki-markup-1.0.0
- HsYAML-0.2.0.0
- HsYAML-aeson-0.2.0.0
- doctemplates-0.8
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index 45e40a830..3543cdbb3 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -100,6 +100,8 @@ tests pandocPath =
]
, testGroup "jira"
[ testGroup "writer" $ writerTests' "jira"
+ , test' "reader" ["-r", "jira", "-w", "native", "-s"]
+ "jira-reader.jira" "jira-reader.native"
]
, testGroup "native"
[ testGroup "writer" $ writerTests' "native"
diff --git a/test/Tests/Readers/Jira.hs b/test/Tests/Readers/Jira.hs
new file mode 100644
index 000000000..220bd8069
--- /dev/null
+++ b/test/Tests/Readers/Jira.hs
@@ -0,0 +1,114 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{- |
+ Module : Tests.Readers.Jira
+ Copyright : © 2019 Albert Krewinel
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Albert Krewinkel <tarleb@zeitkraut.de>
+ Stability : alpha
+ Portability : portable
+
+Tests for the RST reader.
+-}
+module Tests.Readers.Jira (tests) where
+
+import Prelude
+import Data.Text (Text)
+import Test.Tasty (TestTree, testGroup)
+import Tests.Helpers (ToString, purely, test, (=?>))
+import Text.Pandoc (def)
+import Text.Pandoc.Readers.Jira (readJira)
+import Text.Pandoc.Builder
+
+jira :: Text -> Pandoc
+jira = purely $ readJira def
+
+infix 4 =:
+(=:) :: ToString c
+ => String -> (Text, c) -> TestTree
+(=:) = test jira
+
+tests :: [TestTree]
+tests =
+ [ testGroup "para"
+ [ "Simple sentence" =:
+ "Hello, World!" =?> para "Hello, World!"
+ ]
+
+ , testGroup "header"
+ [ "header" =:
+ "h1. Main\n" =?> header 1 "Main"
+ ]
+
+ , testGroup "list"
+ [ "simple list" =:
+ "* foo\n* bar\n" =?> bulletList [para "foo", para "bar"]
+
+ , "list with minus as bullets" =:
+ "- foo\n- bar\n" =?> bulletList [para "foo", para "bar"]
+
+ , "ordered list / enumeration" =:
+ "# first\n# second\n" =?> orderedList [para "first", para "second"]
+ ]
+
+ , testGroup "block quote"
+ [ "simple block quote" =:
+ "bq. _Don't_ quote me on this." =?>
+ blockQuote (para $ emph "Don't" <> space <> "quote me on this.")
+ ]
+
+ , testGroup "table"
+ [ "table without header" =:
+ "| one | two |\n| three | four |\n" =?>
+ simpleTable []
+ [ [para "one", para "two"]
+ , [para "three", para "four"]]
+
+ , "table with header" =:
+ "|| one || two ||\n| three | four |\n| five | six |\n" =?>
+ simpleTable [para "one", para "two"]
+ [ [para "three", para "four"]
+ , [para "five", para "six"]]
+
+ , "table with column header" =:
+ "|| language | haskell | lua |\n|| type | static | dynamic |\n" =?>
+ simpleTable []
+ [ [para "language", para "haskell", para "lua"]
+ , [para "type", para "static", para "dynamic"]]
+ ]
+
+ , testGroup "inlines"
+ [ "emphasis" =:
+ "*quid pro quo*" =?>
+ para (strong "quid pro quo")
+
+ , "deleted" =:
+ "-old-" =?>
+ para (strikeout "old")
+
+ , "monospaced" =:
+ "{{this *is* monospace}}" =?>
+ para (code "this is monospace")
+
+ , "sub- and superscript" =:
+ "HCO ~3~^-^" =?>
+ para ("HCO " <> subscript "3" <> superscript "-")
+
+ , "linebreak" =:
+ "first\nsecond" =?>
+ para ("first" <> linebreak <> "second")
+
+ , "link" =:
+ "[Example|https://example.org]" =?>
+ para (link "https://example.org" "" "Example")
+
+ , "image" =:
+ "!https://example.com/image.jpg!" =?>
+ para (image "https://example.com/image.jpg" "" mempty)
+
+ , "HTML entity" =:
+ "me &amp; you" =?> para "me & you"
+ ]
+ ]
diff --git a/test/jira-reader.jira b/test/jira-reader.jira
new file mode 100644
index 000000000..79dfec945
--- /dev/null
+++ b/test/jira-reader.jira
@@ -0,0 +1,284 @@
+h1. {anchor:headers}Headers
+h2. {anchor:level-2-with-an-embedded-link}Level 2 with an [embedded link|https://test.example/url]
+h3. {anchor:level-3-with-emphasis}Level 3 with _emphasis_
+h4. Level 4
+h5. Level 5
+h6. Level 6
+
+h0. this is not a header.
+
+----
+h1. Paragraphs
+Here’s a regular paragraph.
+
+Here’s one with a bullet. * criminey.
+
+There should be a hard line break
+here.
+
+----
+h1. Block Quotes
+E-mail style:
+
+bq. This is a block quote. It is pretty short.
+{quote}
+Code in a block quote:
+
+{code:java}
+sub status {
+ print "working";
+}
+{code}
+
+An enumeration:
+
+# item one
+# item two
+{quote}
+
+A following paragraph.
+
+----
+h1. Code Blocks
+
+Code:
+
+{code:java}
+---- (should be four hyphens)
+
+sub status {
+ print "working";
+}
+{code}
+And:
+
+{code:java}
+ this code block is indented by two tabs
+
+These should not be escaped: \$ \\ \> \[ \{
+{code}
+
+----
+h1. {anchor:lists}Lists
+h2. {anchor:unordered}Unordered
+Asterisks:
+
+* asterisk 1
+* asterisk 2
+* asterisk 3
+
+Minuses:
+
+- Minus 1
+- Minus 2
+- Minus 3
+
+h2. Ordered
+
+# First
+# Second
+# Third
+
+Linebreak in paragraph:
+
+# Item 1, line one.
+Item 1. line two. The quick brown fox jumped over the lazy dog’s back.
+# Item 2.
+# Item 3.
+
+h2. Nested
+* Tab
+** Tab
+*** Tab
+
+Here’s another:
+
+# First
+# Second:
+#* Fee
+#* Fie
+#* Foe
+# Third
+
+Nested enumerations:
+
+# Essential
+## Important
+### Relevant
+#### Insignificant
+
+----
+h1. Linebreaks and Markup in Lists
+
+* *apple*
+red fruit
+* *orange*
+orange fruit
+* *banana*
+yellow fruit
+
+Multiple blocks with italics:
+
+* *_apple_*
+red fruit
+contains seeds, crisp, pleasant to taste
+* *_orange_*
+orange fruit
+{code:java}
+{ orange code block }
+{code}
+bq. orange block quote
+
+----
+h1. Colored Text Blocks
+{color:red}
+This is red.
+{color}
+
+h2. Eiffel 65
+
+{color:blue}
+da ba dee
+{color}
+
+----
+h1. Inline Markup
+This is _emphasized_, and so _is this_.
+
+This is *strong*, and so *is this*.
+
+An _[emphasized link|https://my.example/url]_.
+
+*_This is strong and em._*
+
+So is *_this_* word.
+
+This is code: {{>}}, {{$}}, {{&bsol;}}, {{&bsol;$}}, {{<html>}}.
+
+-This is _strikeout_.-
+
+Superscripts: a{^}bc{^}d a{^}_hello_{^} a{^}hello there{^}.
+
+Subscripts: H{~}2{~}O, C{~}6{~}H{~}12{~}O{~}6{~}, C{~} n {~}H{~}_2n_{~}O{~}n{~}.
+
+These should not be superscripts or subscripts, because of markers used within words: a^b c^d, a~b c~d.
+
+----
+h1. Dashes, and emoticons
+
+Some dashes: one -- two --- three.
+
+Sure (/)
+Nope (x)
+
+Nice :D
+
+Capital d\:D
+
+----
+h1. Math
+
+* 2 + 2 = 4
+* _x_ ∈ {_}y{_}
+* _α_ ∧ {_}ω{_}
+* _p_-Tree
+* Here’s one more: _α_ + {_}ω{_} × {_}x{_}^2^.
+
+
+----
+h1. Special Characters
+Here is some unicode:
+
+* I hat: Î
+* o umlaut: ö
+* section: §
+* set membership: ∈
+* copyright: ©
+
+AT&T has an ampersand in their name.
+
+AT&amp;T is another way to write it.
+
+This & that.
+
+4 < 5.
+
+6 > 5.
+
+Backslash: &bsol;
+
+Backtick: `
+
+Asterisk: *
+
+Underscore: _
+
+Left brace: {
+
+Right brace: }
+
+Left bracket: [
+
+Right bracket: ]
+
+Left paren: (
+
+Right paren: )
+
+Greater-than: >
+
+Hash: #
+
+Period: .
+
+Bang: !
+
+Plus: +
+
+Minus: -
+
+----
+h1. Links
+h2. Explicit
+Just a [URL|https://example.org/url].
+
+[File URL|file://some/file/name/].
+
+[IRC link|irc://example.org/pandoc].
+
+[Email link|mailto:nobody@nowhere.invalid]
+
+[Not a link|not a URL].
+
+h2. Reference
+With [embedded \[brackets\]|https://example.net/url/].
+
+https://pandoc.org by itself should be a link.
+
+h2. With ampersands
+Here’s a [link with an ampersand in the URL|http://example.com/?foo=1&bar=2].
+
+Here’s a link with an ampersand in the link text: [AT&T|http://att.com/].
+
+h2. Autolinks
+With an ampersand: http://example.com/?foo=1&bar=2
+
+* In a list?
+* http://example.com/
+* It should.
+
+An e-mail address: mailto:nobody@nowhere.invalid
+
+bq. Blockquoted: http://example.com/
+
+{code:java}
+Autolink should not occur here: <http://example.com/>
+{code}
+
+----
+h1. Images
+From "Voyage dans la Lune" by Georges Melies (1902):
+
+!lalune.jpg!
+
+Here is a movie !movie.jpg! icon.
diff --git a/test/jira-reader.native b/test/jira-reader.native
new file mode 100644
index 000000000..618ff225b
--- /dev/null
+++ b/test/jira-reader.native
@@ -0,0 +1,185 @@
+Pandoc (Meta {unMeta = fromList []})
+[Header 1 ("",[],[]) [Span ("headers",[],[]) [],Str "Headers"]
+,Header 2 ("",[],[]) [Span ("level-2-with-an-embedded-link",[],[]) [],Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embedded",Space,Str "link"] ("https://test.example/url","")]
+,Header 3 ("",[],[]) [Span ("level-3-with-emphasis",[],[]) [],Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]]
+,Header 4 ("",[],[]) [Str "Level",Space,Str "4"]
+,Header 5 ("",[],[]) [Str "Level",Space,Str "5"]
+,Header 6 ("",[],[]) [Str "Level",Space,Str "6"]
+,Para [Str "h0.",Space,Str "this",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "header."]
+,HorizontalRule
+,Header 1 ("",[],[]) [Str "Paragraphs"]
+,Para [Str "Here\8217s",Space,Str "a",Space,Str "regular",Space,Str "paragraph."]
+,Para [Str "Here\8217s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet.",Space,Str "*",Space,Str "criminey."]
+,Para [Str "There",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "hard",Space,Str "line",Space,Str "break",LineBreak,Str "here."]
+,HorizontalRule
+,Header 1 ("",[],[]) [Str "Block",Space,Str "Quotes"]
+,Para [Str "E-mail",Space,Str "style:"]
+,BlockQuote
+ [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote.",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short."]]
+,BlockQuote
+ [Para [Str "Code",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote:"]
+ ,CodeBlock ("",["java"],[]) "sub status {\n print \"working\";\n}\n"
+ ,Para [Str "An",Space,Str "enumeration:"]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "item",Space,Str "one"]]
+ ,[Para [Str "item",Space,Str "two"]]]]
+,Para [Str "A",Space,Str "following",Space,Str "paragraph."]
+,HorizontalRule
+,Header 1 ("",[],[]) [Str "Code",Space,Str "Blocks"]
+,Para [Str "Code:"]
+,CodeBlock ("",["java"],[]) "---- (should be four hyphens)\n\nsub status {\n print \"working\";\n}\n"
+,Para [Str "And:"]
+,CodeBlock ("",["java"],[]) " this code block is indented by two tabs\n\nThese should not be escaped: \\$ \\\\ \\> \\[ \\{\n"
+,HorizontalRule
+,Header 1 ("",[],[]) [Span ("lists",[],[]) [],Str "Lists"]
+,Header 2 ("",[],[]) [Span ("unordered",[],[]) [],Str "Unordered"]
+,Para [Str "Asterisks:"]
+,BulletList
+ [[Para [Str "asterisk",Space,Str "1"]]
+ ,[Para [Str "asterisk",Space,Str "2"]]
+ ,[Para [Str "asterisk",Space,Str "3"]]]
+,Para [Str "Minuses:"]
+,BulletList
+ [[Para [Str "Minus",Space,Str "1"]]
+ ,[Para [Str "Minus",Space,Str "2"]]
+ ,[Para [Str "Minus",Space,Str "3"]]]
+,Header 2 ("",[],[]) [Str "Ordered"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "First"]]
+ ,[Para [Str "Second"]]
+ ,[Para [Str "Third"]]]
+,Para [Str "Linebreak",Space,Str "in",Space,Str "paragraph:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "Item",Space,Str "1,",Space,Str "line",Space,Str "one.",LineBreak,Str "Item",Space,Str "1.",Space,Str "line",Space,Str "two.",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog\8217s",Space,Str "back."]]
+ ,[Para [Str "Item",Space,Str "2."]]
+ ,[Para [Str "Item",Space,Str "3."]]]
+,Header 2 ("",[],[]) [Str "Nested"]
+,BulletList
+ [[Para [Str "Tab"]
+ ,BulletList
+ [[Para [Str "Tab"]
+ ,BulletList
+ [[Para [Str "Tab"]]]]]]]
+,Para [Str "Here\8217s",Space,Str "another:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "First"]]
+ ,[Para [Str "Second:"]
+ ,BulletList
+ [[Para [Str "Fee"]]
+ ,[Para [Str "Fie"]]
+ ,[Para [Str "Foe"]]]]
+ ,[Para [Str "Third"]]]
+,Para [Str "Nested",Space,Str "enumerations:"]
+,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "Essential"]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "Important"]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "Relevant"]
+ ,OrderedList (1,DefaultStyle,DefaultDelim)
+ [[Para [Str "Insignificant"]]]]]]]]]
+,HorizontalRule
+,Header 1 ("",[],[]) [Str "Linebreaks",Space,Str "and",Space,Str "Markup",Space,Str "in",Space,Str "Lists"]
+,BulletList
+ [[Para [Strong [Str "apple"],LineBreak,Str "red",Space,Str "fruit"]]
+ ,[Para [Strong [Str "orange"],LineBreak,Str "orange",Space,Str "fruit"]]
+ ,[Para [Strong [Str "banana"],LineBreak,Str "yellow",Space,Str "fruit"]]]
+,Para [Str "Multiple",Space,Str "blocks",Space,Str "with",Space,Str "italics:"]
+,BulletList
+ [[Para [Strong [Emph [Str "apple"]],LineBreak,Str "red",Space,Str "fruit",LineBreak,Str "contains",Space,Str "seeds,",Space,Str "crisp,",Space,Str "pleasant",Space,Str "to",Space,Str "taste"]]
+ ,[Para [Strong [Emph [Str "orange"]],LineBreak,Str "orange",Space,Str "fruit"]
+ ,CodeBlock ("",["java"],[]) "{ orange code block }\n"
+ ,BlockQuote
+ [Para [Str "orange",Space,Str "block",Space,Str "quote"]]]]
+,HorizontalRule
+,Header 1 ("",[],[]) [Str "Colored",Space,Str "Text",Space,Str "Blocks"]
+,Div ("",[],[("color","red")])
+ [Para [LineBreak,Str "This",Space,Str "is",Space,Str "red."]]
+,Header 2 ("",[],[]) [Str "Eiffel",Space,Str "65"]
+,Div ("",[],[("color","blue")])
+ [Para [LineBreak,Str "da",Space,Str "ba",Space,Str "dee"]]
+,HorizontalRule
+,Header 1 ("",[],[]) [Str "Inline",Space,Str "Markup"]
+,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."]
+,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."]
+,Para [Str "An",Space,Emph [Link ("",[],[]) [Str "emphasized",Space,Str "link"] ("https://my.example/url","")],Str "."]
+,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
+,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
+,Para [Str "This",Space,Str "is",Space,Str "code:",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."]
+,Para [Strikeout [Str "This",Space,Str "is",Space,Emph [Str "strikeout"],Str "."]]
+,Para [Str "Superscripts:",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Superscript [Emph [Str "hello"]],Space,Str "a",Superscript [Str "hello\160there"],Str "."]
+,Para [Str "Subscripts:",Space,Str "H",Subscript [Str "2"],Str "O,",Space,Str "C",Subscript [Str "6"],Str "H",Subscript [Str "12"],Str "O",Subscript [Str "6"],Str ",",Space,Str "C",Subscript [Str "\160n\160"],Str "H",Subscript [Emph [Str "2n"]],Str "O",Subscript [Str "n"],Str "."]
+,Para [Str "These",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "superscripts",Space,Str "or",Space,Str "subscripts,",Space,Str "because",Space,Str "of",Space,Str "markers",Space,Str "used",Space,Str "within",Space,Str "words:",Space,Str "a^b",Space,Str "c^d,",Space,Str "a~b",Space,Str "c~d."]
+,HorizontalRule
+,Header 1 ("",[],[]) [Str "Dashes,",Space,Str "and",Space,Str "emoticons"]
+,Para [Str "Some",Space,Str "dashes:",Space,Str "one",Space,Str "\8211",Space,Str "two",Space,Str "\8212",Space,Str "three."]
+,Para [Str "Sure",Space,Str "\10003",LineBreak,Str "Nope",Space,Str "\127303"]
+,Para [Str "Nice",Space,Str "\128515"]
+,Para [Str "Capital",Space,Str "d:D"]
+,HorizontalRule
+,Header 1 ("",[],[]) [Str "Math"]
+,BulletList
+ [[Para [Str "2\8197+\8197\&2\8196=\8196\&4"]]
+ ,[Para [Emph [Str "x"],Str "\8196\8712\8196",Emph [Str "y"]]]
+ ,[Para [Emph [Str "\945"],Str "\8197\8743\8197",Emph [Str "\969"]]]
+ ,[Para [Emph [Str "p"],Str "-Tree"]]
+ ,[Para [Str "Here\8217s",Space,Str "one",Space,Str "more:",Space,Emph [Str "\945"],Str "\8197+\8197",Emph [Str "\969"],Str "\8197\215\8197",Emph [Str "x"],Superscript [Str "2"],Str "."]]]
+,HorizontalRule
+,Header 1 ("",[],[]) [Str "Special",Space,Str "Characters"]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode:"]
+,BulletList
+ [[Para [Str "I",Space,Str "hat:",Space,Str "\206"]]
+ ,[Para [Str "o",Space,Str "umlaut:",Space,Str "\246"]]
+ ,[Para [Str "section:",Space,Str "\167"]]
+ ,[Para [Str "set",Space,Str "membership:",Space,Str "\8712"]]
+ ,[Para [Str "copyright:",Space,Str "\169"]]]
+,Para [Str "AT&T",Space,Str "has",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "their",Space,Str "name."]
+,Para [Str "AT&T",Space,Str "is",Space,Str "another",Space,Str "way",Space,Str "to",Space,Str "write",Space,Str "it."]
+,Para [Str "This",Space,Str "&",Space,Str "that."]
+,Para [Str "4",Space,Str "<",Space,Str "5."]
+,Para [Str "6",Space,Str ">",Space,Str "5."]
+,Para [Str "Backslash:",Space,Str "\\"]
+,Para [Str "Backtick:",Space,Str "`"]
+,Para [Str "Asterisk:",Space,Str "*"]
+,Para [Str "Underscore:",Space,Str "_"]
+,Para [Str "Left",Space,Str "brace:",Space,Str "{"]
+,Para [Str "Right",Space,Str "brace:",Space,Str "}"]
+,Para [Str "Left",Space,Str "bracket:",Space,Str "["]
+,Para [Str "Right",Space,Str "bracket:",Space,Str "]"]
+,Para [Str "Left",Space,Str "paren:",Space,Str "("]
+,Para [Str "Right",Space,Str "paren:",Space,Str ")"]
+,Para [Str "Greater-than:",Space,Str ">"]
+,Para [Str "Hash:",Space,Str "#"]
+,Para [Str "Period:",Space,Str "."]
+,Para [Str "Bang:",Space,Str "!"]
+,Para [Str "Plus:",Space,Str "+"]
+,Para [Str "Minus:",Space,Str "-"]
+,HorizontalRule
+,Header 1 ("",[],[]) [Str "Links"]
+,Header 2 ("",[],[]) [Str "Explicit"]
+,Para [Str "Just",Space,Str "a",Space,Link ("",[],[]) [Str "URL"] ("https://example.org/url",""),Str "."]
+,Para [Link ("",[],[]) [Str "File",Space,Str "URL"] ("file://some/file/name/",""),Str "."]
+,Para [Link ("",[],[]) [Str "IRC",Space,Str "link"] ("irc://example.org/pandoc",""),Str "."]
+,Para [Link ("",[],[]) [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.invalid","")]
+,Para [Str "[Not",Space,Str "a",Space,Str "link|not",Space,Str "a",Space,Str "URL]."]
+,Header 2 ("",[],[]) [Str "Reference"]
+,Para [Str "With",Space,Link ("",[],[]) [Str "embedded",Space,Str "[brackets]"] ("https://example.net/url/",""),Str "."]
+,Para [Link ("",[],[]) [Str "https://pandoc.org by itself should be a link."] ("https://pandoc.org by itself should be a link.","")]
+,Header 2 ("",[],[]) [Str "With",Space,Str "ampersands"]
+,Para [Str "Here\8217s",Space,Str "a",Space,Link ("",[],[]) [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
+,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link ("",[],[]) [Str "AT&T"] ("http://att.com/",""),Str "."]
+,Header 2 ("",[],[]) [Str "Autolinks"]
+,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",[],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
+,BulletList
+ [[Para [Str "In",Space,Str "a",Space,Str "list?"]]
+ ,[Para [Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
+ ,[Para [Str "It",Space,Str "should."]]]
+,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",[],[]) [Str "mailto:nobody@nowhere.invalid"] ("mailto:nobody@nowhere.invalid","")]
+,BlockQuote
+ [Para [Str "Blockquoted:",Space,Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
+,CodeBlock ("",["java"],[]) "Autolink should not occur here: <http://example.com/>\n"
+,HorizontalRule
+,Header 1 ("",[],[]) [Str "Images"]
+,Para [Str "From",Space,Str "\"Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune\"",Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
+,Para [Image ("",[],[]) [] ("lalune.jpg","")]
+,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [] ("movie.jpg",""),Space,Str "icon."]]
diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs
index 775f998ca..9d64b61b6 100644
--- a/test/test-pandoc.hs
+++ b/test/test-pandoc.hs
@@ -17,6 +17,7 @@ import qualified Tests.Readers.EPUB
import qualified Tests.Readers.FB2
import qualified Tests.Readers.HTML
import qualified Tests.Readers.JATS
+import qualified Tests.Readers.Jira
import qualified Tests.Readers.LaTeX
import qualified Tests.Readers.Markdown
import qualified Tests.Readers.Muse
@@ -73,6 +74,7 @@ tests pandocPath = testGroup "pandoc tests"
, testGroup "Markdown" Tests.Readers.Markdown.tests
, testGroup "HTML" Tests.Readers.HTML.tests
, testGroup "JATS" Tests.Readers.JATS.tests
+ , testGroup "Jira" Tests.Readers.Jira.tests
, testGroup "Org" Tests.Readers.Org.tests
, testGroup "RST" Tests.Readers.RST.tests
, testGroup "Docx" Tests.Readers.Docx.tests