Copyright | Ian Lynagh 2007 |
---|---|
License | BSD3 |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- data Verbosity
- silent :: Verbosity
- normal :: Verbosity
- verbose :: Verbosity
- deafening :: Verbosity
- moreVerbose :: Verbosity -> Verbosity
- lessVerbose :: Verbosity -> Verbosity
- isVerboseQuiet :: Verbosity -> Bool
- intToVerbosity :: Int -> Maybe Verbosity
- flagToVerbosity :: ReadE Verbosity
- showForCabal :: Verbosity -> String
- showForGHC :: Verbosity -> String
- verboseNoFlags :: Verbosity -> Verbosity
- verboseHasFlags :: Verbosity -> Bool
- modifyVerbosity :: (Verbosity -> Verbosity) -> Verbosity -> Verbosity
- verboseCallSite :: Verbosity -> Verbosity
- verboseCallStack :: Verbosity -> Verbosity
- isVerboseCallSite :: Verbosity -> Bool
- isVerboseCallStack :: Verbosity -> Bool
- verboseMarkOutput :: Verbosity -> Verbosity
- isVerboseMarkOutput :: Verbosity -> Bool
- verboseUnmarkOutput :: Verbosity -> Verbosity
- verboseNoWrap :: Verbosity -> Verbosity
- isVerboseNoWrap :: Verbosity -> Bool
- verboseTimestamp :: Verbosity -> Verbosity
- isVerboseTimestamp :: Verbosity -> Bool
- verboseNoTimestamp :: Verbosity -> Verbosity
- verboseStderr :: Verbosity -> Verbosity
- isVerboseStderr :: Verbosity -> Bool
- verboseNoStderr :: Verbosity -> Verbosity
- verboseNoWarn :: Verbosity -> Verbosity
- isVerboseNoWarn :: Verbosity -> Bool
Verbosity
Instances
Parsec Verbosity Source # | Parser verbosity
Note: this parser will eat trailing spaces. |
Defined in Distribution.Verbosity parsec :: CabalParsing m => m Verbosity Source # | |
Pretty Verbosity Source # | |
Defined in Distribution.Verbosity | |
Structured Verbosity Source # | |
Defined in Distribution.Verbosity | |
Bounded Verbosity Source # | |
Enum Verbosity Source # | |
Defined in Distribution.Verbosity succ :: Verbosity -> Verbosity Source # pred :: Verbosity -> Verbosity Source # toEnum :: Int -> Verbosity Source # fromEnum :: Verbosity -> Int Source # enumFrom :: Verbosity -> [Verbosity] Source # enumFromThen :: Verbosity -> Verbosity -> [Verbosity] Source # enumFromTo :: Verbosity -> Verbosity -> [Verbosity] Source # enumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity] Source # | |
Generic Verbosity Source # | |
Read Verbosity Source # | |
Show Verbosity Source # | |
Binary Verbosity Source # | |
Eq Verbosity Source # | |
Ord Verbosity Source # | |
Defined in Distribution.Verbosity | |
type Rep Verbosity Source # | |
Defined in Distribution.Verbosity type Rep Verbosity = D1 ('MetaData "Verbosity" "Distribution.Verbosity" "Cabal-3.10.1.0" '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)))) |
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.
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.
showForCabal :: Verbosity -> String Source #
showForGHC :: Verbosity -> String Source #
verboseNoFlags :: Verbosity -> Verbosity Source #
Turn off all flags.
verboseHasFlags :: Verbosity -> Bool Source #
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: Cabal-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: Cabal-3.4.0.0
isVerboseStderr :: Verbosity -> Bool Source #
Test if we should output to stderr
when we log.
Since: Cabal-3.4.0.0
verboseNoStderr :: Verbosity -> Verbosity Source #
Switch logging to stdout
.
Since: Cabal-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.