{-# LANGUAGE CPP, TemplateHaskell #-}

{-|
Module      : Client.State.Focus
Description : Types for representing the current window being displayed
Copyright   : (c) Eric Mertens, 2016
License     : ISC
Maintainer  : emertens@gmail.com

The client has a primary message window whose contents are determined
by a 'Focus'. In order to provide different views of channels
the 'Subfocus' breaks down channel focus into different subviews.
-}

module Client.State.Focus
  ( -- * Types
    Focus(..)
  , Subfocus(..)
  , WindowsFilter(..)

  -- * Focus operations
  , focusNetwork

  -- * Focus Prisms
  , _ChannelFocus
  , _NetworkFocus
  , _Unfocused
  ) where

import Control.Lens (makePrisms)
import Data.Text (Text)
import Irc.Identifier (Identifier)

-- | Currently focused window
data Focus
 = Unfocused                      -- ^ No network
 | NetworkFocus !Text             -- ^ Network
 | ChannelFocus !Text !Identifier -- ^ Network Channel/Nick
  deriving (Focus -> Focus -> Bool
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
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

-- | Subfocus view
data Subfocus
  = FocusMessages    -- ^ Show messages
  | FocusInfo        -- ^ Show channel metadata
  | FocusUsers       -- ^ Show channel user list
  | FocusMasks !Char -- ^ Show channel mask list for given mode
  | FocusWindows WindowsFilter -- ^ Show client windows
  | FocusPalette     -- ^ Show current palette
  | FocusMentions    -- ^ Show all mentions
  | FocusDigraphs    -- ^ Show all digraphs
  | FocusKeyMap      -- ^ Show key bindings
  | FocusHelp (Maybe Text) -- ^ Show help window with optional command
  | FocusRtsStats    -- ^ Show GHC RTS statistics
  | FocusIgnoreList  -- ^ Show ignored masks
  | FocusCert        -- ^ Show rendered certificate
  | FocusChanList (Maybe Int) (Maybe Int) -- ^ Show channel list
  | FocusWho -- ^ Show last reply to a WHO query
  deriving (Subfocus -> Subfocus -> Bool
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
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)

-- | Unfocused first, followed by focuses sorted by network.
-- Within the same network the network focus comes first and
-- then the channels are ordered by channel identifier
instance Ord Focus where
  compare :: Focus -> Focus -> Ordering
compare Focus
Unfocused            Focus
Unfocused            = Ordering
EQ
  compare (NetworkFocus Text
x)     (NetworkFocus Text
y    ) = forall a. Ord a => a -> a -> Ordering
compare Text
x Text
y
  compare (ChannelFocus Text
x1 Identifier
x2) (ChannelFocus Text
y1 Identifier
y2) = forall a. Ord a => a -> a -> Ordering
compare Text
x1 Text
y1 forall a. Semigroup a => a -> a -> a
<> 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
_) = forall a. Ord a => a -> a -> Ordering
compare Text
x Text
y forall a. Semigroup a => a -> a -> a
<> Ordering
LT
  compare (ChannelFocus Text
x Identifier
_) (NetworkFocus Text
y  ) = forall a. Ord a => a -> a -> Ordering
compare Text
x Text
y forall a. Semigroup a => a -> a -> a
<> Ordering
GT

-- | Return the network associated with the current focus
focusNetwork :: Focus -> Maybe Text {- ^ network -}
focusNetwork :: Focus -> Maybe Text
focusNetwork Focus
Unfocused = forall a. Maybe a
Nothing
focusNetwork (NetworkFocus Text
network) = forall a. a -> Maybe a
Just Text
network
focusNetwork (ChannelFocus Text
network Identifier
_) = forall a. a -> Maybe a
Just Text
network

-- | Filter argument for 'FocusWindows'
data WindowsFilter
  = AllWindows     -- ^ no filter
  | NetworkWindows -- ^ only network windows
  | ChannelWindows -- ^ only channel windows
  | UserWindows    -- ^ only user windows
  deriving (WindowsFilter -> WindowsFilter -> Bool
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
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)