about summary refs log tree commit diff
path: root/src
diff options
context:
space:
mode:
authorAzat Bahawi <azahi@teknik.io>2021-11-23 03:19:06 +0300
committerAzat Bahawi <azahi@teknik.io>2021-11-23 03:19:06 +0300
commit729e030dd25da2e36fa5a1312b8ecb3415dc1675 (patch)
tree53166b6c3bd96f860d0a7242353ef9cc7bb1790f /src
parentRemove tests (diff)
Huge update
Diffstat (limited to 'src')
-rw-r--r--src/XMonad/Actions/FloatSnapSpaced.hs154
-rw-r--r--src/XMonad/Actions/PerConditionKeys.hs34
-rw-r--r--src/XMonad/Custom/Workspaces.hs34
-rw-r--r--src/exe/Main.hs (renamed from src/Main.hs)17
-rw-r--r--src/lib/XMonad/Custom/Bindings.hs (renamed from src/XMonad/Custom/Bindings.hs)34
-rw-r--r--src/lib/XMonad/Custom/Event.hs (renamed from src/XMonad/Custom/Event.hs)13
-rw-r--r--src/lib/XMonad/Custom/Layout.hs (renamed from src/XMonad/Custom/Layout.hs)17
-rw-r--r--src/lib/XMonad/Custom/Log.hs (renamed from src/XMonad/Custom/Log.hs)14
-rw-r--r--src/lib/XMonad/Custom/Manage.hs (renamed from src/XMonad/Custom/Manage.hs)14
-rw-r--r--src/lib/XMonad/Custom/Misc.hs (renamed from src/XMonad/Custom/Misc.hs)15
-rw-r--r--src/lib/XMonad/Custom/Navigation.hs (renamed from src/XMonad/Custom/Navigation.hs)13
-rw-r--r--src/lib/XMonad/Custom/Projects.hs (renamed from src/XMonad/Custom/Projects.hs)13
-rw-r--r--src/lib/XMonad/Custom/Prompt.hs (renamed from src/XMonad/Custom/Prompt.hs)15
-rw-r--r--src/lib/XMonad/Custom/Scratchpads.hs (renamed from src/XMonad/Custom/Scratchpads.hs)13
-rw-r--r--src/lib/XMonad/Custom/Startup.hs (renamed from src/XMonad/Custom/Startup.hs)14
-rw-r--r--src/lib/XMonad/Custom/Theme.hs (renamed from src/XMonad/Custom/Theme.hs)15
-rw-r--r--src/lib/XMonad/Custom/Workspaces.hs18
17 files changed, 127 insertions, 320 deletions
diff --git a/src/XMonad/Actions/FloatSnapSpaced.hs b/src/XMonad/Actions/FloatSnapSpaced.hs
deleted file mode 100644
index ad14016..0000000
--- a/src/XMonad/Actions/FloatSnapSpaced.hs
+++ /dev/null
@@ -1,154 +0,0 @@
--- |
--- Module      : XMonad.Actions.FloatSnapSpaced
--- Copyright   : (c) 2009 Anders Engstrom <ankaan@gmail.com>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
---
-
-module XMonad.Actions.FloatSnapSpaced
-  ( snapSpacedMagicMove
-  ) where
-
-import           Data.List
-import           Data.Maybe
-import           Data.Set                       ( fromList )
-import           XMonad
-import           XMonad.Hooks.ManageDocks
-import qualified XMonad.StackSet               as S
-
-snapSpacedMagicMove :: Int -> Maybe Int -> Maybe Int -> Window -> X ()
-snapSpacedMagicMove spacing collidedist snapdist w =
-  whenX (isClient w) $ withDisplay $ \d -> do
-    io $ raiseWindow d w
-    wa <- io $ getWindowAttributes d w
-
-    nx <- handleAxis True d wa
-    ny <- handleAxis False d wa
-
-    io $ moveWindow d w (fromIntegral nx) (fromIntegral ny)
-    float w
- where
-  handleAxis horiz d wa = do
-    ((mbl, mbr, bs), (mfl, mfr, fs)) <- getSnap horiz collidedist d w
-    return $ if bs || fs
-      then wpos wa
-      else
-        let
-          b = case (mbl, mbr) of
-            (Just bl, Just br) ->
-              if wpos wa - bl < br - wpos wa then bl + spacing else br + spacing
-            (Just bl, Nothing) -> bl + spacing
-            (Nothing, Just br) -> br + spacing
-            (Nothing, Nothing) -> wpos wa + spacing
-
-          f = case (mfl, mfr) of
-            (Just fl, Just fr) ->
-              if wpos wa + wdim wa - fl < fr - wpos wa - wdim wa
-                then fl - spacing
-                else fr - spacing
-            (Just fl, Nothing) -> fl - spacing
-            (Nothing, Just fr) -> fr - spacing
-            (Nothing, Nothing) -> wpos wa - spacing
-
-          newpos = if abs (b - wpos wa) <= abs (f - wpos wa - wdim wa)
-            then b
-            else f - wdim wa
-        in
-          if isNothing snapdist || abs (newpos - wpos wa) <= fromJust snapdist
-            then newpos
-            else wpos wa
-    where (wpos, wdim, _, _) = constructors horiz
-
-getSnap
-  :: Bool
-  -> Maybe Int
-  -> Display
-  -> Window
-  -> X ((Maybe Int, Maybe Int, Bool), (Maybe Int, Maybe Int, Bool))
-getSnap horiz collidedist d w = do
-  wa     <- io $ getWindowAttributes d w
-  screen <- S.current <$> gets windowset
-  let sr = screenRect $ S.screenDetail screen
-      wl = S.integrate' . S.stack $ S.workspace screen
-  gr  <- fmap ($ sr) $ calcGap $ fromList [minBound .. maxBound]
-  wla <- filter (collides wa)
-    <$> io (mapM (getWindowAttributes d) $ filter (/= w) wl)
-
-  return
-    ( neighbours (back wa sr gr wla)  (wpos wa)
-    , neighbours (front wa sr gr wla) (wpos wa + wdim wa)
-    )
- where
-  wborder                        = fromIntegral . wa_border_width
-
-  (wpos   , wdim   , rpos, rdim) = constructors horiz
-  (refwpos, refwdim, _   , _   ) = constructors $ not horiz
-
-  back wa sr gr wla =
-    dropWhile (< rpos sr)
-      $ takeWhile (< rpos sr + rdim sr)
-      $ sort
-      $ rpos sr
-      : rpos gr
-      : (rpos gr + rdim gr)
-      : foldr
-          (\a as -> wpos a : (wpos a + wdim a + wborder a + wborder wa) : as)
-          []
-          wla
-
-  front wa sr gr wla =
-    dropWhile (<= rpos sr)
-      $ takeWhile (<= rpos sr + rdim sr)
-      $ sort
-      $ (rpos gr - 2 * wborder wa)
-      : (rpos gr + rdim gr - 2 * wborder wa)
-      : (rpos sr + rdim sr - 2 * wborder wa)
-      : foldr
-          (\a as -> (wpos a - wborder a - wborder wa) : (wpos a + wdim a) : as)
-          []
-          wla
-
-  neighbours l v =
-    ( listToMaybe $ reverse $ takeWhile (< v) l
-    , listToMaybe $ dropWhile (<= v) l
-    , v `elem` l
-    )
-
-  collides wa oa = case collidedist of
-    Nothing -> True
-    Just dist ->
-      refwpos oa
-        -  wborder oa
-        <  refwpos wa
-        +  refwdim wa
-        +  wborder wa
-        +  dist
-        && refwpos wa
-        -  wborder wa
-        -  dist
-        <  refwpos oa
-        +  refwdim oa
-        +  wborder oa
-
-
-constructors
-  :: Bool
-  -> ( WindowAttributes -> Int
-     , WindowAttributes -> Int
-     , Rectangle -> Int
-     , Rectangle -> Int
-     )
-constructors True =
-  ( fromIntegral . wa_x
-  , fromIntegral . wa_width
-  , fromIntegral . rect_x
-  , fromIntegral . rect_width
-  )
-constructors False =
-  ( fromIntegral . wa_y
-  , fromIntegral . wa_height
-  , fromIntegral . rect_y
-  , fromIntegral . rect_height
-  )
diff --git a/src/XMonad/Actions/PerConditionKeys.hs b/src/XMonad/Actions/PerConditionKeys.hs
deleted file mode 100644
index 09372cd..0000000
--- a/src/XMonad/Actions/PerConditionKeys.hs
+++ /dev/null
@@ -1,34 +0,0 @@
--- |
--- Module      : XMonad.Actions.PerConditionKeys
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
---
-
-module XMonad.Actions.PerConditionKeys
-  ( XCond(..)
-  , chooseAction
-  , bindOn
-  ) where
-
-import           Data.List
-import           XMonad
-import qualified XMonad.StackSet               as S
-
-data XCond = WS | LD
-
-chooseAction :: XCond -> (String -> X ()) -> X ()
-chooseAction WS f = withWindowSet (f . S.currentTag)
-chooseAction LD f =
-  withWindowSet (f . description . S.layout . S.workspace . S.current)
-
-bindOn :: XCond -> [(String, X ())] -> X ()
-bindOn xc bindings = chooseAction xc chooser
- where
-  chooser x = case find ((x ==) . fst) bindings of
-    Just (_, action) -> action
-    Nothing          -> case find (("" ==) . fst) bindings of
-      Just (_, action) -> action
-      Nothing          -> return ()
diff --git a/src/XMonad/Custom/Workspaces.hs b/src/XMonad/Custom/Workspaces.hs
deleted file mode 100644
index 65d1b14..0000000
--- a/src/XMonad/Custom/Workspaces.hs
+++ /dev/null
@@ -1,34 +0,0 @@
--- |
--- Module      : XMonad.Custom.Workspaces
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
---
-
-module XMonad.Custom.Workspaces
-  ( workspaces
-  ) where
-
-import           XMonad.Actions.DynamicProjects
-import           XMonad.Core             hiding ( workspaces )
-
-workspaces :: [WorkspaceId]
-workspaces = map show [1 .. 9 :: Int]
-
-projects :: [Project]
-projects =
-  [ Project { projectName      = "scratch"
-            , projectDirectory = "~/"
-            , projectStartHook = Nothing
-            }
-  , Project { projectName      = "www"
-            , projectDirectory = "~/"
-            , projectStartHook = Nothing
-            }
-  , Project { projectName      = "mail"
-            , projectDirectory = "~/"
-            , projectStartHook = Nothing
-            }
-  ]
diff --git a/src/Main.hs b/src/exe/Main.hs
index 74b63a1..3a57650 100644
--- a/src/Main.hs
+++ b/src/exe/Main.hs
@@ -1,10 +1,12 @@
 -- |
--- Module      : Main
--- Copyright   : (c) 2018-2020 Azat Bahawi
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : Main
+-- Description             : Entrypoint
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
+--
 
 module Main where
 
@@ -17,7 +19,6 @@ import           XMonad                         ( Default(def)
                                                   , handleEventHook
                                                   , keys
                                                   , layoutHook
-                                                  , logHook
                                                   , manageHook
                                                   , modMask
                                                   , mouseBindings
@@ -33,7 +34,6 @@ import           XMonad.Actions.Navigation2D    ( withNavigation2DConfig )
 import qualified XMonad.Custom.Bindings        as C
 import qualified XMonad.Custom.Event           as C
 import qualified XMonad.Custom.Layout          as C
-import qualified XMonad.Custom.Log             as C
 import qualified XMonad.Custom.Manage          as C
 import qualified XMonad.Custom.Misc            as C
 import qualified XMonad.Custom.Navigation      as C
@@ -61,7 +61,6 @@ main =
           , focusedBorderColor = C.colorF
           , modMask            = C.modMask
           , keys               = C.keys
-          , logHook            = C.logHook
           , startupHook        = C.startupHook
           , mouseBindings      = C.mouseBindings
           , manageHook         = C.manageHook
diff --git a/src/XMonad/Custom/Bindings.hs b/src/lib/XMonad/Custom/Bindings.hs
index de0fd26..208ccdf 100644
--- a/src/XMonad/Custom/Bindings.hs
+++ b/src/lib/XMonad/Custom/Bindings.hs
@@ -1,12 +1,13 @@
 {-# LANGUAGE LambdaCase #-}
 
 -- |
--- Module      : XMonad.Custom.Bindings
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Bindings
+-- Description             : Key bindings and keys configuration
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
 --
 
 module XMonad.Custom.Bindings
@@ -29,10 +30,8 @@ import           XMonad.Actions.DynamicWorkspaces
 import qualified XMonad.Actions.FlexibleManipulate
                                                as F
 import           XMonad.Actions.FloatSnap
-import           XMonad.Actions.FloatSnapSpaced
 import           XMonad.Actions.MessageFeedback
 import           XMonad.Actions.Navigation2D
-import           XMonad.Actions.PerConditionKeys
 import           XMonad.Actions.Promote
 import           XMonad.Actions.UpdatePointer
 import           XMonad.Actions.WithAll
@@ -70,6 +69,7 @@ wsKeys = map show [1 .. 9 :: Int]
 
 zipKeys :: [a] -> [[a]] -> [t1] -> (t1 -> b) -> [([a], b)]
 zipKeys m ks as f = zipWith (\k d -> (m ++ k, f d)) ks as
+
 zipKeys' :: [a] -> [[a]] -> [t1] -> (t1 -> t2 -> b) -> t2 -> [([a], b)]
 zipKeys' m ks as f b = zipWith (\k d -> (m ++ k, f d b)) ks as
 
@@ -126,8 +126,9 @@ rawKeys c = withUpdatePointer $ concatMap ($ c) keymaps
 keysBase :: XConfig Layout -> [(String, X ())]
 keysBase _ =
   [ ("M-S-q", confirmPrompt hotPromptTheme "Quit XMonad?" $ io exitSuccess)
-  , ("M-q"  , spawn "xmonad --restart") -- TODO Replace with interal calls
-  , ("M-C-q", spawn "xmonad --recompile && xmonad --restart")
+  , ("M-q"  , spawn "xmonad --restart")
+  , -- TODO Replace with interal calls
+    ("M-C-q", spawn "xmonad --recompile && xmonad --restart")
   , ("M-x"  , shellPrompt promptTheme)
   , ("M-w"  , windowPrompt promptTheme Goto allWindows)
   , ("M-S-w", windowPrompt promptTheme Bring allWindows)
@@ -135,8 +136,9 @@ keysBase _ =
 
 keysSystem :: XConfig Layout -> [(String, X ())]
 keysSystem _ =
-  [ ("M-C-g"            , return ()) -- TODO Replace scripts with internal functions
-  , ("<XF86ScreenSaver>", spawn "~/.xmonad/scripts/screenlock.sh")
+  [ ("M-C-g"            , return ())
+  , -- TODO Replace scripts with internal functions
+    ("<XF86ScreenSaver>", spawn "~/.xmonad/scripts/screenlock.sh")
   , ("M-<Print>", spawn "~/.xmonad/scripts/xshot-upload.sh")
   , ("M-S-<Print>", spawn "~/.xmonad/scripts/xshot-select-upload.sh")
   , ("M-C-c", spawn "~/.xmonad/scripts/toggle-compton.sh")
@@ -189,17 +191,13 @@ keysWindows _ =
   [ ("M-d"  , kill)
     , ("M-S-d", confirmPrompt hotPromptTheme "Kill all" killAll)
     , ("M-a"  , toggleCopyToAll)
-    , ("M-e"  , withFocused hideWindow) -- FIXME This is so broken
+    , ("M-e"  , withFocused hideWindow)
     , ("M-S-e", popOldestHiddenWindow)
     , ("M-p"  , promote)
     , ("M-g", withFocused $ sendMessage . MergeAll)
     , ("M-S-g", withFocused $ sendMessage . UnMerge)
     , ("M-u"  , focusUrgent)
     , ("M-s"  , windows S.focusMaster)
-    , ( "M-'"
-      , bindOn LD [("Tabs", windows S.focusDown), ("", onGroup S.focusDown')]
-      )
-    , ("M-;", bindOn LD [("Tabs", windows S.focusUp), ("", onGroup S.focusUp')])
     , ("M-S-'", windows S.swapDown)
     , ("M-S-;", windows S.swapUp)
     ]
@@ -245,7 +243,7 @@ mouseBindings XConfig{} = M.fromList
     , \w ->
       focus w
         >> F.mouseWindow F.position w
-        >> ifClick (snapSpacedMagicMove gapFull (Just 50) (Just 50) w)
+        >> ifClick (snapMagicMove (Just 50) (Just 50) w)
         >> windows S.shiftMaster
     )
   , ( (modMask, button3)
diff --git a/src/XMonad/Custom/Event.hs b/src/lib/XMonad/Custom/Event.hs
index f55511d..9ff2552 100644
--- a/src/XMonad/Custom/Event.hs
+++ b/src/lib/XMonad/Custom/Event.hs
@@ -1,10 +1,11 @@
 -- |
--- Module      : XMonad.Custom.Event
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Event
+-- Description             : Event hooks and stuff
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
 --
 
 module XMonad.Custom.Event
diff --git a/src/XMonad/Custom/Layout.hs b/src/lib/XMonad/Custom/Layout.hs
index fe9224a..8ed7d08 100644
--- a/src/XMonad/Custom/Layout.hs
+++ b/src/lib/XMonad/Custom/Layout.hs
@@ -1,15 +1,16 @@
-{-# LANGUAGE DeriveDataTypeable    #-}
+{-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
-{-# LANGUAGE TypeSynonymInstances  #-}
+{-# LANGUAGE TypeSynonymInstances #-}
 {-# OPTIONS_GHC -Wno-missing-signatures #-}
 
 -- |
--- Module      : XMonad.Custom.Layout
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Layout
+-- Description             : Layouts and such
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
 --
 
 module XMonad.Custom.Layout
diff --git a/src/XMonad/Custom/Log.hs b/src/lib/XMonad/Custom/Log.hs
index 6b7af37..e9d3c1a 100644
--- a/src/XMonad/Custom/Log.hs
+++ b/src/lib/XMonad/Custom/Log.hs
@@ -1,10 +1,12 @@
 -- |
--- Module      : XMonad.Custom.Log
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Log
+-- Description             : Loggers and statusbar configuration
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
+--
 
 module XMonad.Custom.Log
   ( logHook
diff --git a/src/XMonad/Custom/Manage.hs b/src/lib/XMonad/Custom/Manage.hs
index ac4201b..dbc560e 100644
--- a/src/XMonad/Custom/Manage.hs
+++ b/src/lib/XMonad/Custom/Manage.hs
@@ -1,10 +1,11 @@
 -- |
--- Module      : XMonad.Custom.Manage
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Manage
+-- Description             : Window management hooks and scratchpads
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
 --
 
 module XMonad.Custom.Manage
@@ -44,7 +45,6 @@ composeActions =
   tileBelow        = insertPosition Below Newer
   tileBelowNoFocus = insertPosition Below Older
 
-
 manageHook :: ManageHook
 manageHook = mconcat
   [ manageDocks
diff --git a/src/XMonad/Custom/Misc.hs b/src/lib/XMonad/Custom/Misc.hs
index aa48ee2..b9901b4 100644
--- a/src/XMonad/Custom/Misc.hs
+++ b/src/lib/XMonad/Custom/Misc.hs
@@ -1,12 +1,14 @@
 {-# OPTIONS_GHC -funbox-strict-fields #-}
 
 -- |
--- Module      : XMonad.Custom.Misc
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Misc
+-- Description             : Miscellaneous functions and constants
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
+--
 
 module XMonad.Custom.Misc
   ( Applications(..)
@@ -23,6 +25,7 @@ data Applications = Applications
   }
   deriving (Eq, Show)
 
+
 applications :: Applications
 applications = Applications { browser = "qutebrowser"
                             , mixer   = "pulsemixer"
diff --git a/src/XMonad/Custom/Navigation.hs b/src/lib/XMonad/Custom/Navigation.hs
index 812dd30..2646db4 100644
--- a/src/XMonad/Custom/Navigation.hs
+++ b/src/lib/XMonad/Custom/Navigation.hs
@@ -1,10 +1,11 @@
 -- |
--- Module      : XMonad.Custom.Navigation
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Navigation
+-- Description             : Window navigation and layouts
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
 --
 
 module XMonad.Custom.Navigation
diff --git a/src/XMonad/Custom/Projects.hs b/src/lib/XMonad/Custom/Projects.hs
index 4726fc7..9fa7a37 100644
--- a/src/XMonad/Custom/Projects.hs
+++ b/src/lib/XMonad/Custom/Projects.hs
@@ -1,10 +1,11 @@
 -- |
--- Module      : XMonad.Custom.Projects
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Projects
+-- Description             : Per-project workspaces
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
 --
 
 module XMonad.Custom.Projects
diff --git a/src/XMonad/Custom/Prompt.hs b/src/lib/XMonad/Custom/Prompt.hs
index e8762d1..c54a00f 100644
--- a/src/XMonad/Custom/Prompt.hs
+++ b/src/lib/XMonad/Custom/Prompt.hs
@@ -1,10 +1,11 @@
 -- |
--- Module      : XMonad.Custom.Prompt
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Prompt
+-- Description             : Prompt configuration
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
 --
 
 module XMonad.Custom.Prompt
@@ -14,7 +15,7 @@ module XMonad.Custom.Prompt
   ) where
 
 import           Data.Char
-import           Data.List
+import           Data.List                      ( isInfixOf )
 import           XMonad.Prompt
 
 listCompFunc :: XPConfig -> [String] -> String -> IO [String]
diff --git a/src/XMonad/Custom/Scratchpads.hs b/src/lib/XMonad/Custom/Scratchpads.hs
index 157a1fb..5570435 100644
--- a/src/XMonad/Custom/Scratchpads.hs
+++ b/src/lib/XMonad/Custom/Scratchpads.hs
@@ -1,10 +1,11 @@
 -- |
--- Module      : XMonad.Custom.Scratchpads
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Scratchpads
+-- Description             : Scratchpads configuration
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
 --
 
 module XMonad.Custom.Scratchpads
diff --git a/src/XMonad/Custom/Startup.hs b/src/lib/XMonad/Custom/Startup.hs
index cdd63ac..f2415ea 100644
--- a/src/XMonad/Custom/Startup.hs
+++ b/src/lib/XMonad/Custom/Startup.hs
@@ -1,10 +1,12 @@
 -- |
--- Module      : XMonad.Custom.Startup
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Startup
+-- Description             : Startup hooks
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
+--
 
 module XMonad.Custom.Startup
   ( startupHook
diff --git a/src/XMonad/Custom/Theme.hs b/src/lib/XMonad/Custom/Theme.hs
index 64b52a8..cfcd176 100644
--- a/src/XMonad/Custom/Theme.hs
+++ b/src/lib/XMonad/Custom/Theme.hs
@@ -1,10 +1,11 @@
 -- |
--- Module      : XMonad.Custom.Theme
--- Copyright   : (c) 2018-2020 Azat Bahawi <azahi@teknik.io>
--- License     : BSD3-style (see LICENSE)
--- Maintainer  : Azat Bahawi <azahi@teknik.io>
--- Stability   : unstable
--- Portability : unportable
+-- Module                  : XMonad.Custom.Theme
+-- Description             : Theming and styles
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
 --
 
 module XMonad.Custom.Theme
@@ -37,7 +38,7 @@ module XMonad.Custom.Theme
 
 import           Data.Char
 import           Data.Function
-import           Data.List
+import           Data.List                      ( isInfixOf )
 import           Data.Ratio
 import           Graphics.X11.Xlib.Types
 import           XMonad.Layout.Decoration
diff --git a/src/lib/XMonad/Custom/Workspaces.hs b/src/lib/XMonad/Custom/Workspaces.hs
new file mode 100644
index 0000000..ba2a1e7
--- /dev/null
+++ b/src/lib/XMonad/Custom/Workspaces.hs
@@ -0,0 +1,18 @@
+-- |
+-- Module                  : XMonad.Custom.Workspaces
+-- Description             : General workspace configuration
+-- Copyright               : (c) Azat Bahawi 2018-2021
+-- SPDX-License-Identifier : GPL-3.0-or-later
+-- Maintainer              : azahi@teknik.io
+-- Stability               : experimental
+-- Portability             : non-portable
+--
+
+module XMonad.Custom.Workspaces
+  ( workspaces
+  ) where
+
+import           XMonad.Core             hiding ( workspaces )
+
+workspaces :: [WorkspaceId]
+workspaces = map show [1 .. 9 :: Int]

Consider giving Nix/NixOS a try! <3