{-# LANGUAGE ViewPatterns #-}
module XMonad.Actions.FocusNth (
focusNth,focusNth',
swapNth,swapNth') where
import XMonad
import XMonad.Prelude
import XMonad.StackSet
focusNth :: Int -> X ()
focusNth :: Int -> X ()
focusNth = (WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (Int -> WindowSet -> WindowSet) -> Int -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Stack Window -> Stack Window) -> WindowSet -> WindowSet
forall a i l s sd.
(Stack a -> Stack a) -> StackSet i l a s sd -> StackSet i l a s sd
modify' ((Stack Window -> Stack Window) -> WindowSet -> WindowSet)
-> (Int -> Stack Window -> Stack Window)
-> Int
-> WindowSet
-> WindowSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Stack Window -> Stack Window
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0, ([a]
ls, a
t:[a]
rs) <- Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
n (Stack a -> [a]
forall a. Stack a -> [a]
integrate Stack a
s) = a -> [a] -> [a] -> Stack a
forall a. a -> [a] -> [a] -> Stack a
Stack a
t ([a] -> [a]
forall a. [a] -> [a]
reverse [a]
ls) [a]
rs
| Bool
otherwise = Stack a
s
swapNth :: Int -> X ()
swapNth :: Int -> X ()
swapNth = (WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (Int -> WindowSet -> WindowSet) -> Int -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Stack Window -> Stack Window) -> WindowSet -> WindowSet
forall a i l s sd.
(Stack a -> Stack a) -> StackSet i l a s sd -> StackSet i l a s sd
modify' ((Stack Window -> Stack Window) -> WindowSet -> WindowSet)
-> (Int -> Stack Window -> Stack Window)
-> Int
-> WindowSet
-> WindowSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Stack Window -> Stack Window
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) Bool -> Bool -> Bool
|| (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
r) Bool -> Bool -> Bool
|| (Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l) = Stack a
s
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l = let ([a]
nl, [a] -> NonEmpty a
forall a. HasCallStack => [a] -> NonEmpty a
notEmpty -> a
nc :| [a]
nr) = Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt ([a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [a]
l in a -> [a] -> [a] -> Stack a
forall a. a -> [a] -> [a] -> Stack a
Stack a
nc ([a]
nl [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ a
c a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
nr) [a]
r
| Bool
otherwise = let ([a]
nl, [a] -> NonEmpty a
forall a. HasCallStack => [a] -> NonEmpty a
notEmpty -> a
nc :| [a]
nr) = Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [a]
r in a -> [a] -> [a] -> Stack a
forall a. a -> [a] -> [a] -> Stack a
Stack a
nc [a]
l ([a]
nl [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ a
c a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
nr)