mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-05 22:51:54 -07:00
Unclobber dirs/Dirs in import XMonad
"dirs" is used several times in xmonad-contrib as a short for
"directions" and when I tried renaming those uses, I had a really hard
time coming up with something nice/meaningful. Therefore I think it's
best if we rename this instead, "dirs" is a valuable part of the
namespace. :-)
Fixes: 735fb58f6c
("Revise XDG handling")
This commit is contained in:
@@ -29,7 +29,7 @@ module XMonad.Core (
|
|||||||
getAtom, spawn, spawnPID, xfork, recompile, trace, whenJust, whenX,
|
getAtom, spawn, spawnPID, xfork, recompile, trace, whenJust, whenX,
|
||||||
getXMonadDir, getXMonadCacheDir, getXMonadDataDir, stateFileName,
|
getXMonadDir, getXMonadCacheDir, getXMonadDataDir, stateFileName,
|
||||||
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_TAKE_FOCUS, withWindowAttributes,
|
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, atom_WM_TAKE_FOCUS, withWindowAttributes,
|
||||||
ManageHook, Query(..), runQuery, Directories(..), Dirs, getDirs
|
ManageHook, Query(..), runQuery, Directories'(..), Directories, getDirectories,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import XMonad.StackSet hiding (modify)
|
import XMonad.StackSet hiding (modify)
|
||||||
@@ -94,7 +94,7 @@ data XConf = XConf
|
|||||||
-- ^ position of the mouse according to
|
-- ^ position of the mouse according to
|
||||||
-- the event currently being processed
|
-- the event currently being processed
|
||||||
, currentEvent :: !(Maybe Event) -- ^ event currently being processed
|
, currentEvent :: !(Maybe Event) -- ^ event currently being processed
|
||||||
, dirs :: !Dirs -- ^ directories to use
|
, directories :: !Directories -- ^ directories to use
|
||||||
}
|
}
|
||||||
|
|
||||||
-- todo, better name
|
-- todo, better name
|
||||||
@@ -478,9 +478,9 @@ runOnWorkspaces job = do
|
|||||||
-- * @cacheDir@: This directory is used to store temporary files that
|
-- * @cacheDir@: This directory is used to store temporary files that
|
||||||
-- can easily be recreated. For example, the XPrompt history file.
|
-- can easily be recreated. For example, the XPrompt history file.
|
||||||
--
|
--
|
||||||
-- For how these directories are chosen, see 'getDirs'.
|
-- For how these directories are chosen, see 'getDirectories'.
|
||||||
--
|
--
|
||||||
data Directories a = Dirs
|
data Directories' a = Directories
|
||||||
{ dataDir :: !a
|
{ dataDir :: !a
|
||||||
, cfgDir :: !a
|
, cfgDir :: !a
|
||||||
, cacheDir :: !a
|
, cacheDir :: !a
|
||||||
@@ -489,7 +489,7 @@ data Directories a = Dirs
|
|||||||
|
|
||||||
-- | Convenient type alias for the most common case in which one might
|
-- | Convenient type alias for the most common case in which one might
|
||||||
-- want to use the 'Directories' type.
|
-- want to use the 'Directories' type.
|
||||||
type Dirs = Directories FilePath
|
type Directories = Directories' FilePath
|
||||||
|
|
||||||
-- | Build up the 'Dirs' that xmonad will use. They are chosen as
|
-- | Build up the 'Dirs' that xmonad will use. They are chosen as
|
||||||
-- follows:
|
-- follows:
|
||||||
@@ -506,13 +506,13 @@ type Dirs = Directories FilePath
|
|||||||
-- The xmonad configuration file (or the build script, if present) is
|
-- The xmonad configuration file (or the build script, if present) is
|
||||||
-- always assumed to be in @cfgDir@.
|
-- always assumed to be in @cfgDir@.
|
||||||
--
|
--
|
||||||
getDirs :: IO Dirs
|
getDirectories :: IO Directories
|
||||||
getDirs = xmEnvDirs <|> xmDirs <|> xdgDirs
|
getDirectories = xmEnvDirs <|> xmDirs <|> xdgDirs
|
||||||
where
|
where
|
||||||
-- | Check for xmonad's environment variables first
|
-- | Check for xmonad's environment variables first
|
||||||
xmEnvDirs :: IO Dirs
|
xmEnvDirs :: IO Directories
|
||||||
xmEnvDirs = do
|
xmEnvDirs = do
|
||||||
let xmEnvs = Dirs{ dataDir = "XMONAD_DATA_DIR"
|
let xmEnvs = Directories{ dataDir = "XMONAD_DATA_DIR"
|
||||||
, cfgDir = "XMONAD_CONFIG_DIR"
|
, cfgDir = "XMONAD_CONFIG_DIR"
|
||||||
, cacheDir = "XMONAD_CACHE_DIR"
|
, cacheDir = "XMONAD_CACHE_DIR"
|
||||||
}
|
}
|
||||||
@@ -520,7 +520,7 @@ getDirs = xmEnvDirs <|> xmDirs <|> xdgDirs
|
|||||||
|
|
||||||
-- | Check whether the config file or a build script is in the
|
-- | Check whether the config file or a build script is in the
|
||||||
-- @~\/.xmonad@ directory
|
-- @~\/.xmonad@ directory
|
||||||
xmDirs :: IO Dirs
|
xmDirs :: IO Directories
|
||||||
xmDirs = do
|
xmDirs = do
|
||||||
xmDir <- getAppUserDataDirectory "xmonad"
|
xmDir <- getAppUserDataDirectory "xmonad"
|
||||||
conf <- doesFileExist $ xmDir </> "xmonad.hs"
|
conf <- doesFileExist $ xmDir </> "xmonad.hs"
|
||||||
@@ -528,29 +528,29 @@ getDirs = xmEnvDirs <|> xmDirs <|> xdgDirs
|
|||||||
|
|
||||||
-- Place *everything* in ~/.xmonad if yes
|
-- Place *everything* in ~/.xmonad if yes
|
||||||
guard $ conf || build
|
guard $ conf || build
|
||||||
pure Dirs{ dataDir = xmDir, cfgDir = xmDir, cacheDir = xmDir }
|
pure Directories{ dataDir = xmDir, cfgDir = xmDir, cacheDir = xmDir }
|
||||||
|
|
||||||
-- | Use XDG directories as a fallback
|
-- | Use XDG directories as a fallback
|
||||||
xdgDirs :: IO Dirs
|
xdgDirs :: IO Directories
|
||||||
xdgDirs =
|
xdgDirs =
|
||||||
for Dirs{ dataDir = XdgData, cfgDir = XdgConfig, cacheDir = XdgCache }
|
for Directories{ dataDir = XdgData, cfgDir = XdgConfig, cacheDir = XdgCache }
|
||||||
$ \dir -> do d <- getXdgDirectory dir "xmonad"
|
$ \dir -> do d <- getXdgDirectory dir "xmonad"
|
||||||
d <$ createDirectoryIfMissing True d
|
d <$ createDirectoryIfMissing True d
|
||||||
|
|
||||||
-- | Return the path to the xmonad configuration directory.
|
-- | Return the path to the xmonad configuration directory.
|
||||||
getXMonadDir :: X String
|
getXMonadDir :: X String
|
||||||
getXMonadDir = asks (cfgDir . dirs)
|
getXMonadDir = asks (cfgDir . directories)
|
||||||
{-# DEPRECATED getXMonadDir "Use `asks (cfgDir . dirs)' instead." #-}
|
{-# DEPRECATED getXMonadDir "Use `asks (cfgDir . directories)' instead." #-}
|
||||||
|
|
||||||
-- | Return the path to the xmonad cache directory.
|
-- | Return the path to the xmonad cache directory.
|
||||||
getXMonadCacheDir :: X String
|
getXMonadCacheDir :: X String
|
||||||
getXMonadCacheDir = asks (cacheDir . dirs)
|
getXMonadCacheDir = asks (cacheDir . directories)
|
||||||
{-# DEPRECATED getXMonadCacheDir "Use `asks (cacheDir . dirs)' instead." #-}
|
{-# DEPRECATED getXMonadCacheDir "Use `asks (cacheDir . directories)' instead." #-}
|
||||||
|
|
||||||
-- | Return the path to the xmonad data directory.
|
-- | Return the path to the xmonad data directory.
|
||||||
getXMonadDataDir :: X String
|
getXMonadDataDir :: X String
|
||||||
getXMonadDataDir = asks (dataDir . dirs)
|
getXMonadDataDir = asks (dataDir . directories)
|
||||||
{-# DEPRECATED getXMonadDataDir "Use `asks (dataDir . dirs)' instead." #-}
|
{-# DEPRECATED getXMonadDataDir "Use `asks (dataDir . directories)' instead." #-}
|
||||||
|
|
||||||
-- | Get the name of the file used to store the xmonad window state.
|
-- | Get the name of the file used to store the xmonad window state.
|
||||||
stateFileName :: X FilePath
|
stateFileName :: X FilePath
|
||||||
@@ -575,8 +575,8 @@ stateFileName = (</> "xmonad.state") <$> getXMonadDataDir
|
|||||||
--
|
--
|
||||||
-- 'False' is returned if there are compilation errors.
|
-- 'False' is returned if there are compilation errors.
|
||||||
--
|
--
|
||||||
recompile :: MonadIO m => Dirs -> Bool -> m Bool
|
recompile :: MonadIO m => Directories -> Bool -> m Bool
|
||||||
recompile Dirs{ cfgDir, dataDir } force = io $ do
|
recompile Directories{ cfgDir, dataDir } force = io $ do
|
||||||
let binn = "xmonad-"++arch++"-"++os
|
let binn = "xmonad-"++arch++"-"++os
|
||||||
bin = dataDir </> binn
|
bin = dataDir </> binn
|
||||||
err = dataDir </> "xmonad.errors"
|
err = dataDir </> "xmonad.errors"
|
||||||
|
@@ -59,7 +59,7 @@ xmonad :: (LayoutClass l Window, Read (l Window)) => XConfig l -> IO ()
|
|||||||
xmonad conf = do
|
xmonad conf = do
|
||||||
installSignalHandlers -- important to ignore SIGCHLD to avoid zombies
|
installSignalHandlers -- important to ignore SIGCHLD to avoid zombies
|
||||||
|
|
||||||
dirs <- getDirs
|
dirs <- getDirectories
|
||||||
let launch' args = do
|
let launch' args = do
|
||||||
catchIO (buildLaunch dirs)
|
catchIO (buildLaunch dirs)
|
||||||
conf'@XConfig { layoutHook = Layout l }
|
conf'@XConfig { layoutHook = Layout l }
|
||||||
@@ -111,8 +111,8 @@ usage = do
|
|||||||
--
|
--
|
||||||
-- * Missing XMonad\/XMonadContrib modules due to ghc upgrade
|
-- * Missing XMonad\/XMonadContrib modules due to ghc upgrade
|
||||||
--
|
--
|
||||||
buildLaunch :: Dirs -> IO ()
|
buildLaunch :: Directories -> IO ()
|
||||||
buildLaunch dirs@Dirs{ dataDir } = do
|
buildLaunch dirs@Directories{ dataDir } = do
|
||||||
whoami <- getProgName
|
whoami <- getProgName
|
||||||
let compiledConfig = "xmonad-"++arch++"-"++os
|
let compiledConfig = "xmonad-"++arch++"-"++os
|
||||||
unless (whoami == compiledConfig) $ do
|
unless (whoami == compiledConfig) $ do
|
||||||
@@ -165,7 +165,7 @@ sendReplace = do
|
|||||||
-- function instead of 'xmonad'. You probably also want to have a key
|
-- function instead of 'xmonad'. You probably also want to have a key
|
||||||
-- binding to the 'XMonad.Operations.restart` function that restarts
|
-- binding to the 'XMonad.Operations.restart` function that restarts
|
||||||
-- your custom binary with the resume flag set to @True@.
|
-- your custom binary with the resume flag set to @True@.
|
||||||
launch :: (LayoutClass l Window, Read (l Window)) => XConfig l -> Dirs -> IO ()
|
launch :: (LayoutClass l Window, Read (l Window)) => XConfig l -> Directories -> IO ()
|
||||||
launch initxmc drs = do
|
launch initxmc drs = do
|
||||||
-- setup locale information from environment
|
-- setup locale information from environment
|
||||||
setLocale LC_ALL (Just "")
|
setLocale LC_ALL (Just "")
|
||||||
@@ -216,7 +216,7 @@ launch initxmc drs = do
|
|||||||
, mouseFocused = False
|
, mouseFocused = False
|
||||||
, mousePosition = Nothing
|
, mousePosition = Nothing
|
||||||
, currentEvent = Nothing
|
, currentEvent = Nothing
|
||||||
, dirs = drs
|
, directories = drs
|
||||||
}
|
}
|
||||||
|
|
||||||
st = XState
|
st = XState
|
||||||
|
Reference in New Issue
Block a user