Use imported `fi' alias for fromIntegral more often.

Also moves `fi' into U.Image to avoid cyclic imports,
though XUtils sill exports that definition.
This commit is contained in:
Adam Vogt 2010-04-16 21:29:39 +00:00
parent d511ffd01a
commit 78f13d2acd
9 changed files with 11 additions and 23 deletions

View File

@ -20,6 +20,7 @@ module XMonad.Actions.FlexibleResize (
) where ) where
import XMonad import XMonad
import XMonad.Util.XUtils (fi)
import Foreign.C.Types import Foreign.C.Types
-- $usage -- $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) Just True -> (0, (fi k + fi p -).fi, (fi k + fi p -).fi)
Nothing -> (k `div` 2, const p, const $ fi k) Nothing -> (k `div` 2, const p, const $ fi k)
Just False -> (k, const p, subtract (fi p) . fi) Just False -> (k, const p, subtract (fi p) . fi)
fi :: (Num b, Integral a) => a -> b
fi = fromIntegral

View File

@ -24,6 +24,7 @@ module XMonad.Actions.UpdatePointer
where where
import XMonad import XMonad
import XMonad.Util.XUtils (fi)
import Control.Monad import Control.Monad
import XMonad.StackSet (member, peek, screenDetail, current) import XMonad.StackSet (member, peek, screenDetail, current)
import Data.Maybe import Data.Maybe
@ -102,6 +103,3 @@ moveWithin now lower upper =
else if now > upper else if now > upper
then upper then upper
else now else now
fi :: (Num b, Integral a) => a -> b
fi = fromIntegral

View File

@ -33,6 +33,7 @@ import Foreign.C.Types (CLong)
import XMonad.Layout.LayoutModifier import XMonad.Layout.LayoutModifier
import XMonad.Util.Types import XMonad.Util.Types
import XMonad.Util.WindowProperties (getProp32s) import XMonad.Util.WindowProperties (getProp32s)
import XMonad.Util.XUtils (fi)
import qualified Data.Set as S import qualified Data.Set as S
@ -211,9 +212,6 @@ type Strut = (Direction2D, CLong, CLong, CLong)
type RectC = (CLong, CLong, CLong, CLong) type RectC = (CLong, CLong, CLong, CLong)
fi :: (Integral a, Num b) => a -> b
fi = fromIntegral
-- | Invertible conversion. -- | Invertible conversion.
r2c :: Rectangle -> RectC r2c :: Rectangle -> RectC

View File

@ -38,6 +38,7 @@ import qualified XMonad.StackSet as S
import XMonad.Layout.WindowArranger import XMonad.Layout.WindowArranger
import XMonad.Actions.FloatKeys import XMonad.Actions.FloatKeys
import XMonad.Util.XUtils
import qualified Data.Map as M import qualified Data.Map as M
import Data.Ratio ((%)) import Data.Ratio ((%))
@ -262,8 +263,6 @@ checkBounds (Rectangle x1 y1 w1 h1) (Rectangle x2 y2 w2 h2)
scale :: (RealFrac a, Integral b) => a -> b -> b -> b scale :: (RealFrac a, Integral b) => a -> b -> b -> b
scale r n1 n2 = truncate $ r * fi n2 + (1 - r) * fi n1 scale r n1 n2 = truncate $ r * fi n2 + (1 - r) * fi n1
fi :: (Integral a, Num b) => a -> b
fi = fromIntegral
r2rr :: Rectangle -> Rectangle -> S.RationalRect r2rr :: Rectangle -> Rectangle -> S.RationalRect
r2rr (Rectangle x0 y0 w0 h0) (Rectangle x y w h) r2rr (Rectangle x0 y0 w0 h0) (Rectangle x y w h)

View File

@ -38,6 +38,7 @@ import Graphics.X11 (Rectangle(..))
import XMonad.Layout.LayoutModifier import XMonad.Layout.LayoutModifier
import XMonad.Util.Types (Direction2D(..)) import XMonad.Util.Types (Direction2D(..))
import XMonad.Util.XUtils (fi)
import Data.List (delete) import Data.List (delete)
@ -133,9 +134,6 @@ toggleGap conf cur d | d `elem` cur = delete d cur
incGap :: GapSpec -> Direction2D -> Int -> GapSpec incGap :: GapSpec -> Direction2D -> Int -> GapSpec
incGap gs d i = map (\(dir,j) -> if dir == d then (dir,max (j+i) 0) else (dir,j)) gs incGap gs d i = map (\(dir,j) -> if dir == d then (dir,max (j+i) 0) else (dir,j)) gs
fi :: (Num b, Integral a) => a -> b
fi = fromIntegral
-- | Add togglable manual gaps to a layout. -- | Add togglable manual gaps to a layout.
gaps :: GapSpec -- ^ The gaps to allow, paired with their initial sizes. gaps :: GapSpec -- ^ The gaps to allow, paired with their initial sizes.
-> l a -- ^ The layout to modify. -> l a -- ^ The layout to modify.

View File

@ -32,6 +32,7 @@ module XMonad.Layout.Magnifier
import XMonad import XMonad
import XMonad.StackSet import XMonad.StackSet
import XMonad.Layout.LayoutModifier import XMonad.Layout.LayoutModifier
import XMonad.Util.XUtils
-- $usage -- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@ -159,6 +160,3 @@ fit (Rectangle sx sy sw sh) (Rectangle x y w h) = Rectangle x' y' w' h'
y' = max sy (y - (max 0 (y + fi h - sy - fi sh))) y' = max sy (y - (max 0 (y + fi h - sy - fi sh)))
w' = min sw w w' = min sw w
h' = min sh h h' = min sh h
fi :: (Num b, Integral a) => a -> b
fi = fromIntegral

View File

@ -29,6 +29,7 @@ import Control.Arrow (second)
import XMonad.Layout.LayoutModifier import XMonad.Layout.LayoutModifier
import XMonad.Layout.MultiToggle import XMonad.Layout.MultiToggle
import XMonad.Util.XUtils (fi)
-- $usage -- $usage
-- You can use this module by importing it into your @~\/.xmonad\/xmonad.hs@ file: -- You can use this module by importing it into your @~\/.xmonad\/xmonad.hs@ file:
@ -85,8 +86,6 @@ reflectRect Horiz (Rectangle sx _ sw _) (Rectangle rx ry rw rh) =
reflectRect Vert (Rectangle _ sy _ sh) (Rectangle rx ry rw rh) = reflectRect Vert (Rectangle _ sy _ sh) (Rectangle rx ry rw rh) =
Rectangle rx (2*sy + fi sh - ry - fi rh) rw rh Rectangle rx (2*sy + fi sh - ry - fi rh) rw rh
fi :: (Integral a, Num b) => a -> b
fi = fromIntegral
data Reflect a = Reflect ReflectDir deriving (Show, Read) data Reflect a = Reflect ReflectDir deriving (Show, Read)

View File

@ -17,7 +17,9 @@ module XMonad.Util.Image
-- $usage -- $usage
Placement(..), Placement(..),
iconPosition, iconPosition,
drawIcon drawIcon,
fi,
) where ) where
import XMonad import XMonad
@ -86,6 +88,7 @@ drawIcon dpy drw gc fc bc x y icon = do
io $ setForeground dpy gc fcolor io $ setForeground dpy gc fcolor
io $ drawPoints dpy drw gc (movePoints x y (iconToPoints icon)) coordModeOrigin io $ drawPoints dpy drw gc (movePoints x y (iconToPoints icon)) coordModeOrigin
-- | Short-hand for 'fromIntegral' -- | Short-hand for 'fromIntegral'
fi :: (Integral a, Num b) => a -> b fi :: (Integral a, Num b) => a -> b
fi = fromIntegral fi = fromIntegral

View File

@ -204,6 +204,3 @@ mkWindow d s rw x y w h p o = do
createWindow d rw x y w h 0 (defaultDepthOfScreen s) createWindow d rw x y w h 0 (defaultDepthOfScreen s)
inputOutput visual attrmask attributes inputOutput visual attrmask attributes
-- | Short-hand for 'fromIntegral'
fi :: (Integral a, Num b) => a -> b
fi = fromIntegral