formatn-0.2.0: Formatting of doubles.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.FormatN

Description

Text formatting of Doubles.

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

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"]

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 get around this.

>>> formats False (const CommaStyle) (Just 2) $ (1e3*) <$> xs
["-1,000","0","1,000","1,000","1,000","1,100","1,200"]
>>> distinguish 4 False (const CommaStyle) (Just 2) $ (1e3*) <$> xs
["-1,000","0","1,000","1,010","1,020","1,100","1,200"]

SigFig

data SigFig Source #

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} \]

Constructors

SigFig 

Fields

Instances

Instances details
Eq SigFig Source # 
Instance details

Defined in Data.FormatN

Methods

(==) :: SigFig -> SigFig -> Bool #

(/=) :: SigFig -> SigFig -> Bool #

Show SigFig Source # 
Instance details

Defined in Data.FormatN

data SigFigSign Source #

Sign component

Constructors

SigFigNeg 
SigFigPos 

Instances

Instances details
Eq SigFigSign Source # 
Instance details

Defined in Data.FormatN

Show SigFigSign Source # 
Instance details

Defined in Data.FormatN

toSigFig :: Maybe Int -> Double -> SigFig Source #

convert from a Double to a SigFig

>>> toSigFig (Just 2) 1234
SigFig {sfSign = SigFigPos, sfFigures = 12, sfExponent = 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

incSigFig :: Int -> SigFig -> SigFig Source #

increase significant figures

specific formatters

data FormatStyle Source #

Data type representing styles of formatting

Constructors

DecimalStyle

1000 1 0.001

ExponentStyle (Maybe Int)

The parameter represents the exponent to format to with Nothing meaning:

1e3 1e1 1e-3

CommaStyle

1,000 1 0.001

FixedStyle Int
  1. 00 1.00 0.00
PercentStyle

100,000% 100% 0.1%

DollarStyle

$1,000 $1 $0.001

precStyle :: Double -> FormatStyle Source #

DecimalStyle between 0.001 and 1000000 and ExponentStyle outside this range.

commaPrecStyle :: Double -> FormatStyle Source #

CommaStyle above 1,000 but below a million, DecimalStyle between 0.001 and a million and ExponentStyle outside this range.

data FStyle Source #

Data type representing styles of formatting dependent on the number

Instances

Instances details
Eq FStyle Source # 
Instance details

Defined in Data.FormatN

Methods

(==) :: FStyle -> FStyle -> Bool #

(/=) :: FStyle -> FStyle -> Bool #

Ord FStyle Source # 
Instance details

Defined in Data.FormatN

Show FStyle Source # 
Instance details

Defined in Data.FormatN

SigFig formatters

fixedSF :: Maybe Int -> SigFig -> Text Source #

expt format for a SigFig

exptSF :: SigFig -> Text Source #

expt format for a SigFig

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"

decimalSF :: SigFig -> Text Source #

decimal format for a SigFig

commaSF :: SigFig -> Text Source #

comma format for a SigFig

dollarSF :: (SigFig -> Text) -> SigFig -> Text Source #

dollar format for a SigFig

percentSF :: (SigFig -> Text) -> SigFig -> Text Source #

percent format for a SigFig

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"

specific 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"

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 FormatStyle so a list of numbers can all have the same formatting

Also equalises the exponent to 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)

formats Source #

Arguments

:: Bool

left pad to the largest text length

-> (Double -> FormatStyle)

style

-> Maybe Int

significant figures requested

-> [Double]

list of numbers

-> [Text] 

Consistently format a list of numbers

>>> formats True precStyle (Just 1) [0,0.5,1,2]
["0.0","0.5","1.0","2.0"]
>>> formats False precStyle (Just 1) $ ((-1)*) <$> [0,0.5,1,2]
["0.0","-0.5","-1.0","-2.0"]
>>> formats True commaPrecStyle (Just 1) $ ((-1000)*) <$> [0,0.5,1,2]
["     0","  -500","-1,000","-2,000"]
>>> formats True commaPrecStyle (Just 1) $ ((1e6)*) <$> [0,0.5,1,2]
["        0","  500,000","1,000,000","2,000,000"]
>>> formats True commaPrecStyle (Just 1) $ ((1e6)*) <$> [0.9,2,3]
["0.9e6","2.0e6","3.0e6"]
>>> formats 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 commaPrecStyle (Just 1) $ ((1e-3)*) <$> [0,0.5,1,2]
["0.0000","0.0005","0.0010","0.0020"]

distinguish Source #

Arguments

:: Int

maximum number of iterations

-> Bool

left pad to the largest text length

-> (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 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 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"]

FormatN

data FormatN Source #

Wrapper for the various formatting options.

>>> defaultFormatN
FormatN {fstyle = FSCommaPrec, sigFigs = Just 2, addLPad = True}

Constructors

FormatN 

Instances

Instances details
Eq FormatN Source # 
Instance details

Defined in Data.FormatN

Methods

(==) :: FormatN -> FormatN -> Bool #

(/=) :: FormatN -> FormatN -> Bool #

Show FormatN Source # 
Instance details

Defined in Data.FormatN

Generic FormatN Source # 
Instance details

Defined in Data.FormatN

Associated Types

type Rep FormatN :: Type -> Type #

Methods

from :: FormatN -> Rep FormatN x #

to :: Rep FormatN x -> FormatN #

type Rep FormatN Source # 
Instance details

Defined in Data.FormatN

type Rep FormatN = D1 ('MetaData "FormatN" "Data.FormatN" "formatn-0.2.0-78iiLNR847w1DgaEoH4RCk" '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 "addLPad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))

defaultFormatN :: FormatN Source #

The official FormatN

formatN :: FormatN -> Double -> Text Source #

run a FormatN

>>> formatN defaultFormatN 1234
"1,200"

formatNs :: Int -> FormatN -> [Double] -> [Text] Source #

Consistently format a list of numbers via using distinguish.

>>> formatNs 4 defaultFormatN [0,1,1.01,1.02,1.1,1.2]
["0.00","1.00","1.01","1.02","1.10","1.20"]