Z-IO-0.6.1.0: Simple and high performance IO toolkit for Haskell
Copyright(c) Dong Han 2020
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.IO.Environment

Description

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

arguments

getArgs :: IO [CBytes] Source #

Computation getArgs returns a list of the program's command line arguments (including the program path).

This is different from base's getArgs since result includes the program path(more like C's *argv).

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

getCWD :: HasCallStack => IO CBytes Source #

Gets the current working directory.

chDir :: HasCallStack => CBytes -> IO () Source #

Changes the current working directory.

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 ResUsage Source #

Data type for resource usage results.

Members marked with (X) are unsupported on Windows. See getrusage(2) for supported fields on Unix

Constructors

ResUsage 

Fields

Instances

Instances details
Eq ResUsage Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord ResUsage Source # 
Instance details

Defined in Z.IO.UV.FFI

Read ResUsage Source # 
Instance details

Defined in Z.IO.UV.FFI

Show ResUsage Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic ResUsage Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep ResUsage :: Type -> Type #

Methods

from :: ResUsage -> Rep ResUsage x #

to :: Rep ResUsage x -> ResUsage #

JSON ResUsage Source # 
Instance details

Defined in Z.IO.UV.FFI

Print ResUsage Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toUTF8BuilderP :: Int -> ResUsage -> Builder () #

type Rep ResUsage Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep ResUsage = D1 ('MetaData "ResUsage" "Z.IO.UV.FFI" "Z-IO-0.6.1.0-gzKEsYtajW4dyRTMbokGF" 'False) (C1 ('MetaCons "ResUsage" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "ru_utime") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 TimeVal) :*: S1 ('MetaSel ('Just "ru_stime") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 TimeVal)) :*: (S1 ('MetaSel ('Just "ru_maxrss") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "ru_ixrss") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "ru_idrss") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "ru_isrss") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "ru_minflt") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "ru_majflt") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64)))) :*: (((S1 ('MetaSel ('Just "ru_nswap") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "ru_inblock") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "ru_oublock") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "ru_msgsnd") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "ru_msgrcv") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "ru_nsignals") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "ru_nvcsw") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "ru_nivcsw") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64))))))

data TimeVal Source #

Data type for storing times. typedef struct { long tv_sec; long tv_usec; } uv_timeval_t;

Constructors

TimeVal 

Fields

Instances

Instances details
Eq TimeVal Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

(==) :: TimeVal -> TimeVal -> Bool #

(/=) :: TimeVal -> TimeVal -> Bool #

Ord TimeVal Source # 
Instance details

Defined in Z.IO.UV.FFI

Read TimeVal Source # 
Instance details

Defined in Z.IO.UV.FFI

Show TimeVal Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic TimeVal Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep TimeVal :: Type -> Type #

Methods

from :: TimeVal -> Rep TimeVal x #

to :: Rep TimeVal x -> TimeVal #

JSON TimeVal Source # 
Instance details

Defined in Z.IO.UV.FFI

Print TimeVal Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toUTF8BuilderP :: Int -> TimeVal -> Builder () #

type Rep TimeVal Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep TimeVal = D1 ('MetaData "TimeVal" "Z.IO.UV.FFI" "Z-IO-0.6.1.0-gzKEsYtajW4dyRTMbokGF" '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.

getUpTime :: HasCallStack => IO Double Source #

Gets the current system uptime.

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.

newtype PID Source #

Constructors

PID CInt 

Instances

Instances details
Eq PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

(==) :: PID -> PID -> Bool #

(/=) :: PID -> PID -> Bool #

Ord PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

compare :: PID -> PID -> Ordering #

(<) :: PID -> PID -> Bool #

(<=) :: PID -> PID -> Bool #

(>) :: PID -> PID -> Bool #

(>=) :: PID -> PID -> Bool #

max :: PID -> PID -> PID #

min :: PID -> PID -> PID #

Read PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Show PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

showsPrec :: Int -> PID -> ShowS #

show :: PID -> String #

showList :: [PID] -> ShowS #

Generic PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep PID :: Type -> Type #

Methods

from :: PID -> Rep PID x #

to :: Rep PID x -> PID #

JSON PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Print PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toUTF8BuilderP :: Int -> PID -> Builder () #

Unaligned PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Prim PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

sizeOf :: PID -> Int #

alignment :: PID -> Int #

peekElemOff :: Ptr PID -> Int -> IO PID #

pokeElemOff :: Ptr PID -> Int -> PID -> IO () #

peekByteOff :: Ptr b -> Int -> IO PID #

pokeByteOff :: Ptr b -> Int -> PID -> IO () #

peek :: Ptr PID -> IO PID #

poke :: Ptr PID -> PID -> IO () #

type Rep PID Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep PID = D1 ('MetaData "PID" "Z.IO.UV.FFI" "Z-IO-0.6.1.0-gzKEsYtajW4dyRTMbokGF" 'True) (C1 ('MetaCons "PID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)))

getPID :: IO PID Source #

Returns the current process ID.

getPPID :: IO PID Source #

Returns the parent process ID.

getHostname :: HasCallStack => IO CBytes Source #

Returns the hostname as a null-terminated string.

data OSName Source #

Data type for operating system name and version information.

Instances

Instances details
Eq OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

(==) :: OSName -> OSName -> Bool #

(/=) :: OSName -> OSName -> Bool #

Ord OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

Read OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

Show OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep OSName :: Type -> Type #

Methods

from :: OSName -> Rep OSName x #

to :: Rep OSName x -> OSName #

JSON OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

Print OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toUTF8BuilderP :: Int -> OSName -> Builder () #

type Rep OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep OSName = D1 ('MetaData "OSName" "Z.IO.UV.FFI" "Z-IO-0.6.1.0-gzKEsYtajW4dyRTMbokGF" '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 PassWD Source #

Data type for password file information.

Instances

Instances details
Eq PassWD Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

(==) :: PassWD -> PassWD -> Bool #

(/=) :: PassWD -> PassWD -> Bool #

Ord PassWD Source # 
Instance details

Defined in Z.IO.UV.FFI

Read PassWD Source # 
Instance details

Defined in Z.IO.UV.FFI

Show PassWD Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic PassWD Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep PassWD :: Type -> Type #

Methods

from :: PassWD -> Rep PassWD x #

to :: Rep PassWD x -> PassWD #

JSON PassWD Source # 
Instance details

Defined in Z.IO.UV.FFI

Print PassWD Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toUTF8BuilderP :: Int -> PassWD -> Builder () #

type Rep PassWD Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep PassWD = D1 ('MetaData "PassWD" "Z.IO.UV.FFI" "Z-IO-0.6.1.0-gzKEsYtajW4dyRTMbokGF" '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)))))

data UID Source #

Instances

Instances details
Eq UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

(==) :: UID -> UID -> Bool #

(/=) :: UID -> UID -> Bool #

Num UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

(+) :: UID -> UID -> UID #

(-) :: UID -> UID -> UID #

(*) :: UID -> UID -> UID #

negate :: UID -> UID #

abs :: UID -> UID #

signum :: UID -> UID #

fromInteger :: Integer -> UID #

Ord UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

compare :: UID -> UID -> Ordering #

(<) :: UID -> UID -> Bool #

(<=) :: UID -> UID -> Bool #

(>) :: UID -> UID -> Bool #

(>=) :: UID -> UID -> Bool #

max :: UID -> UID -> UID #

min :: UID -> UID -> UID #

Read UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Show UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

showsPrec :: Int -> UID -> ShowS #

show :: UID -> String #

showList :: [UID] -> ShowS #

Generic UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep UID :: Type -> Type #

Methods

from :: UID -> Rep UID x #

to :: Rep UID x -> UID #

JSON UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Print UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toUTF8BuilderP :: Int -> UID -> Builder () #

Unaligned UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Prim UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

sizeOf :: UID -> Int #

alignment :: UID -> Int #

peekElemOff :: Ptr UID -> Int -> IO UID #

pokeElemOff :: Ptr UID -> Int -> UID -> IO () #

peekByteOff :: Ptr b -> Int -> IO UID #

pokeByteOff :: Ptr b -> Int -> UID -> IO () #

peek :: Ptr UID -> IO UID #

poke :: Ptr UID -> UID -> IO () #

type Rep UID Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep UID = D1 ('MetaData "UID" "Z.IO.UV.FFI" "Z-IO-0.6.1.0-gzKEsYtajW4dyRTMbokGF" 'True) (C1 ('MetaCons "UID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

data GID Source #

Instances

Instances details
Eq GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

(==) :: GID -> GID -> Bool #

(/=) :: GID -> GID -> Bool #

Num GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

(+) :: GID -> GID -> GID #

(-) :: GID -> GID -> GID #

(*) :: GID -> GID -> GID #

negate :: GID -> GID #

abs :: GID -> GID #

signum :: GID -> GID #

fromInteger :: Integer -> GID #

Ord GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

compare :: GID -> GID -> Ordering #

(<) :: GID -> GID -> Bool #

(<=) :: GID -> GID -> Bool #

(>) :: GID -> GID -> Bool #

(>=) :: GID -> GID -> Bool #

max :: GID -> GID -> GID #

min :: GID -> GID -> GID #

Read GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Show GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

showsPrec :: Int -> GID -> ShowS #

show :: GID -> String #

showList :: [GID] -> ShowS #

Generic GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep GID :: Type -> Type #

Methods

from :: GID -> Rep GID x #

to :: Rep GID x -> GID #

JSON GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Print GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toUTF8BuilderP :: Int -> GID -> Builder () #

Unaligned GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Prim GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

sizeOf :: GID -> Int #

alignment :: GID -> Int #

peekElemOff :: Ptr GID -> Int -> IO GID #

pokeElemOff :: Ptr GID -> Int -> GID -> IO () #

peekByteOff :: Ptr b -> Int -> IO GID #

pokeByteOff :: Ptr b -> Int -> GID -> IO () #

peek :: Ptr GID -> IO GID #

poke :: Ptr GID -> GID -> IO () #

type Rep GID Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep GID = D1 ('MetaData "GID" "Z.IO.UV.FFI" "Z-IO-0.6.1.0-gzKEsYtajW4dyRTMbokGF" 'True) (C1 ('MetaCons "GID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

getCPUInfo :: HasCallStack => IO [CPUInfo] Source #

Gets information about the CPUs on the system.

data CPUInfo Source #

Data type for CPU information.

Constructors

CPUInfo 

Fields

Instances

Instances details
Eq CPUInfo Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

(==) :: CPUInfo -> CPUInfo -> Bool #

(/=) :: CPUInfo -> CPUInfo -> Bool #

Ord CPUInfo Source # 
Instance details

Defined in Z.IO.UV.FFI

Read CPUInfo Source # 
Instance details

Defined in Z.IO.UV.FFI

Show CPUInfo Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic CPUInfo Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep CPUInfo :: Type -> Type #

Methods

from :: CPUInfo -> Rep CPUInfo x #

to :: Rep CPUInfo x -> CPUInfo #

JSON CPUInfo Source # 
Instance details

Defined in Z.IO.UV.FFI

Print CPUInfo Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toUTF8BuilderP :: Int -> CPUInfo -> Builder () #

type Rep CPUInfo Source # 
Instance details

Defined in Z.IO.UV.FFI

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.