Skip to content

Commit 9e7e6bd

Browse files
labels for RealFloat format parameters
1 parent 072ade0 commit 9e7e6bd

File tree

1 file changed

+41
-13
lines changed

1 file changed

+41
-13
lines changed

Data/ByteString/Builder/RealFloat.hs

Lines changed: 41 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,8 @@
88
{-# LANGUAGE TypeApplications #-}
99
{-# LANGUAGE BlockArguments #-}
1010
{-# LANGUAGE NamedFieldPuns #-}
11+
{-# LANGUAGE NoFieldSelectors #-}
12+
{-# LANGUAGE DuplicateRecordFields #-}
1113
-- |
1214
-- Module : Data.ByteString.Builder.RealFloat
1315
-- Copyright : (c) Lawrence Wu 2021
@@ -119,22 +121,45 @@ doubleDec = formatFloating generic
119121
--
120122
-- @since 0.11.2.0
121123
data FloatFormat
122-
= FScientific Word8# R.SpecialStrings -- ^ scientific notation
123-
| FStandard (Maybe Int) R.SpecialStrings -- ^ standard notation with `Maybe Int` digits after the decimal
124-
| FGeneric Word8# (Maybe Int) (Int,Int) R.SpecialStrings -- ^ dispatches to scientific or standard notation based on the exponent
124+
-- | scientific notation
125+
= FScientific
126+
{ eE :: Word8#
127+
, specials :: R.SpecialStrings
128+
}
129+
-- | standard notation with `Maybe Int` digits after the decimal
130+
| FStandard
131+
{ precision :: Maybe Int
132+
, specials :: R.SpecialStrings
133+
}
134+
-- | dispatches to scientific or standard notation based on the exponent
135+
| FGeneric
136+
{ eE :: Word8#
137+
, precision :: Maybe Int
138+
, stdExpoRange :: (Int, Int)
139+
, specials :: R.SpecialStrings
140+
}
125141
deriving Show
126142

127143
fScientific :: Char -> R.SpecialStrings -> FloatFormat
128-
fScientific eE = FScientific (R.asciiRaw $ ord eE)
144+
fScientific eE specials = FScientific
145+
{ eE = R.asciiRaw $ ord eE
146+
, specials
147+
}
129148

130149
fGeneric :: Char -> Maybe Int -> (Int, Int) -> R.SpecialStrings -> FloatFormat
131-
fGeneric eE = FGeneric (R.asciiRaw $ ord eE)
150+
fGeneric eE precision stdExpoRange specials = FGeneric
151+
{ eE = R.asciiRaw $ ord eE
152+
, ..
153+
}
132154

133155
-- | Standard notation with `n` decimal places
134156
--
135157
-- @since 0.11.2.0
136158
standard :: Int -> FloatFormat
137-
standard n = FStandard (Just n) standardSpecialStrings {positiveZero, negativeZero}
159+
standard n = FStandard
160+
{ precision = Just n
161+
, specials = standardSpecialStrings {positiveZero, negativeZero}
162+
}
138163
where
139164
positiveZero = if n == 0
140165
then "0"
@@ -145,7 +170,10 @@ standard n = FStandard (Just n) standardSpecialStrings {positiveZero, negativeZe
145170
--
146171
-- @since 0.11.2.0
147172
standardDefaultPrecision :: FloatFormat
148-
standardDefaultPrecision = FStandard Nothing standardSpecialStrings
173+
standardDefaultPrecision = FStandard
174+
{ precision = Nothing
175+
, specials = standardSpecialStrings
176+
}
149177

150178
-- | Scientific notation with \'default precision\' (decimal places matching `show`)
151179
--
@@ -254,19 +282,19 @@ formatFloating :: forall a mw ew ei.
254282
, R.FromInt ei
255283
) => FloatFormat -> a -> Builder
256284
formatFloating fmt f = case fmt of
257-
FGeneric eE prec (minExpo,maxExpo) ss -> specialsOr ss
285+
FGeneric {stdExpoRange = (minExpo,maxExpo), ..} -> specialsOr specials
258286
if e' >= minExpo && e' <= maxExpo
259-
then std prec
287+
then std precision
260288
else sci eE
261-
FScientific eE ss -> specialsOr ss $ sci eE
262-
FStandard prec ss -> specialsOr ss $ std prec
289+
FScientific {..} -> specialsOr specials $ sci eE
290+
FStandard {..} -> specialsOr specials $ std precision
263291
where
264292
sci eE = BP.primBounded (R.toCharsScientific @a Proxy eE sign m e) ()
265-
std prec = printSign f `mappend` showStandard (toWord64 m) e' prec
293+
std precision = printSign f `mappend` showStandard (toWord64 m) e' precision
266294
e' = R.toInt e + R.decimalLength m
267295
R.FloatingDecimal m e = toD @a mantissa expo
268296
(sign, mantissa, expo) = R.breakdown f
269-
specialsOr ss = flip fromMaybe $ R.toCharsNonNumbersAndZero ss f
297+
specialsOr specials = flip fromMaybe $ R.toCharsNonNumbersAndZero specials f
270298

271299
class ToWord64 a where toWord64 :: a -> Word64
272300
instance ToWord64 Word32 where toWord64 = R.word32ToWord64

0 commit comments

Comments
 (0)