{-# LANGUAGE CPP #-}
{-# LANGUAGE PackageImports #-}
module System.Process.Environment.OsString (
getArgs,
getEnv,
getEnvironment,
) where
import Data.Coerce (coerce)
#if MIN_VERSION_filepath(1, 5, 0)
import "os-string" System.OsString.Internal.Types (OsString(OsString))
#else
import "filepath" System.OsString.Internal.Types (OsString(OsString))
#endif
#if defined(mingw32_HOST_OS)
import qualified System.Win32.WindowsString.Console as Platform
#else
import qualified System.Posix.Env.PosixString as Platform
#endif
getArgs :: IO [OsString]
getArgs :: IO [OsString]
getArgs = IO [PosixString] -> IO [OsString]
forall a b. Coercible a b => a -> b
coerce IO [PosixString]
Platform.getArgs
getEnv :: OsString -> IO (Maybe OsString)
getEnv :: OsString -> IO (Maybe OsString)
getEnv = (PosixString -> IO (Maybe PosixString))
-> OsString -> IO (Maybe OsString)
forall a b. Coercible a b => a -> b
coerce PosixString -> IO (Maybe PosixString)
Platform.getEnv
getEnvironment :: IO [(OsString, OsString)]
getEnvironment :: IO [(OsString, OsString)]
getEnvironment = IO [(PosixString, PosixString)] -> IO [(OsString, OsString)]
forall a b. Coercible a b => a -> b
coerce IO [(PosixString, PosixString)]
Platform.getEnvironment