Cabal-3.10.1.0: A framework for packaging Haskell software
CopyrightIan Lynagh 2007
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Verbosity

Description

A Verbosity type with associated utilities.

There are 4 standard verbosity levels from silent, normal, verbose up to deafening. This is used for deciding what logging messages to print.

Verbosity also is equipped with some internal settings which can be used to control at a fine granularity the verbosity of specific settings (e.g., so that you can trace only particular things you are interested in.) It's important to note that the instances for Verbosity assume that this does not exist.

Synopsis

Verbosity

data Verbosity Source #

Instances

Instances details
Parsec Verbosity Source #

Parser verbosity

>>> explicitEitherParsec parsecVerbosity "normal"
Right (Verbosity {vLevel = Normal, vFlags = fromList [], vQuiet = False})
>>> explicitEitherParsec parsecVerbosity "normal+nowrap  "
Right (Verbosity {vLevel = Normal, vFlags = fromList [VNoWrap], vQuiet = False})
>>> explicitEitherParsec parsecVerbosity "normal+nowrap +markoutput"
Right (Verbosity {vLevel = Normal, vFlags = fromList [VNoWrap,VMarkOutput], vQuiet = False})
>>> explicitEitherParsec parsecVerbosity "normal +nowrap +markoutput"
Right (Verbosity {vLevel = Normal, vFlags = fromList [VNoWrap,VMarkOutput], vQuiet = False})
>>> explicitEitherParsec parsecVerbosity "normal+nowrap+markoutput"
Right (Verbosity {vLevel = Normal, vFlags = fromList [VNoWrap,VMarkOutput], vQuiet = False})
>>> explicitEitherParsec parsecVerbosity "deafening+nowrap+stdout+stderr+callsite+callstack"
Right (Verbosity {vLevel = Deafening, vFlags = fromList [VCallStack,VCallSite,VNoWrap,VStderr], vQuiet = False})

Note: this parser will eat trailing spaces.

Instance details

Defined in Distribution.Verbosity

Methods

parsec :: CabalParsing m => m Verbosity #

Pretty Verbosity Source # 
Instance details

Defined in Distribution.Verbosity

Structured Verbosity Source # 
Instance details

Defined in Distribution.Verbosity

Bounded Verbosity Source # 
Instance details

Defined in Distribution.Verbosity

Enum Verbosity Source # 
Instance details

Defined in Distribution.Verbosity

Generic Verbosity Source # 
Instance details

Defined in Distribution.Verbosity

Associated Types

type Rep Verbosity :: Type -> Type #

Read Verbosity Source # 
Instance details

Defined in Distribution.Verbosity

Show Verbosity Source # 
Instance details

Defined in Distribution.Verbosity

Binary Verbosity Source # 
Instance details

Defined in Distribution.Verbosity

Eq Verbosity Source # 
Instance details

Defined in Distribution.Verbosity

Ord Verbosity Source # 
Instance details

Defined in Distribution.Verbosity

type Rep Verbosity Source # 
Instance details

Defined in Distribution.Verbosity

type Rep Verbosity = D1 ('MetaData "Verbosity" "Distribution.Verbosity" "Cabal-3.10.1.0-BylF3CAYviR5JFHXbqfu7l" 'False) (C1 ('MetaCons "Verbosity" 'PrefixI 'True) (S1 ('MetaSel ('Just "vLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VerbosityLevel) :*: (S1 ('MetaSel ('Just "vFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set VerbosityFlag)) :*: S1 ('MetaSel ('Just "vQuiet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

silent :: Verbosity Source #

In silent mode, we should not print anything unless an error occurs.

normal :: Verbosity Source #

Print stuff we want to see by default.

verbose :: Verbosity Source #

Be more verbose about what's going on.

deafening :: Verbosity Source #

Not only are we verbose ourselves (perhaps even noisier than when being verbose), but we tell everything we run to be verbose too.

moreVerbose :: Verbosity -> Verbosity Source #

Increase verbosity level, but stay silent if we are.

lessVerbose :: Verbosity -> Verbosity Source #

Decrease verbosity level, but stay deafening if we are.

isVerboseQuiet :: Verbosity -> Bool Source #

Test if we had called lessVerbose on the verbosity.

intToVerbosity :: Int -> Maybe Verbosity Source #

Numeric verbosity level 0..3: 0 is silent, 3 is deafening.

verboseNoFlags :: Verbosity -> Verbosity Source #

Turn off all flags.

modifyVerbosity :: (Verbosity -> Verbosity) -> Verbosity -> Verbosity Source #

Combinator for transforming verbosity level while retaining the original hidden state.

For instance, the following property holds

isVerboseNoWrap (modifyVerbosity (max verbose) v) == isVerboseNoWrap v

Note: you can use modifyVerbosity (const v1) v0 to overwrite v1's flags with v0's flags.

Since: 2.0.1.0

Call stacks

verboseCallSite :: Verbosity -> Verbosity Source #

Turn on verbose call-site printing when we log.

verboseCallStack :: Verbosity -> Verbosity Source #

Turn on verbose call-stack printing when we log.

isVerboseCallSite :: Verbosity -> Bool Source #

Test if we should output call sites when we log.

isVerboseCallStack :: Verbosity -> Bool Source #

Test if we should output call stacks when we log.

Output markets

verboseMarkOutput :: Verbosity -> Verbosity Source #

Turn on -----BEGIN CABAL OUTPUT----- markers for output from Cabal (as opposed to GHC, or system dependent).

isVerboseMarkOutput :: Verbosity -> Bool Source #

Test if we should output markets.

verboseUnmarkOutput :: Verbosity -> Verbosity Source #

Turn off marking; useful for suppressing nondeterministic output.

Line wrapping

verboseNoWrap :: Verbosity -> Verbosity Source #

Disable line-wrapping for log messages.

isVerboseNoWrap :: Verbosity -> Bool Source #

Test if line-wrapping is disabled for log messages.

Time stamps

verboseTimestamp :: Verbosity -> Verbosity Source #

Turn on timestamps for log messages.

isVerboseTimestamp :: Verbosity -> Bool Source #

Test if we should output timestamps when we log.

verboseNoTimestamp :: Verbosity -> Verbosity Source #

Turn off timestamps for log messages.

Stderr

verboseStderr :: Verbosity -> Verbosity Source #

Switch logging to stderr.

Since: 3.4.0.0

isVerboseStderr :: Verbosity -> Bool Source #

Test if we should output to stderr when we log.

Since: 3.4.0.0

verboseNoStderr :: Verbosity -> Verbosity Source #

Switch logging to stdout.

Since: 3.4.0.0

No warnings

verboseNoWarn :: Verbosity -> Verbosity Source #

Turn off warnings for log messages.

isVerboseNoWarn :: Verbosity -> Bool Source #

Test if we should output warnings when we log.