mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-06 15:01:53 -07:00
Merge pull request #491 from liskin/pr/dynamicicons-changes
X.H.DynamicIcons: Cleanups, docs improvements, composability with other *PPs
This commit is contained in:
@@ -477,7 +477,8 @@ Here is a list of the modules found in @XMonad.Hooks@:
|
|||||||
One-shot and permanent ManageHooks that can be updated at runtime.
|
One-shot and permanent ManageHooks that can be updated at runtime.
|
||||||
|
|
||||||
* "XMonad.Hooks.DynamicIcons":
|
* "XMonad.Hooks.DynamicIcons":
|
||||||
Dynamic Icons based on Windows in Workspaces
|
Dynamically augment workspace names logged to a status bar via DynamicLog
|
||||||
|
based on the contents (windows) of the workspace.
|
||||||
|
|
||||||
* "XMonad.Hooks.DynamicLog": for use with 'XMonad.Core.logHook'; send
|
* "XMonad.Hooks.DynamicLog": for use with 'XMonad.Core.logHook'; send
|
||||||
information about xmonad's state to standard output, suitable for
|
information about xmonad's state to standard output, suitable for
|
||||||
|
@@ -1,3 +1,4 @@
|
|||||||
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
{-# LANGUAGE TupleSections #-}
|
{-# LANGUAGE TupleSections #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
@@ -9,7 +10,8 @@
|
|||||||
-- Stability : unstable
|
-- Stability : unstable
|
||||||
-- Portability : unportable
|
-- Portability : unportable
|
||||||
--
|
--
|
||||||
-- Dynamically change workspace text based on the contents of the workspace
|
-- Dynamically augment workspace names logged to a status bar via DynamicLog
|
||||||
|
-- based on the contents (windows) of the workspace.
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
module XMonad.Hooks.DynamicIcons (
|
module XMonad.Hooks.DynamicIcons (
|
||||||
@@ -17,11 +19,12 @@ module XMonad.Hooks.DynamicIcons (
|
|||||||
-- $usage
|
-- $usage
|
||||||
|
|
||||||
-- * Creating Dynamic Icons
|
-- * Creating Dynamic Icons
|
||||||
dynamicLogIconsWithPP, dynamicLogIconsConvert,
|
dynamicLogIconsWithPP, appIcon,
|
||||||
|
|
||||||
-- * Data Types
|
-- * Customization
|
||||||
appIcon, IconSet,
|
dynamicIconsPP, getWorkspaceIcons,
|
||||||
IconConfig(..), Icon(..),
|
IconConfig(..),
|
||||||
|
iconsFmtAppend, iconsFmtReplace, wrapUnwords,
|
||||||
|
|
||||||
) where
|
) where
|
||||||
import XMonad
|
import XMonad
|
||||||
@@ -30,112 +33,144 @@ import qualified XMonad.StackSet as S
|
|||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
|
||||||
import XMonad.Hooks.DynamicLog
|
import XMonad.Hooks.DynamicLog
|
||||||
import Data.Maybe (catMaybes)
|
import Data.Functor ((<&>))
|
||||||
|
import Data.Traversable (for)
|
||||||
|
import Control.Monad ((<=<), (>=>))
|
||||||
|
|
||||||
-- $usage
|
-- $usage
|
||||||
-- Dynamically changes a 'Workspace's 'WorkspaceId' based on the 'Window's inside the Workspace.
|
-- Dynamically augment Workspace's 'WorkspaceId' as shown on a status bar
|
||||||
-- 'IconSet's describe which icons are shown depending on which windows fit a 'Query'.
|
-- based on the 'Window's inside the Workspace.
|
||||||
--
|
--
|
||||||
-- To create an 'IconSet' make a 'Query' that returns a ['Icon'].
|
-- Icons are specified by a @Query [String]@, which is something like a
|
||||||
|
-- 'ManageHook' (and uses the same syntax) that returns a list of 'String's
|
||||||
|
-- (icons). This 'Query' is evaluated for each window and the results are
|
||||||
|
-- joined together. 'appIcon' is a useful shortcut here.
|
||||||
--
|
--
|
||||||
-- 'appIcon' can be used to simplify this process
|
-- For example:
|
||||||
-- For example,
|
|
||||||
--
|
--
|
||||||
-- > icons :: IconSet
|
-- > myIcons :: Query [String]
|
||||||
-- > icons = composeAll
|
-- > myIcons = composeAll
|
||||||
-- > [ className =? "discord" --> appIcon "\xfb6e"
|
-- > [ className =? "discord" --> appIcon "\xfb6e"
|
||||||
-- > , className =? "Discord" --> appIcon "\xf268"
|
-- > , className =? "Discord" --> appIcon "\xf268"
|
||||||
-- > , className =? "Firefox" --> appIcon "\63288"
|
-- > , className =? "Firefox" --> appIcon "\63288"
|
||||||
-- > , className =? "Spotify" <||> className =? "spotify" --> appIcon "阮"
|
-- > , className =? "Spotify" <||> className =? "spotify" --> appIcon "阮"
|
||||||
-- > ]
|
-- > ]
|
||||||
--
|
--
|
||||||
-- then you can add the hook to your config
|
-- then you can add the hook to your config:
|
||||||
--
|
--
|
||||||
-- > xmonad $ def
|
-- > main = xmonad $ … $ def
|
||||||
-- > { logHook = dynamicLogIconsWithPP icons xmobarPP <> myManageHook
|
-- > { logHook = dynamicLogIconsWithPP icons xmobarPP
|
||||||
-- > }
|
-- > , … }
|
||||||
--
|
--
|
||||||
-- Here is an example of this
|
-- Here is an example of this
|
||||||
--
|
--
|
||||||
-- <<https://imgur.com/download/eauPNPz/Dynamic%20Icons%20in%20XMonad>>
|
-- <<https://user-images.githubusercontent.com/300342/111010930-36a54300-8398-11eb-8aec-b3059b04fa31.png>>
|
||||||
--
|
--
|
||||||
-- NOTE: You can use any string you want here. The example shown here, uses NerdFont Icons to represent open applications
|
-- Note: You can use any string you want here.
|
||||||
|
-- The example shown here uses NerdFont Icons to represent open applications.
|
||||||
|
|
||||||
-- | Custom datatype for custom icons based on the state of the 'Workspace'
|
|
||||||
-- For example,
|
|
||||||
--
|
--
|
||||||
-- > Icon "<bold>discord</bold>" "<bold>discord</bold>" "discord" ""
|
-- If you want to customize formatting and/or combine this with other
|
||||||
|
-- 'PP' extensions like "XMonad.Util.ClickableWorkspaces", here's a more
|
||||||
|
-- advanced example how to do that:
|
||||||
--
|
--
|
||||||
-- Then you can add it to your IconSet.
|
-- > myIconConfig = def{ iconConfigIcons = myIcons, iconConfigFmt = iconsFmtAppend concat }
|
||||||
--
|
-- > main = xmonad $ … $ def
|
||||||
-- > icons :: IconSet
|
-- > { logHook = xmonadPropLog =<< dynamicLogString =<< clickablePP =<<
|
||||||
-- > icons = mconcat
|
-- > dynamicIconsPP myIconConfig xmobarPP
|
||||||
-- > [ className =? "discord" --> pure [Icon "<bold>discord</bold>" "<bold>discord</bold>" "discord" ""]
|
-- > , … }
|
||||||
-- > ]
|
|
||||||
data Icon = Icon
|
|
||||||
{ iconCurrent :: !String -- ^ If the 'Workspace' is the current workspace
|
|
||||||
, iconVisible :: !String -- ^ If the 'Workspace' is visible (Xinerama only)
|
|
||||||
, iconHidden :: !String -- ^ If the 'Workspace' isnt visible but still has windows
|
|
||||||
, iconHiddenNoWindows :: !String -- ^ If the 'Workspace' isnt visible and has no windows
|
|
||||||
}
|
|
||||||
|
|
||||||
-- | The set of Icons to use
|
|
||||||
type IconSet = Query [Icon]
|
|
||||||
|
|
||||||
baseIconSet :: String -> Icon
|
-- | Shortcut for configuring single icons.
|
||||||
baseIconSet x =
|
appIcon :: String -> Query [String]
|
||||||
Icon { iconCurrent = x
|
appIcon = pure . pure
|
||||||
, iconVisible = x
|
|
||||||
, iconHidden = x
|
|
||||||
, iconHiddenNoWindows = x
|
|
||||||
}
|
|
||||||
|
|
||||||
-- | Create an 'IconSet' from a 'String'
|
|
||||||
appIcon :: String -> IconSet
|
|
||||||
appIcon x = pure [baseIconSet x]
|
|
||||||
|
|
||||||
-- | Adjusts the 'PP' and then runs 'dynamicLogWithPP'
|
-- | Adjusts the 'PP' and then runs 'dynamicLogWithPP'
|
||||||
dynamicLogIconsWithPP :: IconSet -- ^ The 'IconSet' to use
|
dynamicLogIconsWithPP :: Query [String] -- ^ The 'IconSet' to use
|
||||||
-> PP -- ^ The 'PP' to alter
|
-> PP -- ^ The 'PP' to alter
|
||||||
-> X () -- ^ The resulting 'X' action
|
-> X () -- ^ The resulting 'X' action
|
||||||
dynamicLogIconsWithPP iconset pp = dynamicLogWithPP =<< dynamicLogIconsConvert (def{ iconConfigIcons = iconset, iconConfigPP = pp })
|
dynamicLogIconsWithPP q = dynamicLogWithPP <=< dynamicIconsPP def{ iconConfigIcons = q }
|
||||||
|
|
||||||
|
-- | Modify "XMonad.Hooks.DynamicLog"\'s pretty-printing format to augment
|
||||||
|
-- workspace names with icons based on the contents (windows) of the workspace.
|
||||||
|
dynamicIconsPP :: IconConfig -> PP -> X PP
|
||||||
|
dynamicIconsPP ic pp = getWorkspaceIcons ic <&> \ren -> pp{ ppRename = ppRename pp >=> ren }
|
||||||
|
|
||||||
|
-- | Returns a function for 'ppRename' that augments workspaces with icons
|
||||||
|
-- according to the provided 'IconConfig'.
|
||||||
|
getWorkspaceIcons :: IconConfig -> X (String -> WindowSpace -> String)
|
||||||
|
getWorkspaceIcons IconConfig{..} = fmt <$> getWorkspaceIcons' iconConfigIcons
|
||||||
|
where
|
||||||
|
fmt icons s w = iconConfigFmt s (M.findWithDefault [] (S.tag w) icons)
|
||||||
|
|
||||||
|
getWorkspaceIcons' :: Query [String] -> X (M.Map WorkspaceId [String])
|
||||||
|
getWorkspaceIcons' q = do
|
||||||
|
ws <- gets (S.workspaces . windowset)
|
||||||
|
is <- for ws $ foldMap (runQuery q) . S.integrate' . S.stack
|
||||||
|
pure $ M.fromList (zip (map S.tag ws) is)
|
||||||
|
|
||||||
|
|
||||||
-- | Datatype for expanded 'Icon' configurations
|
-- | Datatype for expanded 'Icon' configurations
|
||||||
data IconConfig = IconConfig
|
data IconConfig = IconConfig
|
||||||
{ iconConfigIcons :: IconSet -- ^ The 'IconSet' to use
|
{ iconConfigIcons :: Query [String]
|
||||||
, iconConfigStack :: [String] -> String -- ^ The function to manage stacking of 'Icon's
|
-- ^ What icons to use for each window.
|
||||||
, iconConfigPP :: PP -- ^ The 'PP' to alter
|
, iconConfigFmt :: WorkspaceId -> [String] -> String
|
||||||
|
-- ^ How to format the result, see 'iconsFmtReplace', 'iconsFmtAppend'.
|
||||||
}
|
}
|
||||||
|
|
||||||
instance Default IconConfig where
|
instance Default IconConfig where
|
||||||
def = IconConfig
|
def = IconConfig
|
||||||
{ iconConfigIcons = mempty
|
{ iconConfigIcons = mempty
|
||||||
, iconConfigStack = wrap "[" "]" . unwords
|
, iconConfigFmt = iconsFmtReplace (wrapUnwords "{" "}")
|
||||||
, iconConfigPP = def
|
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | This is the same as 'dynamicLogIconsWithPP' but it takes a 'IconConfig'.
|
-- | 'iconConfigFmt' that replaces the workspace name with icons, if any.
|
||||||
-- This allows you to manually customise the 'Icon's the stacking function and also your `PP`
|
--
|
||||||
dynamicLogIconsConvert :: IconConfig -> X PP
|
-- First parameter specifies how to concatenate multiple icons. Useful values
|
||||||
dynamicLogIconsConvert iconConfig = do
|
-- include: 'concat', 'unwords', 'wrapUnwords'.
|
||||||
ws <- gets (S.workspaces . windowset)
|
--
|
||||||
icons <- M.fromList . catMaybes <$> mapM (getIcons (iconConfigIcons iconConfig)) ws
|
-- ==== __Examples__
|
||||||
pure $ (iconConfigPP iconConfig)
|
--
|
||||||
{ ppCurrent = ppSection ppCurrent iconCurrent icons
|
-- >>> iconsFmtReplace concat "1" []
|
||||||
, ppVisible = ppSection ppVisible iconVisible icons
|
-- "1"
|
||||||
, ppHidden = ppSection ppHidden iconHidden icons
|
--
|
||||||
, ppHiddenNoWindows = ppSection ppHiddenNoWindows iconHiddenNoWindows icons
|
-- >>> iconsFmtReplace concat "1" ["A", "B"]
|
||||||
}
|
-- "AB"
|
||||||
where
|
--
|
||||||
ppSection pF f icons = pF (iconConfigPP iconConfig) . concatIcons f . iconLookup icons
|
-- >>> iconsFmtReplace (wrapUnwords "{" "}") "1" ["A", "B"]
|
||||||
iconLookup icons x = M.findWithDefault [baseIconSet x] x icons
|
-- "{A B}"
|
||||||
concatIcons f y
|
iconsFmtReplace :: ([String] -> String) -> WorkspaceId -> [String] -> String
|
||||||
| length y > 1 = iconConfigStack iconConfig $ map f y
|
iconsFmtReplace cat ws is | null is = ws
|
||||||
| otherwise = concatMap f y
|
| otherwise = cat is
|
||||||
|
|
||||||
|
-- | 'iconConfigFmt' that appends icons to the workspace name.
|
||||||
|
--
|
||||||
|
-- First parameter specifies how to concatenate multiple icons. Useful values
|
||||||
|
-- include: 'concat', 'unwords', 'wrapUnwords'.
|
||||||
|
--
|
||||||
|
-- ==== __Examples__
|
||||||
|
--
|
||||||
|
-- >>> iconsFmtAppend concat "1" []
|
||||||
|
-- "1"
|
||||||
|
--
|
||||||
|
-- >>> iconsFmtAppend concat "1" ["A", "B"]
|
||||||
|
-- "1:AB"
|
||||||
|
iconsFmtAppend :: ([String] -> String) -> WorkspaceId -> [String] -> String
|
||||||
|
iconsFmtAppend cat ws is | null is = ws
|
||||||
|
| otherwise = ws ++ ':' : cat is
|
||||||
|
|
||||||
getIcons :: IconSet -> WindowSpace -> X (Maybe (WorkspaceId, [Icon]))
|
-- | Join words with spaces, and wrap the result in delimiters unless there
|
||||||
getIcons is w = do
|
-- was exactly one element.
|
||||||
validIcons <- sequence $ foldMap (runQuery is) . S.integrate <$> S.stack w
|
--
|
||||||
pure $ (S.tag w,) <$> (validIcons >>= \x -> if null x then Nothing else Just x)
|
-- ==== __Examples__
|
||||||
|
--
|
||||||
|
-- >>> wrapUnwords "{" "}" ["A", "B"]
|
||||||
|
-- "{A B}"
|
||||||
|
--
|
||||||
|
-- >>> wrapUnwords "{" "}" ["A"]
|
||||||
|
-- "A"
|
||||||
|
--
|
||||||
|
-- >>> wrapUnwords "{" "}" []
|
||||||
|
-- ""
|
||||||
|
wrapUnwords :: String -> String -> [String] -> String
|
||||||
|
wrapUnwords _ _ [x] = x
|
||||||
|
wrapUnwords l r xs = wrap l r (unwords xs)
|
||||||
|
Reference in New Issue
Block a user