module Propellor.Property.Chroot.Util where

import Propellor.Property.Mount

import Utility.Env
import Utility.Directory

import Control.Applicative
import Prelude

-- | When chrooting, it's useful to ensure that PATH has all the standard
-- directories in it. This adds those directories to whatever PATH is
-- already set.
standardPathEnv :: IO [(String, String)]
standardPathEnv :: IO [(String, String)]
standardPathEnv = do
	String
path <- String -> String -> IO String
getEnvDefault String
"PATH" String
"/bin"
	forall k v. Eq k => k -> v -> [(k, v)] -> [(k, v)]
addEntry String
"PATH" (String
path forall a. [a] -> [a] -> [a]
++ String
stdPATH)
		forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [(String, String)]
getEnvironment

stdPATH :: String
stdPATH :: String
stdPATH = String
"/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"

-- | Removes the contents of a chroot. First, unmounts any filesystems
-- mounted within it.
removeChroot :: FilePath -> IO ()
removeChroot :: String -> IO ()
removeChroot String
c = do
	String -> IO ()
unmountBelow String
c
	String -> IO ()
removeDirectoryRecursive String
c