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

newtype UVRunMode Source #

Constructors

UVRunMode CInt 
Instances
Eq UVRunMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord UVRunMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Show UVRunMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic UVRunMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep UVRunMode :: Type -> Type #

ShowT UVRunMode Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep UVRunMode Source # 
Instance details

Defined in Z.IO.UV.FFI

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

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.

newtype Membership Source #

Constructors

Membership CInt 
Instances
Eq Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Show Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep Membership :: Type -> Type #

ToValue Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: Membership -> Value #

EncodeJSON Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: Membership -> Builder () #

FromValue Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep Membership Source # 
Instance details

Defined in Z.IO.UV.FFI

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

newtype UDPFlag Source #

Constructors

UDPFlag CInt 
Instances
Eq UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

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

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

Num UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Show UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep UDPFlag :: Type -> Type #

Methods

from :: UDPFlag -> Rep UDPFlag x #

to :: Rep UDPFlag x -> UDPFlag #

FiniteBits UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

ToValue UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: UDPFlag -> Value #

EncodeJSON UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: UDPFlag -> Builder () #

FromValue UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Unaligned UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Bits UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep UDPFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

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

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

Just pass null pointer as SocketAddr to disconnect

newtype TTYMode Source #

Terminal mode.

When in UV_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.

Constructors

TTYMode CInt 
Instances
Eq TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

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

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

Num TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Show TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep TTYMode :: Type -> Type #

Methods

from :: TTYMode -> Rep TTYMode x #

to :: Rep TTYMode x -> TTYMode #

FiniteBits TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

ToValue TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: TTYMode -> Value #

EncodeJSON TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: TTYMode -> Builder () #

FromValue TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Unaligned TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Bits TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

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

newtype FileMode Source #

Constructors

FileMode CInt 
Instances
Eq FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Num FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Show FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep FileMode :: Type -> Type #

Methods

from :: FileMode -> Rep FileMode x #

to :: Rep FileMode x -> FileMode #

FiniteBits FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

ToValue FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: FileMode -> Value #

EncodeJSON FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: FileMode -> Builder () #

FromValue FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Unaligned FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Bits FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep FileMode Source # 
Instance details

Defined in Z.IO.UV.FFI

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

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).

newtype FileFlag Source #

Constructors

FileFlag CInt 
Instances
Eq FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Num FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Show FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep FileFlag :: Type -> Type #

Methods

from :: FileFlag -> Rep FileFlag x #

to :: Rep FileFlag x -> FileFlag #

FiniteBits FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

ToValue FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: FileFlag -> Value #

EncodeJSON FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: FileFlag -> Builder () #

FromValue FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Unaligned FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Bits FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep FileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

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

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.

newtype UVDirEntType Source #

Constructors

UVDirEntType CChar 
Instances
Eq UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Num UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Show UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep UVDirEntType :: Type -> Type #

FiniteBits UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

ToValue UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

EncodeJSON UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

FromValue UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Unaligned UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

Bits UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep UVDirEntType Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep UVDirEntType = D1 (MetaData "UVDirEntType" "Z.IO.UV.FFI" "Z-IO-0.1.4.0-IfRX4KH4mesBaX238HlX2d" True) (C1 (MetaCons "UVDirEntType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CChar)))

data DirEntType Source #

Instances
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.4.0-IfRX4KH4mesBaX238HlX2d" 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
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.4.0-IfRX4KH4mesBaX238HlX2d" 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
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

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

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.4.0-IfRX4KH4mesBaX238HlX2d" False) (C1 (MetaCons "FStat" PrefixI True) ((((S1 (MetaSel (Just "stDev") SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64) :*: S1 (MetaSel (Just "stMode") SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64)) :*: (S1 (MetaSel (Just "stNlink") SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64) :*: S1 (MetaSel (Just "stUid") SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64))) :*: ((S1 (MetaSel (Just "stGid") SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64) :*: 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))))))

newtype CopyFileFlag 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.

Constructors

CopyFileFlag CInt 
Instances
Eq CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Num CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Show CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep CopyFileFlag :: Type -> Type #

FiniteBits CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

ToValue CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

EncodeJSON CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

FromValue CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Unaligned CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Bits CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep CopyFileFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

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

newtype AccessMode Source #

Constructors

AccessMode CInt 
Instances
Eq AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Num AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Show AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep AccessMode :: Type -> Type #

FiniteBits AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

ToValue AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: AccessMode -> Value #

EncodeJSON AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: AccessMode -> Builder () #

FromValue AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Unaligned AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Bits AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep AccessMode Source # 
Instance details

Defined in Z.IO.UV.FFI

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

pattern F_OK :: AccessMode Source #

pattern R_OK :: AccessMode Source #

pattern W_OK :: AccessMode Source #

pattern X_OK :: AccessMode Source #

data AccessResult Source #

Instances
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.4.0-IfRX4KH4mesBaX238HlX2d" 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)))

newtype SymlinkFlag Source #

Constructors

SymlinkFlag CInt 
Instances
Eq SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Num SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Show SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep SymlinkFlag :: Type -> Type #

FiniteBits SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

ToValue SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: SymlinkFlag -> Value #

EncodeJSON SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

FromValue SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Unaligned SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

Bits SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep SymlinkFlag Source # 
Instance details

Defined in Z.IO.UV.FFI

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

newtype UVHandleType Source #

Constructors

UVHandleType CInt 
Instances
Eq UVHandleType Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord UVHandleType Source # 
Instance details

Defined in Z.IO.UV.FFI

Show UVHandleType Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic UVHandleType Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep UVHandleType :: Type -> Type #

ToValue UVHandleType Source # 
Instance details

Defined in Z.IO.UV.FFI

EncodeJSON UVHandleType Source # 
Instance details

Defined in Z.IO.UV.FFI

FromValue UVHandleType Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT UVHandleType Source # 
Instance details

Defined in Z.IO.UV.FFI

Unaligned UVHandleType Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable UVHandleType Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep UVHandleType Source # 
Instance details

Defined in Z.IO.UV.FFI

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

data TimeVal Source #

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

Constructors

TimeVal 

Fields

Instances
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

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.4.0-IfRX4KH4mesBaX238HlX2d" 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
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

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.4.0-IfRX4KH4mesBaX238HlX2d" 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
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

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

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