Skip to content

Instantly share code, notes, and snippets.

@portnov
Created January 1, 2024 17:21
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save portnov/4db3caf2cc606d96accef78a514281ff to your computer and use it in GitHub Desktop.
Save portnov/4db3caf2cc606d96accef78a514281ff to your computer and use it in GitHub Desktop.
Default layouts
module DefaultLayouts where
import Control.Monad
import qualified Data.Set as S
import qualified Data.Map as M
import XMonad
import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Utils
type LayoutPerWorkspace = M.Map WorkspaceId String
newtype SeenWorkspaces = SeenWorkspaces (S.Set WorkspaceId)
deriving (Eq, Read, Show, Typeable)
instance ExtensionClass SeenWorkspaces where
initialValue = SeenWorkspaces S.empty
extensionType = PersistentExtension
dfltLayoutPerWorkspace :: LayoutPerWorkspace -> X ()
dfltLayoutPerWorkspace m = do
wksp <- getCurrentWorkspace
SeenWorkspaces seen <- XS.get
unless (wksp `S.member` seen) $ do
whenJust (M.lookup wksp m) $ \layoutName -> do
sendMessage (JumpToLayout layoutName)
XS.put $ SeenWorkspaces $ S.insert wksp seen
import DefaultLayouts
myLayouts = named "tall" (Tall 1 (1/100) (1/2)) ||| named "grid" Grid ||| ...
dfltLayouts = M.fromList [("1", "tall"), ("2", "grid"), ...]
main = xmonad $ def {
workspaces = ["1", "2", "3" ...],
layoutHook = myLayouts,
logHook = dfltLayoutPerWorkspace dfltLayouts
}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment