summaryrefslogtreecommitdiff
path: root/src/Propellor/Property/Mount.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Propellor/Property/Mount.hs')
-rw-r--r--src/Propellor/Property/Mount.hs84
1 files changed, 7 insertions, 77 deletions
diff --git a/src/Propellor/Property/Mount.hs b/src/Propellor/Property/Mount.hs
index 943986c6..bb0f60a7 100644
--- a/src/Propellor/Property/Mount.hs
+++ b/src/Propellor/Property/Mount.hs
@@ -1,14 +1,15 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeSynonymInstances, FlexibleInstances #-}
+-- | Properties in this module ensure that things are currently mounted,
+-- but without making the mount persistent. Use `Propellor.Property.Fstab`
+-- to configure persistent mounts.
+
module Propellor.Property.Mount where
import Propellor.Base
-import qualified Propellor.Property.File as File
import Utility.Path
-import Data.Char
import Data.List
-import Utility.Table
-- | type of filesystem to mount ("auto" to autodetect)
type FsType = String
@@ -20,6 +21,8 @@ type Source = String
type MountPoint = FilePath
-- | Filesystem mount options. Eg, MountOpts ["errors=remount-ro"]
+--
+-- For default mount options, use `mempty`.
newtype MountOpts = MountOpts [String]
deriving Monoid
@@ -36,7 +39,7 @@ formatMountOpts :: MountOpts -> String
formatMountOpts (MountOpts []) = "defaults"
formatMountOpts (MountOpts l) = intercalate "," l
--- | Mounts a device.
+-- | Mounts a device, without listing it in </etc/fstab>.
mounted :: FsType -> Source -> MountPoint -> MountOpts -> Property UnixLike
mounted fs src mnt opts = property (mnt ++ " mounted") $
toResult <$> liftIO (mount fs src mnt opts)
@@ -57,79 +60,6 @@ mount fs src mnt opts = boolSystem "mount" $
, Param mnt
]
-newtype SwapPartition = SwapPartition FilePath
-
--- | Replaces </etc/fstab> with a file that should cause the currently
--- mounted partitions to be re-mounted the same way on boot.
---
--- For each specified MountPoint, the UUID of each partition
--- (or if there is no UUID, its label), its filesystem type,
--- and its mount options are all automatically probed.
---
--- The SwapPartitions are also included in the generated fstab.
-fstabbed :: [MountPoint] -> [SwapPartition] -> Property Linux
-fstabbed mnts swaps = property' "fstabbed" $ \o -> do
- fstab <- liftIO $ genFstab mnts swaps id
- ensureProperty o $
- "/etc/fstab" `File.hasContent` fstab
-
-genFstab :: [MountPoint] -> [SwapPartition] -> (MountPoint -> MountPoint) -> IO [String]
-genFstab mnts swaps mnttransform = do
- fstab <- liftIO $ mapM getcfg (sort mnts)
- swapfstab <- liftIO $ mapM getswapcfg swaps
- return $ header ++ formatTable (legend : fstab ++ swapfstab)
- where
- header =
- [ "# /etc/fstab: static file system information. See fstab(5)"
- , "# "
- ]
- legend = ["# <file system>", "<mount point>", "<type>", "<options>", "<dump>", "<pass>"]
- getcfg mnt = sequence
- [ fromMaybe (error $ "unable to find mount source for " ++ mnt)
- <$> getM (\a -> a mnt)
- [ uuidprefix getMountUUID
- , sourceprefix getMountLabel
- , getMountSource
- ]
- , pure (mnttransform mnt)
- , fromMaybe "auto" <$> getFsType mnt
- , formatMountOpts <$> getFsMountOpts mnt
- , pure "0"
- , pure (if mnt == "/" then "1" else "2")
- ]
- getswapcfg (SwapPartition swap) = sequence
- [ fromMaybe swap <$> getM (\a -> a swap)
- [ uuidprefix getSourceUUID
- , sourceprefix getSourceLabel
- ]
- , pure "none"
- , pure "swap"
- , pure (formatMountOpts mempty)
- , pure "0"
- , pure "0"
- ]
- prefix s getter m = fmap (s ++) <$> getter m
- uuidprefix = prefix "UUID="
- sourceprefix = prefix "LABEL="
-
--- | Checks if </etc/fstab> is not configured.
--- This is the case if it doesn't exist, or
--- consists entirely of blank lines or comments.
---
--- So, if you want to only replace the fstab once, and then never touch it
--- again, allowing local modifications:
---
--- > check noFstab (fstabbed mnts [])
-noFstab :: IO Bool
-noFstab = ifM (doesFileExist "/etc/fstab")
- ( null . filter iscfg . lines <$> readFile "/etc/fstab"
- , return True
- )
- where
- iscfg l
- | null l = False
- | otherwise = not $ "#" `isPrefixOf` dropWhile isSpace l
-
-- | Lists all mount points of the system.
mountPoints :: IO [MountPoint]
mountPoints = lines <$> readProcess "findmnt" ["-rn", "--output", "target"]