module Matterhorn.State.PostListOverlay
( enterFlaggedPostListMode
, enterPinnedPostListMode
, enterSearchResultPostListMode
, postListJumpToCurrent
, postListSelectUp
, postListSelectDown
, postListUnflagSelected
, exitPostListMode
)
where
import GHC.Exts ( IsList(..) )
import Prelude ()
import Matterhorn.Prelude
import qualified Data.Foldable as F
import qualified Data.Text as T
import Lens.Micro.Platform ( (.=) )
import Network.Mattermost.Endpoints
import Network.Mattermost.Types
import Matterhorn.State.Messages ( jumpToPost )
import Matterhorn.State.Common
import Matterhorn.State.MessageSelect
import Matterhorn.State.Messages ( addObtainedMessages
, asyncFetchMessagesSurrounding )
import Matterhorn.Types
import Matterhorn.Types.DirectionalSeq (emptyDirSeq)
enterPostListMode :: PostListContents -> Messages -> MH ()
enterPostListMode contents msgs = do
csPostListOverlay.postListPosts .= msgs
let mlatest = getLatestPostMsg msgs
pId = mlatest >>= messagePostId
cId = mlatest >>= \m -> m^.mChannelId
csPostListOverlay.postListSelected .= pId
setMode $ PostListOverlay contents
case (pId, cId) of
(Just p, Just c) -> asyncFetchMessagesSurrounding c p
_ -> return ()
exitPostListMode :: MH ()
exitPostListMode = do
csPostListOverlay.postListPosts .= emptyDirSeq
csPostListOverlay.postListSelected .= Nothing
setMode Main
createPostList :: PostListContents -> (Session -> IO Posts) -> MH ()
createPostList contentsType fetchOp = do
session <- getSession
doAsyncWith Preempt $ do
posts <- fetchOp session
return $ Just $ do
messages <- installMessagesFromPosts posts
let plist = F.toList $ postsPosts posts
postsSpec p = Posts { postsPosts = fromList [(postId p, p)]
, postsOrder = fromList [postId p]
}
mapM_ (\p -> addObtainedMessages (postChannelId p) 0 False $ postsSpec p) plist
enterPostListMode contentsType messages
enterFlaggedPostListMode :: MH ()
enterFlaggedPostListMode = createPostList PostListFlagged $
mmGetListOfFlaggedPosts UserMe defaultFlaggedPostsQuery
enterPinnedPostListMode :: MH ()
enterPinnedPostListMode = do
cId <- use csCurrentChannelId
createPostList (PostListPinned cId) $ mmGetChannelPinnedPosts cId
enterSearchResultPostListMode :: Text -> MH ()
enterSearchResultPostListMode terms
| T.null (T.strip terms) = postInfoMessage "Search command requires at least one search term."
| otherwise = do
enterPostListMode (PostListSearch terms True) noMessages
tId <- gets myTeamId
createPostList (PostListSearch terms False) $
mmSearchForTeamPosts tId (SearchPosts terms False)
postListSelectUp :: MH ()
postListSelectUp = do
selId <- use (csPostListOverlay.postListSelected)
posts <- use (csPostListOverlay.postListPosts)
let nextMsg = getNextMessage (MessagePostId <$> selId) posts
case nextMsg of
Nothing -> return ()
Just m -> do
let pId = m^.mMessageId >>= messageIdPostId
csPostListOverlay.postListSelected .= pId
case (m^.mChannelId, pId) of
(Just c, Just p) -> asyncFetchMessagesSurrounding c p
o -> mhLog LogError
(T.pack $ "postListSelectUp" <>
" unable to get channel or post ID: " <> show o)
postListSelectDown :: MH ()
postListSelectDown = do
selId <- use (csPostListOverlay.postListSelected)
posts <- use (csPostListOverlay.postListPosts)
let prevMsg = getPrevMessage (MessagePostId <$> selId) posts
case prevMsg of
Nothing -> return ()
Just m -> do
let pId = m^.mMessageId >>= messageIdPostId
csPostListOverlay.postListSelected .= pId
case (m^.mChannelId, pId) of
(Just c, Just p) -> asyncFetchMessagesSurrounding c p
o -> mhLog LogError
(T.pack $ "postListSelectDown" <>
" unable to get channel or post ID: " <> show o)
postListUnflagSelected :: MH ()
postListUnflagSelected = do
msgId <- use (csPostListOverlay.postListSelected)
case msgId of
Nothing -> return ()
Just pId -> flagMessage pId False
postListJumpToCurrent :: MH ()
postListJumpToCurrent = do
msgId <- use (csPostListOverlay.postListSelected)
case msgId of
Nothing -> return ()
Just pId -> jumpToPost pId