Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Text formatting of Double
s.
In particular, the library provides functionality to calculate and display a fixed number of significant figures for a variety of different number formatting styles.
Some similar libraries that may be better suited for different use cases include:
Flexible formatters. These libraries provide more flexibility around formatting options, but do not have a concept of significance:
text-format has similar functionality but is not native haskell and I wanted to do some tweaking to defaults. It's probably safer and faster.
rounded seems to be much more about doing computation taking rounding into account, compared with the much simpler task of pretty printing a number.
This library could have just provided an ability to compute a significant figure version of a number and then use these other libraries, but the round trip (from Double to SigFig to Double) introduces errors (eg the least significant figure goes from being a '4' to a '3999999' via float maths).
Synopsis
- data FormatN
- = FormatFixed (Maybe Int)
- | FormatDecimal (Maybe Int)
- | FormatComma (Maybe Int)
- | FormatExpt (Maybe Int)
- | FormatPrec (Maybe Int)
- | FormatDollar (Maybe Int)
- | FormatPercent (Maybe Int)
- | FormatNone
- defaultFormatN :: FormatN
- formatN :: FormatN -> Double -> Text
- formatNs :: FormatN -> [Double] -> [Text]
- precision :: (Maybe Int -> Double -> Text) -> Maybe Int -> [Double] -> [Text]
- data SigFig = SigFig {}
- data SigFigSign
- toSigFig :: Maybe Int -> Double -> SigFig
- fromSigFig :: SigFig -> Double
- fixed :: Maybe Int -> Double -> Text
- expt :: Maybe Int -> Double -> Text
- decimal :: Maybe Int -> Double -> Text
- prec :: Maybe Int -> Double -> Text
- comma :: Maybe Int -> Double -> Text
- dollar :: Maybe Int -> Double -> Text
- percent :: Maybe Int -> Double -> Text
- showOr :: FormatN -> Double -> Text
Usage
>>>
import Data.FormatN
>>>
xs = [(-1),0,1,1.01,1.02,1.1,1.2]
>>>
fixed (Just 2) <$> xs
["-1.00","0.00","1.00","1.01","1.02","1.10","1.20"]
>>>
decimal (Just 2) <$> xs
["-1.0","0.0","1.0","1.0","1.0","1.1","1.2"]
formatn is used in the chart-svg library to automate consistent number formatting across different scales.
>>>
comma (Just 3) <$> xs
["-1.00","0.00","1.00","1.01","1.02","1.10","1.20"]
>>>
comma (Just 3) . (1e3*) <$> xs
["-1,000","0.00","1,000","1,010","1,020","1,100","1,200"]
>>>
comma (Just 3) . (1e-3*) <$> xs
["-0.00100","0.00","0.00100","0.00101","0.00102","0.00110","0.00120"]
>>>
comma (Just 3) . (1e-6*) <$> xs
["-1.00e-6","0.00","1.00e-6","1.01e-6","1.02e-6","1.10e-6","1.20e-6"]
Using significant figures actually changes numbers - numbers that were slightly different end up being (and looking like) the same. precision
increases the number of significant figures to get around this.
>>>
comma (Just 2) . (1e3*) <$> xs
["-1,000","0.0","1,000","1,000","1,000","1,100","1,200"]
>>>
precision comma (Just 2) $ (1e3*) <$> [0,1,1.01,1.02,1.1,1.2]
["0.00","1,000","1,010","1,020","1,100","1,200"]
Also note the clunkiness of the treatment of zero. It is problematic to default format zero consistently.
FormatN
Wrapper for the various formatting options.
Nothing in the context of these constructors means do not perform and significant figure adjustments to the numbers (or decimal figures with respect to FormatFixed).
FormatFixed (Maybe Int) | |
FormatDecimal (Maybe Int) | |
FormatComma (Maybe Int) | |
FormatExpt (Maybe Int) | |
FormatPrec (Maybe Int) | |
FormatDollar (Maybe Int) | |
FormatPercent (Maybe Int) | |
FormatNone |
Instances
defaultFormatN :: FormatN Source #
The official format
>>>
defaultFormatN
FormatComma (Just 2)
formatNs :: FormatN -> [Double] -> [Text] Source #
Consistently format a list of numbers via using precision
.
>>>
formatNs defaultFormatN [0,1,1.01,1.02,1.1,1.2]
["0.00","1.00","1.01","1.02","1.10","1.20"]
precision :: (Maybe Int -> Double -> Text) -> Maybe Int -> [Double] -> [Text] Source #
Provide formatted text for a list of numbers so that they are just distinguished.
For example, precision comma (Just 2)
means use as much significant figures as is needed for the numbers to be distinguished on rendering, but with at least 2 significant figures.
The difference between this and fmap (comma (Just 2))
can be seen in these examples:
>>>
precision comma (Just 2) [0,1,1.01,1.02,1.1,1.2]
["0.00","1.00","1.01","1.02","1.10","1.20"]
>>>
fmap (comma (Just 2)) [0,1,1.01,1.02,1.1,1.2]
["0.0","1.0","1.0","1.0","1.1","1.2"]
SigFig
Decomposition of a Double into the components that are needed to determine significant figure formatting.
eliding type changes, the relationship between a Double and a SigFig is:
\[ x == sign * figures * 10^{exponent} \]
data SigFigSign Source #
Sign component
Instances
Eq SigFigSign Source # | |
Defined in Data.FormatN (==) :: SigFigSign -> SigFigSign -> Bool # (/=) :: SigFigSign -> SigFigSign -> Bool # | |
Show SigFigSign Source # | |
Defined in Data.FormatN showsPrec :: Int -> SigFigSign -> ShowS # show :: SigFigSign -> String # showList :: [SigFigSign] -> ShowS # |
toSigFig :: Maybe Int -> Double -> SigFig Source #
convert from a Double to a SigFig
>>>
toSigFig (Just 2) 1234
SigFig {sign = SigFigPos, figures = 12, exponent = 2}
\x -> let (SigFig s fs e) = toSigFig Nothing x in let x' = ((if (s==SigFigNeg) then (-1.0) else 1.0) * fromIntegral fs * 10.0**fromIntegral e) in (x==0 || abs (x/x'-1) < 1e-6)
fromSigFig :: SigFig -> Double Source #
convert from a SigFig
to a Double
>>>
fromSigFig (SigFig SigFigPos 12 2)
1200.0
fromSigFig . toSigFig Nothing
may not be isomorphic
formatters
fixed :: Maybe Int -> Double -> Text Source #
Format to x decimal places with no significant figure rounding.
>>>
fixed (Just 2) 100
"100.00"
>>>
fixed (Just 2) 0.001
"0.00"
expt :: Maybe Int -> Double -> Text Source #
Format in exponential style, maybe with significant figure rounding.
>>>
expt Nothing 1245
"1.245e3"
>>>
expt (Just 3) 1245
"1.24e3"
>>>
expt (Just 3) 0.1245
"1.24e-1"
decimal :: Maybe Int -> Double -> Text Source #
Format in decimal style, and maybe round to n significant figures.
>>>
decimal Nothing 1.2345e-2
"0.012345"
>>>
decimal (Just 2) 0.012345
"0.012"
>>>
decimal (Just 2) 12345
"12000"
prec :: Maybe Int -> Double -> Text Source #
Format between 0.001 and 1,000,000 using decimal style and exponential style outside this range.
>>>
prec (Just 2) 0.00234
"0.0023"
>>>
prec (Just 2) 0.000023
"2.3e-5"
>>>
prec (Just 2) 123
"120"
>>>
prec (Just 2) 123456
"120000"
>>>
prec (Just 2) 1234567
"1.2e6"
comma :: Maybe Int -> Double -> Text Source #
Format using comma separators for numbers above 1,000 but below 1 million, otherwise use prec style.
>>>
comma (Just 3) 1234
"1,230"
dollar :: Maybe Int -> Double -> Text Source #
Format as dollars, always using comma notation
>>>
dollar (Just 3) 1234
"$1,230"
>>>
dollar (Just 2) 0.01234
"$0.012"