{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
module Text.Jira.Parser.Inline
( inline
, anchor
, autolink
, colorInline
, dash
, emoji
, entity
, image
, linebreak
, link
, monospaced
, specialChar
, str
, styled
, whitespace
, specialChars
) where
import Control.Monad (guard, void)
import Data.Char (isAlphaNum, isPunctuation, ord)
#if !MIN_VERSION_base(4,13,0)
import Data.Monoid ((<>), All (..))
#else
import Data.Monoid (All (..))
#endif
import Data.Text (append, pack)
import Text.Jira.Markup
import Text.Jira.Parser.Core
import Text.Jira.Parser.Shared
import Text.Parsec
inline :: JiraParser Inline
inline = notFollowedBy' blockEnd *> choice
[ whitespace
, emoji
, dash
, autolink
, str
, linebreak
, link
, image
, styled
, colorInline
, monospaced
, anchor
, entity
, specialChar
] <?> "inline"
where
blockEnd = char '{' *> choice (map string blockNames) <* char '}'
specialChars :: String
specialChars = "_+-*^~|[]{}(!&\\:;"
linebreak :: JiraParser Inline
linebreak = Linebreak <$ try (
choice [ void $ newline <* notFollowedBy' endOfPara
, void $ string "\\\\" <* notFollowedBy' (char '\\')
]
<* updateLastSpcPos
) <?> "linebreak"
whitespace :: JiraParser Inline
whitespace = Space <$ skipMany1 (char ' ') <* updateLastSpcPos
<?> "whitespace"
str :: JiraParser Inline
str = Str . pack . mconcat
<$> many1 (alphaNums <|> otherNonSpecialChars)
<?> "string"
where
nonStrChars = " \n" ++ specialChars
alphaNums = many1 alphaNum <* updateLastStrPos
otherNonSpecialChars = many1 . satisfy $ \c ->
not (isAlphaNum c || c `elem` nonStrChars)
entity :: JiraParser Inline
entity = Entity . pack
<$> try (char '&' *> (numerical <|> named) <* char ';')
where
numerical = (:) <$> char '#' <*> many1 digit
named = many1 letter
emoji :: JiraParser Inline
emoji = Emoji <$> icon <* notFollowedBy' letter <?> "emoji"
dash :: JiraParser Inline
dash = try $ do
guard =<< notAfterString
_ <- string "--"
choice [ Str "—" <$ char '-'
, pure (Str "–")
] <* lookAhead (void (char ' ') <|> eof)
specialChar :: JiraParser Inline
specialChar = SpecialChar <$> (escapedChar <|> plainSpecialChar)
<?> "special char"
where
escapedChar = try (char '\\' *> satisfy isPunctuation)
plainSpecialChar = do
inTablePred <- do
b <- stateInTable <$> getState
return $ if b then All . (/= '|') else mempty
inLinkPred <- do
b <- stateInLink <$> getState
return $ if b then All . (`notElem` ("]|\n" :: String)) else mempty
oneOf $ filter (getAll . (inTablePred <> inLinkPred)) specialChars
anchor :: JiraParser Inline
anchor = Anchor . pack . filter (/= ' ')
<$> try (string "{anchor:" *> noneOf "\n" `manyTill` char '}')
image :: JiraParser Inline
image = try $ do
src <- char '!' *> (URL . pack <$> many1 (noneOf "\r\t\n|]!"))
params <- option [] (char '|' *> (thumbnail <|> imgParams `sepBy` comma))
_ <- char '!'
return $ Image params src
where
thumbnail = [Parameter "thumbnail" ""] <$ try (string "thumbnail")
imgParams = try (Parameter <$> key <*> (char '=' *> value))
key = pack <$> many1 (noneOf ",\"'\t\n\r |{}=!")
value = pack <$> many1 (noneOf ",\"'\n\r|{}=!")
comma = char ',' *> skipSpaces
link :: JiraParser Inline
link = try $ do
guard . not . stateInLink =<< getState
withStateFlag (\b st -> st { stateInLink = b }) $ do
_ <- char '['
alias <- option [] $ try (many inline <* char '|')
linkUrl <- email <|> url
_ <- char ']'
return $ Link alias linkUrl
autolink :: JiraParser Inline
autolink = AutoLink <$> (email <|> url) <?> "email or other URL"
url :: JiraParser URL
url = try $ do
urlScheme <- scheme
sep <- pack <$> string "://"
rest <- pack <$> many urlChar
return $ URL (urlScheme `append` sep `append` rest)
where
scheme = do
first <- letter
case first of
'f' -> ("file" <$ string "ile") <|> ("ftp" <$ string "tp")
'h' -> string "ttp" *> option "http" ("https" <$ char 's')
'i' -> "irc" <$ string "rc"
'n' -> ("nntp" <$ string "ntp") <|> ("news" <$ string "ews")
_ -> fail "not looking at a known scheme"
email :: JiraParser URL
email = URL . pack <$> try
((++) <$> string "mailto:" <*> many1 urlChar)
urlChar :: JiraParser Char
urlChar = satisfy $ \c ->
c `notElem` ("|]" :: String) && ord c >= 32 && ord c <= 127
colorInline :: JiraParser Inline
colorInline = try $ do
name <- string "{color:" *> (colorName <|> colorCode) <* char '}'
content <- inline `manyTill` try (string "{color}")
return $ ColorInline (ColorName $ pack name) content
where
colorName = many1 letter
colorCode = (:) <$> option '#' (char '#') <*> count 6 digit
styled :: JiraParser Inline
styled = (simpleStyled <|> forceStyled) <?> "styled text"
where
simpleStyled = try $ do
styleChar <- lookAhead $ oneOf "-_+*~^"
content <- styleChar `delimitingMany` inline
let style = delimiterStyle styleChar
return $ Styled style content
forceStyled = try $ do
styleChar <- char '{' *> oneOf "-_+*~^" <* char '}'
let closing = try $ string ['{', styleChar, '}']
let style = delimiterStyle styleChar
content <- manyTill inline closing
return $ Styled style content
delimiterStyle :: Char -> InlineStyle
delimiterStyle = \case
'*' -> Strong
'+' -> Insert
'-' -> Strikeout
'^' -> Superscript
'_' -> Emphasis
'~' -> Subscript
c -> error ("Unknown delimiter character: " ++ [c])
monospaced :: JiraParser Inline
monospaced = Monospaced
<$> enclosed (try $ string "{{") (try $ string "}}") inline
<?> "monospaced"
delimitingMany :: Char -> JiraParser a -> JiraParser [a]
delimitingMany c = enclosed (char c) (char c)
enclosed :: JiraParser opening -> JiraParser closing
-> JiraParser a
-> JiraParser [a]
enclosed opening closing parser = try $ do
guard =<< notAfterString
opening *> notFollowedBy space *> manyTill parser closing'
where
closing' = try $ do
guard . not =<< afterSpace
closing <* lookAhead wordBoundary
wordBoundary = void (satisfy (not . isAlphaNum)) <|> eof