diff --git a/CHANGES.md b/CHANGES.md
index 649e2acd..0d9868db 100644
--- a/CHANGES.md
+++ b/CHANGES.md
@@ -78,6 +78,10 @@
     but handle the wrapping case by exchanging the windows at either end of the stack
     instead of rotating the stack.
 
+  * `XMonad.Hooks.DynamicIcons`
+
+    Added Dynamic Strings as `dynamicLogIconWithPP` based on a Workspaces Windows
+
   * `XMonad.Hooks.WindowSwallowing`
 
     A handleEventHook that implements window swallowing:
diff --git a/XMonad/Doc/Extending.hs b/XMonad/Doc/Extending.hs
index 93710831..c52099db 100644
--- a/XMonad/Doc/Extending.hs
+++ b/XMonad/Doc/Extending.hs
@@ -476,6 +476,9 @@ Here is a list of the modules found in @XMonad.Hooks@:
 * "XMonad.Hooks.DynamicHooks":
     One-shot and permanent ManageHooks that can be updated at runtime.
 
+* "XMonad.Hooks.DynamicIcons":
+    Dynamic Icons based on Windows in Workspaces
+
 * "XMonad.Hooks.DynamicLog": for use with 'XMonad.Core.logHook'; send
   information about xmonad's state to standard output, suitable for
   putting in a status bar of some sort. See
diff --git a/XMonad/Hooks/DynamicIcons.hs b/XMonad/Hooks/DynamicIcons.hs
new file mode 100644
index 00000000..44dc7fbd
--- /dev/null
+++ b/XMonad/Hooks/DynamicIcons.hs
@@ -0,0 +1,141 @@
+{-# LANGUAGE TupleSections #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Hooks.DynamicIcons
+-- Copyright   :  (c) Will Pierlot <willp@outlook.com.au>
+-- License     :  BSD3-style (see LICENSE)
+--
+-- Maintainer  :  Will Pierlot <willp@outlook.com.au>
+-- Stability   :  unstable
+-- Portability :  unportable
+--
+-- Dynamically change workspace text based on the contents of the workspace
+-----------------------------------------------------------------------------
+
+module XMonad.Hooks.DynamicIcons (
+    -- * Usage
+    -- $usage
+
+    -- * Creating Dynamic Icons
+    dynamicLogIconsWithPP, dynamicLogIconsConvert,
+
+    -- * Data Types
+    appIcon, IconSet,
+    IconConfig(..), Icon(..),
+
+    ) where
+import XMonad
+
+import qualified XMonad.StackSet as S
+import qualified Data.Map as M
+
+import XMonad.Hooks.DynamicLog
+import Data.Maybe (catMaybes)
+
+-- $usage
+--  Dynamically changes a 'Workspace's 'WorkspaceId' based on the 'Window's inside the Workspace.
+-- 'IconSet's describe which icons are shown depending on which windows fit a 'Query'.
+--
+-- To create an 'IconSet' make a 'Query' that returns a ['Icon'].
+--
+-- 'appIcon' can be used to simplify this process
+-- For example,
+--
+-- > icons :: IconSet
+-- > icons = composeAll
+-- >           [ className =? "discord" --> appIcon "\xfb6e"
+-- >           , className =? "Discord" --> appIcon "\xf268"
+-- >           , className =? "Firefox" --> appIcon "\63288"
+-- >           , className =? "Spotify" <||> className =? "spotify" --> appIcon "阮"
+-- >           ]
+--
+-- then you can add the hook to your config
+--
+-- > xmonad $ def
+-- >      { logHook = dynamicLogIconsWithPP icons xmobarPP <> myManageHook
+-- >      }
+--
+--  Here is an example of this
+--
+--  <<https://imgur.com/download/eauPNPz/Dynamic%20Icons%20in%20XMonad>>
+--  
+--  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" ""
+--
+-- Then you can add it to your IconSet.
+--
+-- > icons :: IconSet
+-- > icons = mconcat
+-- >    [ 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
+baseIconSet x =
+    Icon { iconCurrent = x
+         , 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'
+dynamicLogIconsWithPP :: IconSet -- ^ The 'IconSet' to use
+                      -> PP -- ^ The 'PP' to alter
+                      -> X () -- ^ The resulting 'X' action
+dynamicLogIconsWithPP iconset pp = dynamicLogWithPP =<< dynamicLogIconsConvert (def{ iconConfigIcons = iconset, iconConfigPP = pp })
+
+-- | Datatype for expanded 'Icon' configurations
+data IconConfig = IconConfig
+    { iconConfigIcons :: IconSet -- ^ The 'IconSet' to use
+    , iconConfigStack :: [String] -> String -- ^ The function to manage stacking of 'Icon's
+    , iconConfigPP    :: PP -- ^ The 'PP' to alter
+    }
+
+instance Default IconConfig where
+    def = IconConfig
+        { iconConfigIcons = mempty
+        , iconConfigStack = wrap "[" "]" . unwords
+        , iconConfigPP = def
+        }
+
+-- | This is the same as 'dynamicLogIconsWithPP' but it takes a 'IconConfig'.
+-- This allows you to manually customise the 'Icon's the stacking function and also your `PP`
+dynamicLogIconsConvert :: IconConfig -> X PP
+dynamicLogIconsConvert iconConfig = do
+    ws <- gets (S.workspaces . windowset)
+    icons <- M.fromList . catMaybes <$> mapM (getIcons (iconConfigIcons iconConfig)) ws
+    pure $ (iconConfigPP iconConfig)
+        { ppCurrent = ppSection ppCurrent iconCurrent icons
+        , ppVisible = ppSection ppVisible iconVisible icons
+        , ppHidden = ppSection ppHidden iconHidden icons
+        , ppHiddenNoWindows =  ppSection ppHiddenNoWindows iconHiddenNoWindows icons
+        }
+  where
+    ppSection pF f icons = pF (iconConfigPP iconConfig) . concatIcons f . iconLookup icons
+    iconLookup icons x = M.findWithDefault [baseIconSet x] x icons
+    concatIcons f y
+        | length y > 1 = iconConfigStack iconConfig $ map f y
+        | otherwise = concatMap f y
+
+
+getIcons :: IconSet -> WindowSpace -> X (Maybe (WorkspaceId, [Icon]))
+getIcons is w = do
+    validIcons <- sequence $ foldMap (runQuery is) . S.integrate <$> S.stack w
+    pure $ (S.tag w,) <$> (validIcons >>= \x -> if null x then Nothing else Just x)
diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal
index 9484ec6c..10e06994 100644
--- a/xmonad-contrib.cabal
+++ b/xmonad-contrib.cabal
@@ -165,6 +165,7 @@ library
                         XMonad.Hooks.DebugStack
                         XMonad.Hooks.DynamicBars
                         XMonad.Hooks.DynamicHooks
+                        XMonad.Hooks.DynamicIcons
                         XMonad.Hooks.DynamicLog
                         XMonad.Hooks.DynamicProperty
                         XMonad.Hooks.EwmhDesktops