mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 11:30:22 -07:00
PositionStore utility to store information about position and size of a window
This commit is contained in:
parent
addb6a99e1
commit
6a8e6af48f
81
XMonad/Util/PositionStore.hs
Normal file
81
XMonad/Util/PositionStore.hs
Normal file
@ -0,0 +1,81 @@
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
|
||||
----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad.Util.PositionStore
|
||||
-- Copyright : (c) Jan Vornberger 2009
|
||||
-- License : BSD3-style (see LICENSE)
|
||||
--
|
||||
-- Maintainer : jan.vornberger@informatik.uni-oldenburg.de
|
||||
-- Stability : unstable
|
||||
-- Portability : not portable
|
||||
--
|
||||
-- A utility module to store information about position and size of a window.
|
||||
--
|
||||
-----------------------------------------------------------------------------
|
||||
|
||||
module XMonad.Util.PositionStore (
|
||||
getPosStore,
|
||||
modifyPosStore,
|
||||
|
||||
posStoreInsert,
|
||||
posStoreMove,
|
||||
posStoreQuery,
|
||||
posStoreRemove
|
||||
) where
|
||||
|
||||
import XMonad
|
||||
import XMonad.Util.ExtensibleState
|
||||
import Graphics.X11.Xlib
|
||||
import Graphics.X11.Types
|
||||
import Data.Typeable
|
||||
import qualified Data.Map as M
|
||||
|
||||
-- Store window positions relative to the upper left screen edge
|
||||
-- and windows sizes as well as positions as fractions of the screen size.
|
||||
-- This way windows can be easily relocated and scaled when switching screens.
|
||||
|
||||
data PositionStore = PS (M.Map Window PosStoreRectangle)
|
||||
deriving (Read,Show,Typeable)
|
||||
data PosStoreRectangle = PSRectangle Double Double Double Double
|
||||
deriving (Read,Show,Typeable)
|
||||
|
||||
instance ExtensionClass PositionStore where
|
||||
initialValue = PS M.empty
|
||||
extensionType = PersistentExtension
|
||||
|
||||
getPosStore :: X (PositionStore)
|
||||
getPosStore = getState
|
||||
|
||||
modifyPosStore :: (PositionStore -> PositionStore) -> X ()
|
||||
modifyPosStore f = do
|
||||
posStore <- getState
|
||||
putState (f posStore)
|
||||
|
||||
posStoreInsert :: PositionStore -> Window -> Rectangle -> Rectangle -> PositionStore
|
||||
posStoreInsert (PS posStoreMap) w (Rectangle x y wh ht) (Rectangle srX srY srWh srHt) =
|
||||
let offsetX = x - srX
|
||||
offsetY = y - srY
|
||||
in PS $ M.insert w (PSRectangle (fromIntegral offsetX / fromIntegral srWh)
|
||||
(fromIntegral offsetY / fromIntegral srHt)
|
||||
(fromIntegral wh / fromIntegral srWh)
|
||||
(fromIntegral ht / fromIntegral srHt)) posStoreMap
|
||||
|
||||
posStoreRemove :: PositionStore -> Window -> PositionStore
|
||||
posStoreRemove (PS posStoreMap) w = PS $ M.delete w posStoreMap
|
||||
|
||||
posStoreQuery :: PositionStore -> Window -> Rectangle -> Maybe Rectangle
|
||||
posStoreQuery (PS posStoreMap) w (Rectangle srX srY srWh srHt) = do
|
||||
(PSRectangle x y wh ht) <- M.lookup w posStoreMap
|
||||
let realWh = fromIntegral srWh * wh
|
||||
realHt = fromIntegral srHt * ht
|
||||
realOffsetX = fromIntegral srWh * x
|
||||
realOffsetY = fromIntegral srHt * y
|
||||
return (Rectangle (srX + round realOffsetX) (srY + round realOffsetY)
|
||||
(round realWh) (round realHt))
|
||||
|
||||
posStoreMove :: PositionStore -> Window -> Position -> Position -> Rectangle -> Rectangle -> PositionStore
|
||||
posStoreMove posStore w x y oldSr newSr =
|
||||
case (posStoreQuery posStore w oldSr) of
|
||||
Nothing -> posStore -- not in store, can't move -> do nothing
|
||||
Just (Rectangle _ _ wh ht) -> posStoreInsert posStore w (Rectangle x y wh ht) newSr
|
@ -230,6 +230,7 @@ library
|
||||
XMonad.Util.NamedScratchpad
|
||||
XMonad.Util.NamedWindows
|
||||
XMonad.Util.Paste
|
||||
XMonad.Util.PositionStore
|
||||
XMonad.Util.Replace
|
||||
XMonad.Util.Run
|
||||
XMonad.Util.Scratchpad
|
||||
|
Loading…
x
Reference in New Issue
Block a user