mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-10 17:52:09 -07:00
.github
XMonad
Actions
Config
Doc
Hooks
Layout
DecorationEx
Groups
MultiToggle
Accordion.hs
AutoMaster.hs
AvoidFloats.hs
BinaryColumn.hs
BinarySpacePartition.hs
BorderResize.hs
BoringWindows.hs
ButtonDecoration.hs
CenterMainFluid.hs
CenteredIfSingle.hs
CenteredMaster.hs
Circle.hs
CircleEx.hs
Column.hs
Columns.hs
Combo.hs
ComboP.hs
Cross.hs
Decoration.hs
DecorationAddons.hs
DecorationEx.hs
DecorationMadness.hs
Dishes.hs
DragPane.hs
DraggingVisualizer.hs
Drawer.hs
Dwindle.hs
DwmStyle.hs
FixedAspectRatio.hs
FixedColumn.hs
FocusTracking.hs
Fullscreen.hs
Gaps.hs
Grid.hs
GridVariants.hs
Groups.hs
Hidden.hs
HintedGrid.hs
HintedTile.hs
IM.hs
IfMax.hs
ImageButtonDecoration.hs
IndependentScreens.hs
LayoutBuilder.hs
LayoutCombinators.hs
LayoutHints.hs
LayoutModifier.hs
LayoutScreens.hs
LimitWindows.hs
MagicFocus.hs
Magnifier.hs
Master.hs
Maximize.hs
MessageControl.hs
Minimize.hs
Monitor.hs
Mosaic.hs
MosaicAlt.hs
MouseResizableTile.hs
MultiColumns.hs
MultiDishes.hs
MultiToggle.hs
Named.hs
NoBorders.hs
NoFrillsDecoration.hs
OnHost.hs
OneBig.hs
PerScreen.hs
PerWorkspace.hs
PositionStoreFloat.hs
Reflect.hs
Renamed.hs
ResizableThreeColumns.hs
ResizableTile.hs
ResizeScreen.hs
Roledex.hs
ShowWName.hs
SideBorderDecoration.hs
SimpleDecoration.hs
SimpleFloat.hs
Simplest.hs
SimplestFloat.hs
SortedLayout.hs
Spacing.hs
Spiral.hs
Square.hs
StackTile.hs
StateFull.hs
Stoppable.hs
SubLayouts.hs
TabBarDecoration.hs
Tabbed.hs
TallMastersCombo.hs
ThreeColumns.hs
ToggleLayouts.hs
TrackFloating.hs
TwoPane.hs
TwoPanePersistent.hs
VoidBorders.hs
WindowArranger.hs
WindowNavigation.hs
WindowSwitcherDecoration.hs
WorkspaceDir.hs
ZoomRow.hs
Prompt
Util
Doc.hs
Prelude.hs
Prompt.hs
scripts
tests
.gitignore
.hlint.yaml
.mailmap
CHANGES.md
CONTRIBUTING.md
LICENSE
NIX.md
README.md
Setup.lhs
cabal.haskell-ci
cabal.project
flake.nix
stack-master.yaml
stack.yaml
xmonad-contrib.cabal
With XDG support so firmly ingrained now, it's about time we stop hard-coding the configuration path in the docs.
126 lines
4.5 KiB
Haskell
126 lines
4.5 KiB
Haskell
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, FlexibleContexts #-}
|
|
|
|
-----------------------------------------------------------------------------
|
|
-- |
|
|
-- Module : XMonad.Layout.IM
|
|
-- Description : Layout modfier for multi-windowed instant messengers like Psi or Tkabber.
|
|
-- Copyright : (c) Roman Cheplyaka, Ivan N. Veselov <veselov@gmail.com>
|
|
-- License : BSD-style (see LICENSE)
|
|
--
|
|
-- Maintainer : Roman Cheplyaka <roma@ro-che.info>
|
|
-- Stability : unstable
|
|
-- Portability : unportable
|
|
--
|
|
-- Layout modfier suitable for workspace with multi-windowed instant messenger
|
|
-- (like Psi or Tkabber).
|
|
--
|
|
-----------------------------------------------------------------------------
|
|
|
|
module XMonad.Layout.IM (
|
|
-- * Usage
|
|
-- $usage
|
|
|
|
-- * Hints
|
|
-- $hints
|
|
|
|
-- * TODO
|
|
-- $todo
|
|
Property(..), IM(..), withIM, gridIM,
|
|
AddRoster,
|
|
) where
|
|
|
|
import XMonad
|
|
import XMonad.Layout.Grid
|
|
import XMonad.Layout.LayoutModifier
|
|
import XMonad.Prelude
|
|
import XMonad.Util.WindowProperties
|
|
import qualified XMonad.StackSet as S
|
|
|
|
import Control.Arrow (first)
|
|
|
|
-- $usage
|
|
-- You can use this module with the following in your @xmonad.hs@:
|
|
--
|
|
-- > import XMonad.Layout.IM
|
|
-- > import Data.Ratio ((%))
|
|
--
|
|
-- Then edit your @layoutHook@ by adding IM modifier to layout which you prefer
|
|
-- for managing your chat windows (Grid in this example, another useful choice
|
|
-- to consider is Tabbed layout).
|
|
--
|
|
-- > myLayout = withIM (1%7) (ClassName "Tkabber") Grid ||| Full ||| etc..
|
|
-- > main = xmonad def { layoutHook = myLayout }
|
|
--
|
|
-- Here @1%7@ is the part of the screen which your roster will occupy,
|
|
-- @ClassName \"Tkabber\"@ tells xmonad which window is actually your roster.
|
|
--
|
|
-- Screenshot: <http://haskell.org/haskellwiki/Image:Xmonad-layout-im.png>
|
|
--
|
|
-- For more detailed instructions on editing the layoutHook see
|
|
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
|
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
|
|
|
-- $hints
|
|
--
|
|
-- To launch IM layout automatically on your IM workspace use "XMonad.Layout.PerWorkspace".
|
|
--
|
|
-- By default the roster window will appear on the left side.
|
|
-- To place roster window on the right side, use @reflectHoriz@ from
|
|
-- "XMonad.Layout.Reflect" module.
|
|
|
|
-- $todo
|
|
-- This item are questionable. Please let me know if you find them useful.
|
|
--
|
|
-- * shrink\/expand
|
|
--
|
|
|
|
-- | Data type for LayoutModifier which converts given layout to IM-layout
|
|
-- (with dedicated space for the roster and original layout for chat windows)
|
|
data AddRoster a = AddRoster Rational Property deriving (Read, Show)
|
|
|
|
instance LayoutModifier AddRoster Window where
|
|
modifyLayout (AddRoster ratio prop) = applyIM ratio prop
|
|
modifierDescription _ = "IM"
|
|
|
|
-- | Modifier which converts given layout to IM-layout (with dedicated
|
|
-- space for roster and original layout for chat windows)
|
|
withIM :: LayoutClass l a => Rational -> Property -> l a -> ModifiedLayout AddRoster l a
|
|
withIM ratio prop = ModifiedLayout $ AddRoster ratio prop
|
|
|
|
-- | IM layout modifier applied to the Grid layout
|
|
gridIM :: Rational -> Property -> ModifiedLayout AddRoster Grid a
|
|
gridIM ratio prop = withIM ratio prop Grid
|
|
|
|
-- | Internal function for adding space for the roster specified by
|
|
-- the property and running original layout for all chat windows
|
|
applyIM :: (LayoutClass l Window) =>
|
|
Rational
|
|
-> Property
|
|
-> S.Workspace WorkspaceId (l Window) Window
|
|
-> Rectangle
|
|
-> X ([(Window, Rectangle)], Maybe (l Window))
|
|
applyIM ratio prop wksp rect = do
|
|
let stack = S.stack wksp
|
|
let ws = S.integrate' stack
|
|
let (masterRect, slaveRect) = splitHorizontallyBy ratio rect
|
|
master <- findM (hasProperty prop) ws
|
|
case master of
|
|
Just w -> do
|
|
let filteredStack = stack >>= S.filter (w /=)
|
|
wrs <- runLayout (wksp {S.stack = filteredStack}) slaveRect
|
|
return (first ((w, masterRect) :) wrs)
|
|
Nothing -> runLayout wksp rect
|
|
|
|
-- | This is for compatibility with old configs only and will be removed in future versions!
|
|
data IM a = IM Rational Property deriving (Read, Show)
|
|
instance LayoutClass IM Window where
|
|
description _ = "IM"
|
|
doLayout (IM r prop) rect stack = do
|
|
let ws = S.integrate stack
|
|
let (masterRect, slaveRect) = splitHorizontallyBy r rect
|
|
master <- findM (hasProperty prop) ws
|
|
let positions = case master of
|
|
Just w -> (w, masterRect) : arrange defaultRatio slaveRect (filter (w /=) ws)
|
|
Nothing -> arrange defaultRatio rect ws
|
|
return (positions, Nothing)
|