2022-02-22 14:05:45 +00:00
|
|
|
{-# LANGUAGE DeriveGeneric #-}
|
2021-05-09 10:53:18 +01:00
|
|
|
{-# LANGUAGE LambdaCase #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
|
|
|
module Simplex.Chat.Markdown where
|
|
|
|
|
|
|
|
import Control.Applicative ((<|>))
|
2022-02-22 14:05:45 +00:00
|
|
|
import Data.Aeson (ToJSON)
|
|
|
|
import qualified Data.Aeson as J
|
2021-05-09 10:53:18 +01:00
|
|
|
import Data.Attoparsec.Text (Parser)
|
|
|
|
import qualified Data.Attoparsec.Text as A
|
2022-02-22 14:05:45 +00:00
|
|
|
import Data.Bifunctor (second)
|
2021-05-09 10:53:18 +01:00
|
|
|
import Data.Either (fromRight)
|
|
|
|
import Data.Functor (($>))
|
|
|
|
import Data.Map.Strict (Map)
|
|
|
|
import qualified Data.Map.Strict as M
|
2022-02-23 08:45:49 +00:00
|
|
|
import Data.Maybe (isNothing)
|
2021-05-09 10:53:18 +01:00
|
|
|
import Data.String
|
|
|
|
import Data.Text (Text)
|
|
|
|
import qualified Data.Text as T
|
2022-02-22 14:05:45 +00:00
|
|
|
import GHC.Generics
|
|
|
|
import Simplex.Messaging.Parsers (fstToLower, sumTypeJSON)
|
2021-05-09 10:53:18 +01:00
|
|
|
import System.Console.ANSI.Types
|
|
|
|
|
2022-02-22 14:05:45 +00:00
|
|
|
data Markdown = Markdown (Maybe Format) Text | Markdown :|: Markdown
|
2021-05-09 10:53:18 +01:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
data Format
|
|
|
|
= Bold
|
|
|
|
| Italic
|
|
|
|
| Underline
|
|
|
|
| StrikeThrough
|
|
|
|
| Snippet
|
|
|
|
| Secret
|
2022-02-23 12:30:48 +00:00
|
|
|
| Colored {color :: FormatColor}
|
2022-02-22 18:18:35 +00:00
|
|
|
| Uri
|
2022-02-23 08:45:49 +00:00
|
|
|
| Email
|
|
|
|
| Phone
|
2022-02-22 14:05:45 +00:00
|
|
|
deriving (Eq, Show, Generic)
|
|
|
|
|
|
|
|
colored :: Color -> Format
|
|
|
|
colored = Colored . FormatColor
|
|
|
|
|
|
|
|
markdown :: Format -> Text -> Markdown
|
|
|
|
markdown = Markdown . Just
|
|
|
|
|
|
|
|
instance ToJSON Format where toEncoding = J.genericToEncoding $ sumTypeJSON fstToLower
|
2021-05-09 10:53:18 +01:00
|
|
|
|
2022-02-22 18:18:35 +00:00
|
|
|
instance Semigroup Markdown where
|
|
|
|
m <> (Markdown _ "") = m
|
|
|
|
(Markdown _ "") <> m = m
|
|
|
|
m1@(Markdown f1 s1) <> m2@(Markdown f2 s2)
|
|
|
|
| f1 == f2 = Markdown f1 $ s1 <> s2
|
|
|
|
| otherwise = m1 :|: m2
|
|
|
|
m1@(Markdown f1 s1) <> ms@(Markdown f2 s2 :|: m3)
|
|
|
|
| f1 == f2 = Markdown f1 (s1 <> s2) :|: m3
|
|
|
|
| otherwise = m1 :|: ms
|
|
|
|
ms@(m1 :|: Markdown f2 s2) <> m3@(Markdown f3 s3)
|
|
|
|
| f2 == f3 = m1 :|: Markdown f2 (s2 <> s3)
|
|
|
|
| otherwise = ms :|: m3
|
|
|
|
m1 <> m2 = m1 :|: m2
|
2021-05-09 10:53:18 +01:00
|
|
|
|
|
|
|
instance Monoid Markdown where mempty = unmarked ""
|
|
|
|
|
|
|
|
instance IsString Markdown where fromString = unmarked . T.pack
|
|
|
|
|
2022-02-22 14:05:45 +00:00
|
|
|
newtype FormatColor = FormatColor Color
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
instance ToJSON FormatColor where
|
|
|
|
toJSON (FormatColor c) = case c of
|
|
|
|
Red -> "red"
|
|
|
|
Green -> "green"
|
|
|
|
Blue -> "blue"
|
|
|
|
Yellow -> "yellow"
|
|
|
|
Cyan -> "cyan"
|
|
|
|
Magenta -> "magenta"
|
|
|
|
Black -> "black"
|
|
|
|
White -> "white"
|
|
|
|
|
|
|
|
data FormattedText = FormattedText {format :: Maybe Format, text :: Text}
|
|
|
|
deriving (Eq, Show, Generic)
|
|
|
|
|
|
|
|
instance ToJSON FormattedText where
|
|
|
|
toEncoding = J.genericToEncoding J.defaultOptions {J.omitNothingFields = True}
|
|
|
|
|
|
|
|
type MarkdownList = [FormattedText]
|
|
|
|
|
2021-05-09 10:53:18 +01:00
|
|
|
unmarked :: Text -> Markdown
|
2022-02-22 14:05:45 +00:00
|
|
|
unmarked = Markdown Nothing
|
2021-05-09 10:53:18 +01:00
|
|
|
|
|
|
|
colorMD :: Char
|
|
|
|
colorMD = '!'
|
|
|
|
|
|
|
|
secretMD :: Char
|
|
|
|
secretMD = '#'
|
|
|
|
|
|
|
|
formats :: Map Char Format
|
|
|
|
formats =
|
|
|
|
M.fromList
|
|
|
|
[ ('*', Bold),
|
|
|
|
('_', Italic),
|
|
|
|
('+', Underline),
|
|
|
|
('~', StrikeThrough),
|
|
|
|
('`', Snippet),
|
|
|
|
(secretMD, Secret),
|
2022-02-22 14:05:45 +00:00
|
|
|
(colorMD, colored White)
|
2021-05-09 10:53:18 +01:00
|
|
|
]
|
|
|
|
|
2022-02-22 14:05:45 +00:00
|
|
|
colors :: Map Text FormatColor
|
2021-05-09 10:53:18 +01:00
|
|
|
colors =
|
2022-02-22 14:05:45 +00:00
|
|
|
M.fromList . map (second FormatColor) $
|
2021-05-09 10:53:18 +01:00
|
|
|
[ ("red", Red),
|
|
|
|
("green", Green),
|
|
|
|
("blue", Blue),
|
|
|
|
("yellow", Yellow),
|
|
|
|
("cyan", Cyan),
|
|
|
|
("magenta", Magenta),
|
|
|
|
("r", Red),
|
|
|
|
("g", Green),
|
|
|
|
("b", Blue),
|
|
|
|
("y", Yellow),
|
|
|
|
("c", Cyan),
|
|
|
|
("m", Magenta),
|
|
|
|
("1", Red),
|
|
|
|
("2", Green),
|
|
|
|
("3", Blue),
|
|
|
|
("4", Yellow),
|
|
|
|
("5", Cyan),
|
|
|
|
("6", Magenta)
|
|
|
|
]
|
|
|
|
|
2022-02-23 08:45:49 +00:00
|
|
|
parseMaybeMarkdownList :: Text -> Maybe MarkdownList
|
|
|
|
parseMaybeMarkdownList s =
|
|
|
|
let m = markdownToList $ parseMarkdown s
|
|
|
|
in if all (isNothing . format) m then Nothing else Just m
|
|
|
|
|
2022-02-22 14:05:45 +00:00
|
|
|
parseMarkdownList :: Text -> MarkdownList
|
|
|
|
parseMarkdownList = markdownToList . parseMarkdown
|
|
|
|
|
|
|
|
markdownToList :: Markdown -> MarkdownList
|
|
|
|
markdownToList (Markdown f s) = [FormattedText f s]
|
|
|
|
markdownToList (m1 :|: m2) = markdownToList m1 <> markdownToList m2
|
|
|
|
|
2021-05-09 10:53:18 +01:00
|
|
|
parseMarkdown :: Text -> Markdown
|
|
|
|
parseMarkdown s = fromRight (unmarked s) $ A.parseOnly (markdownP <* A.endOfInput) s
|
|
|
|
|
|
|
|
markdownP :: Parser Markdown
|
2022-02-22 18:18:35 +00:00
|
|
|
markdownP = mconcat <$> A.many' fragmentP
|
2021-05-09 10:53:18 +01:00
|
|
|
where
|
|
|
|
fragmentP :: Parser Markdown
|
|
|
|
fragmentP =
|
2022-02-22 18:18:35 +00:00
|
|
|
A.peekChar >>= \case
|
|
|
|
Just ' ' -> unmarked <$> A.takeWhile (== ' ')
|
|
|
|
Just c -> case M.lookup c formats of
|
|
|
|
Just Secret -> A.char secretMD *> secretP
|
|
|
|
Just (Colored (FormatColor White)) -> A.char colorMD *> coloredP
|
|
|
|
Just f -> A.char c *> formattedP c "" f
|
|
|
|
Nothing -> wordsP
|
|
|
|
Nothing -> fail ""
|
2021-05-09 10:53:18 +01:00
|
|
|
formattedP :: Char -> Text -> Format -> Parser Markdown
|
|
|
|
formattedP c p f = do
|
|
|
|
s <- A.takeTill (== c)
|
2022-02-22 14:05:45 +00:00
|
|
|
(A.char c $> md c p f s) <|> noFormat (c `T.cons` p <> s)
|
|
|
|
md :: Char -> Text -> Format -> Text -> Markdown
|
|
|
|
md c p f s
|
2021-05-09 10:53:18 +01:00
|
|
|
| T.null s || T.head s == ' ' || T.last s == ' ' =
|
|
|
|
unmarked $ c `T.cons` p <> s `T.snoc` c
|
2022-02-22 14:05:45 +00:00
|
|
|
| otherwise = markdown f s
|
2021-05-09 10:53:18 +01:00
|
|
|
secretP :: Parser Markdown
|
|
|
|
secretP = secret <$> A.takeWhile (== secretMD) <*> A.takeTill (== secretMD) <*> A.takeWhile (== secretMD)
|
|
|
|
secret :: Text -> Text -> Text -> Markdown
|
|
|
|
secret b s a
|
|
|
|
| T.null a || T.null s || T.head s == ' ' || T.last s == ' ' =
|
|
|
|
unmarked $ secretMD `T.cons` ss
|
2022-02-22 14:05:45 +00:00
|
|
|
| otherwise = markdown Secret $ T.init ss
|
2021-05-09 10:53:18 +01:00
|
|
|
where
|
|
|
|
ss = b <> s <> a
|
|
|
|
coloredP :: Parser Markdown
|
|
|
|
coloredP = do
|
2022-02-23 12:30:48 +00:00
|
|
|
cStr <- A.takeWhile (\c -> c /= ' ' && c /= colorMD)
|
|
|
|
case M.lookup cStr colors of
|
2021-05-09 10:53:18 +01:00
|
|
|
Just c ->
|
|
|
|
let f = Colored c
|
2022-02-23 12:30:48 +00:00
|
|
|
in (A.char ' ' *> formattedP colorMD (cStr `T.snoc` ' ') f)
|
|
|
|
<|> noFormat (colorMD `T.cons` cStr)
|
|
|
|
_ -> noFormat (colorMD `T.cons` cStr)
|
2022-02-22 18:18:35 +00:00
|
|
|
wordsP :: Parser Markdown
|
2021-05-09 10:53:18 +01:00
|
|
|
wordsP = do
|
2022-02-22 18:18:35 +00:00
|
|
|
word <- wordMD <$> A.takeTill (== ' ')
|
|
|
|
s <- (word <>) <$> (unmarked <$> A.takeWhile (== ' '))
|
2021-05-09 10:53:18 +01:00
|
|
|
A.peekChar >>= \case
|
|
|
|
Nothing -> pure s
|
|
|
|
Just c -> case M.lookup c formats of
|
|
|
|
Just _ -> pure s
|
|
|
|
Nothing -> (s <>) <$> wordsP
|
2022-02-22 18:18:35 +00:00
|
|
|
wordMD :: Text -> Markdown
|
|
|
|
wordMD s
|
|
|
|
| "http://" `T.isPrefixOf` s || "https://" `T.isPrefixOf` s || "simplex:/" `T.isPrefixOf` s = markdown Uri s
|
|
|
|
| otherwise = unmarked s
|
2021-05-09 10:53:18 +01:00
|
|
|
noFormat :: Text -> Parser Markdown
|
|
|
|
noFormat = pure . unmarked
|