aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions
diff options
context:
space:
mode:
authorMats Rauhala <mats.rauhala@gmail.com>2011-05-04 21:24:55 +0200
committerMats Rauhala <mats.rauhala@gmail.com>2011-05-04 21:24:55 +0200
commit828571625f7d55fdabb9f3b563e131244d638409 (patch)
tree064f346992e00a38041ba9d600c6902e6175ed7a /XMonad/Actions
parentb29fee817d4b8b91165f40b5aa14590bc28b8375 (diff)
downloadXMonadContrib-828571625f7d55fdabb9f3b563e131244d638409.tar.gz
XMonadContrib-828571625f7d55fdabb9f3b563e131244d638409.tar.xz
XMonadContrib-828571625f7d55fdabb9f3b563e131244d638409.zip
Compile with ghc7
Ignore-this: 218d2e19835f1e4315c01bd6214899ce darcs-hash:20110504192455-af521-ba19a95226d2527af9fbad8ed902982f2db567db.gz
Diffstat (limited to 'XMonad/Actions')
-rw-r--r--XMonad/Actions/DynamicWorkspaces.hs5
-rw-r--r--XMonad/Actions/FlexibleManipulate.hs38
2 files changed, 13 insertions, 30 deletions
diff --git a/XMonad/Actions/DynamicWorkspaces.hs b/XMonad/Actions/DynamicWorkspaces.hs
index 0e66587..d91b654 100644
--- a/XMonad/Actions/DynamicWorkspaces.hs
+++ b/XMonad/Actions/DynamicWorkspaces.hs
@@ -35,11 +35,6 @@ import Data.List (find)
import Data.Maybe (isNothing)
import Control.Monad (when)
--- The following imports are to allow haddock to find links for documentation
--- only.
-import XMonad.Actions.CopyWindow (copy)
-import XMonad.Prompt (defaultXPConfig)
-
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@ file:
--
diff --git a/XMonad/Actions/FlexibleManipulate.hs b/XMonad/Actions/FlexibleManipulate.hs
index 6ec3739..54bf586 100644
--- a/XMonad/Actions/FlexibleManipulate.hs
+++ b/XMonad/Actions/FlexibleManipulate.hs
@@ -82,17 +82,17 @@ mouseWindow f w = whenX (isClient w) $ withDisplay $ \d -> do
sh <- io $ getWMNormalHints d w
pointer <- io $ queryPointer d w >>= return . pointerPos
- let uv = (pointer - wpos) / wsize
+ let uv = zipP (/) (zipP (-) pointer wpos) wsize
fc = mapP f uv
mul = mapP (\x -> 2 - 2 * abs(x - 0.5)) fc --Fudge factors: interpolation between 1 when on edge, 2 in middle
- atl = ((1, 1) - fc) * mul
- abr = fc * mul
+ atl = zipP (*) (zipP (-) (1, 1) fc) mul
+ abr = zipP (*) fc mul
mouseDrag (\ex ey -> io $ do
- let offset = (fromIntegral ex, fromIntegral ey) - pointer
- npos = wpos + offset * atl
- nbr = (wpos + wsize) + offset * abr
- ntl = minP (nbr - (32, 32)) npos --minimum size
- nwidth = applySizeHintsContents sh $ mapP (round :: Double -> Integer) (nbr - ntl)
+ let offset = zipP (-) (fromIntegral ex, fromIntegral ey) pointer
+ npos = zipP (*) wpos $ zipP (*) offset atl
+ nbr = zipP (+) (zipP (+) wpos wsize) (zipP (*) offset abr)
+ ntl = minP (zipP (-) nbr (32, 32)) npos --minimum size
+ nwidth = applySizeHintsContents sh $ mapP (round :: Double -> Integer) (zipP (-) nbr ntl)
moveResizeWindow d w (round $ fst ntl) (round $ snd ntl) `uncurry` nwidth
return ())
(float w)
@@ -100,14 +100,14 @@ mouseWindow f w = whenX (isClient w) $ withDisplay $ \d -> do
float w
where
- pointerPos (_,_,_,px,py,_,_,_) = (fromIntegral px,fromIntegral py) :: Pnt
- winAttrs :: WindowAttributes -> [Pnt]
+ pointerPos (_,_,_,px,py,_,_,_) = (fromIntegral px,fromIntegral py)
+ winAttrs :: WindowAttributes -> [(Double, Double)]
winAttrs x = pairUp $ map (fromIntegral . ($ x)) [wa_x, wa_y, wa_width, wa_height]
+ -- Changed the type = Pnt implementation to use the zipP functionality
+ -- because (on ghc7) the previous implementation caused Orphan Instances
+ -- warnings
--- I'd rather I didn't have to do this, but I hate writing component 2d math
-type Pnt = (Double, Double)
-
pairUp :: [a] -> [(a,a)]
pairUp [] = []
pairUp [_] = []
@@ -120,15 +120,3 @@ zipP f (ax,ay) (bx,by) = (f ax bx, f ay by)
minP :: Ord a => (a,a) -> (a,a) -> (a,a)
minP = zipP min
-
-instance Num Pnt where
- (+) = zipP (+)
- (-) = zipP (-)
- (*) = zipP (*)
- abs = mapP abs
- signum = mapP signum
- fromInteger = const undefined
-
-instance Fractional Pnt where
- fromRational = const undefined
- recip = mapP recip