verbosity-0.2.0.0: Simple enum that encodes application verbosity.

Copyright(c) 2015, Peter Trško
LicenseBSD3
Maintainerpeter.trsko@gmail.com
Stabilityexperimental
PortabilityNoImplicitPrelude
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Verbosity.Class

Contents

Description

Type class for accessing Verbosity.

Synopsis

Hand Written Instance Example

Lets define simple data type that looks something like:

data Config = Config
    { _appVerbosity :: Verbosity
    , ...
    }
  deriving (Show, ...)

Now we can define instance of HasVerbosity by hand:

instance HasVerbosity Config where
    verbosity f c@Config{_appVerbosity = a} =
        (b -> c{_appVerbosity = b}) <$> f a

TemplateHaskell Example

Package lens has TemplateHaskell functions that can define lenses for you:

import Control.Lens.TH (makeLenses)

data Config = Config
    { _appVerbosity :: Verbosity
    , ...
    }
  deriving (Show, ...)

makeLenses ''Config

Don't forget to to turn on TemplateHaskell by putting following pragma at the beginning of your module:

{-# LANGUAGE TemplateHaskell #-}

Now definition of HasVerbosity instance will look like:

instance HasVerbosity Config where
    verbosity = appVerbosity

HasVerbosity Type Class

class HasVerbosity s where Source

Methods

verbosity :: Functor f => (Verbosity -> f Verbosity) -> s -> f s Source

Lens for accessing Verbosity.

getVerbosity :: HasVerbosity s => s -> Verbosity Source

Specialization of verbosity lens in to getter function.

setVerbosity :: HasVerbosity s => Verbosity -> s -> s Source

Specialization of verbosity lens in to setter function.

Verbosity Re-export