Portability | portable |
---|---|
Stability | experimental |
Maintainer | Nicola Squartini <[email protected]> |
Safe Haskell | Safe |
System.Linux.Mount
Contents
Description
linux-mount
provides bindings to the Linux
mount()
and
umount()
syscalls. All
functions below may fail with
if the
user does not have the required privileges.
isPermissionError
- mount :: String -> FilePath -> String -> [MountFlag] -> DriverData -> IO ()
- remount :: FilePath -> [MountFlag] -> DriverData -> IO ()
- data MountFlag
- = ReadOnly
- | NoSUID
- | NoDev
- | NoExec
- | Synchronous
- | MandLock
- | DirSync
- | NoATime
- | NoDirATime
- | Silent
- | PosixACL
- | RelATime
- | IVersion
- | StrictATime
- type DriverData = ByteString
- noData :: DriverData
- bind :: FilePath -> FilePath -> IO ()
- rBind :: FilePath -> FilePath -> IO ()
- rebind :: FilePath -> [MountFlag] -> IO ()
- makeShared :: FilePath -> IO ()
- makeRShared :: FilePath -> IO ()
- makeSlave :: FilePath -> IO ()
- makeRSlave :: FilePath -> IO ()
- makePrivate :: FilePath -> IO ()
- makeRPrivate :: FilePath -> IO ()
- makeUnbindable :: FilePath -> IO ()
- makeRUnbindable :: FilePath -> IO ()
- move :: FilePath -> FilePath -> IO ()
- umount :: FilePath -> IO ()
- umountWith :: UmountFlag -> SymLink -> FilePath -> IO ()
- data UmountFlag
- data SymLink
Mount a filesystem
Arguments
:: String | Device file |
-> FilePath | Mount point |
-> String | Filesystem type |
-> [MountFlag] | List of mount options |
-> DriverData | Driver specific options |
-> IO () |
Mount a filesystem (call to
mount()
).
Arguments
:: FilePath | Mount point |
-> [MountFlag] | List of mount options |
-> DriverData | Driver specific options |
-> IO () |
Alter flags of a mounted filesystem (call to
mount()
with
MS_REMOUNT
).
Mount flags
A filesystem independent option to be used when mounting a filesystem.
Constructors
ReadOnly | Mount read-only ( |
NoSUID | Ignore suid and sgid bits ( |
NoDev | Disallow access to device special files
( |
NoExec | Disallow program execution ( |
Synchronous | Writes are synced at once ( |
MandLock | Allow mandatory locks on a filesystem
( |
DirSync | Directory modifications are synchronous
( |
NoATime | Do not update access times ( |
NoDirATime | Do not update directory access times
( |
Silent | Silent mount ( |
PosixACL | VFS does not apply the umask ( |
RelATime | Update atime relative to mtime/ctime
( |
IVersion | Update inode I_version field
( |
StrictATime | Always perform atime updates
( |
type DriverData = ByteStringSource
Filesystem dependent options to be used when mounting a filesystem; the
content of
is passed directly to the filesystem driver.
DriverData
Empty
.
DriverData
Bind a filesystem
Mount an already mounted filesystem under a new directory (call to
mount()
with
MS_BIND
).
Mount an already mounted filesystem and all its submounts under a new
directory (call to
mount()
with MS_BIND
and MS_REC
).
Alter flags of a bound filesystem (call to
mount()
with
MS_REMOUNT
and MS_BIND
).
Change propagation flags
These functions change the propagation flag of an already mounted filesystem, as explained in https://www.kernel.org/doc/Documentation/filesystems/sharedsubtree.txt. They all take the mount point as argument.
makeShared :: FilePath -> IO ()Source
Set the MS_SHARED
propagation flag on a mounted filesystem.
makeRShared :: FilePath -> IO ()Source
Set the MS_SHARED
propagation flag on a mounted filesystem and
recursively on all submounts.
makeRSlave :: FilePath -> IO ()Source
Set the MS_SLAVE
propagation flag on a mounted filesystem recursively on
all submounts.
makePrivate :: FilePath -> IO ()Source
Set the MS_PRIVATE
propagation flag on a mounted filesystem.
makeRPrivate :: FilePath -> IO ()Source
Set the MS_PRIVATE
propagation flag on a mounted filesystem and
recursively on all submounts.
makeUnbindable :: FilePath -> IO ()Source
Set the MS_UNBINDABLE
propagation flag on a mounted filesystem.
makeRUnbindable :: FilePath -> IO ()Source
Set the MS_UNBINDABLE
propagation flag on a mounted filesystem and
recursively on all submounts.
Move a filesystem
Atomically move a mounted filesystem to another mount point (call to
mount()
with
MS_MOVE
).
Unmount a filesystem
Arguments
:: UmountFlag | Unmount option |
-> SymLink | |
-> FilePath | Mount point |
-> IO () |
Unmount a filesystem using specific unmount options (call to
umount2()
). See
for details.
UmountFlag
Unmount flags
data UmountFlag Source
A filesystem independent option to be used when unmounting a filesystem.
Constructors
Plain | Plain unmount, behaves like |
Force | Force unmount even if busy. |
Detach | Perform a lazy unmount: make the mount point unavailable for new accesses, and actually perform the unmount when the mount point ceases to be busy. |
Expire | Mark the mount point as expired. If a mount point
is not currently in use, then an initial call to
|
Instances