module System.Environment
(
getArgs,
getProgName,
getEnv,
#ifndef __NHC__
withArgs,
withProgName,
#endif
#ifdef __GLASGOW_HASKELL__
getEnvironment,
#endif
) where
import Prelude
#ifdef __GLASGOW_HASKELL__
import Foreign.Safe
import Foreign.C
import Control.Exception.Base ( bracket )
import GHC.IO.Exception
import GHC.IO.Encoding (getFileSystemEncoding)
import qualified GHC.Foreign as GHC
import Data.List
#ifdef mingw32_HOST_OS
import GHC.Environment
import GHC.Windows
#else
import Control.Monad
#endif
#endif
#ifdef __HUGS__
import Hugs.System
#endif
#ifdef __NHC__
import System
( getArgs
, getProgName
, getEnv
)
#endif
#ifdef __GLASGOW_HASKELL__
#ifdef mingw32_HOST_OS
getWin32ProgArgv_certainly :: IO [String]
getWin32ProgArgv_certainly = do
mb_argv <- getWin32ProgArgv
case mb_argv of
Nothing -> fmap dropRTSArgs getFullArgs
Just argv -> return argv
withWin32ProgArgv :: [String] -> IO a -> IO a
withWin32ProgArgv argv act = bracket begin setWin32ProgArgv (\_ -> act)
where
begin = do
mb_old_argv <- getWin32ProgArgv
setWin32ProgArgv (Just argv)
return mb_old_argv
getWin32ProgArgv :: IO (Maybe [String])
getWin32ProgArgv = alloca $ \p_argc -> alloca $ \p_argv -> do
c_getWin32ProgArgv p_argc p_argv
argc <- peek p_argc
argv_p <- peek p_argv
if argv_p == nullPtr
then return Nothing
else do
argv_ps <- peekArray (fromIntegral argc) argv_p
fmap Just $ mapM peekCWString argv_ps
setWin32ProgArgv :: Maybe [String] -> IO ()
setWin32ProgArgv Nothing = c_setWin32ProgArgv 0 nullPtr
setWin32ProgArgv (Just argv) = withMany withCWString argv $ \argv_ps -> withArrayLen argv_ps $ \argc argv_p -> do
c_setWin32ProgArgv (fromIntegral argc) argv_p
foreign import ccall unsafe "getWin32ProgArgv"
c_getWin32ProgArgv :: Ptr CInt -> Ptr (Ptr CWString) -> IO ()
foreign import ccall unsafe "setWin32ProgArgv"
c_setWin32ProgArgv :: CInt -> Ptr CWString -> IO ()
dropRTSArgs :: [String] -> [String]
dropRTSArgs [] = []
dropRTSArgs ("+RTS":rest) = dropRTSArgs (dropWhile (/= "-RTS") rest)
dropRTSArgs ("--RTS":rest) = rest
dropRTSArgs ("-RTS":rest) = dropRTSArgs rest
dropRTSArgs (arg:rest) = arg : dropRTSArgs rest
#endif
getArgs :: IO [String]
#ifdef mingw32_HOST_OS
getArgs = fmap tail getWin32ProgArgv_certainly
#else
getArgs =
alloca $ \ p_argc ->
alloca $ \ p_argv -> do
getProgArgv p_argc p_argv
p <- fromIntegral `liftM` peek p_argc
argv <- peek p_argv
enc <- getFileSystemEncoding
peekArray (p 1) (advancePtr argv 1) >>= mapM (GHC.peekCString enc)
foreign import ccall unsafe "getProgArgv"
getProgArgv :: Ptr CInt -> Ptr (Ptr CString) -> IO ()
#endif
getProgName :: IO String
#ifdef mingw32_HOST_OS
getProgName = fmap (basename . head) getWin32ProgArgv_certainly
#else
getProgName =
alloca $ \ p_argc ->
alloca $ \ p_argv -> do
getProgArgv p_argc p_argv
argv <- peek p_argv
unpackProgName argv
unpackProgName :: Ptr (Ptr CChar) -> IO String
unpackProgName argv = do
enc <- getFileSystemEncoding
s <- peekElemOff argv 0 >>= GHC.peekCString enc
return (basename s)
#endif
basename :: FilePath -> FilePath
basename f = go f f
where
go acc [] = acc
go acc (x:xs)
| isPathSeparator x = go xs xs
| otherwise = go acc xs
isPathSeparator :: Char -> Bool
isPathSeparator '/' = True
#ifdef mingw32_HOST_OS
isPathSeparator '\\' = True
#endif
isPathSeparator _ = False
getEnv :: String -> IO String
#ifdef mingw32_HOST_OS
getEnv name = withCWString name $ \s -> try_size s 256
where
try_size s size = allocaArray (fromIntegral size) $ \p_value -> do
res <- c_GetEnvironmentVariable s p_value size
case res of
0 -> do
err <- c_GetLastError
if err == eRROR_ENVVAR_NOT_FOUND
then ioe_missingEnvVar name
else throwGetLastError "getEnv"
_ | res > size -> try_size s res
| otherwise -> peekCWString p_value
eRROR_ENVVAR_NOT_FOUND :: DWORD
eRROR_ENVVAR_NOT_FOUND = 203
foreign import stdcall unsafe "windows.h GetLastError"
c_GetLastError:: IO DWORD
foreign import stdcall unsafe "windows.h GetEnvironmentVariableW"
c_GetEnvironmentVariable :: LPTSTR -> LPTSTR -> DWORD -> IO DWORD
#else
getEnv name =
withCString name $ \s -> do
litstring <- c_getenv s
if litstring /= nullPtr
then getFileSystemEncoding >>= \enc -> GHC.peekCString enc litstring
else ioe_missingEnvVar name
foreign import ccall unsafe "getenv"
c_getenv :: CString -> IO (Ptr CChar)
#endif
ioe_missingEnvVar :: String -> IO a
ioe_missingEnvVar name = ioException (IOError Nothing NoSuchThing "getEnv"
"no environment variable" Nothing (Just name))
withArgs :: [String] -> IO a -> IO a
withArgs xs act = do
p <- System.Environment.getProgName
withArgv (p:xs) act
withProgName :: String -> IO a -> IO a
withProgName nm act = do
xs <- System.Environment.getArgs
withArgv (nm:xs) act
withArgv :: [String] -> IO a -> IO a
#ifdef mingw32_HOST_OS
withArgv new_args act = withWin32ProgArgv new_args $ withProgArgv new_args act
#else
withArgv = withProgArgv
#endif
withProgArgv :: [String] -> IO a -> IO a
withProgArgv new_args act = do
pName <- System.Environment.getProgName
existing_args <- System.Environment.getArgs
bracket (setProgArgv new_args)
(\argv -> do _ <- setProgArgv (pName:existing_args)
freeProgArgv argv)
(const act)
freeProgArgv :: Ptr CString -> IO ()
freeProgArgv argv = do
size <- lengthArray0 nullPtr argv
sequence_ [peek (argv `advancePtr` i) >>= free | i <- [size, size1 .. 0]]
free argv
setProgArgv :: [String] -> IO (Ptr CString)
setProgArgv argv = do
enc <- getFileSystemEncoding
vs <- mapM (GHC.newCString enc) argv >>= newArray0 nullPtr
c_setProgArgv (genericLength argv) vs
return vs
foreign import ccall unsafe "setProgArgv"
c_setProgArgv :: CInt -> Ptr CString -> IO ()
getEnvironment :: IO [(String, String)]
#ifdef mingw32_HOST_OS
getEnvironment = bracket c_GetEnvironmentStrings c_FreeEnvironmentStrings $ \pBlock ->
if pBlock == nullPtr then return []
else go pBlock
where
go pBlock = do
c <- peek pBlock
if c == 0 then return []
else do
pBlock' <- seekNull pBlock False
str <- peekCWString pBlock
fmap (divvy str :) $ go pBlock'
seekNull pBlock done = do
let pBlock' = pBlock `plusPtr` sizeOf (undefined :: CWchar)
if done then return pBlock'
else do
c <- peek pBlock'
seekNull pBlock' (c == (0 :: Word8 ))
foreign import stdcall unsafe "windows.h GetEnvironmentStringsW"
c_GetEnvironmentStrings :: IO (Ptr CWchar)
foreign import stdcall unsafe "windows.h FreeEnvironmentStringsW"
c_FreeEnvironmentStrings :: Ptr CWchar -> IO Bool
#else
getEnvironment = do
pBlock <- getEnvBlock
if pBlock == nullPtr then return []
else do
enc <- getFileSystemEncoding
stuff <- peekArray0 nullPtr pBlock >>= mapM (GHC.peekCString enc)
return (map divvy stuff)
foreign import ccall unsafe "__hscore_environ"
getEnvBlock :: IO (Ptr CString)
#endif
divvy :: String -> (String, String)
divvy str =
case break (=='=') str of
(xs,[]) -> (xs,[])
(name,_:value) -> (name,value)
#endif /* __GLASGOW_HASKELL__ */