-- | Maintainer: Jelmer Vernooij <jelmer@jelmer.uk>

module Propellor.Property.Logcheck (
	ReportLevel (Workstation, Server, Paranoid),
	Service,
	defaultPrefix,
	ignoreFilePath,
	ignoreLines,
	installed,
) where

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

data ReportLevel = Workstation | Server | Paranoid
type Service = String

instance ConfigurableValue ReportLevel where
	val :: ReportLevel -> String
val ReportLevel
Workstation = String
"workstation"
	val ReportLevel
Server = String
"server"
	val ReportLevel
Paranoid = String
"paranoid"

-- The common prefix used by default in syslog lines.
defaultPrefix :: String
defaultPrefix :: String
defaultPrefix = String
"^\\w{3} [ :[:digit:]]{11} [._[:alnum:]-]+ "

ignoreFilePath :: ReportLevel -> Service -> FilePath
ignoreFilePath :: ReportLevel -> String -> String
ignoreFilePath ReportLevel
t String
n = String
"/etc/logcheck/ignore.d." String -> String -> String
forall a. [a] -> [a] -> [a]
++ (ReportLevel -> String
forall t. ConfigurableValue t => t -> String
val ReportLevel
t) String -> String -> String
</> String
n

ignoreLines :: ReportLevel -> Service -> [String] -> Property UnixLike
ignoreLines :: ReportLevel -> String -> [String] -> Property UnixLike
ignoreLines ReportLevel
t String
n [String]
ls = (ReportLevel -> String -> String
ignoreFilePath ReportLevel
t String
n) String -> [String] -> Property UnixLike
`File.containsLines` [String]
ls
	Property UnixLike -> String -> Property UnixLike
forall p. IsProp p => p -> String -> p
`describe` (String
"logcheck ignore lines for " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"(" String -> String -> String
forall a. [a] -> [a] -> [a]
++ ReportLevel -> String
forall t. ConfigurableValue t => t -> String
val ReportLevel
t String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")

installed :: Property DebianLike
installed :: Property DebianLike
installed = [String] -> Property DebianLike
Apt.installed [String
"logcheck"]