Compare commits

..

28 Commits

Author SHA1 Message Date
b9e180f910 Bump base version 2020-03-02 10:17:21 +02:00
d88a4aa7a0 Use the swap screen from linenavigation2d 2020-02-12 13:45:08 +02:00
93e4e9f930 Comment out shifting windows
I'm pretty sure I've never used these mappings except by accident, now
then knowing how to undo it. I'm commenting them out for now to see if I
end up missing them for whatever reason
2020-02-12 13:27:22 +02:00
30d3f4ea2c Navigate to different screens better 2020-02-12 13:25:26 +02:00
e80b309569 Get rid of ideHooks 2020-02-03 09:58:24 +02:00
d15ae94ba5 Update tests 2020-02-03 09:54:07 +02:00
a69b41e652 Disable focus follows mouse with the reasoning 2020-02-03 09:48:52 +02:00
321ed016a0 Go back to google 2020-02-03 09:48:41 +02:00
6e2a821531 Run shell commands 2019-11-19 12:57:05 +02:00
059635057b searx 2019-10-04 09:28:43 +03:00
8e1f9908c9 Focus follows mouse 2019-08-23 13:05:58 +03:00
c6406cc2dd More correct way of locking the screen 2019-08-09 16:31:38 +03:00
2f2593eabc Zoom button 2019-06-03 15:27:18 +03:00
892c6c3b72 Reduce clip time 2019-06-03 09:59:56 +03:00
cb8917f6cf No need for 18.09 anymore 2019-05-23 12:26:31 +03:00
6c9bc7399a Dev tooling 2019-05-23 12:22:14 +03:00
f7b1d89755 asd 2019-05-23 12:21:57 +03:00
1639feed4c Don't hide unselected topic 2019-05-23 11:53:37 +03:00
3789e23cb9 Remove unused key binding 2019-05-23 11:45:16 +03:00
7c27571ca7 Configurable music toggle 2019-05-13 08:48:16 +03:00
dbd3024d98 Fixup 2019-04-08 12:11:19 +03:00
9b16e074ef Use the provided browser for searching 2019-04-08 12:10:55 +03:00
bd4f5d7e30 Search endpoints 2019-04-04 08:11:50 +03:00
41806dca67 Remove the irc layout, don't like it 2019-04-02 16:08:05 +03:00
2ad7555b2d Formatting changes 2019-03-21 23:29:39 +02:00
d5c86cddee Enable unstable tests 2019-03-21 22:27:26 +02:00
5041d5bf99 hlint rules 2019-03-21 22:26:47 +02:00
c3d5eaed3e Bump base 2019-03-21 22:19:57 +02:00
9 changed files with 129 additions and 79 deletions

View File

@ -10,10 +10,10 @@ before_script:
matrix:
include:
- env:
- NIXPKGS=https://github.com/NixOS/nixpkgs-channels/archive/nixos-18.09.tar.gz
- VERSION=19.09
- env:
- NIXPKGS=https://github.com/NixOS/nixpkgs-channels/archive/nixos-19.03.tar.gz
- VERSION=unstable
script:
# - nix run nixpkgs.haskellPackages.hlint -c hlint src
- nix build -I nixpkgs=$NIXPKGS -f ./release.nix xmonad-masser
- nix run nixpkgs.haskellPackages.hlint -c hlint src
- nix build -I nixpkgs=https://github.com/NixOS/nixpkgs-channels/archive/nixos-$VERSION.tar.gz -f ./release.nix xmonad-masser

View File

@ -1,3 +1,13 @@
{ haskellPackages }:
{ lib, haskellPackages }:
haskellPackages.callCabal2nix "xmonad-masser" ./. {}
let
filtered = src: lib.sourceByRegex src [
"^src.*"
"Setup.hs"
".*cabal"
"LICENSE"
];
in
haskellPackages.callCabal2nix "xmonad-masser" (filtered ./.) {}

View File

@ -1,13 +1,16 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module XMonad.Config.MasseR where
import XMonad.Password
import XMonad.CustomPrompt
import XMonad.TopicSpace
import Control.Lens ((^.))
import Data.Generics.Product (field)
import qualified Data.List as List
import XMonad
import XMonad.Actions.CycleWS (swapNextScreen)
-- import XMonad.Actions.CycleWS (swapNextScreen)
import XMonad.Actions.Search
import XMonad.Hooks.EwmhDesktops (ewmh, ewmhDesktopsStartup)
import XMonad.Hooks.SetWMName (setWMName)
@ -18,10 +21,9 @@ import XMonad.Layout.BinarySpacePartition (emptyBSP)
import XMonad.Layout.Decoration (Decoration,
DefaultShrinker)
import XMonad.Layout.DwmStyle
import XMonad.Layout.HintedGrid
import XMonad.Layout.LayoutModifier (ModifiedLayout)
import XMonad.Layout.Master
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Layout.NoBorders (noBorders, smartBorders)
import XMonad.Layout.PerWorkspace (onWorkspace)
import XMonad.Layout.Renamed
import XMonad.Layout.Simplest (Simplest)
@ -29,12 +31,16 @@ import XMonad.Layout.Spiral
import XMonad.Layout.Tabbed (TabbedDecoration,
Theme (..), shrinkText,
tabbed)
import XMonad.Layout.ToggleLayouts (ToggleLayout (..))
import XMonad.Layout.ToggleLayouts (ToggleLayout (..),
toggleLayouts)
import XMonad.Password
import XMonad.Prompt.RunOrRaise (runOrRaisePrompt)
import XMonad.Prompt.Shell (shellPrompt)
import qualified XMonad.StackSet as W
import XMonad.TopicSpace
import XMonad.Util.EZConfig
import XMonad.XMobar (zenburnPP)
import XMonad.XMobar (zenburnPP)
import Data.Monoid (Endo, (<>))
@ -43,6 +49,7 @@ import XMonad.Util.SpawnOnce
import System.IO (hClose, hPutStr)
import XMonad.Actions.Navigation2D
import XMonad.Actions.UpdatePointer (updatePointer)
import XMonad.Util.NamedActions
import XMonad.Util.Run (spawnPipe)
@ -55,9 +62,9 @@ import XMonad.Hooks.DynamicLog (statusBar)
import qualified Data.Set as S
spotify :: XConfig l -> NamedAction
spotify conf = submapName . mkNamedKeymap conf $
[ ("M-p", addName "Play" $ spawn "sp play") ]
spotify :: ExtraConfig -> XConfig l -> NamedAction
spotify extraConf conf = submapName . mkNamedKeymap conf $
[ ("M-p", addName "Play" $ spawn (musicToggle . applications $ extraConf)) ]
scratchpads :: [NamedScratchpad]
scratchpads = [
@ -71,18 +78,22 @@ scratchSubmaps conf = submapName . mkNamedKeymap conf $ [
]
-- Search engines inside submaps
searchSubmaps :: XConfig l -> NamedAction
searchSubmaps conf =
let mkBrowser = promptSearchBrowser def "qutebrowser"
_googleP = addName "Search google" $ mkBrowser google
ddgP = addName "Search duckduckgo" $ mkBrowser (searchEngine "duckduckgo" "http://duckduckgo.com/?q=")
searchSubmaps :: ExtraConfig -> XConfig l -> NamedAction
searchSubmaps extraConfig conf =
let mkBrowser = promptSearchBrowser def (extraConfig ^. field @"applications" . field @"browser")
googleP = addName "Search google" $ mkBrowser google
extras = [(key, addName name $ mkBrowser (searchEngine name url)) | Search{..} <- searchEndpoints extraConfig]
in submapName . mkNamedKeymap conf $
[ ("d", ddgP) -- Training to use ddg again
, ("g", ddgP) -- training to use ddg again
]
("g", googleP) : extras
myNav2d :: Navigation2DConfig
myNav2d = def { defaultTiledNavigation = lineNavigation }
myNav2d =
def { defaultTiledNavigation = nav
, screenNavigation = nav
}
where
nav = hybridOf lineNavigation sideNavigation
showKeybindings :: [((KeyMask, KeySym), NamedAction)] -> NamedAction
showKeybindings x = addName "Show keybindings" $ io $ do
@ -117,14 +128,10 @@ myManageHook = composeAll $ concat [
, documentHooks
, floatHooks
, debuggerHooks
, ideHooks
, flowHook
]
where
classHook y = map (\x -> className =? x --> y)
ideHooks = classHook (doShift "eclipse") [
"Anypoint Studio"
]
webHooks = classHook (doShift "web") [
"Firefox"
, "qutebrowser"
@ -144,7 +151,7 @@ myManageHook = composeAll $ concat [
"libreoffice"
, "libreoffice-calc"
, "Assistant"
, "Bouml"
, "Bouml" -- Oh wow, didn't even remember this existed
]
floatHooks = classHook doFloat [
"SMplayer"
@ -152,11 +159,11 @@ myManageHook = composeAll $ concat [
, "MPlayer"
, "Kaffeine"
, "Xmessage"
, "Wfica_Seamless"
, "Wfica_Seamless" -- I think this is citrix
, "mpv"
]
debuggerHooks = classHook (doShift "debugger") [
"JSwat Debugger",
"JSwat Debugger", -- Haven't used this in years. A good thing?
"DBeaver"
]
dynamicsHook = [title =~? "Dynamics" --> doShift "dynamics"]
@ -172,38 +179,40 @@ myKeys extraConfig conf =
, ("<XF86AudioLowerVolume>", addName "Decrease volume" $ spawn "amixer set Master 2%-")
, ("M-<plus>", addName "Increase volume" $ spawn "amixer set Master 2+")
, ("M-<minus>", addName "Decrease volume" $ spawn "amixer set Master 2-")
-- , ("<XF86AudioPlay>", addName "Play/pause spotify" $ spawn "/home/masse/.local/bin/sp play")
, ("<XF86AudioPlay>", addName "Play/pause mopidy" $ spawn "mpc toggle")
, ("M-m", spotify conf)
, ("M-S-<Space>", addName "Swap screens" swapNextScreen)
, ("<XF86AudioPlay>", addName "Play/pause music" $ spawn "mpc toggle")
, ("M-m", spotify extraConfig conf)
-- , ("M-S-<Space>", addName "Swap screens" swapNextScreen)
, ("M-<Backspace>", addName "Kill window" kill)
-- scrot requires `unGrab`
, ("M-<Print>", addName "Take screenshot" $ spawn (screenshot . applications $ extraConfig))] ^++^
subKeys "Launchers" [ ("M-S-y", addName "Open youtube" $ spawn "mpv $(clip -o)")
, ("M-S-<Return>", addName "Open terminal" $ spawn $ XMonad.terminal conf)
subKeys "Launchers" [ ("M-S-<Return>", addName "Open terminal" $ spawn $ XMonad.terminal conf)
, ("M-n", scratchSubmaps conf)
, ("M-s", searchSubmaps conf)
, ("M-s", searchSubmaps extraConfig conf)
, ("M-p", addName "Retrieve password" $ passPrompt def)
, ("M-S-e", addName "Open with app" xdg_open)
, ("M-e", addName "Run app" $ runOrRaisePrompt def)] ^++^
, ("M-e", addName "Run app" $ runOrRaisePrompt def)
, ("M-S-e", addName "Run shell command" $ shellPrompt def)] ^++^
subKeys "Windows" [ ("M-j", addName "Go down" $ windowGo D False)
, ("M-k", addName "Go up" $ windowGo U False)
, ("M-h", addName "Go left" $ windowGo L False)
, ("M-l", addName "Go right" $ windowGo R False)
, ("M-S-j", addName "Shift window down" $ windowSwap D False)
, ("M-S-k", addName "Shift window up" $ windowSwap U False)
, ("M-S-h", addName "Shift window left" $ windowSwap L False)
, ("M-S-l", addName "Shift window right" $ windowSwap R False)
-- Swap screen left or right, don't wrap
, ("M-S-h", addName "Shift window up" $ screenSwap L True)
, ("M-S-l", addName "Shift window right" $ screenSwap R True)
-- , ("M-S-j", addName "Shift window down" $ windowSwap D False)
-- , ("M-S-k", addName "Shift window up" $ windowSwap U False)
-- , ("M-S-h", addName "Shift window left" $ windowSwap L False)
-- , ("M-S-l", addName "Shift window right" $ windowSwap R False)
, ("M-.", addName "Go to previous window" $ windows W.focusDown)
, ("M-,", addName "Go to next window" $ windows W.focusUp)
, ("M-S-m", addName "Swap master" $ windows W.swapMaster)
] ^++^
subKeys "Projects & Workspaces" (topicKeys' extraConfig conf) ^++^
subKeys "Layout management" [ ("M-C-<Space>", addName "Toggle layout" $ sendMessage ToggleLayout)
, ("M-z", addName "Toggle zoom" $ sendMessage (Toggle "Zoom"))
, ("M-<Space>", addName "Next layout" $ sendMessage NextLayout)] ^++^
subKeys "Resize" []
where
locker = "sh ~/scripts/lock.sh"
locker = "xset s activate"
@ -233,19 +242,24 @@ masser extraConfig = xmonad =<< statusBar (bar extraConfig) zenburnPP toggleStru
, normalBorderColor = "#262626"
, focusedBorderColor = "#7F9F7F"
, manageHook = myManageHook
-- The focus follows mouse is a bad idea for me because
-- it misbehaves with accordion. If I accidentally hover
-- my mouse at the lower edge of the accordion, it will
-- just cycle through to the last accordion
, focusFollowsMouse = False
, logHook = updatePointer (0.25, 0.25) (0.25, 0.25)
}
myLayout = onWorkspace "web" webLayout $
onWorkspace "dynamics" webLayout $
onWorkspace "pdf" pdfLayout $
onWorkspace "documents" documentLayout $
onWorkspace "mail" mailLayout $
onWorkspace "irc" ircLayout
defLayout
myLayout = toggleLayouts zoom workspaceLayouts
where
zoom = renamed [Replace "Zoom"] (noBorders Full)
workspaceLayouts = onWorkspace "web" webLayout $
onWorkspace "dynamics" webLayout $
onWorkspace "pdf" pdfLayout $
onWorkspace "documents" documentLayout $
onWorkspace "mail" mailLayout
defLayout
-- Default layout
defLayout = tiled ||| tabLayout ||| readLayout ||| bspLayout ||| vimLayout ||| spiral (6/7) ||| Full
ircLayout = GridRatio (4/3) False ||| emptyBSP
-- Pdfs are restricted to tabs
vimLayout = Mirror (mastered (1/100) (4/5) Accordion)
pdfLayout = readLayout ||| tiled ||| tabLayout

View File

@ -4,11 +4,30 @@ module XMonad.Config.MasseR.ExtraConfig where
import GHC.Generics (Generic)
import Data.Text (Text)
data Applications = Applications { browser :: FilePath, launcher :: FilePath, prompt :: FilePath, screenshot :: FilePath, urxvt :: FilePath } deriving (Show, Generic)
data Applications =
Applications { browser :: FilePath
, launcher :: FilePath
, prompt :: FilePath
, screenshot :: FilePath
, urxvt :: FilePath
, musicToggle :: FilePath
} deriving (Show, Generic)
data TopicRule = TopicRule { topicName :: Text
, topicHome :: Maybe Text
, topicAction :: Maybe Text }
deriving (Show, Generic)
data TopicRule =
TopicRule { topicName :: Text
, topicHome :: Maybe Text
, topicAction :: Maybe Text
}
deriving (Show, Generic)
data ExtraConfig = ExtraConfig { applications :: Applications, topics :: [ TopicRule ] } deriving (Show, Generic)
data Search = Search { name :: String
, key :: String
, url :: String
}
deriving (Show, Generic)
data ExtraConfig =
ExtraConfig { applications :: Applications
, topics :: [ TopicRule ]
, searchEndpoints :: [Search] }
deriving (Show, Generic)

View File

@ -1,4 +1,4 @@
module XMonad.CustomPrompt (xdg_open, browser) where
module XMonad.CustomPrompt (xdgOpen, browser) where
import qualified XMonad.Prompt.AppLauncher as AL
import XMonad.Prompt
@ -7,8 +7,8 @@ import XMonad (X)
launchApp :: AL.Application -> X ()
launchApp = AL.launchApp def
xdg_open :: X ()
xdg_open = launchApp "xdg-open"
xdgOpen :: X ()
xdgOpen = launchApp "xdg-open"
browser :: X ()
browser = launchApp "qutebrowser"

View File

@ -10,7 +10,7 @@ import XMonad.Core
import XMonad.Prompt
import XMonad.Util.Run (runProcessWithInput)
data Pass = Pass { passLabel :: String }
newtype Pass = Pass { passLabel :: String }
-- Rosetta code levenshtein
levenshtein :: String -> String -> Int
@ -37,7 +37,7 @@ mkPassPrompt label f conf = do
-- I'm just sorting here, but could use some kind of fuzzy matching instead, but it requires a bit more effort
passwords <- sort <$> liftIO getPasswords
-- Other change, use infixof instead of prefixof
mkXPrompt (Pass label) conf (\input -> pure (sortBy (compare `on` (levenshtein input)) . filter (consumes input) $ passwords)) f
mkXPrompt (Pass label) conf (\input -> pure (sortBy (compare `on` levenshtein input) . filter (consumes input) $ passwords)) f
where
consumes [] _ = True -- everything consumed
consumes (_:_) [] = False -- all not consumed
@ -54,4 +54,4 @@ mkPassPrompt label f conf = do
selectPassword :: String -> X ()
selectPassword pass = spawn $ "pass --clip " ++ pass
selectPassword pass = spawn $ "PASSWORD_STORE_CLIP_TIME=10 pass --clip " ++ pass

View File

@ -4,7 +4,6 @@ module XMonad.TopicSpace (topicKeys', addTopic, TopicAction(..)) where
import XMonad.Actions.TopicSpace
import XMonad
import qualified Data.Map as M
import XMonad.Actions.GridSelect
import XMonad.Actions.DynamicWorkspaces
import XMonad.TopicUtils
import XMonad.Util.EZConfig (mkNamedKeymap)
@ -42,7 +41,6 @@ myTopicConfig extraConfig =
topicKeys' :: ExtraConfig -> XConfig l -> [(String, NamedAction)]
topicKeys' extraConfig conf = [ ("M-y", addName "Change topic" $ visualSelect (myTopicConfig extraConfig))
, ("M-S-g", addName "Move window to topic" $ gridselectMove def)
, ("M-u", addName "Select window" $ gotoSelected' def{gs_colorizer = fromClassName})
, ("M-<Return>", addName "Open project action" $ currentTopicAction' (myTopicConfig extraConfig))
, ("M-w", modificationSubmaps' conf)]

View File

@ -1,7 +1,8 @@
{-# LANGUAGE TupleSections #-}
module XMonad.TopicUtils where
import Data.Maybe (fromMaybe, listToMaybe, mapMaybe)
import Data.List (isPrefixOf, sort, nub)
import Data.List (isPrefixOf, nub, sortOn)
import XMonad.Actions.TopicSpace
import XMonad
import qualified Data.Map as M
@ -11,6 +12,7 @@ import qualified XMonad.StackSet as W
import XMonad.Util.Dmenu (dmenu)
import XMonad.Actions.DynamicWorkspaces
import XMonad.Util.NamedWindows (getName)
import Data.Ord
realTopicDir :: M.Map String FilePath -> X String
@ -24,9 +26,11 @@ safeRunInTerm dir Nothing = safeSpawn "urxvt" ["-cd", dir]
safeRunInTerm dir (Just command) = safeSpawn "urxvt" ["-cd", dir, "-e", command]
inactiveTags :: X [WorkspaceId]
inactiveTags = map W.tag . inactive' <$> gets windowset
inactiveTags = inactive' <$> gets windowset
where
inactive' s = W.hidden s ++ map W.workspace (filter (\w -> (W.tag . W.workspace . W.current) s /= (W.tag . W.workspace) w) (W.visible s))
inactive' s =
let current = W.currentTag s
in filter (current /=) . map W.tag $ W.hidden s <> map W.workspace (W.visible s)
gridselectMove :: GSConfig WorkspaceId -> X ()
gridselectMove conf = do
@ -46,7 +50,10 @@ gsConfig = def{gs_navigate = navNSearch, gs_colorizer = fromClassName}
-- - Takes a topicspace viewfunc
gridselectWorkspace :: GSConfig WorkspaceId -> (WorkspaceId -> X ()) -> X ()
gridselectWorkspace conf viewFunc = withWindowSet $ \ws -> do
let wss = map W.tag . W.hidden $ ws
let wss = filter (/= current) . map W.tag $ invisible <> visible
visible = fmap W.workspace (W.visible ws)
invisible = W.hidden ws
current = W.currentTag ws
gridselect conf (zip wss wss) >>= flip whenJust viewFunc
gotoSelected' :: GSConfig Window -> X ()
@ -58,7 +65,7 @@ gridselectCurrentWindows :: GSConfig Window -> X (Maybe Window)
gridselectCurrentWindows gsconf = windowMap >>= gridselect gsconf
where
getName' = fmap show . getName
kvPair w = flip (,) w `fmap` getName' w
kvPair w = (, w) <$> getName' w
windowMap = do
ws <- gets (nub . W.integrate' . W.stack . W.workspace . W.current . windowset)
mapM kvPair ws
@ -78,11 +85,11 @@ currentTopicAction' tg = do
copyTopic :: X ()
copyTopic = do
currentTopic <- realTopic
lastN <- gets (listToMaybe . reverse . sort . mapMaybe (subset currentTopic . W.tag) . W.workspaces . windowset)
addWorkspace (currentTopic ++ ":" ++ (show $ maybe 2 (+1) lastN))
lastN <- gets (listToMaybe . sortOn Down . mapMaybe (subset currentTopic . W.tag) . W.workspaces . windowset)
addWorkspace (currentTopic ++ ":" ++ show (maybe 2 (+1) lastN))
where
subset :: String -> String -> Maybe Int
subset topic other = if topic `isPrefixOf` other then (readM $ tail' $ snd $ break (== ':') other) else Nothing
subset topic other = if topic `isPrefixOf` other then readM $ tail' $ dropWhile (/= ':') other else Nothing
readM a = case reads a of
[(x,_)] -> Just x
_ -> Nothing

View File

@ -25,7 +25,7 @@ library
, XMonad.TopicSpace
, XMonad.XMobar
-- other-extensions:
build-depends: base >=4.11 && <4.12
build-depends: base >=4.11 && <4.14
, xmonad
, xmonad-contrib
, mtl
@ -34,5 +34,7 @@ library
, unix
, containers
, text
, lens
, generic-lens
hs-source-dirs: src
default-language: Haskell2010