flake.nix: Fix build

As advised in [1], provide a way to set the path for the xmessage and
ghc binaries via XMONAD_XMESSAGE and XMONAD_GHC environment variables.

[1]: 36d5761b3e
This commit is contained in:
Tomasz Hołubowicz 2022-07-23 15:54:37 +02:00 committed by Tony Zorman
parent 366c09b3d7
commit 117583e473
2 changed files with 8 additions and 8 deletions

View File

@ -20,13 +20,10 @@
overrides = composeExtensions (old.overrides or (_: _: {})) overrides = composeExtensions (old.overrides or (_: _: {}))
(hol final prev); (hol final prev);
})); }));
patch = unstable
+ "/pkgs/development/haskell-modules/patches/xmonad_0_17_0-nix.patch";
hoverlay = final: prev: hself: hsuper: hoverlay = final: prev: hself: hsuper:
with prev.haskell.lib.compose; { with prev.haskell.lib.compose; {
xmonad = appendPatch patch xmonad = hself.callCabal2nix "xmonad"
(hself.callCabal2nix "xmonad" (git-ignore-nix.lib.gitignoreSource ./.) { };
(git-ignore-nix.lib.gitignoreSource ./.) { });
}; };
overlay = fromHOL hoverlay { }; overlay = fromHOL hoverlay { };
overlays = [ overlay ]; overlays = [ overlay ];

View File

@ -51,6 +51,7 @@ import Data.Semigroup
import Data.Traversable (for) import Data.Traversable (for)
import Data.Time.Clock (UTCTime) import Data.Time.Clock (UTCTime)
import Data.Default.Class import Data.Default.Class
import System.Environment (lookupEnv)
import System.FilePath import System.FilePath
import System.IO import System.IO
import System.Info import System.Info
@ -457,7 +458,8 @@ xfork x = io . forkProcess . finally nullStdin $ do
-- | Use @xmessage@ to show information to the user. -- | Use @xmessage@ to show information to the user.
xmessage :: MonadIO m => String -> m () xmessage :: MonadIO m => String -> m ()
xmessage msg = void . xfork $ do xmessage msg = void . xfork $ do
executeFile "xmessage" True xmessageBin <- fromMaybe "xmessage" <$> liftIO (lookupEnv "XMONAD_XMESSAGE")
executeFile xmessageBin True
[ "-default", "okay" [ "-default", "okay"
, "-xrm", "*international:true" , "-xrm", "*international:true"
, "-xrm", "*fontSet:-*-fixed-medium-r-normal-*-18-*-*-*-*-*-*-*,-*-fixed-*-*-*-*-18-*-*-*-*-*-*-*,-*-*-*-*-*-*-18-*-*-*-*-*-*-*" , "-xrm", "*fontSet:-*-fixed-medium-r-normal-*-18-*-*-*-*-*-*-*,-*-fixed-*-*-*-*-18-*-*-*-*-*-*-*,-*-*-*-*-*-*-18-*-*-*-*-*-*-*"
@ -653,8 +655,9 @@ compile dirs method =
withFile (errFileName dirs) WriteMode $ \err -> do withFile (errFileName dirs) WriteMode $ \err -> do
let run = runProc (cfgDir dirs) err let run = runProc (cfgDir dirs) err
case method of case method of
CompileGhc -> CompileGhc -> do
run "ghc" ghcArgs ghc <- fromMaybe "ghc" <$> lookupEnv "XMONAD_GHC"
run ghc ghcArgs
CompileStackGhc stackYaml -> CompileStackGhc stackYaml ->
run "stack" ["build", "--silent", "--stack-yaml", stackYaml] .&&. run "stack" ["build", "--silent", "--stack-yaml", stackYaml] .&&.
run "stack" ("ghc" : "--stack-yaml" : stackYaml : "--" : ghcArgs) run "stack" ("ghc" : "--stack-yaml" : stackYaml : "--" : ghcArgs)