-- | Maintainer: Félix Sipma <felix+propellor@gueux.org>

module Propellor.Property.Nginx 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]

siteEnabled :: HostName -> ConfigFile -> RevertableProperty DebianLike DebianLike
siteEnabled :: HostName -> ConfigFile -> RevertableProperty DebianLike DebianLike
siteEnabled HostName
hn 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 = HostName -> HostName
siteVal HostName
hn HostName -> LinkTarget -> RevertableProperty UnixLike UnixLike
`File.isSymlinkedTo` HostName -> LinkTarget
siteValRelativeCfg HostName
hn
		forall p. IsProp p => p -> HostName -> p
`describe` (HostName
"nginx site enabled " forall a. [a] -> [a] -> [a]
++ HostName
hn)
		forall x y. Combines x y => x -> y -> CombinedType x y
`requires` HostName -> ConfigFile -> Property DebianLike
siteAvailable HostName
hn 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
	disable :: CombinedType (Property DebianLike) (Property DebianLike)
disable = HostName -> Property UnixLike
File.notPresent (HostName -> HostName
siteVal HostName
hn)
		forall p. IsProp p => p -> HostName -> p
`describe` (HostName
"nginx site disable" forall a. [a] -> [a] -> [a]
++ HostName
hn)
		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

siteAvailable :: HostName -> ConfigFile -> Property DebianLike
siteAvailable :: HostName -> ConfigFile -> Property DebianLike
siteAvailable HostName
hn ConfigFile
cf = HostName
"nginx site available " forall a. [a] -> [a] -> [a]
++ HostName
hn forall i.
IsProp (Property i) =>
HostName -> Property i -> Property i
==> forall (p :: * -> *) (untightened :: [MetaType])
       (tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
 SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets Property UnixLike
go
  where
	comment :: HostName
comment = HostName
"# deployed with propellor, do not modify"
	go :: Property UnixLike
go = HostName -> HostName
siteCfg HostName
hn HostName -> ConfigFile -> Property UnixLike
`File.hasContent` (HostName
comment forall a. a -> [a] -> [a]
: ConfigFile
cf)

siteCfg :: HostName -> FilePath
siteCfg :: HostName -> HostName
siteCfg HostName
hn = HostName
"/etc/nginx/sites-available/" forall a. [a] -> [a] -> [a]
++ HostName
hn

siteVal :: HostName -> FilePath
siteVal :: HostName -> HostName
siteVal HostName
hn = HostName
"/etc/nginx/sites-enabled/" forall a. [a] -> [a] -> [a]
++ HostName
hn

siteValRelativeCfg :: HostName -> File.LinkTarget
siteValRelativeCfg :: HostName -> LinkTarget
siteValRelativeCfg HostName
hn = HostName -> LinkTarget
File.LinkTarget (HostName
"../sites-available/" forall a. [a] -> [a] -> [a]
++ HostName
hn)

installed :: Property DebianLike
installed :: Property DebianLike
installed = ConfigFile -> Property DebianLike
Apt.installed [HostName
"nginx"]

restarted :: Property DebianLike
restarted :: Property DebianLike
restarted = HostName -> Property DebianLike
Service.restarted HostName
"nginx"

reloaded :: Property DebianLike
reloaded :: Property DebianLike
reloaded = HostName -> Property DebianLike
Service.reloaded HostName
"nginx"