aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/AfterDrag.hs
diff options
context:
space:
mode:
authorankaan <ankaan@gmail.com>2015-03-06 18:17:02 +0100
committerankaan <ankaan@gmail.com>2015-03-06 18:17:02 +0100
commit90fa406833c7158525e6ff4f941a85abf2dabd9b (patch)
tree76c635a8a3ac075fe3633154f579754620577878 /XMonad/Actions/AfterDrag.hs
parentdcb29816dd1627411028aa05e2331f3e8050e5ff (diff)
downloadXMonadContrib-90fa406833c7158525e6ff4f941a85abf2dabd9b.tar.gz
XMonadContrib-90fa406833c7158525e6ff4f941a85abf2dabd9b.tar.xz
XMonadContrib-90fa406833c7158525e6ff4f941a85abf2dabd9b.zip
X.L.AvoidFloats, like avoidStruts but for floats
Ignore-this: 3722d7787dd2429313f92f85f3ae1251 Checks for floating windows within the layout area and finds a maximum area rectangle within that does not overlap with any of the floating windows. This rectangle is used for all non-floating windows. This new functionality introduced problems with the recommended configuration of one of my other modules (X.A.FloatSnap.) A new and more reliable method of distinguishing between clicks and drags where therefore introduced in the new module X.A.AfterDrag. This does not break any prior use of FloatSnap, but will require changes in configuration if used together with AvoidFloats. (This is mentioned in the docs for AvoidFloats and I recommend using the new configuration method even if AvoidFloats is not in use.) darcs-hash:20150306171702-3948e-a8b8c75ba49306a33d87c9414117f8a49c536dbf.gz
Diffstat (limited to 'XMonad/Actions/AfterDrag.hs')
-rw-r--r--XMonad/Actions/AfterDrag.hs71
1 files changed, 71 insertions, 0 deletions
diff --git a/XMonad/Actions/AfterDrag.hs b/XMonad/Actions/AfterDrag.hs
new file mode 100644
index 0000000..261ea91
--- /dev/null
+++ b/XMonad/Actions/AfterDrag.hs
@@ -0,0 +1,71 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Actions.AfterDrag
+-- Copyright : (c) 2014 Anders Engstrom <ankaan@gmail.com>
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : Anders Engstrom <ankaan@gmail.com>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- Perform an action after the current mouse drag is completed.
+-----------------------------------------------------------------------------
+
+module XMonad.Actions.AfterDrag (
+ -- * Usage
+ -- $usage
+ afterDrag,
+ ifClick,
+ ifClick') where
+
+import XMonad
+import System.Time
+
+-- $usage
+-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Actions.AfterDrag
+--
+-- Then add appropriate mouse bindings, for example:
+--
+-- > , ((modm, button3), (\w -> focus w >> mouseResizeWindow w >> ifClick (windows $ W.float w $ W.RationalRect 0 0 1 1)))
+--
+-- This will allow you to resize windows as usual, but if you instead of
+-- draging click the mouse button the window will be automatically resized to
+-- fill the whole screen.
+--
+-- For detailed instructions on editing your mouse bindings, see
+-- "XMonad.Doc.Extending#Editing_mouse_bindings".
+--
+-- More practical examples are available in "XMonad.Actions.FloatSnap".
+
+-- | Schedule a task to take place after the current dragging is completed.
+afterDrag
+ :: X () -- ^ The task to schedule.
+ -> X ()
+afterDrag task = do drag <- gets dragging
+ case drag of
+ Nothing -> return () -- Not dragging
+ Just (motion, cleanup) -> modify $ \s -> s { dragging = Just(motion, cleanup >> task) }
+
+-- | Take an action if the current dragging can be considered a click,
+-- supposing the drag just started before this function is called.
+-- A drag is considered a click if it is completed within 300 ms.
+ifClick
+ :: X () -- ^ The action to take if the dragging turned out to be a click.
+ -> X ()
+ifClick action = ifClick' 300 action (return ())
+
+-- | Take an action if the current dragging is completed within a certain time (in milliseconds.)
+ifClick'
+ :: Int -- ^ Maximum time of dragging for it to be considered a click (in milliseconds.)
+ -> X () -- ^ The action to take if the dragging turned out to be a click.
+ -> X () -- ^ The action to take if the dragging turned out to not be a click.
+ -> X ()
+ifClick' ms click drag = do
+ start <- io $ getClockTime
+ afterDrag $ do
+ stop <- io $ getClockTime
+ if diffClockTimes stop start <= noTimeDiff { tdPicosec = fromIntegral ms * 10^(9 :: Integer) }
+ then click
+ else drag