{-# LANGUAGE ViewPatterns #-}

-----------------------------------------------------------------------------
-- |
-- Module       : XMonad.Actions.FocusNth
-- Description  : Focus the nth window of the current workspace.
-- Copyright    : (c) Karsten Schoelzel <kuser@gmx.de>
-- License      : BSD
--
-- Maintainer   : Karsten Schoelzel <kuser@gmx.de>
-- Stability    : stable
-- Portability  : unportable
--
-- Focus the nth window of the current workspace.
-----------------------------------------------------------------------------

module XMonad.Actions.FocusNth (
                 -- * Usage
                 -- $usage
                 focusNth,focusNth',
                 swapNth,swapNth') where

import XMonad
import XMonad.Prelude
import XMonad.StackSet

-- $usage
-- Add the import to your @xmonad.hs@:
--
-- > import XMonad.Actions.FocusNth
--
-- Then add appropriate keybindings, for example:
--
-- > -- mod4-[1..9] @@ Switch to window N
-- > ++ [((modm, k), focusNth i)
-- >     | (i, k) <- zip [0 .. 8] [xK_1 ..]]
--
-- For detailed instructions on editing your key bindings, see
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.

-- | Give focus to the nth window of the current workspace.
focusNth :: Int -> X ()
focusNth :: Int -> X ()
focusNth = (WindowSet -> WindowSet) -> X ()
windows forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a i l s sd.
(Stack a -> Stack a) -> StackSet i l a s sd -> StackSet i l a s sd
modify' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> Stack a -> Stack a
focusNth'

focusNth' :: Int -> Stack a -> Stack a
focusNth' :: forall a. Int -> Stack a -> Stack a
focusNth' Int
n Stack a
s | Int
n forall a. Ord a => a -> a -> Bool
>= Int
0, ([a]
ls, a
t:[a]
rs) <- forall a. Int -> [a] -> ([a], [a])
splitAt Int
n (forall a. Stack a -> [a]
integrate Stack a
s) = forall a. a -> [a] -> [a] -> Stack a
Stack a
t (forall a. [a] -> [a]
reverse [a]
ls) [a]
rs
              | Bool
otherwise = Stack a
s

-- | Swap current window with nth. Focus stays in the same position
swapNth :: Int -> X ()
swapNth :: Int -> X ()
swapNth = (WindowSet -> WindowSet) -> X ()
windows forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a i l s sd.
(Stack a -> Stack a) -> StackSet i l a s sd -> StackSet i l a s sd
modify' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> Stack a -> Stack a
swapNth'

swapNth' :: Int -> Stack a -> Stack a
swapNth' :: forall a. Int -> Stack a -> Stack a
swapNth' Int
n s :: Stack a
s@(Stack a
c [a]
l [a]
r)
  | (Int
n forall a. Ord a => a -> a -> Bool
< Int
0) Bool -> Bool -> Bool
|| (Int
n forall a. Ord a => a -> a -> Bool
> forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l forall a. Num a => a -> a -> a
+ forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
r) Bool -> Bool -> Bool
|| (Int
n forall a. Eq a => a -> a -> Bool
== forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l) = Stack a
s
  | Int
n forall a. Ord a => a -> a -> Bool
< forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l = let ([a]
nl, forall a. HasCallStack => [a] -> NonEmpty a
notEmpty -> a
nc :| [a]
nr) = forall a. Int -> [a] -> ([a], [a])
splitAt (forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l forall a. Num a => a -> a -> a
- Int
n forall a. Num a => a -> a -> a
- Int
1) [a]
l in forall a. a -> [a] -> [a] -> Stack a
Stack a
nc ([a]
nl forall a. [a] -> [a] -> [a]
++ a
c forall a. a -> [a] -> [a]
: [a]
nr) [a]
r
  | Bool
otherwise    = let ([a]
nl, forall a. HasCallStack => [a] -> NonEmpty a
notEmpty -> a
nc :| [a]
nr) = forall a. Int -> [a] -> ([a], [a])
splitAt (Int
n forall a. Num a => a -> a -> a
- forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l forall a. Num a => a -> a -> a
- Int
1) [a]
r in forall a. a -> [a] -> [a] -> Stack a
Stack a
nc [a]
l ([a]
nl forall a. [a] -> [a] -> [a]
++ a
c forall a. a -> [a] -> [a]
: [a]
nr)