{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TupleSections #-}
{-# OPTIONS_GHC -Wall #-}
module Data.FormatN
(
SigFig (..),
SigFigSign (..),
toSigFig,
fromSigFig,
incSigFig,
FormatStyle (..),
precStyle,
commaPrecStyle,
FStyle (..),
fixedSF,
exptSF,
exptSFWith,
decimalSF,
commaSF,
dollarSF,
percentSF,
formatSF,
format,
formatOrShow,
fixed,
expt,
exptWith,
decimal,
prec,
comma,
commaPrec,
dollar,
percent,
majorityStyle,
formats,
distinguish,
FormatN (..),
defaultFormatN,
formatN,
formatNs,
)
where
import Data.Bifunctor
import Data.Bool
import Data.Containers.ListUtils (nubOrd)
import Data.Foldable
import qualified Data.List as List
import qualified Data.Map.Strict as Map
import Data.Maybe
import Data.Ord
import Data.Text (Text, pack)
import qualified Data.Text as Text
import GHC.Generics hiding (prec)
import Numeric
import Prelude hiding (exponent)
data SigFig = SigFig
{
SigFig -> SigFigSign
sfSign :: SigFigSign,
SigFig -> Integer
sfFigures :: Integer,
SigFig -> Int
sfExponent :: Int
}
deriving (SigFig -> SigFig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SigFig -> SigFig -> Bool
$c/= :: SigFig -> SigFig -> Bool
== :: SigFig -> SigFig -> Bool
$c== :: SigFig -> SigFig -> Bool
Eq, Int -> SigFig -> ShowS
[SigFig] -> ShowS
SigFig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigFig] -> ShowS
$cshowList :: [SigFig] -> ShowS
show :: SigFig -> String
$cshow :: SigFig -> String
showsPrec :: Int -> SigFig -> ShowS
$cshowsPrec :: Int -> SigFig -> ShowS
Show)
data SigFigSign = SigFigNeg | SigFigPos deriving (SigFigSign -> SigFigSign -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SigFigSign -> SigFigSign -> Bool
$c/= :: SigFigSign -> SigFigSign -> Bool
== :: SigFigSign -> SigFigSign -> Bool
$c== :: SigFigSign -> SigFigSign -> Bool
Eq, Int -> SigFigSign -> ShowS
[SigFigSign] -> ShowS
SigFigSign -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigFigSign] -> ShowS
$cshowList :: [SigFigSign] -> ShowS
show :: SigFigSign -> String
$cshow :: SigFigSign -> String
showsPrec :: Int -> SigFigSign -> ShowS
$cshowsPrec :: Int -> SigFigSign -> ShowS
Show)
sfsign :: SigFigSign -> String
sfsign :: SigFigSign -> String
sfsign SigFigSign
s = forall a. a -> a -> Bool -> a
bool String
"" String
"-" (SigFigSign
s forall a. Eq a => a -> a -> Bool
== SigFigSign
SigFigNeg)
toSigFig :: Maybe Int -> Double -> SigFig
toSigFig :: Maybe Int -> Double -> SigFig
toSigFig Maybe Int
n Double
x = SigFigSign -> Integer -> Int -> SigFig
SigFig SigFigSign
s Integer
fs' Int
expo'
where
(SigFigSign
s, ([Int]
floatfs, Int
floate)) = forall a. a -> a -> Bool -> a
bool (SigFigSign
SigFigPos, forall a. RealFloat a => Integer -> a -> ([Int], Int)
floatToDigits Integer
10 Double
x) (SigFigSign
SigFigNeg, forall a. RealFloat a => Integer -> a -> ([Int], Int)
floatToDigits Integer
10 (-Double
x)) (Double
x forall a. Ord a => a -> a -> Bool
< Double
0)
floate' :: Int
floate' = forall a. a -> a -> Bool -> a
bool Int
floate (Int
floate forall a. Num a => a -> a -> a
+ Int
1) (Double
x forall a. Eq a => a -> a -> Bool
== Double
0)
nsig :: Int
nsig = forall a. a -> Maybe a -> a
fromMaybe (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
floatfs) Maybe Int
n
([Int]
floatfs', Int
e) =
forall a. a -> a -> Bool -> a
bool
([Int]
floatfs, Int
floate' forall a. Num a => a -> a -> a
- forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
floatfs)
([Int]
floatfs forall a. Semigroup a => a -> a -> a
<> forall a. Int -> a -> [a]
replicate (Int
nsig forall a. Num a => a -> a -> a
- forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
floatfs) Int
0, Int
floate' forall a. Num a => a -> a -> a
- Int
nsig)
(forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
floatfs forall a. Ord a => a -> a -> Bool
< Int
nsig)
([Int]
fs0, [Int]
fs1) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
nsig [Int]
floatfs'
fs :: Integer
fs =
forall a b. (RealFrac a, Integral b) => a -> b
round forall a b. (a -> b) -> a -> b
$
(forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Int
x' Int
a -> Int
x' forall a. Num a => a -> a -> a
* Int
10 forall a. Num a => a -> a -> a
+ Int
a) Int
0 [Int]
fs0 :: Double)
forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Int
x' Int
a -> Int
x' forall a. Num a => a -> a -> a
* Int
10 forall a. Num a => a -> a -> a
+ Int
a) Int
0 [Int]
fs1) forall a. Fractional a => a -> a -> a
/ (Double
10.0 forall a b. (Num a, Integral b) => a -> b -> a
^ (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
fs1 :: Int))
(Integer
fs', Int
expo) =
forall a. a -> a -> Bool -> a
bool
(Integer
fs, Int
e forall a. Num a => a -> a -> a
+ forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
floatfs' forall a. Num a => a -> a -> a
- Int
nsig)
(Integer
fs forall a. Integral a => a -> a -> a
`div` Integer
10, Int
e forall a. Num a => a -> a -> a
+ forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
floatfs' forall a. Num a => a -> a -> a
- Int
nsig forall a. Num a => a -> a -> a
+ Int
1)
(forall (t :: * -> *) a. Foldable t => t a -> Int
length (forall a. Show a => a -> String
show Integer
fs) forall a. Ord a => a -> a -> Bool
> Int
nsig)
expo' :: Int
expo' = forall a. a -> a -> Bool -> a
bool Int
expo Int
0 (Integer
fs' forall a. Eq a => a -> a -> Bool
== Integer
0 Bool -> Bool -> Bool
&& Int
expo forall a. Ord a => a -> a -> Bool
> Int
0)
fromSigFig :: SigFig -> Double
fromSigFig :: SigFig -> Double
fromSigFig (SigFig SigFigSign
s Integer
fs Int
e) = forall a. a -> a -> Bool -> a
bool Double
1 (-Double
1) (SigFigSign
s forall a. Eq a => a -> a -> Bool
== SigFigSign
SigFigNeg) forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
fs forall a. Num a => a -> a -> a
* Double
10 forall a. Floating a => a -> a -> a
** forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
e
incSigFig :: Int -> SigFig -> SigFig
incSigFig :: Int -> SigFig -> SigFig
incSigFig Int
n (SigFig SigFigSign
s Integer
fs Int
e) = SigFigSign -> Integer -> Int -> SigFig
SigFig SigFigSign
s (Integer
fs forall a. Num a => a -> a -> a
* (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall a. Ord a => a -> a -> a
max Int
0 Int
n)) (Int
e forall a. Num a => a -> a -> a
- Int
n)
eSF :: SigFig -> Int
eSF :: SigFig -> Int
eSF (SigFig SigFigSign
_ Integer
fs Int
e) = Int
e forall a. Num a => a -> a -> a
+ forall (t :: * -> *) a. Foldable t => t a -> Int
length (forall a. Show a => a -> String
show Integer
fs) forall a. Num a => a -> a -> a
- Int
1
fixedSF :: Maybe Int -> SigFig -> Text
fixedSF :: Maybe Int -> SigFig -> Text
fixedSF Maybe Int
n SigFig
sf = Maybe Int -> Double -> Text
fixed Maybe Int
n (SigFig -> Double
fromSigFig SigFig
sf)
exptSF :: SigFig -> Text
exptSF :: SigFig -> Text
exptSF (SigFig SigFigSign
s Integer
i Int
e) = String -> Text
pack forall a b. (a -> b) -> a -> b
$ SigFigSign -> String
sfsign SigFigSign
s forall a. Semigroup a => a -> a -> a
<> forall a. a -> a -> Bool -> a
bool (String
i'' forall a. Semigroup a => a -> a -> a
<> String
"e" forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Int
e') String
"0" (Integer
i forall a. Eq a => a -> a -> Bool
== Integer
0)
where
i'' :: String
i''
| forall (t :: * -> *) a. Foldable t => t a -> Int
length String
i' forall a. Eq a => a -> a -> Bool
== Int
1 = String
i'
| Bool
otherwise = forall a. Int -> [a] -> [a]
take Int
1 String
i' forall a. Semigroup a => a -> a -> a
<> String
"." forall a. Semigroup a => a -> a -> a
<> forall a. Int -> [a] -> [a]
drop Int
1 String
i'
i' :: String
i' = forall a. Show a => a -> String
show Integer
i
e' :: Int
e' = Int
e forall a. Num a => a -> a -> a
+ forall (t :: * -> *) a. Foldable t => t a -> Int
length String
i' forall a. Num a => a -> a -> a
- Int
1
exptSFWith :: Maybe Int -> SigFig -> Text
exptSFWith :: Maybe Int -> SigFig -> Text
exptSFWith Maybe Int
eover (SigFig SigFigSign
s Integer
i Int
e) = String -> Text
pack (SigFigSign -> String
sfsign SigFigSign
s) forall a. Semigroup a => a -> a -> a
<> Integer -> Int -> Text
posDecimalSF Integer
i (Int
e forall a. Num a => a -> a -> a
- Int
e') forall a. Semigroup a => a -> a -> a
<> Text
"e" forall a. Semigroup a => a -> a -> a
<> String -> Text
pack (forall a. Show a => a -> String
show Int
e')
where
e' :: Int
e' = forall a. a -> Maybe a -> a
fromMaybe (forall a. a -> a -> Bool -> a
bool (Int
e forall a. Num a => a -> a -> a
+ forall (t :: * -> *) a. Foldable t => t a -> Int
length (forall a. Show a => a -> String
show Integer
i) forall a. Num a => a -> a -> a
- Int
1) Int
0 (Integer
i forall a. Eq a => a -> a -> Bool
== Integer
0)) Maybe Int
eover
posDecimalSF :: Integer -> Int -> Text
posDecimalSF :: Integer -> Int -> Text
posDecimalSF Integer
xs Int
e = String -> Text
pack String
t
where
xs' :: String
xs' = forall a. Show a => a -> String
show Integer
xs
nsf :: Int
nsf = forall (t :: * -> *) a. Foldable t => t a -> Int
length String
xs'
extrasf :: Int
extrasf = forall a. a -> a -> Bool -> a
bool (-(Int
e forall a. Num a => a -> a -> a
+ Int
nsf)) (-(Int
e forall a. Num a => a -> a -> a
+ Int
nsf)) (Integer
xs forall a. Eq a => a -> a -> Bool
== Integer
0)
oversf :: Int
oversf = forall (t :: * -> *) a. Foldable t => t a -> Int
length String
xs' forall a. Num a => a -> a -> a
+ Int
e
t :: String
t
| Int
e forall a. Ord a => a -> a -> Bool
>= Int
0 = forall a. a -> a -> Bool -> a
bool (String
xs' forall a. Semigroup a => a -> a -> a
<> forall a. Int -> a -> [a]
replicate Int
e Char
'0') String
xs' (Integer
xs forall a. Eq a => a -> a -> Bool
== Integer
0)
| Int
e forall a. Ord a => a -> a -> Bool
<= -Int
nsf = String
"0." forall a. Semigroup a => a -> a -> a
<> forall a. Int -> a -> [a]
replicate Int
extrasf Char
'0' forall a. Semigroup a => a -> a -> a
<> String
xs'
| Bool
otherwise = forall a. Int -> [a] -> [a]
take Int
oversf String
xs' forall a. Semigroup a => a -> a -> a
<> String
"." forall a. Semigroup a => a -> a -> a
<> forall a. Int -> [a] -> [a]
drop Int
oversf String
xs'
maybeCommaSF :: Bool -> SigFig -> Text
maybeCommaSF :: Bool -> SigFig -> Text
maybeCommaSF Bool
doCommas (SigFig SigFigSign
s Integer
xs Int
e) = String -> Text
pack (SigFigSign -> String
sfsign SigFigSign
s) forall a. Semigroup a => a -> a -> a
<> forall a. a -> a -> Bool -> a
bool forall a. a -> a
id Text -> Text
addcommas Bool
doCommas (Integer -> Int -> Text
posDecimalSF Integer
xs Int
e)
where
addcommas :: Text -> Text
addcommas =
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. Semigroup a => a -> a -> a
(<>)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Text -> Text
Text.reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
Text.intercalate Text
"," forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> [Text]
Text.chunksOf Int
3 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
Text.reverse)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> (Text, Text)
Text.breakOn Text
"."
commaSF :: SigFig -> Text
commaSF :: SigFig -> Text
commaSF = Bool -> SigFig -> Text
maybeCommaSF Bool
True
decimalSF :: SigFig -> Text
decimalSF :: SigFig -> Text
decimalSF = Bool -> SigFig -> Text
maybeCommaSF Bool
False
percentSF :: (SigFig -> Text) -> SigFig -> Text
percentSF :: (SigFig -> Text) -> SigFig -> Text
percentSF SigFig -> Text
f (SigFig SigFigSign
s Integer
figs Int
e) = (forall a. Semigroup a => a -> a -> a
<> Text
"%") forall a b. (a -> b) -> a -> b
$ SigFig -> Text
f (SigFigSign -> Integer -> Int -> SigFig
SigFig SigFigSign
s Integer
figs (Int
e forall a. Num a => a -> a -> a
+ Int
2))
dollarSF :: (SigFig -> Text) -> SigFig -> Text
dollarSF :: (SigFig -> Text) -> SigFig -> Text
dollarSF SigFig -> Text
f SigFig
sf =
case SigFig -> SigFigSign
sfSign SigFig
sf of
SigFigSign
SigFigNeg -> Text
"-" forall a. Semigroup a => a -> a -> a
<> (SigFig -> Text) -> SigFig -> Text
dollarSF SigFig -> Text
f (SigFigSign -> Integer -> Int -> SigFig
SigFig SigFigSign
SigFigPos (SigFig -> Integer
sfFigures SigFig
sf) (SigFig -> Int
sfExponent SigFig
sf))
SigFigSign
SigFigPos -> Text
"$" forall a. Semigroup a => a -> a -> a
<> SigFig -> Text
f SigFig
sf
fixed :: Maybe Int -> Double -> Text
fixed :: Maybe Int -> Double -> Text
fixed Maybe Int
n Double
x = String -> Text
pack forall a b. (a -> b) -> a -> b
$ forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat Maybe Int
n Double
x String
""
expt :: Maybe Int -> Double -> Text
expt :: Maybe Int -> Double -> Text
expt Maybe Int
n Double
x = SigFig -> Text
exptSF (Maybe Int -> Double -> SigFig
toSigFig Maybe Int
n Double
x)
exptWith :: Maybe Int -> Maybe Int -> Double -> Text
exptWith :: Maybe Int -> Maybe Int -> Double -> Text
exptWith Maybe Int
n' Maybe Int
n Double
x = Maybe Int -> SigFig -> Text
exptSFWith Maybe Int
n' (Maybe Int -> Double -> SigFig
toSigFig Maybe Int
n Double
x)
decimal :: Maybe Int -> Double -> Text
decimal :: Maybe Int -> Double -> Text
decimal Maybe Int
n Double
x = SigFig -> Text
decimalSF (Maybe Int -> Double -> SigFig
toSigFig Maybe Int
n Double
x)
comma :: Maybe Int -> Double -> Text
comma :: Maybe Int -> Double -> Text
comma Maybe Int
n Double
x = SigFig -> Text
commaSF (Maybe Int -> Double -> SigFig
toSigFig Maybe Int
n Double
x)
percent :: (SigFig -> Text) -> Maybe Int -> Double -> Text
percent :: (SigFig -> Text) -> Maybe Int -> Double -> Text
percent SigFig -> Text
f Maybe Int
n Double
x = (SigFig -> Text) -> SigFig -> Text
percentSF SigFig -> Text
f (Maybe Int -> Double -> SigFig
toSigFig Maybe Int
n Double
x)
dollar :: (SigFig -> Text) -> Maybe Int -> Double -> Text
dollar :: (SigFig -> Text) -> Maybe Int -> Double -> Text
dollar SigFig -> Text
f Maybe Int
n Double
x = (SigFig -> Text) -> SigFig -> Text
dollarSF SigFig -> Text
f (Maybe Int -> Double -> SigFig
toSigFig Maybe Int
n Double
x)
data FormatStyle
=
DecimalStyle
|
ExponentStyle (Maybe Int)
|
CommaStyle
|
FixedStyle Int
|
PercentStyle
|
DollarStyle
deriving (Int -> FormatStyle -> ShowS
[FormatStyle] -> ShowS
FormatStyle -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FormatStyle] -> ShowS
$cshowList :: [FormatStyle] -> ShowS
show :: FormatStyle -> String
$cshow :: FormatStyle -> String
showsPrec :: Int -> FormatStyle -> ShowS
$cshowsPrec :: Int -> FormatStyle -> ShowS
Show, FormatStyle -> FormatStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormatStyle -> FormatStyle -> Bool
$c/= :: FormatStyle -> FormatStyle -> Bool
== :: FormatStyle -> FormatStyle -> Bool
$c== :: FormatStyle -> FormatStyle -> Bool
Eq, Eq FormatStyle
FormatStyle -> FormatStyle -> Bool
FormatStyle -> FormatStyle -> Ordering
FormatStyle -> FormatStyle -> FormatStyle
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FormatStyle -> FormatStyle -> FormatStyle
$cmin :: FormatStyle -> FormatStyle -> FormatStyle
max :: FormatStyle -> FormatStyle -> FormatStyle
$cmax :: FormatStyle -> FormatStyle -> FormatStyle
>= :: FormatStyle -> FormatStyle -> Bool
$c>= :: FormatStyle -> FormatStyle -> Bool
> :: FormatStyle -> FormatStyle -> Bool
$c> :: FormatStyle -> FormatStyle -> Bool
<= :: FormatStyle -> FormatStyle -> Bool
$c<= :: FormatStyle -> FormatStyle -> Bool
< :: FormatStyle -> FormatStyle -> Bool
$c< :: FormatStyle -> FormatStyle -> Bool
compare :: FormatStyle -> FormatStyle -> Ordering
$ccompare :: FormatStyle -> FormatStyle -> Ordering
Ord)
precStyle :: Double -> FormatStyle
precStyle :: Double -> FormatStyle
precStyle Double
x
| Double
x forall a. Eq a => a -> a -> Bool
== Double
0 = FormatStyle
DecimalStyle
| forall a. Num a => a -> a
abs Double
x forall a. Ord a => a -> a -> Bool
< Double
0.001 = Maybe Int -> FormatStyle
ExponentStyle (forall a. a -> Maybe a
Just (SigFig -> Int
eSF (Maybe Int -> Double -> SigFig
toSigFig forall a. Maybe a
Nothing Double
x)))
| forall a. Num a => a -> a
abs Double
x forall a. Ord a => a -> a -> Bool
> Double
1e6 = Maybe Int -> FormatStyle
ExponentStyle (forall a. a -> Maybe a
Just (SigFig -> Int
eSF (Maybe Int -> Double -> SigFig
toSigFig forall a. Maybe a
Nothing Double
x)))
| Bool
otherwise = FormatStyle
DecimalStyle
commaPrecStyle :: Double -> FormatStyle
commaPrecStyle :: Double -> FormatStyle
commaPrecStyle Double
x
| Double
x forall a. Eq a => a -> a -> Bool
== Double
0 = FormatStyle
CommaStyle
| forall a. Num a => a -> a
abs Double
x forall a. Ord a => a -> a -> Bool
< Double
0.001 = Maybe Int -> FormatStyle
ExponentStyle (forall a. a -> Maybe a
Just (SigFig -> Int
eSF (Maybe Int -> Double -> SigFig
toSigFig forall a. Maybe a
Nothing Double
x)))
| forall a. Num a => a -> a
abs Double
x forall a. Ord a => a -> a -> Bool
> Double
1e6 = Maybe Int -> FormatStyle
ExponentStyle (forall a. a -> Maybe a
Just (SigFig -> Int
eSF (Maybe Int -> Double -> SigFig
toSigFig forall a. Maybe a
Nothing Double
x)))
| Bool
otherwise = FormatStyle
CommaStyle
data FStyle
= FSDecimal
| FSExponent (Maybe Int)
| FSComma
| FSFixed Int
| FSPercent
| FSDollar
| FSPrec
| FSCommaPrec
| FSNone
deriving (Int -> FStyle -> ShowS
[FStyle] -> ShowS
FStyle -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FStyle] -> ShowS
$cshowList :: [FStyle] -> ShowS
show :: FStyle -> String
$cshow :: FStyle -> String
showsPrec :: Int -> FStyle -> ShowS
$cshowsPrec :: Int -> FStyle -> ShowS
Show, FStyle -> FStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FStyle -> FStyle -> Bool
$c/= :: FStyle -> FStyle -> Bool
== :: FStyle -> FStyle -> Bool
$c== :: FStyle -> FStyle -> Bool
Eq, Eq FStyle
FStyle -> FStyle -> Bool
FStyle -> FStyle -> Ordering
FStyle -> FStyle -> FStyle
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FStyle -> FStyle -> FStyle
$cmin :: FStyle -> FStyle -> FStyle
max :: FStyle -> FStyle -> FStyle
$cmax :: FStyle -> FStyle -> FStyle
>= :: FStyle -> FStyle -> Bool
$c>= :: FStyle -> FStyle -> Bool
> :: FStyle -> FStyle -> Bool
$c> :: FStyle -> FStyle -> Bool
<= :: FStyle -> FStyle -> Bool
$c<= :: FStyle -> FStyle -> Bool
< :: FStyle -> FStyle -> Bool
$c< :: FStyle -> FStyle -> Bool
compare :: FStyle -> FStyle -> Ordering
$ccompare :: FStyle -> FStyle -> Ordering
Ord)
majorityStyle :: (Double -> FormatStyle) -> [Double] -> FormatStyle
majorityStyle :: (Double -> FormatStyle) -> [Double] -> FormatStyle
majorityStyle Double -> FormatStyle
s [Double]
xs = FormatStyle
maj'
where
maj :: FormatStyle
maj = forall a. a -> Maybe a -> a
fromMaybe FormatStyle
CommaStyle (forall a. Ord a => [a] -> Maybe a
major (FormatStyle -> FormatStyle
neutralExpStyle forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> FormatStyle
s forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double]
xs))
maj' :: FormatStyle
maj' = forall a. a -> a -> Bool -> a
bool FormatStyle
maj (Maybe Int -> FormatStyle
ExponentStyle (forall a. a -> Maybe a -> a
fromMaybe forall a. Maybe a
Nothing Maybe (Maybe Int)
expXs)) (FormatStyle
maj forall a. Eq a => a -> a -> Bool
== Maybe Int -> FormatStyle
ExponentStyle forall a. Maybe a
Nothing)
neutralExpStyle :: FormatStyle -> FormatStyle
neutralExpStyle (ExponentStyle Maybe Int
_) = Maybe Int -> FormatStyle
ExponentStyle forall a. Maybe a
Nothing
neutralExpStyle FormatStyle
x = FormatStyle
x
expXs :: Maybe (Maybe Int)
expXs = forall a. Ord a => [a] -> Maybe a
major [Maybe Int
x | (ExponentStyle Maybe Int
x) <- Double -> FormatStyle
s forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double]
xs]
major :: (Ord a) => [a] -> Maybe a
major :: forall a. Ord a => [a] -> Maybe a
major [a]
xs = forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. [a] -> Maybe a
listToMaybe (forall b a. Ord b => (a -> b) -> [a] -> [a]
List.sortOn (forall a. a -> Down a
Down forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
Map.toList forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith forall a. Num a => a -> a -> a
(+) ((,Integer
1 :: Integer) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [a]
xs))
format :: FormatStyle -> Maybe Int -> Double -> Text
format :: FormatStyle -> Maybe Int -> Double -> Text
format FormatStyle
fs Maybe Int
n Double
x = forall a. a -> a -> Bool -> a
bool (Double -> Text
go Double
x) (Text
"-" forall a. Semigroup a => a -> a -> a
<> Double -> Text
go (-Double
x)) (Double
x forall a. Ord a => a -> a -> Bool
< Double
0)
where
go :: Double -> Text
go Double
x' = case FormatStyle
fs of
FormatStyle
DecimalStyle -> Maybe Int -> Double -> Text
decimal Maybe Int
n Double
x'
ExponentStyle Maybe Int
n' -> Maybe Int -> Maybe Int -> Double -> Text
exptWith Maybe Int
n' Maybe Int
n Double
x'
FormatStyle
CommaStyle -> Maybe Int -> Double -> Text
comma Maybe Int
n Double
x'
FixedStyle Int
n' -> Maybe Int -> Double -> Text
fixed (forall a. a -> Maybe a
Just Int
n') Double
x'
FormatStyle
PercentStyle -> (SigFig -> Text) -> Maybe Int -> Double -> Text
percent SigFig -> Text
commaSF Maybe Int
n Double
x'
FormatStyle
DollarStyle -> (SigFig -> Text) -> Maybe Int -> Double -> Text
dollar SigFig -> Text
commaSF Maybe Int
n Double
x'
formatSF :: FormatStyle -> SigFig -> Text
formatSF :: FormatStyle -> SigFig -> Text
formatSF FormatStyle
fs SigFig
x = case FormatStyle
fs of
FormatStyle
DecimalStyle -> SigFig -> Text
decimalSF SigFig
x
ExponentStyle Maybe Int
n' -> Maybe Int -> SigFig -> Text
exptSFWith Maybe Int
n' SigFig
x
FormatStyle
CommaStyle -> SigFig -> Text
commaSF SigFig
x
FixedStyle Int
n -> Maybe Int -> Double -> Text
fixed (forall a. a -> Maybe a
Just Int
n) (SigFig -> Double
fromSigFig SigFig
x)
FormatStyle
PercentStyle -> (SigFig -> Text) -> SigFig -> Text
percentSF SigFig -> Text
commaSF SigFig
x
FormatStyle
DollarStyle -> (SigFig -> Text) -> SigFig -> Text
dollarSF SigFig -> Text
commaSF SigFig
x
prec :: Maybe Int -> Double -> Text
prec :: Maybe Int -> Double -> Text
prec Maybe Int
n Double
x = FormatStyle -> Maybe Int -> Double -> Text
format (Double -> FormatStyle
precStyle Double
x) Maybe Int
n Double
x
commaPrec :: Maybe Int -> Double -> Text
commaPrec :: Maybe Int -> Double -> Text
commaPrec Maybe Int
n Double
x = FormatStyle -> Maybe Int -> Double -> Text
format (Double -> FormatStyle
commaPrecStyle Double
x) Maybe Int
n Double
x
formats ::
Bool ->
(Double -> FormatStyle) ->
Maybe Int ->
[Double] ->
[Text]
formats :: Bool -> (Double -> FormatStyle) -> Maybe Int -> [Double] -> [Text]
formats Bool
lpad Double -> FormatStyle
s Maybe Int
n0 [Double]
xs = forall a. a -> a -> Bool -> a
bool [Text]
fsigs ([Text] -> [Text]
lpads [Text]
fsigs) Bool
lpad
where
sigs :: [SigFig]
sigs = Maybe Int -> Double -> SigFig
toSigFig Maybe Int
n0 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double]
xs
minexp :: Int
minexp = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum (SigFig -> Int
sfExponent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. (a -> Bool) -> [a] -> [a]
filter (\SigFig
x -> SigFig -> Integer
sfFigures SigFig
x forall a. Eq a => a -> a -> Bool
/= Integer
0) [SigFig]
sigs)
sigs' :: [SigFig]
sigs' = (\SigFig
x -> forall a. a -> a -> Bool -> a
bool (Int -> SigFig -> SigFig
incSigFig (SigFig -> Int
sfExponent SigFig
x forall a. Num a => a -> a -> a
- Int
minexp) SigFig
x) (SigFig
x {sfExponent :: Int
sfExponent = forall a. Ord a => a -> a -> a
min Int
1 Int
minexp}) (SigFig -> Integer
sfFigures SigFig
x forall a. Eq a => a -> a -> Bool
== Integer
0)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SigFig]
sigs
maj :: FormatStyle
maj = (Double -> FormatStyle) -> [Double] -> FormatStyle
majorityStyle Double -> FormatStyle
s (SigFig -> Double
fromSigFig forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SigFig]
sigs')
fsigs :: [Text]
fsigs = FormatStyle -> SigFig -> Text
formatSF FormatStyle
maj forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SigFig]
sigs'
lpads :: [Text] -> [Text]
lpads :: [Text] -> [Text]
lpads [Text]
ts = (\Text
x -> forall a. Monoid a => [a] -> a
mconcat (forall a. Int -> a -> [a]
replicate (Int
maxl forall a. Num a => a -> a -> a
- Text -> Int
Text.length Text
x) Text
" ") forall a. Semigroup a => a -> a -> a
<> Text
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text]
ts
where
maxl :: Int
maxl = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum forall a b. (a -> b) -> a -> b
$ Text -> Int
Text.length forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text]
ts
distinguish ::
Int ->
Bool ->
(Double -> FormatStyle) ->
Maybe Int ->
[Double] ->
[Text]
distinguish :: Int
-> Bool
-> (Double -> FormatStyle)
-> Maybe Int
-> [Double]
-> [Text]
distinguish Int
maxi Bool
pad Double -> FormatStyle
f Maybe Int
n [Double]
xs =
case Maybe Int
n of
Maybe Int
Nothing -> Bool -> (Double -> FormatStyle) -> Maybe Int -> [Double] -> [Text]
formats Bool
pad Double -> FormatStyle
f forall a. Maybe a
Nothing [Double]
xs
Just Int
n0 -> Int -> [Double] -> [Text]
loop Int
n0 [Double]
xs
where
loop :: Int -> [Double] -> [Text]
loop Int
n' [Double]
xs' =
let s :: [Text]
s = Bool -> (Double -> FormatStyle) -> Maybe Int -> [Double] -> [Text]
formats Bool
pad Double -> FormatStyle
f (forall a. a -> Maybe a
Just Int
n') [Double]
xs'
in forall a. a -> a -> Bool -> a
bool (Int -> [Double] -> [Text]
loop (Int
1 forall a. Num a => a -> a -> a
+ Int
n') [Double]
xs') [Text]
s ([Text]
s forall a. Eq a => a -> a -> Bool
== forall a. Ord a => [a] -> [a]
nubOrd [Text]
s Bool -> Bool -> Bool
|| Int
n' forall a. Ord a => a -> a -> Bool
> Int
maxi)
data FormatN = FormatN {FormatN -> FStyle
fstyle :: FStyle, FormatN -> Maybe Int
sigFigs :: Maybe Int, FormatN -> Bool
addLPad :: Bool} deriving (FormatN -> FormatN -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormatN -> FormatN -> Bool
$c/= :: FormatN -> FormatN -> Bool
== :: FormatN -> FormatN -> Bool
$c== :: FormatN -> FormatN -> Bool
Eq, Int -> FormatN -> ShowS
[FormatN] -> ShowS
FormatN -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FormatN] -> ShowS
$cshowList :: [FormatN] -> ShowS
show :: FormatN -> String
$cshow :: FormatN -> String
showsPrec :: Int -> FormatN -> ShowS
$cshowsPrec :: Int -> FormatN -> ShowS
Show, forall x. Rep FormatN x -> FormatN
forall x. FormatN -> Rep FormatN x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FormatN x -> FormatN
$cfrom :: forall x. FormatN -> Rep FormatN x
Generic)
defaultFormatN :: FormatN
defaultFormatN :: FormatN
defaultFormatN = FStyle -> Maybe Int -> Bool -> FormatN
FormatN FStyle
FSCommaPrec (forall a. a -> Maybe a
Just Int
2) Bool
True
formatN :: FormatN -> Double -> Text
formatN :: FormatN -> Double -> Text
formatN (FormatN FStyle
FSDecimal Maybe Int
sf Bool
_) Double
x = FormatStyle -> Maybe Int -> Double -> Text
format FormatStyle
DecimalStyle Maybe Int
sf Double
x
formatN (FormatN (FSExponent Maybe Int
n) Maybe Int
sf Bool
_) Double
x = FormatStyle -> Maybe Int -> Double -> Text
format (Maybe Int -> FormatStyle
ExponentStyle Maybe Int
n) Maybe Int
sf Double
x
formatN (FormatN FStyle
FSComma Maybe Int
sf Bool
_) Double
x = FormatStyle -> Maybe Int -> Double -> Text
format FormatStyle
CommaStyle Maybe Int
sf Double
x
formatN (FormatN (FSFixed Int
n) Maybe Int
sf Bool
_) Double
x = FormatStyle -> Maybe Int -> Double -> Text
format (Int -> FormatStyle
FixedStyle Int
n) Maybe Int
sf Double
x
formatN (FormatN FStyle
FSPercent Maybe Int
sf Bool
_) Double
x = FormatStyle -> Maybe Int -> Double -> Text
format FormatStyle
PercentStyle Maybe Int
sf Double
x
formatN (FormatN FStyle
FSDollar Maybe Int
sf Bool
_) Double
x = FormatStyle -> Maybe Int -> Double -> Text
format FormatStyle
DollarStyle Maybe Int
sf Double
x
formatN (FormatN FStyle
FSPrec Maybe Int
sf Bool
_) Double
x = FormatStyle -> Maybe Int -> Double -> Text
format (Double -> FormatStyle
precStyle Double
x) Maybe Int
sf Double
x
formatN (FormatN FStyle
FSCommaPrec Maybe Int
sf Bool
_) Double
x = FormatStyle -> Maybe Int -> Double -> Text
format (Double -> FormatStyle
commaPrecStyle Double
x) Maybe Int
sf Double
x
formatN (FormatN FStyle
FSNone Maybe Int
_ Bool
_) Double
x = String -> Text
pack (forall a. Show a => a -> String
show Double
x)
formatNs :: Int -> FormatN -> [Double] -> [Text]
formatNs :: Int -> FormatN -> [Double] -> [Text]
formatNs Int
maxi (FormatN FStyle
FSDecimal Maybe Int
sf Bool
pad) [Double]
x = Int
-> Bool
-> (Double -> FormatStyle)
-> Maybe Int
-> [Double]
-> [Text]
distinguish Int
maxi Bool
pad (forall a b. a -> b -> a
const FormatStyle
DecimalStyle) Maybe Int
sf [Double]
x
formatNs Int
maxi (FormatN (FSExponent Maybe Int
n) Maybe Int
sf Bool
pad) [Double]
x = Int
-> Bool
-> (Double -> FormatStyle)
-> Maybe Int
-> [Double]
-> [Text]
distinguish Int
maxi Bool
pad (forall a b. a -> b -> a
const (Maybe Int -> FormatStyle
ExponentStyle Maybe Int
n)) Maybe Int
sf [Double]
x
formatNs Int
maxi (FormatN FStyle
FSComma Maybe Int
sf Bool
pad) [Double]
x = Int
-> Bool
-> (Double -> FormatStyle)
-> Maybe Int
-> [Double]
-> [Text]
distinguish Int
maxi Bool
pad (forall a b. a -> b -> a
const FormatStyle
CommaStyle) Maybe Int
sf [Double]
x
formatNs Int
maxi (FormatN (FSFixed Int
n) Maybe Int
sf Bool
pad) [Double]
x = Int
-> Bool
-> (Double -> FormatStyle)
-> Maybe Int
-> [Double]
-> [Text]
distinguish Int
maxi Bool
pad (forall a b. a -> b -> a
const (Int -> FormatStyle
FixedStyle Int
n)) Maybe Int
sf [Double]
x
formatNs Int
maxi (FormatN FStyle
FSPercent Maybe Int
sf Bool
pad) [Double]
x = Int
-> Bool
-> (Double -> FormatStyle)
-> Maybe Int
-> [Double]
-> [Text]
distinguish Int
maxi Bool
pad (forall a b. a -> b -> a
const FormatStyle
PercentStyle) Maybe Int
sf [Double]
x
formatNs Int
maxi (FormatN FStyle
FSDollar Maybe Int
sf Bool
pad) [Double]
x = Int
-> Bool
-> (Double -> FormatStyle)
-> Maybe Int
-> [Double]
-> [Text]
distinguish Int
maxi Bool
pad (forall a b. a -> b -> a
const FormatStyle
DollarStyle) Maybe Int
sf [Double]
x
formatNs Int
maxi (FormatN FStyle
FSPrec Maybe Int
sf Bool
pad) [Double]
x = Int
-> Bool
-> (Double -> FormatStyle)
-> Maybe Int
-> [Double]
-> [Text]
distinguish Int
maxi Bool
pad Double -> FormatStyle
precStyle Maybe Int
sf [Double]
x
formatNs Int
maxi (FormatN FStyle
FSCommaPrec Maybe Int
sf Bool
pad) [Double]
x = Int
-> Bool
-> (Double -> FormatStyle)
-> Maybe Int
-> [Double]
-> [Text]
distinguish Int
maxi Bool
pad Double -> FormatStyle
commaPrecStyle Maybe Int
sf [Double]
x
formatNs Int
_ (FormatN FStyle
FSNone Maybe Int
_ Bool
pad) [Double]
x = forall a. a -> a -> Bool -> a
bool forall a. a -> a
id [Text] -> [Text]
lpads Bool
pad forall a b. (a -> b) -> a -> b
$ String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double]
x
formatOrShow :: FormatStyle -> Maybe Int -> Double -> Text
formatOrShow :: FormatStyle -> Maybe Int -> Double -> Text
formatOrShow FormatStyle
f Maybe Int
n Double
x = forall a. a -> a -> Bool -> a
bool (forall a. a -> a -> Bool -> a
bool Text
f' (String -> Text
pack String
s') (Text -> Int
Text.length (String -> Text
pack String
s') forall a. Ord a => a -> a -> Bool
< Text -> Int
Text.length Text
f')) Text
"0" (Double
x forall a. Ord a => a -> a -> Bool
< Double
1e-6 Bool -> Bool -> Bool
&& Double
x forall a. Ord a => a -> a -> Bool
> -Double
1e-6)
where
f' :: Text
f' = FormatStyle -> Maybe Int -> Double -> Text
format FormatStyle
f Maybe Int
n Double
x
s' :: String
s' = forall a. Show a => a -> String
show Double
x