{-# Language OverloadedStrings #-}
module Client.View.UrlSelection
( urlSelectionView
) where
import Client.Configuration
import Client.Image.Message
import Client.Image.PackedImage
import Client.Image.Palette
import Client.Image.LineWrap
import Client.Message
import Client.State
import Client.State.Focus
import Client.State.Network
import Client.State.Window
import Control.Lens
import Data.HashSet (HashSet)
import qualified Data.HashSet as HashSet
import Data.Text (Text)
import Graphics.Vty.Attributes
import Irc.Identifier
import Irc.UserInfo (userNick)
import Text.Read (readMaybe)
urlSelectionView ::
Int ->
Focus ->
String ->
ClientState ->
[Image']
urlSelectionView w focus arg st
= concat
$ zipWith (draw w me pal padding selected) [1..] (toListOf urled st)
where
urled = clientWindows . ix focus
. winMessages . each
. folding matches
focused = focus == view clientFocus st
selected
| not focused = 0
| all (==' ') arg = 1
| Just i <- readMaybe arg = i
| otherwise = 0
cfg = view clientConfig st
padding = view configNickPadding cfg
pal = view configPalette cfg
me = maybe HashSet.empty HashSet.singleton
$ do net <- focusNetwork focus
preview (clientConnection net . csNick) st
matches :: WindowLine -> [(Maybe Identifier, Text)]
matches wl = [ (views wlSummary summaryActor wl, url) | url <- views wlText urlMatches wl ]
summaryActor :: IrcSummary -> Maybe Identifier
summaryActor s =
case s of
JoinSummary who -> Just who
QuitSummary who -> Just who
PartSummary who -> Just who
NickSummary who _ -> Just who
ChatSummary who -> Just (userNick who)
CtcpSummary who -> Just who
DccSendSummary who -> Just who
AcctSummary who -> Just who
ChngSummary who -> Just who
ReplySummary {} -> Nothing
NoSummary -> Nothing
draw ::
Int ->
HashSet Identifier ->
Palette ->
PaddingMode ->
Int ->
Int ->
(Maybe Identifier, Text) ->
[Image']
draw w me pal padding selected i (who,url)
= reverse
$ lineWrapPrefix w
(string defAttr (shows i ". ") <>
nickPad padding
(foldMap (coloredIdentifier pal NormalIdentifier me) who) <> ": ")
(text' attr (cleanText url))
where
attr | selected == i = withStyle defAttr reverseVideo
| otherwise = defAttr