module Propellor.Property.HostingProvider.DigitalOcean (
	distroKernel
) where
import Propellor
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.File as File
import qualified Propellor.Property.Reboot as Reboot
import Data.List
distroKernel :: Property
distroKernel = propertyList "digital ocean distro kernel hack"
	[ Apt.installed ["grub-pc", "kexec-tools", "file"]
	, "/etc/default/kexec" `File.containsLines`
		[ "LOAD_KEXEC=true"
		, "USE_GRUB_CONFIG=true"
		] `describe` "kexec configured"
	, check (not <$> runningInstalledKernel) Reboot.now
		`describe` "running installed kernel"
	]
runningInstalledKernel :: IO Bool
runningInstalledKernel = do
	kernelver <- takeWhile (/= '\n') <$> readProcess "uname" ["-r"]
	when (null kernelver) $
		error "failed to read uname -r"
	kernelimages <- concat <$> mapM kernelsIn ["/", "/boot/"] 
	when (null kernelimages) $
		error "failed to find any installed kernel images"
	findVersion kernelver <$>
		readProcess "file" ("-L" : kernelimages)
findVersion :: String -> String -> Bool
findVersion ver s = (" version " ++ ver ++ " ") `isInfixOf` s
kernelsIn :: FilePath -> IO [FilePath]
kernelsIn d = filter ("vmlinu" `isInfixOf`) <$> dirContents d