{-# LINE 1 "System/Posix/Env.hsc" #-}{-# LANGUAGE CApiFFI #-}{-# LANGUAGE Safe #-}------------------------------------------------------------------------------- |-- Module : System.Posix.Env-- Copyright : (c) The University of Glasgow 2002-- License : BSD-style (see the file libraries/base/LICENSE)---- Maintainer : libraries@haskell.org-- Stability : provisional-- Portability : non-portable (requires POSIX)---- POSIX environment support-------------------------------------------------------------------------------moduleSystem.Posix.Env(getEnv ,getEnvDefault ,getEnvironmentPrim ,getEnvironment ,setEnvironment ,putEnv ,setEnv ,unsetEnv ,clearEnv )whereimportForeignhiding(void)importForeign.C.Error(throwErrnoIfMinus1_)importForeign.C.TypesimportForeign.C.StringimportControl.MonadimportData.Maybe(fromMaybe)importSystem.Posix.InternalsimportqualifiedSystem.Posix.Env.Internal asInternal-- |'getEnv' looks up a variable in the environment.getEnv ::String{- ^ variable name -}->IO(MaybeString){- ^ variable value -}getEnv :: String -> IO (Maybe String) getEnv String name =doCString litstring <-String -> (CString -> IO CString) -> IO CString forall a. String -> (CString -> IO a) -> IO a withFilePathString name CString -> IO CString c_getenv ifCString litstring CString -> CString -> Bool forall a. Eq a => a -> a -> Bool /=CString forall a. Ptr a nullPtrthenString -> Maybe String forall a. a -> Maybe a Just(String -> Maybe String) -> IO String -> IO (Maybe String) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>CString -> IO String peekFilePathCString litstring elseMaybe String -> IO (Maybe String) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnMaybe String forall a. Maybe a Nothing-- |'getEnvDefault' is a wrapper around 'getEnv' where the-- programmer can specify a fallback if the variable is not found-- in the environment.getEnvDefault ::String{- ^ variable name -}->String{- ^ fallback value -}->IOString{- ^ variable value or fallback value -}getEnvDefault :: String -> String -> IO String getEnvDefault String name String fallback =String -> Maybe String -> String forall a. a -> Maybe a -> a fromMaybeString fallback (Maybe String -> String) -> IO (Maybe String) -> IO String forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>String -> IO (Maybe String) getEnv String name foreignimportccallunsafe"getenv"c_getenv ::CString->IOCStringgetEnvironmentPrim ::IO[String]getEnvironmentPrim :: IO [String] getEnvironmentPrim =IO [CString] Internal.getEnvironmentPrim IO [CString] -> ([CString] -> IO [String]) -> IO [String] forall a b. IO a -> (a -> IO b) -> IO b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>=(CString -> IO String) -> [CString] -> IO [String] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b] mapMCString -> IO String peekFilePath-- |'getEnvironment' retrieves the entire environment as a-- list of @(key,value)@ pairs.getEnvironment ::IO[(String,String)]{- ^ @[(key,value)]@ -}getEnvironment :: IO [(String, String)] getEnvironment =do[String] env <-IO [String] getEnvironmentPrim [(String, String)] -> IO [(String, String)] forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return([(String, String)] -> IO [(String, String)]) -> [(String, String)] -> IO [(String, String)] forall a b. (a -> b) -> a -> b $(String -> (String, String)) -> [String] -> [(String, String)] forall a b. (a -> b) -> [a] -> [b] map((String, String) -> (String, String) dropEq ((String, String) -> (String, String)) -> (String -> (String, String)) -> String -> (String, String) forall b c a. (b -> c) -> (a -> b) -> a -> c .((Char -> Bool) -> String -> (String, String) forall a. (a -> Bool) -> [a] -> ([a], [a]) break(Char -> Char -> Bool forall a. Eq a => a -> a -> Bool (==)Char '=')))[String] env wheredropEq :: (String, String) -> (String, String) dropEq (String x ,Char '=':String ys )=(String x ,String ys )dropEq (String x ,String _)=String -> (String, String) forall a. HasCallStack => String -> a error(String -> (String, String)) -> String -> (String, String) forall a b. (a -> b) -> a -> b $String "getEnvironment: insane variable "String -> String -> String forall a. [a] -> [a] -> [a] ++String x -- |'setEnvironment' resets the entire environment to the given list of-- @(key,value)@ pairs.setEnvironment ::[(String,String)]{- ^ @[(key,value)]@ -}->IO()setEnvironment :: [(String, String)] -> IO () setEnvironment [(String, String)] env =doIO () clearEnv [(String, String)] -> ((String, String) -> IO ()) -> IO () forall (t :: * -> *) (m :: * -> *) a b. (Foldable t, Monad m) => t a -> (a -> m b) -> m () forM_[(String, String)] env (((String, String) -> IO ()) -> IO ()) -> ((String, String) -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\(String key ,String value )->String -> String -> Bool -> IO () setEnv String key String value Bool True{-overwrite-}-- |The 'unsetEnv' function deletes all instances of the variable name-- from the environment.unsetEnv ::String{- ^ variable name -}->IO(){-# LINE 95 "System/Posix/Env.hsc" #-}unsetEnv :: String -> IO () {-# LINE 96 "System/Posix/Env.hsc" #-} unsetEnvname=withFilePathname$\s->throwErrnoIfMinus1_"unsetenv"(c_unsetenvs)-- POSIX.1-2001 compliant unsetenv(3)foreignimportcapiunsafe"HsUnix.h unsetenv"c_unsetenv ::CString->IOCInt{-# LINE 109 "System/Posix/Env.hsc" #-}{-# LINE 112 "System/Posix/Env.hsc" #-}-- |'putEnv' function takes an argument of the form @name=value@-- and is equivalent to @setEnv(key,value,True{-overwrite-})@.putEnv ::String{- ^ "key=value" -}->IO()putEnv :: String -> IO () putEnv String keyvalue =doCString s <-String -> IO CString newFilePathString keyvalue -- Do not free `s` after calling putenv.-- According to SUSv2, the string passed to putenv-- becomes part of the environment. #7342String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "putenv"(CString -> IO CInt c_putenv CString s )foreignimportccallunsafe"putenv"c_putenv ::CString->IOCInt{- |The 'setEnv' function inserts or resets the environment variable name in the current environment list. If the variable @name@ does not exist in the list, it is inserted with the given value. If the variable does exist, the argument @overwrite@ is tested; if @overwrite@ is @False@, the variable is not reset, otherwise it is reset to the given value. -}setEnv ::String{- ^ variable name -}->String{- ^ variable value -}->Bool{- ^ overwrite -}->IO(){-# LINE 139 "System/Posix/Env.hsc" #-}setEnvkeyvalueovrwrt=dowithFilePathkey$\keyP->withFilePathvalue$\valueP->throwErrnoIfMinus1_"setenv"$c_setenvkeyPvalueP(fromIntegral(fromEnumovrwrt))foreignimportccallunsafe"setenv"c_setenv ::CString->CString->CInt->IOCInt{-# LINE 155 "System/Posix/Env.hsc" #-}-- |The 'clearEnv' function clears the environment of all name-value pairs.clearEnv ::IO()clearEnv :: IO () {-# LINE 159 "System/Posix/Env.hsc" #-} clearEnv=voidc_clearenvforeignimportccallunsafe"clearenv"c_clearenv ::IOInt{-# LINE 170 "System/Posix/Env.hsc" #-}