Skip to content
Snippets Groups Projects
Commit 79353b6c authored by Edward Z. Yang's avatar Edward Z. Yang
Browse files

Add compatibility implementation of unsetEnv.


Signed-off-by: default avatarEdward Z. Yang <ezyang@cs.stanford.edu>
parent 56b7eb7a
No related branches found
No related tags found
No related merge requests found
......@@ -3,15 +3,24 @@
{-# OPTIONS_HADDOCK hide #-}
module Distribution.Compat.Environment
( getEnvironment, lookupEnv, setEnv )
( getEnvironment, lookupEnv, setEnv, unsetEnv )
where
import Prelude ()
import Distribution.Compat.Prelude
#ifndef mingw32_HOST_OS
#if __GLASGOW_HASKELL__ < 708
import Foreign.C.Error (throwErrnoIf_)
#endif
#endif
import qualified System.Environment as System
#if __GLASGOW_HASKELL__ >= 706
import System.Environment (lookupEnv)
#if __GLASGOW_HASKELL__ >= 708
import System.Environment (unsetEnv)
#endif
#else
import Distribution.Compat.Exception (catchIO)
#endif
......@@ -86,3 +95,34 @@ setEnv_ key value = do
foreign import ccall unsafe "setenv"
c_setenv :: CString -> CString -> CInt -> IO CInt
#endif /* mingw32_HOST_OS */
#if __GLASGOW_HASKELL__ < 708
-- | @unsetEnv name@ removes the specified environment variable from the
-- environment of the current process.
--
-- Throws `Control.Exception.IOException` if @name@ is the empty string or
-- contains an equals sign.
--
-- @since 4.7.0.0
unsetEnv :: String -> IO ()
#ifdef mingw32_HOST_OS
unsetEnv key = withCWString key $ \k -> do
success <- c_SetEnvironmentVariable k nullPtr
unless success $ do
-- We consider unsetting an environment variable that does not exist not as
-- an error, hence we ignore eRROR_ENVVAR_NOT_FOUND.
err <- c_GetLastError
unless (err == eRROR_ENVVAR_NOT_FOUND) $ do
throwGetLastError "unsetEnv"
#else
unsetEnv key = withFilePath key (throwErrnoIf_ (/= 0) "unsetEnv" . c_unsetenv)
#if __GLASGOW_HASKELL__ > 706
foreign import ccall unsafe "__hsbase_unsetenv" c_unsetenv :: CString -> IO CInt
#else
-- HACK: We hope very hard that !UNSETENV_RETURNS_VOID
foreign import ccall unsafe "unsetenv" c_unsetenv :: CString -> IO CInt
#endif
#endif
#endif
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment