diff --git a/src/Simplex/Chat/Markdown.hs b/src/Simplex/Chat/Markdown.hs index d18f28db3..b54cda9a0 100644 --- a/src/Simplex/Chat/Markdown.hs +++ b/src/Simplex/Chat/Markdown.hs @@ -17,7 +17,7 @@ import qualified Data.Attoparsec.Text as A import Data.Char (isDigit) import Data.Either (fromRight) import Data.Functor (($>)) -import Data.List (intercalate, foldl') +import Data.List (foldl', intercalate) import Data.List.NonEmpty (NonEmpty) import qualified Data.List.NonEmpty as L import Data.Maybe (fromMaybe, isNothing) @@ -51,8 +51,16 @@ data Format | SimplexLink {linkType :: SimplexLinkType, simplexUri :: Text, trustedUri :: Bool, smpHosts :: NonEmpty Text} | Email | Phone + | Edited EditAction Format deriving (Eq, Show, Generic) +data EditAction = EAInsert | EADelete | EAChangeFormat + deriving (Eq, Show, Generic) + +instance ToJSON EditAction where + toJSON = J.genericToJSON . enumJSON $ dropPrefix "EA" + toEncoding = J.genericToEncoding . enumJSON $ dropPrefix "EA" + data SimplexLinkType = XLContact | XLInvitation | XLGroup deriving (Eq, Show, Generic) @@ -129,7 +137,7 @@ parseMaybeMarkdownList s | otherwise = Just . reverse $ foldl' acc [] ml where ml = intercalate ["\n"] . map (markdownToList . parseMarkdown) $ T.lines s - acc [] m = [m] + acc [] m = [m] acc ms@(FormattedText f t : ms') ft@(FormattedText f' t') | f == f' = FormattedText f (t <> t') : ms' | otherwise = ft : ms @@ -170,14 +178,14 @@ markdownP = mconcat <$> A.many' fragmentP md :: Char -> Format -> Text -> Markdown md c f s | T.null s || T.head s == ' ' || T.last s == ' ' = - unmarked $ c `T.cons` s `T.snoc` c + unmarked $ c `T.cons` s `T.snoc` c | otherwise = markdown f s secretP :: Parser Markdown secretP = secret <$> A.takeWhile (== '#') <*> A.takeTill (== '#') <*> A.takeWhile (== '#') secret :: Text -> Text -> Text -> Markdown secret b s a | T.null a || T.null s || T.head s == ' ' || T.last s == ' ' = - unmarked $ '#' `T.cons` ss + unmarked $ '#' `T.cons` ss | otherwise = markdown Secret $ T.init ss where ss = b <> s <> a @@ -218,8 +226,8 @@ markdownP = mconcat <$> A.many' fragmentP wordMD s | T.null s = unmarked s | isUri s = case strDecode $ encodeUtf8 s of - Right cReq -> markdown (simplexUriFormat cReq) s - _ -> markdown Uri s + Right cReq -> markdown (simplexUriFormat cReq) s + _ -> markdown Uri s | isEmail s = markdown Email s | otherwise = unmarked s isUri s = T.length s >= 10 && any (`T.isPrefixOf` s) ["http://", "https://", "simplex:/"] diff --git a/src/Simplex/Chat/MarkdownDiff.hs b/src/Simplex/Chat/MarkdownDiff.hs index 851f312f3..1076c2203 100644 --- a/src/Simplex/Chat/MarkdownDiff.hs +++ b/src/Simplex/Chat/MarkdownDiff.hs @@ -7,12 +7,8 @@ module Simplex.Chat.MarkdownDiff ( DiffChar (..), DiffPlainChar (..), - DiffStatus (..), - DiffPlainStatus (..), DiffFormatStatus (..), FormatChar (..), - LeftSide (..), - RightSide (..), diff, plainDiff, ) @@ -20,34 +16,22 @@ where import qualified Data.Diff.Myers as D import qualified Data.Foldable as F -import Data.Function ((&)) +import Data.Map.Strict (Map) import qualified Data.Map.Strict as M import Data.Sequence (Seq (..), (><)) import qualified Data.Sequence as S import qualified Data.Text as T -import Simplex.Chat.Markdown (Format) - -data DiffStatus - = UnchangedChar DiffFormatStatus - | Inserted - | Deleted - deriving (Show, Eq) - -data DiffPlainStatus - = UnchangedP - | InsertedP - | DeletedP - deriving (Show, Eq) +import Simplex.Chat.Markdown (EditAction (..), Format) data DiffFormatStatus = UnchangedFormat | ChangedToFormat (Maybe Format) deriving (Show, Eq) -data DiffChar = DiffChar FormatChar DiffStatus +data DiffChar = DiffChar FormatChar (Maybe EditAction) deriving (Show, Eq) -data DiffPlainChar = DiffPlainChar Char DiffPlainStatus +data DiffPlainChar = DiffPlainChar Char (Maybe EditAction) deriving (Show, Eq) data FormatChar = FormatChar @@ -56,48 +40,44 @@ data FormatChar = FormatChar } deriving (Show, Eq) -newtype LeftSide a = LeftSide a deriving (Show, Eq) +newtype DeleteIndices = DeleteIndices (Seq Int) deriving (Show, Eq) -newtype RightSide a = RightSide a deriving (Show, Eq) +newtype InsertIndices = InsertIndices (Seq Int) deriving (Show, Eq) -newtype DeleteIndicies = DeleteIndicies (Seq Int) deriving (Show, Eq) - -newtype InsertIndicies = InsertIndicies (Seq Int) deriving (Show, Eq) - -plainDiff :: LeftSide T.Text -> RightSide T.Text -> Seq DiffPlainChar -plainDiff (LeftSide left) (RightSide right) = toPlain <$> formattedDiff +plainDiff :: T.Text -> T.Text -> Seq DiffPlainChar +plainDiff left right = toPlain <$> formattedDiff where - formattedDiff = diff (LeftSide $ toFormatted left) (RightSide $ toFormatted right) - + formattedDiff = diff (toFormatted left) (toFormatted right) toPlain :: DiffChar -> DiffPlainChar - toPlain (DiffChar (FormatChar c _) diffStatus) = DiffPlainChar c diffStatusPlain + toPlain (DiffChar (FormatChar c _) editAction) = DiffPlainChar c editActionPlain where - diffStatusPlain = case diffStatus of - UnchangedChar _ -> UnchangedP - Inserted -> InsertedP - Deleted -> DeletedP + editActionPlain = case editAction of + Just EAInsert -> Just EAInsert + Just EADelete -> Just EADelete + Just EAChangeFormat -> Nothing + Nothing -> Nothing toFormatted :: T.Text -> Seq FormatChar toFormatted = fmap (`FormatChar` Nothing) . S.fromList . T.unpack -diff :: LeftSide (Seq FormatChar) -> RightSide (Seq FormatChar) -> Seq DiffChar -diff (LeftSide left) (RightSide right) = addInserts markDeletesAndUnchangedChars +diff :: Seq FormatChar -> Seq FormatChar -> Seq DiffChar +diff left right = addInserts markDeletesAndUnchangedChars where edits = D.diffTexts (toText left) (toText right) - (DeleteIndicies deleteIndicies, InsertIndicies insertIndicies) = indices + (DeleteIndices deleteIndicies, InsertIndices insertIndicies) = indices toText :: Seq FormatChar -> T.Text toText = T.pack . F.toList . fmap char - indices :: (DeleteIndicies, InsertIndicies) - indices = F.foldl' f (DeleteIndicies S.empty, InsertIndicies S.empty) edits + indices :: (DeleteIndices, InsertIndices) + indices = F.foldl' f (DeleteIndices S.empty, InsertIndices S.empty) edits where - f :: (DeleteIndicies, InsertIndicies) -> D.Edit -> (DeleteIndicies, InsertIndicies) - f (x@(DeleteIndicies ds), y@(InsertIndicies is)) e = case e of - D.EditDelete m n -> (x', y) where x' = DeleteIndicies $ ds >< S.fromList [m .. n] - D.EditInsert _ m n -> (x, y') where y' = InsertIndicies $ is >< S.fromList [m .. n] + f :: (DeleteIndices, InsertIndices) -> D.Edit -> (DeleteIndices, InsertIndices) + f (x@(DeleteIndices ds), y@(InsertIndices is)) e = case e of + D.EditDelete m n -> (x', y) where x' = DeleteIndices $ ds >< S.fromList [m .. n] + D.EditInsert _ m n -> (x, y') where y' = InsertIndices $ is >< S.fromList [m .. n] - unchangedChars :: M.Map Int DiffFormatStatus -- indexed in left + unchangedChars :: Map Int DiffFormatStatus -- indexed in left unchangedChars = F.foldl' f mempty unchangedCharPairs where unchangedCharPairs :: Seq (Int, FormatChar, FormatChar) @@ -105,17 +85,15 @@ diff (LeftSide left) (RightSide right) = addInserts markDeletesAndUnchangedChars leftWithoutDeletes :: Seq (Int, FormatChar) leftWithoutDeletes = - left - & S.zip (S.fromList [0 .. S.length left - 1]) - & S.filter (\(i, _) -> i `notElem` deleteIndicies) + S.filter (\(i, _) -> i `notElem` deleteIndicies) $ + S.zip (S.fromList [0 .. S.length left - 1]) left rightWithoutInserts :: Seq (Int, FormatChar) rightWithoutInserts = - right - & S.zip (S.fromList [0 .. S.length right - 1]) - & S.filter (\(i, _) -> i `notElem` insertIndicies) + S.filter (\(i, _) -> i `notElem` insertIndicies) $ + S.zip (S.fromList [0 .. S.length right - 1]) right - f :: M.Map Int DiffFormatStatus -> (Int, FormatChar, FormatChar) -> M.Map Int DiffFormatStatus + f :: Map Int DiffFormatStatus -> (Int, FormatChar, FormatChar) -> Map Int DiffFormatStatus f acc (i, FormatChar _ fL, FormatChar _ fR) = M.insert i x acc where x = if fL == fR then UnchangedFormat else ChangedToFormat fR @@ -127,11 +105,11 @@ diff (LeftSide left) (RightSide right) = addInserts markDeletesAndUnchangedChars markDeletesAndUnchangedChars = S.mapWithIndex f left where f :: Int -> FormatChar -> DiffChar - f i x = - DiffChar x $ - if i `elem` deleteIndicies - then Deleted - else UnchangedChar $ unchangedChars M.! i -- should never error + f i x@(FormatChar c _) + | i `elem` deleteIndicies = DiffChar x (Just EADelete) + | otherwise = case unchangedChars M.! i of -- should never error + UnchangedFormat -> DiffChar x Nothing + ChangedToFormat f' -> DiffChar (FormatChar c f') (Just EAChangeFormat) addInserts :: Seq DiffChar -> Seq DiffChar addInserts base = F.foldr f base edits -- start from end and work backwards, hence foldr where @@ -150,9 +128,9 @@ diff (LeftSide left) (RightSide right) = addInserts markDeletesAndUnchangedChars slidePastDeleteBlock x = case S.lookup x acc of Nothing -> x Just (DiffChar _ diffStatus) -> - if diffStatus == Deleted + if diffStatus == Just EADelete then slidePastDeleteBlock (x + 1) else x rightFormatChars = S.take (n - m + 1) $ S.drop m right - inserts = fmap (`DiffChar` Inserted) rightFormatChars + inserts = fmap (`DiffChar` Just EAInsert) rightFormatChars diff --git a/tests/MarkdownDiffTests.hs b/tests/MarkdownDiffTests.hs index fa88f8289..daa7ef65d 100644 --- a/tests/MarkdownDiffTests.hs +++ b/tests/MarkdownDiffTests.hs @@ -5,7 +5,6 @@ module MarkdownDiffTests where import qualified Data.List.NonEmpty as NE -import qualified Data.Sequence as S import Simplex.Chat.Markdown import Simplex.Chat.MarkdownDiff import System.Console.ANSI.Types @@ -17,449 +16,319 @@ markdownDiffTests = do formattedEditedTextTests :: Spec formattedEditedTextTests = describe "show edits" do - it "empty no change" do - diff - ( LeftSide $ - S.fromList - [] - ) - ( RightSide $ - S.fromList - [] - ) - `shouldBe` S.fromList - [] - - it "no change" do - diff - ( LeftSide $ - S.fromList - [ FormatChar 'H' Nothing - ] - ) - ( RightSide $ - S.fromList - [ FormatChar 'H' Nothing - ] - ) - `shouldBe` S.fromList - [ DiffChar (FormatChar 'H' Nothing) $ UnchangedChar UnchangedFormat - ] - - it "add 1 char to empty" do - diff - ( LeftSide $ - S.fromList - [] - ) - ( RightSide $ - S.fromList - [ FormatChar 'H' Nothing - ] - ) - `shouldBe` S.fromList - [ DiffChar (FormatChar 'H' Nothing) Inserted - ] - - it "del the one and only" do - diff - ( LeftSide $ - S.fromList - [ FormatChar 'H' Nothing - ] - ) - ( RightSide $ - S.fromList - [] - ) - `shouldBe` S.fromList - [ DiffChar (FormatChar 'H' Nothing) Deleted - ] - + it "empty no change" $ + diff [] [] `shouldBe` [] + it "no change" $ + diff [FormatChar 'H' Nothing] [FormatChar 'H' Nothing] + `shouldBe` [DiffChar (FormatChar 'H' Nothing) Nothing] + it "add 1 char to empty" $ + diff [] [FormatChar 'H' Nothing] + `shouldBe` [DiffChar (FormatChar 'H' Nothing) $ Just EAInsert] + it "del the one and only" $ + diff [FormatChar 'H' Nothing] [] + `shouldBe` [DiffChar (FormatChar 'H' Nothing) $ Just EADelete] it "one character change" do diff - ( LeftSide $ - S.fromList - [ FormatChar 'H' Nothing, - FormatChar 'r' Nothing, - FormatChar 'l' Nothing, - FormatChar 'l' Nothing, - FormatChar 'o' Nothing - ] - ) - ( RightSide $ - S.fromList - [ FormatChar 'H' Nothing, - FormatChar 'e' Nothing, - FormatChar 'l' Nothing, - FormatChar 'l' Nothing, - FormatChar 'o' Nothing - ] - ) - `shouldBe` S.fromList - [ DiffChar (FormatChar 'H' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'r' Nothing) Deleted, - DiffChar (FormatChar 'e' Nothing) Inserted, - DiffChar (FormatChar 'l' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'l' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'o' Nothing) $ UnchangedChar UnchangedFormat - ] + [ FormatChar 'H' Nothing, + FormatChar 'r' Nothing, + FormatChar 'l' Nothing, + FormatChar 'l' Nothing, + FormatChar 'o' Nothing + ] + [ FormatChar 'H' Nothing, + FormatChar 'e' Nothing, + FormatChar 'l' Nothing, + FormatChar 'l' Nothing, + FormatChar 'o' Nothing + ] + `shouldBe` [ DiffChar (FormatChar 'H' Nothing) Nothing, + DiffChar (FormatChar 'r' Nothing) $ Just EADelete, + DiffChar (FormatChar 'e' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'l' Nothing) Nothing, + DiffChar (FormatChar 'l' Nothing) Nothing, + DiffChar (FormatChar 'o' Nothing) Nothing + ] it "more1" do diff - ( LeftSide $ - S.fromList - [ FormatChar 'H' Nothing, - FormatChar 'r' Nothing, - FormatChar 'l' Nothing, - FormatChar 'l' Nothing, - FormatChar 'o' Nothing - ] - ) - ( RightSide $ - S.fromList - [ FormatChar 'H' Nothing, - FormatChar 'e' Nothing, - FormatChar 'l' Nothing, - FormatChar 'l' Nothing, - FormatChar 'o' Nothing, - FormatChar 'x' Nothing, - FormatChar 'y' Nothing, - FormatChar 'z' Nothing - ] - ) - `shouldBe` S.fromList - [ DiffChar (FormatChar 'H' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'r' Nothing) Deleted, - DiffChar (FormatChar 'e' Nothing) Inserted, - DiffChar (FormatChar 'l' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'l' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'o' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'x' Nothing) Inserted, - DiffChar (FormatChar 'y' Nothing) Inserted, - DiffChar (FormatChar 'z' Nothing) Inserted - ] + [ FormatChar 'H' Nothing, + FormatChar 'r' Nothing, + FormatChar 'l' Nothing, + FormatChar 'l' Nothing, + FormatChar 'o' Nothing + ] + [ FormatChar 'H' Nothing, + FormatChar 'e' Nothing, + FormatChar 'l' Nothing, + FormatChar 'l' Nothing, + FormatChar 'o' Nothing, + FormatChar 'x' Nothing, + FormatChar 'y' Nothing, + FormatChar 'z' Nothing + ] + `shouldBe` [ DiffChar (FormatChar 'H' Nothing) Nothing, + DiffChar (FormatChar 'r' Nothing) $ Just EADelete, + DiffChar (FormatChar 'e' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'l' Nothing) Nothing, + DiffChar (FormatChar 'l' Nothing) Nothing, + DiffChar (FormatChar 'o' Nothing) Nothing, + DiffChar (FormatChar 'x' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'y' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'z' Nothing) $ Just EAInsert + ] it "more2" do diff - ( LeftSide $ - S.fromList - [ FormatChar 'H' Nothing, - FormatChar 'r' Nothing, - FormatChar 'l' Nothing, - FormatChar 'l' Nothing, - FormatChar 'o' Nothing - ] - ) - ( RightSide $ - S.fromList - [ FormatChar 'H' Nothing, - FormatChar 'e' Nothing, - FormatChar 'x' Nothing, - FormatChar 'y' Nothing, - FormatChar 'z' Nothing, - FormatChar 'o' Nothing - ] - ) - `shouldBe` S.fromList - [ DiffChar (FormatChar 'H' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'r' Nothing) Deleted, - DiffChar (FormatChar 'l' Nothing) Deleted, - DiffChar (FormatChar 'l' Nothing) Deleted, - DiffChar (FormatChar 'e' Nothing) Inserted, - DiffChar (FormatChar 'x' Nothing) Inserted, - DiffChar (FormatChar 'y' Nothing) Inserted, - DiffChar (FormatChar 'z' Nothing) Inserted, - DiffChar (FormatChar 'o' Nothing) $ UnchangedChar UnchangedFormat - ] + [ FormatChar 'H' Nothing, + FormatChar 'r' Nothing, + FormatChar 'l' Nothing, + FormatChar 'l' Nothing, + FormatChar 'o' Nothing + ] + [ FormatChar 'H' Nothing, + FormatChar 'e' Nothing, + FormatChar 'x' Nothing, + FormatChar 'y' Nothing, + FormatChar 'z' Nothing, + FormatChar 'o' Nothing + ] + `shouldBe` [ DiffChar (FormatChar 'H' Nothing) Nothing, + DiffChar (FormatChar 'r' Nothing) $ Just EADelete, + DiffChar (FormatChar 'l' Nothing) $ Just EADelete, + DiffChar (FormatChar 'l' Nothing) $ Just EADelete, + DiffChar (FormatChar 'e' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'x' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'y' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'z' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'o' Nothing) Nothing + ] it "more3" do diff - ( LeftSide $ - S.fromList - [ FormatChar 'H' $ Just Bold, - FormatChar 'H' $ Just Bold, - FormatChar 'r' Nothing, - FormatChar 'l' $ Just Secret, - FormatChar 'l' Nothing, - FormatChar 'o' $ Just $ colored Green - ] - ) - ( RightSide $ - S.fromList - [ FormatChar 'H' $ Just Italic, - FormatChar 'H' $ Just Bold, - FormatChar 'e' $ Just $ colored Cyan, - FormatChar 'x' Nothing, - FormatChar 'y' Nothing, - FormatChar 'z' $ Just Secret, - FormatChar 'o' $ Just $ colored Blue - ] - ) - `shouldBe` S.fromList - [ DiffChar (FormatChar 'H' (Just Bold)) $ UnchangedChar $ ChangedToFormat $ Just Italic, - DiffChar (FormatChar 'H' (Just Bold)) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'r' Nothing) Deleted, - DiffChar (FormatChar 'l' (Just Secret)) Deleted, - DiffChar (FormatChar 'l' Nothing) Deleted, - DiffChar (FormatChar 'e' (Just $ colored Cyan)) Inserted, - DiffChar (FormatChar 'x' Nothing) Inserted, - DiffChar (FormatChar 'y' Nothing) Inserted, - DiffChar (FormatChar 'z' (Just Secret)) Inserted, - DiffChar (FormatChar 'o' (Just $ colored Green)) $ UnchangedChar $ ChangedToFormat $ Just $ colored Blue - ] + [ FormatChar 'H' $ Just Bold, + FormatChar 'H' $ Just Bold, + FormatChar 'r' Nothing, + FormatChar 'l' $ Just Secret, + FormatChar 'l' Nothing, + FormatChar 'o' $ Just $ colored Green + ] + [ FormatChar 'H' $ Just Italic, + FormatChar 'H' $ Just Bold, + FormatChar 'e' $ Just $ colored Cyan, + FormatChar 'x' Nothing, + FormatChar 'y' Nothing, + FormatChar 'z' $ Just Secret, + FormatChar 'o' $ Just $ colored Blue + ] + `shouldBe` [ DiffChar (FormatChar 'H' (Just Italic)) (Just EAChangeFormat), + DiffChar (FormatChar 'H' (Just Bold)) Nothing, + DiffChar (FormatChar 'r' Nothing) $ Just EADelete, + DiffChar (FormatChar 'l' (Just Secret)) $ Just EADelete, + DiffChar (FormatChar 'l' Nothing) $ Just EADelete, + DiffChar (FormatChar 'e' (Just $ colored Cyan)) $ Just EAInsert, + DiffChar (FormatChar 'x' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'y' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'z' (Just Secret)) $ Just EAInsert, + DiffChar (FormatChar 'o' (Just $ colored Blue)) (Just EAChangeFormat) + ] it "more4" do diff - ( LeftSide $ - S.fromList - [ FormatChar 'H' Nothing, - FormatChar 'r' Nothing, - FormatChar 'l' Nothing, - FormatChar '~' Nothing, - FormatChar '!' Nothing, - FormatChar '@' Nothing, - FormatChar 'l' Nothing, - FormatChar 'o' Nothing - ] - ) - ( RightSide $ - S.fromList - [ FormatChar 'H' Nothing, - FormatChar 'e' Nothing, - FormatChar 'r' Nothing, - FormatChar 'x' Nothing, - FormatChar 'y' Nothing, - FormatChar '!' Nothing, - FormatChar '@' Nothing, - FormatChar 'z' Nothing, - FormatChar 'o' Nothing, - FormatChar '1' Nothing, - FormatChar '2' Nothing - ] - ) - `shouldBe` S.fromList - [ DiffChar (FormatChar 'H' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'e' Nothing) Inserted, - DiffChar (FormatChar 'r' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'l' Nothing) Deleted, - DiffChar (FormatChar '~' Nothing) Deleted, - DiffChar (FormatChar 'x' Nothing) Inserted, - DiffChar (FormatChar 'y' Nothing) Inserted, - DiffChar (FormatChar '!' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar '@' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar 'l' Nothing) Deleted, - DiffChar (FormatChar 'z' Nothing) Inserted, - DiffChar (FormatChar 'o' Nothing) $ UnchangedChar UnchangedFormat, - DiffChar (FormatChar '1' Nothing) Inserted, - DiffChar (FormatChar '2' Nothing) Inserted - ] + [ FormatChar 'H' Nothing, + FormatChar 'r' Nothing, + FormatChar 'l' Nothing, + FormatChar '~' Nothing, + FormatChar '!' Nothing, + FormatChar '@' Nothing, + FormatChar 'l' Nothing, + FormatChar 'o' Nothing + ] + [ FormatChar 'H' Nothing, + FormatChar 'e' Nothing, + FormatChar 'r' Nothing, + FormatChar 'x' Nothing, + FormatChar 'y' Nothing, + FormatChar '!' Nothing, + FormatChar '@' Nothing, + FormatChar 'z' Nothing, + FormatChar 'o' Nothing, + FormatChar '1' Nothing, + FormatChar '2' Nothing + ] + `shouldBe` [ DiffChar (FormatChar 'H' Nothing) Nothing, + DiffChar (FormatChar 'e' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'r' Nothing) Nothing, + DiffChar (FormatChar 'l' Nothing) $ Just EADelete, + DiffChar (FormatChar '~' Nothing) $ Just EADelete, + DiffChar (FormatChar 'x' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'y' Nothing) $ Just EAInsert, + DiffChar (FormatChar '!' Nothing) Nothing, + DiffChar (FormatChar '@' Nothing) Nothing, + DiffChar (FormatChar 'l' Nothing) $ Just EADelete, + DiffChar (FormatChar 'z' Nothing) $ Just EAInsert, + DiffChar (FormatChar 'o' Nothing) Nothing, + DiffChar (FormatChar '1' Nothing) $ Just EAInsert, + DiffChar (FormatChar '2' Nothing) $ Just EAInsert + ] it "SimplexLink 1" do diff - ( LeftSide $ - S.fromList - [ FormatChar '>' $ - Just $ - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/2/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host1", "host2", "host3"] - } - ] - ) - ( RightSide $ - S.fromList - [ FormatChar '>' $ - Just - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/3/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host0", "host2", "host3"] - } - ] - ) - `shouldBe` S.fromList - [ DiffChar - ( FormatChar '>' $ - Just - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/2/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host1", "host2", "host3"] - } - ) - $ UnchangedChar - $ ChangedToFormat - $ Just - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/3/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host0", "host2", "host3"] - } - ] + [ FormatChar '>' $ + Just $ + SimplexLink + { linkType = XLContact, + simplexUri = "https://api.twitter.com/2/tweets/:id", + trustedUri = True, + smpHosts = NE.fromList ["host1", "host2", "host3"] + } + ] + [ FormatChar '>' $ + Just + SimplexLink + { linkType = XLContact, + simplexUri = "https://api.twitter.com/3/tweets/:id", + trustedUri = True, + smpHosts = NE.fromList ["host0", "host2", "host3"] + } + ] + `shouldBe` [ DiffChar + ( FormatChar '>' $ + Just + SimplexLink + { linkType = XLContact, + simplexUri = "https://api.twitter.com/3/tweets/:id", + trustedUri = True, + smpHosts = NE.fromList ["host0", "host2", "host3"] + } + ) + (Just EAChangeFormat) + ] it "SimplexLink 2" do diff - ( LeftSide $ - S.fromList - [ FormatChar '>' $ - Just $ - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/2/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host1", "host2", "host3"] - } - ] - ) - ( RightSide $ - S.fromList - [ FormatChar '>' $ - Just - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/3/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host1", "host2", "host3"] - } - ] - ) - `shouldBe` S.fromList - [ DiffChar - ( FormatChar '>' $ - Just - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/2/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host1", "host2", "host3"] - } - ) - $ UnchangedChar - $ ChangedToFormat - $ Just - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/3/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host1", "host2", "host3"] - } - ] + [ FormatChar '>' $ + Just $ + SimplexLink + { linkType = XLContact, + simplexUri = "https://api.twitter.com/2/tweets/:id", + trustedUri = True, + smpHosts = NE.fromList ["host1", "host2", "host3"] + } + ] + [ FormatChar '>' $ + Just + SimplexLink + { linkType = XLContact, + simplexUri = "https://api.twitter.com/3/tweets/:id", + trustedUri = True, + smpHosts = NE.fromList ["host1", "host2", "host3"] + } + ] + `shouldBe` [ DiffChar + ( FormatChar '>' $ + Just + SimplexLink + { linkType = XLContact, + simplexUri = "https://api.twitter.com/3/tweets/:id", + trustedUri = True, + smpHosts = NE.fromList ["host1", "host2", "host3"] + } + ) + (Just EAChangeFormat) + ] it "SimplexLink 3" do diff - ( LeftSide $ - S.fromList - [ FormatChar '>' $ - Just $ - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/2/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host1", "host2", "host3"] - } - ] - ) - ( RightSide $ - S.fromList - [ FormatChar '>' $ - Just - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/2/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host0", "host2", "host3"] - } - ] - ) - `shouldBe` S.fromList - [ DiffChar - ( FormatChar '>' $ - Just - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/2/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host1", "host2", "host3"] - } - ) - $ UnchangedChar - $ ChangedToFormat - $ Just - SimplexLink - { linkType = XLContact, - simplexUri = "https://api.twitter.com/2/tweets/:id", - trustedUri = True, - smpHosts = NE.fromList ["host0", "host2", "host3"] - } - ] + [ FormatChar '>' $ + Just $ + SimplexLink + { linkType = XLContact, + simplexUri = "https://api.twitter.com/2/tweets/:id", + trustedUri = True, + smpHosts = NE.fromList ["host1", "host2", "host3"] + } + ] + [ FormatChar '>' $ + Just + SimplexLink + { linkType = XLContact, + simplexUri = "https://api.twitter.com/2/tweets/:id", + trustedUri = True, + smpHosts = NE.fromList ["host0", "host2", "host3"] + } + ] + `shouldBe` [ DiffChar + ( FormatChar '>' $ + Just + SimplexLink + { linkType = XLContact, + simplexUri = "https://api.twitter.com/2/tweets/:id", + trustedUri = True, + smpHosts = NE.fromList ["host0", "host2", "host3"] + } + ) + (Just EAChangeFormat) + ] it "plainDiff 1" do plainDiff - (LeftSide "https://api.twitter.com/2/tweets/:id") - (RightSide "https://api.twitter.com/3/tweets/:id") - `shouldBe` S.fromList - [ DiffPlainChar 'h' UnchangedP, - DiffPlainChar 't' UnchangedP, - DiffPlainChar 't' UnchangedP, - DiffPlainChar 'p' UnchangedP, - DiffPlainChar 's' UnchangedP, - DiffPlainChar ':' UnchangedP, - DiffPlainChar '/' UnchangedP, - DiffPlainChar '/' UnchangedP, - DiffPlainChar 'a' UnchangedP, - DiffPlainChar 'p' UnchangedP, - DiffPlainChar 'i' UnchangedP, - DiffPlainChar '.' UnchangedP, - DiffPlainChar 't' UnchangedP, - DiffPlainChar 'w' UnchangedP, - DiffPlainChar 'i' UnchangedP, - DiffPlainChar 't' UnchangedP, - DiffPlainChar 't' UnchangedP, - DiffPlainChar 'e' UnchangedP, - DiffPlainChar 'r' UnchangedP, - DiffPlainChar '.' UnchangedP, - DiffPlainChar 'c' UnchangedP, - DiffPlainChar 'o' UnchangedP, - DiffPlainChar 'm' UnchangedP, - DiffPlainChar '/' UnchangedP, - DiffPlainChar '2' DeletedP, - DiffPlainChar '3' InsertedP, - DiffPlainChar '/' UnchangedP, - DiffPlainChar 't' UnchangedP, - DiffPlainChar 'w' UnchangedP, - DiffPlainChar 'e' UnchangedP, - DiffPlainChar 'e' UnchangedP, - DiffPlainChar 't' UnchangedP, - DiffPlainChar 's' UnchangedP, - DiffPlainChar '/' UnchangedP, - DiffPlainChar ':' UnchangedP, - DiffPlainChar 'i' UnchangedP, - DiffPlainChar 'd' UnchangedP - ] + "https://api.twitter.com/2/tweets/:id" + "https://api.twitter.com/3/tweets/:id" + `shouldBe` [ DiffPlainChar 'h' Nothing, + DiffPlainChar 't' Nothing, + DiffPlainChar 't' Nothing, + DiffPlainChar 'p' Nothing, + DiffPlainChar 's' Nothing, + DiffPlainChar ':' Nothing, + DiffPlainChar '/' Nothing, + DiffPlainChar '/' Nothing, + DiffPlainChar 'a' Nothing, + DiffPlainChar 'p' Nothing, + DiffPlainChar 'i' Nothing, + DiffPlainChar '.' Nothing, + DiffPlainChar 't' Nothing, + DiffPlainChar 'w' Nothing, + DiffPlainChar 'i' Nothing, + DiffPlainChar 't' Nothing, + DiffPlainChar 't' Nothing, + DiffPlainChar 'e' Nothing, + DiffPlainChar 'r' Nothing, + DiffPlainChar '.' Nothing, + DiffPlainChar 'c' Nothing, + DiffPlainChar 'o' Nothing, + DiffPlainChar 'm' Nothing, + DiffPlainChar '/' Nothing, + DiffPlainChar '2' $ Just EADelete, + DiffPlainChar '3' $ Just EAInsert, + DiffPlainChar '/' Nothing, + DiffPlainChar 't' Nothing, + DiffPlainChar 'w' Nothing, + DiffPlainChar 'e' Nothing, + DiffPlainChar 'e' Nothing, + DiffPlainChar 't' Nothing, + DiffPlainChar 's' Nothing, + DiffPlainChar '/' Nothing, + DiffPlainChar ':' Nothing, + DiffPlainChar 'i' Nothing, + DiffPlainChar 'd' Nothing + ] it "plainDiff 2" do plainDiff - (LeftSide "Hrl~!@lo") - (RightSide "Herxy!@zo12") - `shouldBe` S.fromList - [ DiffPlainChar 'H' UnchangedP, - DiffPlainChar 'e' InsertedP, - DiffPlainChar 'r' UnchangedP, - DiffPlainChar 'l' DeletedP, - DiffPlainChar '~' DeletedP, - DiffPlainChar 'x' InsertedP, - DiffPlainChar 'y' InsertedP, - DiffPlainChar '!' UnchangedP, - DiffPlainChar '@' UnchangedP, - DiffPlainChar 'l' DeletedP, - DiffPlainChar 'z' InsertedP, - DiffPlainChar 'o' UnchangedP, - DiffPlainChar '1' InsertedP, - DiffPlainChar '2' InsertedP - ] \ No newline at end of file + "Hrl~!@lo" + "Herxy!@zo12" + `shouldBe` [ DiffPlainChar 'H' Nothing, + DiffPlainChar 'e' $ Just EAInsert, + DiffPlainChar 'r' Nothing, + DiffPlainChar 'l' $ Just EADelete, + DiffPlainChar '~' $ Just EADelete, + DiffPlainChar 'x' $ Just EAInsert, + DiffPlainChar 'y' $ Just EAInsert, + DiffPlainChar '!' Nothing, + DiffPlainChar '@' Nothing, + DiffPlainChar 'l' $ Just EADelete, + DiffPlainChar 'z' $ Just EAInsert, + DiffPlainChar 'o' Nothing, + DiffPlainChar '1' $ Just EAInsert, + DiffPlainChar '2' $ Just EAInsert + ] \ No newline at end of file diff --git a/tests/Test.hs b/tests/Test.hs index bf74d27a1..7e4d94bdf 100644 --- a/tests/Test.hs +++ b/tests/Test.hs @@ -5,8 +5,8 @@ import ChatTests import ChatTests.Utils (xdescribe'') import Control.Logger.Simple import Data.Time.Clock.System -import MarkdownTests import MarkdownDiffTests +import MarkdownTests import MobileTests import ProtocolTests import SchemaDump @@ -21,6 +21,7 @@ main = do withGlobalLogging logCfg . hspec $ do describe "Schema dump" schemaDumpTest describe "SimpleX chat markdown" markdownTests + fdescribe "SimpleX chat markdown diff" markdownDiffTests describe "SimpleX chat view" viewTests describe "SimpleX chat protocol" protocolTests describe "WebRTC encryption" webRTCTests