From 39f010d82d0292d9417a06abaf91dabb43ea3ef4 Mon Sep 17 00:00:00 2001 From: Daniel Wagner Date: Sun, 31 Jul 2011 19:08:50 +0200 Subject: GHC 7 compat Ignore-this: 17a43a709e70ebccc925e016d7057399 * true error: more modules export foldl/foldl'/foldr, so explicitly use the Data.Foldable one * -Werror error: transition from Control.OldException to Control.Exception, assuming everything was IOException darcs-hash:20110731170850-76d51-71271524485f6d10f84521f271182bea5085d400.gz --- XMonad/Actions/GroupNavigation.hs | 12 ++++++------ XMonad/Actions/TagWindows.hs | 7 ++++++- 2 files changed, 12 insertions(+), 7 deletions(-) (limited to 'XMonad/Actions') diff --git a/XMonad/Actions/GroupNavigation.hs b/XMonad/Actions/GroupNavigation.hs index f478e95..910e8ed 100644 --- a/XMonad/Actions/GroupNavigation.hs +++ b/XMonad/Actions/GroupNavigation.hs @@ -30,12 +30,12 @@ module XMonad.Actions.GroupNavigation ( -- * Usage ) where import Control.Monad.Reader -import Data.Foldable +import Data.Foldable as Fold import Data.Map as Map import Data.Sequence as Seq import Data.Set as Set import Graphics.X11.Types -import Prelude hiding (concatMap, drop, elem, filter, foldl, foldr, null, reverse) +import Prelude hiding (concatMap, drop, elem, filter, null, reverse) import XMonad.Core import XMonad.ManageHook import XMonad.Operations (windows, withFocused) @@ -127,7 +127,7 @@ orderedWindowList dir = withWindowSet $ \ss -> do wsids <- asks (Seq.fromList . workspaces . config) let wspcs = orderedWorkspaceList ss wsids wins = dirfun dir - $ foldl' (><) Seq.empty + $ Fold.foldl' (><) Seq.empty $ fmap (Seq.fromList . SS.integrate' . SS.stack) wspcs cur = currentWindow ss return $ maybe wins (rotfun wins) cur @@ -146,7 +146,7 @@ orderedWorkspaceList :: WindowSet -> Seq String -> Seq WindowSpace orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs' where wspcs = SS.workspaces ss - wspcsMap = foldl' (\m ws -> Map.insert (SS.tag ws) ws m) Map.empty wspcs + wspcsMap = Fold.foldl' (\m ws -> Map.insert (SS.tag ws) ws m) Map.empty wspcs wspcs' = fmap (\wsid -> wspcsMap ! wsid) wsids isCurWS ws = SS.tag ws == SS.tag (SS.workspace $ SS.current ss) @@ -184,12 +184,12 @@ updateHistory (HistoryDB oldcur oldhist) = withWindowSet $ \ss -> do --- with Seq.filter and Seq.breakl. flt :: (a -> Bool) -> Seq a -> Seq a -flt p = foldl (\xs x -> if p x then xs |> x else xs) Seq.empty +flt p = Fold.foldl (\xs x -> if p x then xs |> x else xs) Seq.empty brkl :: (a -> Bool) -> Seq a -> (Seq a, Seq a) brkl p xs = flip Seq.splitAt xs $ snd - $ foldr (\x (i, j) -> if p x then (i-1, i-1) else (i-1, j)) (l, l) xs + $ Fold.foldr (\x (i, j) -> if p x then (i-1, i-1) else (i-1, j)) (l, l) xs where l = Seq.length xs diff --git a/XMonad/Actions/TagWindows.hs b/XMonad/Actions/TagWindows.hs index d972aa4..a300f88 100644 --- a/XMonad/Actions/TagWindows.hs +++ b/XMonad/Actions/TagWindows.hs @@ -25,14 +25,19 @@ module XMonad.Actions.TagWindows ( tagDelPrompt ) where +import Prelude hiding (catch) import Data.List (nub,sortBy) import Control.Monad +import Control.Exception import XMonad.StackSet hiding (filter) import XMonad.Prompt import XMonad hiding (workspaces) +econst :: Monad m => a -> IOException -> m a +econst = const . return + -- $usage -- -- To use window tags, import this module into your @~\/.xmonad\/xmonad.hs@: @@ -79,7 +84,7 @@ getTags w = withDisplay $ \d -> io $ catch (internAtom d "_XMONAD_TAGS" False >>= getTextProperty d w >>= wcTextPropertyToTextList d) - (\_ -> return [[]]) + (econst [[]]) >>= return . words . unwords -- | check a window for the given tag -- cgit v1.2.3