{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE TypeApplications #-}

{- |
 Module      :  XMonad.Hooks.StatusBar.WorkspaceScreen
 Description :  Combine workspace names with screen information
 Copyright   :  (c) Yecine Megdiche <yecine.megdiche@gmail.com>
 License     :  BSD3-style (see LICENSE)

 Maintainer  :  Yecine Megdiche <yecine.megdiche@gmail.com>
 Stability   :  unstable
 Portability :  unportable

 In multi-head setup, it might be useful to have screen information of the
 visible workspaces combined with the workspace name, for example in a status
 bar. This module provides utility functions to do just that.
-}
module XMonad.Hooks.StatusBar.WorkspaceScreen
    (
    -- * Usage
    -- $usage
      combineWithScreen
    , combineWithScreenName
    , combineWithScreenNumber
    , WorkspaceScreenCombiner
    -- * Limitations
    -- $limitations
    ) where

import           Graphics.X11.Xrandr
import           XMonad
import           XMonad.Hooks.StatusBar.PP
import           XMonad.Prelude
import qualified XMonad.StackSet               as W

{- $usage
 You can use this module with the following in your @xmonad.hs@:

 > import XMonad
 > import XMonad.Hooks.StatusBar
 > import XMonad.Hooks.StatusBar.PP
 > import XMonad.Hooks.StatusBar.WorkspaceScreen

 For example, to add the screen number in parentheses to each visible
 workspace number, you can use 'combineWithScreenNumber':

 > myWorkspaceScreenCombiner :: WorkspaceId -> String -> String
 > myWorkspaceScreenCombiner w sc = w <> wrap "(" ")" sc
 >
 > mySB = statusBarProp "xmobar" (combineWithScreenNumber myWorkspaceScreenCombiner xmobarPP)
 > main = xmonad $ withEasySB mySB defToggleStrutsKey def

 This will annotate the workspace names as following:

 > [1(0)] 2 3 4 <5(1)> 6 7 8 9

 To use the screen's name instead, checkout 'combineWithScreenName':

 > [1(eDP-1)] 2 3 4 <5(HDMI-1)> 6 7 8 9

 For advanced cases, use 'combineWithScreen'.
-}

{- $limitations
 For simplicity, this module assumes xmonad screen ids match screen/monitor
 numbers as managed by the X server (for example, as given by @xrandr
 --listactivemonitors@). Thus, it may not work well when screens show an
 overlapping range of the framebuffer, e.g. when using a projector. This also
 means that it doesn't work with "XMonad.Layout.LayoutScreens".
 (This isn't difficult to fix, PRs welcome.)
-}

-- | Type synonym for a function that combines a workspace name with a screen.
type WorkspaceScreenCombiner = WorkspaceId -> WindowScreen -> String

-- | A helper function that returns a list of screen names.
screenNames :: X [Maybe String]
screenNames :: X [Maybe WorkspaceId]
screenNames = do
    XConf { Display
display :: XConf -> Display
display :: Display
display, Window
theRoot :: XConf -> Window
theRoot :: Window
theRoot } <- forall r (m :: * -> *). MonadReader r m => m r
ask
    let getName :: XRRMonitorInfo -> IO (Maybe WorkspaceId)
getName XRRMonitorInfo
mi = Display -> Window -> IO (Maybe WorkspaceId)
getAtomName Display
display (XRRMonitorInfo -> Window
xrr_moninf_name XRRMonitorInfo
mi)
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
io
        forall a b. (a -> b) -> a -> b
$   forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (f :: * -> *) a. Applicative f => a -> f a
pure []) (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse XRRMonitorInfo -> IO (Maybe WorkspaceId)
getName)
        forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Display -> Window -> Bool -> IO (Maybe [XRRMonitorInfo])
xrrGetMonitors Display
display Window
theRoot Bool
True

-- | Combine a workspace name with the screen name it's visible on.
combineWithScreenName :: (WorkspaceId -> String -> String) -> PP -> X PP
combineWithScreenName :: (WorkspaceId -> WorkspaceId -> WorkspaceId) -> PP -> X PP
combineWithScreenName WorkspaceId -> WorkspaceId -> WorkspaceId
c = X WorkspaceScreenCombiner -> PP -> X PP
combineWithScreen forall a b. (a -> b) -> a -> b
$ do
    [Maybe WorkspaceId]
screens <- X [Maybe WorkspaceId]
screenNames
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ \WorkspaceId
w WindowScreen
sc -> forall b a. b -> (a -> b) -> Maybe a -> b
maybe WorkspaceId
w (WorkspaceId -> WorkspaceId -> WorkspaceId
c WorkspaceId
w) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => m (m a) -> m a
join ([Maybe WorkspaceId]
screens forall a. [a] -> Int -> Maybe a
!? forall a b. (Integral a, Num b) => a -> b
fi (forall i l a sid sd. Screen i l a sid sd -> sid
W.screen WindowScreen
sc))

-- | Combine a workspace name with the screen number it's visible on.
combineWithScreenNumber :: (WorkspaceId -> String -> String) -> PP -> X PP
combineWithScreenNumber :: (WorkspaceId -> WorkspaceId -> WorkspaceId) -> PP -> X PP
combineWithScreenNumber WorkspaceId -> WorkspaceId -> WorkspaceId
c =
    X WorkspaceScreenCombiner -> PP -> X PP
combineWithScreen forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ \WorkspaceId
w WindowScreen
sc -> WorkspaceId -> WorkspaceId -> WorkspaceId
c WorkspaceId
w (forall a. Show a => a -> WorkspaceId
show @Int forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fi forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a sid sd. Screen i l a sid sd -> sid
W.screen forall a b. (a -> b) -> a -> b
$ WindowScreen
sc)

-- | Combine a workspace name with a screen according to the given
-- 'WorkspaceScreenCombiner'.
combineWithScreen :: X WorkspaceScreenCombiner -> PP -> X PP
combineWithScreen :: X WorkspaceScreenCombiner -> PP -> X PP
combineWithScreen X WorkspaceScreenCombiner
xCombiner PP
pp = do
    WorkspaceScreenCombiner
combiner <- X WorkspaceScreenCombiner
xCombiner
    [WindowScreen]
ss       <- forall a. (WindowSet -> X a) -> X a
withWindowSet (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a s sd. StackSet i l a s sd -> [Screen i l a s sd]
W.screens)
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ PP
pp
        { ppRename :: WorkspaceId -> WindowSpace -> WorkspaceId
ppRename = PP -> WorkspaceId -> WindowSpace -> WorkspaceId
ppRename PP
pp forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< \WorkspaceId
s WindowSpace
w ->
            forall b a. b -> (a -> b) -> Maybe a -> b
maybe WorkspaceId
s (WorkspaceScreenCombiner
combiner WorkspaceId
s) (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((forall a. Eq a => a -> a -> Bool
== forall i l a. Workspace i l a -> i
W.tag WindowSpace
w) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a. Workspace i l a -> i
W.tag forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
W.workspace) [WindowScreen]
ss)
        }