Copyright | (c) Winterland 2017-2018 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
INTERNAL MODULE, provides all libuv side operations(env related is moved to FFI_ENV).
Synopsis
- uv_version :: IO CUInt
- uv_version_string :: IO CString
- type UVSlot = Int
- newtype UVSlotUnsafe = UVSlotUnsafe {}
- type FD = CInt
- pattern SO_REUSEPORT_LOAD_BALANCE :: Int
- pattern INIT_LOOP_SIZE :: Int
- data UVLoop
- data UVLoopData
- peekUVEventQueue :: Ptr UVLoopData -> IO (Int, Ptr Int)
- clearUVEventCounter :: Ptr UVLoopData -> IO ()
- peekUVBufferTable :: Ptr UVLoopData -> IO (Ptr (Ptr Word8), Ptr CSsize)
- type UVRunMode = CInt
- pattern UV_RUN_DEFAULT :: UVRunMode
- pattern UV_RUN_ONCE :: UVRunMode
- pattern UV_RUN_NOWAIT :: UVRunMode
- peekUVLoopData :: Ptr UVLoop -> IO (Ptr UVLoopData)
- hs_uv_loop_init :: Int -> IO (Ptr UVLoop)
- hs_uv_loop_close :: Ptr UVLoop -> IO ()
- uv_run :: Ptr UVLoop -> UVRunMode -> IO CInt
- uv_run_safe :: Ptr UVLoop -> UVRunMode -> IO CInt
- uv_loop_alive :: Ptr UVLoop -> IO CInt
- hs_uv_wake_up_timer :: Ptr UVLoopData -> IO CInt
- hs_uv_wake_up_async :: Ptr UVLoopData -> IO CInt
- data UVHandle
- peekUVHandleData :: Ptr UVHandle -> IO UVSlotUnsafe
- hs_uv_fileno :: Ptr UVHandle -> IO FD
- hs_uv_handle_alloc :: Ptr UVLoop -> IO (Ptr UVHandle)
- hs_uv_handle_free :: Ptr UVHandle -> IO ()
- hs_uv_handle_close :: Ptr UVHandle -> IO ()
- uv_unref :: Ptr UVHandle -> IO ()
- hs_uv_cancel :: Ptr UVLoop -> UVSlot -> IO ()
- hs_uv_check_alloc :: IO (Ptr UVHandle)
- hs_uv_check_init :: Ptr UVHandle -> Ptr UVHandle -> IO CInt
- hs_uv_check_close :: Ptr UVHandle -> IO ()
- hs_uv_listen :: Ptr UVHandle -> CInt -> IO CInt
- hs_uv_listen_resume :: Ptr UVHandle -> IO ()
- hs_uv_read_start :: Ptr UVHandle -> IO CInt
- uv_read_stop :: Ptr UVHandle -> IO CInt
- hs_uv_write :: Ptr UVHandle -> Ptr Word8 -> Int -> IO UVSlotUnsafe
- hs_uv_try_write :: Ptr UVHandle -> Ptr Word8 -> Int -> IO Int
- hs_uv_shutdown :: Ptr UVHandle -> IO UVSlotUnsafe
- hs_uv_accept_check_start :: Ptr UVHandle -> IO CInt
- uv_tcp_open :: Ptr UVHandle -> FD -> IO CInt
- uv_tcp_init :: Ptr UVLoop -> Ptr UVHandle -> IO CInt
- uv_tcp_init_ex :: Ptr UVLoop -> Ptr UVHandle -> CUInt -> IO CInt
- uv_tcp_nodelay :: Ptr UVHandle -> CInt -> IO CInt
- uv_tcp_keepalive :: Ptr UVHandle -> CInt -> CUInt -> IO CInt
- uv_tcp_getsockname :: Ptr UVHandle -> MBA# SocketAddr -> MBA# CInt -> IO CInt
- uv_tcp_getpeername :: Ptr UVHandle -> MBA# SocketAddr -> MBA# CInt -> IO CInt
- uV_TCP_IPV6ONLY :: CUInt
- uv_tcp_bind :: Ptr UVHandle -> MBA# SocketAddr -> CUInt -> IO CInt
- hs_uv_tcp_connect :: Ptr UVHandle -> MBA# SocketAddr -> IO UVSlotUnsafe
- hs_set_socket_reuse :: Ptr UVHandle -> IO CInt
- uv_pipe_open :: Ptr UVHandle -> FD -> IO CInt
- uv_pipe_init :: Ptr UVLoop -> Ptr UVHandle -> CInt -> IO CInt
- uv_pipe_bind :: Ptr UVHandle -> BA# Word8 -> IO CInt
- hs_uv_pipe_connect :: Ptr UVHandle -> BA# Word8 -> IO UVSlotUnsafe
- uv_udp_init :: Ptr UVLoop -> Ptr UVHandle -> IO CInt
- uv_udp_init_ex :: Ptr UVLoop -> Ptr UVHandle -> CUInt -> IO CInt
- uv_udp_open :: Ptr UVHandle -> FD -> IO CInt
- uv_udp_bind :: Ptr UVHandle -> MBA# SocketAddr -> UDPFlag -> IO CInt
- type Membership = CInt
- pattern LEAVE_GROUP :: Membership
- pattern JOIN_GROUP :: Membership
- type UDPFlag = CInt
- pattern UDP_DEFAULT :: UDPFlag
- pattern UDP_IPV6ONLY :: UDPFlag
- pattern UDP_REUSEADDR :: UDPFlag
- pattern UV_UDP_PARTIAL :: Int32
- uv_udp_connect :: Ptr UVHandle -> MBA# SocketAddr -> IO CInt
- uv_udp_disconnect :: Ptr UVHandle -> Ptr SocketAddr -> IO CInt
- uv_udp_set_membership :: Ptr UVHandle -> BA# Word8 -> BA# Word8 -> Membership -> IO CInt
- uv_udp_set_source_membership :: Ptr UVHandle -> BA# Word8 -> BA# Word8 -> BA# Word8 -> Membership -> IO CInt
- uv_udp_set_multicast_loop :: Ptr UVHandle -> CInt -> IO CInt
- uv_udp_set_multicast_ttl :: Ptr UVHandle -> CInt -> IO CInt
- uv_udp_set_multicast_interface :: Ptr UVHandle -> BA# Word8 -> IO CInt
- uv_udp_set_broadcast :: Ptr UVHandle -> CInt -> IO CInt
- uv_udp_set_ttl :: Ptr UVHandle -> CInt -> IO CInt
- hs_uv_udp_recv_start :: Ptr UVHandle -> IO CInt
- uv_udp_recv_stop :: Ptr UVHandle -> IO CInt
- hs_uv_udp_check_start :: Ptr UVHandle -> IO CInt
- hs_uv_udp_send :: Ptr UVHandle -> MBA# SocketAddr -> Ptr Word8 -> Int -> IO UVSlotUnsafe
- hs_uv_udp_send_connected :: Ptr UVHandle -> Ptr Word8 -> Int -> IO UVSlotUnsafe
- uv_udp_getsockname :: Ptr UVHandle -> MBA# SocketAddr -> MBA# CInt -> IO CInt
- uv_udp_getpeername :: Ptr UVHandle -> MBA# SocketAddr -> MBA# CInt -> IO CInt
- type TTYMode = CInt
- pattern TTY_MODE_NORMAL :: TTYMode
- pattern TTY_MODE_RAW :: TTYMode
- pattern TTY_MODE_IO :: TTYMode
- uv_tty_init :: Ptr UVLoop -> Ptr UVHandle -> CInt -> IO CInt
- uv_tty_set_mode :: Ptr UVHandle -> TTYMode -> IO CInt
- uv_tty_get_winsize :: Ptr UVHandle -> MBA# CInt -> MBA# CInt -> IO CInt
- type FileMode = CInt
- pattern S_IRWXU :: FileMode
- pattern S_IRUSR :: FileMode
- pattern S_IWUSR :: FileMode
- pattern S_IXUSR :: FileMode
- pattern S_IRWXG :: FileMode
- pattern S_IRGRP :: FileMode
- pattern S_IWGRP :: FileMode
- pattern S_IXGRP :: FileMode
- pattern S_IRWXO :: FileMode
- pattern S_IROTH :: FileMode
- pattern S_IWOTH :: FileMode
- pattern S_IXOTH :: FileMode
- pattern DEFAULT_FILE_MODE :: FileMode
- pattern DEFAULT_DIR_MODE :: FileMode
- pattern S_IFMT :: FileMode
- pattern S_IFLNK :: FileMode
- pattern S_IFDIR :: FileMode
- pattern S_IFREG :: FileMode
- hs_uv_fs_open :: BA# Word8 -> FileFlag -> FileMode -> IO FD
- hs_uv_fs_close :: FD -> IO Int
- hs_uv_fs_read :: FD -> Ptr Word8 -> Int -> Int64 -> IO Int
- hs_uv_fs_write :: FD -> Ptr Word8 -> Int -> Int64 -> IO Int
- hs_uv_fs_unlink :: BA# Word8 -> IO Int
- hs_uv_fs_mkdir :: BA# Word8 -> FileMode -> IO Int
- hs_uv_fs_rmdir :: BA# Word8 -> IO Int
- hs_uv_fs_mkdtemp :: BA# Word8 -> Int -> MBA# Word8 -> IO Int
- hs_uv_fs_mkstemp :: BA# Word8 -> Int -> MBA# Word8 -> IO Int
- hs_uv_fs_open_threaded :: BA# Word8 -> FileFlag -> FileMode -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_close_threaded :: FD -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_read_threaded :: FD -> Ptr Word8 -> Int -> Int64 -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_write_threaded :: FD -> Ptr Word8 -> Int -> Int64 -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_unlink_threaded :: BA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_mkdir_threaded :: BA# Word8 -> FileMode -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_rmdir_threaded :: BA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_mkdtemp_threaded :: BA# Word8 -> Int -> MBA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_mkstemp_threaded :: BA# Word8 -> Int -> MBA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
- type FileFlag = CInt
- pattern O_APPEND :: FileFlag
- pattern O_CREAT :: FileFlag
- pattern O_DIRECT :: FileFlag
- pattern O_DIRECTORY :: FileFlag
- pattern O_DSYNC :: FileFlag
- pattern O_EXCL :: FileFlag
- pattern O_EXLOCK :: FileFlag
- pattern O_NOATIME :: FileFlag
- pattern O_NOCTTY :: FileFlag
- pattern O_NOFOLLOW :: FileFlag
- pattern O_NONBLOCK :: FileFlag
- pattern O_RANDOM :: FileFlag
- pattern O_RDONLY :: FileFlag
- pattern O_RDWR :: FileFlag
- pattern O_SEQUENTIAL :: FileFlag
- pattern O_SHORT_LIVED :: FileFlag
- pattern O_SYMLINK :: FileFlag
- pattern O_SYNC :: FileFlag
- pattern O_TEMPORARY :: FileFlag
- pattern O_TRUNC :: FileFlag
- pattern O_WRONLY :: FileFlag
- type Whence = CInt
- pattern SEEK_SET :: Whence
- pattern SEEK_CUR :: Whence
- pattern SEEK_END :: Whence
- hs_seek :: FD -> Int64 -> Whence -> IO Int64
- type UVDirEntType = CChar
- data DirEntType
- fromUVDirEntType :: UVDirEntType -> DirEntType
- peekUVDirEnt :: Ptr DirEntType -> IO (CString, UVDirEntType)
- hs_uv_fs_scandir_cleanup :: Ptr (Ptr DirEntType) -> Int -> IO ()
- hs_uv_fs_scandir :: BA# Word8 -> MBA# (Ptr DirEntType) -> IO Int
- hs_uv_fs_scandir_extra_cleanup :: Ptr (Ptr (Ptr DirEntType)) -> Int -> IO ()
- hs_uv_fs_scandir_threaded :: BA# Word8 -> Ptr (Ptr (Ptr DirEntType)) -> Ptr UVLoop -> IO UVSlotUnsafe
- data UVTimeSpec = UVTimeSpec {
- uvtSecond :: !CLong
- uvtNanoSecond :: !CLong
- data FStat = FStat {}
- uvStatSize :: Int
- peekUVStat :: Ptr FStat -> IO FStat
- hs_uv_fs_stat :: BA# Word8 -> Ptr FStat -> IO Int
- hs_uv_fs_fstat :: FD -> Ptr FStat -> IO Int
- hs_uv_fs_lstat :: BA# Word8 -> Ptr FStat -> IO Int
- hs_uv_fs_rename :: BA# Word8 -> BA# Word8 -> IO Int
- hs_uv_fs_fsync :: FD -> IO Int
- hs_uv_fs_fdatasync :: FD -> IO Int
- hs_uv_fs_ftruncate :: FD -> Int64 -> IO Int
- hs_uv_fs_stat_threaded :: BA# Word8 -> Ptr FStat -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_fstat_threaded :: FD -> Ptr FStat -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_lstat_threaded :: BA# Word8 -> Ptr FStat -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_rename_threaded :: BA# Word8 -> BA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_fsync_threaded :: FD -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_fdatasync_threaded :: FD -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_ftruncate_threaded :: FD -> Int64 -> Ptr UVLoop -> IO UVSlotUnsafe
- type CopyFileFlag = CInt
- pattern COPYFILE_DEFAULT :: CopyFileFlag
- pattern COPYFILE_EXCL :: CopyFileFlag
- pattern COPYFILE_FICLONE :: CopyFileFlag
- pattern COPYFILE_FICLONE_FORCE :: CopyFileFlag
- hs_uv_fs_copyfile :: BA# Word8 -> BA# Word8 -> CopyFileFlag -> IO Int
- hs_uv_fs_copyfile_threaded :: BA# Word8 -> BA# Word8 -> CopyFileFlag -> Ptr UVLoop -> IO UVSlotUnsafe
- type AccessMode = CInt
- pattern F_OK :: AccessMode
- pattern R_OK :: AccessMode
- pattern W_OK :: AccessMode
- pattern X_OK :: AccessMode
- data AccessResult
- hs_uv_fs_access :: BA# Word8 -> AccessMode -> IO Int
- hs_uv_fs_access_threaded :: BA# Word8 -> AccessMode -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_chmod :: BA# Word8 -> FileMode -> IO Int
- hs_uv_fs_chmod_threaded :: BA# Word8 -> FileMode -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_fchmod :: FD -> FileMode -> IO Int
- hs_uv_fs_fchmod_threaded :: FD -> FileMode -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_utime :: BA# Word8 -> Double -> Double -> IO Int
- hs_uv_fs_utime_threaded :: BA# Word8 -> Double -> Double -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_futime :: FD -> Double -> Double -> IO Int
- hs_uv_fs_futime_threaded :: FD -> Double -> Double -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_lutime :: BA# Word8 -> Double -> Double -> IO Int
- hs_uv_fs_lutime_threaded :: BA# Word8 -> Double -> Double -> Ptr UVLoop -> IO UVSlotUnsafe
- type SymlinkFlag = CInt
- pattern SYMLINK_DEFAULT :: SymlinkFlag
- pattern SYMLINK_DIR :: SymlinkFlag
- pattern SYMLINK_JUNCTION :: SymlinkFlag
- hs_uv_fs_link :: BA# Word8 -> BA# Word8 -> IO Int
- hs_uv_fs_link_threaded :: BA# Word8 -> BA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_symlink :: BA# Word8 -> BA# Word8 -> SymlinkFlag -> IO Int
- hs_uv_fs_symlink_threaded :: BA# Word8 -> BA# Word8 -> SymlinkFlag -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_readlink_cleanup :: CString -> IO ()
- hs_uv_fs_readlink :: BA# Word8 -> MBA# CString -> IO Int
- hs_uv_fs_realpath :: BA# Word8 -> MBA# CString -> IO Int
- hs_uv_fs_readlink_extra_cleanup :: Ptr CString -> IO ()
- hs_uv_fs_readlink_threaded :: BA# Word8 -> Ptr CString -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_realpath_threaded :: BA# Word8 -> Ptr CString -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_chown :: BA# Word8 -> UID -> GID -> IO Int
- hs_uv_fs_chown_threaded :: BA# Word8 -> UID -> GID -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_fchown :: FD -> UID -> GID -> IO Int
- hs_uv_fs_fchown_threaded :: FD -> UID -> GID -> Ptr UVLoop -> IO UVSlotUnsafe
- hs_uv_fs_lchown :: BA# Word8 -> UID -> GID -> IO Int
- hs_uv_fs_lchown_threaded :: BA# Word8 -> UID -> GID -> Ptr UVLoop -> IO UVSlotUnsafe
- newtype UID = UID Word32
- newtype GID = GID Word32
- type ProcessFlag = CUInt
- pattern PROCESS_SETUID :: ProcessFlag
- pattern PROCESS_SETGID :: ProcessFlag
- pattern PROCESS_WINDOWS_VERBATIM_ARGUMENTS :: ProcessFlag
- pattern PROCESS_DETACHED :: ProcessFlag
- pattern PROCESS_WINDOWS_HIDE :: ProcessFlag
- pattern PROCESS_WINDOWS_HIDE_CONSOLE :: ProcessFlag
- pattern PROCESS_WINDOWS_HIDE_GUI :: ProcessFlag
- data ProcessOptions = ProcessOptions {}
- data ProcessStdStream
- processStdStreamFlag :: ProcessStdStream -> CInt
- hs_uv_spawn :: Ptr UVLoop -> MBA# ProcessOptions -> BA# Word8 -> BAArray# Word8 -> Int -> BAArray# Word8 -> Int -> BA# Word8 -> MBA# ProcessStdStream -> IO Int
- uv_kill :: CInt -> CInt -> IO CInt
- type UVHandleType = CInt
- pattern UV_UNKNOWN_HANDLE :: UVHandleType
- pattern UV_ASYNC :: UVHandleType
- pattern UV_CHECK :: UVHandleType
- pattern UV_FS_EVENT :: UVHandleType
- pattern UV_FS_POLL :: UVHandleType
- pattern UV_HANDLE :: UVHandleType
- pattern UV_IDLE :: UVHandleType
- pattern UV_NAMED_PIPE :: UVHandleType
- pattern UV_POLL :: UVHandleType
- pattern UV_PREPARE :: UVHandleType
- pattern UV_PROCESS :: UVHandleType
- pattern UV_STREAM :: UVHandleType
- pattern UV_TCP :: UVHandleType
- pattern UV_TIMER :: UVHandleType
- pattern UV_TTY :: UVHandleType
- pattern UV_UDP :: UVHandleType
- pattern UV_SIGNAL :: UVHandleType
- pattern UV_FILE :: UVHandleType
- uv_guess_handle :: FD -> IO UVHandleType
- uv_fs_event_init :: Ptr UVLoop -> Ptr UVHandle -> IO CInt
- hs_uv_fs_event_start :: Ptr UVHandle -> BA# Word8 -> CUInt -> IO CInt
- uv_fs_event_stop :: Ptr UVHandle -> IO CInt
- hs_uv_fs_event_check_start :: Ptr UVHandle -> IO CInt
- pattern UV_RENAME :: Word8
- pattern UV_CHANGE :: Word8
- pattern UV_FS_EVENT_RECURSIVE :: CUInt
Documentation
uv_version :: IO CUInt Source #
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.
pattern SO_REUSEPORT_LOAD_BALANCE :: Int Source #
pattern INIT_LOOP_SIZE :: Int Source #
data UVLoopData Source #
peekUVEventQueue :: Ptr UVLoopData -> IO (Int, Ptr Int) Source #
clearUVEventCounter :: Ptr UVLoopData -> IO () Source #
pattern UV_RUN_DEFAULT :: UVRunMode Source #
pattern UV_RUN_ONCE :: UVRunMode Source #
pattern UV_RUN_NOWAIT :: UVRunMode Source #
peekUVLoopData :: Ptr UVLoop -> IO (Ptr UVLoopData) Source #
Peek loop data pointer from uv loop pointer.
hs_uv_wake_up_timer :: Ptr UVLoopData -> IO CInt Source #
hs_uv_wake_up_async :: Ptr UVLoopData -> IO CInt Source #
peekUVHandleData :: Ptr UVHandle -> IO UVSlotUnsafe Source #
hs_uv_write :: Ptr UVHandle -> Ptr Word8 -> Int -> IO UVSlotUnsafe Source #
hs_uv_shutdown :: Ptr UVHandle -> IO UVSlotUnsafe Source #
uv_tcp_bind :: Ptr UVHandle -> MBA# SocketAddr -> CUInt -> IO CInt Source #
hs_uv_tcp_connect :: Ptr UVHandle -> MBA# SocketAddr -> IO UVSlotUnsafe Source #
hs_uv_pipe_connect :: Ptr UVHandle -> BA# Word8 -> IO UVSlotUnsafe Source #
uv_udp_bind :: Ptr UVHandle -> MBA# SocketAddr -> UDPFlag -> IO CInt Source #
type Membership = CInt Source #
pattern LEAVE_GROUP :: Membership Source #
pattern JOIN_GROUP :: Membership Source #
pattern UDP_DEFAULT :: UDPFlag Source #
pattern UDP_IPV6ONLY :: UDPFlag Source #
pattern UDP_REUSEADDR :: UDPFlag Source #
pattern UV_UDP_PARTIAL :: Int32 Source #
uv_udp_connect :: Ptr UVHandle -> MBA# SocketAddr -> IO CInt Source #
uv_udp_disconnect :: Ptr UVHandle -> Ptr SocketAddr -> IO CInt Source #
Just pass null pointer as SocketAddr to disconnect
uv_udp_set_source_membership :: Ptr UVHandle -> BA# Word8 -> BA# Word8 -> BA# Word8 -> Membership -> IO CInt Source #
hs_uv_udp_send :: Ptr UVHandle -> MBA# SocketAddr -> Ptr Word8 -> Int -> IO UVSlotUnsafe Source #
hs_uv_udp_send_connected :: Ptr UVHandle -> Ptr Word8 -> Int -> IO UVSlotUnsafe 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 TTY_MODE_NORMAL :: TTYMode Source #
pattern TTY_MODE_RAW :: TTYMode Source #
pattern TTY_MODE_IO :: TTYMode Source #
pattern DEFAULT_FILE_MODE :: FileMode Source #
Default mode for file open, 0x666(readable and writable).
pattern DEFAULT_DIR_MODE :: FileMode Source #
Default mode for open, 0x755.
hs_uv_fs_open_threaded :: BA# Word8 -> FileFlag -> FileMode -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_close_threaded :: FD -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_write_threaded :: FD -> Ptr Word8 -> Int -> Int64 -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_unlink_threaded :: BA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_mkdir_threaded :: BA# Word8 -> FileMode -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_rmdir_threaded :: BA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_mkdtemp_threaded :: BA# Word8 -> Int -> MBA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_mkstemp_threaded :: BA# Word8 -> Int -> MBA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe Source #
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_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_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.
type UVDirEntType = CChar Source #
data DirEntType Source #
Instances
peekUVDirEnt :: Ptr DirEntType -> IO (CString, UVDirEntType) Source #
hs_uv_fs_scandir_cleanup :: Ptr (Ptr DirEntType) -> Int -> IO () Source #
hs_uv_fs_scandir :: BA# Word8 -> MBA# (Ptr DirEntType) -> IO Int Source #
hs_uv_fs_scandir_extra_cleanup :: Ptr (Ptr (Ptr DirEntType)) -> Int -> IO () Source #
hs_uv_fs_scandir_threaded :: BA# Word8 -> Ptr (Ptr (Ptr DirEntType)) -> Ptr UVLoop -> IO UVSlotUnsafe Source #
data UVTimeSpec Source #
UVTimeSpec | |
|
Instances
FStat | |
|
Instances
uvStatSize :: Int Source #
hs_uv_fs_fstat_threaded :: FD -> Ptr FStat -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_fsync_threaded :: FD -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_fdatasync_threaded :: FD -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_ftruncate_threaded :: FD -> Int64 -> Ptr UVLoop -> IO UVSlotUnsafe Source #
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 COPYFILE_DEFAULT :: CopyFileFlag Source #
pattern COPYFILE_EXCL :: CopyFileFlag Source #
pattern COPYFILE_FICLONE :: CopyFileFlag Source #
pattern COPYFILE_FICLONE_FORCE :: CopyFileFlag Source #
hs_uv_fs_copyfile :: BA# Word8 -> BA# Word8 -> CopyFileFlag -> IO Int Source #
hs_uv_fs_copyfile_threaded :: BA# Word8 -> BA# Word8 -> CopyFileFlag -> Ptr UVLoop -> IO UVSlotUnsafe Source #
type AccessMode = CInt Source #
pattern F_OK :: AccessMode Source #
pattern R_OK :: AccessMode Source #
pattern W_OK :: AccessMode Source #
pattern X_OK :: AccessMode Source #
data AccessResult Source #
Instances
hs_uv_fs_access :: BA# Word8 -> AccessMode -> IO Int Source #
hs_uv_fs_access_threaded :: BA# Word8 -> AccessMode -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_chmod_threaded :: BA# Word8 -> FileMode -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_fchmod_threaded :: FD -> FileMode -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_futime_threaded :: FD -> Double -> Double -> Ptr UVLoop -> IO UVSlotUnsafe Source #
type SymlinkFlag = CInt Source #
On Windows the flags parameter can be specified to control how the symlink will be created:
SYMLINK_DIR
: indicates that path points to a directory.SYMLINK_JUNCTION
: request that the symlink is created using junction points.
pattern SYMLINK_DEFAULT :: SymlinkFlag Source #
pattern SYMLINK_DIR :: SymlinkFlag Source #
pattern SYMLINK_JUNCTION :: SymlinkFlag Source #
hs_uv_fs_symlink :: BA# Word8 -> BA# Word8 -> SymlinkFlag -> IO Int Source #
hs_uv_fs_symlink_threaded :: BA# Word8 -> BA# Word8 -> SymlinkFlag -> Ptr UVLoop -> IO UVSlotUnsafe Source #
hs_uv_fs_readlink_cleanup :: CString -> IO () Source #
hs_uv_fs_fchown_threaded :: FD -> UID -> GID -> Ptr UVLoop -> IO UVSlotUnsafe Source #
Instances
Instances
type ProcessFlag = CUInt Source #
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 #
ProcessOptions | |
|
Instances
data ProcessStdStream Source #
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
hs_uv_spawn :: Ptr UVLoop -> MBA# ProcessOptions -> BA# Word8 -> BAArray# Word8 -> Int -> BAArray# Word8 -> Int -> BA# Word8 -> MBA# ProcessStdStream -> IO Int Source #
type UVHandleType = CInt Source #
pattern UV_UNKNOWN_HANDLE :: UVHandleType Source #
pattern UV_ASYNC :: UVHandleType Source #
pattern UV_CHECK :: UVHandleType Source #
pattern UV_FS_EVENT :: UVHandleType Source #
pattern UV_FS_POLL :: UVHandleType Source #
pattern UV_HANDLE :: UVHandleType Source #
pattern UV_IDLE :: UVHandleType Source #
pattern UV_NAMED_PIPE :: UVHandleType Source #
pattern UV_POLL :: UVHandleType Source #
pattern UV_PREPARE :: UVHandleType Source #
pattern UV_PROCESS :: UVHandleType Source #
pattern UV_STREAM :: UVHandleType Source #
pattern UV_TCP :: UVHandleType Source #
pattern UV_TIMER :: UVHandleType Source #
pattern UV_TTY :: UVHandleType Source #
pattern UV_UDP :: UVHandleType Source #
pattern UV_SIGNAL :: UVHandleType Source #
pattern UV_FILE :: UVHandleType Source #
uv_guess_handle :: FD -> IO UVHandleType Source #
pattern UV_FS_EVENT_RECURSIVE :: CUInt Source #