module Propellor.Property.Obnam where
import Propellor.Base
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.Cron as Cron
import qualified Propellor.Property.Gpg as Gpg
import Data.List
type ObnamParam = String
data NumClients = OnlyClient | MultipleClients
	deriving (Eq)
backup :: FilePath -> Cron.Times -> [ObnamParam] -> NumClients -> Property NoInfo
backup dir crontimes params numclients =
	backup' dir crontimes params numclients
		`requires` restored dir params
backupEncrypted :: FilePath -> Cron.Times -> [ObnamParam] -> NumClients -> Gpg.GpgKeyId -> Property HasInfo
backupEncrypted dir crontimes params numclients keyid =
	backup dir crontimes params' numclients
		`requires` Gpg.keyImported keyid (User "root")
  where
	params' = ("--encrypt-with=" ++ Gpg.getGpgKeyId keyid) : params
backup' :: FilePath -> Cron.Times -> [ObnamParam] -> NumClients -> Property NoInfo
backup' dir crontimes params numclients = cronjob `describe` desc
  where
	desc = dir ++ " backed up by obnam"
	cronjob = Cron.niceJob ("obnam_backup" ++ dir) crontimes (User "root") "/" $
		unwords $ catMaybes
			[ if numclients == OnlyClient
				
				then Just $ forcelockcmd ++ " 2>/dev/null ;"
				else Nothing
			, Just backupcmd
			, if any isKeepParam params
				then Just $ "&& " ++ forgetcmd
				else Nothing
			]
	forcelockcmd = unwords $
		[ "obnam"
		, "force-lock"
		] ++ map shellEscape params
	backupcmd = unwords $
		[ "obnam"
		, "backup"
		, shellEscape dir
		] ++ map shellEscape params
	forgetcmd = unwords $
		[ "obnam"
		, "forget"
		] ++ map shellEscape params
restored :: FilePath -> [ObnamParam] -> Property NoInfo
restored dir params = property (dir ++ " restored by obnam") go
	`requires` installed
  where
	go = ifM (liftIO needsRestore)
		( do
			warningMessage $ dir ++ " is empty/missing; restoring from backup ..."
			liftIO restore
		, noChange
		)
	needsRestore = null <$> catchDefaultIO [] (dirContents dir)
	restore = withTmpDirIn (takeDirectory dir) "obnam-restore" $ \tmpdir -> do
		ok <- boolSystem "obnam" $
			[ Param "restore"
			, Param "--to"
			, Param tmpdir
			] ++ map Param params
		let restoreddir = tmpdir ++ "/" ++ dir
		ifM (pure ok <&&> doesDirectoryExist restoreddir)
			( do
				void $ tryIO $ removeDirectory dir
				renameDirectory restoreddir dir
				return MadeChange
			, return FailedChange
			)
data KeepPolicy 
	= KeepHours Int
	| KeepDays Int
	| KeepWeeks Int
	| KeepMonths Int
	| KeepYears Int
keepParam :: [KeepPolicy] -> ObnamParam
keepParam ps = "--keep=" ++ intercalate "," (map go ps)
  where
	go (KeepHours n) = mk n 'h'
	go (KeepDays n) = mk n 'd'
	go (KeepWeeks n) = mk n 'w'
	go (KeepMonths n) = mk n 'm'
	go (KeepYears n) = mk n 'y'
	mk n c = show n ++ [c]
isKeepParam :: ObnamParam -> Bool
isKeepParam p = "--keep=" `isPrefixOf` p
installed :: Property NoInfo
installed = Apt.installed ["obnam"]