Z-IO-0.1.8.0: Simple and high performance IO toolkit for Haskell
Copyright(c) Winterland 2017-2018
LicenseBSD
Maintainerdrkoster@qq.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.IO.UV.FFI

Description

INTERNAL MODULE, provides all libuv side operations.

Synopsis

Documentation

newtype UVSlotUnsafe Source #

UVSlotUnsafe wrap a slot which may not have a MVar in blocking table, i.e. the blocking table need to be resized.

Constructors

UVSlotUnsafe 

type FD = CInt Source #

peekUVLoopData :: Ptr UVLoop -> IO (Ptr UVLoopData) Source #

Peek loop data pointer from uv loop pointer.

uv_run :: Ptr UVLoop -> UVRunMode -> IO CInt Source #

uv_run with usafe FFI.

uv_run_safe :: Ptr UVLoop -> UVRunMode -> IO CInt Source #

uv_run with safe FFI.

hs_uv_check_init Source #

Arguments

:: Ptr UVHandle

uv_check_t

-> Ptr UVHandle

uv_handle_t

-> IO CInt 

uv_udp_disconnect :: Ptr UVHandle -> Ptr SocketAddr -> IO CInt Source #

Just pass null pointer as SocketAddr to disconnect

type TTYMode = CInt Source #

Terminal mode.

When in TTY_MODE_RAW mode, input is always available character-by-character, not including modifiers. Additionally, all special processing of characters by the terminal is disabled, including echoing input characters. Note that CTRL+C will no longer cause a SIGINT when in this mode.

pattern S_IRWXU :: FileMode Source #

00700 user (file owner) has read, write and execute permission

pattern S_IRUSR :: FileMode Source #

00400 user has read permission

pattern S_IWUSR :: FileMode Source #

00200 user has write permission

pattern S_IXUSR :: FileMode Source #

00100 user has execute permission

pattern S_IRWXG :: FileMode Source #

00070 group has read, write and execute permission

pattern S_IRGRP :: FileMode Source #

00040 group has read permission

pattern S_IWGRP :: FileMode Source #

00020 group has write permission

pattern S_IXGRP :: FileMode Source #

00010 group has execute permission

pattern S_IRWXO :: FileMode Source #

00007 others have read, write and execute permission

pattern S_IROTH :: FileMode Source #

00004 others have read permission

pattern S_IWOTH :: FileMode Source #

00002 others have write permission

pattern S_IXOTH :: FileMode Source #

00001 others have execute permission

pattern DEFAULT_MODE :: FileMode Source #

Default mode for open, 0o666(readable and writable).

pattern S_IFMT :: FileMode Source #

This is the file type mask.

pattern S_IFLNK :: FileMode Source #

This is the file type constant of a symbolic link.

pattern S_IFDIR :: FileMode Source #

This is the file type constant of a directory file.

pattern S_IFREG :: FileMode Source #

This is the file type constant of a regular file.

pattern O_APPEND :: FileFlag Source #

The file is opened in append mode. Before each write, the file offset is positioned at the end of the file.

pattern O_CREAT :: FileFlag Source #

The file is created if it does not already exist.

pattern O_DIRECT :: FileFlag Source #

File IO is done directly to and from user-space buffers, which must be aligned. Buffer size and address should be a multiple of the physical sector size of the block device, (DO NOT USE WITH Z-IO's BufferedIO)

pattern O_DIRECTORY :: FileFlag Source #

If the path is not a directory, fail the open. (Not useful on regular file)

Note O_DIRECTORY is not supported on Windows.

pattern O_DSYNC :: FileFlag Source #

The file is opened for synchronous IO. Write operations will complete once all data and a minimum of metadata are flushed to disk.

Note O_DSYNC is supported on Windows via FILE_FLAG_WRITE_THROUGH.

pattern O_EXCL :: FileFlag Source #

If the O_CREAT flag is set and the file already exists, fail the open.

Note In general, the behavior of O_EXCL is undefined if it is used without O_CREAT. There is one exception: on Linux 2.6 and later, O_EXCL can be used without O_CREAT if pathname refers to a block device. If the block device is in use by the system (e.g., mounted), the open will fail with the error EBUSY.

pattern O_EXLOCK :: FileFlag Source #

Atomically obtain an exclusive lock.

Note UV_FS_O_EXLOCK is only supported on macOS and Windows. (libuv: Changed in version 1.17.0: support is added for Windows.)

pattern O_NOATIME :: FileFlag Source #

Do not update the file access time when the file is read.

Note O_NOATIME is not supported on Windows.

pattern O_NOCTTY :: FileFlag Source #

If the path identifies a terminal device, opening the path will not cause that terminal to become the controlling terminal for the process (if the process does not already have one). (Not sure if this flag is useful)

Note O_NOCTTY is not supported on Windows.

pattern O_NOFOLLOW :: FileFlag Source #

If the path is a symbolic link, fail the open.

Note O_NOFOLLOW is not supported on Windows.

pattern O_NONBLOCK :: FileFlag Source #

Open the file in nonblocking mode if possible. (Definitely not useful in Z-IO)

Note O_NONBLOCK is not supported on Windows. (Not useful on regular file anyway)

pattern O_RANDOM :: FileFlag Source #

Access is intended to be random. The system can use this as a hint to optimize file caching.

Note O_RANDOM is only supported on Windows via FILE_FLAG_RANDOM_ACCESS.

pattern O_RDONLY :: FileFlag Source #

Open the file for read-only access.

pattern O_RDWR :: FileFlag Source #

Open the file for read-write access.

pattern O_SEQUENTIAL :: FileFlag Source #

Access is intended to be sequential from beginning to end. The system can use this as a hint to optimize file caching.

Note O_SEQUENTIAL is only supported on Windows via FILE_FLAG_SEQUENTIAL_SCAN.

pattern O_SHORT_LIVED :: FileFlag Source #

The file is temporary and should not be flushed to disk if possible.

Note O_SHORT_LIVED is only supported on Windows via FILE_ATTRIBUTE_TEMPORARY.

pattern O_SYMLINK :: FileFlag Source #

Open the symbolic link itself rather than the resource it points to.

pattern O_SYNC :: FileFlag Source #

The file is opened for synchronous IO. Write operations will complete once all data and all metadata are flushed to disk.

Note O_SYNC is supported on Windows via FILE_FLAG_WRITE_THROUGH.

pattern O_TEMPORARY :: FileFlag Source #

The file is temporary and should not be flushed to disk if possible.

Note O_TEMPORARY is only supported on Windows via FILE_ATTRIBUTE_TEMPORARY.

pattern O_TRUNC :: FileFlag Source #

If the file exists and is a regular file, and the file is opened successfully for write access, its length shall be truncated to zero.

pattern O_WRONLY :: FileFlag Source #

Open the file for write-only access.

data DirEntType Source #

Instances

Instances details
Enum DirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Eq DirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord DirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Read DirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Show DirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic DirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep DirEntType :: Type -> Type #

ToValue DirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: DirEntType -> Value #

EncodeJSON DirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: DirEntType -> Builder () #

FromValue DirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT DirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep DirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep DirEntType = D1 ('MetaData "DirEntType" "Z.IO.UV.FFI" "Z-IO-0.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" 'False) (((C1 ('MetaCons "DirEntUnknown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DirEntFile" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DirEntDir" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DirEntLink" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DirEntFIFO" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DirEntSocket" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DirEntChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DirEntBlock" 'PrefixI 'False) (U1 :: Type -> Type))))

data UVTimeSpec Source #

Constructors

UVTimeSpec 

Instances

Instances details
Eq UVTimeSpec Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord UVTimeSpec Source # 
Instance details

Defined in Z.IO.UV.FFI

Read UVTimeSpec Source # 
Instance details

Defined in Z.IO.UV.FFI

Show UVTimeSpec Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic UVTimeSpec Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep UVTimeSpec :: Type -> Type #

ToValue UVTimeSpec Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: UVTimeSpec -> Value #

EncodeJSON UVTimeSpec Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: UVTimeSpec -> Builder () #

FromValue UVTimeSpec Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT UVTimeSpec Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable UVTimeSpec Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep UVTimeSpec Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep UVTimeSpec = D1 ('MetaData "UVTimeSpec" "Z.IO.UV.FFI" "Z-IO-0.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" 'False) (C1 ('MetaCons "UVTimeSpec" 'PrefixI 'True) (S1 ('MetaSel ('Just "uvtSecond") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 CLong) :*: S1 ('MetaSel ('Just "uvtNanoSecond") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 CLong)))

data FStat Source #

Instances

Instances details
Eq FStat Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

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

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

Ord FStat Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

compare :: FStat -> FStat -> Ordering #

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

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

(>) :: FStat -> FStat -> Bool #

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

max :: FStat -> FStat -> FStat #

min :: FStat -> FStat -> FStat #

Read FStat Source # 
Instance details

Defined in Z.IO.UV.FFI

Show FStat Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

showsPrec :: Int -> FStat -> ShowS #

show :: FStat -> String #

showList :: [FStat] -> ShowS #

Generic FStat Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep FStat :: Type -> Type #

Methods

from :: FStat -> Rep FStat x #

to :: Rep FStat x -> FStat #

ToValue FStat Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: FStat -> Value #

EncodeJSON FStat Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: FStat -> Builder () #

FromValue FStat Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT FStat Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

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

type Rep FStat Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep FStat = D1 ('MetaData "FStat" "Z.IO.UV.FFI" "Z-IO-0.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" 'False) (C1 ('MetaCons "FStat" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "stDev") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "stMode") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 FileMode)) :*: (S1 ('MetaSel ('Just "stNlink") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "stUID") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 UID))) :*: ((S1 ('MetaSel ('Just "stGID") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 GID) :*: S1 ('MetaSel ('Just "stRdev") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "stIno") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "stSize") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64)))) :*: (((S1 ('MetaSel ('Just "stBlksize") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "stBlocks") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "stFlags") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "stGen") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "stAtim") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 UVTimeSpec) :*: S1 ('MetaSel ('Just "stMtim") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 UVTimeSpec)) :*: (S1 ('MetaSel ('Just "stCtim") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 UVTimeSpec) :*: S1 ('MetaSel ('Just "stBirthtim") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 UVTimeSpec))))))

type CopyFileFlag = CInt Source #

Flags control copying.

  • COPYFILE_EXCL: If present, uv_fs_copyfile() will fail with UV_EEXIST if the destination path already exists. The default behavior is to overwrite the destination if it exists.
  • COPYFILE_FICLONE: If present, uv_fs_copyfile() will attempt to create a copy-on-write reflink. If the underlying platform does not support copy-on-write, then a fallback copy mechanism is used.
  • COPYFILE_FICLONE_FORCE: If present, uv_fs_copyfile() will attempt to create a copy-on-write reflink. If the underlying platform does not support copy-on-write, or an error occurs while attempting to use copy-on-write, then an error is returned.

pattern F_OK :: AccessMode Source #

pattern R_OK :: AccessMode Source #

pattern W_OK :: AccessMode Source #

pattern X_OK :: AccessMode Source #

data AccessResult Source #

Instances

Instances details
Enum AccessResult Source # 
Instance details

Defined in Z.IO.UV.FFI

Eq AccessResult Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord AccessResult Source # 
Instance details

Defined in Z.IO.UV.FFI

Show AccessResult Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic AccessResult Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep AccessResult :: Type -> Type #

ToValue AccessResult Source # 
Instance details

Defined in Z.IO.UV.FFI

EncodeJSON AccessResult Source # 
Instance details

Defined in Z.IO.UV.FFI

FromValue AccessResult Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT AccessResult Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep AccessResult Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep AccessResult = D1 ('MetaData "AccessResult" "Z.IO.UV.FFI" "Z-IO-0.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" 'False) (C1 ('MetaCons "NoExistence" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NoPermission" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccessOK" 'PrefixI 'False) (U1 :: Type -> Type)))

type SymlinkFlag = CInt Source #

On Windows the flags parameter can be specified to control how the symlink will be created:

newtype UID Source #

Constructors

UID Word32 

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 #

ToValue UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: UID -> Value #

EncodeJSON UID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: UID -> Builder () #

FromValue UID Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT 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.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" 'True) (C1 ('MetaCons "UID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

newtype GID Source #

Constructors

GID Word32 

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 #

ToValue GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: GID -> Value #

EncodeJSON GID Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: GID -> Builder () #

FromValue GID Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT 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.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" 'True) (C1 ('MetaCons "GID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

pattern PROCESS_SETUID :: ProcessFlag Source #

Set the child process' user id.

This is not supported on Windows, uv_spawn() will fail and set the error to UV_ENOTSUP.

pattern PROCESS_SETGID :: ProcessFlag Source #

Set the child process' user id.

This is not supported on Windows, uv_spawn() will fail and set the error to UV_ENOTSUP.

pattern PROCESS_WINDOWS_VERBATIM_ARGUMENTS :: ProcessFlag Source #

Do not wrap any arguments in quotes, or perform any other escaping, when converting the argument list into a command line string.

This option is only meaningful on Windows systems. On Unix it is silently ignored.

pattern PROCESS_DETACHED :: ProcessFlag Source #

Spawn the child process in a detached state

This will make it a process group leader, and will effectively enable the child to keep running after the parent exits.

pattern PROCESS_WINDOWS_HIDE :: ProcessFlag Source #

Hide the subprocess window that would normally be created.

This option is only meaningful on Windows systems. On Unix it is silently ignored.

pattern PROCESS_WINDOWS_HIDE_CONSOLE :: ProcessFlag Source #

Hide the subprocess console window that would normally be created.

This option is only meaningful on Windows systems. On Unix it is silently ignored.

pattern PROCESS_WINDOWS_HIDE_GUI :: ProcessFlag Source #

Hide the subprocess GUI window that would normally be created.

This option is only meaningful on Windows systems. On Unix it is silently ignored.

data ProcessOptions Source #

Constructors

ProcessOptions 

Fields

Instances

Instances details
Eq ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

Read ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

Show ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep ProcessOptions :: Type -> Type #

ToValue ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

EncodeJSON ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

FromValue ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

data ProcessStdStream Source #

Constructors

ProcessIgnore

redirect process std stream to /dev/null

ProcessCreate

create a new std stream

ProcessInherit FD

pass an existing FD to child process as std stream

Instances

Instances details
Eq ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

Read ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

Show ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep ProcessStdStream :: Type -> Type #

ToValue ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

EncodeJSON ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

FromValue ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep ProcessStdStream = D1 ('MetaData "ProcessStdStream" "Z.IO.UV.FFI" "Z-IO-0.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" 'False) (C1 ('MetaCons "ProcessIgnore" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ProcessCreate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProcessInherit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FD))))

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 #

ToValue TimeVal Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: TimeVal -> Value #

EncodeJSON TimeVal Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: TimeVal -> Builder () #

FromValue TimeVal Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT 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.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" '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 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 #

ToValue ResUsage Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: ResUsage -> Value #

EncodeJSON ResUsage Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: ResUsage -> Builder () #

FromValue ResUsage Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT 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.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" '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))))))

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 #

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

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.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" 'True) (C1 ('MetaCons "PID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)))

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 #

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

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.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" '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 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 #

ToValue PassWD Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: PassWD -> Value #

EncodeJSON PassWD Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: PassWD -> Builder () #

FromValue PassWD Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT 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.1.8.0-7YhFIAPi9HDI1OeLA2mSRE" '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 :: 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 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 #

ToValue CPUInfo Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: CPUInfo -> Value #

EncodeJSON CPUInfo Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: CPUInfo -> Builder () #

FromValue CPUInfo Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT 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

getCPUInfo :: IO [CPUInfo] Source #

Gets information about the CPUs on the system.

pattern UV_RENAME :: Word8 Source #

pattern UV_CHANGE :: Word8 Source #