aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/GroupNavigation.hs
diff options
context:
space:
mode:
authorNorbert Zeh <nzeh@cs.dal.ca>2010-05-15 00:21:53 +0200
committerNorbert Zeh <nzeh@cs.dal.ca>2010-05-15 00:21:53 +0200
commit08f91158db018414e5cdc14df4b920218635b3f0 (patch)
tree8637cf68e42938119a0bb105a2b6521d8ddbed47 /XMonad/Actions/GroupNavigation.hs
parent62245955bc752166c993829a400c5a23fff68fd3 (diff)
downloadXMonadContrib-08f91158db018414e5cdc14df4b920218635b3f0.tar.gz
XMonadContrib-08f91158db018414e5cdc14df4b920218635b3f0.tar.xz
XMonadContrib-08f91158db018414e5cdc14df4b920218635b3f0.zip
X.A.GroupNavigation with containers < 0.3.0.0 compatibility
Ignore-this: e0cf2a784ff02829ad10962863fd50ed This patch replaces the use of Seq.filter and Seq.breakl with two functions flt and brkl that do the same. This is necessary to keep compatibility with containers < 0.3.0.0 because Seq.filter and Seq.breakl were introduced only in containers 0.3.0.0. darcs-hash:20100514222153-18a2b-0b11f7214f473df160de9db0e6dfc9ff0ec13376.gz
Diffstat (limited to 'XMonad/Actions/GroupNavigation.hs')
-rw-r--r--XMonad/Actions/GroupNavigation.hs23
1 files changed, 19 insertions, 4 deletions
diff --git a/XMonad/Actions/GroupNavigation.hs b/XMonad/Actions/GroupNavigation.hs
index adde3f9..306c0f2 100644
--- a/XMonad/Actions/GroupNavigation.hs
+++ b/XMonad/Actions/GroupNavigation.hs
@@ -37,7 +37,7 @@ import Data.Maybe
import Data.Sequence as Seq
import Data.Set as Set
import Graphics.X11.Types
-import Prelude hiding (concatMap, drop, elem, filter, null, reverse)
+import Prelude hiding (concatMap, drop, elem, filter, foldl, foldr, null, reverse)
import XMonad.Core
import XMonad.ManageHook
import XMonad.Operations
@@ -174,12 +174,27 @@ updateHistory :: HistoryDB -> X HistoryDB
updateHistory (HistoryDB oldcur oldhist) = withWindowSet $ \ss -> do
let newcur = currentWindow ss
wins = Set.fromList $ SS.allWindows ss
- newhist = Seq.filter (flip Set.member wins) oldhist
+ newhist = flt (flip Set.member wins) oldhist
return $ HistoryDB newcur (del newcur $ ins oldcur newhist)
where
ins x xs = maybe xs (<| xs) x
- del x xs = maybe xs (\x' -> Seq.filter (/= x') xs) x
+ del x xs = maybe xs (\x' -> flt (/= x') xs) x
+--- Two replacements for Seq.filter and Seq.breakl available only in
+--- containers-0.3.0.0, which only ships with ghc 6.12. Once we
+--- decide to no longer support ghc < 6.12, these should be replaced
+--- 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
+
+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
+ where
+ l = Seq.length xs
+
--- Some sequence helpers --------------------------------------------
-- Rotates the sequence by one position
@@ -192,7 +207,7 @@ rotate xs = rotate' (viewl xs)
-- Rotates the sequence until an element matching the given condition
-- is at the beginning of the sequence.
rotateTo :: (a -> Bool) -> Seq a -> Seq a
-rotateTo cond xs = let (lxs, rxs) = breakl cond xs in rxs >< lxs
+rotateTo cond xs = let (lxs, rxs) = brkl cond xs in rxs >< lxs
--- A monadic find ---------------------------------------------------