Skip to content

Commit

Permalink
Unset GHC_ENVIRONMENT and GHC_PACKAGE_PATH before invocing GHC
Browse files Browse the repository at this point in the history
When we are invoked under Stack (as part of HIE's test suite for example)
our choice of Cabal library when invoking GHC gets interferred with by the
GHC_ENVIRONMENT variable.

Since we're just using boot packages simply unsetting GHC package related
envvars seems like a fairly decent fix here. See the issue below for more
details.

Fixes DanielG#78
  • Loading branch information
DanielG committed Jan 11, 2020
1 parent 996c067 commit 1c0f2e8
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 19 deletions.
29 changes: 13 additions & 16 deletions src/CabalHelper/Compiletime/Process.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,9 +20,9 @@ module CabalHelper.Compiletime.Process
, module System.Process
) where

import Control.Arrow (second)
import Data.Char
import Data.List
import Data.Maybe
import qualified Data.Map.Strict as Map
import GHC.IO.Exception (IOErrorType(OtherError))
import System.IO
Expand All @@ -42,7 +42,7 @@ readProcessStderr :: Verbose => Maybe FilePath -> [(String, EnvOverride)]
-> FilePath -> [String] -> String -> IO String
readProcessStderr mcwd env exe args inp = do
logProcessCall mcwd env exe args
env' <- execEnvOverrides env
env' <- execEnvOverrides env <$> getEnvironment
outp <- readCreateProcess (proc exe args)
{ cwd = mcwd
, env = if env == [] then Nothing else Just env'
Expand All @@ -57,7 +57,7 @@ callProcessStderr'
-> FilePath -> [String] -> IO ExitCode
callProcessStderr' mcwd env exe args = do
logProcessCall mcwd env exe args
env' <- execEnvOverrides env
env' <- execEnvOverrides env <$> getEnvironment
(_, _, _, h) <- createProcess (proc exe args)
{ std_out = UseHandle stderr
, env = if env == [] then Nothing else Just env'
Expand All @@ -74,21 +74,18 @@ logProcessCall mcwd env exe args = do
cd = case mcwd of
Nothing -> []; Just cwd -> [ "cd", formatProcessArg cwd++";" ]

execEnvOverride :: EnvOverride -> String -> String
execEnvOverride (EnvPrepend x) y = x ++ y
execEnvOverride (EnvAppend y) x = x ++ y
execEnvOverride (EnvReplace x) _ = x
execEnvOverride :: EnvOverride -> String -> Maybe String
execEnvOverride (EnvPrepend x) y = Just (x ++ y)
execEnvOverride (EnvAppend y) x = Just (x ++ y)
execEnvOverride (EnvSet x) _ = Just x
execEnvOverride EnvUnset _ = Nothing

execEnvOverrides :: [(String, EnvOverride)] -> IO [(String, String)]
execEnvOverrides overrides = do
envs <- getEnvironment
return $ do
(k,v) <- envs
case Map.lookup k overrides_map of
Just os -> return (k, foldr execEnvOverride v os)
Nothing -> return (k, v)
execEnvOverrides
:: [(String, EnvOverride)] -> [(String, String)] -> [(String, String)]
execEnvOverrides overrides env =
Map.toList $ foldl f (Map.fromList env) overrides
where
overrides_map = Map.fromListWith (++) $ map (second (:[])) overrides
f em (k, o) = Map.alter (execEnvOverride o . fromMaybe "") k em

-- | Essentially 'System.Process.callProcess' but with additional options
-- and logging to stderr when verbosity is enabled.
Expand Down
5 changes: 4 additions & 1 deletion src/CabalHelper/Compiletime/Program/GHC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -134,7 +134,10 @@ cabalVersionExistsInPkgDb cabalVer db@(PackageDbDir db_path) = do

invokeGhc :: Env => GhcInvocation -> IO (Either ExitCode FilePath)
invokeGhc GhcInvocation {..} = do
rv <- callProcessStderr' (Just "/") [] (ghcProgram ?progs) $ concat
-- We unset some interferring envvars here for stack, see:
-- https://github.com/DanielG/cabal-helper/issues/78#issuecomment-557860898
let eos = [("GHC_ENVIRONMENT", EnvUnset), ("GHC_PACKAGE_PATH", EnvUnset)]
rv <- callProcessStderr' (Just "/") eos (ghcProgram ?progs) $ concat
[ [ "-outputdir", giOutDir
, "-o", giOutput
]
Expand Down
5 changes: 3 additions & 2 deletions src/CabalHelper/Compiletime/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -570,9 +570,10 @@ defaultPrograms =
Programs "cabal" [] [] "stack" [] [] [] "ghc" "ghc-pkg" "haddock"

data EnvOverride
= EnvPrepend String
= EnvUnset
| EnvSet String
| EnvAppend String
| EnvReplace String
| EnvPrepend String
deriving (Eq, Ord, Show, Read, Generic, Typeable)

data CompileOptions = CompileOptions
Expand Down

0 comments on commit 1c0f2e8

Please sign in to comment.