Skip to content

Commit

Permalink
breakingchange: override sep.characters (#86)
Browse files Browse the repository at this point in the history
* breakingchange: override sep.characters

This is a breaking change as it changes the
`Data.Formatter.Number.Formatter`
record.

It adds support to have different
characters for decimal- and thousand-
group-separaters.

A use case would be formatting numbers
in Germany as there these characters are
flipped (1.234,56 instead of 1,234.56)

* added link to change-log

* sorry forgot my name

* renamed changeSeparators to withSeparators

* Update package set

---------

Co-authored-by: Carsten König <[email protected]>
Co-authored-by: Gary Burgess <[email protected]>
  • Loading branch information
3 people authored Feb 16, 2023
1 parent 0b4deda commit c9e8226
Show file tree
Hide file tree
Showing 5 changed files with 103 additions and 13 deletions.
2 changes: 2 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,8 @@ Notable changes to this project are documented in this file. The format is based

Breaking changes:

- Support for different separators ([PR](https://github.com/purescript-contrib/purescript-formatters/pull/86) by @carstenkoenig)

New features:

Bugfixes:
Expand Down
4 changes: 4 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,10 @@ Formatter has following properties
+ Should sign be printed for positive numbers
+ Should thousands be separated by comma
+ Should output string have abbreviations (like `K` or `M`)
+ What decimal-separator character should be used (default '.')
+ What thousand-group-separator character should be used (default '+')

**Note:** The parser will return a formatter with the default separator-characters - use `withSeparators` to override this after parsing.

Number will be padded with zeros to have at least this number of leading zeros. This doesn't restrict number to have more digits then leading zeros in format string.
+ `0000.0` will show 4 digits: `12 → "0012.0"`, `1234 → "1234.0"`
Expand Down
2 changes: 1 addition & 1 deletion packages.dhall
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
let upstream =
https://raw.githubusercontent.com/purescript/package-sets/prepare-0.15/src/packages.dhall
https://raw.githubusercontent.com/purescript/package-sets/psc-0.15.7-20230216/src/packages.dhall

in upstream
35 changes: 25 additions & 10 deletions src/Data/Formatter/Number.purs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
-- | because one could just compose it with `flip append "%"` or whatever
module Data.Formatter.Number
( Formatter(..)
, withSeparators
, printFormatter
, parseFormatString
, format
Expand All @@ -29,6 +30,7 @@ import Data.Number as Number
import Data.Show.Generic (genericShow)
import Data.String as Str
import Data.String.CodeUnits as CU
import Data.String.CodeUnits as String
import Data.Traversable (for)
import Parsing as P
import Parsing.Combinators as PC
Expand All @@ -41,8 +43,18 @@ newtype Formatter = Formatter
, after :: Int
, abbreviations :: Boolean
, sign :: Boolean
, groupSeparator :: Char
, decimalSeparator :: Char
}

-- | change the default Separators
-- | for example for german formatting you could do
-- |
-- | > parseFormatString ".." # map (withSeparators { groupSeparator: '.', decimalSeparator: ','})
withSeparators :: { groupSeparator :: Char, decimalSeparator :: Char } -> Formatter -> Formatter
withSeparators { groupSeparator, decimalSeparator } (Formatter formatter) =
Formatter (formatter { groupSeparator = groupSeparator, decimalSeparator = decimalSeparator })

derive instance genericFormatter :: Generic Formatter _
derive instance newtypeFormatter :: Newtype Formatter _

Expand Down Expand Up @@ -79,6 +91,8 @@ formatParser = do
, comma: isJust comma
, after: fromMaybe zero $ Arr.length <$> after
, abbreviations: isJust abbreviations
, groupSeparator: ','
, decimalSeparator: '.'
}

-- converts a number to a string of the nearest integer _without_ appending ".0" (like `show` for `Number`) or
Expand Down Expand Up @@ -147,12 +161,12 @@ format (Formatter f) num = do
Just { head, tail } | counter < 3 ->
addCommas (Arr.cons head acc) (counter + one) tail
_ ->
addCommas (Arr.cons ',' acc) zero input
addCommas (Arr.cons f.groupSeparator acc) zero input

leftovers =
if f.after < 1 then ""
else
"."
String.singleton f.decimalSeparator
<> (if leftover == 0.0 then repeat "0" f.after else "")
<> (if leftover > 0.0 then leftoverWithZeros else "")

Expand All @@ -178,24 +192,25 @@ unformatParser (Formatter f) = do
digitsWithCommas :: P.Parser String (Array Int)
digitsWithCommas =
if not f.comma then
some parseDigit <* PS.string "."
some parseDigit <* PS.char (f.decimalSeparator)
else
digitsWithCommas' []
digitsWithCommas' false []

digitsWithCommas' :: Array Int -> P.Parser String (Array Int)
digitsWithCommas' accum = do
digitsWithCommas' :: Boolean -> Array Int -> P.Parser String (Array Int)
digitsWithCommas' inGroup accum = do
ds <- some parseDigit

when (Arr.null accum && Arr.length ds > 3) do
P.fail "Wrong number of digits between thousand separators"
P.fail "Wrong number of digits in front of first thousand separator"

when (Arr.length ds /= 3) do
when (inGroup && Arr.length ds /= 3) do
P.fail "Wrong number of digits between thousand separators"

sep <- PSB.oneOf [ ',', '.' ]
case sep of
'.' -> pure $ accum <> ds
',' -> digitsWithCommas' $ accum <> ds
s
| s == f.decimalSeparator -> pure $ accum <> ds
| s == f.groupSeparator -> digitsWithCommas' true $ accum <> ds
_ -> P.fail "Incorrect symbol, expected ',' or '.'"

beforeDigits <- digitsWithCommas
Expand Down
73 changes: 71 additions & 2 deletions test/src/Number.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,10 +3,9 @@ module Test.Number (numberTest) where
import Prelude

import Control.Monad.Reader.Class (class MonadReader)
import Data.Formatter.Number (Formatter(..), printFormatter, parseFormatString, format, unformat)
import Data.Either (Either(..))
import Data.Formatter.Number (Formatter(..), format, parseFormatString, printFormatter, unformat, withSeparators)
import Effect.Aff.Class (class MonadAff)

import Test.Utils (forAll, describe, shouldEqual)

numberTest :: forall m. MonadReader Int m => MonadAff m => m Unit
Expand All @@ -16,6 +15,11 @@ numberTest = describe "Data.Formatter.Number" do
numberformatts
(\({ fmt, str }) -> printFormatter fmt `shouldEqual` str)

forAll _.str
"should print formatter with different separators the same"
numberformatts
(\({ fmt, str }) -> printFormatter (germanStyleSeparators fmt) `shouldEqual` str)

forAll _.str
"parse format string"
numberformatts
Expand All @@ -26,16 +30,36 @@ numberTest = describe "Data.Formatter.Number" do
[ 100.2, 100.1, 100.3, 10004000.0, -100.2, -100.1, -100.3, -10004000.0 ]
(\n -> unformat fmt1 (format fmt1 n) `shouldEqual` (Right n))

forAll show
"unformat (format n) = n"
[ 100.2, 100.1, 100.3, 10004000.0, -100.2, -100.1, -100.3, -10004000.0 ]
(\n -> unformat fmt1 (format fmt1 n) `shouldEqual` (Right n))

forAll show
"unformat (format n) = n for changed separators"
[ 100.2, 100.1, 100.3, 10004000.0, -100.2, -100.1, -100.3, -10004000.0 ]
(\n -> unformat (germanStyleSeparators fmt1) (format (germanStyleSeparators fmt1) n) `shouldEqual` (Right n))

forAll show
"format (unformat n) = n"
[ "001.12", "001.02", "-001.12", "-001.02" ]
(\n -> (format fmt1 <$> (unformat fmt1 n)) `shouldEqual` (Right n))

forAll show
"format (unformat n) = n for changed separators"
[ "1,12", "1,02", "-1,12", "-1,02", "-1.012,33" ]
(\n -> (format (germanStyleSeparators fmt1') <$> (unformat (germanStyleSeparators fmt1') n)) `shouldEqual` (Right n))

forAll show
"format (unformat n) = n"
[ "+02.12", "+13.12", "-02.12", "-13.12" ]
(\n -> (format fmt3 <$> (unformat fmt3 n)) `shouldEqual` (Right n))

forAll show
"format (unformat n) = n for changed separators"
[ "+02,12", "+13,12", "-02,12", "-13,12" ]
(\n -> (format (germanStyleSeparators fmt3) <$> (unformat (germanStyleSeparators fmt3) n)) `shouldEqual` (Right n))

forAll (\{ fmt: (Formatter fmt), input } -> "rounds up " <> show input <> " (" <> show fmt.after <> " digits)")
"rounding"
[ { fmt: fmt4, input: 1.99999, expected: "02" }
Expand All @@ -53,13 +77,43 @@ numberTest = describe "Data.Formatter.Number" do
format fmt (negate input) `shouldEqual` ("-" <> expected)
)

forAll (\{ fmt: (Formatter fmt), input } -> "rounds up " <> show input <> " (" <> show fmt.after <> " digits)")
"rounding for changed separators"
[ { fmt: germanStyleSeparators fmt4, input: 1.99999, expected: "02" }
, { fmt: germanStyleSeparators fmt1, input: 1.99999, expected: "002,00" }
, { fmt: germanStyleSeparators fmt5, input: 1.99999, expected: "2,0000" }
, { fmt: germanStyleSeparators fmt1, input: 1.89999, expected: "001,90" }
, { fmt: germanStyleSeparators fmt5, input: 1.67899, expected: "1,6790" }
, { fmt: germanStyleSeparators fmt6, input: 12.9, expected: "13" }
, { fmt: germanStyleSeparators fmt7, input: 1.123456789012345678901234, expected: "1,1234567890123457" }
, { fmt: germanStyleSeparators fmt6, input: 12345678901234567.8901234, expected: "12.345.678.901.234.568" }
, { fmt: germanStyleSeparators fmt5, input: 123456789012.345678901234, expected: "123.456.789.012,3457" }
]
( \{ fmt, input, expected } -> do
format fmt input `shouldEqual` expected
format fmt (negate input) `shouldEqual` ("-" <> expected)
)

fmt1 :: Formatter
fmt1 = Formatter
{ comma: false
, before: 3
, after: 2
, abbreviations: false
, sign: false
, groupSeparator: ','
, decimalSeparator: '.'
}

fmt1' :: Formatter
fmt1' = Formatter
{ comma: true
, before: 0
, after: 2
, abbreviations: false
, sign: false
, groupSeparator: ','
, decimalSeparator: '.'
}

fmt2 :: Formatter
Expand All @@ -69,6 +123,8 @@ fmt2 = Formatter
, after: 4
, abbreviations: false
, sign: true
, groupSeparator: ','
, decimalSeparator: '.'
}

fmt3 :: Formatter
Expand All @@ -78,6 +134,8 @@ fmt3 = Formatter
, after: 2
, abbreviations: true
, sign: true
, groupSeparator: ','
, decimalSeparator: '.'
}

fmt4 :: Formatter
Expand All @@ -87,6 +145,8 @@ fmt4 = Formatter
, after: 0
, abbreviations: false
, sign: false
, groupSeparator: ','
, decimalSeparator: '.'
}

fmt5 :: Formatter
Expand All @@ -96,6 +156,8 @@ fmt5 = Formatter
, after: 4
, abbreviations: false
, sign: false
, groupSeparator: ','
, decimalSeparator: '.'
}

fmt6 :: Formatter
Expand All @@ -105,6 +167,8 @@ fmt6 = Formatter
, after: -1
, abbreviations: false
, sign: false
, groupSeparator: ','
, decimalSeparator: '.'
}

fmt7 :: Formatter
Expand All @@ -114,6 +178,8 @@ fmt7 = Formatter
, after: 16
, abbreviations: false
, sign: false
, groupSeparator: ','
, decimalSeparator: '.'
}

numberformatts :: Array { fmt :: Formatter, str :: String }
Expand All @@ -128,3 +194,6 @@ numberformatts =
, fmt: fmt3
}
]

germanStyleSeparators :: Formatter -> Formatter
germanStyleSeparators = withSeparators { decimalSeparator: ',', groupSeparator: '.' }

0 comments on commit c9e8226

Please sign in to comment.