about summary refs log tree commit diff
path: root/src/XMonad/Custom
diff options
context:
space:
mode:
authorazahi <azahi@teknik.io>2019-06-29 18:16:16 +0300
committerazahi <azahi@teknik.io>2019-06-29 18:16:16 +0300
commit9394e86a2ea44c29035630f54d276bd9712746c9 (patch)
tree765f36c517f1e99169741990d1923722d9515882 /src/XMonad/Custom
parentBump version 0.15.3 (diff)
Replace alsa-mixer with external shell alternative
Modify fonts
Remove urgency hook
Remove selection notification
Decrease spacing and apply it to bars
Tweak colors
Diffstat (limited to 'src/XMonad/Custom')
-rw-r--r--src/XMonad/Custom/Bindings.hs14
-rw-r--r--src/XMonad/Custom/Layout.hs5
-rw-r--r--src/XMonad/Custom/Log.hs2
-rw-r--r--src/XMonad/Custom/Theme.hs9
4 files changed, 15 insertions, 15 deletions
diff --git a/src/XMonad/Custom/Bindings.hs b/src/XMonad/Custom/Bindings.hs
index 772b0ad..cbe5056 100644
--- a/src/XMonad/Custom/Bindings.hs
+++ b/src/XMonad/Custom/Bindings.hs
@@ -19,7 +19,6 @@ module XMonad.Custom.Bindings
     , mouseBindings
     ) where
 
-import           Control.Monad
 import qualified Data.Map                            as M
 import           System.Exit
 import           XMonad                              hiding (keys, modMask,
@@ -77,9 +76,6 @@ zipKeys' m ks as f b = zipWith (\k d -> (m ++ k, f d b)) ks as
 tryMessageR_ :: (Message a, Message b) => a -> b -> X ()
 tryMessageR_ x y = sequence_ [tryMessageWithNoRefreshToCurrent x y, refresh]
 
--- xSelectionNotify :: MonadIO m => m ()
--- xSelectionNotify = join $ io
---     $ unsafeSpawn . (\x -> C.notify C.applications ++ " Clipboard " ++ wrap "\"\\\"" "\"\\\"" x) <$> getSelection
 
 toggleCopyToAll :: X ()
 toggleCopyToAll = wsContainingCopies >>= \case [] -> windows copyToAll
@@ -132,7 +128,6 @@ keysSystem :: XConfig Layout -> [(String, X ())]
 keysSystem _ =
     [ ("M-C-g"             , return ())
     , ("<XF86ScreenSaver>" , spawn "~/.xmonad/scripts/screenlock.sh")
-    -- , ("M-S-c"             , xSelectionNotify)
     , ("M-<Print>"         , spawn "~/.xmonad/scripts/xshot-upload.sh")
     , ("M-S-<Print>"       , spawn "~/.xmonad/scripts/xshot-select-upload.sh")
     , ("M-<Insert>"        , spawn "~/.xmonad/scripts/xcast.sh --webm")
@@ -146,11 +141,10 @@ keysSystem _ =
 
 keysMedia :: XConfig Layout -> [(String, X ())]
 keysMedia _ =
-    [
- -- , ("<XF86AudioMute>"        , void   toggleMute)
- -- , ("<XF86AudioLowerVolume>" , void $ lowerVolume 5)
- -- , ("<XF86AudioRaiseVolume>" , void $ raiseVolume 5)
-      ("<XF86AudioPlay>"        , spawn "~/.xmonad/scripts/mpc-play-pause.sh")
+    [ ("<XF86AudioMute>"        , spawn "amixer set Master toggle")
+    , ("<XF86AudioLowerVolume>" , spawn "amixer set Master 5-")
+    , ("<XF86AudioRaiseVolume>" , spawn "amixer set Master 5+")
+    , ("<XF86AudioPlay>"        , spawn "~/.xmonad/scripts/mpc-play-pause.sh")
     , ("<XF86AudioStop>"        , spawn "mpc --no-status stop")
     , ("<XF86AudioPrev>"        , spawn "mpc --no-status prev")
     , ("<XF86AudioNext>"        , spawn "mpc --no-status next")
diff --git a/src/XMonad/Custom/Layout.hs b/src/XMonad/Custom/Layout.hs
index f0a763b..652aed8 100644
--- a/src/XMonad/Custom/Layout.hs
+++ b/src/XMonad/Custom/Layout.hs
@@ -39,7 +39,7 @@ import           XMonad.Layout.Tabbed
 import           XMonad.Layout.WindowNavigation
 
 applySpacing :: l a -> ModifiedLayout Spacing l a
-applySpacing = spacingRaw True (Border 12 12 12 12) True (Border 12 12 12 12) True
+applySpacing = spacingRaw False (Border 6 6 6 6) True (Border 6 6 6 6) True
 
 data CustomTransformers = GAPS
                         deriving (Read, Show, Eq, Typeable)
@@ -51,7 +51,8 @@ layoutHook = fullscreenFloat
              $ lessBorders OnlyLayoutFloat
              $ mkToggle (single NBFULL)
              $ avoidStruts
-             $ mkToggle (single GAPS)
+             $ applySpacing
+          -- $ mkToggle (single GAPS)
              $ mkToggle (single REFLECTX)
              $ mkToggle (single REFLECTY)
              $ windowNavigation
diff --git a/src/XMonad/Custom/Log.hs b/src/XMonad/Custom/Log.hs
index e441a02..dfa60c1 100644
--- a/src/XMonad/Custom/Log.hs
+++ b/src/XMonad/Custom/Log.hs
@@ -39,7 +39,7 @@ topBarPP = def
     , ppVisible         = xmobarColor white1 ""                . wrap "~" "~"
     , ppHidden          = xmobarColor white1 ""                . wrap "-" "-"
     , ppHiddenNoWindows = xmobarColor white1 ""                . wrap "_" "_"
-    , ppUrgent          = xmobarColor red1   ""                . wrap "!" "!"
+    , ppUrgent          = xmobarColor red2   ""                . wrap "!" "!"
     , ppSep             = " / "
     , ppWsSep           = " "
     , ppTitle           = xmobarColor white1 "" . shorten 50
diff --git a/src/XMonad/Custom/Theme.hs b/src/XMonad/Custom/Theme.hs
index d25cb55..2860b91 100644
--- a/src/XMonad/Custom/Theme.hs
+++ b/src/XMonad/Custom/Theme.hs
@@ -44,6 +44,7 @@ import           Data.List
 import           Graphics.X11.Xlib.Types
 import           XMonad.Layout.Decoration
 import qualified XMonad.Prompt            as P
+import Data.Ratio
 
 font :: String
 font = "xft:tewi:style=Regular:size=8" -- TODO CJKのフォールバックフォントを追加する
@@ -92,7 +93,7 @@ colorN = black2
 colorF = white2
 
 gapBase, gapFull :: Int
-gapBase = 12
+gapBase = 6
 gapFull = gapBase * 2
 
 height, border :: Dimension
@@ -123,9 +124,13 @@ promptTheme = def
     , P.bgHLight          = black2
     , P.borderColor       = white2
     , P.promptBorderWidth = border
-    , P.position          = P.Bottom
+    , P.position          = P.CenteredAt { P.xpCenterY = 3 % 10
+                                         , P.xpWidth   = 9 % 10
+                                         }
     , P.height            = height
+    , P.maxComplRows      = Just 5
     , P.searchPredicate   = isInfixOf `on` map toLower
+    , P.alwaysHighlight   = True
     }
 hotPromptTheme = promptTheme
     { P.bgColor           = black2

Consider giving Nix/NixOS a try! <3