Jira: support citations, attachment links, and user links

Closes: #6231
Closes: #6238
Closes: #6239
This commit is contained in:
Albert Krewinkel 2020-04-04 14:27:27 +02:00
parent d867cac8ca
commit c3f539364a
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
6 changed files with 109 additions and 9 deletions

View file

@ -412,7 +412,7 @@ library
blaze-html >= 0.9 && < 0.10,
blaze-markup >= 0.8 && < 0.9,
vector >= 0.10 && < 0.13,
jira-wiki-markup >= 1.2.1 && < 1.3,
jira-wiki-markup >= 1.3 && < 1.4,
hslua >= 1.0.1 && < 1.2,
hslua-module-system >= 0.2 && < 0.3,
hslua-module-text >= 0.2 && < 0.3,

View file

@ -119,13 +119,14 @@ jiraToPandocInlines :: Jira.Inline -> Inlines
jiraToPandocInlines = \case
Jira.Anchor t -> spanWith (t, [], []) mempty
Jira.AutoLink url -> link (Jira.fromURL url) "" (str (Jira.fromURL url))
Jira.Citation ils -> str "" <> space <> emph (fromInlines ils)
Jira.ColorInline c ils -> spanWith ("", [], [("color", colorName c)]) $
fromInlines ils
Jira.Emoji icon -> str . iconUnicode $ icon
Jira.Entity entity -> str . fromEntity $ entity
Jira.Image params url -> let (title, attr) = imgParams params
in imageWith attr (Jira.fromURL url) title mempty
Jira.Link alias url -> link (Jira.fromURL url) "" (fromInlines alias)
Jira.Link lt alias url -> jiraLinkToPandoc lt alias url
Jira.Linebreak -> linebreak
Jira.Monospaced inlns -> code . stringify . toList . fromInlines $ inlns
Jira.Space -> space
@ -157,6 +158,19 @@ jiraToPandocInlines = \case
_ -> let kv = (Jira.parameterKey p, Jira.parameterValue p)
in (title, (ident, classes, kv:kvs))
-- | Convert a Jira link to pandoc inlines.
jiraLinkToPandoc :: Jira.LinkType -> [Jira.Inline] -> Jira.URL -> Inlines
jiraLinkToPandoc linkType alias url =
let url' = (if linkType == Jira.User then ("~" <>) else id) $ Jira.fromURL url
alias' = case alias of
[] -> str url'
_ -> foldMap jiraToPandocInlines alias
in case linkType of
Jira.External -> link url' "" alias'
Jira.Email -> link ("mailto:" <> url') "" alias'
Jira.Attachment -> linkWith ("", ["attachment"], []) url' "" alias'
Jira.User -> linkWith ("", ["user-account"], []) url' "" alias'
-- | Get unicode representation of a Jira icon.
iconUnicode :: Jira.Icon -> Text
iconUnicode = \case

View file

@ -1,5 +1,6 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{- |
Module : Text.Pandoc.Writers.Jira
Copyright : © 2010-2020 Albert Krewinkel, John MacFarlane
@ -25,7 +26,7 @@ import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
import Text.Pandoc.Options (WriterOptions (writerTemplate, writerWrapText),
WrapOption (..))
import Text.Pandoc.Shared (linesToPara)
import Text.Pandoc.Shared (linesToPara, stringify)
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Writers.Math (texMathToInlines)
import Text.Pandoc.Writers.Shared (defField, metaToContext)
@ -193,8 +194,7 @@ toJiraInlines inlines = do
Emph xs -> styled Jira.Emphasis xs
Image attr _ tgt -> imageToJira attr (fst tgt) (snd tgt)
LineBreak -> pure . singleton $ Jira.Linebreak
Link _ xs (tgt, _) -> singleton . flip Jira.Link (Jira.URL tgt)
<$> toJiraInlines xs
Link attr xs tgt -> toJiraLink attr tgt xs
Math mtype cs -> mathToJira mtype cs
Note bs -> registerNotes bs
Quoted qt xs -> quotedToJira qt xs
@ -242,6 +242,28 @@ imageToJira (_, classes, kvs) src title =
else Jira.Parameter "title" title : imgParams
in pure . singleton $ Jira.Image imgParams' (Jira.URL src)
-- | Creates a Jira Link element.
toJiraLink :: PandocMonad m
=> Attr
-> Target
-> [Inline]
-> JiraConverter m [Jira.Inline]
toJiraLink (_, classes, _) (url, _) alias = do
let (linkType, url') = toLinkType url
description <- if url `elem` [stringify alias, "mailto:" <> stringify alias]
then pure mempty
else toJiraInlines alias
pure . singleton $ Jira.Link linkType description (Jira.URL url')
where
toLinkType url'
| Just email <- T.stripPrefix "mailto:" url' = (Jira.Email, email)
| "user-account" `elem` classes = (Jira.User, dropTilde url)
| "attachment" `elem` classes = (Jira.Attachment, url)
| otherwise = (Jira.External, url)
dropTilde txt = case T.uncons txt of
Just ('~', username) -> username
_ -> txt
mathToJira :: PandocMonad m
=> MathType
-> Text

View file

@ -20,7 +20,7 @@ extra-deps:
- regex-pcre-builtin-0.95.0.8.8.35
- doclayout-0.3
- emojis-0.1
- jira-wiki-markup-1.2.0
- jira-wiki-markup-1.3.0
- HsYAML-0.2.0.0
- HsYAML-aeson-0.2.0.0
- doctemplates-0.8.1

View file

@ -111,6 +111,10 @@ tests =
"HCO ~3~^-^" =?>
para ("HCO " <> subscript "3" <> superscript "-")
, "citation" =:
"Et tu, Brute? ??Caesar??" =?>
para ("Et tu, Brute? — " <> emph "Caesar")
, "color" =:
"This is {color:red}red{color}." =?>
para ("This is " <> spanWith ("", [], [("color", "red")]) "red" <> ".")
@ -123,9 +127,35 @@ tests =
"first\nsecond" =?>
para ("first" <> linebreak <> "second")
, "link" =:
"[Example|https://example.org]" =?>
para (link "https://example.org" "" "Example")
, testGroup "links"
[ "external" =:
"[Example|https://example.org]" =?>
para (link "https://example.org" "" "Example")
, "email" =:
"[mailto:me@example.org]" =?>
para (link "mailto:me@example.org" "" "me@example.org")
, "email with description" =:
"[email|mailto:me@example.org]" =?>
para (link "mailto:me@example.org" "" "email")
, "attachment" =:
"[^example.txt]" =?>
para (linkWith ("", ["attachment"], []) "example.txt" "" "example.txt")
, "attachment with description" =:
"[an example^example.txt]" =?>
para (linkWith ("", ["attachment"], []) "example.txt" "" "an example")
, "user" =:
"[~johndoe]" =?>
para (linkWith ("", ["user-account"], []) "~johndoe" "" "~johndoe")
, "user with description" =:
"[John Doe|~johndoe]" =?>
para (linkWith ("", ["user-account"], []) "~johndoe" "" "John Doe")
]
, "image" =:
"!https://example.com/image.jpg!" =?>

View file

@ -28,5 +28,39 @@ tests =
imageWith ("", [], [("align", "right"), ("height", "50")])
"image.png" "" mempty =?>
"!image.png|align=right, height=50!"
, testGroup "links"
[ "external link" =:
link "https://example.com/test.php" "" "test" =?>
"[test|https://example.com/test.php]"
, "external link without description" =:
link "https://example.com/tmp.js" "" "https://example.com/tmp.js" =?>
"[https://example.com/tmp.js]"
, "email link" =:
link "mailto:me@example.com" "" "Jane" =?>
"[Jane|mailto:me@example.com]"
, "email link without description" =:
link "mailto:me@example.com" "" "me@example.com" =?>
"[mailto:me@example.com]"
, "attachment link" =:
linkWith ("", ["attachment"], []) "foo.txt" "" "My file" =?>
"[My file^foo.txt]"
, "attachment link without description" =:
linkWith ("", ["attachment"], []) "foo.txt" "" "foo.txt" =?>
"[^foo.txt]"
, "user link" =:
linkWith ("", ["user-account"], []) "~johndoe" "" "John Doe" =?>
"[John Doe|~johndoe]"
, "user link with user as description" =:
linkWith ("", ["user-account"], []) "~johndoe" "" "~johndoe" =?>
"[~johndoe]"
]
]
]