module Nagios.Config.EDSL.Types where
data Host = Host { hostUse :: Maybe Host
, hostName :: String
, hostHostName :: Maybe String
, hostAlias :: Maybe String
, hostDisplayName :: Maybe String
, hostAddress :: Maybe String
, hostParents :: [Host]
, hostGroups :: [HostGroup]
, hostCheckCommand :: Maybe CommandApp
, hostMaxCheckAttempts :: Maybe Int
, hostCheckInterval :: Maybe Int
, hostRetryInterval :: Maybe Int
, hostNotes :: Maybe String
, hostCheckPeriod :: Maybe TimePeriod
, hostEventHandlerEnabled :: Maybe Bool
, hostFlapDetectionEnabled :: Maybe Bool
, hostProcessPerfData :: Maybe Bool
, hostRetainStatusInformation :: Maybe Bool
, hostRetainNonStatusInformation :: Maybe Bool
, hostContactGroups :: [ContactGroup]
, hostNotificationInterval :: Maybe Int
, hostNotificationPeriod :: Maybe TimePeriod
, hostNotificationOptions :: [HostNotificationOption]
, hostNotificationsEnabled :: Maybe Bool
, hostRegister :: Maybe Bool
} deriving (Show)
host :: String -> Host
host name = Host { hostUse = Nothing
, hostHostName = Nothing
, hostName = name
, hostAlias = Nothing
, hostDisplayName = Nothing
, hostAddress = Nothing
, hostParents = []
, hostGroups = []
, hostCheckCommand = Nothing
, hostMaxCheckAttempts = Nothing
, hostCheckInterval = Nothing
, hostRetryInterval = Nothing
, hostNotes = Nothing
, hostCheckPeriod = Nothing
, hostEventHandlerEnabled = Nothing
, hostFlapDetectionEnabled = Nothing
, hostProcessPerfData = Nothing
, hostRetainStatusInformation = Nothing
, hostRetainNonStatusInformation = Nothing
, hostContactGroups = []
, hostNotificationInterval = Nothing
, hostNotificationPeriod = Nothing
, hostNotificationOptions = []
, hostNotificationsEnabled = Nothing
, hostRegister = Nothing
}
data HostGroup = HostGroup { hostGroupName :: String
, hostGroupAlias :: String
, hostGroupMembers :: [Host]
, hostGroupHostGroupMembers :: [HostGroup]
, hostGroupNotes :: Maybe String
} deriving (Show)
hostgroup :: String -> String -> HostGroup
hostgroup name alias = HostGroup { hostGroupName = name
, hostGroupAlias = alias
, hostGroupMembers = []
, hostGroupHostGroupMembers = []
, hostGroupNotes = Nothing
}
data Service = Service { serviceUse :: Maybe Service
, serviceName :: String
, serviceHosts :: [Host]
, serviceHostGroups :: [HostGroup]
, serviceDescription :: Maybe String
, serviceDisplayName :: Maybe String
, serviceIsVolatile :: Maybe Bool
, serviceCheckCommand :: Maybe CommandApp
, serviceInitialState :: Maybe ServiceState
, serviceMaxCheckAttempts :: Maybe Int
, serviceCheckInterval :: Maybe Int
, serviceRetryInterval :: Maybe Int
, serviceActiveChecksEnabled :: Maybe Bool
, servicePassiveChecksEnabled :: Maybe Bool
, serviceParallelizeCheck :: Maybe Bool
, serviceCheckPeriod :: Maybe TimePeriod
, serviceObsessOverService :: Maybe Bool
, serviceCheckFreshness :: Maybe Bool
, serviceFreshnessThreshold :: Maybe Int
, serviceEventHandler :: Maybe CommandApp
, serviceEventHandlerEnabled :: Maybe Bool
, serviceFlapDetectionEnabled :: Maybe Bool
, serviceProcessPerfData :: Maybe Bool
, serviceRetainStatusInformation :: Maybe Bool
, serviceRetainNonStatusInformation :: Maybe Bool
, serviceNotificationInterval :: Maybe Int
, serviceNotificationPeriod :: Maybe TimePeriod
, serviceNotificationOptions :: [ServiceNotificationOption]
, serviceNotificationsEnabled :: Maybe Bool
, serviceContacts :: [Contact]
, serviceContactGroups :: [ContactGroup]
, serviceNotes :: Maybe String
, serviceRegister :: Maybe Bool
} deriving (Show)
service :: String -> Service
service name = Service { serviceUse = Nothing
, serviceName = name
, serviceHosts = []
, serviceHostGroups = []
, serviceDescription = Nothing
, serviceDisplayName = Nothing
, serviceIsVolatile = Nothing
, serviceCheckCommand = Nothing
, serviceInitialState = Nothing
, serviceMaxCheckAttempts = Nothing
, serviceCheckInterval = Nothing
, serviceRetryInterval = Nothing
, serviceActiveChecksEnabled = Nothing
, servicePassiveChecksEnabled = Nothing
, serviceParallelizeCheck = Nothing
, serviceCheckPeriod = Nothing
, serviceObsessOverService = Nothing
, serviceCheckFreshness = Nothing
, serviceFreshnessThreshold = Nothing
, serviceEventHandler = Nothing
, serviceEventHandlerEnabled = Nothing
, serviceFlapDetectionEnabled = Nothing
, serviceProcessPerfData = Nothing
, serviceRetainStatusInformation = Nothing
, serviceRetainNonStatusInformation = Nothing
, serviceNotificationInterval = Nothing
, serviceNotificationPeriod = Nothing
, serviceNotificationOptions = []
, serviceNotificationsEnabled = Nothing
, serviceContacts = []
, serviceContactGroups = []
, serviceNotes = Nothing
, serviceRegister = Nothing
}
data ServiceGroup = ServiceGroup { serviceGroupName :: String
, serviceGroupAlias :: String
, serviceGroupMembers :: [Service]
, serviceGroupNotes :: Maybe String
} deriving (Show)
data Command = Command { commandName :: String
, commandLine :: String
} deriving (Show)
data CommandApp = CommandApp Command [String] deriving (Show)
apply :: Command -> [String] -> CommandApp
apply = CommandApp
command :: CommandApp -> Command
command (CommandApp x _) = x
data TimePeriod = TimePeriod { timePeriodName :: String
, timePeriodAlias :: String
, timePeriodWeekdays :: [Weekday String]
} deriving (Show)
data Contact = Contact { contactUse :: Maybe Contact
, contactName :: String
, contactAlias :: Maybe String
, contactGroups :: [ContactGroup]
, contactHostNotificationsEnabled :: Maybe Bool
, contactServiceNotificationsEnabled :: Maybe Bool
, contactHostNotificationPeriod :: Maybe TimePeriod
, contactServiceNotificationPeriod :: Maybe TimePeriod
, contactHostNotificationOptions :: [HostNotificationOption]
, contactServiceNotificationOptions :: [ServiceNotificationOption]
, contactHostNotificationCommands :: Maybe CommandApp
, contactServiceNotificationCommands :: Maybe CommandApp
, contactEmail :: Maybe String
, contactCanSubmitCommands :: Maybe Bool
, contactRetainStatusInformation :: Maybe Bool
, contactRetainNonStatusInformation :: Maybe Bool
, contactRegister :: Maybe Bool
} deriving (Show)
contact :: String -> Contact
contact name = Contact { contactUse = Nothing
, contactName = name
, contactAlias = Nothing
, contactGroups = []
, contactHostNotificationsEnabled = Nothing
, contactServiceNotificationsEnabled = Nothing
, contactHostNotificationPeriod = Nothing
, contactServiceNotificationPeriod = Nothing
, contactHostNotificationOptions = []
, contactServiceNotificationOptions = []
, contactHostNotificationCommands = Nothing
, contactServiceNotificationCommands = Nothing
, contactEmail = Nothing
, contactCanSubmitCommands = Nothing
, contactRetainStatusInformation = Nothing
, contactRetainNonStatusInformation = Nothing
, contactRegister = Nothing
}
data ContactGroup = ContactGroup { contactGroupName :: String
, contactGroupAlias :: String
, contactGroupMembers :: [Contact]
} deriving (Show)
contactgroup :: String -> String -> ContactGroup
contactgroup name alias = ContactGroup { contactGroupName = name
, contactGroupAlias = alias
, contactGroupMembers = []
}
data ServiceState = ServiceStateOK
| ServiceStateWarning
| ServiceStateUnknown
| ServiceStateCritical
deriving (Show)
data ServiceNotificationOption = ServiceNotificationWarning
| ServiceNotificationUnknown
| ServiceNotificationCritical
| ServiceNotificationRecovery
| ServiceNotificationFlapping
| ServiceNotificationScheduledDowntime
deriving (Show)
serviceNotificationAlways :: [ServiceNotificationOption]
serviceNotificationAlways = [ServiceNotificationWarning
, ServiceNotificationUnknown
, ServiceNotificationCritical
, ServiceNotificationRecovery
, ServiceNotificationFlapping
, ServiceNotificationScheduledDowntime]
data HostNotificationOption = HostNotificationDown
| HostNotificationUnreachable
| HostNotificationRecovery
| HostNotificationFlapping
| HostNotificationScheduledDowntime
deriving (Show)
hostNotificationAlways :: [HostNotificationOption]
hostNotificationAlways = [HostNotificationDown
, HostNotificationUnreachable
, HostNotificationRecovery
, HostNotificationFlapping
, HostNotificationScheduledDowntime]
data Weekday a = Monday a
| Tuesday a
| Wednesday a
| Thursday a
| Friday a
| Saterday a
| Sunday a
deriving (Show)