From 64eb4e46ecffb6abd4a845c2db61d379642aa7c8 Mon Sep 17 00:00:00 2001 From: brandon s allbery kf8nh Date: Sat, 20 Aug 2022 12:00:28 -0400 Subject: [PATCH 1/2] modify `mkAbsolutePath` to support environment vars If you want more general support, comment on PR #744. --- CHANGES.md | 4 ++++ XMonad/Prelude.hs | 26 +++++++++++++++++--------- 2 files changed, 21 insertions(+), 9 deletions(-) diff --git a/CHANGES.md b/CHANGES.md index c5d33eb2b2..457ce10457 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -184,6 +184,10 @@ - Added `WindowScreen`, which is a type synonym for the specialized `Screen` type, that results from the `WindowSet` definition in `XMonad.Core`. + - Modified `mkAbsolutePath` to support a leading environment variable, so + things like `$HOME/NOTES` work. If you want more general environment + variable support, comment on [this PR]. + * `XMonad.Util.XUtils` - Added `withSimpleWindow`, `showSimpleWindow`, `WindowConfig`, and diff --git a/XMonad/Prelude.hs b/XMonad/Prelude.hs index 466290d6c4..721038f436 100644 --- a/XMonad/Prelude.hs +++ b/XMonad/Prelude.hs @@ -1,5 +1,6 @@ -{-# LANGUAGE BangPatterns #-} -{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE ScopedTypeVariables #-} -------------------------------------------------------------------- -- | -- Module : XMonad.Prelude @@ -60,6 +61,8 @@ import Data.List.NonEmpty (NonEmpty ((:|))) import Data.Tuple (swap) import GHC.Stack import System.Directory (getHomeDirectory) +import System.Environment (getEnv) +import Control.Exception (SomeException, handle) import qualified XMonad.StackSet as W -- | Short for 'fromIntegral'. @@ -80,7 +83,7 @@ chunksOf i xs = chunk : chunksOf i rest (!?) xs n | n < 0 = Nothing | otherwise = listToMaybe $ drop n xs --- | Multivariant composition. +-- | Multivariable composition. -- -- > f .: g ≡ (f .) . g ≡ \c d -> f (g c d) (.:) :: (a -> b) -> (c -> d -> a) -> c -> d -> b @@ -108,14 +111,19 @@ safeGetWindowAttributes w = withDisplay $ \dpy -> io . alloca $ \p -> -- * If it starts with @~\/@, replace that with the actual home -- * directory. -- --- * Otherwise, prepend a @\/@ to the path. +-- * If it starts with @$@, read the name of an environment +-- * variable and replace it with the contents of that. +-- +-- * Otherwise, prepend the home directory and @\/@ to the path. mkAbsolutePath :: MonadIO m => FilePath -> m FilePath mkAbsolutePath ps = do - home <- liftIO getHomeDirectory - pure $ case ps of - '/' : _ -> ps - '~' : '/' : _ -> home <> drop 1 ps - _ -> home <> ('/' : ps) + home <- io getHomeDirectory + case ps of + '/' : _ -> pure ps + '~' : '/' : _ -> pure (home <> drop 1 ps) + '$' : _ -> let (v,ps') = span (`elem` ("_"<>['A'..'Z']<>['a'..'z']<>['0'..'9'])) (drop 1 ps) + in io ((\(_ :: SomeException) -> pure "") `handle` getEnv v) Exports.<&> (<> ps') + _ -> pure (home <> ('/' : ps)) {-# SPECIALISE mkAbsolutePath :: FilePath -> IO FilePath #-} {-# SPECIALISE mkAbsolutePath :: FilePath -> X FilePath #-} From 2c5ea5f94aee8c5669598316e0376fe5082a1efd Mon Sep 17 00:00:00 2001 From: brandon s allbery kf8nh Date: Sat, 20 Aug 2022 12:01:42 -0400 Subject: [PATCH 2/2] change `XMonad.Prompt.AppendFile` to use `mkAbsolutePath` --- CHANGES.md | 7 +++++++ XMonad/Prompt/AppendFile.hs | 3 ++- 2 files changed, 9 insertions(+), 1 deletion(-) diff --git a/CHANGES.md b/CHANGES.md index 457ce10457..bd29dfcf1c 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -94,6 +94,11 @@ ### Bug Fixes and Minor Changes + * `XMonad.Prompt.AppendFile` + + - Use `XMonad.Prelude.mkAbsolutePath` to force names to be relative to the + home directory and support `~/` prefixes. + * `XMonad.Prompt.OrgMode` - Fixes the date parsing issue such that entries with format of @@ -225,6 +230,8 @@ - Added a `Default` instance for `UrgencyConfig` and `DzenUrgencyHook`. +[this PR]: https://github.com/xmonad/xmonad-contrib/pull/744 + ### Other changes * Migrated the sample build scripts from the deprecated `xmonad-testing` repo to diff --git a/XMonad/Prompt/AppendFile.hs b/XMonad/Prompt/AppendFile.hs index 99fe376df1..f802d737ac 100644 --- a/XMonad/Prompt/AppendFile.hs +++ b/XMonad/Prompt/AppendFile.hs @@ -30,6 +30,7 @@ module XMonad.Prompt.AppendFile ( import XMonad.Core import XMonad.Prompt +import XMonad.Prelude (mkAbsolutePath) import System.IO @@ -91,4 +92,4 @@ appendFilePrompt' c trans fn = mkXPrompt (AppendFile fn) -- | Append a string to a file. doAppend :: (String -> String) -> FilePath -> String -> X () -doAppend trans fn = io . withFile fn AppendMode . flip hPutStrLn . trans +doAppend trans fn s = mkAbsolutePath fn >>= \f -> (io . withFile f AppendMode . flip hPutStrLn . trans) s