{-# Language OverloadedStrings #-}
module Client.View.ChannelList ( channelListLines ) where
import Client.Image.LineWrap (lineWrapPrefix)
import Client.Image.Message (IdentifierColorMode(NormalIdentifier), coloredIdentifier)
import Client.Image.PackedImage
import Client.Image.Palette
import Client.State
import Client.State.Network
import Control.Lens
import Data.Text (Text)
import qualified Data.Text as Text
import Graphics.Vty.Attributes (defAttr)
import Irc.Identifier
import qualified Data.HashMap.Strict as HashMap
import Client.State.Focus (Subfocus(FocusChanList))
channelListLines ::
Text ->
Int ->
ClientState ->
(Maybe Int, Maybe Int) ->
[Image']
channelListLines :: Text -> Int -> ClientState -> (Maybe Int, Maybe Int) -> [Image']
channelListLines Text
network Int
width ClientState
st (Maybe Int, Maybe Int)
bounds =
case Getting (First NetworkState) ClientState NetworkState
-> ClientState -> Maybe NetworkState
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Getting (First NetworkState) ClientState NetworkState
forall (f :: * -> *).
Applicative f =>
Text -> LensLike' f ClientState NetworkState
clientConnection Text
network) ClientState
st of
Just NetworkState
cs -> NetworkState
-> Int -> ClientState -> (Maybe Int, Maybe Int) -> [Image']
channelListLines' NetworkState
cs Int
width ClientState
st (Maybe Int, Maybe Int)
bounds
Maybe NetworkState
Nothing -> [Attr -> Text -> Image'
text' (Getting Attr Palette Attr -> Palette -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Palette Attr
Lens' Palette Attr
palError Palette
pal) Text
"No connection"]
where
pal :: Palette
pal = ClientState -> Palette
clientPalette ClientState
st
channelListLines' ::
NetworkState ->
Int -> ClientState -> (Maybe Int, Maybe Int) -> [Image']
channelListLines' :: NetworkState
-> Int -> ClientState -> (Maybe Int, Maybe Int) -> [Image']
channelListLines' NetworkState
cs Int
width ClientState
st (Maybe Int
min', Maybe Int
max')
| ChannelList
chanListChannelList -> Getting Bool ChannelList Bool -> Bool
forall s a. s -> Getting a s a -> a
^.Getting Bool ChannelList Bool
Lens' ChannelList Bool
clsDone = Image'
countImage Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<> Image'
queryPart Image' -> [Image'] -> [Image']
forall a. a -> [a] -> [a]
: [Image']
images
| Bool
otherwise = Image'
countImagePending Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<> Image'
queryPart Image' -> [Image'] -> [Image']
forall a. a -> [a] -> [a]
: [Image']
images
where
chanList :: ChannelList
chanList = NetworkState
csNetworkState
-> Getting ChannelList NetworkState ChannelList -> ChannelList
forall s a. s -> Getting a s a -> a
^.Getting ChannelList NetworkState ChannelList
Lens' NetworkState ChannelList
csChannelList
els :: Maybe Text
els = ChannelList
chanListChannelList
-> Getting (Maybe Text) ChannelList (Maybe Text) -> Maybe Text
forall s a. s -> Getting a s a -> a
^.Getting (Maybe Text) ChannelList (Maybe Text)
Lens' ChannelList (Maybe Text)
clsElist
pal :: Palette
pal = ClientState -> Palette
clientPalette ClientState
st
countImagePending :: Image'
countImagePending = Image'
countImage Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<> Attr -> Text -> Image'
text' (Getting Attr Palette Attr -> Palette -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Palette Attr
Lens' Palette Attr
palLabel Palette
pal) Text
"..."
countImage :: Image'
countImage = Attr -> Text -> Image'
text' (Getting Attr Palette Attr -> Palette -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Palette Attr
Lens' Palette Attr
palLabel Palette
pal) Text
"Channels (visible/total): " Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<>
Attr -> String -> Image'
string Attr
defAttr (Int -> String
forall a. Show a => a -> String
show ([(Identifier, Int, Text)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Identifier, Int, Text)]
entries')) Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<>
Attr -> Char -> Image'
char (Getting Attr Palette Attr -> Palette -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Palette Attr
Lens' Palette Attr
palLabel Palette
pal) Char
'/' Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<>
Attr -> String -> Image'
string Attr
defAttr (Int -> String
forall a. Show a => a -> String
show ([(Identifier, Int, Text)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Identifier, Int, Text)]
entries))
queryPart :: Image'
queryPart = [Image'] -> Image'
forall a. Monoid a => [a] -> a
mconcat ([Image'] -> Image') -> [Image'] -> Image'
forall a b. (a -> b) -> a -> b
$
[Attr -> Text -> Image'
text' (Getting Attr Palette Attr -> Palette -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Palette Attr
Lens' Palette Attr
palLabel Palette
pal) Text
" More-than: " Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<> Attr -> String -> Image'
string Attr
defAttr (Int -> String
forall a. Show a => a -> String
show Int
lo) | FocusChanList Text
_ (Just Int
lo) Maybe Int
_ <- [ClientState
stClientState -> Getting Subfocus ClientState Subfocus -> Subfocus
forall s a. s -> Getting a s a -> a
^.Getting Subfocus ClientState Subfocus
Lens' ClientState Subfocus
clientSubfocus]] [Image'] -> [Image'] -> [Image']
forall a. [a] -> [a] -> [a]
++
[Attr -> Text -> Image'
text' (Getting Attr Palette Attr -> Palette -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Palette Attr
Lens' Palette Attr
palLabel Palette
pal) Text
" Less-than: " Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<> Attr -> String -> Image'
string Attr
defAttr (Int -> String
forall a. Show a => a -> String
show Int
hi) | FocusChanList Text
_ Maybe Int
_ (Just Int
hi) <- [ClientState
stClientState -> Getting Subfocus ClientState Subfocus -> Subfocus
forall s a. s -> Getting a s a -> a
^.Getting Subfocus ClientState Subfocus
Lens' ClientState Subfocus
clientSubfocus]] [Image'] -> [Image'] -> [Image']
forall a. [a] -> [a] -> [a]
++
[Attr -> Text -> Image'
text' (Getting Attr Palette Attr -> Palette -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Palette Attr
Lens' Palette Attr
palLabel Palette
pal) Text
" Elist: " Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<> Attr -> Text -> Image'
text' Attr
defAttr Text
txt | Just Text
txt <- [Maybe Text
els], Bool -> Bool
not (Text -> Bool
Text.null Text
txt)]
entries :: [(Identifier, Int, Text)]
entries = ChannelList
chanListChannelList
-> Getting
[(Identifier, Int, Text)] ChannelList [(Identifier, Int, Text)]
-> [(Identifier, Int, Text)]
forall s a. s -> Getting a s a -> a
^.Getting
[(Identifier, Int, Text)] ChannelList [(Identifier, Int, Text)]
Lens' ChannelList [(Identifier, Int, Text)]
clsItems
entries' :: [(Identifier, Int, Text)]
entries' = ClientState
-> Maybe Int
-> Maybe Int
-> [(Identifier, Int, Text)]
-> [(Identifier, Int, Text)]
clientFilterChannels ClientState
st Maybe Int
min' Maybe Int
max' [(Identifier, Int, Text)]
entries
images :: [Image']
images = ((Identifier, Int, Text) -> [Image'])
-> [(Identifier, Int, Text)] -> [Image']
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Identifier, Int, Text) -> [Image']
listItemImage [(Identifier, Int, Text)]
entries'
listItemImage :: (Identifier, Int, Text) -> [Image']
listItemImage :: (Identifier, Int, Text) -> [Image']
listItemImage (Identifier
chan, Int
users, Text
topic)
| Text -> Bool
Text.null Text
topic = [Image'
baseImage]
| Bool
otherwise = [Image'] -> [Image']
forall a. [a] -> [a]
reverse ([Image'] -> [Image']) -> [Image'] -> [Image']
forall a b. (a -> b) -> a -> b
$ Int -> Image' -> Image' -> [Image']
lineWrapPrefix Int
width (Image'
baseImage Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<> Text -> Image'
label Text
" topic:") (Attr -> Text -> Image'
text' Attr
defAttr Text
topic)
where
chanImage :: Image'
chanImage = Palette
-> IdentifierColorMode
-> HashMap Identifier Highlight
-> Identifier
-> Image'
coloredIdentifier Palette
pal IdentifierColorMode
NormalIdentifier HashMap Identifier Highlight
forall k v. HashMap k v
HashMap.empty Identifier
chan
baseImage :: Image'
baseImage = Image'
chanImage Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<> Text -> Image'
label Text
" users: " Image' -> Image' -> Image'
forall a. Semigroup a => a -> a -> a
<> Attr -> Text -> Image'
text' Attr
defAttr (String -> Text
Text.pack (String -> Text) -> (Int -> String) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show (Int -> Text) -> Int -> Text
forall a b. (a -> b) -> a -> b
$ Int
users)
label :: Text -> Image'
label = Attr -> Text -> Image'
text' (Getting Attr Palette Attr -> Palette -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Palette Attr
Lens' Palette Attr
palLabel Palette
pal)