diff options
author | Adam Vogt <vogt.adam@gmail.com> | 2010-04-16 23:29:39 +0200 |
---|---|---|
committer | Adam Vogt <vogt.adam@gmail.com> | 2010-04-16 23:29:39 +0200 |
commit | c5b25d0fb00ff878886df89842c4a442819a0800 (patch) | |
tree | 983f531785953c66b51d71f0bbd132236961f257 /XMonad/Actions | |
parent | 879a7a8dd2e0c9360ed9a90f8bab1f945b265211 (diff) | |
download | XMonadContrib-c5b25d0fb00ff878886df89842c4a442819a0800.tar.gz XMonadContrib-c5b25d0fb00ff878886df89842c4a442819a0800.tar.xz XMonadContrib-c5b25d0fb00ff878886df89842c4a442819a0800.zip |
Use imported `fi' alias for fromIntegral more often.
Ignore-this: 51040e693066fd7803cc1b108c1a13d5
Also moves `fi' into U.Image to avoid cyclic imports,
though XUtils sill exports that definition.
darcs-hash:20100416212939-1499c-a12428074d873b1eaea197e1b79c0ca07a96b05f.gz
Diffstat (limited to 'XMonad/Actions')
-rw-r--r-- | XMonad/Actions/FlexibleResize.hs | 4 | ||||
-rw-r--r-- | XMonad/Actions/UpdatePointer.hs | 4 |
2 files changed, 2 insertions, 6 deletions
diff --git a/XMonad/Actions/FlexibleResize.hs b/XMonad/Actions/FlexibleResize.hs index a387c19..05f232f 100644 --- a/XMonad/Actions/FlexibleResize.hs +++ b/XMonad/Actions/FlexibleResize.hs @@ -20,6 +20,7 @@ module XMonad.Actions.FlexibleResize ( ) where import XMonad +import XMonad.Util.XUtils (fi) import Foreign.C.Types -- $usage @@ -76,6 +77,3 @@ mouseResizeEdgeWindow edge w = whenX (isClient w) $ withDisplay $ \d -> do Just True -> (0, (fi k + fi p -).fi, (fi k + fi p -).fi) Nothing -> (k `div` 2, const p, const $ fi k) Just False -> (k, const p, subtract (fi p) . fi) - -fi :: (Num b, Integral a) => a -> b -fi = fromIntegral diff --git a/XMonad/Actions/UpdatePointer.hs b/XMonad/Actions/UpdatePointer.hs index 7fff869..4eed35d 100644 --- a/XMonad/Actions/UpdatePointer.hs +++ b/XMonad/Actions/UpdatePointer.hs @@ -24,6 +24,7 @@ module XMonad.Actions.UpdatePointer where import XMonad +import XMonad.Util.XUtils (fi) import Control.Monad import XMonad.StackSet (member, peek, screenDetail, current) import Data.Maybe @@ -102,6 +103,3 @@ moveWithin now lower upper = else if now > upper then upper else now - -fi :: (Num b, Integral a) => a -> b -fi = fromIntegral |