From e3853a9cb2a9a2cffa174d1334e2ca8ba610f151 Mon Sep 17 00:00:00 2001 From: Jose Antonio Ortega Ruiz Date: Tue, 21 Dec 2010 02:36:35 +0100 Subject: Haskell sources moved to src/ to unclutter toplevel --- src/Plugins/XMonadLog.hs | 72 ++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 72 insertions(+) create mode 100644 src/Plugins/XMonadLog.hs (limited to 'src/Plugins/XMonadLog.hs') diff --git a/src/Plugins/XMonadLog.hs b/src/Plugins/XMonadLog.hs new file mode 100644 index 0000000..3461e26 --- /dev/null +++ b/src/Plugins/XMonadLog.hs @@ -0,0 +1,72 @@ +{-# LANGUAGE CPP #-} + +----------------------------------------------------------------------------- +-- | +-- Module : Plugins.StdinReader +-- Copyright : (c) Spencer Janssen +-- License : BSD-style (see LICENSE) +-- +-- Maintainer : Spencer Janssen +-- Stability : unstable +-- Portability : unportable +-- +-- A plugin to display information from _XMONAD_LOG, specified at +-- http://code.haskell.org/XMonadContrib/XMonad/Hooks/DynamicLog.hs +-- +----------------------------------------------------------------------------- + +module Plugins.XMonadLog (XMonadLog(..)) where + +import Control.Monad +import Graphics.X11 +import Graphics.X11.Xlib.Extras +import Plugins +#ifdef UTF8 +#undef UTF8 +import Codec.Binary.UTF8.String as UTF8 +#define UTF8 +#endif +import Foreign.C (CChar) +import XUtil (nextEvent') + + +data XMonadLog = XMonadLog | XPropertyLog String + deriving (Read, Show) + +instance Exec XMonadLog where + alias XMonadLog = "XMonadLog" + alias (XPropertyLog atom) = atom + + start x cb = do + let atom = case x of + XMonadLog -> "_XMONAD_LOG" + XPropertyLog a -> a + d <- openDisplay "" + xlog <- internAtom d atom False + + root <- rootWindow d (defaultScreen d) + selectInput d root propertyChangeMask + + let update = do + mwp <- getWindowProperty8 d xlog root + maybe (return ()) (cb . decodeCChar) mwp + + update + + allocaXEvent $ \ep -> forever $ do + nextEvent' d ep + e <- getEvent ep + case e of + PropertyEvent { ev_atom = a } | a == xlog -> update + _ -> return () + + return () + +decodeCChar :: [CChar] -> String +#ifdef UTF8 +#undef UTF8 +decodeCChar = UTF8.decode . map fromIntegral +#define UTF8 +#else +decodeCChar = map (toEnum . fromIntegral) +#endif -- cgit v1.2.3