| Copyright | (c) 2015-2019 Peter Trško |
|---|---|
| License | BSD3 |
| Maintainer | peter.trsko@gmail.com |
| Stability | experimental |
| Portability | GHC specific language extensions. |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Verbosity.Class
Contents
Description
Type class for accessing Verbosity.
Synopsis
- class HasVerbosity s where
- getVerbosity :: HasVerbosity s => s -> Verbosity
- setVerbosity :: HasVerbosity s => Verbosity -> s -> s
- modifyVerbosity :: HasVerbosity s => (Verbosity -> Verbosity) -> s -> s
- module Data.Verbosity
GHC Generics Example
Lets define simple data type that looks something like:
data Config = Config
{ _appVerbosity :: Verbosity
, ...
}
deriving (Generic, Show, ...)
Type class HasVerbosity uses
generic-lens package and
DefaultSignatures language extension so that we can define instance of
HasVerbosity by simply stating:
instance HasVerbosity Config
With DerivingStrategies we can rewrite the above example as:
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
import GHC.Generics (Generic)
data Config = Config
{ _appVerbosity :: Verbosity
, ...
}
deriving stock (Generic, Show, ...)
deriving anyclass (HasVerbosity)
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:
instanceHasVerbosityConfig 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:
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens.TH (makeLenses)
data Config = Config
{ _appVerbosity :: Verbosity
, ...
}
deriving (Show, ...)
makeLenses ''Config
Now definition of HasVerbosity instance will look like:
instanceHasVerbosityConfig whereverbosity= appVerbosity -- Lens generated by makeLenses.
HasVerbosity Type Class
class HasVerbosity s where Source #
Minimal complete definition
Nothing
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.
modifyVerbosity :: HasVerbosity s => (Verbosity -> Verbosity) -> s -> s Source #
Specialization of verbosity lens in to modification function.
Verbosity Re-export
module Data.Verbosity