module Matterhorn.Events.ChannelListWindow
  ( onEventChannelListWindow
  , channelListWindowKeybindings
  , channelListWindowKeyHandlers
  )
where

import           Prelude ()
import           Matterhorn.Prelude

import qualified Graphics.Vty as Vty

import           Network.Mattermost.Types ( TeamId )

import           Matterhorn.Events.Keybindings
import           Matterhorn.State.ChannelListWindow
import           Matterhorn.State.ListWindow
import           Matterhorn.Types


onEventChannelListWindow :: TeamId -> Vty.Event -> MH ()
onEventChannelListWindow :: TeamId -> Event -> MH ()
onEventChannelListWindow TeamId
tId =
    MH Bool -> MH ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MH Bool -> MH ()) -> (Event -> MH Bool) -> Event -> MH ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' ChatState (ListWindowState Channel ChannelSearchScope)
-> (KeyConfig -> KeyHandlerMap) -> Event -> MH Bool
forall a b.
Lens' ChatState (ListWindowState a b)
-> (KeyConfig -> KeyHandlerMap) -> Event -> MH Bool
onEventListWindow (TeamId -> Lens' ChatState TeamState
csTeam(TeamId
tId)((TeamState -> f TeamState) -> ChatState -> f ChatState)
-> ((ListWindowState Channel ChannelSearchScope
     -> f (ListWindowState Channel ChannelSearchScope))
    -> TeamState -> f TeamState)
-> (ListWindowState Channel ChannelSearchScope
    -> f (ListWindowState Channel ChannelSearchScope))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(ListWindowState Channel ChannelSearchScope
 -> f (ListWindowState Channel ChannelSearchScope))
-> TeamState -> f TeamState
Lens' TeamState (ListWindowState Channel ChannelSearchScope)
tsChannelListWindow) (TeamId -> KeyConfig -> KeyHandlerMap
channelListWindowKeybindings TeamId
tId)

-- | The keybindings we want to use while viewing a channel list window
channelListWindowKeybindings :: TeamId -> KeyConfig -> KeyHandlerMap
channelListWindowKeybindings :: TeamId -> KeyConfig -> KeyHandlerMap
channelListWindowKeybindings TeamId
tId = [KeyEventHandler] -> KeyConfig -> KeyHandlerMap
mkKeybindings (TeamId -> [KeyEventHandler]
channelListWindowKeyHandlers TeamId
tId)

channelListWindowKeyHandlers :: TeamId -> [KeyEventHandler]
channelListWindowKeyHandlers :: TeamId -> [KeyEventHandler]
channelListWindowKeyHandlers TeamId
tId =
    [ KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
CancelEvent Text
"Close the channel search list" (TeamId
-> Lens' ChatState (ListWindowState Channel ChannelSearchScope)
-> MH ()
forall a b.
TeamId -> Lens' ChatState (ListWindowState a b) -> MH ()
exitListWindow TeamId
tId (TeamId -> Lens' ChatState TeamState
csTeam(TeamId
tId)((TeamState -> f TeamState) -> ChatState -> f ChatState)
-> ((ListWindowState Channel ChannelSearchScope
     -> f (ListWindowState Channel ChannelSearchScope))
    -> TeamState -> f TeamState)
-> (ListWindowState Channel ChannelSearchScope
    -> f (ListWindowState Channel ChannelSearchScope))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(ListWindowState Channel ChannelSearchScope
 -> f (ListWindowState Channel ChannelSearchScope))
-> TeamState -> f TeamState
Lens' TeamState (ListWindowState Channel ChannelSearchScope)
tsChannelListWindow))
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
SearchSelectUpEvent Text
"Select the previous channel" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$ TeamId -> MH ()
channelListSelectUp TeamId
tId
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
SearchSelectDownEvent Text
"Select the next channel" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$ TeamId -> MH ()
channelListSelectDown TeamId
tId
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
PageDownEvent Text
"Page down in the channel list" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$ TeamId -> MH ()
channelListPageDown TeamId
tId
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
PageUpEvent Text
"Page up in the channel list" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$ TeamId -> MH ()
channelListPageUp TeamId
tId
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
ActivateListItemEvent Text
"Join the selected channel" (TeamId
-> Lens' ChatState (ListWindowState Channel ChannelSearchScope)
-> MH ()
forall a b.
TeamId -> Lens' ChatState (ListWindowState a b) -> MH ()
listWindowActivateCurrent TeamId
tId (TeamId -> Lens' ChatState TeamState
csTeam(TeamId
tId)((TeamState -> f TeamState) -> ChatState -> f ChatState)
-> ((ListWindowState Channel ChannelSearchScope
     -> f (ListWindowState Channel ChannelSearchScope))
    -> TeamState -> f TeamState)
-> (ListWindowState Channel ChannelSearchScope
    -> f (ListWindowState Channel ChannelSearchScope))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(ListWindowState Channel ChannelSearchScope
 -> f (ListWindowState Channel ChannelSearchScope))
-> TeamState -> f TeamState
Lens' TeamState (ListWindowState Channel ChannelSearchScope)
tsChannelListWindow))
    ]