Merge pull request #66 from mathstuf/fix-warnings

Fix warnings
This commit is contained in:
Brent Yorgey
2016-08-01 14:12:35 -04:00
committed by GitHub
8 changed files with 22 additions and 26 deletions

View File

@@ -154,13 +154,13 @@ dynamicProjects ps c =
-- | Log hook for tracking workspace changes.
dynamicProjectsLogHook :: X ()
dynamicProjectsLogHook = do
name <- gets (W.tag . W.workspace . W.current . windowset)
state <- XS.get
name <- gets (W.tag . W.workspace . W.current . windowset)
xstate <- XS.get
unless (Just name == previousProject state) $ do
XS.put (state {previousProject = Just name})
unless (Just name == previousProject xstate) $ do
XS.put (xstate {previousProject = Just name})
activateProject . fromMaybe (defProject name) $
Map.lookup name (projects state)
Map.lookup name (projects xstate)
--------------------------------------------------------------------------------
-- | Start-up hook for recording configured projects.

View File

@@ -44,7 +44,7 @@ import Data.Functor((<$>))
import qualified Data.Set as S
import qualified Data.Map as M
import Data.Maybe (fromMaybe, catMaybes)
import Data.Maybe (fromMaybe)
import Control.Monad (when, forM_, filterM)
-- $usage
@@ -272,15 +272,14 @@ instance Message SetStruts
instance LayoutModifier AvoidStruts a where
modifyLayoutWithUpdate as@(AvoidStruts ss cache smap) w r = do
let dockWins = M.keys smap
nsmap <- getRawStruts dockWins
(nr, nsmap) <- case cache of
Just (ss', r', nr) | ss' == ss, r' == r -> do
nsmap <- getRawStruts dockWins
if nsmap /= smap
then do
nr <- fmap ($ r) (calcGap dockWins ss)
setWorkarea nr
return (nr, nsmap)
wnr <- fmap ($ r) (calcGap dockWins ss)
setWorkarea wnr
return (wnr, nsmap)
else do
return (nr, smap)
_ -> do

View File

@@ -88,8 +88,6 @@ positionStoreInit mDecoTheme w = withDisplay $ \d -> do
else do
sc <- fromMaybe (W.current ws) <$> pointScreen (fi $ wa_x wa) (fi $ wa_y wa)
let sr = screenRect . W.screenDetail $ sc
rootw <- asks theRoot
(_,_,wins) <- io $ queryTree d rootw
sr' <- fmap ($ sr) (calcGapForAll $ S.fromList [minBound .. maxBound]) -- take docks into account, accepting
-- a somewhat unfortunate inter-dependency
-- with 'XMonad.Hooks.ManageDocks'

View File

@@ -425,6 +425,7 @@ optimizeOrientation rct (t, cs) = Just (opt t rct, cs)
-- initially focused leaf, path from root to selected node, window ids of borders highlighting the selection
data NodeRef = NodeRef { refLeaf :: Int, refPath :: [Direction2D], refWins :: [Window] } deriving (Show,Read,Eq)
noRef :: NodeRef
noRef = NodeRef (-1) [] []
goToNode :: NodeRef -> Zipper a -> Maybe (Zipper a)

View File

@@ -14,7 +14,7 @@
--
-----------------------------------------------------------------------------
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, PatternGuards #-}
module XMonad.Layout.IfMax
( -- * Usage

View File

@@ -91,9 +91,9 @@ allWindows = windowMap
-- | A helper to get the map of windows of the current workspace.
wsWindows :: XWindowMap
wsWindows = withWindowSet (return . W.index) >>= windowMap
wsWindows = withWindowSet (return . W.index) >>= winmap
where
windowMap = fmap M.fromList . mapM pair
winmap = fmap M.fromList . mapM pair
pair w = do name <- fmap show $ getName w
return (name, w)
@@ -102,16 +102,16 @@ wsWindows = withWindowSet (return . W.index) >>= windowMap
type XWindowMap = X (M.Map String Window)
-- | Pops open a prompt with window titles belonging to
-- windowMap. Choose one, and an action is applied on the
-- winmap. Choose one, and an action is applied on the
-- selected window, according to WindowPrompt.
windowPrompt :: XPConfig -> WindowPrompt -> XWindowMap -> X ()
windowPrompt c t windowMap = do
windowPrompt c t winmap = do
a <- case t of
Goto -> fmap gotoAction windowMap
Bring -> fmap bringAction windowMap
BringCopy -> fmap bringCopyAction windowMap
BringToMaster -> fmap bringToMaster windowMap
wm <- windowMap
Goto -> fmap gotoAction winmap
Bring -> fmap bringAction winmap
BringCopy -> fmap bringCopyAction winmap
BringToMaster -> fmap bringToMaster winmap
wm <- winmap
mkXPrompt t c (compList wm) a
where

View File

@@ -93,7 +93,7 @@ nspTrackHook _ (DestroyWindowEvent {ev_window = w}) = do
return (All True)
nspTrackHook ns (ConfigureRequestEvent {ev_window = w}) = do
NSPTrack ws <- XS.get
ws' <- forM (zip3 [0..] ws ns) $ \(n,w',NS _ _ q _) -> do
ws' <- forM (zip3 [0..] ws ns) $ \(_,w',NS _ _ q _) -> do
p <- runQuery q w
return $ if p then Just w else w'
XS.put $ NSPTrack ws'

View File

@@ -7,8 +7,7 @@ import XMonad.Core
import XMonad.ManageHook
import Graphics.X11.Xlib (Window)
import Graphics.X11.Xlib.Atom (aTOM)
import Graphics.X11.Xlib.Extras (getWindowProperty32
,changeProperty32
import Graphics.X11.Xlib.Extras (changeProperty32
,propModePrepend)
import Control.Monad.Reader (ask)
@@ -27,7 +26,6 @@ markNoTaskbar w = withDisplay $ \d -> do
ws <- getAtom "_NET_WM_STATE"
ntb <- getAtom "_NET_WM_STATE_SKIP_TASKBAR"
npg <- getAtom "_NET_WM_STATE_SKIP_PAGER"
wst' <- io $ getWindowProperty32 d ws w
io $ changeProperty32 d w ws aTOM propModePrepend [fi ntb,fi npg]
-- sigh