
Hi, today I was refreshing my memories about arrows and I thought to rewrite the minimal example of X selections I've sent a couple of days ago. It was written in a strict C style, as Dons observed, so I thought to rewrite it with a simple Kleisli arrow to force myself to use another coding paradigm. It's a mess, and, I think, not only for my personal lack of programming style. Arguments of functions are disposed in a convenient way for imperative programming, but when it comes to function composition it just gets very difficult for me. I would like to have you suggestions. This could help me improve my style, and perhaps contribute to introducing the Haskell community to X programming by making the code we produce within this project more adherent to the Haskell way of doing things. Thanks for your kind attention. Andrea the code below requires my last patch to X11-extras available here: http://www.haskell.org/pipermail/xmonad/2007-August/001661.html module Main where import Graphics.X11.Xlib import Graphics.X11.Xlib.Extras import System.Exit (exitWith, ExitCode(..)) import Data.Maybe import Data.Char import Control.Arrow dpyWin :: Kleisli IO String (Display, Window) dpyWin = Kleisli openDisplay >>> arr id &&& arr defaultScreen >>> arr fst &&& Kleisli (uncurry rootWindow) >>> arr fst &&& cw where cw = Kleisli (uncurry $ cw' 0 0 200 100 0 0 0) cw' x y wh ht back border i d rw = createSimpleWindow d rw x y wh ht back border i atoms :: Kleisli IO (Display, Window) ((Display, Window),(Atom, Atom)) atoms = arr id &&& (arr fst >>> Kleisli (atom "PRIMARY" True) &&& Kleisli (atom "BLITZ_SEL_STRING" False)) where atom t b d = internAtom d t b convertSel :: ((Display, Window),(Atom, Atom)) -> IO () convertSel ((d,w),(a,b)) = xConvertSelection d a sTRING b w currentTime -- ok I'm giving up getSel :: ((Display, Window), (t, Atom)) -> IO () getSel ((d,w),(p,clp)) = do allocaXEvent $ \e -> do nextEvent d e ev <- getEvent e if ev_event_type ev == selectionNotify then do res <- getWindowProperty8 d clp w putStrLn $ map (chr . fromIntegral) . fromMaybe [] $ res else do putStrLn "Failed!" destroyWindow d w doRun = dpyWin >>> atoms >>> Kleisli convertSel &&& Kleisli getSel >>> Kleisli (\_ -> exitWith ExitSuccess) main :: IO () main = runKleisli doRun ""