Copyright | (c) Winterland 2020 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
INTERNAL MODULE, split from Z.IO.UV.FFI to make it buildable under constrained memory.
Synopsis
- uv_resident_set_memory :: MBA# CSize -> IO CInt
- uv_uptime :: MBA# Double -> IO CInt
- uv_getrusage :: MBA# a -> IO CInt
- uv_get_free_memory :: IO Word64
- uv_get_total_memory :: IO Word64
- uv_get_constrained_memory :: IO Word64
- data TimeVal = TimeVal {}
- 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
- sizeOfResUsage :: Int
- peekResUsage :: MBA# a -> IO ResUsage
- uv_os_getpid :: IO PID
- uv_os_getppid :: IO PID
- uv_os_getpriority :: PID -> MBA# CInt -> IO CInt
- uv_os_setpriority :: PID -> CInt -> IO CInt
- newtype PID = PID CInt
- type Priority = CInt
- pattern PRIORITY_LOW :: Priority
- pattern PRIORITY_BELOW_NORMAL :: Priority
- pattern PRIORITY_NORMAL :: Priority
- pattern PRIORITY_ABOVE_NORMAL :: Priority
- pattern PRIORITY_HIGH :: Priority
- pattern PRIORITY_HIGHEST :: Priority
- uv_hrtime :: IO Word64
- uv_os_environ :: MBA# (Ptr a) -> MBA# CInt -> IO CInt
- uv_os_free_environ :: Ptr a -> CInt -> IO ()
- uv_os_getenv :: BA# Word8 -> MBA# Word8 -> MBA# CSize -> IO CInt
- uv_os_setenv :: BA# Word8 -> BA# Word8 -> IO CInt
- uv_os_unsetenv :: BA# Word8 -> IO CInt
- pattern UV_MAXHOSTNAMESIZE :: CSize
- uv_os_gethostname :: MBA# Word8 -> MBA# CSize -> IO CInt
- data OSName = OSName {
- os_sysname :: CBytes
- os_release :: CBytes
- os_version :: CBytes
- os_machine :: CBytes
- getOSName :: HasCallStack => IO OSName
- uv_os_uname :: MBA# OSName -> IO CInt
- hs_uv_random :: MBA# Word8 -> CSize -> CInt -> IO CInt
- hs_uv_random_threaded :: Ptr Word8 -> CSize -> CInt -> Ptr UVLoop -> IO UVSlotUnsafe
- data PassWD = PassWD {}
- uv_os_get_passwd :: MBA# PassWD -> IO CInt
- uv_os_free_passwd :: MBA# PassWD -> IO ()
- getPassWD :: HasCallStack => IO PassWD
- uv_cwd :: MBA# Word8 -> MBA# CSize -> IO CInt
- uv_chdir :: BA# Word8 -> IO CInt
- uv_os_homedir :: MBA# Word8 -> MBA# CSize -> IO CInt
- uv_os_tmpdir :: MBA# Word8 -> MBA# CSize -> IO CInt
- uv_cpu_info :: MBA# (Ptr CPUInfo) -> MBA# CInt -> IO CInt
- uv_free_cpu_info :: Ptr CPUInfo -> CInt -> IO ()
- data CPUInfo = CPUInfo {}
- getCPUInfo :: HasCallStack => IO [CPUInfo]
- peekCPUInfoOff :: Ptr CPUInfo -> Int -> IO CPUInfo
- uv_loadavg :: MBA# (Double, Double, Double) -> IO ()
- getLoadAvg :: IO (Double, Double, Double)
- data TimeVal64 = TimeVal64 {}
- uv_gettimeofday :: MBA# TimeVal64 -> IO CInt
- getTimeOfDay :: HasCallStack => IO TimeVal64
Documentation
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))) |
Data type for resource usage results.
Members marked with (X) are unsupported on Windows. See getrusage(2) for supported fields on Unix
ResUsage | |
|
Instances
sizeOfResUsage :: Int Source #
uv_os_getpid :: IO PID Source #
uv_os_getppid :: IO PID Source #
Instances
pattern PRIORITY_LOW :: Priority Source #
pattern PRIORITY_BELOW_NORMAL :: Priority Source #
pattern PRIORITY_NORMAL :: Priority Source #
pattern PRIORITY_ABOVE_NORMAL :: Priority Source #
pattern PRIORITY_HIGH :: Priority Source #
pattern PRIORITY_HIGHEST :: Priority Source #
pattern UV_MAXHOSTNAMESIZE :: CSize Source #
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)))) |
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))))) |
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 CPU information.
CPUInfo | |
|
Instances
getCPUInfo :: HasCallStack => IO [CPUInfo] Source #
Gets information about the CPUs on the system.
getLoadAvg :: IO (Double, Double, Double) Source #
Gets the load average. See: https://en.wikipedia.org/wiki/Load_(computing)
Alternative data type for storing times. typedef struct { int64_t tv_sec; int32_t tv_usec; } uv_timeval64_t;
Instances
Eq TimeVal64 Source # | |
Ord TimeVal64 Source # | |
Defined in Z.IO.UV.FFI_Env | |
Read TimeVal64 Source # | |
Show TimeVal64 Source # | |
Generic TimeVal64 Source # | |
JSON TimeVal64 Source # | |
Print TimeVal64 Source # | |
Defined in Z.IO.UV.FFI_Env toUTF8BuilderP :: Int -> TimeVal64 -> Builder () # | |
type Rep TimeVal64 Source # | |
Defined in Z.IO.UV.FFI_Env type Rep TimeVal64 = D1 ('MetaData "TimeVal64" "Z.IO.UV.FFI_Env" "Z-IO-0.6.4.0-3RdtkLMi3pWlcaS0GimBE" 'False) (C1 ('MetaCons "TimeVal64" 'PrefixI 'True) (S1 ('MetaSel ('Just "tv64_sec") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: S1 ('MetaSel ('Just "tv64_usec") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int32))) |
getTimeOfDay :: HasCallStack => IO TimeVal64 Source #
Cross-platform implementation of gettimeofday(2). The timezone argument to gettimeofday() is not supported, as it is considered obsolete.