Compare commits

..

10 commits

5 changed files with 72 additions and 71 deletions

View file

@ -125,7 +125,7 @@ in
(sources.agenix + "/modules/age.nix")
(import sources.url-eater).nixosModules.default
sources.url-eater.asFlake.nixosModules.default
(sources.nixos-hardware + "/framework/13-inch/7040-amd")
@ -190,7 +190,7 @@ in
# Extern modules
#
(sources.agenix + "/modules/age-home.nix")
(import sources.wired-notify).homeManagerModules.default
sources.wired-notify.asFlake.homeManagerModules.default
];
}

View file

@ -62,10 +62,8 @@ config =
, commands =
[ Run $ DateZone "%a %d %H:%M:%S" "" "" "hereClock" (1 &second)
, Run $ DateZone "%H:%M" "" "America/Aruba" "arubaClock" (10 &second)
, Run $ DateZone "%H:%M" "" "Europe/Dublin" "dublinClock" (10 &second)
, Run $ DateZone "%H:%M" "" "America/New_York" "newYorkClock" (10 &second)
, Run $ DateZone "%H:%M" "" "Europe/Paris" "cetClock" (10 &second)
, Run $ DateZone "%H:%M" "" "Europe/Paris" "parisClock" (10 &second)
, Run $ DateZone "%H:%M" "" "Asia/Taipei" "tstClock" (10 &second)
, Run $
Com
@ -76,8 +74,7 @@ config =
, "--target", "2025-09-16=snip snip"
, "--target", "2025-10-13=no teef"
, "--target", "2025-10-31=dragon book"
, "--target", "2025-11-21=scalpel"
, "--target", "2025-11-21=baguette"
, "--target", "2025-11-19=scalpel"
, "--target", "2025-11-29=à deux"
, "--target", "2025-12-16=dragon book"
, "--target", "2025-12-30=seule"
@ -125,10 +122,8 @@ config =
<> alignSep config
<> intercalate "|"
[ (unwords . map greyFg)
[ "[AUA: %arubaClock%]"
, "[DUB: %dublinClock%]"
, "[JFK: %newYorkClock%]"
, "[CDG: %cetClock%]"
[ "[DUB: %dublinClock%]"
, "[CDG: %parisClock%]"
, "[TPE: %tstClock%]"
]
<> " "

View file

@ -25,7 +25,6 @@ library
hs-source-dirs: lib
exposed-modules:
XMonad.Layout.Reflect.Message
XMonad.Layout.ResizableTile.FixDescription
Data.Char.Greek
executable leanamonad

View file

@ -1,23 +0,0 @@
{-# 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) =
(fmap . fmap) RTFixDescription . handleMessage l
description (RTFixDescription l) =
description l <> " " <> show (_nmaster l)

View file

@ -13,12 +13,12 @@ import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.OnPropertyChange
import XMonad.Hooks.RefocusLast
import XMonad.Hooks.StatusBar
import XMonad.Layout.FocusTracking
import XMonad.Layout.NoBorders
import XMonad.Layout.Reflect
import XMonad.Layout.Reflect.Message
import XMonad.Layout.Renamed
import XMonad.Layout.ResizableTile
import XMonad.Layout.ResizableTile.FixDescription
import XMonad.Layout.Spacing
import qualified XMonad.StackSet as W
import XMonad.Util.EZConfig
@ -27,7 +27,9 @@ import XMonad.Util.NamedScratchpad
import XMonad.Util.SpawnOnce
import XMonad.Layout.Magnifier
import Data.Function
import Data.Char.Greek
import Data.Ratio
import Data.Semigroup
import qualified Data.Map.Strict as M
import System.Posix
@ -38,10 +40,10 @@ main =
xmonad
-- Fix all java things that don't scale with XMonad
-- https://wiki.archlinux.org/title/java#Gray_window,_applications_not_resizing_with_WM,_menus_immediately_closing
. javaHack
. withSB xmobarConfig . docks
. setEwmhActivateHook myActivateHook
. ewmhFullscreen . ewmh
$ javaHack
$ withSB xmobarConfig . docks
$ setEwmhActivateHook myActivateHook
$ ewmhFullscreen . ewmh
$ def
{ modMask = superMask
, borderWidth = 5
@ -62,14 +64,14 @@ main =
`additionalKeys` keybinds
myLayout =
let tallr = renamed [ KeepWordsRight 2 ] {- keep "ResizableTall n" -}
let tallr = renamed [ Replace "Tall" ]
$ 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
in avoidStruts
$ smartBorders
$ mag tallr ||| focusTracking Full
isSioyek :: Query Bool
isSioyek = className =? "sioyek"
@ -148,27 +150,35 @@ myManageHook =
]
<> namedScratchpadManageHook myScratchpads
-- TODO: is there a way to always open certain sites in new windows in firefox?
-- TODO: stop full screen when move happens
myEventHandleHook :: Event -> X All
myEventHandleHook =
-- TODO: is there a way to always open certain sites in new windows in firefox?
onTitleChange $ composeAll
[ isSpotify --> doShiftAndViewIfMoved multimediaWS
, isYouTube --> doShiftAndViewIfMoved multimediaWS
, isDiscord --> doShiftAndViewIfMoved chatWS
, isWhatsApp --> doShiftAndViewIfMoved chatWS
, isElement --> doShiftAndViewIfMoved chatWS
-- If the title changes in the background, we don't want to greedy view that workspace.
-- Imagine Spotify playing in the background, a track change would focus that workspace.
-- We prevent this by checking if the window is in the current workspace
onTitleChange
$ (windowIsInCurrentWorkspace -->)
$ composeAll
[ isSpotify --> doShiftAndGreedyView multimediaWS
, isYouTube --> doShiftAndGreedyView multimediaWS
, isDiscord --> doShiftAndGreedyView chatWS
, isWhatsApp --> doShiftAndGreedyView chatWS
, isElement --> doShiftAndGreedyView chatWS
]
-- If the title changes in the background, we don't want to greedy view that workspace.
-- Imagine Spotify playing in the background, a track change would focus that workspace.
-- We prevent this by checking if the window is already there.
doShiftAndViewIfMoved :: WorkspaceId -> Query (Endo WindowSet)
doShiftAndViewIfMoved n = doF . shiftAndViewIfMoved n =<< ask
doShiftAndGreedyView :: WorkspaceId -> Query (Endo WindowSet)
doShiftAndGreedyView n = doF . go =<< ask
where go :: Window -> WindowSet -> WindowSet
go w s = W.greedyView n $ W.shiftWin n w s
shiftAndViewIfMoved :: WorkspaceId -> Window -> WindowSet -> WindowSet
shiftAndViewIfMoved n w s = case W.findTag w s of
Just from | n `W.tagMember` s && n /= from -> W.greedyView n $ W.shiftWin n w s
_ -> s
hasProp :: (Window -> WindowSet -> Bool) -> Query Bool
hasProp f = f <$> ask <*> (liftX $ gets windowset)
windowIsInCurrentWorkspace :: Query Bool
windowIsInCurrentWorkspace = hasProp $ \w s -> case W.findTag w s of
Just from | from == W.currentTag s -> True
_ -> False
myStartupHook :: X ()
myStartupHook = do
@ -315,21 +325,41 @@ chatWS :: WorkspaceId
chatWS = myWorkspaces !! 3
centeredFloat, smallFloat, fullFloat, buttomRightFloat :: W.RationalRect
centeredFloat = W.RationalRect (1/9) (1/9) (7/9) (7/9)
smallFloat = W.RationalRect (3/5) (3/5) (2/7) (2/7)
centeredFloat = W.RationalRect (1%9) (1%9) (7%9) (7%9)
smallFloat = W.RationalRect (3%5) (3%5) (2%7) (2%7)
fullFloat = W.RationalRect 0 0 1 1
buttomRightFloat = W.RationalRect (1/2) (1/2) (1/2) (1/2)
buttomRightFloat = W.RationalRect (1%2) (1%2) (1%2) (1%2)
xmobarConfig :: StatusBarConfig
xmobarConfig = statusBarProp "xmobar -x 0" (pure myPrettyPrinter)
xmobarConfig = statusBarProp "xmobar -x 0" myPrettyPrinter
where
myPrettyPrinter =
filterOutWsPP [scratchpadWorkspaceTag]
$ def
{ ppCurrent = xmobarColor "#000000" "#ffffff" . wrap " " " " . fmap toUpper
, ppHiddenNoWindows = xmobarColor "#9c9c9c" "" . const ""
, ppSep = " | "
}
mkPpCurrent :: X (String -> String)
mkPpCurrent = do
windowCount <- gets $ length . W.integrate' . W.stack . W.workspace . W.current . windowset
pure $ \wid ->
wid <> (if windowCount > 1 then ":" <> show windowCount else mempty)
& xmobarColor "#000000" "#ffffff" . wrap " " " "
mkPpHidden :: X (String -> String)
mkPpHidden = do
m <- gets $ M.fromList . map (\x -> (W.tag x, length . W.integrate' . W.stack $ x)) . W.hidden . windowset
pure $ \wid ->
let windowCount = m M.! wid
in wid <> (if windowCount > 1 then ":" <> show windowCount else mempty)
& xmobarColor "#ffffff" ""
myPrettyPrinter :: X PP
myPrettyPrinter = do
myPpCurrent <- mkPpCurrent
myPpHidden <- mkPpHidden
pure
$ filterOutWsPP [scratchpadWorkspaceTag]
$ def
{ ppCurrent = myPpCurrent
, ppHiddenNoWindows = xmobarColor "#9c9c9c" "" . const ""
, ppHidden = myPpHidden
, ppSep = " | "
}
myScratchpads :: [NamedScratchpad]
myScratchpads =