#ifdef DERIVE_DATA_TYPEABLE
#endif
#ifdef DERIVE_GHC_GENERICS
#endif
#ifdef DECLARE_NFDATA_INSTANCE
#endif
module Data.Verbosity
( Verbosity(..)
, fromInt
#ifdef DERIVE_DATA_TYPEABLE
, parse
#endif
)
where
import Prelude
( Bounded(maxBound, minBound)
, Enum(fromEnum, toEnum)
#ifdef DECLARE_BINARY_INSTANCE
, fromIntegral
#endif
)
import Data.Bool ((&&), otherwise)
import Data.Eq (Eq)
import Data.Int (Int)
import Data.Maybe (Maybe(..))
import Data.Ord (Ord(..))
import Text.Read (Read)
import Text.Show (Show)
#ifdef DERIVE_DATA_TYPEABLE
import Data.Data (Data(toConstr), Typeable, showConstr)
import Data.List (lookup)
import Data.String (IsString(fromString))
#endif
#ifdef DERIVE_GHC_GENERICS
import GHC.Generics (Generic)
#endif
#ifdef DECLARE_BINARY_INSTANCE
import Control.Applicative ((<$>))
import Data.Function ((.))
import Data.Binary (Binary(get, put), getWord8, putWord8)
#endif
#ifdef DECLARE_DEFAULT_INSTANCE
import Data.Default.Class (Default(def))
#endif
#ifdef DECLARE_NFDATA_INSTANCE
import Control.DeepSeq (NFData(rnf))
#endif
data Verbosity
= Silent
| Normal
| Verbose
| Annoying
deriving
( Bounded, Enum, Eq, Ord, Read, Show
#ifdef DERIVE_GHC_GENERICS
, Generic
#endif
#ifdef DERIVE_DATA_TYPEABLE
, Data, Typeable
#endif
)
#ifdef DECLARE_DEFAULT_INSTANCE
instance Default Verbosity where
def = Normal
#endif
#ifdef DECLARE_BINARY_INSTANCE
instance Binary Verbosity where
get = toEnum . fromIntegral <$> getWord8
put = putWord8 . fromIntegral . fromEnum
#endif
#ifdef DECLARE_NFDATA_INSTANCE
instance NFData Verbosity where
rnf !_ = ()
#endif
fromInt :: Int -> Maybe Verbosity
fromInt n
| n >= minVerbosity && n <= maxVerbosity = Just (toEnum n)
| otherwise = Nothing
where
minVerbosity = fromEnum (minBound :: Verbosity)
maxVerbosity = fromEnum (maxBound :: Verbosity)
#ifdef DERIVE_DATA_TYPEABLE
parse :: (Eq string, IsString string) => string -> Maybe Verbosity
parse = (`lookup` [(str v, v) | v <- [minBound..maxBound :: Verbosity]])
where
str = fromString . showConstr . toConstr
#endif