{-# LINE 1 "System/Environment/Blank.hsc" #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE CApiFFI #-}
module System.Environment.Blank
(
module System.Environment,
getEnv,
getEnvDefault,
setEnv,
unsetEnv,
) where
import Foreign.C
{-# LINE 48 "System/Environment/Blank.hsc" #-}
import System.Posix.Internals
{-# LINE 50 "System/Environment/Blank.hsc" #-}
import GHC.IO.Exception
import System.IO.Error
import Control.Exception.Base
import Data.Maybe
import System.Environment
(
getArgs,
getProgName,
getExecutablePath,
withArgs,
withProgName,
getEnvironment
)
{-# LINE 65 "System/Environment/Blank.hsc" #-}
import qualified System.Environment as Environment
{-# LINE 67 "System/Environment/Blank.hsc" #-}
{-# LINE 79 "System/Environment/Blank.hsc" #-}
throwInvalidArgument :: String -> IO a
throwInvalidArgument from =
throwIO (mkIOError InvalidArgument from Nothing Nothing)
getEnv :: String -> IO (Maybe String)
{-# LINE 91 "System/Environment/Blank.hsc" #-}
getEnv = Environment.lookupEnv
{-# LINE 93 "System/Environment/Blank.hsc" #-}
getEnvDefault ::
String ->
String ->
IO String
getEnvDefault name fallback = fromMaybe fallback <$> getEnv name
setEnv ::
String ->
String ->
Bool ->
IO ()
setEnv key_ value_ overwrite
| null key = throwInvalidArgument "setEnv"
| '=' `elem` key = throwInvalidArgument "setEnv"
| otherwise =
if overwrite
then setEnv_ key value
else do
env_var <- getEnv key
case env_var of
Just _ -> return ()
Nothing -> setEnv_ key value
where
key = takeWhile (/= '\NUL') key_
value = takeWhile (/= '\NUL') value_
setEnv_ :: String -> String -> IO ()
{-# LINE 133 "System/Environment/Blank.hsc" #-}
setEnv_ key value =
withFilePath key $ \ keyP ->
withFilePath value $ \ valueP ->
throwErrnoIfMinus1_ "setenv" $
c_setenv keyP valueP (fromIntegral (fromEnum True))
foreign import ccall unsafe "setenv"
c_setenv :: CString -> CString -> CInt -> IO CInt
{-# LINE 142 "System/Environment/Blank.hsc" #-}
unsetEnv :: String -> IO ()
{-# LINE 163 "System/Environment/Blank.hsc" #-}
{-# LINE 164 "System/Environment/Blank.hsc" #-}
unsetEnv name = withFilePath name $ \ s ->
throwErrnoIfMinus1_ "unsetenv" (c_unsetenv s)
foreign import capi unsafe "HsBase.h unsetenv"
c_unsetenv :: CString -> IO CInt
{-# LINE 177 "System/Environment/Blank.hsc" #-}
{-# LINE 194 "System/Environment/Blank.hsc" #-}