mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-01 04:31:52 -07:00
The base that comes with ghc-7.6.1 no longer includes Prelude.catch; so these modules were changed so that there is no warning for import Prelude hiding (catch) At the same time these changes should be compatible with older GHCs, since the catch being has never been the one in the Prelude.
64 lines
2.0 KiB
Haskell
64 lines
2.0 KiB
Haskell
-----------------------------------------------------------------------------
|
|
-- |
|
|
-- Module : XMonad.Util.NamedWindows
|
|
-- Copyright : (c) David Roundy <droundy@darcs.net>
|
|
-- License : BSD3-style (see LICENSE)
|
|
--
|
|
-- Maintainer : none
|
|
-- Stability : unstable
|
|
-- Portability : unportable
|
|
--
|
|
-- This module allows you to associate the X titles of windows with
|
|
-- them.
|
|
--
|
|
-----------------------------------------------------------------------------
|
|
|
|
module XMonad.Util.NamedWindows (
|
|
-- * Usage
|
|
-- $usage
|
|
NamedWindow,
|
|
getName,
|
|
withNamedWindow,
|
|
unName
|
|
) where
|
|
|
|
import Control.Applicative ( (<$>) )
|
|
import Control.Exception.Extensible as E
|
|
import Data.Maybe ( fromMaybe, listToMaybe )
|
|
|
|
import qualified XMonad.StackSet as W ( peek )
|
|
|
|
|
|
import XMonad
|
|
|
|
-- $usage
|
|
-- See "XMonad.Layout.Tabbed" for an example of its use.
|
|
|
|
|
|
data NamedWindow = NW !String !Window
|
|
instance Eq NamedWindow where
|
|
(NW s _) == (NW s' _) = s == s'
|
|
instance Ord NamedWindow where
|
|
compare (NW s _) (NW s' _) = compare s s'
|
|
instance Show NamedWindow where
|
|
show (NW n _) = n
|
|
|
|
getName :: Window -> X NamedWindow
|
|
getName w = withDisplay $ \d -> do
|
|
-- TODO, this code is ugly and convoluted -- clean it up
|
|
let getIt = bracket getProp (xFree . tp_value) (fmap (`NW` w) . copy)
|
|
|
|
getProp = (internAtom d "_NET_WM_NAME" False >>= getTextProperty d w)
|
|
`E.catch` \(SomeException _) -> getTextProperty d w wM_NAME
|
|
|
|
copy prop = fromMaybe "" . listToMaybe <$> wcTextPropertyToTextList d prop
|
|
|
|
io $ getIt `E.catch` \(SomeException _) -> ((`NW` w) . resName) `fmap` getClassHint d w
|
|
|
|
unName :: NamedWindow -> Window
|
|
unName (NW _ w) = w
|
|
|
|
withNamedWindow :: (NamedWindow -> X ()) -> X ()
|
|
withNamedWindow f = do ws <- gets windowset
|
|
whenJust (W.peek ws) $ \w -> getName w >>= f
|