module Propellor.Property.Fail2Ban where

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

installed :: Property DebianLike
installed :: Property DebianLike
installed = Package -> Property DebianLike
Apt.serviceInstalledRunning Package
"fail2ban"

reloaded :: Property DebianLike
reloaded :: Property DebianLike
reloaded = Package -> Property DebianLike
Service.reloaded Package
"fail2ban"

type Jail = String

type Filter = String

type Action = String

-- | By default, fail2ban only enables the ssh jail, but many others
-- are available to be enabled, for example "postfix-sasl"
jailEnabled :: Jail -> Property DebianLike
jailEnabled :: Package -> Property DebianLike
jailEnabled Package
name = Package -> [(Package, Package)] -> Property DebianLike
jailEnabled' Package
name []
	forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
reloaded

jailEnabled' :: Jail -> [(IniKey, String)] -> Property DebianLike
jailEnabled' :: Package -> [(Package, Package)] -> Property DebianLike
jailEnabled' Package
name [(Package, Package)]
settings =
	Package -> [(Package, Package)] -> Property UnixLike
jailConfigured' Package
name ((Package
"enabled", Package
"true") forall a. a -> [a] -> [a]
: [(Package, Package)]
settings)
	forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
reloaded

-- | Configures a jail. For example:
--
-- > jailConfigured' "sshd" [("port", "2222")]
jailConfigured' :: Jail -> [(IniKey, String)] -> Property UnixLike
jailConfigured' :: Package -> [(Package, Package)] -> Property UnixLike
jailConfigured' Package
name [(Package, Package)]
settings = forall {k} (metatypes :: k).
SingI metatypes =>
Package
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList (Package
"jail \"" forall a. [a] -> [a] -> [a]
++ Package
name forall a. [a] -> [a] -> [a]
++ Package
"\" configuration") forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	-- removes .conf files added by old versions of Fail2Ban properties
	forall {a} p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Package -> Property UnixLike
File.notPresent (Package -> Package
oldJailConfFile Package
name)
	forall {a} p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Package -> Package
jailConfFile Package
name Package
-> [(Package, [(Package, Package)])]
-> RevertableProperty UnixLike UnixLike
`iniFileContains` [(Package
name, [(Package, Package)]
settings)]

-- | Adds a setting to a given jail. For example:
--
-- > jailConfigured "sshd" "port"  "2222"
jailConfigured :: Jail -> IniKey -> String -> Property UnixLike
jailConfigured :: Package -> Package -> Package -> Property UnixLike
jailConfigured Package
name Package
key Package
value = forall {k} (metatypes :: k).
SingI metatypes =>
Package
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList (Package
"jail \"" forall a. [a] -> [a] -> [a]
++ Package
name forall a. [a] -> [a] -> [a]
++ Package
"\" configuration") forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	-- removes .conf files added by old versions of Fail2Ban properties
	forall {a} p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Package -> Property UnixLike
File.notPresent (Package -> Package
oldJailConfFile Package
name)
	forall {a} p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Package -> Package
jailConfFile Package
name Package -> (Package, Package, Package) -> Property UnixLike
`containsIniSetting` (Package
name, Package
key, Package
value)

oldJailConfFile :: Jail -> FilePath
oldJailConfFile :: Package -> Package
oldJailConfFile Package
name = Package
"/etc/fail2ban/jail.d/" forall a. [a] -> [a] -> [a]
++ Package
name forall a. [a] -> [a] -> [a]
++ Package
".conf"

jailConfFile :: Jail -> FilePath
jailConfFile :: Package -> Package
jailConfFile Package
name = Package
"/etc/fail2ban/jail.d/" forall a. [a] -> [a] -> [a]
++ Package
name forall a. [a] -> [a] -> [a]
++ Package
".local"

filterConfFile :: Filter -> FilePath
filterConfFile :: Package -> Package
filterConfFile Package
name = Package
"/etc/fail2ban/filter.d/" forall a. [a] -> [a] -> [a]
++ Package
name forall a. [a] -> [a] -> [a]
++ Package
".local"

actionConfFile :: Action -> FilePath
actionConfFile :: Package -> Package
actionConfFile Package
name = Package
"/etc/fail2ban/action.d/" forall a. [a] -> [a] -> [a]
++ Package
name forall a. [a] -> [a] -> [a]
++ Package
".local"