mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-20 06:33:47 -07:00
The latter is pretty useless, as there's no way to find out what layouts are available, but it can at least allow you to select between any layouts that you happen to be using already (in one workspace or another). The former is handy any time you'd rather have a short name for a layout (either for selecting, or for viewing in a status bar).
40 lines
1.3 KiB
Haskell
40 lines
1.3 KiB
Haskell
{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-}
|
|
|
|
-----------------------------------------------------------------------------
|
|
-- |
|
|
-- Module : XMonad.Layout.Named
|
|
-- Copyright : (c) David Roundy <droundy@darcs.net>
|
|
-- License : BSD3-style (see LICENSE)
|
|
--
|
|
-- Maintainer : David Roundy <droundy@darcs.net>
|
|
-- Stability : unstable
|
|
-- Portability : unportable
|
|
--
|
|
-----------------------------------------------------------------------------
|
|
|
|
module XMonad.Layout.Named (
|
|
-- * Usage
|
|
-- $usage
|
|
Named(Named)
|
|
) where
|
|
|
|
import XMonad
|
|
|
|
-- $usage
|
|
-- You can use this module with the following in your Config.hs file:
|
|
--
|
|
-- > import XMonad.Layout.Named
|
|
--
|
|
-- and change the name of a given layout by
|
|
--
|
|
-- > layout = Named "real big" Full ||| ...
|
|
|
|
data Named l a = Named String (l a) deriving ( Read, Show )
|
|
|
|
instance (LayoutClass l a) => LayoutClass (Named l) a where
|
|
doLayout (Named n l) r s = do (ws, ml') <- doLayout l r s
|
|
return (ws, Named n `fmap` ml')
|
|
handleMessage (Named n l) mess = do ml' <- handleMessage l mess
|
|
return $ Named n `fmap` ml'
|
|
description (Named n _) = n
|