Compare commits

...

6 commits

7 changed files with 201 additions and 174 deletions

View file

@ -24,8 +24,9 @@ library
import: common import: common
hs-source-dirs: lib hs-source-dirs: lib
exposed-modules: exposed-modules:
Leanamonad.Layouts.ReflectMsg XMonad.Layout.Reflect.Message
Leanamonad.GreekChar XMonad.Layout.ResizableTile.FixDescription
Data.Char.Greek
executable leanamonad executable leanamonad
import: common import: common

View file

@ -1,4 +1,4 @@
module Leanamonad.GreekChar where module Data.Char.Greek where
import Data.List (find) import Data.List (find)

View file

@ -1,7 +1,7 @@
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
module Leanamonad.Layouts.ReflectMsg where module XMonad.Layout.Reflect.Message where
import XMonad ( import XMonad (
Resize (Expand, Shrink), Resize (Expand, Shrink),

View file

@ -0,0 +1,26 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module XMonad.Layout.ResizableTile.FixDescription
( RTFixDescription(..)
) where
import XMonad
import qualified XMonad.StackSet as W
import XMonad.Layout.ResizableTile
newtype RTFixDescription a = RTFixDescription { unwrapRT :: ResizableTall a }
deriving (Read, Show)
instance LayoutClass RTFixDescription a where
runLayout (W.Workspace t l s) =
let ws' = W.Workspace t (unwrapRT l) s
in fmap (fmap (fmap RTFixDescription))
. runLayout ws'
handleMessage (RTFixDescription l) m =
fmap (fmap RTFixDescription)
$ handleMessage l m
description (RTFixDescription l) =
description l <> " " <> show (_nmaster l)

View file

@ -12,8 +12,10 @@ import XMonad.Hooks.RefocusLast
import XMonad.Hooks.StatusBar import XMonad.Hooks.StatusBar
import XMonad.Layout.NoBorders import XMonad.Layout.NoBorders
import XMonad.Layout.Reflect import XMonad.Layout.Reflect
import XMonad.Layout.Reflect.Message
import XMonad.Layout.Renamed import XMonad.Layout.Renamed
import XMonad.Layout.ResizableTile import XMonad.Layout.ResizableTile
import XMonad.Layout.ResizableTile.FixDescription
import XMonad.Layout.Spacing import XMonad.Layout.Spacing
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import XMonad.Util.EZConfig import XMonad.Util.EZConfig
@ -26,8 +28,7 @@ import qualified Data.Map.Strict as M
import System.Posix import System.Posix
import Graphics.X11.ExtraTypes.XF86 import Graphics.X11.ExtraTypes.XF86
import Leanamonad.Layouts.ReflectMsg import Data.Char.Greek
import Leanamonad.GreekChar
main :: IO () main :: IO ()
main = main =
@ -45,10 +46,54 @@ main =
, focusFollowsMouse = True , focusFollowsMouse = True
, terminal = myTerm , terminal = myTerm
, workspaces = myWorkspaces , workspaces = myWorkspaces
, logHook = refocusLastLogHook , logHook = refocusLastLogHook
, startupHook = myStartupHook
, layoutHook = myLayout
, manageHook = myManageHook
}
, startupHook = do -- Only remove mappings that needs pass through
`removeKeys` removedKeybinds
`additionalKeys` keybinds
myLayout =
let tallr = renamed [ KeepWordsRight 2 ] {- keep "ResizableTall n" -}
$ smartSpacingWithEdge 5
$ reflectMsg . reflectHoriz
$ RTFixDescription
$ ResizableTall 1 (1/10) (3/7) []
mag = magnifyxy 1.05 1.3 (NoMaster 3) False
in avoidStruts . smartBorders $
mag tallr ||| Full
isOneOf :: Eq a => Query a -> [a] -> Query Bool
isOneOf q = fmap or . traverse (q =?)
myManageHook :: ManageHook
myManageHook =
composeAll
[ className ~? "NautilusPreviewer" --> customFloating centeredFloat
, className =? "feh" --> customFloating buttomRightFloat
, className =? "Minder"
<&&> not <$> title ~? "Pick a Color" -- ignore the color picker
--> customFloating centeredFloat
, className =? "firefox"
<&&> title =? "Picture-in-Picture"
--> doFloat
, namedScratchpadManageHook myScratchpads
]
<> composeOne
[ className =? "firefox" -?> insertPosition Master Newer
, className =? "kitty" -?> insertPosition Below Newer
, className `isOneOf`
[ "sioyek"
, "Nautilus"
]
-?> insertPosition End Older
]
myStartupHook :: X ()
myStartupHook = do
spawnOnce "fcitx5 &" -- Input method spawnOnce "fcitx5 &" -- Input method
spawn "feh --no-fehbg --bg-fill ~/.wallpaper &" -- wallpaper spawn "feh --no-fehbg --bg-fill ~/.wallpaper &" -- wallpaper
@ -64,41 +109,8 @@ main =
putEnv "GLFW_IM_MODULE=ibus" -- Make sure kitty knows how to talk to fcitx putEnv "GLFW_IM_MODULE=ibus" -- Make sure kitty knows how to talk to fcitx
putEnv "MOZ_USE_XINPUT2=1" -- Force touchpad for firefox putEnv "MOZ_USE_XINPUT2=1" -- Force touchpad for firefox
, layoutHook = removedKeybinds :: [(KeyMask, KeySym)]
let tallr = named "Normal" removedKeybinds =
$ smartSpacingWithEdge 5
$ reflectMsg . reflectHoriz
$ ResizableTall 1 (1/10) (3/7) []
mag = magnifyxy 1.05 1.3 (NoMaster 3) False
in avoidStruts . smartBorders $
mag tallr ||| Full
, manageHook =
composeAll
[ className ~? "NautilusPreviewer" --> customFloating centeredFloat
, className =? "feh" --> customFloating buttomRightFloat
, className =? "Minder"
<&&> not <$> title ~? "Pick a Color" -- ignore the color picker
--> customFloating centeredFloat
, isFirefoxPIP --> doFloat
, namedScratchpadManageHook myScratchpads
]
<>
composeOne
[ className =? "firefox" -?> insertPosition Master Newer
, className =? "kitty" -?> insertPosition Below Newer
, className `isOneOf`
[ "sioyek"
, "Nautilus"
]
-?> insertPosition End Older
]
}
-- Only remove mappings that needs pass through (it's a map).
`removeKeys`
[ (superMask, xK_h) [ (superMask, xK_h)
, (superMask, xK_l) , (superMask, xK_l)
, (superMask, xK_p) , (superMask, xK_p)
@ -109,7 +121,8 @@ main =
++ [ (superMask , n) | n <- [xK_1 .. xK_9] ] ++ [ (superMask , n) | n <- [xK_1 .. xK_9] ]
++ [ (superMask .|. shiftMask, n) | n <- [xK_1 .. xK_9] ] ++ [ (superMask .|. shiftMask, n) | n <- [xK_1 .. xK_9] ]
`additionalKeys` keybinds :: [((KeyMask, KeySym), X ())]
keybinds =
[ [
-- Display -- Display
((0, xF86XK_MonBrightnessDown), spawn "light -U 5") ((0, xF86XK_MonBrightnessDown), spawn "light -U 5")
@ -156,58 +169,52 @@ main =
] ]
-- Screenshots -- Screenshots
++ (let ++ (let fullscreen = "maim -u | xclip -in -selection clipboard -t image/png"
fullscreen = "maim -u | xclip -in -selection clipboard -t image/png"
withSelection = "maim -u -s -b 5 -o | xclip -in -selection clipboard -t image/png" withSelection = "maim -u -s -b 5 -o | xclip -in -selection clipboard -t image/png"
toFloat = "maim -u -s -b 5 -o | feh --auto-zoom -" toFloat = "maim -u -s -b 5 -o | feh --auto-zoom -"
in in [ ((0, xK_Print), spawn fullscreen )
[ ((0, xK_Print), spawn fullscreen )
, ((superMask .|. shiftMask, xK_3 ), spawn fullscreen ) , ((superMask .|. shiftMask, xK_3 ), spawn fullscreen )
, ((superMask .|. shiftMask, xK_4 ), spawn withSelection) , ((superMask .|. shiftMask, xK_4 ), spawn withSelection)
, ((superMask .|. shiftMask, xK_5 ), spawn toFloat ) , ((superMask .|. shiftMask, xK_5 ), spawn toFloat )
]) ]
)
-- Yeet -- Yeet
++ (let ++ (let workspaceKeys = [xK_h, xK_t, xK_n, xK_s, xK_m, xK_w, xK_v, xK_z]
workspaceKeys = [xK_h, xK_t, xK_n, xK_s, xK_m, xK_w, xK_v, xK_z] in [ ((superMask, k), windows $ W.greedyView space)
in
[ ((superMask, k), windows $ W.greedyView space)
| (k, space) <- zip workspaceKeys myWorkspaces | (k, space) <- zip workspaceKeys myWorkspaces
] ]
++ ++ [ ((superMask .|. altMask, k), windows $ W.greedyView space . W.shift space)
[ ((superMask .|. altMask, k), windows $ W.greedyView space . W.shift space)
| (k, space) <- zip workspaceKeys myWorkspaces | (k, space) <- zip workspaceKeys myWorkspaces
] ]
++ ++ [ ((superMask .|. controlMask, k), windows $ swapWithCurrent space)
[ ((superMask .|. controlMask, k), windows $ swapWithCurrent space)
| (k, space) <- zip workspaceKeys myWorkspaces | (k, space) <- zip workspaceKeys myWorkspaces
]) ]
)
-- Launcher -- Launcher
++ (let ++ (let launchFirefox = "if type firefox; then firefox; else firefox-esr; fi"
launchFirefox = "if type firefox; then firefox; else firefox-esr; fi"
launchDmenu = "dmenu_run -i -fn \"Iosevka-14\" -nb \"#36363a\" -nf \"#e2e2e4\" -sb \"#f7f7f8\" -sf \"#36363a\" -l 10" launchDmenu = "dmenu_run -i -fn \"Iosevka-14\" -nb \"#36363a\" -nf \"#e2e2e4\" -sb \"#f7f7f8\" -sf \"#36363a\" -l 10"
lock = "xscreensaver-command -lock" lock = "xscreensaver-command -lock"
in in [ ((controlMask .|. altMask, xK_m), namedScratchpadAction myScratchpads "cmus" )
[ ((controlMask .|. altMask, xK_m), namedScratchpadAction myScratchpads "cmus" )
, ((controlMask .|. altMask, xK_t), namedScratchpadAction myScratchpads "btop" ) , ((controlMask .|. altMask, xK_t), namedScratchpadAction myScratchpads "btop" )
, ((controlMask .|. altMask, xK_p), namedScratchpadAction myScratchpads "pass" ) , ((controlMask .|. altMask, xK_p), namedScratchpadAction myScratchpads "pass" )
, ((controlMask .|. altMask, xK_e), namedScratchpadAction myScratchpads "emoji-picker") , ((controlMask .|. altMask, xK_e), namedScratchpadAction myScratchpads "emoji-picker")
, ((controlMask .|. altMask, xK_b), spawn launchFirefox ) , ((controlMask .|. altMask, xK_b), spawn launchFirefox )
, ((superMask, xK_o), spawn launchDmenu ) , ((superMask, xK_o), spawn launchDmenu )
, ((superMask, xK_l), spawn lock ) , ((superMask, xK_l), spawn lock )
]) ]
)
++ (let ++ (let powerprofile p = (p, spawn $ "powerprofilesctl set " ++ p)
powerprofile p = (p, spawn $ "powerprofilesctl set " ++ p) in [ ( (superMask, xK_p), visualSubmap def $ M.fromList
in
[ ( (superMask, xK_p), visualSubmap def $ M.fromList
[ ((0, xK_1), powerprofile "power-saver") [ ((0, xK_1), powerprofile "power-saver")
, ((0, xK_2), powerprofile "balanced" ) , ((0, xK_2), powerprofile "balanced" )
, ((0, xK_3), powerprofile "performance") , ((0, xK_3), powerprofile "performance")
] ]
) )
]) ]
)
myTerm :: String myTerm :: String
myTerm = "kitty" myTerm = "kitty"
@ -217,7 +224,7 @@ superMask = mod4Mask
altMask = mod1Mask altMask = mod1Mask
myWorkspaces :: [String] myWorkspaces :: [String]
myWorkspaces = take 8 . fmap (:[]) $ greekLower myWorkspaces = map (:[]) $ take 8 greekLower
centeredFloat, smallFloat, fullFloat, buttomRightFloat :: W.RationalRect centeredFloat, smallFloat, fullFloat, buttomRightFloat :: W.RationalRect
centeredFloat = W.RationalRect (1/9) (1/9) (7/9) (7/9) centeredFloat = W.RationalRect (1/9) (1/9) (7/9) (7/9)
@ -236,30 +243,25 @@ xmobarConfig = statusBarProp "xmobar -x 0" (pure myPrettyPrinter)
, ppSep = " | " , ppSep = " | "
} }
isOneOf :: Eq a => Query a -> [a] -> Query Bool
isOneOf q = fmap or . traverse (q =?)
isFirefoxPIP :: Query Bool
isFirefoxPIP =
className =? "firefox"
<&&> title =? "Picture-in-Picture"
myScratchpads :: [NamedScratchpad] myScratchpads :: [NamedScratchpad]
myScratchpads = myScratchpads =
[ NS "cmus" [ NS
"cmus"
(myTerm ++ " -T 'cmus' cmus") (myTerm ++ " -T 'cmus' cmus")
(title =? "cmus") (title =? "cmus")
(customFloating centeredFloat) (customFloating centeredFloat)
, NS "btop" , NS
"btop"
(myTerm ++ " -T 'btop' btop") (myTerm ++ " -T 'btop' btop")
(title =? "btop") (title =? "btop")
(customFloating fullFloat) (customFloating fullFloat)
, NS "pass" , NS
"pass"
(myTerm ++ " -T 'pass' -- fish -i -c 'while :; fzf-pass; end'") (myTerm ++ " -T 'pass' -- fish -i -c 'while :; fzf-pass; end'")
(title =? "pass") (title =? "pass")
(customFloating smallFloat) (customFloating smallFloat)
, NS "emoji-picker" , NS
"emoji-picker"
(myTerm ++ " -T 'emoji-picker' -- fish -i -c 'while :; emoji-picker; end'") (myTerm ++ " -T 'emoji-picker' -- fish -i -c 'while :; emoji-picker; end'")
(title =? "emoji-picker") (title =? "emoji-picker")
(customFloating smallFloat) (customFloating smallFloat)

View file

@ -61,8 +61,6 @@
# Gotta purify my smoos brain for a while # Gotta purify my smoos brain for a while
0.0.0.0 instagram.com 0.0.0.0 instagram.com
0.0.0.0 www.instagram.com 0.0.0.0 www.instagram.com
0.0.0.0 youtube.com
0.0.0.0 www.youtube.com
''; '';
}; };

View file

@ -12,8 +12,8 @@
domain = "git.confusedcompiler.org"; domain = "git.confusedcompiler.org";
owner = "leana8959"; owner = "leana8959";
repo = "ruler"; repo = "ruler";
rev = "12b287522215781b21791101bf85f8a0dddd1225"; rev = "f328620a52b25d4c9dea64425afe5995dfb8cb5a";
hash = "sha256-XoTTxKxlUmtM9mxguwdEsMSp6qBkEgBcviM8bTgs95o="; hash = "sha256-8nSVFckWXkf9dRTdzjbHRhf/qPdbXHEkVI4DyW3zfSo=";
}) })
{}; {};