Copyright | (c) Dong Han 2020 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provide methods for retrieving various environment infomation. There's no encoding guarantee about these information, if you want textual representation, UTF8 assumption is recommended. i.e. use validate
.
Synopsis
- getArgs :: IO [CBytes]
- getAllEnv :: HasCallStack => IO [(CBytes, CBytes)]
- getEnv :: HasCallStack => CBytes -> IO (Maybe CBytes)
- getEnv' :: HasCallStack => CBytes -> IO CBytes
- setEnv :: HasCallStack => CBytes -> CBytes -> IO ()
- unsetEnv :: HasCallStack => CBytes -> IO ()
- getCWD :: HasCallStack => IO CBytes
- chDir :: HasCallStack => CBytes -> IO ()
- getHomeDir :: HasCallStack => IO CBytes
- getTempDir :: HasCallStack => IO CBytes
- getRandom :: Int -> IO Bytes
- getRandomT :: Int -> IO Bytes
- getResUsage :: HasCallStack => IO ResUsage
- data ResUsage = ResUsage {
- ru_utime :: !TimeVal
- ru_stime :: !TimeVal
- ru_maxrss :: !Word64
- ru_ixrss :: !Word64
- ru_idrss :: !Word64
- ru_isrss :: !Word64
- ru_minflt :: !Word64
- ru_majflt :: !Word64
- ru_nswap :: !Word64
- ru_inblock :: !Word64
- ru_oublock :: !Word64
- ru_msgsnd :: !Word64
- ru_msgrcv :: !Word64
- ru_nsignals :: !Word64
- ru_nvcsw :: !Word64
- ru_nivcsw :: !Word64
- data TimeVal = TimeVal {}
- getResidentSetMemory :: HasCallStack => IO CSize
- getUpTime :: HasCallStack => IO Double
- getHighResolutionTime :: IO Word64
- newtype PID = PID CInt
- getPID :: IO PID
- getPPID :: IO PID
- getHostname :: HasCallStack => IO CBytes
- getOSName :: HasCallStack => IO OSName
- data OSName = OSName {
- os_sysname :: CBytes
- os_release :: CBytes
- os_version :: CBytes
- os_machine :: CBytes
- getPassWD :: HasCallStack => IO PassWD
- data PassWD = PassWD {}
- data UID
- data GID
- getCPUInfo :: HasCallStack => IO [CPUInfo]
- data CPUInfo = CPUInfo {}
- getLoadAvg :: IO (Double, Double, Double)
- getFreeMem :: IO Word64
- getTotalMem :: IO Word64
- getConstrainedMem :: IO Word64
arguments
environment variables
getAllEnv :: HasCallStack => IO [(CBytes, CBytes)] Source #
Retrieves the environment variable.
Warning: This function is not thread safe.
getEnv :: HasCallStack => CBytes -> IO (Maybe CBytes) Source #
Retrieves the environment variable specified by name.
Warning: This function is not thread safe.
getEnv' :: HasCallStack => CBytes -> IO CBytes Source #
Retrieves the environment variable specified by name, throw NoSuchThing
if not exists.
Warning: This function is not thread safe.
setEnv :: HasCallStack => CBytes -> CBytes -> IO () Source #
Creates or updates the environment variable specified by name with value.
Warning: This function is not thread safe.
unsetEnv :: HasCallStack => CBytes -> IO () Source #
Deletes the environment variable specified by name if such environment variable exists.
Warning: This function is not thread safe.
other environment infos
getHomeDir :: HasCallStack => IO CBytes Source #
Gets the current user’s home directory.
On Windows, first checks the USERPROFILE environment variable using GetEnvironmentVariableW(). If USERPROFILE is not set, GetUserProfileDirectoryW() is called. On all other operating systems, first checks the HOME environment variable using getenv(3). If HOME is not set, getpwuid_r(3) is called.
Warning getHomeDir
is not thread safe.
getTempDir :: HasCallStack => IO CBytes Source #
Gets the temp directory.
On Windows, uses GetTempPathW(). On all other operating systems,
uses the first environment variable found in the ordered list TMPDIR, TMP, TEMP, and TEMPDIR.
If none of these are found, the path /tmp
is used, or, on Android, /data/local/tmp
is used.
Warning getHomeDir
is not thread safe.
getRandom :: Int -> IO Bytes Source #
Fill buf with exactly buflen cryptographically strong random bytes acquired from the system CSPRNG.
The function may block indefinitely when not enough entropy is available, don't use it to get long random sequences.
getRandomT :: Int -> IO Bytes Source #
Fill buf with exactly buflen cryptographically strong random bytes acquired from the system CSPRNG.
The function run getRandom
in libuv's threadpool, suitable for get long random byte sequences.
getResUsage :: HasCallStack => IO ResUsage Source #
Gets the resource usage measures for the current process.
On Windows not all fields are set, the unsupported fields are filled with zeroes.
See ResUsage
for more details.
Data type for resource usage results.
Members marked with (X) are unsupported on Windows. See getrusage(2) for supported fields on Unix
ResUsage | |
|
Instances
Data type for storing times. typedef struct { long tv_sec; long tv_usec; } uv_timeval_t;
Instances
Eq TimeVal Source # | |
Ord TimeVal Source # | |
Read TimeVal Source # | |
Show TimeVal Source # | |
Generic TimeVal Source # | |
JSON TimeVal Source # | |
Print TimeVal Source # | |
Defined in Z.IO.UV.FFI_Env toUTF8BuilderP :: Int -> TimeVal -> Builder () # | |
type Rep TimeVal Source # | |
Defined in Z.IO.UV.FFI_Env type Rep TimeVal = D1 ('MetaData "TimeVal" "Z.IO.UV.FFI_Env" "Z-IO-0.6.4.0-3RdtkLMi3pWlcaS0GimBE" 'False) (C1 ('MetaCons "TimeVal" 'PrefixI 'True) (S1 ('MetaSel ('Just "tv_sec") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 CLong) :*: S1 ('MetaSel ('Just "tv_usec") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 CLong))) |
getResidentSetMemory :: HasCallStack => IO CSize Source #
Gets the resident set size (RSS) for the current process.
getHighResolutionTime :: IO Word64 Source #
Returns the current high-resolution real time.
This is expressed in nanoseconds. It is relative to an arbitrary time in the past. It is not related to the time of day and therefore not subject to clock drift. The primary use is for measuring performance between intervals.
Instances
getHostname :: HasCallStack => IO CBytes Source #
Returns the hostname as a null-terminated string.
Data type for operating system name and version information.
OSName | |
|
Instances
Eq OSName Source # | |
Ord OSName Source # | |
Read OSName Source # | |
Show OSName Source # | |
Generic OSName Source # | |
JSON OSName Source # | |
Print OSName Source # | |
Defined in Z.IO.UV.FFI_Env toUTF8BuilderP :: Int -> OSName -> Builder () # | |
type Rep OSName Source # | |
Defined in Z.IO.UV.FFI_Env type Rep OSName = D1 ('MetaData "OSName" "Z.IO.UV.FFI_Env" "Z-IO-0.6.4.0-3RdtkLMi3pWlcaS0GimBE" 'False) (C1 ('MetaCons "OSName" 'PrefixI 'True) ((S1 ('MetaSel ('Just "os_sysname") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBytes) :*: S1 ('MetaSel ('Just "os_release") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBytes)) :*: (S1 ('MetaSel ('Just "os_version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBytes) :*: S1 ('MetaSel ('Just "os_machine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBytes)))) |
getPassWD :: HasCallStack => IO PassWD Source #
Gets a subset of the password file entry for the current effective uid (not the real uid).
The populated data includes the username, euid, gid, shell, and home directory. On non-Windows systems, all data comes from getpwuid_r(3). On Windows, uid and gid are set to -1 and have no meaning, and shell is empty.
Data type for password file information.
PassWD | |
|
Instances
Eq PassWD Source # | |
Ord PassWD Source # | |
Read PassWD Source # | |
Show PassWD Source # | |
Generic PassWD Source # | |
JSON PassWD Source # | |
Print PassWD Source # | |
Defined in Z.IO.UV.FFI_Env toUTF8BuilderP :: Int -> PassWD -> Builder () # | |
type Rep PassWD Source # | |
Defined in Z.IO.UV.FFI_Env type Rep PassWD = D1 ('MetaData "PassWD" "Z.IO.UV.FFI_Env" "Z-IO-0.6.4.0-3RdtkLMi3pWlcaS0GimBE" 'False) (C1 ('MetaCons "PassWD" 'PrefixI 'True) ((S1 ('MetaSel ('Just "passwd_username") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBytes) :*: S1 ('MetaSel ('Just "passwd_uid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UID)) :*: (S1 ('MetaSel ('Just "passwd_gid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GID) :*: (S1 ('MetaSel ('Just "passwd_shell") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBytes) :*: S1 ('MetaSel ('Just "passwd_homedir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBytes))))) |
Instances
Instances
getCPUInfo :: HasCallStack => IO [CPUInfo] Source #
Gets information about the CPUs on the system.
Data type for CPU information.
CPUInfo | |
|
Instances
getLoadAvg :: IO (Double, Double, Double) Source #
Gets the load average. See: https://en.wikipedia.org/wiki/Load_(computing)
getFreeMem :: IO Word64 Source #
Gets the amount of free memory available in the system, as reported by the kernel (in bytes).
getTotalMem :: IO Word64 Source #
Gets the total amount of physical memory in the system (in bytes).
getConstrainedMem :: IO Word64 Source #
Gets the amount of memory available to the process (in bytes) based on limits imposed by the OS.
If there is no such constraint, or the constraint is unknown, 0 is returned.
Note that it is not unusual for this value to be less than or greater than getTotalMem
.
Note This function currently only returns a non-zero value on Linux, based on cgroups if it is present.