{-# Language OverloadedStrings #-}
module Client.View.Cert
( certViewLines
) where
import Client.Image.PackedImage
import Client.Image.Palette
import Client.Image.MircFormatting
import Client.State
import Client.State.Focus
import Client.State.Network
import Control.Lens
import Data.Text (Text)
import qualified Data.Text.Lazy as LText
certViewLines ::
ClientState -> [Image']
certViewLines :: ClientState -> [Image']
certViewLines ClientState
st
| Just Text
network <- ClientState -> Maybe Text
currentNetwork ClientState
st
, Just NetworkState
cs <- 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
, let xs :: [Text]
xs = Getting [Text] NetworkState [Text] -> NetworkState -> [Text]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting [Text] NetworkState [Text]
Lens' NetworkState [Text]
csCertificate NetworkState
cs
, Bool -> Bool
not ([Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
xs)
= (Text -> Image') -> [Text] -> [Image']
forall a b. (a -> b) -> [a] -> [b]
map (Palette -> Text -> Image'
parseIrcText Palette
pal)
([Text] -> [Image']) -> [Text] -> [Image']
forall a b. (a -> b) -> a -> b
$ ClientState -> (Text -> Text) -> [Text] -> [Text]
forall a. ClientState -> (a -> Text) -> [a] -> [a]
clientFilter ClientState
st Text -> Text
LText.fromStrict [Text]
xs
| Bool
otherwise = [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 certificate available"]
where
pal :: Palette
pal = ClientState -> Palette
clientPalette ClientState
st
currentNetwork :: ClientState -> Maybe Text
currentNetwork :: ClientState -> Maybe Text
currentNetwork ClientState
st =
case Getting Focus ClientState Focus -> ClientState -> Focus
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Focus ClientState Focus
Lens' ClientState Focus
clientFocus ClientState
st of
NetworkFocus Text
net -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
net
ChannelFocus Text
net Identifier
_ -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
net
Focus
Unfocused -> Maybe Text
forall a. Maybe a
Nothing