Stability | provisional |
---|---|
Portability | non-portable (requires Linux) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Deprecated: This module is deprecated and will be removed in a future version of this library. Please leave a comment on https://github.com/redneb/hs-btrfs/issues/5 if you think that is should not be removed.
Most functions in this module come in two flavors: one that operates on
file descriptors and another one that operates on file paths. The former
can be distinguished by the Fd
suffix in their names.
Synopsis
- type FileSize = Word64
- type ObjectType = Word8
- type ObjectId = Word64
- type InodeNum = ObjectId
- type SubvolId = ObjectId
- data CompressionType
- compressNone :: CompressionType
- compressZlib :: CompressionType
- compressLZO :: CompressionType
- compressZstd :: CompressionType
- cloneFd :: Fd -> Fd -> IO ()
- clone :: RawFilePath -> RawFilePath -> IO ()
- cloneNew :: RawFilePath -> RawFilePath -> IO ()
- cloneRangeFd :: Fd -> FileSize -> FileSize -> Fd -> FileSize -> IO ()
- cloneRange :: RawFilePath -> FileSize -> FileSize -> RawFilePath -> FileSize -> IO ()
- data CloneResult
- cloneRangeIfSameFd :: Fd -> FileSize -> FileSize -> [(Fd, FileSize)] -> IO [CloneResult]
- cloneRangeIfSame :: RawFilePath -> FileSize -> FileSize -> [(RawFilePath, FileSize)] -> IO [CloneResult]
- createSubvol :: RawFilePath -> IO ()
- destroySubvol :: RawFilePath -> IO ()
- snapshotFd :: Fd -> RawFilePath -> Bool -> IO ()
- snapshot :: RawFilePath -> RawFilePath -> Bool -> IO ()
- getSubvolReadOnlyFd :: Fd -> IO Bool
- getSubvolReadOnly :: RawFilePath -> IO Bool
- setSubvolReadOnlyFd :: Fd -> Bool -> IO ()
- setSubvolReadOnly :: RawFilePath -> Bool -> IO ()
- getSubvolFd :: Fd -> IO SubvolId
- getSubvol :: RawFilePath -> IO SubvolId
- lookupSubvolFd :: Fd -> SubvolId -> IO (SubvolId, InodeNum, RawFilePath)
- lookupSubvol :: RawFilePath -> SubvolId -> IO (SubvolId, InodeNum, RawFilePath)
- resolveSubvolFd :: Fd -> SubvolId -> IO RawFilePath
- resolveSubvol :: RawFilePath -> SubvolId -> IO RawFilePath
- rootSubvol :: SubvolId
- listSubvolsFd :: Fd -> IO [(SubvolId, SubvolId, InodeNum, RawFilePath)]
- listSubvols :: RawFilePath -> IO [(SubvolId, SubvolId, InodeNum, RawFilePath)]
- listSubvolPathsFd :: Fd -> IO [(SubvolId, SubvolId, RawFilePath)]
- listSubvolPaths :: RawFilePath -> IO [(SubvolId, SubvolId, RawFilePath)]
- childSubvolsFd :: Fd -> SubvolId -> IO [(SubvolId, InodeNum, RawFilePath)]
- childSubvols :: RawFilePath -> SubvolId -> IO [(SubvolId, InodeNum, RawFilePath)]
- childSubvolPathsFd :: Fd -> SubvolId -> IO [(SubvolId, RawFilePath)]
- childSubvolPaths :: RawFilePath -> SubvolId -> IO [(SubvolId, RawFilePath)]
- data SubvolInfo = SubvolInfo {
- siGeneration :: Word64
- siLastSnapshot :: Maybe Word64
- siParSnapGen :: Maybe Word64
- siReadOnly :: Bool
- siUuid :: Maybe UUID
- siPUuid :: Maybe UUID
- siReceivedUuid :: Maybe UUID
- siCTransId :: Maybe Word64
- siOTransId :: Maybe Word64
- siSTransId :: Maybe Word64
- siRTransId :: Maybe Word64
- siCTime :: Maybe UTCTime
- siOTime :: Maybe UTCTime
- siSTime :: Maybe UTCTime
- siRTime :: Maybe UTCTime
- getSubvolInfoFd :: Fd -> SubvolId -> IO SubvolInfo
- getSubvolInfo :: RawFilePath -> SubvolId -> IO SubvolInfo
- getSubvolByUuidFd :: Fd -> UUID -> IO SubvolId
- getSubvolByUuid :: RawFilePath -> UUID -> IO SubvolId
- getSubvolByReceivedUuidFd :: Fd -> UUID -> IO SubvolId
- getSubvolByReceivedUuid :: RawFilePath -> UUID -> IO SubvolId
- getDefaultSubvolFd :: Fd -> IO SubvolId
- getDefaultSubvol :: RawFilePath -> IO SubvolId
- setDefaultSubvolFd :: Fd -> ObjectId -> IO ()
- setDefaultSubvol :: RawFilePath -> SubvolId -> IO ()
- defragFd :: Fd -> IO ()
- defrag :: RawFilePath -> IO ()
- data DefragRangeArgs = DefragRangeArgs {}
- defaultDefragRangeArgs :: DefragRangeArgs
- defragRangeFd :: Fd -> DefragRangeArgs -> IO ()
- defragRange :: RawFilePath -> DefragRangeArgs -> IO ()
- data FSInfo
- fsiDeviceCount :: FSInfo -> Word64
- fsiUuid :: FSInfo -> UUID
- fsiNodeSize :: FSInfo -> FileSize
- fsiSectorSize :: FSInfo -> FileSize
- fsiCloneAlignment :: FSInfo -> FileSize
- getFSInfoFd :: Fd -> IO FSInfo
- getFSInfo :: RawFilePath -> IO FSInfo
- getFSLabelFd :: Fd -> IO RawFilePath
- getFSLabel :: RawFilePath -> IO RawFilePath
- setFSLabelFd :: Fd -> RawFilePath -> IO ()
- setFSLabel :: RawFilePath -> RawFilePath -> IO ()
- syncFd :: Fd -> IO ()
- sync :: RawFilePath -> IO ()
- startSyncFd :: Fd -> IO ()
- startSync :: RawFilePath -> IO ()
- waitSyncFd :: Fd -> IO ()
- waitSync :: RawFilePath -> IO ()
- resolveLogicalFd :: Fd -> FileSize -> IO ([(InodeNum, FileSize, SubvolId)], Int)
- resolveLogical :: RawFilePath -> FileSize -> IO ([(InodeNum, FileSize, SubvolId)], Int)
- resolveInodeFd :: Fd -> InodeNum -> IO ([RawFilePath], Int)
- resolveInode :: RawFilePath -> InodeNum -> IO ([RawFilePath], Int)
- lookupInodeFd :: Fd -> SubvolId -> InodeNum -> IO (SubvolId, RawFilePath)
- lookupInode :: RawFilePath -> SubvolId -> InodeNum -> IO (SubvolId, RawFilePath)
- getFileNoCOWFd :: Fd -> IO Bool
- getFileNoCOW :: RawFilePath -> IO Bool
- setFileNoCOWFd :: Fd -> Bool -> IO ()
- setFileNoCOW :: RawFilePath -> Bool -> IO ()
- data SearchKey = SearchKey {}
- defaultSearchKey :: SearchKey
- data SearchHeader = SearchHeader {
- shTransId :: Word64
- shObjectId :: ObjectId
- shOffset :: Word64
- shType :: ObjectType
- shLen :: Word32
- treeSearchFd :: Fd -> SearchKey -> Int -> (SearchHeader -> Ptr i -> IO ()) -> IO ()
- treeSearch :: RawFilePath -> SearchKey -> Int -> (SearchHeader -> Ptr i -> IO ()) -> IO ()
- treeSearchListFd :: Fd -> SearchKey -> (SearchHeader -> Ptr i -> IO (Maybe a)) -> IO [a]
- treeSearchList :: RawFilePath -> SearchKey -> (SearchHeader -> Ptr i -> IO (Maybe a)) -> IO [a]
- findFirstItemFd :: Fd -> SearchKey -> (SearchHeader -> Ptr i -> IO a) -> IO a
- findFirstItem :: RawFilePath -> SearchKey -> (SearchHeader -> Ptr i -> IO a) -> IO a
Basic types
type ObjectType = Word8 Source #
data CompressionType Source #
Instances
Show CompressionType Source # | |
Defined in System.Linux.Btrfs.ByteString showsPrec :: Int -> CompressionType -> ShowS # show :: CompressionType -> String # showList :: [CompressionType] -> ShowS # | |
Eq CompressionType Source # | |
Defined in System.Linux.Btrfs.ByteString (==) :: CompressionType -> CompressionType -> Bool # (/=) :: CompressionType -> CompressionType -> Bool # |
File cloning/deduplication
:: RawFilePath | The source file. |
-> RawFilePath | The destination file. |
-> IO () |
Clone an entire file to an existing file.
Note: calls the BTRFS_IOC_CLONE
/FICLONE
ioctl
.
cloneNew :: RawFilePath -> RawFilePath -> IO () Source #
Like clone
except that it will create or truncate the destination
file if necessary. This is similar to cp --reflink=always
.
Note: calls the BTRFS_IOC_CLONE
/FICLONE
ioctl
.
:: RawFilePath | The source file. |
-> FileSize | The offset within the source file. |
-> FileSize | The length of the range. A length of 0 selects the range from the source offset to the end. |
-> RawFilePath | The destination file. |
-> FileSize | The offset within the destination file. |
-> IO () |
Clones a range of bytes from a file to another file. All ranges must
be block-aligned (the block size can be obtained using getFSInfo
and
fsiCloneAlignment
).
Note: calls the BTRFS_IOC_CLONE_RANGE
/FICLONERANGE
ioctl
.
data CloneResult Source #
The result of a cloneRangeIfSame
operation.
CRError IOError | Cloning failed because of an error. |
CRDataDiffers | No cloning was performed because the contents of the source and the destination file differ. |
CRSuccess FileSize | Cloning succeeded, the returned integer indicates the number of bytes that were deduped. |
Instances
Show CloneResult Source # | |
Defined in System.Linux.Btrfs.ByteString showsPrec :: Int -> CloneResult -> ShowS # show :: CloneResult -> String # showList :: [CloneResult] -> ShowS # | |
Eq CloneResult Source # | |
Defined in System.Linux.Btrfs.ByteString (==) :: CloneResult -> CloneResult -> Bool # (/=) :: CloneResult -> CloneResult -> Bool # |
cloneRangeIfSameFd :: Fd -> FileSize -> FileSize -> [(Fd, FileSize)] -> IO [CloneResult] Source #
:: RawFilePath | The source file. |
-> FileSize | The offset within the source file. |
-> FileSize | The length of the range. |
-> [(RawFilePath, FileSize)] | The destination files and corresponding offsets. |
-> IO [CloneResult] |
Similar to cloneRange
except that it performs the cloning only if
the data ranges contain identical data.
Additionally, it accepts multiple destination files. The same thing can
be accomplished with cloneRange
in conjunction with file locking but
this function uses in-kernel locking to guarantee that the deduplicated
data is identical at the time of the operation. On the other hand, this
function will not clone arbitrarily large ranges; the kernel has an upper
limit for the length and if cloning bigger ranges is desired then it
has to be called multiple times. Note that cloning may succeed for some
of the destination files and fail for others. Because of that, this
function returns a list of outcomes, one for each destination file, and
no exceptions will be raised for the failed files.
Note: calls the BTRFS_IOC_FILE_EXTENT_SAME
/FIDEDUPERANGE
ioctl
.
Requires Linux 3.12 or later.
Subvolumes and snapshots
createSubvol :: RawFilePath -> IO () Source #
Create an (initially) empty new subvolume.
Note: calls the BTRFS_IOC_SUBVOL_CREATE
ioctl
.
destroySubvol :: RawFilePath -> IO () Source #
Destroy (delete) a subvolume. The directory that corresponds to the
subvolume is removed asynchronously. As a result, the subvolume may
appear again after a crash. If this is not acceptable, call startSync
followed by a waitSync
, after the destroySubvol
call.
Note: calls the BTRFS_IOC_SNAP_DESTROY
ioctl
.
snapshotFd :: Fd -> RawFilePath -> Bool -> IO () Source #
:: RawFilePath | The source subvolume. |
-> RawFilePath | The destination subvolume (must not exist). |
-> Bool | Create a read-only snapshot? |
-> IO () |
Create a snapshot of an existing subvolume.
Note: calls the BTRFS_IOC_SNAP_CREATE_V2
ioctl
.
getSubvolReadOnly :: RawFilePath -> IO Bool Source #
Is the subvolume read-only?
Note: calls the BTRFS_IOC_SUBVOL_GETFLAGS
ioctl
.
setSubvolReadOnly :: RawFilePath -> Bool -> IO () Source #
Make a subvolume read-only (or read-write).
Note: calls the BTRFS_IOC_SUBVOL_GETFLAGS
and
BTRFS_IOC_SUBVOL_SETFLAGS
ioctl
s.
getSubvol :: RawFilePath -> IO SubvolId Source #
Find the id of the subvolume where the given file resides. This is
merely a wrapper around lookupInode
provided for convenience.
lookupSubvolFd :: Fd -> SubvolId -> IO (SubvolId, InodeNum, RawFilePath) Source #
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> SubvolId | The id of the subvolume. |
-> IO (SubvolId, InodeNum, RawFilePath) |
Given the id of a subvolume, find the id of the parent subvolume, the
inode number of the directory containing it, and its name. This is
a wrapper around treeSearch
.
resolveSubvolFd :: Fd -> SubvolId -> IO RawFilePath Source #
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> SubvolId | The id of the subvolume. |
-> IO RawFilePath |
Given the id of a subvolume, find its path relative to the root of the
volume. This function calls lookupSubvol
recursively.
rootSubvol :: SubvolId Source #
The id the root subvolume.
listSubvolsFd :: Fd -> IO [(SubvolId, SubvolId, InodeNum, RawFilePath)] Source #
listSubvols :: RawFilePath -> IO [(SubvolId, SubvolId, InodeNum, RawFilePath)] Source #
Find all subvolumes of the given volume. For each subvolume found, it
returns: its id, the id of its parent subvolume, the inode number of the
directory containing it, and its name. This is a wrapper around
treeSearch
.
listSubvolPathsFd :: Fd -> IO [(SubvolId, SubvolId, RawFilePath)] Source #
listSubvolPaths :: RawFilePath -> IO [(SubvolId, SubvolId, RawFilePath)] Source #
Find all subvolumes of the given volume. For each subvolume found, it
returns: its id, the id of its parent subvolume, and its path relative
to the root of the volume. This is a wrapper around treeSearch
and
resolveSubvol
.
childSubvolsFd :: Fd -> SubvolId -> IO [(SubvolId, InodeNum, RawFilePath)] Source #
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> SubvolId | The id of the subvolume. |
-> IO [(SubvolId, InodeNum, RawFilePath)] |
Find all child subvolumes of the given subvolume. For each child,
returns its id, the inode number of the directory containing it, and its
name. This is a wrapper around treeSearch
.
childSubvolPathsFd :: Fd -> SubvolId -> IO [(SubvolId, RawFilePath)] Source #
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> SubvolId | The id of the subvolume. |
-> IO [(SubvolId, RawFilePath)] |
Find all child subvolumes of the given subvolume. For each child,
returns its id and its path relative to the root of the parent.
This is a wrapper around treeSearch
and lookupInode
.
data SubvolInfo Source #
Information about a subvolume.
SubvolInfo | |
|
Instances
Show SubvolInfo Source # | |
Defined in System.Linux.Btrfs.ByteString showsPrec :: Int -> SubvolInfo -> ShowS # show :: SubvolInfo -> String # showList :: [SubvolInfo] -> ShowS # | |
Eq SubvolInfo Source # | |
Defined in System.Linux.Btrfs.ByteString (==) :: SubvolInfo -> SubvolInfo -> Bool # (/=) :: SubvolInfo -> SubvolInfo -> Bool # |
getSubvolInfoFd :: Fd -> SubvolId -> IO SubvolInfo Source #
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> SubvolId | The id of the subvolume. |
-> IO SubvolInfo |
Retrieve information about a subvolume. This is a wrapper around treeSearch
.
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> UUID | The UUID of the subvolume. |
-> IO SubvolId |
Find the id of a subvolume, given its UUID. This is a wrapper around
treeSearch
.
Requires Linux 3.12 or later.
getSubvolByReceivedUuid Source #
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> UUID | The |
-> IO SubvolId |
Find the id of a subvolume, given its siReceivedUuid
. This is a
wrapper around treeSearch
.
Requires Linux 3.12 or later.
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> IO SubvolId |
Find the id of the default subvolume. This is a wrapper around
treeSearch
.
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> SubvolId | The id of the new default subvolume. |
-> IO () |
Set the default subvolume.
Note: calls the BTRFS_IOC_DEFAULT_SUBVOL
ioctl
.
Defrag
There is a limitation in the kernel whereby a defrag operation
will be silently aborted when the calling process receives any
signal. This does not play well with GHC's rts which in some
cases uses signals as a way to preempt haskell threads. So in order
to use defrag
or defragRange
, you must compile your program with
GHC >=8.2 and the use the threaded runtime which does not use
signals anymore. Alternatively, for older versions of GHC, you can
use something like the withRTSSignalsBlocked
function from
here.
defrag :: RawFilePath -> IO () Source #
Defrag a single file.
Note: calls the BTRFS_IOC_DEFRAG
ioctl
.
data DefragRangeArgs Source #
Argument to the defragRange
operation.
DefragRangeArgs | |
|
Instances
Show DefragRangeArgs Source # | |
Defined in System.Linux.Btrfs.ByteString showsPrec :: Int -> DefragRangeArgs -> ShowS # show :: DefragRangeArgs -> String # showList :: [DefragRangeArgs] -> ShowS # | |
Eq DefragRangeArgs Source # | |
Defined in System.Linux.Btrfs.ByteString (==) :: DefragRangeArgs -> DefragRangeArgs -> Bool # (/=) :: DefragRangeArgs -> DefragRangeArgs -> Bool # |
defaultDefragRangeArgs :: DefragRangeArgs Source #
Defaults for defragRange
. Selects the entire file, no compression,
and no flushing.
defragRangeFd :: Fd -> DefragRangeArgs -> IO () Source #
defragRange :: RawFilePath -> DefragRangeArgs -> IO () Source #
Defrag a range within a single file.
Note: calls the BTRFS_IOC_DEFRAG_RANGE
ioctl
.
File system info
Information about a btrfs file system.
fsiDeviceCount :: FSInfo -> Word64 Source #
The number of devices in the file system.
fsiNodeSize :: FSInfo -> FileSize Source #
The tree block size in which metadata is stored.
fsiSectorSize :: FSInfo -> FileSize Source #
The minimum data block allocation unit.
fsiCloneAlignment :: FSInfo -> FileSize Source #
The size that is used for the alignment constraints of clone range operations.
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> IO FSInfo |
Retrieve information about a btrfs file system.
Note: calls the BTRFS_IOC_FS_INFO
ioctl
.
File system label
getFSLabelFd :: Fd -> IO RawFilePath Source #
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> IO RawFilePath |
Retrieve the label of a btrfs file system.
Note: calls the BTRFS_IOC_GET_FSLABEL
ioctl
.
setFSLabelFd :: Fd -> RawFilePath -> IO () Source #
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> RawFilePath | The new label. |
-> IO () |
Set the label of a btrfs file system. Note that a label can be up to 255 bytes long. If the provided label is longer, it will be silently truncated.
Note: calls the BTRFS_IOC_SET_FSLABEL
ioctl
.
Sync
sync :: RawFilePath -> IO () Source #
Sync the file system identified by the supplied path.
The FilePath
can refer to any file in the file system.
Note: calls the BTRFS_IOC_SYNC
ioctl
.
startSyncFd :: Fd -> IO () Source #
startSync :: RawFilePath -> IO () Source #
Initiate a sync for the file system identified by the supplied path.
Note: calls the BTRFS_IOC_START_SYNC
ioctl
.
waitSyncFd :: Fd -> IO () Source #
waitSync :: RawFilePath -> IO () Source #
Wait until the sync operation completes.
Note: calls the BTRFS_IOC_WAIT_SYNC
ioctl
.
Inspect internal
:: RawFilePath | The mount point of the volume (or any file in that volume). |
-> FileSize | The physical byte offset in the underlying block device. |
-> IO ([(InodeNum, FileSize, SubvolId)], Int) |
Given a physical offset, look for any inodes that this byte belongs to. For each inode, it returns the inode number, the logical offset (i.e. the offset within the inode), and the subvolume id. If a large number of inodes is found, then not all of them will be returned by this function. This is due to a current limitation in the kernel. The integer returned along with list of inodes indicates the number of inodes found but not included in the list.
Note: calls the BTRFS_IOC_LOGICAL_INO
ioctl
.
resolveInodeFd :: Fd -> InodeNum -> IO ([RawFilePath], Int) Source #
:: RawFilePath | The path to the subvolume (or any file in that subvolume). |
-> InodeNum | The inode number. |
-> IO ([RawFilePath], Int) |
Find the file path(s) given an inode number. Returns a list of file paths and an integer indicating the number of paths found but not included in the resulting list. This is because of a limitation in the kernel (it will not return an arbitrarily large list). The paths returned are relative to the root of the subvolume.
Note: calls the BTRFS_IOC_INO_PATHS
ioctl
.
lookupInodeFd :: Fd -> SubvolId -> InodeNum -> IO (SubvolId, RawFilePath) Source #
:: RawFilePath | The path to any file in the volume. The subvolume where
this file resides is ignored unless no |
-> SubvolId | The id of the subvolume. Can be 0. In that case, the
subvolume of the |
-> InodeNum | The inode number. |
-> IO (SubvolId, RawFilePath) |
Find the path of a file given its inode number and the id of the
subvolume. If multiple files share the same inode number, only one of
them is returned. The id of the subvolume is also returned. This is
useful when 0 is given for the SubvolId
argument (also see
getSubvol
for this case).
Note: calls the BTRFS_IOC_INO_LOOKUP
ioctl
.
Miscellaneous
getFileNoCOW :: RawFilePath -> IO Bool Source #
Determine whether the NOCOW flag is enabled for the specified file.
Note: calls the FS_IOC_GETFLAGS
ioctl
.
setFileNoCOW :: RawFilePath -> Bool -> IO () Source #
Set or clear the NOCOW flag for the specified file. If the file is not empty, this has no effect and no error will be reported.
Note: calls the FS_IOC_GETFLAGS
and FS_IOC_GETFLAGS
ioctl
s.
Tree search
Low-level API for tree search using the BTRFS_IOC_TREE_SEARCH
ioctl
.
SearchKey | |
|
data SearchHeader Source #
SearchHeader | |
|
Instances
Show SearchHeader Source # | |
Defined in System.Linux.Btrfs.ByteString showsPrec :: Int -> SearchHeader -> ShowS # show :: SearchHeader -> String # showList :: [SearchHeader] -> ShowS # | |
Eq SearchHeader Source # | |
Defined in System.Linux.Btrfs.ByteString (==) :: SearchHeader -> SearchHeader -> Bool # (/=) :: SearchHeader -> SearchHeader -> Bool # |
treeSearchFd :: Fd -> SearchKey -> Int -> (SearchHeader -> Ptr i -> IO ()) -> IO () Source #
treeSearch :: RawFilePath -> SearchKey -> Int -> (SearchHeader -> Ptr i -> IO ()) -> IO () Source #
treeSearchListFd :: Fd -> SearchKey -> (SearchHeader -> Ptr i -> IO (Maybe a)) -> IO [a] Source #
treeSearchList :: RawFilePath -> SearchKey -> (SearchHeader -> Ptr i -> IO (Maybe a)) -> IO [a] Source #
findFirstItemFd :: Fd -> SearchKey -> (SearchHeader -> Ptr i -> IO a) -> IO a Source #
findFirstItem :: RawFilePath -> SearchKey -> (SearchHeader -> Ptr i -> IO a) -> IO a Source #