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

module Propellor.Property.Uwsgi 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 AppName = String

appEnabled :: AppName -> ConfigFile -> RevertableProperty DebianLike DebianLike
appEnabled :: AppName -> ConfigFile -> RevertableProperty DebianLike DebianLike
appEnabled AppName
an 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 = AppName -> AppName
appVal AppName
an AppName -> LinkTarget -> RevertableProperty UnixLike UnixLike
`File.isSymlinkedTo` AppName -> LinkTarget
appValRelativeCfg AppName
an
		forall p. IsProp p => p -> AppName -> p
`describe` (AppName
"uwsgi app enabled " forall a. [a] -> [a] -> [a]
++ AppName
an)
		forall x y. Combines x y => x -> y -> CombinedType x y
`requires` AppName -> ConfigFile -> Property DebianLike
appAvailable AppName
an 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 = AppName -> Property UnixLike
File.notPresent (AppName -> AppName
appVal AppName
an)
		forall p. IsProp p => p -> AppName -> p
`describe` (AppName
"uwsgi app disable" forall a. [a] -> [a] -> [a]
++ AppName
an)
		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

appAvailable :: AppName -> ConfigFile -> Property DebianLike
appAvailable :: AppName -> ConfigFile -> Property DebianLike
appAvailable AppName
an ConfigFile
cf = (AppName
"uwsgi app available " forall a. [a] -> [a] -> [a]
++ AppName
an) forall i.
IsProp (Property i) =>
AppName -> Property i -> Property i
==>
	forall (p :: * -> *) (untightened :: [MetaType])
       (tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
 SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (AppName -> AppName
appCfg AppName
an AppName -> ConfigFile -> Property UnixLike
`File.hasContent` (AppName
comment forall a. a -> [a] -> [a]
: ConfigFile
cf))
  where
	comment :: AppName
comment = AppName
"# deployed with propellor, do not modify"

appCfg :: AppName -> FilePath
appCfg :: AppName -> AppName
appCfg AppName
an = AppName
"/etc/uwsgi/apps-available" AppName -> AppName -> AppName
</> AppName
an AppName -> AppName -> AppName
<.> AppName
"ini"

appVal :: AppName -> FilePath
appVal :: AppName -> AppName
appVal AppName
an = AppName
"/etc/uwsgi/apps-enabled/" AppName -> AppName -> AppName
</> AppName
an AppName -> AppName -> AppName
<.> AppName
"ini"

appValRelativeCfg :: AppName -> File.LinkTarget
appValRelativeCfg :: AppName -> LinkTarget
appValRelativeCfg AppName
an = AppName -> LinkTarget
File.LinkTarget forall a b. (a -> b) -> a -> b
$ AppName
"../apps-available" AppName -> AppName -> AppName
</> AppName
an AppName -> AppName -> AppName
<.> AppName
"ini"

installed :: Property DebianLike
installed :: Property DebianLike
installed = ConfigFile -> Property DebianLike
Apt.installed [AppName
"uwsgi"]

restarted :: Property DebianLike
restarted :: Property DebianLike
restarted = AppName -> Property DebianLike
Service.restarted AppName
"uwsgi"

reloaded :: Property DebianLike
reloaded :: Property DebianLike
reloaded = AppName -> Property DebianLike
Service.reloaded AppName
"uwsgi"