Skip to content

Commit

Permalink
Merge pull request #499 from slotThe/contrib-prelude
Browse files Browse the repository at this point in the history
New module: XMonad.Prelude
  • Loading branch information
slotThe committed May 14, 2021
2 parents 02d0b79 + 00e7a5c commit bf5dce5
Show file tree
Hide file tree
Showing 189 changed files with 377 additions and 621 deletions.
2 changes: 1 addition & 1 deletion XMonad/Actions/Commands.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ import XMonad.Util.Dmenu (dmenu)

import qualified Data.Map as M
import System.Exit
import Data.Maybe
import XMonad.Prelude

-- $usage
--
Expand Down
3 changes: 1 addition & 2 deletions XMonad/Actions/CycleSelectedLayouts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,7 @@ module XMonad.Actions.CycleSelectedLayouts (
cycleThroughLayouts) where

import XMonad
import Data.List (findIndex)
import Data.Maybe (fromMaybe)
import XMonad.Prelude (findIndex, fromMaybe)
import XMonad.Layout.LayoutCombinators (JumpToLayout(..))
import qualified XMonad.StackSet as S

Expand Down
4 changes: 1 addition & 3 deletions XMonad/Actions/CycleWS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -78,9 +78,7 @@ module XMonad.Actions.CycleWS (

) where

import Data.List ( find, findIndex )
import Data.Maybe ( isNothing, isJust )

import XMonad.Prelude (find, findIndex, isJust, isNothing)
import XMonad hiding (workspaces)
import qualified XMonad.Hooks.WorkspaceHistory as WH
import XMonad.StackSet hiding (filter)
Expand Down
4 changes: 1 addition & 3 deletions XMonad/Actions/CycleWorkspaceByScreen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,14 +23,12 @@ module XMonad.Actions.CycleWorkspaceByScreen (
, repeatableAction
) where

import Control.Monad
import Data.IORef
import Data.List
import Data.Maybe

import Graphics.X11.Xlib.Extras

import XMonad
import XMonad.Prelude
import XMonad.Hooks.WorkspaceHistory
import qualified XMonad.StackSet as W

Expand Down
6 changes: 1 addition & 5 deletions XMonad/Actions/DynamicProjects.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,14 +43,10 @@ module XMonad.Actions.DynamicProjects
) where

--------------------------------------------------------------------------------
import Control.Applicative ((<|>))
import Control.Monad (when, unless)
import Data.Char (isSpace)
import Data.List (sort, union, stripPrefix)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe, isNothing)
import System.Directory (setCurrentDirectory, getHomeDirectory, makeAbsolute)
import XMonad.Prelude
import XMonad
import XMonad.Actions.DynamicWorkspaces
import XMonad.Prompt
Expand Down
2 changes: 1 addition & 1 deletion XMonad/Actions/DynamicWorkspaceGroups.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,11 +36,11 @@ module XMonad.Actions.DynamicWorkspaceGroups
, WSGPrompt
) where

import Data.List (find)
import Control.Arrow ((&&&))
import qualified Data.Map as M

import XMonad
import XMonad.Prelude (find)
import qualified XMonad.StackSet as W

import XMonad.Prompt
Expand Down
2 changes: 1 addition & 1 deletion XMonad/Actions/DynamicWorkspaceOrder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ import XMonad.Actions.CycleWS (findWorkspace, WSType(..), Direction1D(..), doTo)

import qualified Data.Map as M
import qualified Data.Set as S
import Data.Maybe (fromJust, fromMaybe)
import XMonad.Prelude (fromJust, fromMaybe)
import Data.Ord (comparing)

-- $usage
Expand Down
4 changes: 1 addition & 3 deletions XMonad/Actions/DynamicWorkspaces.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,14 +35,12 @@ module XMonad.Actions.DynamicWorkspaces (
WorkspaceIndex
) where

import XMonad.Prelude (find, isNothing, when)
import XMonad hiding (workspaces)
import XMonad.StackSet hiding (filter, modify, delete)
import XMonad.Prompt.Workspace ( Wor(Wor), workspacePrompt )
import XMonad.Prompt ( XPConfig, mkXPrompt )
import XMonad.Util.WorkspaceCompare ( getSortByIndex )
import Data.List (find)
import Data.Maybe (isNothing)
import Control.Monad (when)
import qualified Data.Map.Strict as Map
import qualified XMonad.Util.ExtensibleState as XS

Expand Down
25 changes: 10 additions & 15 deletions XMonad/Actions/EasyMotion.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,18 +38,13 @@ module XMonad.Actions.EasyMotion ( -- * Usage
) where

import XMonad
import XMonad.StackSet as W
import XMonad.Prelude
import qualified XMonad.StackSet as W
import XMonad.Util.Font (releaseXMF, initXMF, Align(AlignCenter), XMonadFont(..), textExtentsXMF)
import XMonad.Util.XUtils (fi, createNewWindow, paintAndWrite, deleteWindow, showWindow)
import Control.Monad (replicateM)
import XMonad.Util.XUtils (createNewWindow, paintAndWrite, deleteWindow, showWindow)

import Control.Arrow ((&&&))
import Data.Functor (($>))
import Data.Maybe (isJust, listToMaybe)
import qualified Data.Map.Strict as M (Map, map, mapWithKey, elems)
import Data.Set (toList)
import Graphics.X11.Xlib.Extras (getWindowAttributes, getEvent)
import qualified Data.List as L (filter, partition, find, nub)
import Data.List (sortOn)
import qualified Data.Map.Strict as M (Map, elems, map, mapWithKey)

-- $usage
--
Expand Down Expand Up @@ -275,9 +270,9 @@ handleSelectWindow c = do
$ M.mapWithKey (\sid ks -> buildOverlays ks <$> sortedOverlayWindows sid) m
where
screenById :: ScreenId -> Maybe (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail)
screenById sid = L.find ((== sid) . screen) (W.screens ws)
screenById sid = find ((== sid) . W.screen) (W.screens ws)
visibleWindowsOnScreen :: ScreenId -> [Window]
visibleWindowsOnScreen sid = L.filter (`elem` toList mappedWins) $ W.integrate' $ screenById sid >>= W.stack . W.workspace
visibleWindowsOnScreen sid = filter (`elem` toList mappedWins) $ W.integrate' $ screenById sid >>= W.stack . W.workspace
sortedOverlayWindows :: ScreenId -> X [OverlayWindow]
sortedOverlayWindows sid = sortOverlayWindows <$> buildOverlayWindows dpy th (visibleWindowsOnScreen sid)
status <- io $ grabKeyboard dpy rw True grabModeAsync grabModeAsync currentTime
Expand Down Expand Up @@ -331,7 +326,7 @@ selectWindow conf =
where
-- make sure the key lists don't contain: backspace, our cancel key, or duplicates
sanitise :: [KeySym] -> [KeySym]
sanitise = L.nub . L.filter (`notElem` [xK_BackSpace, cancelKey conf])
sanitise = nub . filter (`notElem` [xK_BackSpace, cancelKey conf])
sanitiseKeys :: ChordKeys -> ChordKeys
sanitiseKeys cKeys =
case cKeys of
Expand Down Expand Up @@ -381,12 +376,12 @@ handleKeyboard dpy drawFn cancel selected deselected = do
case x of
Backspace -> redraw >> handleKeyboard dpy drawFn cancel selected deselected
_ -> return x
isNextOverlayKey keySym = isJust (L.find ((== Just keySym) . listToMaybe .chord) selected)
isNextOverlayKey keySym = isJust (find ((== Just keySym) . listToMaybe .chord) selected)
handleNextOverlayKey keySym =
case fg of
[x] -> return $ Selected x
_ -> handleKeyboard dpy drawFn cancel (trim fg) (clear bg) >>= retryBackspace
where
(fg, bg) = L.partition ((== Just keySym) . listToMaybe . chord) selected
(fg, bg) = partition ((== Just keySym) . listToMaybe . chord) selected
trim = map (\o -> o { chord = tail $ chord o })
clear = map (\o -> o { chord = [] })
4 changes: 1 addition & 3 deletions XMonad/Actions/FindEmptyWorkspace.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,9 +18,7 @@ module XMonad.Actions.FindEmptyWorkspace (
viewEmptyWorkspace, tagToEmptyWorkspace, sendToEmptyWorkspace
) where

import Data.List
import Data.Maybe ( isNothing )

import XMonad.Prelude
import XMonad
import XMonad.StackSet

Expand Down
2 changes: 1 addition & 1 deletion XMonad/Actions/FlexibleResize.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ module XMonad.Actions.FlexibleResize (
) where

import XMonad
import XMonad.Util.XUtils (fi)
import XMonad.Prelude (fi)
import Foreign.C.Types

-- $usage
Expand Down
3 changes: 1 addition & 2 deletions XMonad/Actions/FloatSnap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,8 +27,7 @@ module XMonad.Actions.FloatSnap (
ifClick') where

import XMonad
import Data.List (sort)
import Data.Maybe (listToMaybe,fromJust,isNothing)
import XMonad.Prelude (fromJust, isNothing, listToMaybe, sort)
import qualified XMonad.StackSet as W
import qualified Data.Set as S

Expand Down
5 changes: 2 additions & 3 deletions XMonad/Actions/GridSelect.hs
Original file line number Diff line number Diff line change
Expand Up @@ -78,15 +78,14 @@ module XMonad.Actions.GridSelect (
-- * Types
TwoDState,
) where
import Data.Maybe
import Control.Arrow ((***))
import Data.Bits
import Data.Char
import Data.Ord (comparing)
import Control.Monad.State
import Control.Arrow
import Data.List as L
import qualified Data.Map as M
import XMonad hiding (liftX)
import XMonad.Prelude
import XMonad.Util.Font
import XMonad.Prompt (mkUnmanagedWindow)
import XMonad.StackSet as W
Expand Down
36 changes: 11 additions & 25 deletions XMonad/Actions/GroupNavigation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,15 +35,17 @@ module XMonad.Actions.GroupNavigation ( -- * Usage

import Control.Monad.Reader
import Control.Monad.State
import Data.Foldable as Fold
import Data.Map as Map
import Data.Sequence as Seq
import Data.Set as Set
import Data.Map ((!))
import qualified Data.Map as Map
import Data.Sequence (Seq, ViewL (EmptyL, (:<)), viewl, (<|), (><), (|>))
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import Graphics.X11.Types
import Prelude hiding (concatMap, drop, elem, filter, null, reverse)
import XMonad.Core
import XMonad.ManageHook
import XMonad.Operations (windows, withFocused)
import XMonad.Prelude (elem, foldl')
import qualified XMonad.StackSet as SS
import qualified XMonad.Util.ExtensibleState as XS

Expand Down Expand Up @@ -132,7 +134,7 @@ orderedWindowList dir = withWindowSet $ \ss -> do
wsids <- asks (Seq.fromList . workspaces . config)
let wspcs = orderedWorkspaceList ss wsids
wins = dirfun dir
$ Fold.foldl' (><) Seq.empty
$ foldl' (><) Seq.empty
$ fmap (Seq.fromList . SS.integrate' . SS.stack) wspcs
cur = SS.peek ss
return $ maybe wins (rotfun wins) cur
Expand All @@ -146,7 +148,7 @@ orderedWorkspaceList :: WindowSet -> Seq String -> Seq WindowSpace
orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs'
where
wspcs = SS.workspaces ss
wspcsMap = Fold.foldl' (\m ws -> Map.insert (SS.tag ws) ws m) Map.empty wspcs
wspcsMap = foldl' (\m ws -> Map.insert (SS.tag ws) ws m) Map.empty wspcs
wspcs' = fmap (wspcsMap !) wsids
isCurWS ws = SS.tag ws == SS.tag (SS.workspace $ SS.current ss)

Expand All @@ -172,26 +174,11 @@ updateHistory :: HistoryDB -> X HistoryDB
updateHistory (HistoryDB oldcur oldhist) = withWindowSet $ \ss -> do
let newcur = SS.peek ss
wins = Set.fromList $ SS.allWindows ss
newhist = flt (`Set.member` wins) (ins oldcur oldhist)
newhist = Seq.filter (`Set.member` wins) (ins oldcur oldhist)
return $ HistoryDB newcur (del newcur newhist)
where
ins x xs = maybe xs (<| 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 = 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
$ 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
del x xs = maybe xs (\x' -> Seq.filter (/= x') xs) x

--- Some sequence helpers --------------------------------------------

Expand All @@ -205,7 +192,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) = brkl cond xs in rxs >< lxs
rotateTo cond xs = let (lxs, rxs) = Seq.breakl cond xs in rxs >< lxs

--- A monadic find ---------------------------------------------------

Expand Down Expand Up @@ -239,4 +226,3 @@ isOnAnyVisibleWS = do
visibleWs = w `elem` allVisible
unfocused = maybe True (w /=) $ SS.peek ws
return $ visibleWs && unfocused

3 changes: 1 addition & 2 deletions XMonad/Actions/KeyRemap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,11 +27,10 @@ module XMonad.Actions.KeyRemap (
) where

import XMonad
import XMonad.Prelude
import XMonad.Util.Paste
import Data.List

import qualified XMonad.Util.ExtensibleState as XS
import Control.Monad


data KeymapTable = KeymapTable [((KeyMask, KeySym), (KeyMask, KeySym))] deriving (Typeable, Show)
Expand Down
3 changes: 1 addition & 2 deletions XMonad/Actions/Launcher.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,10 +18,9 @@ module XMonad.Actions.Launcher(
, launcherPrompt
) where

import Data.List (find, findIndex, isPrefixOf, tails)
import qualified Data.Map as M
import Data.Maybe (isJust)
import XMonad hiding (config)
import XMonad.Prelude
import XMonad.Prompt
import XMonad.Util.Run

Expand Down
6 changes: 2 additions & 4 deletions XMonad/Actions/MessageFeedback.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,13 +51,11 @@ module XMonad.Actions.MessageFeedback

import XMonad ( Window )
import XMonad.Core ( X(), Message, SomeMessage(..), LayoutClass(..), windowset, catchX, WorkspaceId, Layout, whenJust )
import XMonad.StackSet ( Workspace, current, workspace, layout, tag )
import XMonad.Operations ( updateLayout, windowBracket, modifyWindowSet )
import XMonad.Prelude ( isJust, liftA2, void )
import XMonad.StackSet ( Workspace, current, workspace, layout, tag )

import Data.Maybe ( isJust )
import Control.Monad ( void )
import Control.Monad.State ( gets )
import Control.Applicative ( liftA2 )

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
Expand Down
3 changes: 1 addition & 2 deletions XMonad/Actions/Minimize.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ module XMonad.Actions.Minimize
) where

import XMonad
import XMonad.Prelude (fromMaybe, join, listToMaybe)
import qualified XMonad.StackSet as W

import qualified XMonad.Layout.BoringWindows as BW
Expand All @@ -43,8 +44,6 @@ import XMonad.Util.Minimize
import XMonad.Util.WindowProperties (getProp32)

import Foreign.C.Types (CLong)
import Control.Monad (join)
import Data.Maybe (fromMaybe, listToMaybe)
import qualified Data.List as L
import qualified Data.Map as M

Expand Down
3 changes: 1 addition & 2 deletions XMonad/Actions/MouseGestures.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,14 +21,13 @@ module XMonad.Actions.MouseGestures (
mkCollect
) where

import XMonad.Prelude
import XMonad
import XMonad.Util.Types (Direction2D(..))

import Data.IORef
import qualified Data.Map as M
import Data.Map (Map)
import Data.Maybe
import Control.Monad

-- $usage
--
Expand Down
7 changes: 1 addition & 6 deletions XMonad/Actions/Navigation2D.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,11 +57,10 @@ module XMonad.Actions.Navigation2D ( -- * Usage
, Direction2D(..)
) where

import Control.Applicative
import qualified Data.List as L
import qualified Data.Map as M
import Data.Maybe
import Data.Ord (comparing)
import XMonad.Prelude
import XMonad hiding (Screen)
import qualified XMonad.StackSet as W
import qualified XMonad.Util.ExtensibleState as XS
Expand Down Expand Up @@ -890,10 +889,6 @@ swap win winset = W.focusWindow cur
centerOf :: Rectangle -> (Position, Position)
centerOf r = (rect_x r + fi (rect_width r) `div` 2, rect_y r + fi (rect_height r) `div` 2)

-- | Shorthand for integer conversions
fi :: (Integral a, Num b) => a -> b
fi = fromIntegral

-- | Functions to choose the subset of windows to operate on
thisLayer, otherLayer :: a -> a -> a
thisLayer = curry fst
Expand Down
Loading

0 comments on commit bf5dce5

Please sign in to comment.