remove folder names, deletion, add autocreate
This commit is contained in:
parent
94fb992b4c
commit
dc8895c50c
@ -1044,16 +1044,7 @@ processChatCommand' vr = \case
|
||||
withStore' (\db -> setContactDeleted db user ct)
|
||||
`catchChatError` (toView . CRChatError (Just user))
|
||||
pure $ map aConnId conns
|
||||
CTLocal -> do
|
||||
nf <- withStore $ \db -> getNoteFolder db user chatId
|
||||
filesInfo <- withStore' $ \db -> getNoteFolderFileInfo db user nf
|
||||
withChatLock "deleteChat local" . procCmd $ do
|
||||
mapM_ (deleteFile user) filesInfo
|
||||
-- functions below are called in separate transactions to prevent crashes on android
|
||||
-- (possibly, race condition on integrity check?)
|
||||
withStore' $ \db -> deleteNoteFolderFiles db userId nf
|
||||
withStore' $ \db -> deleteNoteFolder db user nf
|
||||
pure $ CRNoteFolderDeleted user nf
|
||||
CTLocal -> pure $ chatCmdError (Just user) "not supported"
|
||||
CTContactRequest -> pure $ chatCmdError (Just user) "not supported"
|
||||
APIClearChat (ChatRef cType chatId) -> withUser $ \user@User {userId} -> case cType of
|
||||
CTDirect -> do
|
||||
@ -1858,15 +1849,9 @@ processChatCommand' vr = \case
|
||||
quotedItemId <- withStore $ \db -> getGroupChatItemIdByText db user groupId cName quotedMsg
|
||||
let mc = MCText msg
|
||||
processChatCommand . APISendMessage (ChatRef CTGroup groupId) False Nothing $ ComposedMessage Nothing (Just quotedItemId) mc
|
||||
NewNoteFolder displayName -> withUser $ \user@User {userId} -> do
|
||||
checkValidName displayName
|
||||
withStore $ \db -> CRNoteFolderCreated user <$> createNewNoteFolder db userId displayName
|
||||
ClearNoteFolder displayName -> withUser $ \user -> do
|
||||
folderId <- withStore $ \db -> getNoteFolderIdByName db user displayName
|
||||
processChatCommand $ APIClearChat (ChatRef CTLocal folderId)
|
||||
DeleteNoteFolder displayName -> withUser $ \user -> do
|
||||
folderId <- withStore $ \db -> getNoteFolderIdByName db user displayName
|
||||
processChatCommand $ APIDeleteChat (ChatRef CTLocal folderId) True
|
||||
LastChats count_ -> withUser' $ \user -> do
|
||||
let count = fromMaybe 5000 count_
|
||||
(errs, previews) <- partitionEithers <$> withStore' (\db -> getChatPreviews db vr user False (PTLast count) clqNoFilters)
|
||||
@ -6113,7 +6098,7 @@ createLocalChatItem user cd content itemTs_ = do
|
||||
let itemTs = fromMaybe createdAt itemTs_
|
||||
gVar <- asks random
|
||||
ciId <- withStore $ \db -> do
|
||||
when (ciRequiresAttention content) . liftIO $ updateChatTs db user cd createdAt
|
||||
liftIO $ updateChatTs db user cd createdAt
|
||||
createWithRandomId gVar $ \sharedMsgId ->
|
||||
let smi_ = Just (SharedMsgId sharedMsgId)
|
||||
in createNewChatItem_ db user cd Nothing smi_ content (Nothing, Nothing, Nothing, Nothing, Nothing) Nothing False itemTs Nothing createdAt
|
||||
@ -6394,7 +6379,6 @@ chatCommandP =
|
||||
("/remove " <|> "/rm ") *> char_ '#' *> (RemoveMember <$> displayName <* A.space <* char_ '@' <*> displayName),
|
||||
("/leave " <|> "/l ") *> char_ '#' *> (LeaveGroup <$> displayName),
|
||||
("/delete #" <|> "/d #") *> (DeleteGroup <$> displayName),
|
||||
("/delete $" <|> "/d $") *> (DeleteNoteFolder <$> displayName),
|
||||
("/delete " <|> "/d ") *> char_ '@' *> (DeleteContact <$> displayName),
|
||||
"/clear $" *> (ClearNoteFolder <$> displayName),
|
||||
"/clear #" *> (ClearGroup <$> displayName),
|
||||
@ -6421,9 +6405,6 @@ chatCommandP =
|
||||
"/_invite member contact @" *> (APISendMemberContactInvitation <$> A.decimal <*> optional (A.space *> msgContentP)),
|
||||
(">#" <|> "> #") *> (SendGroupMessageQuote <$> displayName <* A.space <*> pure Nothing <*> quotedMsg <*> msgTextP),
|
||||
(">#" <|> "> #") *> (SendGroupMessageQuote <$> displayName <* A.space <* char_ '@' <*> (Just <$> displayName) <* A.space <*> quotedMsg <*> msgTextP),
|
||||
-- "/notes" $> ListNoteFolders, -- TODO
|
||||
-- "/_new local chat " *> (APINewLocalChat <$> A.decimal <*> jsonP),
|
||||
"/note folder " *> (NewNoteFolder <$> (char_ '$' *> displayName)),
|
||||
"/_contacts " *> (APIListContacts <$> A.decimal),
|
||||
"/contacts" $> ListContacts,
|
||||
"/_connect plan " *> (APIConnectPlan <$> A.decimal <* A.space <*> strP),
|
||||
|
@ -408,9 +408,7 @@ data ChatCommand
|
||||
| DeleteGroupLink GroupName
|
||||
| ShowGroupLink GroupName
|
||||
| SendGroupMessageQuote {groupName :: GroupName, contactName_ :: Maybe ContactName, quotedMsg :: Text, message :: Text}
|
||||
| NewNoteFolder NoteFolderName
|
||||
| ClearNoteFolder NoteFolderName
|
||||
| DeleteNoteFolder NoteFolderName
|
||||
| LastChats (Maybe Int) -- UserId (not used in UI)
|
||||
| LastMessages (Maybe ChatName) Int (Maybe String) -- UserId (not used in UI)
|
||||
| LastChatItemId (Maybe ChatName) Int -- UserId (not used in UI)
|
||||
@ -559,8 +557,6 @@ data ChatResponse
|
||||
| CRUserDeletedMember {user :: User, groupInfo :: GroupInfo, member :: GroupMember}
|
||||
| CRGroupsList {user :: User, groups :: [(GroupInfo, GroupSummary)]}
|
||||
| CRSentGroupInvitation {user :: User, groupInfo :: GroupInfo, contact :: Contact, member :: GroupMember}
|
||||
| CRNoteFolderCreated {user :: User, noteFolder :: NoteFolder}
|
||||
| CRNoteFolderDeleted {user :: User, noteFolder :: NoteFolder}
|
||||
| CRFileTransferStatus User (FileTransfer, [Integer]) -- TODO refactor this type to FileTransferStatus
|
||||
| CRFileTransferStatusXFTP User AChatItem
|
||||
| CRLocalFileStatus User LocalFileMeta
|
||||
|
@ -11,32 +11,31 @@ m20231219_note_folders =
|
||||
CREATE TABLE note_folders (
|
||||
note_folder_id INTEGER PRIMARY KEY AUTOINCREMENT,
|
||||
user_id INTEGER NOT NULL REFERENCES users ON DELETE CASCADE,
|
||||
display_name TEXT NOT NULL,
|
||||
local_display_name TEXT NOT NULL,
|
||||
created_at TEXT NOT NULL,
|
||||
updated_at TEXT NOT NULL,
|
||||
chat_ts TEXT NOT NULL,
|
||||
favorite INTEGER NOT NULL DEFAULT 0,
|
||||
unread_chat INTEGER DEFAULT 0 NOT NULL,
|
||||
FOREIGN KEY (user_id, local_display_name)
|
||||
REFERENCES display_names (user_id, local_display_name)
|
||||
ON DELETE CASCADE
|
||||
ON UPDATE CASCADE
|
||||
);
|
||||
|
||||
CREATE UNIQUE INDEX idx_note_folders_user_id_local_display_name ON note_folders (
|
||||
user_id,
|
||||
local_display_name
|
||||
unread_chat INTEGER DEFAULT 0 NOT NULL
|
||||
);
|
||||
|
||||
ALTER TABLE chat_items ADD COLUMN note_folder_id INTEGER DEFAULT NULL REFERENCES note_folders ON DELETE CASCADE;
|
||||
ALTER TABLE files ADD COLUMN note_folder_id INTEGER DEFAULT NULL REFERENCES note_folders ON DELETE CASCADE;
|
||||
|
||||
INSERT INTO note_folders
|
||||
SELECT
|
||||
NULL as note_folder_id,
|
||||
u.user_id as user_id,
|
||||
datetime('now') as created_at,
|
||||
datetime('now') as updated_at,
|
||||
datetime('now') as chat_ts,
|
||||
0 as favorite,
|
||||
0 as unread_chat
|
||||
FROM users u;
|
||||
|]
|
||||
|
||||
down_m20231219_note_folders :: Query
|
||||
down_m20231219_note_folders =
|
||||
[sql|
|
||||
DROP INDEX idx_note_folders_user_id_local_display_name;
|
||||
DROP TABLE note_folders;
|
||||
ALTER TABLE chat_items DROP COLUMN note_folder_id;
|
||||
ALTER TABLE files DROP COLUMN note_folder_id;
|
||||
|
@ -331,6 +331,11 @@ updateChatTs db User {userId} chatDirection chatTs = case toChatInfo chatDirecti
|
||||
db
|
||||
"UPDATE groups SET chat_ts = ? WHERE user_id = ? AND group_id = ?"
|
||||
(chatTs, userId, groupId)
|
||||
LocalChat NoteFolder {noteFolderId} ->
|
||||
DB.execute
|
||||
db
|
||||
"UPDATE note_folders SET chat_ts = ? WHERE user_id = ? AND note_folder_id = ?"
|
||||
(chatTs, userId, noteFolderId)
|
||||
_ -> pure ()
|
||||
|
||||
createNewSndChatItem :: DB.Connection -> User -> ChatDirection c 'MDSnd -> SndMessage -> CIContent 'MDSnd -> Maybe (CIQuote c) -> Maybe CITimed -> Bool -> UTCTime -> IO ChatItemId
|
||||
@ -781,17 +786,7 @@ findLocalChatPreview_ db User {userId} pagination clq =
|
||||
<> pagQuery
|
||||
)
|
||||
([":user_id" := userId, ":rcv_new" := CISRcvNew] <> pagParams)
|
||||
CLQSearch {search} ->
|
||||
DB.queryNamed
|
||||
db
|
||||
( baseQuery
|
||||
<> [sql|
|
||||
WHERE nf.user_id = :user_id
|
||||
AND nf.local_display_name LIKE '%' || :search || '%'
|
||||
|]
|
||||
<> pagQuery
|
||||
)
|
||||
([":user_id" := userId, ":rcv_new" := CISRcvNew, ":search" := search] <> pagParams)
|
||||
CLQSearch {} -> pure []
|
||||
|
||||
getLocalChatPreview_ :: DB.Connection -> User -> ChatPreviewData 'CTLocal -> ExceptT StoreError IO AChat
|
||||
getLocalChatPreview_ db user (LocalChatPD _ noteFolderId lastItemId_ stats) = do
|
||||
|
@ -4,53 +4,20 @@
|
||||
|
||||
module Simplex.Chat.Store.NoteFolders where
|
||||
|
||||
import Control.Monad.Except (ExceptT (..), runExceptT)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Data.Text (Text)
|
||||
import Control.Monad.Except (ExceptT (..))
|
||||
import Data.Time (getCurrentTime)
|
||||
import Database.SQLite.Simple (Only (..))
|
||||
import Database.SQLite.Simple.QQ (sql)
|
||||
import Simplex.Chat.Store.Shared (StoreError (..), insertedRowId, withLocalDisplayName)
|
||||
import Simplex.Chat.Store.Shared (StoreError (..))
|
||||
import Simplex.Chat.Types (NoteFolder (..), NoteFolderId, NoteFolderName, User (..))
|
||||
import Simplex.Messaging.Agent.Protocol (UserId)
|
||||
import Simplex.Messaging.Agent.Store.SQLite (firstRow)
|
||||
import qualified Simplex.Messaging.Agent.Store.SQLite.DB as DB
|
||||
|
||||
createNewNoteFolder :: DB.Connection -> UserId -> Text -> ExceptT StoreError IO NoteFolder
|
||||
createNewNoteFolder db userId displayName = do
|
||||
ts <- liftIO getCurrentTime
|
||||
ExceptT $ withLocalDisplayName db userId displayName $ \localDisplayName -> runExceptT $ do
|
||||
liftIO $ do
|
||||
DB.execute
|
||||
db
|
||||
[sql|
|
||||
INSERT INTO note_folders
|
||||
(user_id, display_name, local_display_name, created_at, updated_at, chat_ts, favorite, unread_chat)
|
||||
VALUES
|
||||
(?, ?, ?, ?, ?, ?, ?, ?)
|
||||
|]
|
||||
(userId, displayName, localDisplayName, ts, ts, ts, favorite, unread)
|
||||
noteFolderId <- insertedRowId db
|
||||
pure
|
||||
NoteFolder
|
||||
{ noteFolderId,
|
||||
userId,
|
||||
displayName,
|
||||
localDisplayName,
|
||||
createdAt = ts,
|
||||
updatedAt = ts,
|
||||
chatTs = ts,
|
||||
favorite,
|
||||
unread
|
||||
}
|
||||
where
|
||||
favorite = False
|
||||
unread = False
|
||||
|
||||
getNoteFolderIdByName :: DB.Connection -> User -> NoteFolderName -> ExceptT StoreError IO NoteFolderId
|
||||
getNoteFolderIdByName db User {userId} ldn =
|
||||
ExceptT . firstRow fromOnly (SENoteFolderNotFoundByName ldn) $
|
||||
DB.query db [sql| SELECT note_folder_id FROM note_folders WHERE user_id = ? AND local_display_name = ? |] (userId, ldn)
|
||||
DB.query db [sql| SELECT note_folder_id FROM note_folders WHERE user_id = ? AND "notes" = ? |] (userId, ldn)
|
||||
|
||||
getNoteFolder :: DB.Connection -> User -> NoteFolderId -> ExceptT StoreError IO NoteFolder
|
||||
getNoteFolder db User {userId} noteFolderId =
|
||||
@ -59,15 +26,15 @@ getNoteFolder db User {userId} noteFolderId =
|
||||
db
|
||||
[sql|
|
||||
SELECT
|
||||
display_name, local_display_name, created_at, updated_at, chat_ts, favorite, unread_chat
|
||||
created_at, updated_at, chat_ts, favorite, unread_chat
|
||||
FROM note_folders
|
||||
WHERE user_id = ?
|
||||
AND note_folder_id = ?
|
||||
|]
|
||||
(userId, noteFolderId)
|
||||
where
|
||||
toNoteFolder (displayName, localDisplayName, createdAt, updatedAt, chatTs, favorite, unread) =
|
||||
NoteFolder {noteFolderId, userId, displayName, localDisplayName, createdAt, updatedAt, chatTs, favorite, unread}
|
||||
toNoteFolder (createdAt, updatedAt, chatTs, favorite, unread) =
|
||||
NoteFolder {noteFolderId, userId, createdAt, updatedAt, chatTs, favorite, unread}
|
||||
|
||||
updateNoteFolderUnreadChat :: DB.Connection -> User -> NoteFolder -> Bool -> IO ()
|
||||
updateNoteFolderUnreadChat db User {userId} NoteFolder {noteFolderId} unreadChat = do
|
||||
@ -90,7 +57,3 @@ deleteNoteFolderFiles db userId NoteFolder {noteFolderId} = do
|
||||
deleteNoteFolderCIs :: DB.Connection -> User -> NoteFolder -> IO ()
|
||||
deleteNoteFolderCIs db User {userId} NoteFolder {noteFolderId} =
|
||||
DB.execute db [sql| DELETE FROM chat_items WHERE user_id = ? AND note_folder_id = ? |] (userId, noteFolderId)
|
||||
|
||||
deleteNoteFolder :: DB.Connection -> User -> NoteFolder -> IO ()
|
||||
deleteNoteFolder db User {userId} NoteFolder {noteFolderId} =
|
||||
DB.execute db [sql| DELETE FROM note_folders WHERE user_id = ? AND note_folder_id = ? |] (userId, noteFolderId)
|
||||
|
@ -121,6 +121,11 @@ createUserRecordAt db (AgentUserId auId) Profile {displayName, fullName, image,
|
||||
(profileId, displayName, userId, True, currentTs, currentTs, currentTs)
|
||||
contactId <- insertedRowId db
|
||||
DB.execute db "UPDATE users SET contact_id = ? WHERE user_id = ?" (contactId, userId)
|
||||
DB.execute
|
||||
db
|
||||
"INSERT INTO note_folders (user_id, created_at, updated_at, chat_ts, favorite, unread_chat) VALUES (?, ?, ?, ?, ?, ?)"
|
||||
(userId, currentTs, currentTs, currentTs, False, False)
|
||||
|
||||
pure $ toUser $ (userId, auId, contactId, profileId, activeUser, displayName, fullName, image, Nothing, userPreferences) :. (showNtfs, sendRcptsContacts, sendRcptsSmallGroups, Nothing, Nothing)
|
||||
|
||||
getUsersInfo :: DB.Connection -> IO [UserInfo]
|
||||
|
@ -1539,8 +1539,6 @@ data XGrpMemIntroCont = XGrpMemIntroCont
|
||||
data NoteFolder = NoteFolder
|
||||
{ noteFolderId :: NoteFolderId,
|
||||
userId :: UserId,
|
||||
displayName :: NoteFolderName,
|
||||
localDisplayName :: NoteFolderName,
|
||||
createdAt :: UTCTime,
|
||||
updatedAt :: UTCTime,
|
||||
chatTs :: UTCTime,
|
||||
|
@ -263,8 +263,6 @@ responseToView hu@(currentRH, user_) ChatConfig {logLevel, showReactions, showRe
|
||||
CRMemberSubError u g m e -> ttyUser u [ttyGroup' g <> " member " <> ttyMember m <> " error: " <> sShow e]
|
||||
CRMemberSubSummary u summary -> ttyUser u $ viewErrorsSummary (filter (isJust . memberError) summary) " group member errors"
|
||||
CRGroupSubscribed u g -> ttyUser u $ viewGroupSubscribed g
|
||||
CRNoteFolderCreated u NoteFolder {displayName} -> ttyUser u ["new note folder created, use $" <> plain displayName <> " to create a note"]
|
||||
CRNoteFolderDeleted u NoteFolder {displayName} -> ttyUser u ["note folder " <> plain displayName <> " deleted"]
|
||||
CRPendingSubSummary u _ -> ttyUser u []
|
||||
CRSndFileSubError u SndFileTransfer {fileId, fileName} e ->
|
||||
ttyUser u ["sent file " <> sShow fileId <> " (" <> plain fileName <> ") error: " <> sShow e]
|
||||
@ -396,7 +394,7 @@ responseToView hu@(currentRH, user_) ChatConfig {logLevel, showReactions, showRe
|
||||
toChatView :: AChat -> (Text, Text, Maybe ConnStatus)
|
||||
toChatView (AChat _ (Chat (DirectChat Contact {localDisplayName, activeConn}) items _)) = ("@" <> localDisplayName, toCIPreview items Nothing, connStatus <$> activeConn)
|
||||
toChatView (AChat _ (Chat (GroupChat GroupInfo {membership, localDisplayName}) items _)) = ("#" <> localDisplayName, toCIPreview items (Just membership), Nothing)
|
||||
toChatView (AChat _ (Chat (LocalChat NoteFolder {localDisplayName}) items _)) = ("$" <> localDisplayName, toCIPreview items Nothing, Nothing)
|
||||
toChatView (AChat _ (Chat (LocalChat _) items _)) = ("$notes", toCIPreview items Nothing, Nothing)
|
||||
toChatView (AChat _ (Chat (ContactRequest UserContactRequest {localDisplayName}) items _)) = ("<@" <> localDisplayName, toCIPreview items Nothing, Nothing)
|
||||
toChatView (AChat _ (Chat (ContactConnection PendingContactConnection {pccConnId, pccConnStatus}) items _)) = (":" <> T.pack (show pccConnId), toCIPreview items Nothing, Just pccConnStatus)
|
||||
toCIPreview :: [CChatItem c] -> Maybe GroupMember -> Text
|
||||
@ -555,20 +553,20 @@ viewChatItem chat ci@ChatItem {chatDir, meta = meta@CIMeta {forwardedByMember},
|
||||
from = ttyFromGroup g m
|
||||
where
|
||||
quote = maybe [] (groupQuote g) quotedItem
|
||||
LocalChat nf -> case chatDir of
|
||||
LocalChat _ -> case chatDir of
|
||||
CILocalSnd -> case content of
|
||||
CISndMsgContent mc -> hideLive meta $ withLocalFile to $ sndMsg to quote mc
|
||||
CISndGroupEvent {} -> showSndItemProhibited to
|
||||
_ -> showSndItem to
|
||||
where
|
||||
to = ttyToLocal nf
|
||||
to = "$notes "
|
||||
CILocalRcv -> case content of
|
||||
CIRcvMsgContent mc -> withLocalFile from $ rcvMsg from quote mc
|
||||
CIRcvIntegrityError err -> viewRcvIntegrityError from err ts tz meta
|
||||
CIRcvGroupEvent {} -> showRcvItemProhibited from
|
||||
_ -> showRcvItem from
|
||||
where
|
||||
from = ttyFromLocal nf
|
||||
from = "$??? "
|
||||
where
|
||||
quote = []
|
||||
ContactRequest {} -> []
|
||||
@ -725,11 +723,11 @@ viewItemReaction showReactions chat CIReaction {chatDir, chatItem = CChatItem md
|
||||
where
|
||||
from = ttyFromGroup g m
|
||||
reactionMsg mc = quoteText mc . ttyQuotedMember . Just $ sentByMember' g itemDir
|
||||
(LocalChat l, CILocalRcv) -> case ciMsgContent content of
|
||||
(LocalChat _, CILocalRcv) -> case ciMsgContent content of
|
||||
Just mc -> view from $ reactionMsg mc
|
||||
_ -> []
|
||||
where
|
||||
from = ttyFromLocal l
|
||||
from = "$??? "
|
||||
reactionMsg mc = quoteText mc $ if toMsgDirection md == MDSnd then ">>" else ">"
|
||||
(_, CIDirectSnd) -> [sentText]
|
||||
(_, CIGroupSnd) -> [sentText]
|
||||
@ -2069,12 +2067,6 @@ ttyToGroup g = membershipIncognito g <> ttyTo ("#" <> viewGroupName g <> " ")
|
||||
ttyToGroupEdited :: GroupInfo -> StyledString
|
||||
ttyToGroupEdited g = membershipIncognito g <> ttyTo ("#" <> viewGroupName g <> " [edited] ")
|
||||
|
||||
ttyToLocal :: NoteFolder -> StyledString
|
||||
ttyToLocal NoteFolder {localDisplayName} = ttyFrom ("$" <> localDisplayName <> " ")
|
||||
|
||||
ttyFromLocal :: NoteFolder -> StyledString
|
||||
ttyFromLocal NoteFolder {localDisplayName} = ttyFrom ("$" <> localDisplayName <> "> ")
|
||||
|
||||
viewName :: Text -> Text
|
||||
viewName s = if T.any isSpace s then "'" <> s <> "'" else s
|
||||
|
||||
|
@ -194,20 +194,18 @@ testPaginationAllChatTypes =
|
||||
_ts6 <- iso8601Show <$> getCurrentTime
|
||||
|
||||
-- $notes
|
||||
alice ##> "/note folder self"
|
||||
alice <## "new note folder created, use $self to create a note"
|
||||
alice #> "$self psst"
|
||||
alice #> "$notes psst"
|
||||
|
||||
ts7 <- iso8601Show <$> getCurrentTime
|
||||
|
||||
getChats_ alice "count=10" [("$self", "psst"), ("@dan", "hey"), ("#team", ""), (":3", ""), ("<@cath", ""), ("@bob", "hey")]
|
||||
getChats_ alice "count=3" [("$self", "psst"), ("@dan", "hey"), ("#team", "")]
|
||||
getChats_ alice "count=10" [("$notes", "psst"), ("@dan", "hey"), ("#team", ""), (":3", ""), ("<@cath", ""), ("@bob", "hey")]
|
||||
getChats_ alice "count=3" [("$notes", "psst"), ("@dan", "hey"), ("#team", "")]
|
||||
getChats_ alice ("after=" <> ts2 <> " count=2") [(":3", ""), ("<@cath", "")]
|
||||
getChats_ alice ("before=" <> ts5 <> " count=2") [("#team", ""), (":3", "")]
|
||||
getChats_ alice ("after=" <> ts3 <> " count=10") [("$self", "psst"), ("@dan", "hey"), ("#team", ""), (":3", "")]
|
||||
getChats_ alice ("after=" <> ts3 <> " count=10") [("$notes", "psst"), ("@dan", "hey"), ("#team", ""), (":3", "")]
|
||||
getChats_ alice ("before=" <> ts4 <> " count=10") [(":3", ""), ("<@cath", ""), ("@bob", "hey")]
|
||||
getChats_ alice ("after=" <> ts1 <> " count=10") [("$self", "psst"), ("@dan", "hey"), ("#team", ""), (":3", ""), ("<@cath", ""), ("@bob", "hey")]
|
||||
getChats_ alice ("before=" <> ts7 <> " count=10") [("$self", "psst"), ("@dan", "hey"), ("#team", ""), (":3", ""), ("<@cath", ""), ("@bob", "hey")]
|
||||
getChats_ alice ("after=" <> ts1 <> " count=10") [("$notes", "psst"), ("@dan", "hey"), ("#team", ""), (":3", ""), ("<@cath", ""), ("@bob", "hey")]
|
||||
getChats_ alice ("before=" <> ts7 <> " count=10") [("$notes", "psst"), ("@dan", "hey"), ("#team", ""), (":3", ""), ("<@cath", ""), ("@bob", "hey")]
|
||||
getChats_ alice ("after=" <> ts7 <> " count=10") []
|
||||
getChats_ alice ("before=" <> ts1 <> " count=10") []
|
||||
|
||||
|
@ -17,18 +17,18 @@ chatLocalTests = do
|
||||
|
||||
testNotes :: FilePath -> IO ()
|
||||
testNotes tmp = withNewTestChat tmp "alice" aliceProfile $ \alice -> do
|
||||
createFolder alice "self"
|
||||
-- createFolder alice "self"
|
||||
|
||||
alice ##> "/contacts"
|
||||
-- not a contact
|
||||
|
||||
alice #> "$self keep in mind"
|
||||
alice #> "$notes keep in mind"
|
||||
alice ##> "/tail"
|
||||
alice <# "$self keep in mind"
|
||||
alice <# "$notes keep in mind"
|
||||
alice ##> "/chats"
|
||||
alice <# "$self keep in mind"
|
||||
alice <# "$notes keep in mind"
|
||||
alice ##> "/? keep"
|
||||
alice <# "$self keep in mind"
|
||||
alice <# "$notes keep in mind"
|
||||
|
||||
alice #$> ("/_read chat $1 from=1 to=100", id, "ok")
|
||||
alice ##> "/_unread chat $1 on"
|
||||
@ -39,28 +39,23 @@ testNotes tmp = withNewTestChat tmp "alice" aliceProfile $ \alice -> do
|
||||
alice ##> "/tail"
|
||||
alice ##> "/chats"
|
||||
|
||||
alice #> "$self ahoy!"
|
||||
alice #> "$notes ahoy!"
|
||||
alice ##> "/_update item $1 1 text Greetings."
|
||||
alice ##> "/tail $self"
|
||||
alice <# "$self Greetings."
|
||||
|
||||
alice ##> "/delete $self"
|
||||
alice <## "note folder self deleted"
|
||||
alice ##> "/tail $notes"
|
||||
alice <# "$notes Greetings."
|
||||
|
||||
testUserNotes :: FilePath -> IO ()
|
||||
testUserNotes tmp = withNewTestChat tmp "alice" aliceProfile $ \alice -> do
|
||||
createFolder alice "self"
|
||||
|
||||
alice #> "$self keep in mind"
|
||||
alice #> "$notes keep in mind"
|
||||
alice ##> "/tail"
|
||||
alice <# "$self keep in mind"
|
||||
alice <# "$notes keep in mind"
|
||||
|
||||
alice ##> "/create user secret"
|
||||
alice <## "user profile: secret"
|
||||
alice <## "use /p <display name> to change it"
|
||||
alice <## "(the updated profile will be sent to all your contacts)"
|
||||
|
||||
createFolder alice "gossip"
|
||||
alice ##> "/tail"
|
||||
|
||||
alice ##> "/_delete item $1 1 internal"
|
||||
@ -68,22 +63,17 @@ testUserNotes tmp = withNewTestChat tmp "alice" aliceProfile $ \alice -> do
|
||||
|
||||
testFiles :: FilePath -> IO ()
|
||||
testFiles tmp = withNewTestChat tmp "alice" aliceProfile $ \alice -> do
|
||||
createFolder alice "self"
|
||||
-- createFolder alice "self"
|
||||
|
||||
alice #$> ("/_files_folder ./tests/tmp/app_files", id, "ok")
|
||||
copyFile "./tests/fixtures/test.jpg" "./tests/tmp/app_files/test.jpg"
|
||||
alice ##> "/_create $1 json {\"filePath\": \"test.jpg\", \"msgContent\": {\"text\":\"\",\"type\":\"image\",\"image\":\"data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAgAAAAIAQMAAAD+wSzIAAAABlBMVEX///+/v7+jQ3Y5AAAADklEQVQI12P4AIX8EAgALgAD/aNpbtEAAAAASUVORK5CYII=\"}}"
|
||||
alice <# "$self file 1 (test.jpg)"
|
||||
alice <# "$notes file 1 (test.jpg)"
|
||||
alice ##> "/tail"
|
||||
alice <# "$self file 1 (test.jpg)"
|
||||
alice <# "$notes file 1 (test.jpg)"
|
||||
alice ##> "/fs 1"
|
||||
alice <## "local file 1 (test.jpg)"
|
||||
|
||||
alice ##> "/clear $self"
|
||||
alice ##> "/clear $notes"
|
||||
alice ##> "/fs 1"
|
||||
alice <## "chat db error: SEChatItemNotFoundByFileId {fileId = 1}"
|
||||
|
||||
createFolder :: TestCC -> String -> IO ()
|
||||
createFolder cc label = do
|
||||
cc ##> ("/note folder " <> label)
|
||||
cc <## ("new note folder created, use $" <> label <> " to create a note")
|
||||
|
Loading…
Reference in New Issue
Block a user