darcs patch: Extras.hsc: added xSetSelectionOwner, xGetSelectionOwn...

Hi,
with this patch the we can write applications with cut and paste
capabilities.
Spencer: if you don't like the formatting, or where the functions have
been located I can edit and resend.
Let me know, please.
Cheers,
Andrea
Mon Aug 6 11:33:29 CEST 2007 Andrea Rossato

On Mon, Aug 06, 2007 at 11:38:34AM +0200, Andrea Rossato wrote:
Hi,
with this patch the we can write applications with cut and paste capabilities.
just to test it, this does the job of sselp (http://www.suckless.org/download/sselp-0.1.tar.gz). cool, isn't it? ciao andrea the code: module Main where import Graphics.X11.Xlib import Graphics.X11.Xlib.Extras import System.Exit (exitWith, ExitCode(..)) import Data.Maybe import Data.Char main :: IO () main = do dpy <- openDisplay "" let dflt = defaultScreen dpy scr = defaultScreenOfDisplay dpy rootw <- rootWindow dpy dflt win <- createSimpleWindow dpy rootw 0 0 200 100 0 0 0 p <- internAtom dpy "PRIMARY" True clp <- internAtom dpy "BLITZ_SEL_STRING" False xConvertSelection dpy p sTRING clp win currentTime allocaXEvent $ \e -> do nextEvent dpy e ev <- getEvent e if ev_event_type ev == selectionNotify then do res <- getWindowProperty8 dpy clp win putStrLn $ map (chr . fromIntegral) . fromMaybe [] $ res else do putStrLn "failed!" destroyWindow dpy win exitWith ExitSuccess

mailing_list:
On Mon, Aug 06, 2007 at 11:38:34AM +0200, Andrea Rossato wrote:
Hi,
with this patch the we can write applications with cut and paste capabilities.
just to test it, this does the job of sselp (http://www.suckless.org/download/sselp-0.1.tar.gz).
cool, isn't it? ciao andrea
the code:
module Main where import Graphics.X11.Xlib import Graphics.X11.Xlib.Extras import System.Exit (exitWith, ExitCode(..))
import Data.Maybe import Data.Char
main :: IO () main = do dpy <- openDisplay "" let dflt = defaultScreen dpy scr = defaultScreenOfDisplay dpy rootw <- rootWindow dpy dflt win <- createSimpleWindow dpy rootw 0 0 200 100 0 0 0 p <- internAtom dpy "PRIMARY" True clp <- internAtom dpy "BLITZ_SEL_STRING" False xConvertSelection dpy p sTRING clp win currentTime allocaXEvent $ \e -> do nextEvent dpy e ev <- getEvent e if ev_event_type ev == selectionNotify then do res <- getWindowProperty8 dpy clp win putStrLn $ map (chr . fromIntegral) . fromMaybe [] $ res else do putStrLn "failed!" destroyWindow dpy win exitWith ExitSuccess
Cute stuff! I wonder if we can't get a nicer, more haskellish, EDSL for doing these kinds of things. Its still too C-ish for wide use by the community.

On Tue, Aug 07, 2007 at 12:05:03PM +1000, Donald Bruce Stewart wrote:
On Mon, Aug 06, 2007 at 11:38:34AM +0200, Andrea Rossato wrote:
main :: IO () main = do
Cute stuff! I wonder if we can't get a nicer, more haskellish, EDSL for doing these kinds of things. Its still too C-ish for wide use by the community.
Sure we can! Indeed I'm a bit concerned about the style, but at the present time my main goal is to get this stuff to work and the only examples I can copy from are written in C. This is why this code is just a C translation into Haskell. If someone can help me, we could write some more haskellish examples: I have the idea of creating some xmonad utilities to do small jobs like this one (this one is useful for getting firefox to open an url or to look up for a word at dict.org). Such a repository could represent a set of X application examples. Anyway I'm sure that if we provide the community with these tools, together with a compelling reason to use them - XMonad *is* such a reason - a good haskellish way of using them will emerge regardless of my code...;-) Thanks for your kind attention. Andrea
participants (2)
-
Andrea Rossato
-
dons@cse.unsw.edu.au