module Propellor.Property.Prosody where
import Propellor.Base
import qualified Propellor.Property.File as File
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.Service as Service
type ConfigFile = [String]
type Conf = String
confEnabled :: Conf -> ConfigFile -> RevertableProperty DebianLike DebianLike
confEnabled :: Conf -> ConfigFile -> RevertableProperty DebianLike DebianLike
confEnabled Conf
conf ConfigFile
cf = Property DebianLike
enable forall setupmetatypes undometatypes.
Property setupmetatypes
-> Property undometatypes
-> RevertableProperty setupmetatypes undometatypes
<!> Property DebianLike
disable
where
enable :: CombinedType
(CombinedType (Property DebianLike) (Property DebianLike))
(Property DebianLike)
enable = Conf
dir Conf -> LinkTarget -> RevertableProperty UnixLike UnixLike
`File.isSymlinkedTo` LinkTarget
target
forall p. IsProp p => p -> Conf -> p
`describe` (Conf
"prosody conf enabled " forall a. [a] -> [a] -> [a]
++ Conf
conf)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Conf -> ConfigFile -> Property DebianLike
confAvailable Conf
conf ConfigFile
cf
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property DebianLike
installed
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
reloaded
where
target :: LinkTarget
target = Conf -> LinkTarget
confValRelativePath Conf
conf
dir :: Conf
dir = Conf -> Conf
confValPath Conf
conf
confValRelativePath :: Conf -> LinkTarget
confValRelativePath Conf
conf' = Conf -> LinkTarget
File.LinkTarget forall a b. (a -> b) -> a -> b
$
Conf
"../conf.avail" Conf -> Conf -> Conf
</> Conf
conf' Conf -> Conf -> Conf
<.> Conf
"cfg.lua"
disable :: CombinedType (Property DebianLike) (Property DebianLike)
disable = Conf -> Property UnixLike
File.notPresent (Conf -> Conf
confValPath Conf
conf)
forall p. IsProp p => p -> Conf -> p
`describe` (Conf
"prosody conf disabled " forall a. [a] -> [a] -> [a]
++ Conf
conf)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property DebianLike
installed
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
reloaded
confAvailable :: Conf -> ConfigFile -> Property DebianLike
confAvailable :: Conf -> ConfigFile -> Property DebianLike
confAvailable Conf
conf ConfigFile
cf = (Conf
"prosody conf available " forall a. [a] -> [a] -> [a]
++ Conf
conf) forall i. IsProp (Property i) => Conf -> Property i -> Property i
==>
forall (p :: * -> *) (untightened :: [MetaType])
(tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (Conf -> Conf
confAvailPath Conf
conf Conf -> ConfigFile -> Property UnixLike
`File.hasContent` (Conf
comment forall a. a -> [a] -> [a]
: ConfigFile
cf))
where
comment :: Conf
comment = Conf
"-- deployed with propellor, do not modify"
confAvailPath :: Conf -> FilePath
confAvailPath :: Conf -> Conf
confAvailPath Conf
conf = Conf
"/etc/prosody/conf.avail" Conf -> Conf -> Conf
</> Conf
conf Conf -> Conf -> Conf
<.> Conf
"cfg.lua"
confValPath :: Conf -> FilePath
confValPath :: Conf -> Conf
confValPath Conf
conf = Conf
"/etc/prosody/conf.d" Conf -> Conf -> Conf
</> Conf
conf Conf -> Conf -> Conf
<.> Conf
"cfg.lua"
installed :: Property DebianLike
installed :: Property DebianLike
installed = ConfigFile -> Property DebianLike
Apt.installed [Conf
"prosody"]
restarted :: Property DebianLike
restarted :: Property DebianLike
restarted = Conf -> Property DebianLike
Service.restarted Conf
"prosody"
reloaded :: Property DebianLike
reloaded :: Property DebianLike
reloaded = Conf -> Property DebianLike
Service.reloaded Conf
"prosody"