Z-IO-0.1.5.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

Contents

Description

This module provide methods for retrieving various environment infomation. There's no encoding guarantee about these information, if you want textual representation, use UTF8 assumption is recommended. i.e. use "Z.Data.Text.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

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.

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

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 #

ToValue PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: PID -> Value #

EncodeJSON PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: PID -> Builder () #

FromValue PID Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT PID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toTextBuilder :: Int -> PID -> TextBuilder () #

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.1.5.0-8sLj6ZMbh2s3VZm7kS3Now" 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 #

Constructors

OSName 
Instances
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

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 #

ToValue OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: OSName -> Value #

EncodeJSON OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: OSName -> Builder () #

FromValue OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toTextBuilder :: Int -> OSName -> TextBuilder () #

type Rep OSName Source # 
Instance details

Defined in Z.IO.UV.FFI

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.