1 Commits

Author SHA1 Message Date
Peter Jones
1833003404 Update X11 version for xmonad/xmonad#9 2016-11-22 18:49:01 -07:00
25 changed files with 144 additions and 350 deletions

View File

@@ -1,24 +0,0 @@
### Problem Description
Describe the problem you are having, what you expect to happen
instead, and how to reproduce the problem.
### Configuration File
Please include the smallest configuration file that reproduces the
problem you are experiencing:
```haskell
module Main (main) where
import XMonad
main :: IO ()
main = xmonad def
```
### Checklist
- [ ] I've read [CONTRIBUTING.md](https://github.com/xmonad/xmonad/blob/master/CONTRIBUTING.md)
- [ ] I tested my configuration with [xmonad-testing](https://github.com/xmonad/xmonad-testing)

View File

@@ -1,12 +0,0 @@
### Description
Include a description for your changes, including the motivation
behind them.
### Checklist
- [ ] I've read [CONTRIBUTING.md](https://github.com/xmonad/xmonad/blob/master/CONTRIBUTING.md)
- [ ] I tested my changes with [xmonad-testing](https://github.com/xmonad/xmonad-testing)
- [ ] I updated the `CHANGES.md` file

1
.gitignore vendored
View File

@@ -23,4 +23,3 @@ tags
# stack artifacts # stack artifacts
/.stack-work/ /.stack-work/
/cabal.project.local

View File

@@ -13,18 +13,18 @@ before_cache:
matrix: matrix:
include: include:
- env: CABALVER=1.16 GHCVER=7.4.2
compiler: ": #GHC 7.4.2"
addons: {apt: {packages: [cabal-install-1.16,ghc-7.4.2], sources: [hvr-ghc]}}
- env: CABALVER=1.16 GHCVER=7.6.3 - env: CABALVER=1.16 GHCVER=7.6.3
compiler: ": #GHC 7.6.3" compiler: ": #GHC 7.6.3"
addons: {apt: {packages: [cabal-install-1.16,ghc-7.6.3], sources: [hvr-ghc]}} addons: {apt: {packages: [cabal-install-1.16,ghc-7.6.3], sources: [hvr-ghc]}}
- env: CABALVER=1.18 GHCVER=7.8.4 - env: CABALVER=1.18 GHCVER=7.8.4
compiler: ": #GHC 7.8.4" compiler: ": #GHC 7.8.4"
addons: {apt: {packages: [cabal-install-1.18,ghc-7.8.4], sources: [hvr-ghc]}} addons: {apt: {packages: [cabal-install-1.18,ghc-7.8.4], sources: [hvr-ghc]}}
- env: CABALVER=1.22 GHCVER=7.10.3 - env: CABALVER=1.22 GHCVER=7.10.2
compiler: ": #GHC 7.10.3" compiler: ": #GHC 7.10.2"
addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.3], sources: [hvr-ghc]}} addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.2], sources: [hvr-ghc]}}
- env: CABALVER=1.24 GHCVER=8.0.1
compiler: ": #GHC 8.0.1"
addons: {apt: {packages: [cabal-install-1.24,ghc-8.0.1], sources: [hvr-ghc]}}
before_install: before_install:
- unset CC - unset CC
@@ -47,7 +47,7 @@ install:
- sed -i -e '1,/^Resolving /d' installplan.txt; cat installplan.txt - sed -i -e '1,/^Resolving /d' installplan.txt; cat installplan.txt
# check whether current requested install-plan matches cached package-db snapshot # check whether current requested install-plan matches cached package-db snapshot
- if diff -u $HOME/.cabsnap/installplan.txt installplan.txt; - if diff -u installplan.txt $HOME/.cabsnap/installplan.txt;
then then
echo "cabal build-cache HIT"; echo "cabal build-cache HIT";
rm -rfv .ghc; rm -rfv .ghc;

View File

@@ -1,19 +1,16 @@
# Change Log / Release Notes # Change Log / Release Notes
## 0.13 (February 10, 2017) ## 0.13
### Breaking Changes ### Breaking Changes
* The type of `completionKey` (of `XPConfig` record) has been * The type of `completionKey` (of `XPConfig` record) has been
changed from `KeySym` to `(KeyMask, KeySym)`. The default value changed from `KeySym` to `(KeyMask, KeySym)`. The default value
for this is still bound to the `Tab` key. for this is still binded to `Tab` key.
* New constructor `CenteredAt Rational Rational` added for * New constructor `CenteredAt Rational Rational` added for
`XMonad.Prompt.XPPosition`. `XMonad.Prompt.XPPosition`.
* `XMonad.Prompt` now stores its history file in the XMonad cache
directory in a file named `prompt-history`.
### New Modules ### New Modules
* `XMonad.Layout.SortedLayout` * `XMonad.Layout.SortedLayout`
@@ -45,35 +42,13 @@
EWMH taskbars and pagers. Useful for `NamedScratchpad` windows, since EWMH taskbars and pagers. Useful for `NamedScratchpad` windows, since
you will usually be taken to the `NSP` workspace by them. you will usually be taken to the `NSP` workspace by them.
### Bug Fixes and Minor Changes ### Minor Changes
* `XMonad.Hooks.ManageDocks`,
- Fix a very annoying bug where taskbars/docs would be
covered by windows.
- Also fix a bug that caused certain Gtk and Qt application to
have issues displaying menus and popups.
* `XMonad.Layout.LayoutBuilder` * `XMonad.Layout.LayoutBuilder`
Merge all functionality from `XMonad.Layout.LayoutBuilderP` into Merge all functionality from `XMonad.Layout.LayoutBuilderP` into
`XMonad.Layout.LayoutBuilder`. `XMonad.Layout.LayoutBuilder`.
* `XMonad.Actions.WindowGo`
- Fix `raiseNextMaybe` cycling between 2 workspaces only.
* `XMonad.Actions.UpdatePointer`
- Fix bug when cursor gets stuck in one of the corners.
* `XMonad.Actions.Submap`
Establish pointer grab to avoid freezing X, when button press occurs after
submap key press. And terminate submap at button press in the same way,
as we do for wrong key press.
* `XMonad.Actions.DynamicProjects` * `XMonad.Actions.DynamicProjects`
- Switching away from a dynamic project that contains no windows - Switching away from a dynamic project that contains no windows
@@ -82,11 +57,6 @@
The project itself was already being deleted, this just deletes The project itself was already being deleted, this just deletes
the workspace created for it as well. the workspace created for it as well.
- Added function to change the working directory (`changeProjectDirPrompt`)
- All of the prompts are now multiple mode prompts. Try using the
`changeModeKey` in a prompt and see what happens!
## 0.12 (December 14, 2015) ## 0.12 (December 14, 2015)
### Breaking Changes ### Breaking Changes

View File

@@ -1,7 +1,5 @@
# xmonad-contrib: Third Party Extensions to the xmonad Window Manager # xmonad-contrib: Third Party Extensions to the xmonad Window Manager
[![Build Status](https://travis-ci.org/xmonad/xmonad-contrib.svg?branch=master)](https://travis-ci.org/xmonad/xmonad-contrib)
You need the ghc compiler and xmonad window manager installed in You need the ghc compiler and xmonad window manager installed in
order to use these extensions. order to use these extensions.

View File

@@ -239,7 +239,6 @@ data WSType = EmptyWS -- ^ cycle through empty workspaces
| NonEmptyWS -- ^ cycle through non-empty workspaces | NonEmptyWS -- ^ cycle through non-empty workspaces
| HiddenWS -- ^ cycle through non-visible workspaces | HiddenWS -- ^ cycle through non-visible workspaces
| HiddenNonEmptyWS -- ^ cycle through non-empty non-visible workspaces | HiddenNonEmptyWS -- ^ cycle through non-empty non-visible workspaces
| HiddenEmptyWS -- ^ cycle through empty non-visible workspaces
| AnyWS -- ^ cycle through all workspaces | AnyWS -- ^ cycle through all workspaces
| WSTagGroup Char | WSTagGroup Char
-- ^ cycle through workspaces in the same group, the -- ^ cycle through workspaces in the same group, the
@@ -258,9 +257,6 @@ wsTypeToPred HiddenWS = do hs <- gets (map tag . hidden . windowset)
wsTypeToPred HiddenNonEmptyWS = do ne <- wsTypeToPred NonEmptyWS wsTypeToPred HiddenNonEmptyWS = do ne <- wsTypeToPred NonEmptyWS
hi <- wsTypeToPred HiddenWS hi <- wsTypeToPred HiddenWS
return (\w -> hi w && ne w) return (\w -> hi w && ne w)
wsTypeToPred HiddenEmptyWS = do ne <- wsTypeToPred EmptyWS
hi <- wsTypeToPred HiddenWS
return (\w -> hi w && ne w)
wsTypeToPred AnyWS = return (const True) wsTypeToPred AnyWS = return (const True)
wsTypeToPred (WSTagGroup sep) = do cur <- (groupName.workspace.current) `fmap` gets windowset wsTypeToPred (WSTagGroup sep) = do cur <- (groupName.workspace.current) `fmap` gets windowset
return $ (cur ==).groupName return $ (cur ==).groupName

View File

@@ -31,7 +31,6 @@ module XMonad.Actions.DynamicProjects
, switchProjectPrompt , switchProjectPrompt
, shiftToProjectPrompt , shiftToProjectPrompt
, renameProjectPrompt , renameProjectPrompt
, changeProjectDirPrompt
-- * Helper Functions -- * Helper Functions
, switchProject , switchProject
@@ -44,7 +43,6 @@ module XMonad.Actions.DynamicProjects
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Control.Applicative ((<|>)) import Control.Applicative ((<|>))
import Control.Monad (when, unless) import Control.Monad (when, unless)
import Data.Char (isSpace)
import Data.List (sort, union, stripPrefix) import Data.List (sort, union, stripPrefix)
import Data.Map.Strict (Map) import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
@@ -54,7 +52,8 @@ import System.Directory (setCurrentDirectory, getHomeDirectory)
import XMonad import XMonad
import XMonad.Actions.DynamicWorkspaces import XMonad.Actions.DynamicWorkspaces
import XMonad.Prompt import XMonad.Prompt
import XMonad.Prompt.Directory import XMonad.Prompt.Directory (directoryPrompt)
import XMonad.Prompt.Workspace (Wor(..))
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import qualified XMonad.Util.ExtensibleState as XS import qualified XMonad.Util.ExtensibleState as XS
@@ -143,48 +142,6 @@ data ProjectState = ProjectState
instance ExtensionClass ProjectState where instance ExtensionClass ProjectState where
initialValue = ProjectState Map.empty Nothing initialValue = ProjectState Map.empty Nothing
--------------------------------------------------------------------------------
-- Internal types for working with XPrompt.
data ProjectPrompt = ProjectPrompt ProjectMode [ProjectName]
data ProjectMode = SwitchMode | ShiftMode | RenameMode | DirMode
instance XPrompt ProjectPrompt where
showXPrompt (ProjectPrompt submode _) =
case submode of
SwitchMode -> "Switch or Create Project: "
ShiftMode -> "Send Window to Project: "
RenameMode -> "New Project Name: "
DirMode -> "Change Project Directory: "
completionFunction (ProjectPrompt RenameMode _) = return . (:[])
completionFunction (ProjectPrompt DirMode _) =
let xpt = directoryMultipleModes "" (const $ return ())
in completionFunction xpt
completionFunction (ProjectPrompt _ ns) = mkComplFunFromList' ns
modeAction (ProjectPrompt SwitchMode _) buf auto = do
let name = if null auto then buf else auto
ps <- XS.gets projects
case Map.lookup name ps of
Just p -> switchProject p
Nothing | null name -> return ()
| otherwise -> switchProject (defProject name)
modeAction (ProjectPrompt ShiftMode _) buf auto = do
let name = if null auto then buf else auto
ps <- XS.gets projects
shiftToProject . fromMaybe (defProject name) $ Map.lookup name ps
modeAction (ProjectPrompt RenameMode _) name _ =
when (not (null name) && not (all isSpace name)) $ do
renameWorkspaceByName name
modifyProject (\p -> p { projectName = name })
modeAction (ProjectPrompt DirMode _) buf auto = do
let dir = if null auto then buf else auto
modifyProject (\p -> p { projectDirectory = dir })
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Add dynamic projects support to the given config. -- | Add dynamic projects support to the given config.
dynamicProjects :: [Project] -> XConfig a -> XConfig a dynamicProjects :: [Project] -> XConfig a -> XConfig a
@@ -241,21 +198,6 @@ currentProject = do
proj <- lookupProject name proj <- lookupProject name
return $ fromMaybe (defProject name) proj return $ fromMaybe (defProject name) proj
--------------------------------------------------------------------------------
-- | Modify the current project using a pure function.
modifyProject :: (Project -> Project) -> X ()
modifyProject f = do
p <- currentProject
ps <- XS.gets projects
-- If a project is renamed to match another project, the old project
-- will be removed and replaced with this one.
let new = f p
ps' = Map.insert (projectName new) new $ Map.delete (projectName p) ps
XS.modify $ \s -> s {projects = ps'}
activateProject new
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Switch to the given project. -- | Switch to the given project.
switchProject :: Project -> X () switchProject :: Project -> X ()
@@ -278,11 +220,22 @@ switchProject p = do
-- | Prompt for a project name and then switch to it. Automatically -- | Prompt for a project name and then switch to it. Automatically
-- creates a project if a new name is returned from the prompt. -- creates a project if a new name is returned from the prompt.
switchProjectPrompt :: XPConfig -> X () switchProjectPrompt :: XPConfig -> X ()
switchProjectPrompt = projectPrompt [ SwitchMode switchProjectPrompt c = projectPrompt c switch
, ShiftMode where
, RenameMode switch :: ProjectTable -> ProjectName -> X ()
, DirMode switch ps name = case Map.lookup name ps of
] Just p -> switchProject p
Nothing | null name -> return ()
| otherwise -> directoryPrompt dirC "Project Dir: " (mkProject name)
dirC :: XPConfig
dirC = c { alwaysHighlight = False } -- Fix broken tab completion.
mkProject :: ProjectName -> FilePath -> X ()
mkProject name dir = do
let p = Project name dir Nothing
XS.modify $ \s -> s {projects = Map.insert name p $ projects s}
switchProject p
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Shift the currently focused window to the given project. -- | Shift the currently focused window to the given project.
@@ -295,44 +248,40 @@ shiftToProject p = do
-- | Prompts for a project name and then shifts the currently focused -- | Prompts for a project name and then shifts the currently focused
-- window to that project. -- window to that project.
shiftToProjectPrompt :: XPConfig -> X () shiftToProjectPrompt :: XPConfig -> X ()
shiftToProjectPrompt = projectPrompt [ ShiftMode shiftToProjectPrompt c = projectPrompt c go
, RenameMode where
, SwitchMode go :: ProjectTable -> ProjectName -> X ()
, DirMode go ps name = shiftToProject . fromMaybe (defProject name) $
] Map.lookup name ps
--------------------------------------------------------------------------------
-- | Rename the current project.
renameProjectPrompt :: XPConfig -> X ()
renameProjectPrompt = projectPrompt [ RenameMode
, DirMode
, SwitchMode
, ShiftMode
]
--------------------------------------------------------------------------------
-- | Change the working directory used for the current project.
--
-- NOTE: This will only affect new processed started in this project.
-- Existing processes will maintain the previous working directory.
changeProjectDirPrompt :: XPConfig -> X ()
changeProjectDirPrompt = projectPrompt [ DirMode
, SwitchMode
, ShiftMode
, RenameMode
]
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Prompt for a project name. -- | Prompt for a project name.
projectPrompt :: [ProjectMode] -> XPConfig -> X () projectPrompt :: XPConfig -> (ProjectTable -> ProjectName -> X ()) -> X ()
projectPrompt submodes c = do projectPrompt c f = do
ws <- map W.tag `fmap` gets (W.workspaces . windowset) ws <- map W.tag `fmap` gets (W.workspaces . windowset)
ps <- XS.gets projects ps <- XS.gets projects
let names = sort (Map.keys ps `union` ws) let names = sort (Map.keys ps `union` ws)
modes = map (\m -> XPT $ ProjectPrompt m names) submodes label = "Switch or Create Project: "
mkXPromptWithModes modes c mkXPrompt (Wor label) c (mkComplFunFromList' names) (f ps)
--------------------------------------------------------------------------------
-- | Rename the current project.
renameProjectPrompt :: XPConfig -> X ()
renameProjectPrompt c = mkXPrompt (Wor "New Project Name: ") c (return . (:[])) go
where
go :: String -> X ()
go name = do
p <- currentProject
ps <- XS.gets projects
renameWorkspaceByName name
let p' = fromMaybe (p { projectName = name }) $ Map.lookup name ps
ps' = Map.insert name p' $ Map.delete (projectName p) ps
XS.modify $ \s -> s {projects = ps'}
activateProject p'
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Activate a project by updating the working directory and -- | Activate a project by updating the working directory and

View File

@@ -75,23 +75,17 @@ submapDefaultWithKey defAction keys = do
XConf { theRoot = root, display = d } <- ask XConf { theRoot = root, display = d } <- ask
io $ grabKeyboard d root False grabModeAsync grabModeAsync currentTime io $ grabKeyboard d root False grabModeAsync grabModeAsync currentTime
io $ grabPointer d root False buttonPressMask grabModeAsync grabModeAsync
none none currentTime
(m, s) <- io $ allocaXEvent $ \p -> fix $ \nextkey -> do (m, s) <- io $ allocaXEvent $ \p -> fix $ \nextkey -> do
maskEvent d (keyPressMask .|. buttonPressMask) p maskEvent d keyPressMask p
ev <- getEvent p KeyEvent { ev_keycode = code, ev_state = m } <- getEvent p
case ev of keysym <- keycodeToKeysym d code 0
KeyEvent { ev_keycode = code, ev_state = m } -> do if isModifierKey keysym
keysym <- keycodeToKeysym d code 0 then nextkey
if isModifierKey keysym else return (m, keysym)
then nextkey
else return (m, keysym)
_ -> return (0, 0)
-- Remove num lock mask and Xkb group state bits -- Remove num lock mask and Xkb group state bits
m' <- cleanMask $ m .&. ((1 `shiftL` 12) - 1) m' <- cleanMask $ m .&. ((1 `shiftL` 12) - 1)
io $ ungrabPointer d currentTime
io $ ungrabKeyboard d currentTime io $ ungrabKeyboard d currentTime
fromMaybe (defAction (m', s)) (M.lookup (m', s) keys) fromMaybe (defAction (m', s)) (M.lookup (m', s) keys)

View File

@@ -1,8 +1,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonadContrib.UpdatePointer -- Module : XMonadContrib.UpdatePointer
-- Copyright : (c) Robert Marlow <robreim@bobturf.org>, 2015 Evgeny Kurnevsky -- Copyright : (c) Robert Marlow <robreim@bobturf.org>
-- License : BSD3-style (see LICENSE) -- License : BSD3-style (see LICENSE)
-- --
-- Maintainer : Robert Marlow <robreim@bobturf.org> -- Maintainer : Robert Marlow <robreim@bobturf.org>
@@ -29,7 +28,6 @@ import Control.Arrow
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
import Control.Exception
-- $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@:
@@ -65,13 +63,9 @@ updatePointer :: (Rational, Rational) -> (Rational, Rational) -> X ()
updatePointer refPos ratio = do updatePointer refPos ratio = do
ws <- gets windowset ws <- gets windowset
dpy <- asks display dpy <- asks display
let defaultRect = screenRect $ screenDetail $ current ws
rect <- case peek ws of rect <- case peek ws of
Nothing -> return defaultRect Nothing -> return $ (screenRect . screenDetail .current) ws
Just w -> do tryAttributes <- io $ try $ getWindowAttributes dpy w Just w -> windowAttributesToRectangle `fmap` io (getWindowAttributes dpy w)
return $ case tryAttributes of
Left (_ :: SomeException) -> defaultRect
Right attributes -> windowAttributesToRectangle attributes
root <- asks theRoot root <- asks theRoot
mouseIsMoving <- asks mouseFocused mouseIsMoving <- asks mouseFocused
(_sameRoot,_,currentWindow,rootX,rootY,_,_,_) <- io $ queryPointer dpy root (_sameRoot,_,currentWindow,rootX,rootY,_,_,_) <- io $ queryPointer dpy root

View File

@@ -38,14 +38,13 @@ module XMonad.Actions.WindowGo (
import Control.Monad import Control.Monad
import Data.Char (toLower) import Data.Char (toLower)
import qualified Data.List as L (nub,sortBy)
import Data.Monoid import Data.Monoid
import XMonad (Query(), X(), ManageHook, WindowSet, withWindowSet, runQuery, liftIO, ask) import XMonad (Query(), X(), ManageHook, WindowSet, withWindowSet, runQuery, liftIO, ask)
import Graphics.X11 (Window) import Graphics.X11 (Window)
import XMonad.ManageHook import XMonad.ManageHook
import XMonad.Operations (windows) import XMonad.Operations (windows)
import XMonad.Prompt.Shell (getBrowser, getEditor) import XMonad.Prompt.Shell (getBrowser, getEditor)
import qualified XMonad.StackSet as W (peek, swapMaster, focusWindow, workspaces, StackSet, Workspace, integrate', tag, stack) import qualified XMonad.StackSet as W (allWindows, peek, swapMaster, focusWindow)
import XMonad.Util.Run (safeSpawnProg) import XMonad.Util.Run (safeSpawnProg)
{- $usage {- $usage
@@ -67,20 +66,12 @@ appropriate one, or cover your bases by using instead something like:
For detailed instructions on editing your key bindings, see For detailed instructions on editing your key bindings, see
"XMonad.Doc.Extending#Editing_key_bindings". -} "XMonad.Doc.Extending#Editing_key_bindings". -}
-- | Get the list of workspaces sorted by their tag
workspacesSorted :: Ord i => W.StackSet i l a s sd -> [W.Workspace i l a]
workspacesSorted s = L.sortBy (\u t -> W.tag u `compare` W.tag t) $ W.workspaces s
-- | Get a list of all windows in the 'StackSet' with an absolute ordering of workspaces
allWindowsSorted :: Ord i => Eq a => W.StackSet i l a s sd -> [a]
allWindowsSorted = L.nub . concatMap (W.integrate' . W.stack) . workspacesSorted
-- | If windows that satisfy the query exist, apply the supplied -- | If windows that satisfy the query exist, apply the supplied
-- function to them, otherwise run the action given as -- function to them, otherwise run the action given as
-- second parameter. -- second parameter.
ifWindows :: Query Bool -> ([Window] -> X ()) -> X () -> X () ifWindows :: Query Bool -> ([Window] -> X ()) -> X () -> X ()
ifWindows qry f el = withWindowSet $ \wins -> do ifWindows qry f el = withWindowSet $ \wins -> do
matches <- filterM (runQuery qry) $ allWindowsSorted wins matches <- filterM (runQuery qry) $ W.allWindows wins
case matches of case matches of
[] -> el [] -> el
ws -> f ws ws -> f ws

View File

@@ -58,8 +58,8 @@ dynamicPropertyChange prop hook PropertyEvent { ev_window = w, ev_atom = a, ev_p
when (ps == propertyNewValue && a == pa) $ do when (ps == propertyNewValue && a == pa) $ do
g <- appEndo <$> userCodeDef (Endo id) (runQuery hook w) g <- appEndo <$> userCodeDef (Endo id) (runQuery hook w)
windows g windows g
return mempty -- so anything else also processes it return (All False) -- so anything else also processes it
dynamicPropertyChange _ _ _ = return mempty dynamicPropertyChange _ _ _ = return (All False)
-- | A shorthand for the most common case, dynamic titles -- | A shorthand for the most common case, dynamic titles
dynamicTitle :: ManageHook -> Event -> X All dynamicTitle :: ManageHook -> Event -> X All

View File

@@ -140,11 +140,12 @@ docksEventHook (MapNotifyEvent { ev_window = w }) = do
return (All True) return (All True)
docksEventHook (PropertyEvent { ev_window = w docksEventHook (PropertyEvent { ev_window = w
, ev_atom = a }) = do , ev_atom = a }) = do
nws <- getAtom "_NET_WM_STRUT" whenX (runQuery checkDock w) $ do
nwsp <- getAtom "_NET_WM_STRUT_PARTIAL" nws <- getAtom "_NET_WM_STRUT"
when (a == nws || a == nwsp) $ do nwsp <- getAtom "_NET_WM_STRUT_PARTIAL"
strut <- getStrut w when (a == nws || a == nwsp) $ do
whenX (updateStrutCache w strut) refreshDocks strut <- getStrut w
whenX (updateStrutCache w strut) refreshDocks
return (All True) return (All True)
docksEventHook (DestroyWindowEvent {ev_window = w}) = do docksEventHook (DestroyWindowEvent {ev_window = w}) = do
whenX (deleteFromStructCache w) refreshDocks whenX (deleteFromStructCache w) refreshDocks
@@ -245,9 +246,7 @@ instance Message SetStruts
instance LayoutModifier AvoidStruts a where instance LayoutModifier AvoidStruts a where
modifyLayout (AvoidStruts ss) w r = do modifyLayout (AvoidStruts ss) w r = do
srect <- fmap ($ r) (calcGap ss) srect <- fmap ($ r) (calcGap ss)
-- Ensure _NET_WORKAREA is not set. setWorkarea srect
-- See: https://github.com/xmonad/xmonad-contrib/pull/79
rmWorkarea
runLayout w srect runLayout w srect
pureMess as@(AvoidStruts ss) m pureMess as@(AvoidStruts ss) m
@@ -263,11 +262,13 @@ instance LayoutModifier AvoidStruts a where
toggleOne x xs | x `S.member` xs = S.delete x xs toggleOne x xs | x `S.member` xs = S.delete x xs
| otherwise = x `S.insert` xs | otherwise = x `S.insert` xs
rmWorkarea :: X () setWorkarea :: Rectangle -> X ()
rmWorkarea = withDisplay $ \dpy -> do setWorkarea (Rectangle x y w h) = withDisplay $ \dpy -> do
a <- getAtom "_NET_WORKAREA" a <- getAtom "_NET_WORKAREA"
c <- getAtom "CARDINAL"
r <- asks theRoot r <- asks theRoot
io (deleteProperty dpy r a) io $ changeProperty32 dpy r a c propModeReplace [fi x, fi y, fi w, fi h]
-- | (Direction, height\/width, initial pixel, final pixel). -- | (Direction, height\/width, initial pixel, final pixel).

View File

@@ -339,7 +339,7 @@ getNetWMState :: Window -> X [CLong]
getNetWMState w = do getNetWMState w = do
a_wmstate <- getAtom "_NET_WM_STATE" a_wmstate <- getAtom "_NET_WM_STATE"
fromMaybe [] `fmap` getProp32 a_wmstate w fromMaybe [] `fmap` getProp32 a_wmstate w
-- The Non-ICCCM Manifesto: -- The Non-ICCCM Manifesto:
-- Note: Some non-standard choices have been made in this implementation to -- Note: Some non-standard choices have been made in this implementation to
@@ -497,14 +497,14 @@ data BorderUrgencyHook = BorderUrgencyHook { urgencyBorderColor :: !String }
instance UrgencyHook BorderUrgencyHook where instance UrgencyHook BorderUrgencyHook where
urgencyHook BorderUrgencyHook { urgencyBorderColor = cs } w = urgencyHook BorderUrgencyHook { urgencyBorderColor = cs } w =
withDisplay $ \dpy -> do withDisplay $ \dpy -> io $ do
c' <- io (initColor dpy cs) c' <- initColor dpy cs
case c' of case c' of
Just c -> setWindowBorderWithFallback dpy w cs c Just c -> setWindowBorder dpy w c
_ -> io $ hPutStrLn stderr $ concat ["Warning: bad urgentBorderColor " _ -> hPutStrLn stderr $ concat ["Warning: bad urgentBorderColor "
,show cs ,show cs
," in BorderUrgencyHook" ," in BorderUrgencyHook"
] ]
-- | Flashes when a window requests your attention and you can't see it. -- | Flashes when a window requests your attention and you can't see it.
-- Defaults to a duration of five seconds, and no extra args to dzen. -- Defaults to a duration of five seconds, and no extra args to dzen.
@@ -543,3 +543,4 @@ filterUrgencyHook skips w = do
Just tag -> when (tag `elem` skips) Just tag -> when (tag `elem` skips)
$ adjustUrgents (delete w) $ adjustUrgents (delete w)
_ -> return () _ -> return ()

View File

@@ -1,5 +1,5 @@
{-# OPTIONS_GHC -fno-warn-missing-signatures #-} {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
{-# LANGUAGE MultiParamTypeClasses, Rank2Types #-} {-# LANGUAGE MultiParamTypeClasses, Rank2Types, ImpredicativeTypes #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@@ -178,7 +178,7 @@ focusFloatDown = focusHelper id id
-- ** Groups-specific actions -- ** Groups-specific actions
wrap :: G.ModifySpec -> X () wrap :: G.ModifySpec -> X ()
wrap x = sendMessage (G.Modify x) wrap = sendMessage . G.Modify
-- | Swap the focused group with the previous one -- | Swap the focused group with the previous one
swapGroupUp :: X () swapGroupUp :: X ()

View File

@@ -110,7 +110,7 @@ popNewestHiddenWindow = sendMessage PopNewestHiddenWindow
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
hideWindowMsg :: HiddenWindows a -> Window -> X (Maybe (HiddenWindows a)) hideWindowMsg :: HiddenWindows a -> Window -> X (Maybe (HiddenWindows a))
hideWindowMsg (HiddenWindows hidden) win = do hideWindowMsg (HiddenWindows hidden) win = do
modify (\s -> s { windowset = W.delete' win $ windowset s }) windows (W.delete' win)
return . Just . HiddenWindows $ hidden ++ [win] return . Just . HiddenWindows $ hidden ++ [win]
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@@ -130,5 +130,4 @@ popOldestMsg (HiddenWindows (win:rest)) = do
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
restoreWindow :: Window -> X () restoreWindow :: Window -> X ()
restoreWindow win = restoreWindow = windows . W.insertUp
modify (\s -> s { windowset = W.insertUp win $ windowset s })

View File

@@ -195,9 +195,7 @@ navigable :: Direction2D -> Point -> [(Window, Rectangle)] -> [(Window, Rectangl
navigable d pt = sortby d . filter (inr d pt . snd) navigable d pt = sortby d . filter (inr d pt . snd)
sc :: Pixel -> Window -> X () sc :: Pixel -> Window -> X ()
sc c win = withDisplay $ \dpy -> do sc c win = withDisplay $ \dpy -> io $ setWindowBorder dpy win c
colorName <- io (pixelToString dpy c)
setWindowBorderWithFallback dpy win colorName c
center :: Rectangle -> Point center :: Rectangle -> Point
center (Rectangle x y w h) = P (fromIntegral x + fromIntegral w/2) (fromIntegral y + fromIntegral h/2) center (Rectangle x y w h) = P (fromIntegral x + fromIntegral w/2) (fromIntegral y + fromIntegral h/2)

View File

@@ -91,6 +91,7 @@ import Data.List
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Set (fromList, toList) import Data.Set (fromList, toList)
import System.Directory (getAppUserDataDirectory)
import System.IO import System.IO
import System.Posix.Files import System.Posix.Files
@@ -520,59 +521,24 @@ completionHandle c ks@(sym,_) (KeyEvent { ev_event_type = t, ev_state = m }) = d
alwaysHlight <- gets $ alwaysHighlight . config alwaysHlight <- gets $ alwaysHighlight . config
mCleaned <- cleanMask m mCleaned <- cleanMask m
case () of case () of
() | t == keyPress && (mCleaned,sym) == complKey -> do () | t == keyPress && (mCleaned,sym) == complKey ->
st <- get do
st <- get
let updateWins l = redrawWindows l >> eventLoop (completionHandle l) let updateState l = case alwaysHlight of
updateState l = case alwaysHlight of -- modify the buffer's value
False -> simpleComplete l st False -> let newCommand = nextCompletion (currentXPMode st) (command st) l
True | Just (command st) /= highlightedCompl st -> alwaysHighlightCurrent st in modify $ \s -> setCommand newCommand $ s { offset = length newCommand, highlightedCompl = Just newCommand}
| otherwise -> alwaysHighlightNext l st --TODO: Scroll or paginate results
True -> let complIndex' = nextComplIndex st (length l)
case c of highlightedCompl' = highlightedItem st { complIndex = complIndex'} c
[] -> updateWindows >> eventLoop handle in modify $ \s -> setHighlightedCompl highlightedCompl' $ s { complIndex = complIndex' }
[x] -> updateState [x] >> getCompletions >>= updateWins updateWins l = redrawWindows l >> eventLoop (completionHandle l)
l -> updateState l >> updateWins l case c of
[] -> updateWindows >> eventLoop handle
[x] -> updateState [x] >> getCompletions >>= updateWins
l -> updateState l >> updateWins l
| t == keyRelease && (mCleaned,sym) == complKey -> eventLoop (completionHandle c) | t == keyRelease && (mCleaned,sym) == complKey -> eventLoop (completionHandle c)
| otherwise -> keyPressHandle mCleaned ks -- some other key, handle it normally | otherwise -> keyPressHandle mCleaned ks -- some other key, handle it normally
where
-- When alwaysHighlight is off, just complete based on what the
-- user has typed so far.
simpleComplete :: [String] -> XPState -> XP ()
simpleComplete l st = do
let newCommand = nextCompletion (currentXPMode st) (command st) l
modify $ \s -> setCommand newCommand $
s { offset = length newCommand
, highlightedCompl = Just newCommand
}
-- If alwaysHighlight is on, and this is the first use of the
-- completion key, update the buffer so that it contains the
-- current completion item.
alwaysHighlightCurrent :: XPState -> XP ()
alwaysHighlightCurrent st = do
let newCommand = fromMaybe (command st) $ highlightedItem st c
modify $ \s -> setCommand newCommand $
setHighlightedCompl (Just newCommand) $
s { offset = length newCommand
}
-- If alwaysHighlight is on, and the user wants the next
-- completion, move to the next completion item and update the
-- buffer to reflect that.
--
--TODO: Scroll or paginate results
alwaysHighlightNext :: [String] -> XPState -> XP ()
alwaysHighlightNext l st = do
let complIndex' = nextComplIndex st (length l)
highlightedCompl' = highlightedItem st { complIndex = complIndex'} c
newCommand = fromMaybe (command st) $ highlightedCompl'
modify $ \s -> setHighlightedCompl highlightedCompl' $
setCommand newCommand $
s { complIndex = complIndex'
, offset = length newCommand
}
-- some other event: go back to main loop -- some other event: go back to main loop
completionHandle _ k e = handle k e completionHandle _ k e = handle k e
@@ -1098,7 +1064,7 @@ emptyHistory :: History
emptyHistory = M.empty emptyHistory = M.empty
getHistoryFile :: IO FilePath getHistoryFile :: IO FilePath
getHistoryFile = fmap (++ "/prompt-history") getXMonadCacheDir getHistoryFile = fmap (++ "/history") $ getAppUserDataDirectory "xmonad"
readHistory :: IO History readHistory :: IO History
readHistory = readHist `E.catch` \(SomeException _) -> return emptyHistory readHistory = readHist `E.catch` \(SomeException _) -> return emptyHistory
@@ -1204,7 +1170,7 @@ breakAtSpace s
-- | 'historyCompletion' provides a canned completion function much like -- | 'historyCompletion' provides a canned completion function much like
-- 'getShellCompl'; you pass it to mkXPrompt, and it will make completions work -- 'getShellCompl'; you pass it to mkXPrompt, and it will make completions work
-- from the query history stored in the XMonad cache directory. -- from the query history stored in ~\/.xmonad\/history.
historyCompletion :: ComplFunction historyCompletion :: ComplFunction
historyCompletion = historyCompletionP (const True) historyCompletion = historyCompletionP (const True)

View File

@@ -16,8 +16,7 @@ module XMonad.Prompt.Directory (
-- * Usage -- * Usage
-- $usage -- $usage
directoryPrompt, directoryPrompt,
directoryMultipleModes, Dir,
Dir
) where ) where
import XMonad import XMonad
@@ -27,23 +26,13 @@ import XMonad.Util.Run ( runProcessWithInput )
-- $usage -- $usage
-- For an example usage see "XMonad.Layout.WorkspaceDir" -- For an example usage see "XMonad.Layout.WorkspaceDir"
data Dir = Dir String (String -> X ()) data Dir = Dir String
instance XPrompt Dir where instance XPrompt Dir where
showXPrompt (Dir x _) = x showXPrompt (Dir x) = x
completionFunction _ = getDirCompl
modeAction (Dir _ f) buf auto =
let dir = if null auto then buf else auto
in f dir
directoryPrompt :: XPConfig -> String -> (String -> X ()) -> X () directoryPrompt :: XPConfig -> String -> (String -> X ()) -> X ()
directoryPrompt c prom f = mkXPrompt (Dir prom f) c getDirCompl f directoryPrompt c prom = mkXPrompt (Dir prom) c getDirCompl
-- | A @XPType@ entry suitable for using with @mkXPromptWithModes@.
directoryMultipleModes :: String -- ^ Prompt.
-> (String -> X ()) -- ^ Action.
-> XPType
directoryMultipleModes p f = XPT (Dir p f)
getDirCompl :: String -> IO [String] getDirCompl :: String -> IO [String]
getDirCompl s = (filter notboring . lines) `fmap` getDirCompl s = (filter notboring . lines) `fmap`

View File

@@ -4,9 +4,11 @@
-- Copyright : (c) 2007 Valery V. Vorotyntsev -- Copyright : (c) 2007 Valery V. Vorotyntsev
-- License : BSD3-style (see LICENSE) -- License : BSD3-style (see LICENSE)
-- --
-- Maintainer : Valery V. Vorotynsev <valery.vv@gmail.com>
--
-- Customized key bindings. -- Customized key bindings.
-- --
-- See also "XMonad.Util.EZConfig" in xmonad-contrib. -- (See also "XMonad.Util.EZConfig" in xmonad-contrib.)
-------------------------------------------------------------------- --------------------------------------------------------------------
module XMonad.Util.CustomKeys ( module XMonad.Util.CustomKeys (
@@ -23,30 +25,38 @@ import qualified Data.Map as M
-- $usage -- $usage
-- --
-- In @~\/.xmonad\/xmonad.hs@ add: -- 1. In @~\/.xmonad\/xmonad.hs@ add:
-- --
-- > import XMonad.Util.CustomKeys -- > import XMonad.Util.CustomKeys
-- --
-- Set key bindings with 'customKeys': -- 2. Set key bindings with 'customKeys':
-- --
-- > main = xmonad def { keys = customKeys delkeys inskeys } -- > main = xmonad def { keys = customKeys delkeys inskeys }
-- > where -- > where
-- > delkeys :: XConfig l -> [(KeyMask, KeySym)] -- > delkeys :: XConfig l -> [(KeyMask, KeySym)]
-- > delkeys XConfig {modMask = modm} = -- > delkeys XConfig {modMask = modm} =
-- > [ (modm .|. shiftMask, xK_Return) -- > terminal -- > -- we're preferring Futurama to Xinerama here
-- > , (modm .|. shiftMask, xK_c) -- > close the focused window -- > [ (modm .|. m, k) | (m, k) <- zip [0, shiftMask] [xK_w, xK_e, xK_r] ]
-- > ]
-- > ++
-- > [ (modm .|. m, k) | m <- [0, shiftMask], k <- [xK_w, xK_e, xK_r] ]
-- > -- >
-- > inskeys :: XConfig l -> [((KeyMask, KeySym), X ())] -- > inskeys :: XConfig l -> [((KeyMask, KeySym), X ())]
-- > inskeys conf@(XConfig {modMask = modm}) = -- > inskeys conf@(XConfig {modMask = modm}) =
-- > [ ((mod1Mask, xK_F2 ), spawn $ terminal conf) -- mod1-f2 %! Run a terminal emulator -- > [ ((mod1Mask, xK_F2 ), spawn $ terminal conf)
-- > , ((modm, xK_Delete), kill) -- %! Close the focused window
-- > , ((modm .|. controlMask, xK_F11 ), spawn "xscreensaver-command -lock") -- > , ((modm .|. controlMask, xK_F11 ), spawn "xscreensaver-command -lock")
-- > , ((mod1Mask, xK_Down), spawn "amixer set Master 1-") -- > , ((mod1Mask, xK_Down), spawn "amixer set Master 1-")
-- > , ((mod1Mask, xK_Up ), spawn "amixer set Master 1+") -- > , ((mod1Mask, xK_Up ), spawn "amixer set Master 1+")
-- > ] -- > ]
--
-- 0 (/hidden feature/). You can always replace bindings map
-- entirely. No need to import "CustomKeys" this time:
--
-- > import XMonad
-- > import System.Exit
-- > import qualified Data.Map as M
-- >
-- > main = xmonad def {
-- > keys = \_ -> M.fromList [
-- > -- Let me out of here! I want my KDE back! Help! Help!
-- > ( (0, xK_Escape), io (exitWith ExitSuccess) ) ] }
-- | Customize 'XMonad.Config.def' -- delete needless -- | Customize 'XMonad.Config.def' -- delete needless
-- shortcuts and insert those you will use. -- shortcuts and insert those you will use.

View File

@@ -29,7 +29,6 @@ module XMonad.Util.Font
, textExtentsXMF , textExtentsXMF
, printStringXMF , printStringXMF
, stringToPixel , stringToPixel
, pixelToString
, fi , fi
) where ) where
@@ -38,8 +37,6 @@ import Foreign
import Control.Applicative import Control.Applicative
import Control.Exception as E import Control.Exception as E
import Data.Maybe import Data.Maybe
import Data.Bits (shiftR)
import Text.Printf (printf)
#ifdef XFT #ifdef XFT
import Data.List import Data.List
@@ -64,19 +61,6 @@ stringToPixel d s = fromMaybe fallBack <$> io getIt
where getIt = initColor d s where getIt = initColor d s
fallBack = blackPixel d (defaultScreen d) fallBack = blackPixel d (defaultScreen d)
-- | Convert a @Pixel@ into a @String@.
pixelToString :: (MonadIO m) => Display -> Pixel -> m String
pixelToString d p = do
let cm = defaultColormap d (defaultScreen d)
(Color _ r g b _) <- io (queryColor d cm $ Color p 0 0 0 0)
return ("#" ++ hex r ++ hex g ++ hex b)
where
-- NOTE: The @Color@ type has 16-bit values for red, green, and
-- blue, even though the actual type in X is only 8 bits wide. It
-- seems that the upper and lower 8-bit sections of the @Word16@
-- values are the same. So, we just discard the lower 8 bits.
hex = printf "%02x" . (`shiftR` 8)
econst :: a -> IOException -> a econst :: a -> IOException -> a
econst = const econst = const

View File

@@ -28,7 +28,6 @@ module XMonad.Util.XUtils
, paintAndWrite , paintAndWrite
, paintTextAndIcons , paintTextAndIcons
, stringToPixel , stringToPixel
, pixelToString
, fi , fi
) where ) where
@@ -209,3 +208,4 @@ mkWindow d s rw x y w h p o = do
set_background_pixel attributes p set_background_pixel attributes p
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

View File

@@ -1,3 +0,0 @@
packages: ./
../xmonad/
../x11/

View File

@@ -1,9 +0,0 @@
resolver: lts-7.19
packages:
- ./
- ../xmonad
extra-deps:
- X11-1.8
- X11-xft-0.3.1

View File

@@ -1,5 +1,5 @@
name: xmonad-contrib name: xmonad-contrib
version: 0.13 version: 0.12
homepage: http://xmonad.org/ homepage: http://xmonad.org/
synopsis: Third party extensions for xmonad synopsis: Third party extensions for xmonad
description: description:
@@ -35,7 +35,10 @@ cabal-version: >= 1.6
build-type: Simple build-type: Simple
bug-reports: https://github.com/xmonad/xmonad-contrib/issues bug-reports: https://github.com/xmonad/xmonad-contrib/issues
tested-with: GHC==7.6.3, GHC==7.8.4, GHC==7.10.3, GHC==8.0.1 tested-with:
GHC==7.6.3,
GHC==7.8.4,
GHC==7.10.2
source-repository head source-repository head
type: git type: git
@@ -63,8 +66,8 @@ library
random, random,
mtl >= 1 && < 3, mtl >= 1 && < 3,
unix, unix,
X11>=1.6.1 && < 1.9, X11>=1.7 && < 1.8,
xmonad>=0.13 && < 0.14, xmonad>=0.12 && < 0.13,
utf8-string utf8-string
if flag(use_xft) if flag(use_xft)