8
8
{-# LANGUAGE TypeApplications #-}
9
9
{-# LANGUAGE BlockArguments #-}
10
10
{-# LANGUAGE NamedFieldPuns #-}
11
+ {-# LANGUAGE NoFieldSelectors #-}
12
+ {-# LANGUAGE DuplicateRecordFields #-}
11
13
-- |
12
14
-- Module : Data.ByteString.Builder.RealFloat
13
15
-- Copyright : (c) Lawrence Wu 2021
@@ -119,22 +121,45 @@ doubleDec = formatFloating generic
119
121
--
120
122
-- @since 0.11.2.0
121
123
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
+ }
125
141
deriving Show
126
142
127
143
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
+ }
129
148
130
149
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
+ }
132
154
133
155
-- | Standard notation with `n` decimal places
134
156
--
135
157
-- @since 0.11.2.0
136
158
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
+ }
138
163
where
139
164
positiveZero = if n == 0
140
165
then " 0"
@@ -145,7 +170,10 @@ standard n = FStandard (Just n) standardSpecialStrings {positiveZero, negativeZe
145
170
--
146
171
-- @since 0.11.2.0
147
172
standardDefaultPrecision :: FloatFormat
148
- standardDefaultPrecision = FStandard Nothing standardSpecialStrings
173
+ standardDefaultPrecision = FStandard
174
+ { precision = Nothing
175
+ , specials = standardSpecialStrings
176
+ }
149
177
150
178
-- | Scientific notation with \'default precision\' (decimal places matching `show`)
151
179
--
@@ -254,19 +282,19 @@ formatFloating :: forall a mw ew ei.
254
282
, R. FromInt ei
255
283
) => FloatFormat -> a -> Builder
256
284
formatFloating fmt f = case fmt of
257
- FGeneric eE prec (minExpo,maxExpo) ss -> specialsOr ss
285
+ FGeneric {stdExpoRange = (minExpo,maxExpo), .. } -> specialsOr specials
258
286
if e' >= minExpo && e' <= maxExpo
259
- then std prec
287
+ then std precision
260
288
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
263
291
where
264
292
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
266
294
e' = R. toInt e + R. decimalLength m
267
295
R. FloatingDecimal m e = toD @ a mantissa expo
268
296
(sign, mantissa, expo) = R. breakdown f
269
- specialsOr ss = flip fromMaybe $ R. toCharsNonNumbersAndZero ss f
297
+ specialsOr specials = flip fromMaybe $ R. toCharsNonNumbersAndZero specials f
270
298
271
299
class ToWord64 a where toWord64 :: a -> Word64
272
300
instance ToWord64 Word32 where toWord64 = R. word32ToWord64
0 commit comments