{-# LANGUAGE CPP, TemplateHaskell #-}
module Client.State.Focus
(
Focus(..)
, Subfocus(..)
, WindowsFilter(..)
, focusNetwork
, _ChannelFocus
, _NetworkFocus
, _Unfocused
) where
import Control.Lens
import Data.Text (Text)
import Irc.Identifier
data Focus
= Unfocused
| NetworkFocus !Text
| ChannelFocus !Text !Identifier
deriving (Focus -> Focus -> Bool
(Focus -> Focus -> Bool) -> (Focus -> Focus -> Bool) -> Eq Focus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Focus -> Focus -> Bool
$c/= :: Focus -> Focus -> Bool
== :: Focus -> Focus -> Bool
$c== :: Focus -> Focus -> Bool
Eq,Int -> Focus -> ShowS
[Focus] -> ShowS
Focus -> String
(Int -> Focus -> ShowS)
-> (Focus -> String) -> ([Focus] -> ShowS) -> Show Focus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Focus] -> ShowS
$cshowList :: [Focus] -> ShowS
show :: Focus -> String
$cshow :: Focus -> String
showsPrec :: Int -> Focus -> ShowS
$cshowsPrec :: Int -> Focus -> ShowS
Show)
makePrisms ''Focus
data Subfocus
= FocusMessages
| FocusInfo
| FocusUsers
| FocusDCC
| FocusMasks !Char
| FocusWindows WindowsFilter
| FocusPalette
| FocusMentions
| FocusDigraphs
| FocusKeyMap
| FocusHelp (Maybe Text)
| FocusRtsStats
| FocusIgnoreList
| FocusCert
deriving (Subfocus -> Subfocus -> Bool
(Subfocus -> Subfocus -> Bool)
-> (Subfocus -> Subfocus -> Bool) -> Eq Subfocus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Subfocus -> Subfocus -> Bool
$c/= :: Subfocus -> Subfocus -> Bool
== :: Subfocus -> Subfocus -> Bool
$c== :: Subfocus -> Subfocus -> Bool
Eq,Int -> Subfocus -> ShowS
[Subfocus] -> ShowS
Subfocus -> String
(Int -> Subfocus -> ShowS)
-> (Subfocus -> String) -> ([Subfocus] -> ShowS) -> Show Subfocus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Subfocus] -> ShowS
$cshowList :: [Subfocus] -> ShowS
show :: Subfocus -> String
$cshow :: Subfocus -> String
showsPrec :: Int -> Subfocus -> ShowS
$cshowsPrec :: Int -> Subfocus -> ShowS
Show)
instance Ord Focus where
compare :: Focus -> Focus -> Ordering
compare Focus
Unfocused Focus
Unfocused = Ordering
EQ
compare (NetworkFocus Text
x) (NetworkFocus Text
y ) = Text -> Text -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Text
x Text
y
compare (ChannelFocus Text
x1 Identifier
x2) (ChannelFocus Text
y1 Identifier
y2) = Text -> Text -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Text
x1 Text
y1 Ordering -> Ordering -> Ordering
forall a. Semigroup a => a -> a -> a
<> Identifier -> Identifier -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Identifier
x2 Identifier
y2
compare Focus
Unfocused Focus
_ = Ordering
LT
compare Focus
_ Focus
Unfocused = Ordering
GT
compare (NetworkFocus Text
x ) (ChannelFocus Text
y Identifier
_) = Text -> Text -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Text
x Text
y Ordering -> Ordering -> Ordering
forall a. Semigroup a => a -> a -> a
<> Ordering
LT
compare (ChannelFocus Text
x Identifier
_) (NetworkFocus Text
y ) = Text -> Text -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Text
x Text
y Ordering -> Ordering -> Ordering
forall a. Semigroup a => a -> a -> a
<> Ordering
GT
focusNetwork :: Focus -> Maybe Text
focusNetwork :: Focus -> Maybe Text
focusNetwork Focus
Unfocused = Maybe Text
forall a. Maybe a
Nothing
focusNetwork (NetworkFocus Text
network) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
network
focusNetwork (ChannelFocus Text
network Identifier
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
network
data WindowsFilter
= AllWindows
| NetworkWindows
| ChannelWindows
| UserWindows
deriving (WindowsFilter -> WindowsFilter -> Bool
(WindowsFilter -> WindowsFilter -> Bool)
-> (WindowsFilter -> WindowsFilter -> Bool) -> Eq WindowsFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowsFilter -> WindowsFilter -> Bool
$c/= :: WindowsFilter -> WindowsFilter -> Bool
== :: WindowsFilter -> WindowsFilter -> Bool
$c== :: WindowsFilter -> WindowsFilter -> Bool
Eq, Int -> WindowsFilter -> ShowS
[WindowsFilter] -> ShowS
WindowsFilter -> String
(Int -> WindowsFilter -> ShowS)
-> (WindowsFilter -> String)
-> ([WindowsFilter] -> ShowS)
-> Show WindowsFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowsFilter] -> ShowS
$cshowList :: [WindowsFilter] -> ShowS
show :: WindowsFilter -> String
$cshow :: WindowsFilter -> String
showsPrec :: Int -> WindowsFilter -> ShowS
$cshowsPrec :: Int -> WindowsFilter -> ShowS
Show)