Copyright | (c) 2015, Peter Trško |
---|---|
License | BSD3 |
Maintainer | peter.trsko@gmail.com |
Stability | experimental |
Portability | NoImplicitPrelude |
Safe Haskell | Safe |
Language | Haskell2010 |
Type class for accessing Verbosity
.
- class HasVerbosity s where
- getVerbosity :: HasVerbosity s => s -> Verbosity
- setVerbosity :: HasVerbosity s => Verbosity -> s -> s
- module Data.Verbosity
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:
instanceHasVerbosity
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 #
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
module Data.Verbosity