Compare commits

..

4 commits

2 changed files with 33 additions and 19 deletions

View file

@ -1,4 +1,3 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module XMonad.Layout.ResizableTile.FixDescription module XMonad.Layout.ResizableTile.FixDescription
@ -15,12 +14,10 @@ newtype RTFixDescription a = RTFixDescription { unwrapRT :: ResizableTall a }
instance LayoutClass RTFixDescription a where instance LayoutClass RTFixDescription a where
runLayout (W.Workspace t l s) = runLayout (W.Workspace t l s) =
let ws' = W.Workspace t (unwrapRT l) s let ws' = W.Workspace t (unwrapRT l) s
in fmap (fmap (fmap RTFixDescription)) in (fmap . fmap . fmap) RTFixDescription . runLayout ws'
. runLayout ws'
handleMessage (RTFixDescription l) m = handleMessage (RTFixDescription l) =
fmap (fmap RTFixDescription) (fmap . fmap) RTFixDescription . handleMessage l
$ handleMessage l m
description (RTFixDescription l) = description (RTFixDescription l) =
description l <> " " <> show (_nmaster l) description l <> " " <> show (_nmaster l)

View file

@ -1,6 +1,7 @@
{-# LANGUAGE NegativeLiterals #-} {-# LANGUAGE NegativeLiterals #-}
import XMonad import XMonad
import XMonad.Actions.CopyWindow
import XMonad.Actions.Submap import XMonad.Actions.Submap
import XMonad.Actions.SwapWorkspaces import XMonad.Actions.SwapWorkspaces
import XMonad.Hooks.DynamicLog import XMonad.Hooks.DynamicLog
@ -87,8 +88,21 @@ isFirefox = className =? "firefox"
isSpotify :: Query Bool isSpotify :: Query Bool
isSpotify = isFirefox <&&> title ~? "Spotify" isSpotify = isFirefox <&&> title ~? "Spotify"
isYouTube :: Query Bool
isYouTube = isFirefox <&&> title ~? "YouTube"
isWhatsApp :: Query Bool
isWhatsApp = isFirefox <&&> title ~? "WhatsApp"
isSignal :: Query Bool
isSignal = className =? "Signal"
isElement :: Query Bool
isElement = isFirefox <&&> title ~? "Element"
-- This changes depending on the locale of the browser :/
isFirefoxPip :: Query Bool isFirefoxPip :: Query Bool
isFirefoxPip = isFirefox <&&> title =? "Picture-in-Picture" isFirefoxPip = isFirefox <&&> title =? "Incrustation vidéo"
isFeh :: Query Bool isFeh :: Query Bool
isFeh = className =? "feh" isFeh = className =? "feh"
@ -111,6 +125,7 @@ myActivateHook =
composeOne composeOne
[ isDiscord -?> mempty [ isDiscord -?> mempty
, isEvolution -?> mempty , isEvolution -?> mempty
, isSignal -?> mempty
, isSioyek -?> mempty , isSioyek -?> mempty
, isFeh -?> mempty , isFeh -?> mempty
, return True -?> doFocus , return True -?> doFocus
@ -118,16 +133,15 @@ myActivateHook =
myManageHook :: ManageHook myManageHook :: ManageHook
myManageHook = myManageHook =
composeAll composeOne
[ isNautilusPreviewer --> customFloating centeredFloat [ isNautilusPreviewer -?> customFloating centeredFloat
, isFeh --> customFloating buttomRightFloat , isFeh -?> doF copyToAll <> customFloating buttomRightFloat
, isMinder --> customFloating centeredFloat , isMinder -?> customFloating centeredFloat
, isFirefoxPip --> doFloat , isFirefoxPip -?> doF copyToAll <> customFloating buttomRightFloat
, isDiscord --> (doF $ W.shift chatWS) , isDiscord -?> doShift chatWS
, isEvolution --> (doF $ W.shift chatWS) , isEvolution -?> doShift chatWS
] , isSignal -?> doShift chatWS
<> composeOne , isFirefox -?> insertPosition Master Newer
[ isFirefox -?> insertPosition Master Newer
, isKitty -?> insertPosition Below Newer , isKitty -?> insertPosition Below Newer
, isNautilus <||> isSioyek -?> insertPosition End Older , isNautilus <||> isSioyek -?> insertPosition End Older
] ]
@ -137,8 +151,11 @@ myEventHandleHook :: Event -> X All
myEventHandleHook = myEventHandleHook =
-- TODO: is there a way to always open certain sites in new windows in firefox? -- TODO: is there a way to always open certain sites in new windows in firefox?
onTitleChange $ composeAll onTitleChange $ composeAll
[ isSpotify --> doShiftAndViewIfMoved multimediaWS [ isSpotify --> doShiftAndViewIfMoved multimediaWS
, isDiscord --> doShiftAndViewIfMoved chatWS , 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. -- If the title changes in the background, we don't want to greedy view that workspace.