diff options
-rw-r--r-- | XMonad/Prompt.hs | 9 | ||||
-rw-r--r-- | XMonad/Util/XSelection.hs | 44 |
2 files changed, 4 insertions, 49 deletions
diff --git a/XMonad/Prompt.hs b/XMonad/Prompt.hs index 6abb4d0..90e8685 100644 --- a/XMonad/Prompt.hs +++ b/XMonad/Prompt.hs @@ -29,7 +29,7 @@ module XMonad.Prompt , defaultXPKeymap , quit , killBefore, killAfter, startOfLine, endOfLine - , pasteString, copyString, moveCursor + , pasteString, moveCursor , moveWord, killWord, deleteString , moveHistory, setSuccess, setDone , Direction1D(..) @@ -67,7 +67,7 @@ import qualified XMonad as X (numlockMask,config) import qualified XMonad.StackSet as W import XMonad.Util.Font import XMonad.Util.Types -import XMonad.Util.XSelection (getSelection, putSelection) +import XMonad.Util.XSelection (getSelection) import Control.Arrow ((&&&),first) import Control.Concurrent (threadDelay) @@ -403,7 +403,6 @@ defaultXPKeymap = M.fromList $ , (xK_a, startOfLine) , (xK_e, endOfLine) , (xK_y, pasteString) - , (xK_c, copyString) , (xK_Right, moveWord Next) , (xK_Left, moveWord Prev) , (xK_Delete, killWord Next) @@ -505,10 +504,6 @@ insertString str = pasteString :: XP () pasteString = join $ io $ liftM insertString getSelection --- | Copy the currently entered string into the X selection. -copyString :: XP () -copyString = gets command >>= io . putSelection - -- | Remove a character at the cursor position deleteString :: Direction1D -> XP () deleteString d = diff --git a/XMonad/Util/XSelection.hs b/XMonad/Util/XSelection.hs index 83096d2..9113429 100644 --- a/XMonad/Util/XSelection.hs +++ b/XMonad/Util/XSelection.hs @@ -9,7 +9,7 @@ Stability : unstable Portability : unportable A module for accessing and manipulating X Window's mouse selection (the buffer used in copy and pasting). -'getSelection' and 'putSelection' are adaptations of Hxsel.hs and Hxput.hs from the XMonad-utils, available: +'getSelection' is an adaptation of Hxsel.hs and Hxput.hs from the XMonad-utils, available: > $ darcs get <http://gorgias.mine.nu/repos/xmonad-utils> -} @@ -20,13 +20,10 @@ module XMonad.Util.XSelection ( -- * Usage promptSelection, safePromptSelection, transformPromptSelection, - transformSafePromptSelection, - putSelection) where + transformSafePromptSelection) where -import Control.Concurrent (forkIO) import Control.Exception as E (catch) import Control.Monad(Monad (return, (>>)), Functor(..), liftM, join) -import Data.Char (ord) import Data.Maybe (fromMaybe) import XMonad import XMonad.Util.Run (safeSpawn, unsafeSpawn) @@ -81,43 +78,6 @@ getSelection = io $ do return $ decode . map fromIntegral . fromMaybe [] $ res else destroyWindow dpy win >> return "" --- | Set the current X Selection to a specified string. -putSelection :: MonadIO m => String -> m () -putSelection text = io $ do - dpy <- openDisplay "" - let dflt = defaultScreen dpy - rootw <- rootWindow dpy dflt - win <- createSimpleWindow dpy rootw 0 0 1 1 0 0 0 - p <- internAtom dpy "PRIMARY" True - ty <- internAtom dpy "UTF8_STRING" False - xSetSelectionOwner dpy p win currentTime - winOwn <- xGetSelectionOwner dpy p - if winOwn == win - then do forkIO ((allocaXEvent $ processEvent dpy ty text) >> destroyWindow dpy win) >> return () - else do putStrLn "Unable to obtain ownership of the selection" >> destroyWindow dpy win - return () - where - processEvent :: Display -> Atom -> [Char] -> XEventPtr -> IO () - processEvent dpy ty txt e = do - nextEvent dpy e - ev <- getEvent e - if ev_event_type ev == selectionRequest - then do print ev - allocaXEvent $ \replyPtr -> do - changeProperty8 (ev_event_display ev) - (ev_requestor ev) - (ev_property ev) - ty - propModeReplace - (map (fromIntegral . ord) txt) - setSelectionNotify replyPtr (ev_requestor ev) (ev_selection ev) - (ev_target ev) (ev_property ev) (ev_time ev) - sendEvent dpy (ev_requestor ev) False noEventMask replyPtr - sync dpy False - else do putStrLn "Unexpected Message Received" - print ev - processEvent dpy ty text e - {- | A wrapper around 'getSelection'. Makes it convenient to run a program with the current selection as an argument. This is convenient for handling URLs, in particular. For example, in your Config.hs you could bind a key to @promptSelection \"firefox\"@; |