-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Actions.CycleSelectedLayouts
-- Description :  Cycle through the given subset of layouts.
-- Copyright   :  (c) Roman Cheplyaka
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  Roman Cheplyaka <roma@ro-che.info>
-- Stability   :  unstable
-- Portability :  unportable
--
-- This module allows to cycle through the given subset of layouts.
--
-----------------------------------------------------------------------------

module XMonad.Actions.CycleSelectedLayouts (
    -- * Usage
    -- $usage
    cycleThroughLayouts) where

import XMonad
import XMonad.Prelude (elemIndex, fromMaybe)
import qualified XMonad.StackSet as S

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad
-- > import XMonad.Actions.CycleSelectedLayouts
--
-- >   , ((modm,  xK_t ),   cycleThroughLayouts ["Tall", "Mirror Tall"])

cycleToNext :: (Eq a) => [a] -> a -> Maybe a
cycleToNext :: forall a. Eq a => [a] -> a -> Maybe a
cycleToNext [a]
lst a
a = do
    -- not beautiful but simple and readable
    Int
ind <- a -> [a] -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
elemIndex a
a [a]
lst
    a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ [a]
lst [a] -> Int -> a
forall a. [a] -> Int -> a
!! if Int
ind Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
lst Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 then Int
0 else Int
indInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1

-- | If the current layout is in the list, cycle to the next layout. Otherwise,
--   apply the first layout from list.
cycleThroughLayouts :: [String] -> X ()
cycleThroughLayouts :: [String] -> X ()
cycleThroughLayouts [String]
lst = do
    WindowSet
winset <- (XState -> WindowSet) -> X WindowSet
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> WindowSet
windowset
    let ld :: String
ld = Layout Window -> String
forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> String
description (Layout Window -> String)
-> (WindowSet -> Layout Window) -> WindowSet -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Workspace String (Layout Window) Window -> Layout Window
forall i l a. Workspace i l a -> l
S.layout (Workspace String (Layout Window) Window -> Layout Window)
-> (WindowSet -> Workspace String (Layout Window) Window)
-> WindowSet
-> Layout Window
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Screen String (Layout Window) Window ScreenId ScreenDetail
-> Workspace String (Layout Window) Window
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
S.workspace (Screen String (Layout Window) Window ScreenId ScreenDetail
 -> Workspace String (Layout Window) Window)
-> (WindowSet
    -> Screen String (Layout Window) Window ScreenId ScreenDetail)
-> WindowSet
-> Workspace String (Layout Window) Window
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowSet
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
S.current (WindowSet -> String) -> WindowSet -> String
forall a b. (a -> b) -> a -> b
$ WindowSet
winset
    let newld :: String
newld = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe ([String] -> String
forall a. [a] -> a
head [String]
lst) ([String] -> String -> Maybe String
forall a. Eq a => [a] -> a -> Maybe a
cycleToNext [String]
lst String
ld)
    JumpToLayout -> X ()
forall a. Message a => a -> X ()
sendMessage (JumpToLayout -> X ()) -> JumpToLayout -> X ()
forall a b. (a -> b) -> a -> b
$ String -> JumpToLayout
JumpToLayout String
newld