stdio-0.2.0.0: A simple and high performance IO toolkit for Haskell

Copyright(c) Winterland 2017-2018
LicenseBSD
Maintainerdrkoster@qq.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Std.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 Std.IO.UV.FFI

Num UVRunMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Ord UVRunMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Read UVRunMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Show UVRunMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Storable UVRunMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Bits UVRunMode Source # 
Instance details

Defined in Std.IO.UV.FFI

FiniteBits UVRunMode Source # 
Instance details

Defined in Std.IO.UV.FFI

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

Constructors

UVUDPFlag CInt 
Instances
Eq UVUDPFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Num UVUDPFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Ord UVUDPFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Show UVUDPFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Storable UVUDPFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Bits UVUDPFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

FiniteBits UVUDPFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

newtype UVTTYMode 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

UVTTYMode CInt 
Instances
Eq UVTTYMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Num UVTTYMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Ord UVTTYMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Read UVTTYMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Show UVTTYMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Storable UVTTYMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Bits UVTTYMode Source # 
Instance details

Defined in Std.IO.UV.FFI

FiniteBits UVTTYMode Source # 
Instance details

Defined in Std.IO.UV.FFI

newtype UVFileMode Source #

Constructors

UVFileMode CInt 
Instances
Eq UVFileMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Num UVFileMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Ord UVFileMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Read UVFileMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Show UVFileMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Storable UVFileMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Bits UVFileMode Source # 
Instance details

Defined in Std.IO.UV.FFI

FiniteBits UVFileMode Source # 
Instance details

Defined in Std.IO.UV.FFI

pattern S_IRWXU :: UVFileMode Source #

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

pattern S_IRUSR :: UVFileMode Source #

00400 user has read permission

pattern S_IWUSR :: UVFileMode Source #

00200 user has write permission

pattern S_IXUSR :: UVFileMode Source #

00100 user has execute permission

pattern S_IRWXG :: UVFileMode Source #

00070 group has read, write and execute permission

pattern S_IRGRP :: UVFileMode Source #

00040 group has read permission

pattern S_IWGRP :: UVFileMode Source #

00020 group has write permission

pattern S_IXGRP :: UVFileMode Source #

00010 group has execute permission

pattern S_IRWXO :: UVFileMode Source #

00007 others have read, write and execute permission

pattern S_IROTH :: UVFileMode Source #

00004 others have read permission

pattern S_IWOTH :: UVFileMode Source #

00002 others have write permission

pattern S_IXOTH :: UVFileMode Source #

00001 others have execute permission

pattern DEFAULT_MODE :: UVFileMode Source #

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

newtype UVFileFlag Source #

Constructors

UVFileFlag CInt 
Instances
Eq UVFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Num UVFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Ord UVFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Read UVFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Show UVFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Storable UVFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Bits UVFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

FiniteBits UVFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

pattern O_APPEND :: UVFileFlag 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 :: UVFileFlag Source #

The file is created if it does not already exist.

pattern O_DIRECT :: UVFileFlag 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 stdio's BufferedIO)

pattern O_DIRECTORY :: UVFileFlag 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 :: UVFileFlag 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 :: UVFileFlag 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 :: UVFileFlag 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 :: UVFileFlag Source #

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

Note o_NOATIME is not supported on Windows.

pattern O_NOCTTY :: UVFileFlag 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 :: UVFileFlag Source #

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

Note o_NOFOLLOW is not supported on Windows.

pattern O_NONBLOCK :: UVFileFlag Source #

Open the file in nonblocking mode if possible. (Definitely not useful with stdio)

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

pattern O_RANDOM :: UVFileFlag 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 :: UVFileFlag Source #

Open the file for read-only access.

pattern O_RDWR :: UVFileFlag Source #

Open the file for read-write access.

pattern O_SEQUENTIAL :: UVFileFlag 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 :: UVFileFlag 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 :: UVFileFlag Source #

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

pattern O_SYNC :: UVFileFlag 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 :: UVFileFlag 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 :: UVFileFlag 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 :: UVFileFlag Source #

Open the file for write-only access.

newtype UVDirEntType Source #

Constructors

UVDirEntType CChar 
Instances
Eq UVDirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

Num UVDirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

Ord UVDirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

Read UVDirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

Show UVDirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

Storable UVDirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

Bits UVDirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

FiniteBits UVDirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

data DirEntType Source #

Instances
Eq DirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

Ord DirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

Read DirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

Show DirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

Generic DirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

Associated Types

type Rep DirEntType :: Type -> Type #

type Rep DirEntType Source # 
Instance details

Defined in Std.IO.UV.FFI

type Rep DirEntType = D1 (MetaData "DirEntType" "Std.IO.UV.FFI" "stdio-0.2.0.0-5YmH16k3vlO7FAtmF9PgfB" 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 Std.IO.UV.FFI

Ord UVTimeSpec Source # 
Instance details

Defined in Std.IO.UV.FFI

Read UVTimeSpec Source # 
Instance details

Defined in Std.IO.UV.FFI

Show UVTimeSpec Source # 
Instance details

Defined in Std.IO.UV.FFI

Generic UVTimeSpec Source # 
Instance details

Defined in Std.IO.UV.FFI

Associated Types

type Rep UVTimeSpec :: Type -> Type #

Storable UVTimeSpec Source # 
Instance details

Defined in Std.IO.UV.FFI

type Rep UVTimeSpec Source # 
Instance details

Defined in Std.IO.UV.FFI

type Rep UVTimeSpec = D1 (MetaData "UVTimeSpec" "Std.IO.UV.FFI" "stdio-0.2.0.0-5YmH16k3vlO7FAtmF9PgfB" 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 UVStat Source #

Instances
Eq UVStat Source # 
Instance details

Defined in Std.IO.UV.FFI

Methods

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

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

Ord UVStat Source # 
Instance details

Defined in Std.IO.UV.FFI

Read UVStat Source # 
Instance details

Defined in Std.IO.UV.FFI

Show UVStat Source # 
Instance details

Defined in Std.IO.UV.FFI

Generic UVStat Source # 
Instance details

Defined in Std.IO.UV.FFI

Associated Types

type Rep UVStat :: Type -> Type #

Methods

from :: UVStat -> Rep UVStat x #

to :: Rep UVStat x -> UVStat #

type Rep UVStat Source # 
Instance details

Defined in Std.IO.UV.FFI

type Rep UVStat = D1 (MetaData "UVStat" "Std.IO.UV.FFI" "stdio-0.2.0.0-5YmH16k3vlO7FAtmF9PgfB" False) (C1 (MetaCons "UVStat" 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 UVCopyFileFlag 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

UVCopyFileFlag CInt 
Instances
Eq UVCopyFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Num UVCopyFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Ord UVCopyFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Read UVCopyFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Show UVCopyFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Storable UVCopyFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Bits UVCopyFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

FiniteBits UVCopyFileFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

newtype UVAccessMode Source #

Constructors

UVAccessMode CInt 
Instances
Eq UVAccessMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Num UVAccessMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Ord UVAccessMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Read UVAccessMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Show UVAccessMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Storable UVAccessMode Source # 
Instance details

Defined in Std.IO.UV.FFI

Bits UVAccessMode Source # 
Instance details

Defined in Std.IO.UV.FFI

FiniteBits UVAccessMode Source # 
Instance details

Defined in Std.IO.UV.FFI

newtype UVSymlinkFlag Source #

Constructors

UVSymlinkFlag CInt 
Instances
Eq UVSymlinkFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Num UVSymlinkFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Ord UVSymlinkFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Read UVSymlinkFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Show UVSymlinkFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Storable UVSymlinkFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

Bits UVSymlinkFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

FiniteBits UVSymlinkFlag Source # 
Instance details

Defined in Std.IO.UV.FFI

newtype UVHandleType Source #

Constructors

UVHandleType CInt