-- | Maintainer: Sean Whitton <spwhitton@spwhitton.name>

module Propellor.Property.Firejail (
	installed,
	jailed,
) where

import Propellor.Base
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.File as File

-- | Ensures that Firejail is installed
installed :: Property DebianLike
installed :: Property DebianLike
installed = [Package] -> Property DebianLike
Apt.installed [Package
"firejail"]

-- | For each program name passed, create symlinks in /usr/local/bin that
-- will launch that program in a Firejail sandbox.
--
-- The profile for the sandbox will be the same as if the user had run
-- @firejail@ directly without passing @--profile@ (see "SECURITY PROFILES" in
-- firejail(1)).
--
-- See "DESKTOP INTEGRATION" in firejail(1).
jailed :: [String] -> Property DebianLike
jailed :: [Package] -> Property DebianLike
jailed [Package]
ps = forall a. Monoid a => [a] -> a
mconcat (forall a b. (a -> b) -> [a] -> [b]
map Package -> RevertableProperty UnixLike UnixLike
jailed' [Package]
ps)
	forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property DebianLike
installed
	forall p. IsProp p => p -> Package -> p
`describe` [Package] -> Package
unwords (Package
"firejail jailed"forall a. a -> [a] -> [a]
:[Package]
ps)

jailed' :: String -> RevertableProperty UnixLike UnixLike
jailed' :: Package -> RevertableProperty UnixLike UnixLike
jailed' Package
p = (Package
"/usr/local/bin" Package -> Package -> Package
</> Package
p)
	Package -> LinkTarget -> RevertableProperty UnixLike UnixLike
`File.isSymlinkedTo` Package -> LinkTarget
File.LinkTarget Package
"/usr/bin/firejail"