Unixutils-1.54.3: A crude interface between Haskell and Unix-like operating systems
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Unix.Mount

Description

functions for mounting, umounting, parsing /proc/mounts, etc

Synopsis

Documentation

umountBelow Source #

Arguments

:: Bool

Lazy (umount -l flag) if true

-> FilePath

canonicalised, absolute path

-> IO [(FilePath, (ExitCode, String, String))]

paths that we attempted to umount, and the responding output from the umount command

umountBelow - unmounts all mount points below belowPath /proc/mounts must be present and readable. Because of the way linux handles changeroots, we can't trust everything we see in /proc/mounts. However, we make the following assumptions:

  1. there is a one-to-one correspondence between the entries in /proc/mounts and the actual mounts, and
  2. every mount point we might encounter is a suffix of one of the mount points listed in /proc/mounts (because being in a a chroot doesn't affect /proc/mounts.)

So we can search /proc/mounts for an entry has the mount point we are looking for as a substring, then add the extra text on the right to our path and try to unmount that. Then we start again since nested mounts might have been revealed.

For example, suppose we are chrooted into /home/david/environments/sid and we call "umountBelow /proc". We might see the mount point /home/david/environments/sid/proc/bus/usb in /proc/mounts, which means we need to run "umount /proc/bus/usb".

See also: umountSucceeded

umount :: [String] -> IO (ExitCode, String, String) Source #

umount - run umount with the specified args NOTE: this function uses exec, so you do not need to shell-escape NOTE: we don't use the umount system call because the system call is not smart enough to update /etc/mtab

withMount :: (MonadIO m, MonadMask m) => FilePath -> FilePath -> m a -> m a Source #

Do an IO task with a file system remounted using mount --bind. This was written to set up a build environment.

data WithProcAndSys m a Source #

Monad transformer to ensure that proc and sys are mounted during a computation.

Instances

Instances details
MonadTrans WithProcAndSys Source # 
Instance details

Defined in System.Unix.Mount

Methods

lift :: Monad m => m a -> WithProcAndSys m a #

MonadIO m => MonadIO (WithProcAndSys m) Source # 
Instance details

Defined in System.Unix.Mount

Methods

liftIO :: IO a -> WithProcAndSys m a #

Applicative m => Applicative (WithProcAndSys m) Source # 
Instance details

Defined in System.Unix.Mount

Methods

pure :: a -> WithProcAndSys m a #

(<*>) :: WithProcAndSys m (a -> b) -> WithProcAndSys m a -> WithProcAndSys m b #

liftA2 :: (a -> b -> c) -> WithProcAndSys m a -> WithProcAndSys m b -> WithProcAndSys m c #

(*>) :: WithProcAndSys m a -> WithProcAndSys m b -> WithProcAndSys m b #

(<*) :: WithProcAndSys m a -> WithProcAndSys m b -> WithProcAndSys m a #

Functor m => Functor (WithProcAndSys m) Source # 
Instance details

Defined in System.Unix.Mount

Methods

fmap :: (a -> b) -> WithProcAndSys m a -> WithProcAndSys m b #

(<$) :: a -> WithProcAndSys m b -> WithProcAndSys m a #

Monad m => Monad (WithProcAndSys m) Source # 
Instance details

Defined in System.Unix.Mount

Methods

(>>=) :: WithProcAndSys m a -> (a -> WithProcAndSys m b) -> WithProcAndSys m b #

(>>) :: WithProcAndSys m a -> WithProcAndSys m b -> WithProcAndSys m b #

return :: a -> WithProcAndSys m a #

withProcAndSys :: (MonadIO m, MonadMask m) => FilePath -> WithProcAndSys m a -> m a Source #

Mount proc and sys in the specified build root and execute a task. Typically, the task would start with a chroot into the build root. If the build root given is "/" it is assumed that the file systems are already mounted, no mounting or unmounting is done.

withTmp :: (MonadIO m, MonadMask m) => FilePath -> m a -> m a Source #

Do an IO task with /tmp remounted. This could be used to share /tmp with a build root.