-----------------------------------------------------------------------------
-- |
-- 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.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 <- forall a. Eq a => a -> [a] -> Maybe Int
elemIndex a
a [a]
lst
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [a]
lst forall a. [a] -> Int -> a
!! if Int
ind forall a. Eq a => a -> a -> Bool
== forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
lst forall a. Num a => a -> a -> a
- Int
1 then Int
0 else Int
indforall 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 []         = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
cycleThroughLayouts lst :: [String]
lst@(String
x: [String]
_) = do
    WindowSet
winset <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> WindowSet
windowset
    let ld :: String
ld = forall (layout :: * -> *) a.
LayoutClass layout a =>
layout a -> String
description forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a. Workspace i l a -> l
S.layout 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
S.workspace forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
S.current forall a b. (a -> b) -> a -> b
$ WindowSet
winset
    let newld :: String
newld = forall a. a -> Maybe a -> a
fromMaybe String
x (forall a. Eq a => [a] -> a -> Maybe a
cycleToNext [String]
lst String
ld)
    forall a. Message a => a -> X ()
sendMessage forall a b. (a -> b) -> a -> b
$ String -> JumpToLayout
JumpToLayout String
newld