{-# LINE 1 "src/System/Posix/Syslog/Priority.hsc" #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LINE 2 "src/System/Posix/Syslog/Priority.hsc" #-}

{- |
   Maintainer: simons@cryp.to
   Stability: provisional
   Portability: POSIX

   FFI bindings to @syslog(3)@ from
   <http://pubs.opengroup.org/onlinepubs/9699919799/functions/syslog.html POSIX.1-2008>.
   This module is intended for purposes of low-level implementation. Users of
   this library should prefer safer and more convenient API provided by
   "System.Posix.Syslog".
-}

module System.Posix.Syslog.Priority where

import Foreign.C
import GHC.Generics ( Generic )


{-# LINE 21 "src/System/Posix/Syslog/Priority.hsc" #-}

-- * Message Priorities

-- | Log messages are prioritized with one of the following levels:
--
-- >>> [minBound..maxBound] :: [Priority]
-- [Emergency,Alert,Critical,Error,Warning,Notice,Info,Debug]
--
-- The 'Ord' instance for 'Priority' considers the more urgent level lower than
-- less urgent ones:
--
-- >>> Emergency < Debug
-- True
-- >>> minimum [minBound..maxBound] :: Priority
-- Emergency
-- >>> maximum [minBound..maxBound] :: Priority
-- Debug

data Priority = Emergency       -- ^ the system is unusable
              | Alert           -- ^ action must be taken immediately
              | Critical        -- ^ critical conditions
              | Error           -- ^ error conditions
              | Warning         -- ^ warning conditions
              | Notice          -- ^ normal but significant condition
              | Info            -- ^ informational
              | Debug           -- ^ debug-level messages
  deriving (Show, Read, Eq, Ord, Bounded, Enum, Generic)

-- | Translate a 'Priority' into the system-dependent identifier that's used by
-- the @syslog(3)@ implementation.

{-# INLINE fromPriority #-}
fromPriority :: Priority -> CInt
fromPriority Emergency = 0
{-# LINE 55 "src/System/Posix/Syslog/Priority.hsc" #-}
fromPriority Alert     = 1
{-# LINE 56 "src/System/Posix/Syslog/Priority.hsc" #-}
fromPriority Critical  = 2
{-# LINE 57 "src/System/Posix/Syslog/Priority.hsc" #-}
fromPriority Error     = 3
{-# LINE 58 "src/System/Posix/Syslog/Priority.hsc" #-}
fromPriority Warning   = 4
{-# LINE 59 "src/System/Posix/Syslog/Priority.hsc" #-}
fromPriority Notice    = 5
{-# LINE 60 "src/System/Posix/Syslog/Priority.hsc" #-}
fromPriority Info      = 6
{-# LINE 61 "src/System/Posix/Syslog/Priority.hsc" #-}
fromPriority Debug     = 7
{-# LINE 62 "src/System/Posix/Syslog/Priority.hsc" #-}