{-# Language BangPatterns #-}
module Client.View
( viewLines
) where
import Client.Image.PackedImage (Image')
import Client.State
import Client.State.Focus
import Client.State.Help (hsImages)
import Client.View.Cert (certViewLines)
import Client.View.ChannelList (channelListLines)
import Client.View.ChannelInfo (channelInfoImages)
import Client.View.Digraphs (digraphLines)
import Client.View.IgnoreList (ignoreListLines)
import Client.View.KeyMap (keyMapLines)
import Client.View.MaskList (maskListImages)
import Client.View.Mentions (mentionsViewLines)
import Client.View.Messages (chatMessageImages)
import Client.View.Palette (paletteViewLines)
import Client.View.RtsStats (rtsStatsLines)
import Client.View.UrlSelection (urlSelectionView)
import Client.View.UserList (userInfoImages, userListImages)
import Client.View.Who (whoLines)
import Client.View.Windows (windowsImages)
import Client.View.WindowSwitch (windowSwitchImages)
import Control.Lens (view)
viewLines :: Focus -> Subfocus -> Int -> ClientState -> [Image']
viewLines :: Focus -> Subfocus -> Int -> ClientState -> [Image']
viewLines Focus
focus Subfocus
subfocus Int
w !ClientState
st =
case Subfocus
subfocus of
Subfocus
_ | Just (String
"url",String
arg) <- ClientState -> Maybe (String, String)
clientActiveCommand ClientState
st ->
Int -> Focus -> String -> ClientState -> [Image']
urlSelectionView Int
w Focus
focus' String
arg ClientState
st
Subfocus
_ | Just (String
"c",String
arg) <- ClientState -> Maybe (String, String)
clientActiveCommand ClientState
st ->
String -> Int -> ClientState -> [Image']
windowSwitchImages String
arg Int
w ClientState
st
FocusInfo Text
network Identifier
channel ->
Text -> Identifier -> ClientState -> [Image']
channelInfoImages Text
network Identifier
channel ClientState
st
FocusUsers Text
network Identifier
channel
| Getting Bool ClientState Bool -> ClientState -> Bool
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Bool ClientState Bool
Lens' ClientState Bool
clientDetailView ClientState
st -> Text -> Identifier -> ClientState -> [Image']
userInfoImages Text
network Identifier
channel ClientState
st
| Bool
otherwise -> Text -> Identifier -> Int -> ClientState -> [Image']
userListImages Text
network Identifier
channel Int
w ClientState
st
FocusMasks Text
network Identifier
channel Char
mode ->
Char -> Text -> Identifier -> Int -> ClientState -> [Image']
maskListImages Char
mode Text
network Identifier
channel Int
w ClientState
st
FocusWindows WindowsFilter
filt -> WindowsFilter -> ClientState -> [Image']
windowsImages WindowsFilter
filt ClientState
st
Subfocus
FocusMentions -> Int -> ClientState -> [Image']
mentionsViewLines Int
w ClientState
st
Subfocus
FocusPalette -> Palette -> [Image']
paletteViewLines Palette
pal
Subfocus
FocusDigraphs -> Int -> ClientState -> [Image']
digraphLines Int
w ClientState
st
Subfocus
FocusKeyMap -> ClientState -> [Image']
keyMapLines ClientState
st
Subfocus
FocusRtsStats -> Maybe Stats -> Palette -> [Image']
rtsStatsLines (Getting (Maybe Stats) ClientState (Maybe Stats)
-> ClientState -> Maybe Stats
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Maybe Stats) ClientState (Maybe Stats)
Lens' ClientState (Maybe Stats)
clientRtsStats ClientState
st) Palette
pal
Subfocus
FocusIgnoreList -> HashSet Identifier -> Palette -> [Image']
ignoreListLines (Getting (HashSet Identifier) ClientState (HashSet Identifier)
-> ClientState -> HashSet Identifier
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (HashSet Identifier) ClientState (HashSet Identifier)
Lens' ClientState (HashSet Identifier)
clientIgnores ClientState
st) Palette
pal
Subfocus
FocusCert -> ClientState -> [Image']
certViewLines ClientState
st
FocusChanList Text
network Maybe Int
min' Maybe Int
max' ->
Text -> Int -> ClientState -> (Maybe Int, Maybe Int) -> [Image']
channelListLines Text
network Int
w ClientState
st (Maybe Int
min', Maybe Int
max')
FocusWho Text
network ->
Text -> Int -> ClientState -> [Image']
whoLines Text
network Int
w ClientState
st
Subfocus
FocusHelp -> Getting [Image'] ClientState [Image'] -> ClientState -> [Image']
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((HelpState -> Const [Image'] HelpState)
-> ClientState -> Const [Image'] ClientState
Lens' ClientState HelpState
clientHelp ((HelpState -> Const [Image'] HelpState)
-> ClientState -> Const [Image'] ClientState)
-> (([Image'] -> Const [Image'] [Image'])
-> HelpState -> Const [Image'] HelpState)
-> Getting [Image'] ClientState [Image']
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Image'] -> Const [Image'] [Image'])
-> HelpState -> Const [Image'] HelpState
Lens' HelpState [Image']
hsImages) ClientState
st
Subfocus
_ -> Focus -> Int -> ClientState -> [Image']
chatMessageImages Focus
focus Int
w ClientState
st
where
pal :: Palette
pal = ClientState -> Palette
clientPalette ClientState
st
focus' :: Focus
focus' = Subfocus -> Focus -> Focus
actualFocus Subfocus
subfocus Focus
focus