Compare commits

...

11 Commits

Author SHA1 Message Date
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
7 changed files with 68 additions and 33 deletions

View File

@ -9,8 +9,6 @@ before_script:
matrix: matrix:
include: include:
- env:
- NIXPKGS=https://github.com/NixOS/nixpkgs-channels/archive/nixos-18.09.tar.gz
- env: - env:
- NIXPKGS=https://github.com/NixOS/nixpkgs-channels/archive/nixos-19.03.tar.gz - NIXPKGS=https://github.com/NixOS/nixpkgs-channels/archive/nixos-19.03.tar.gz
- env: - env:

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,14 +1,17 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeApplications #-}
module XMonad.Config.MasseR where module XMonad.Config.MasseR where
import XMonad.Password import Control.Lens ((^.))
import XMonad.CustomPrompt import Data.Generics.Product (field)
import XMonad.TopicSpace
import qualified Data.List as List import qualified Data.List as List
import XMonad import XMonad
import XMonad.Actions.CycleWS (swapNextScreen) import XMonad.Actions.CycleWS (swapNextScreen)
import XMonad.Actions.Search import XMonad.Actions.Search
import XMonad.CustomPrompt
import XMonad.Hooks.EwmhDesktops (ewmh, ewmhDesktopsStartup) import XMonad.Hooks.EwmhDesktops (ewmh, ewmhDesktopsStartup)
import XMonad.Hooks.SetWMName (setWMName) import XMonad.Hooks.SetWMName (setWMName)
import XMonad.Hooks.UrgencyHook (args, dzenUrgencyHook, import XMonad.Hooks.UrgencyHook (args, dzenUrgencyHook,
@ -18,7 +21,6 @@ import XMonad.Layout.BinarySpacePartition (emptyBSP)
import XMonad.Layout.Decoration (Decoration, import XMonad.Layout.Decoration (Decoration,
DefaultShrinker) DefaultShrinker)
import XMonad.Layout.DwmStyle import XMonad.Layout.DwmStyle
import XMonad.Layout.HintedGrid
import XMonad.Layout.LayoutModifier (ModifiedLayout) import XMonad.Layout.LayoutModifier (ModifiedLayout)
import XMonad.Layout.Master import XMonad.Layout.Master
import XMonad.Layout.NoBorders (smartBorders) import XMonad.Layout.NoBorders (smartBorders)
@ -30,11 +32,13 @@ import XMonad.Layout.Tabbed (TabbedDecoration,
Theme (..), shrinkText, Theme (..), shrinkText,
tabbed) tabbed)
import XMonad.Layout.ToggleLayouts (ToggleLayout (..)) import XMonad.Layout.ToggleLayouts (ToggleLayout (..))
import XMonad.Password
import XMonad.Prompt.RunOrRaise (runOrRaisePrompt) import XMonad.Prompt.RunOrRaise (runOrRaisePrompt)
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import XMonad.TopicSpace
import XMonad.Util.EZConfig import XMonad.Util.EZConfig
import XMonad.XMobar (zenburnPP) import XMonad.XMobar (zenburnPP)
import Data.Monoid (Endo, (<>)) import Data.Monoid (Endo, (<>))
@ -55,9 +59,9 @@ import XMonad.Hooks.DynamicLog (statusBar)
import qualified Data.Set as S import qualified Data.Set as S
spotify :: XConfig l -> NamedAction spotify :: ExtraConfig -> XConfig l -> NamedAction
spotify conf = submapName . mkNamedKeymap conf $ spotify extraConf conf = submapName . mkNamedKeymap conf $
[ ("M-p", addName "Play" $ spawn "sp play") ] [ ("M-p", addName "Play" $ spawn (musicToggle . applications $ extraConf)) ]
scratchpads :: [NamedScratchpad] scratchpads :: [NamedScratchpad]
scratchpads = [ scratchpads = [
@ -71,15 +75,17 @@ scratchSubmaps conf = submapName . mkNamedKeymap conf $ [
] ]
-- Search engines inside submaps -- Search engines inside submaps
searchSubmaps :: XConfig l -> NamedAction searchSubmaps :: ExtraConfig -> XConfig l -> NamedAction
searchSubmaps conf = searchSubmaps extraConfig conf =
let mkBrowser = promptSearchBrowser def "qutebrowser" let mkBrowser = promptSearchBrowser def (extraConfig ^. field @"applications" . field @"browser")
_googleP = addName "Search google" $ mkBrowser google _googleP = addName "Search google" $ mkBrowser google
ddgP = addName "Search duckduckgo" $ mkBrowser (searchEngine "duckduckgo" "http://duckduckgo.com/?q=") ddgP = addName "Search duckduckgo" $ mkBrowser (searchEngine "duckduckgo" "http://duckduckgo.com/?q=")
extras = [(key, addName name $ mkBrowser (searchEngine name url)) | Search{..} <- searchEndpoints extraConfig]
in submapName . mkNamedKeymap conf $ in submapName . mkNamedKeymap conf $
[ ("d", ddgP) -- Training to use ddg again [ ("d", ddgP) -- Training to use ddg again
, ("g", ddgP) -- training to use ddg again , ("g", ddgP) -- training to use ddg again
] ] ++ extras
myNav2d :: Navigation2DConfig myNav2d :: Navigation2DConfig
myNav2d = def { defaultTiledNavigation = lineNavigation } myNav2d = def { defaultTiledNavigation = lineNavigation }
@ -172,9 +178,8 @@ myKeys extraConfig conf =
, ("<XF86AudioLowerVolume>", addName "Decrease volume" $ spawn "amixer set Master 2%-") , ("<XF86AudioLowerVolume>", addName "Decrease volume" $ spawn "amixer set Master 2%-")
, ("M-<plus>", addName "Increase 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-") , ("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") , ("<XF86AudioPlay>", addName "Play/pause mopidy" $ spawn "mpc toggle")
, ("M-m", spotify conf) , ("M-m", spotify extraConfig conf)
, ("M-S-<Space>", addName "Swap screens" swapNextScreen) , ("M-S-<Space>", addName "Swap screens" swapNextScreen)
, ("M-<Backspace>", addName "Kill window" kill) , ("M-<Backspace>", addName "Kill window" kill)
-- scrot requires `unGrab` -- scrot requires `unGrab`
@ -182,7 +187,7 @@ myKeys extraConfig conf =
subKeys "Launchers" [ ("M-S-y", addName "Open youtube" $ spawn "mpv $(clip -o)") subKeys "Launchers" [ ("M-S-y", addName "Open youtube" $ spawn "mpv $(clip -o)")
, ("M-S-<Return>", addName "Open terminal" $ spawn $ XMonad.terminal conf) , ("M-S-<Return>", addName "Open terminal" $ spawn $ XMonad.terminal conf)
, ("M-n", scratchSubmaps conf) , ("M-n", scratchSubmaps conf)
, ("M-s", searchSubmaps conf) , ("M-s", searchSubmaps extraConfig conf)
, ("M-p", addName "Retrieve password" $ passPrompt def) , ("M-p", addName "Retrieve password" $ passPrompt def)
, ("M-S-e", addName "Open with app" xdgOpen) , ("M-S-e", addName "Open with app" xdgOpen)
, ("M-e", addName "Run app" $ runOrRaisePrompt def)] ^++^ , ("M-e", addName "Run app" $ runOrRaisePrompt def)] ^++^
@ -239,13 +244,11 @@ masser extraConfig = xmonad =<< statusBar (bar extraConfig) zenburnPP toggleStru
onWorkspace "dynamics" webLayout $ onWorkspace "dynamics" webLayout $
onWorkspace "pdf" pdfLayout $ onWorkspace "pdf" pdfLayout $
onWorkspace "documents" documentLayout $ onWorkspace "documents" documentLayout $
onWorkspace "mail" mailLayout $ onWorkspace "mail" mailLayout
onWorkspace "irc" ircLayout
defLayout defLayout
where where
-- Default layout -- Default layout
defLayout = tiled ||| tabLayout ||| readLayout ||| bspLayout ||| vimLayout ||| spiral (6/7) ||| Full defLayout = tiled ||| tabLayout ||| readLayout ||| bspLayout ||| vimLayout ||| spiral (6/7) ||| Full
ircLayout = GridRatio (4/3) False ||| emptyBSP
-- Pdfs are restricted to tabs -- Pdfs are restricted to tabs
vimLayout = Mirror (mastered (1/100) (4/5) Accordion) vimLayout = Mirror (mastered (1/100) (4/5) Accordion)
pdfLayout = readLayout ||| tiled ||| tabLayout pdfLayout = readLayout ||| tiled ||| tabLayout

View File

@ -4,11 +4,30 @@ module XMonad.Config.MasseR.ExtraConfig where
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Data.Text (Text) 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 data TopicRule =
, topicHome :: Maybe Text TopicRule { topicName :: Text
, topicAction :: Maybe Text } , topicHome :: Maybe Text
deriving (Show, Generic) , 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

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

View File

@ -26,9 +26,11 @@ safeRunInTerm dir Nothing = safeSpawn "urxvt" ["-cd", dir]
safeRunInTerm dir (Just command) = safeSpawn "urxvt" ["-cd", dir, "-e", command] safeRunInTerm dir (Just command) = safeSpawn "urxvt" ["-cd", dir, "-e", command]
inactiveTags :: X [WorkspaceId] inactiveTags :: X [WorkspaceId]
inactiveTags = map W.tag . inactive' <$> gets windowset inactiveTags = inactive' <$> gets windowset
where 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 :: GSConfig WorkspaceId -> X ()
gridselectMove conf = do gridselectMove conf = do
@ -48,7 +50,10 @@ gsConfig = def{gs_navigate = navNSearch, gs_colorizer = fromClassName}
-- - Takes a topicspace viewfunc -- - Takes a topicspace viewfunc
gridselectWorkspace :: GSConfig WorkspaceId -> (WorkspaceId -> X ()) -> X () gridselectWorkspace :: GSConfig WorkspaceId -> (WorkspaceId -> X ()) -> X ()
gridselectWorkspace conf viewFunc = withWindowSet $ \ws -> do 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 gridselect conf (zip wss wss) >>= flip whenJust viewFunc
gotoSelected' :: GSConfig Window -> X () gotoSelected' :: GSConfig Window -> X ()

View File

@ -34,5 +34,7 @@ library
, unix , unix
, containers , containers
, text , text
, lens
, generic-lens
hs-source-dirs: src hs-source-dirs: src
default-language: Haskell2010 default-language: Haskell2010