Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
verbosity on showing.
Synopsis
- class Show a => Verbose a where
- data Verbosity
- vshowStr :: Maybe Int -> String -> String
- mnString :: Verbosity -> Maybe Int
- vshowList :: Verbose a => Verbosity -> Maybe Int -> String -> String -> [a] -> String
- mnList :: Verbosity -> Maybe Int
- newtype Percent x = Percent x
- showPercent :: Int -> Double -> String
Verbose
class Show a => Verbose a where Source #
shows a
in the context of verbosity.
Nothing
vshow :: Verbosity -> a -> String Source #
the default implementation is: vshow v a = vshowStr (
mnString
v) (show a)
Instances
Verbose Label Source # | |
Verbose Message Source # | |
Verbose Parameter Source # | |
Verbose V Source # | |
Verbose Integer Source # | |
Verbose () Source # | |
Verbose Char Source # | |
Verbose Double Source # | |
Verbose Int Source # | |
Verbose (Percent Double) Source # | |
Verbose a => Verbose [a] Source # | |
(Verbose a, Verbose b) => Verbose (a, b) Source # | |
(Verbose a, Verbose b, Verbose c) => Verbose (a, b, c) Source # | |
(Verbose a, Verbose b, Verbose c, Verbose d) => Verbose (a, b, c, d) Source # | |
(Verbose a, Verbose b, Verbose c, Verbose d, Verbose e) => Verbose (a, b, c, d, e) Source # | |
(Verbose a, Verbose b, Verbose c, Verbose d, Verbose e, Verbose f) => Verbose (a, b, c, d, e, f) Source # | |
kinds of verbosity.
Instances
Bounded Verbosity Source # | |
Enum Verbosity Source # | |
Defined in OAlg.Control.Verbose succ :: Verbosity -> Verbosity # pred :: Verbosity -> Verbosity # fromEnum :: Verbosity -> Int # enumFrom :: Verbosity -> [Verbosity] # enumFromThen :: Verbosity -> Verbosity -> [Verbosity] # enumFromTo :: Verbosity -> Verbosity -> [Verbosity] # enumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity] # | |
Show Verbosity Source # | |
Eq Verbosity Source # | |
Ord Verbosity Source # | |
Defined in OAlg.Control.Verbose |
vshowStr :: Maybe Int -> String -> String Source #
verbosely showing a string by the given length.
Example
>>>
vshowStr (Just 3) "123456789"
"123.."
>>>
vshowStr Nothing "123456789"
"123456789"
mnString :: Verbosity -> Maybe Int Source #
default length for a string representation in context of verbosity.
vshowList :: Verbose a => Verbosity -> Maybe Int -> String -> String -> [a] -> String Source #
verbosely showing a list by the given length.
Examples
>>>
vshowList Full (Just 3) "[" "]" "abcdef"
"['a','b','c'..]"
>>>
vshowList Low (Just 3) "{" "}" ["abcdef","ghijklmn","op","qrst","uvwxyz"]
"{['a','b'..],['g','h'..],['o','p']..}"
mnList :: Verbosity -> Maybe Int Source #
default number of entries for a list representation in context of verbosity.