Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
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).
formatn is used in the chart-svg library to automate consistent number formatting across different scales.
Synopsis
- data SigFig = SigFig {
- sfSign :: SigFigSign
- sfFigures :: Integer
- sfExponent :: Int
- data SigFigSign
- toSigFig :: Maybe Int -> Double -> SigFig
- fromSigFig :: SigFig -> Double
- isZero :: SigFig -> Bool
- incSigFig :: Int -> SigFig -> SigFig
- decSigFig :: Int -> SigFig -> Maybe SigFig
- data FormatStyle
- precStyle :: Double -> FormatStyle
- commaPrecStyle :: Double -> FormatStyle
- data FStyle
- fixedSF :: Maybe Int -> SigFig -> Text
- exptSF :: SigFig -> Text
- exptSFWith :: Maybe Int -> SigFig -> Text
- decimalSF :: SigFig -> Text
- commaSF :: SigFig -> Text
- dollarSF :: (SigFig -> Text) -> SigFig -> Text
- percentSF :: (SigFig -> Text) -> SigFig -> Text
- formatSF :: FormatStyle -> SigFig -> Text
- format :: FormatStyle -> Maybe Int -> Double -> Text
- formatOrShow :: FormatStyle -> Maybe Int -> Double -> Text
- fixed :: Maybe Int -> Double -> Text
- expt :: Maybe Int -> Double -> Text
- exptWith :: Maybe Int -> Maybe Int -> Double -> Text
- decimal :: Maybe Int -> Double -> Text
- prec :: Maybe Int -> Double -> Text
- comma :: Maybe Int -> Double -> Text
- commaPrec :: Maybe Int -> Double -> Text
- dollar :: (SigFig -> Text) -> Maybe Int -> Double -> Text
- percent :: (SigFig -> Text) -> Maybe Int -> Double -> Text
- majorityStyle :: (Double -> FormatStyle) -> [Double] -> FormatStyle
- formats :: Bool -> Bool -> (Double -> FormatStyle) -> Maybe Int -> [Double] -> [Text]
- formatsSF :: Maybe Int -> [Double] -> [SigFig]
- decSigFigs :: [SigFig] -> [SigFig]
- lpads :: [Text] -> [Text]
- distinguish :: Int -> Bool -> Bool -> (Double -> FormatStyle) -> Maybe Int -> [Double] -> [Text]
- data FormatN = FormatN {}
- defaultFormatN :: FormatN
- formatN :: FormatN -> Double -> Text
- formatNs :: 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"]>>>
decimal (Just 3) . (1e-3*) <$> xs
["-0.00100","0.00","0.00100","0.00101","0.00102","0.00110","0.00120"]>>>
comma (Just 3) . (1e3*) <$> xs
["-1,000","0.00","1,000","1,010","1,020","1,100","1,200"]
formats
is useful when you want a consistent textual style across a list of numbers:
>>>
formats True False (const DecimalStyle) (Just 2) $ (1e-3*) <$> xs
["-0.0010"," 0.0000"," 0.0010"," 0.0010"," 0.0010"," 0.0011"," 0.0012"]
Using significant figures actually changes numbers - numbers that were slightly different end up being (and looking like) the same. distinguish
increases the number of significant figures to compensate for this effect.
>>>
distinguish 4 True False (const DecimalStyle) (Just 2) xs
["-1.00"," 0.00"," 1.00"," 1.01"," 1.02"," 1.10"," 1.20"]
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} \]
SigFig | |
|
data SigFigSign Source #
Sign component
Instances
Show SigFigSign Source # | |
Defined in Data.FormatN showsPrec :: Int -> SigFigSign -> ShowS # show :: SigFigSign -> String # showList :: [SigFigSign] -> ShowS # | |
Eq SigFigSign Source # | |
Defined in Data.FormatN (==) :: SigFigSign -> SigFigSign -> Bool # (/=) :: SigFigSign -> SigFigSign -> Bool # |
toSigFig :: Maybe Int -> Double -> SigFig Source #
convert from a Double to a SigFig
>>>
toSigFig (Just 2) 1234
SigFig {sfSign = SigFigPos, sfFigures = 12, sfExponent = 2}
toSigFig Nothing . fromSigFig <==> id toSigFig (Just x) . fromSigFig . toSigFig (Just x) <==> toSigFig (Just x)
\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)
Checks for a valid number of significant figures and turns it off on a silly number.
>>>
toSigFig Nothing 1234
SigFig {sfSign = SigFigPos, sfFigures = 1234, sfExponent = 0}
>>>
toSigFig (Just (-3)) 1234
SigFig {sfSign = SigFigPos, sfFigures = 1234, sfExponent = 0}
fromSigFig :: SigFig -> Double Source #
convert from a SigFig
to a Double
>>>
fromSigFig (SigFig SigFigPos 12 2)
1200.0
isZero :: SigFig -> Bool Source #
Note that zero can still be represented in a SigFig way, so that we can distinguish between something that starts off as zero, and something that ends up as zero via rounding.
>>>
isZero (SigFig SigFigPos 0 (-3))
True
incSigFig :: Int -> SigFig -> SigFig Source #
increase significant figures
>>>
incSigFig 1 (SigFig SigFigPos 1 0)
SigFig {sfSign = SigFigPos, sfFigures = 10, sfExponent = -1}
decSigFig :: Int -> SigFig -> Maybe SigFig Source #
decrease significant figures, if possible.
>>>
decSigFig 1 (SigFig SigFigPos 100 0)
Just (SigFig {sfSign = SigFigPos, sfFigures = 10, sfExponent = 1})
>>>
decSigFig 1 (SigFig SigFigPos 123 0)
Nothing
Format Styles
data FormatStyle Source #
Data type representing styles of formatting
DecimalStyle | 1000 1 0.001 |
ExponentStyle (Maybe Int) | 1e3 1e0 1e-3 |
CommaStyle | 1,000 1 0.001 |
FixedStyle Int |
|
PercentStyle | 100,000% 100% 0.1% |
DollarStyle | $1,000 $1 $0.001 |
Instances
Show FormatStyle Source # | |
Defined in Data.FormatN showsPrec :: Int -> FormatStyle -> ShowS # show :: FormatStyle -> String # showList :: [FormatStyle] -> ShowS # | |
Eq FormatStyle Source # | |
Defined in Data.FormatN (==) :: FormatStyle -> FormatStyle -> Bool # (/=) :: FormatStyle -> FormatStyle -> Bool # | |
Ord FormatStyle Source # | |
Defined in Data.FormatN compare :: FormatStyle -> FormatStyle -> Ordering # (<) :: FormatStyle -> FormatStyle -> Bool # (<=) :: FormatStyle -> FormatStyle -> Bool # (>) :: FormatStyle -> FormatStyle -> Bool # (>=) :: FormatStyle -> FormatStyle -> Bool # max :: FormatStyle -> FormatStyle -> FormatStyle # min :: FormatStyle -> FormatStyle -> FormatStyle # |
precStyle :: Double -> FormatStyle Source #
DecimalStyle between 0.001 and a million and ExponentStyle outside this range.
commaPrecStyle :: Double -> FormatStyle Source #
CommaStyle above a thousand but below a million, DecimalStyle between 0.001 and a thousand and ExponentStyle outside this range.
Data type representing styles of formatting dependent on the number
SigFig formatters
exptSFWith :: Maybe Int -> SigFig -> Text Source #
expt format for a SigFig, with an exponent override
>>>
exptSFWith (Just 1) (toSigFig (Just 1) 1)
"0.1e1">>>
exptSFWith (Just 0) (toSigFig (Just 1) 1)
"1e0">>>
exptSFWith (Just (-1)) (toSigFig (Just 1) 1)
"10e-1"
formatSF :: FormatStyle -> SigFig -> Text Source #
format a SigFig according to a style
>>>
formatSF CommaStyle (toSigFig (Just 2) 1234)
"1,200">>>
formatSF CommaStyle (SigFig SigFigPos 0 1)
"0">>>
formatSF CommaStyle (SigFig SigFigPos 0 (-1))
"0.0"
Double formatters
format :: FormatStyle -> Maybe Int -> Double -> Text Source #
format a number according to a FormatStyle and significant figures
>>>
format CommaStyle (Just 2) 1234
"1,200"
formatOrShow :: FormatStyle -> Maybe Int -> Double -> Text Source #
Format with the shorter of show and a style.
>>>
format (ExponentStyle Nothing) Nothing 0
"0e0">>>
formatOrShow (ExponentStyle Nothing) Nothing 0
"0"
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">>>
expt (Just 2) 0
"0.0e0"
exptWith :: Maybe Int -> Maybe Int -> Double -> Text Source #
Format in exponential style, with the suggested exponent.
>>>
exptWith (Just 2) Nothing 1245
"12.45e2">>>
exptWith (Just 6) (Just 3) 1245
"0.00124e6"
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 1000000 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 with US-style commas
>>>
comma (Just 3) 1234567
"1,230,000"
commaPrec :: Maybe Int -> Double -> Text Source #
Format using comma separators for numbers above 1,000 but below 1 million, otherwise use prec style.
>>>
commaPrec (Just 3) 1234
"1,230">>>
commaPrec (Just 3) 1234567
"1.23e6"
dollar :: (SigFig -> Text) -> Maybe Int -> Double -> Text Source #
Adjust format to dollar style.
>>>
dollar commaSF (Just 3) 1234
"$1,230">>>
dollar (fixedSF (Just 2)) (Just 2) 0.01234
"$0.01"
percent :: (SigFig -> Text) -> Maybe Int -> Double -> Text Source #
Adjust format to a percent.
>>>
percent commaSF (Just 3) 0.1234
"12.3%">>>
percent decimalSF (Just 1) 0.1234
"10%"
List Modifiers
majorityStyle :: (Double -> FormatStyle) -> [Double] -> FormatStyle Source #
Compute the majority (modal) FormatStyle so a list of numbers can all have the same formatting
Also equalises the exponent to the majority for exponent style.
>>>
commaPrecStyle <$> [0,5e6,1e7,2e7]
[CommaStyle,ExponentStyle (Just 6),ExponentStyle (Just 7),ExponentStyle (Just 7)]>>>
majorityStyle commaPrecStyle [0,5e6,1e7,2e7]
ExponentStyle (Just 7)
:: Bool | left pad to the largest text length |
-> Bool | Try and reduce excess right-hand zeros |
-> (Double -> FormatStyle) | style |
-> Maybe Int | significant figures requested |
-> [Double] | list of numbers |
-> [Text] |
Consistently format a list of numbers,using the minimum number of decimal places or minimum exponent.
>>>
formats True True precStyle (Just 1) [0,0.5,1,2]
["0.0","0.5","1.0","2.0"]
Note how the presence of 0.5 in the example above changes the format of all numbers. Without it:
>>>
formats True True precStyle (Just 1) [0,1,2]
["0","1","2"]
>>>
formats False True precStyle (Just 1) $ ((-1)*) <$> [0,0.5,1,2]
["0.0","-0.5","-1.0","-2.0"]>>>
formats True True commaPrecStyle (Just 1) $ ((-1000)*) <$> [0,0.5,1,2]
[" 0"," -500","-1,000","-2,000"]>>>
formats True True commaPrecStyle (Just 1) $ ((1e6)*) <$> [0,0.5,1,2]
[" 0"," 500,000","1,000,000","2,000,000"]>>>
formats True True commaPrecStyle (Just 1) $ ((1e6)*) <$> [0.9,2,3]
["0.9e6","2.0e6","3.0e6"]>>>
formats True True commaPrecStyle (Just 1) $ ((1e-6)*) <$> [0,0.5,1,2]
["0.0e-6","0.5e-6","1.0e-6","2.0e-6"]>>>
formats True True commaPrecStyle (Just 1) $ ((1e-3)*) <$> [0,0.5,1,2]
["0.0000","0.0005","0.0010","0.0020"]>>>
formats True False (const (ExponentStyle Nothing)) (Just 2) [0..4]
["0.0e0","1.0e0","2.0e0","3.0e0","4.0e0"]>>>
formats True True (const (ExponentStyle Nothing)) (Just 2) [0..4]
["0e0","1e0","2e0","3e0","4e0"]
Consistently convert a list of numbers to SigFig
s, using the minimum natural exponent of the list.
decSigFigs :: [SigFig] -> [SigFig] Source #
Decrease the SigFig figure of a list of SigFigs without loss of precision, if possible. This has the effect of removing right zeros in decimal representations.
lpads :: [Text] -> [Text] Source #
Add spaces to the left of a text representation so that all elements have the same length.
:: Int | maximum number of iterations |
-> Bool | left pad to the largest text length |
-> Bool | try and reduce excess right zero pads |
-> (Double -> FormatStyle) | style |
-> Maybe Int | significant figures requested |
-> [Double] | list of numbers |
-> [Text] |
Provide formatted text for a list of numbers so that they are just distinguished.
For example, distinguish 4 commaPrecStyle (Just 2)
means use as much significant figures as is needed for the numbers to be distinguished on rendering (up to 4+2=6), but with at least 2 significant figures.
The difference between this and formats
can be seen in these examples:
>>>
formats True True commaPrecStyle (Just 2) [0,1,1.01,1.02,1.1,1.2]
["0.0","1.0","1.0","1.0","1.1","1.2"]>>>
distinguish 4 True True commaPrecStyle (Just 2) [0,1,1.01,1.02,1.1,1.2]
["0.00","1.00","1.01","1.02","1.10","1.20"]
A common occurence is that significant figures being increased to enable textual uniqueness results in excess right zeros (after a decimal place). Consider:
>>>
formats True False commaPrecStyle (Just 1) [0, 0.5, 1, 1.5, 2]
["0.0","0.5","1.0","2.0","2.0"]
Note that formats seeks With 1.5 rounding up to 2, the distinguish algorithm will increase the number of sigfigs to 2:
>>>
distinguish 4 True False commaPrecStyle (Just 1) [0, 0.5, 1, 1.5, 2]
["0.00","0.50","1.00","1.50","2.00"]
The format can be simplified further by removing the excess right zeros from each formatted number:
>>>
distinguish 4 True True commaPrecStyle (Just 2) [0, 0.5, 1, 1.5, 2]
["0.0","0.5","1.0","1.5","2.0"]
FormatN
Wrapper for the various formatting options.
>>>
defaultFormatN
FormatN {fstyle = FSCommaPrec, sigFigs = Just 2, maxDistinguishIterations = 4, addLPad = True, cutRightZeros = True}
Instances
Generic FormatN Source # | |
Show FormatN Source # | |
Eq FormatN Source # | |
type Rep FormatN Source # | |
Defined in Data.FormatN type Rep FormatN = D1 ('MetaData "FormatN" "Data.FormatN" "formatn-0.3.0.1-LVR3e3Pxxa85EhLYKcOmHS" 'False) (C1 ('MetaCons "FormatN" 'PrefixI 'True) ((S1 ('MetaSel ('Just "fstyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FStyle) :*: S1 ('MetaSel ('Just "sigFigs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "maxDistinguishIterations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "addLPad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "cutRightZeros") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))) |
defaultFormatN :: FormatN Source #
The official FormatN