Z-IO-0.1.4.0: Simple and high performance IO toolkit for Haskell

Copyright(c) Dong Han 2017~2019
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.IO.FileSystem

Contents

Description

This module provide IO operations related to filesystem, operations are implemented using unsafe FFIs, which should be prefered when the operations' estimated time is short(<1ms), which is much common on modern SSDs.

Synopsis

regular file devices

data File Source #

File and its operations are NOT thread safe, use MVar File in multiple threads

libuv implements read and write method with both implict and explict offset capable. Implict offset interface is provided by Input / Output instances. Explict offset interface is provided by readFile / writeFile.

Instances
Output File Source # 
Instance details

Defined in Z.IO.FileSystem

Methods

writeOutput :: File -> Ptr Word8 -> Int -> IO () Source #

Input File Source # 
Instance details

Defined in Z.IO.FileSystem

Methods

readInput :: File -> Ptr Word8 -> Int -> IO Int Source #

initFile Source #

Arguments

:: HasCallStack 
=> CBytes 
-> FileFlag

Opening flags, e.g. O_CREAT .|. O_RDWR

-> FileMode

Sets the file mode (permission and sticky bits), but only if the file was created, see DEFAULT_MODE.

-> Resource File 

init a file Resource, which open a file when used.

Resource closing is thread safe, on some versions of OSX, repeatly open and close same file Resource may result in shared memory object error, use O_CREAT to avoid that.

readFile Source #

Arguments

:: HasCallStack 
=> File 
-> Ptr Word8

buffer

-> Int

buffer size

-> Int64

file offset, pass -1 to use default(system) offset

-> IO Int

read length

Read file with given offset

Read length may be smaller than buffer size.

writeFile Source #

Arguments

:: HasCallStack 
=> File 
-> Ptr Word8

buffer

-> Int

buffer size

-> Int64

file offset, pass -1 to use default(system) offset

-> IO () 

Write buffer to file

This function will loop until all bytes are written.

file offset bundle

data FilePtr Source #

File bundled with offset.

Reading or writing using Input / Output instance will automatically increase offset. FilePtr and its operations are NOT thread safe, use MVar FilePtr in multiple threads.

Instances
Output FilePtr Source # 
Instance details

Defined in Z.IO.FileSystem

Methods

writeOutput :: FilePtr -> Ptr Word8 -> Int -> IO () Source #

Input FilePtr Source # 
Instance details

Defined in Z.IO.FileSystem

Methods

readInput :: FilePtr -> Ptr Word8 -> Int -> IO Int Source #

newFilePtr Source #

Arguments

:: File

the file we're reading

-> Int64

initial offset

-> IO FilePtr 

Create a file offset bundle from an File.

getFileOffset :: FilePtr -> IO Int64 Source #

Get current offset.

setFileOffset :: FilePtr -> Int64 -> IO () Source #

Change current offset.

opening constant

data FileMode where Source #

Bundled Patterns

pattern DEFAULT_MODE :: FileMode

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

pattern S_IRWXU :: FileMode

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

pattern S_IRUSR :: FileMode

00400 user has read permission

pattern S_IWUSR :: FileMode

00200 user has write permission

pattern S_IXUSR :: FileMode

00100 user has execute permission

pattern S_IRWXG :: FileMode

00070 group has read, write and execute permission

pattern S_IRGRP :: FileMode

00040 group has read permission

pattern S_IWGRP :: FileMode

00020 group has write permission

pattern S_IXGRP :: FileMode

00010 group has execute permission

pattern S_IRWXO :: FileMode

00007 others have read, write and execute permission

pattern S_IROTH :: FileMode

00004 others have read permission

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

data FileFlag where Source #

Bundled Patterns

pattern O_APPEND :: FileFlag

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

The file is created if it does not already exist.

pattern O_DIRECT :: FileFlag

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_DSYNC :: FileFlag

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

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

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

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

Note o_NOATIME is not supported on Windows.

pattern O_NOFOLLOW :: FileFlag

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

Note o_NOFOLLOW is not supported on Windows.

pattern O_RDONLY :: FileFlag

Open the file for read-only access.

pattern O_RDWR :: FileFlag

Open the file for read-write access.

pattern O_SYMLINK :: FileFlag

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

pattern O_SYNC :: FileFlag

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_TRUNC :: FileFlag

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

Open the file for write-only access.

pattern O_RANDOM :: FileFlag

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_SHORT_LIVED :: FileFlag

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_SEQUENTIAL :: FileFlag

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_TEMPORARY :: FileFlag

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.

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

filesystem operations

mkdir :: HasCallStack => CBytes -> FileMode -> IO () Source #

Equivalent to mkdir(2).

Note mode is currently not implemented on Windows.

unlink :: HasCallStack => CBytes -> IO () Source #

Equivalent to unlink(2).

mkdtemp :: HasCallStack => CBytes -> IO CBytes Source #

Equivalent to http://linux.die.net/man/3/mkdtemp

Creates a temporary directory in the most secure manner possible. There are no race conditions in the directory’s creation. The directory is readable, writable, and searchable only by the creating user ID. The user of mkdtemp() is responsible for deleting the temporary directory and its contents when done with it.

Note: the argument is the prefix of the temporary directory, so no need to add XXXXXX ending.

rmdir :: HasCallStack => CBytes -> IO () Source #

Equivalent to rmdir(2).

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

scandir :: HasCallStack => CBytes -> IO [(CBytes, DirEntType)] Source #

Equivalent to scandir(3).

Note Unlike scandir(3), this function does not return the “.” and “..” entries.

Note On Linux, getting the type of an entry is only supported by some file systems (btrfs, ext2, ext3 and ext4 at the time of this writing), check the getdents(2) man page.

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

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

stat :: HasCallStack => CBytes -> IO FStat Source #

Equivalent to stat(2)

fstat :: HasCallStack => File -> IO FStat Source #

Equivalent to fstat(2)

rename :: HasCallStack => CBytes -> CBytes -> IO () Source #

Equivalent to rename(2).

Note On Windows if this function fails with UV_EBUSY, UV_EPERM or UV_EACCES, it will retry to rename the file up to four times with 250ms wait between attempts before giving up. If both path and new_path are existing directories this function will work only if target directory is empty.

fsync :: HasCallStack => File -> IO () Source #

Equivalent to fsync(2).

fdatasync :: HasCallStack => File -> IO () Source #

Equivalent to fdatasync(2).

ftruncate :: HasCallStack => File -> Int64 -> IO () Source #

Equivalent to ftruncate(2).

data CopyFileFlag where 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.

Bundled Patterns

pattern COPYFILE_DEFAULT :: CopyFileFlag 
pattern COPYFILE_EXCL :: CopyFileFlag 
pattern COPYFILE_FICLONE :: CopyFileFlag 
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)))

copyfile :: HasCallStack => CBytes -> CBytes -> CopyFileFlag -> IO () Source #

Copies a file from path to new_path.

Warning: If the destination path is created, but an error occurs while copying the data, then the destination path is removed. There is a brief window of time between closing and removing the file where another process could access the file.

data AccessMode where Source #

Bundled Patterns

pattern F_OK :: AccessMode 
pattern R_OK :: AccessMode 
pattern W_OK :: AccessMode 
pattern X_OK :: AccessMode 
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)))

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

access :: HasCallStack => CBytes -> AccessMode -> IO AccessResult Source #

Equivalent to access(2) on Unix. Windows uses GetFileAttributesW().

chmod :: HasCallStack => CBytes -> FileMode -> IO () Source #

Equivalent to chmod(2).

fchmod :: HasCallStack => File -> FileMode -> IO () Source #

Equivalent to fchmod(2).

utime Source #

Arguments

:: HasCallStack 
=> CBytes 
-> Double

atime, i.e. access time

-> Double

mtime, i.e. modify time

-> IO () 

Equivalent to utime(2).

libuv choose Double type due to cross platform concerns, we only provide micro-second precision.

futime :: HasCallStack => File -> Double -> Double -> IO () Source #

Equivalent to futime(3).

Same precision notes with utime.

lutime Source #

Arguments

:: HasCallStack 
=> CBytes 
-> Double

atime, i.e. access time

-> Double

mtime, i.e. modify time

-> IO () 

Equivalent to lutime(3).

Same precision notes with utime.

data SymlinkFlag where Source #

Bundled Patterns

pattern SYMLINK_DEFAULT :: SymlinkFlag 
pattern SYMLINK_DIR :: SymlinkFlag 
pattern SYMLINK_JUNCTION :: SymlinkFlag 
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)))

link :: HasCallStack => CBytes -> CBytes -> IO () Source #

Equivalent to link(2).

symlink :: HasCallStack => CBytes -> CBytes -> SymlinkFlag -> IO () Source #

Equivalent to symlink(2).

| Note On Windows the flags parameter can be specified to control how the symlink will be created.

On other platforms these flags are ignored.

realpath :: HasCallStack => CBytes -> IO CBytes Source #

Equivalent to realpath(3) on Unix. Windows uses GetFinalPathNameByHandle.

Warning This function has certain platform-specific caveats that were discovered when used in Node.

  • macOS and other BSDs: this function will fail with UV_ELOOP if more than 32 symlinks are found while resolving the given path. This limit is hardcoded and cannot be sidestepped.
  • Windows: while this function works in the common case, there are a number of corner cases where it doesn’t:

    • Paths in ramdisk volumes created by tools which sidestep the Volume Manager (such as ImDisk) cannot be resolved.
    • Inconsistent casing when using drive letters.
    • Resolved path bypasses subst’d drives.

While this function can still be used, it’s not recommended if scenarios such as the above need to be supported. The background story and some more details on these issues can be checked here.

Note This function is not implemented on Windows XP and Windows Server 2003. On these systems, UV_ENOSYS is returned.