module Matterhorn.Draw.ChannelListWindow
  ( drawChannelListWindow
  )
where

import           Prelude ()
import           Matterhorn.Prelude

import           Brick
import qualified Data.Text as T
import           Text.Wrap ( defaultWrapSettings, preserveIndentation )

import           Network.Mattermost.Types
import           Network.Mattermost.Lenses

import           Matterhorn.Draw.ListWindow ( drawListWindow, WindowPosition(..) )
import           Matterhorn.Types
import           Matterhorn.Types.Common ( sanitizeUserText )
import           Matterhorn.Themes


drawChannelListWindow :: ChatState -> TeamId -> Widget Name
drawChannelListWindow :: ChatState -> TeamId -> Widget Name
drawChannelListWindow ChatState
st TeamId
tId =
    let window :: Widget Name
window = forall a b.
ListWindowState a b
-> (b -> Widget Name)
-> (b -> Widget Name)
-> (b -> Widget Name)
-> (Bool -> a -> Widget Name)
-> Maybe (Widget Name)
-> WindowPosition
-> Int
-> Widget Name
drawListWindow (ChatState
stforall s a. s -> Getting a s a -> a
^.TeamId -> Lens' ChatState TeamState
csTeam(TeamId
tId)forall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' TeamState (ListWindowState Channel ChannelSearchScope)
tsChannelListWindow) ChannelSearchScope -> Widget Name
channelSearchScopeHeader
                                  ChannelSearchScope -> Widget Name
channelSearchScopeNoResults ChannelSearchScope -> Widget Name
channelSearchScopePrompt
                                  Bool -> Channel -> Widget Name
renderChannel
                                  forall a. Maybe a
Nothing
                                  WindowPosition
WindowCenter
                                  Int
80
    in forall n. Widget n -> Widget n
joinBorders Widget Name
window

channelSearchScopePrompt :: ChannelSearchScope -> Widget Name
channelSearchScopePrompt :: ChannelSearchScope -> Widget Name
channelSearchScopePrompt ChannelSearchScope
scope =
    forall n. Text -> Widget n
txt forall a b. (a -> b) -> a -> b
$ case ChannelSearchScope
scope of
        ChannelSearchScope
AllChannels -> Text
"Search channels:"

channelSearchScopeNoResults :: ChannelSearchScope -> Widget Name
channelSearchScopeNoResults :: ChannelSearchScope -> Widget Name
channelSearchScopeNoResults ChannelSearchScope
scope =
    forall n. Text -> Widget n
txt forall a b. (a -> b) -> a -> b
$ case ChannelSearchScope
scope of
        ChannelSearchScope
AllChannels -> Text
"No matching channels found."

channelSearchScopeHeader :: ChannelSearchScope -> Widget Name
channelSearchScopeHeader :: ChannelSearchScope -> Widget Name
channelSearchScopeHeader ChannelSearchScope
scope =
    forall n. AttrName -> Widget n -> Widget n
withDefAttr AttrName
clientEmphAttr forall a b. (a -> b) -> a -> b
$ forall n. Text -> Widget n
txt forall a b. (a -> b) -> a -> b
$ case ChannelSearchScope
scope of
        ChannelSearchScope
AllChannels -> Text
"Join a Channel"

renderChannel :: Bool -> Channel -> Widget Name
renderChannel :: Bool -> Channel -> Widget Name
renderChannel Bool
_ Channel
chan =
    let baseStr :: Text
baseStr = (UserText -> Text
sanitizeUserText forall a b. (a -> b) -> a -> b
$ Channel
chanforall s a. s -> Getting a s a -> a
^.Lens' Channel UserText
channelDisplayNameL) forall a. Semigroup a => a -> a -> a
<>
                  Text
" (" forall a. Semigroup a => a -> a -> a
<> (UserText -> Text
sanitizeUserText forall a b. (a -> b) -> a -> b
$ Channel
chanforall s a. s -> Getting a s a -> a
^.Lens' Channel UserText
channelNameL) forall a. Semigroup a => a -> a -> a
<> Text
")"
        s :: Text
s = Text
"  " forall a. Semigroup a => a -> a -> a
<> (Text -> Text
T.strip forall a b. (a -> b) -> a -> b
$ UserText -> Text
sanitizeUserText forall a b. (a -> b) -> a -> b
$ Channel
chanforall s a. s -> Getting a s a -> a
^.Lens' Channel UserText
channelPurposeL)
    in (forall n. Int -> Widget n -> Widget n
vLimit Int
1 forall a b. (a -> b) -> a -> b
$ forall n. Padding -> Widget n -> Widget n
padRight Padding
Max forall a b. (a -> b) -> a -> b
$ forall n. AttrName -> Widget n -> Widget n
withDefAttr AttrName
clientEmphAttr forall a b. (a -> b) -> a -> b
$ forall n. Text -> Widget n
txt Text
baseStr) forall n. Widget n -> Widget n -> Widget n
<=>
       (forall n. Int -> Widget n -> Widget n
vLimit Int
1 forall a b. (a -> b) -> a -> b
$ forall n. WrapSettings -> Text -> Widget n
txtWrapWith (WrapSettings
defaultWrapSettings { preserveIndentation :: Bool
preserveIndentation = Bool
True }) Text
s)