{-# Language OverloadedStrings #-}
module Client.View.MaskList
( maskListImages
) where
import Client.Image.PackedImage
import Client.Image.Palette
import Client.State
import Client.State.Channel
import Client.State.Network
import Control.Lens
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.List
import Data.Ord
import Data.Text (Text)
import qualified Data.Text.Lazy as LText
import Data.Time
import Graphics.Vty.Attributes
import Irc.Identifier
maskListImages ::
Char ->
Text ->
Identifier ->
Int ->
ClientState -> [Image']
maskListImages mode network channel w st =
case mbEntries of
Nothing -> [text' (view palError pal) "Mask list not loaded"]
Just entries -> maskListImages' entries w st
where
pal = clientPalette st
mbEntries = preview
( clientConnection network
. csChannels . ix channel
. chanLists . ix mode
) st
maskListImages' :: HashMap Text MaskListEntry -> Int -> ClientState -> [Image']
maskListImages' entries w st = countImage : images
where
pal = clientPalette st
countImage = text' (view palLabel pal) "Masks (visible/total): " <>
string defAttr (show (length entryList)) <>
char (view palLabel pal) '/' <>
string defAttr (show (HashMap.size entries))
matcher = maybe (const True) matcherPred (clientMatcher st) . LText.fromStrict
matcher' (mask,entry) = matcher mask || matcher (view maskListSetter entry)
entryList = sortBy (flip (comparing (view (_2 . maskListTime))))
$ filter matcher'
$ HashMap.toList entries
renderWhen = formatTime defaultTimeLocale " %F %T"
(masks, whoWhens) = unzip entryList
maskImages = text' defAttr <$> masks
maskColumnWidth = maximum (imageWidth <$> maskImages) + 1
paddedMaskImages = resizeImage maskColumnWidth <$> maskImages
width = max 1 w
images = [ cropLine $ mask <>
text' defAttr who <>
string defAttr (renderWhen when)
| (mask, MaskListEntry who when) <- zip paddedMaskImages whoWhens ]
cropLine img
| imageWidth img > width = resizeImage width img
| otherwise = img