{-# LINE 1 "System/Posix/Env/ByteString.hsc" #-}{-# LANGUAGE CApiFFI #-}{-# LANGUAGE Trustworthy #-}------------------------------------------------------------------------------- |-- Module : System.Posix.Env.ByteString-- 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.ByteString(-- * Environment VariablesgetEnv ,getEnvDefault ,getEnvironmentPrim ,getEnvironment ,setEnvironment ,putEnv ,setEnv ,unsetEnv ,clearEnv -- * Program arguments,getArgs )whereimportControl.MonadimportForeignimportForeign.CimportData.Maybe(fromMaybe)importSystem.Posix.Env (clearEnv )importqualifiedData.ByteStringasBimportqualifiedData.ByteString.Char8asBCimportData.ByteString(ByteString)importData.ByteString.Internal(ByteString(PS))importqualifiedSystem.Posix.Env.Internal asInternal-- |'getEnv' looks up a variable in the environment.getEnv ::ByteString{- ^ variable name -}->IO(MaybeByteString){- ^ variable value -}getEnv :: ByteString -> IO (Maybe ByteString)
getEnv ByteString
name =doCString
litstring <-ByteString -> (CString -> IO CString) -> IO CString
forall a. ByteString -> (CString -> IO a) -> IO a
B.useAsCStringByteString
name CString -> IO CString
c_getenv ifCString
litstring CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
/=CString
forall a. Ptr a
nullPtrthenByteString -> Maybe ByteString
forall a. a -> Maybe a
Just(ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>CString -> IO ByteString
B.packCStringCString
litstring elseMaybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returnMaybe ByteString
forall a. Maybe a
Nothing-- |'getEnvDefault' is a wrapper around 'getEnv' where the-- programmer can specify a fallback as the second argument, which will be-- used if the variable is not found in the environment.getEnvDefault ::ByteString{- ^ variable name -}->ByteString{- ^ fallback value -}->IOByteString{- ^ variable value or fallback value -}getEnvDefault :: ByteString -> ByteString -> IO ByteString
getEnvDefault ByteString
name ByteString
fallback =ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybeByteString
fallback (Maybe ByteString -> ByteString)
-> IO (Maybe ByteString) -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>ByteString -> IO (Maybe ByteString)
getEnv ByteString
name foreignimportccallunsafe"getenv"c_getenv ::CString->IOCStringgetEnvironmentPrim ::IO[ByteString]getEnvironmentPrim :: IO [ByteString]
getEnvironmentPrim =IO [CString]
Internal.getEnvironmentPrim IO [CString] -> ([CString] -> IO [ByteString]) -> IO [ByteString]
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 ByteString) -> [CString] -> IO [ByteString]
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 ByteString
B.packCString-- |'getEnvironment' retrieves the entire environment as a-- list of @(key,value)@ pairs.getEnvironment ::IO[(ByteString,ByteString)]{- ^ @[(key,value)]@ -}getEnvironment :: IO [(ByteString, ByteString)]
getEnvironment =do[ByteString]
env <-IO [ByteString]
getEnvironmentPrim [(ByteString, ByteString)] -> IO [(ByteString, ByteString)]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return([(ByteString, ByteString)] -> IO [(ByteString, ByteString)])
-> [(ByteString, ByteString)] -> IO [(ByteString, ByteString)]
forall a b. (a -> b) -> a -> b
$(ByteString -> (ByteString, ByteString))
-> [ByteString] -> [(ByteString, ByteString)]
forall a b. (a -> b) -> [a] -> [b]
map((ByteString, ByteString) -> (ByteString, ByteString)
dropEq ((ByteString, ByteString) -> (ByteString, ByteString))
-> (ByteString -> (ByteString, ByteString))
-> ByteString
-> (ByteString, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.((Char -> Bool) -> ByteString -> (ByteString, ByteString)
BC.break(Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
(==)Char
'=')))[ByteString]
env wheredropEq :: (ByteString, ByteString) -> (ByteString, ByteString)
dropEq (ByteString
x ,ByteString
y )|ByteString -> Char
BC.headByteString
y Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'='=(ByteString
x ,HasCallStack => ByteString -> ByteString
ByteString -> ByteString
B.tailByteString
y )|Bool
otherwise=[Char] -> (ByteString, ByteString)
forall a. HasCallStack => [Char] -> a
error([Char] -> (ByteString, ByteString))
-> [Char] -> (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$[Char]
"getEnvironment: insane variable "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ByteString -> [Char]
BC.unpackByteString
x -- |'setEnvironment' resets the entire environment to the given list of-- @(key,value)@ pairs.---- @since 2.8.0.0setEnvironment ::[(ByteString,ByteString)]{- ^ @[(key,value)]@ -}->IO()setEnvironment :: [(ByteString, ByteString)] -> IO ()
setEnvironment [(ByteString, ByteString)]
env =doIO ()
clearEnv [(ByteString, ByteString)]
-> ((ByteString, ByteString) -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_[(ByteString, ByteString)]
env (((ByteString, ByteString) -> IO ()) -> IO ())
-> ((ByteString, ByteString) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\(ByteString
key ,ByteString
value )->ByteString -> ByteString -> Bool -> IO ()
setEnv ByteString
key ByteString
value Bool
True{-overwrite-}-- |The 'unsetEnv' function deletes all instances of the variable name-- from the environment.unsetEnv ::ByteString{- ^ variable name -}->IO(){-# LINE 105 "System/Posix/Env/ByteString.hsc" #-}unsetEnv :: ByteString -> IO ()
{-# LINE 106 "System/Posix/Env/ByteString.hsc" #-} unsetEnvname=B.useAsCStringname$\s->throwErrnoIfMinus1_"unsetenv"(c_unsetenvs)-- POSIX.1-2001 compliant unsetenv(3)foreignimportcapiunsafe"HsUnix.h unsetenv"c_unsetenv ::CString->IOCInt{-# LINE 119 "System/Posix/Env/ByteString.hsc" #-}{-# LINE 122 "System/Posix/Env/ByteString.hsc" #-}-- |'putEnv' function takes an argument of the form @name=value@-- and is equivalent to @setEnv(key,value,True{-overwrite-})@.putEnv ::ByteString{- ^ "key=value" -}->IO()putEnv :: ByteString -> IO ()
putEnv (PSForeignPtr Word8
fp Int
o Int
l )=ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtrForeignPtr Word8
fp ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\Ptr Word8
p ->do-- https://pubs.opengroup.org/onlinepubs/009696899/functions/putenv.html---- "the string pointed to by string shall become part of the environment,-- so altering the string shall change the environment. The space used by-- string is no longer used once a new string which defines name is passed to putenv()."---- hence we must not free the bufferPtr Any
buf <-Int -> IO (Ptr Any)
forall a. Int -> IO (Ptr a)
mallocBytes(Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)Ptr Any -> Ptr Any -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytesPtr Any
buf (Ptr Word8
p Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr`Int
o )Int
l Ptr Any -> Int -> Word8 -> IO ()
forall b. Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOffPtr Any
buf Int
l (Word8
0::Word8)[Char] -> IO CInt -> IO ()
forall a. (Eq a, Num a) => [Char] -> IO a -> IO ()
throwErrnoIfMinus1_[Char]
"putenv"(CString -> IO CInt
c_putenv (Ptr Any -> CString
forall a b. Ptr a -> Ptr b
castPtrPtr Any
buf ))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 ::ByteString{- ^ variable name -}->ByteString{- ^ variable value -}->Bool{- ^ overwrite -}->IO(){-# LINE 156 "System/Posix/Env/ByteString.hsc" #-}setEnvkeyvalueovrwrt=doB.useAsCStringkey$\keyP->B.useAsCStringvalue$\valueP->throwErrnoIfMinus1_"setenv"$c_setenvkeyPvalueP(fromIntegral(fromEnumovrwrt))foreignimportccallunsafe"setenv"c_setenv ::CString->CString->CInt->IOCInt{-# LINE 172 "System/Posix/Env/ByteString.hsc" #-}-- | Computation 'getArgs' returns a list of the program's command-- line arguments (not including the program name), as 'ByteString's.---- Unlike 'System.Environment.getArgs', this function does no Unicode-- decoding of the arguments; you get the exact bytes that were passed-- to the program by the OS. To interpret the arguments as text, some-- Unicode decoding should be applied.--getArgs ::IO[ByteString]getArgs :: IO [ByteString]
getArgs =(Ptr CInt -> IO [ByteString]) -> IO [ByteString]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca((Ptr CInt -> IO [ByteString]) -> IO [ByteString])
-> (Ptr CInt -> IO [ByteString]) -> IO [ByteString]
forall a b. (a -> b) -> a -> b
$\Ptr CInt
p_argc ->(Ptr (Ptr CString) -> IO [ByteString]) -> IO [ByteString]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca((Ptr (Ptr CString) -> IO [ByteString]) -> IO [ByteString])
-> (Ptr (Ptr CString) -> IO [ByteString]) -> IO [ByteString]
forall a b. (a -> b) -> a -> b
$\Ptr (Ptr CString)
p_argv ->doPtr CInt -> Ptr (Ptr CString) -> IO ()
getProgArgv Ptr CInt
p_argc Ptr (Ptr CString)
p_argv Int
p <-CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral(CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peekPtr CInt
p_argc Ptr CString
argv <-Ptr (Ptr CString) -> IO (Ptr CString)
forall a. Storable a => Ptr a -> IO a
peekPtr (Ptr CString)
p_argv Int -> Ptr CString -> IO [CString]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray(Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)(Ptr CString -> Int -> Ptr CString
forall a. Storable a => Ptr a -> Int -> Ptr a
advancePtrPtr CString
argv Int
1)IO [CString] -> ([CString] -> IO [ByteString]) -> IO [ByteString]
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 ByteString) -> [CString] -> IO [ByteString]
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 ByteString
B.packCStringforeignimportccallunsafe"getProgArgv"getProgArgv ::PtrCInt->Ptr(PtrCString)->IO()

AltStyle によって変換されたページ (->オリジナル) /