13
13
-- Stability : stable
14
14
-- Portability : portable
15
15
--
16
- -- This module defines a \"Fixed\" type for fixed-precision arithmetic.
17
- -- The parameter to 'Fixed' is any type that's an instance of 'HasResolution'.
18
- -- 'HasResolution' has a single method that gives the resolution of the 'Fixed'
19
- -- type.
16
+ -- This module defines a 'Fixed' type for working with fixed-point arithmetic.
17
+ -- Fixed-point arithmetic represents fractional numbers with a fixed number of
18
+ -- digits for their fractional part. This is different to the behaviour of the floating-point
19
+ -- number types 'Float' and 'Double', because the number of digits of the
20
+ -- fractional part of 'Float' and 'Double' numbers depends on the size of the number.
21
+ -- Fixed point arithmetic is frequently used in financial mathematics, where they
22
+ -- are used for representing decimal currencies.
23
+ --
24
+ -- The type 'Fixed' is used for fixed-point fractional numbers, which are internally
25
+ -- represented as an 'Integer'. The type 'Fixed' takes one parameter, which should implement
26
+ -- the typeclass 'HasResolution', to specify the number of digits of the fractional part.
27
+ -- This module provides instances of the `HasResolution` typeclass for arbitrary typelevel
28
+ -- natural numbers, and for some canonical important fixed-point representations.
20
29
--
21
30
-- This module also contains generalisations of 'div', 'mod', and 'divMod' to
22
31
-- work with any 'Real' instance.
31
40
-----------------------------------------------------------------------------
32
41
33
42
module Data.Fixed
34
- (
35
- div',mod',divMod',
36
-
43
+ ( -- * The Fixed Type
37
44
Fixed (.. ), HasResolution (.. ),
38
45
showFixed,
46
+ -- * Resolution \/ Scaling Factors
47
+ -- | The resolution or scaling factor determines the number of digits in the fractional part.
48
+ --
49
+ -- +------------+----------------------+--------------------------+--------------------------+
50
+ -- | Resolution | Scaling Factor | Synonym for \"Fixed EX\" | show (12345 :: Fixed EX) |
51
+ -- +============+======================+==========================+==========================+
52
+ -- | E0 | 1\/1 | Uni | 12345.0 |
53
+ -- +------------+----------------------+--------------------------+--------------------------+
54
+ -- | E1 | 1\/10 | Deci | 1234.5 |
55
+ -- +------------+----------------------+--------------------------+--------------------------+
56
+ -- | E2 | 1\/100 | Centi | 123.45 |
57
+ -- +------------+----------------------+--------------------------+--------------------------+
58
+ -- | E3 | 1\/1 000 | Milli | 12.345 |
59
+ -- +------------+----------------------+--------------------------+--------------------------+
60
+ -- | E6 | 1\/1 000 000 | Micro | 0.012345 |
61
+ -- +------------+----------------------+--------------------------+--------------------------+
62
+ -- | E9 | 1\/1 000 000 000 | Nano | 0.000012345 |
63
+ -- +------------+----------------------+--------------------------+--------------------------+
64
+ -- | E12 | 1\/1 000 000 000 000 | Pico | 0.000000012345 |
65
+ -- +------------+----------------------+--------------------------+--------------------------+
66
+ --
67
+
68
+ -- ** 1\/1
39
69
E0 ,Uni ,
70
+ -- ** 1\/10
40
71
E1 ,Deci ,
72
+ -- ** 1\/100
41
73
E2 ,Centi ,
74
+ -- ** 1\/1 000
42
75
E3 ,Milli ,
76
+ -- ** 1\/1 000 000
43
77
E6 ,Micro ,
78
+ -- ** 1\/1 000 000 000
44
79
E9 ,Nano ,
45
- E12 ,Pico
80
+ -- ** 1\/1 000 000 000 000
81
+ E12 ,Pico ,
82
+ -- * Generalized Functions on Real's
83
+ div',
84
+ mod',
85
+ divMod'
46
86
) where
47
87
48
88
import Data.Data
@@ -67,7 +107,14 @@ mod' :: (Real a) => a -> a -> a
67
107
mod' n d = n - (fromInteger f) * d where
68
108
f = div' n d
69
109
70
- -- | The type parameter should be an instance of 'HasResolution'.
110
+ -- | The type of fixed-point fractional numbers.
111
+ -- The type parameter specifies the number of digits of the fractional part and should be an instance of the 'HasResolution' typeclass.
112
+ --
113
+ -- === __Examples__
114
+ --
115
+ -- @
116
+ -- MkFixed 12345 :: Fixed E3
117
+ -- @
71
118
newtype Fixed (a :: k ) = MkFixed Integer
72
119
deriving ( Eq -- ^ @since 2.01
73
120
, Ord -- ^ @since 2.01
@@ -77,6 +124,7 @@ newtype Fixed (a :: k) = MkFixed Integer
77
124
-- Our manual instance has the more general (Typeable a) context.
78
125
tyFixed :: DataType
79
126
tyFixed = mkDataType " Data.Fixed.Fixed" [conMkFixed]
127
+
80
128
conMkFixed :: Constr
81
129
conMkFixed = mkConstr tyFixed " MkFixed" [] Prefix
82
130
@@ -87,7 +135,9 @@ instance (Typeable k,Typeable a) => Data (Fixed (a :: k)) where
87
135
dataTypeOf _ = tyFixed
88
136
toConstr _ = conMkFixed
89
137
138
+ -- | Types which can be used as a resolution argument to the 'Fixed' type constructor must implement the 'HasResolution' typeclass.
90
139
class HasResolution (a :: k ) where
140
+ -- | Provide the resolution for a fixed-point fractional number.
91
141
resolution :: p a -> Integer
92
142
93
143
-- | For example, @Fixed 1000@ will give you a 'Fixed' with a resolution of 1000.
@@ -109,33 +159,26 @@ withResolution foo = withType (foo . resolution)
109
159
-- resolution of the 'Fixed' value. For example, when enumerating values of
110
160
-- resolution @10^-3@ of @type Milli = Fixed E3@,
111
161
--
112
- -- @
113
- -- succ (0.000 :: Milli) == 0.001
114
- -- @
115
- --
162
+ -- >>> succ (0.000 :: Milli)
163
+ -- 0.001
116
164
--
117
165
-- and likewise
118
166
--
119
- -- @
120
- -- pred (0.000 :: Milli) == -0.001
121
- -- @
122
- --
167
+ -- >>> pred (0.000 :: Milli)
168
+ -- -0.001
123
169
--
124
170
-- In other words, 'succ' and 'pred' increment and decrement a fixed-precision
125
171
-- value by the least amount such that the value's resolution is unchanged.
126
172
-- For example, @10^-12@ is the smallest (positive) amount that can be added to
127
173
-- a value of @type Pico = Fixed E12@ without changing its resolution, and so
128
174
--
129
- -- @
130
- -- succ (0.000000000000 :: Pico) == 0.000000000001
131
- -- @
132
- --
175
+ -- >>> succ (0.000000000000 :: Pico)
176
+ -- 0.000000000001
133
177
--
134
178
-- and similarly
135
179
--
136
- -- @
137
- -- pred (0.000000000000 :: Pico) == -0.000000000001
138
- -- @
180
+ -- >>> pred (0.000000000000 :: Pico)
181
+ -- -0.000000000001
139
182
--
140
183
--
141
184
-- This is worth bearing in mind when defining 'Fixed' arithmetic sequences. In
@@ -175,6 +218,7 @@ instance Enum (Fixed a) where
175
218
--
176
219
-- >>> (0.2 * 0.6 :: Deci) * 0.9 == 0.2 * (0.6 * 0.9)
177
220
-- False
221
+ --
178
222
-- >>> (0.1 + 0.1 :: Deci) * 0.5 == 0.1 * 0.5 + 0.1 * 0.5
179
223
-- False
180
224
instance (HasResolution a ) => Num (Fixed a ) where
@@ -223,6 +267,15 @@ withDot "" = ""
223
267
withDot s = ' .' : s
224
268
225
269
-- | First arg is whether to chop off trailing zeros
270
+ --
271
+ -- === __Examples__
272
+ --
273
+ -- >>> showFixed True (MkFixed 10000 :: Fixed E3)
274
+ -- "10"
275
+ --
276
+ -- >>> showFixed False (MkFixed 10000 :: Fixed E3)
277
+ -- "10.000"
278
+ --
226
279
showFixed :: (HasResolution a ) => Bool -> Fixed a -> String
227
280
showFixed chopTrailingZeros fa@ (MkFixed a) | a < 0 = " -" ++ (showFixed chopTrailingZeros (asTypeOf (MkFixed (negate a)) fa))
228
281
showFixed chopTrailingZeros fa@ (MkFixed a) = (show i) ++ (withDot (showIntegerZeros chopTrailingZeros digits fracNum)) where
@@ -256,58 +309,135 @@ convertFixed (Number n)
256
309
e = ceiling (logBase 10 (fromInteger r) :: Double )
257
310
convertFixed _ = pfail
258
311
312
+ -- | Resolution of 1, this works the same as Integer.
259
313
data E0
260
314
261
315
-- | @since 4.1.0.0
262
316
instance HasResolution E0 where
263
317
resolution _ = 1
264
- -- | resolution of 1, this works the same as Integer
318
+
319
+ -- | Resolution of 1, this works the same as Integer.
320
+ --
321
+ -- === __Examples__
322
+ --
323
+ -- >>> show (MkFixed 12345 :: Fixed E0)
324
+ -- "12345.0"
325
+ --
326
+ -- >>> show (MkFixed 12345 :: Uni)
327
+ -- "12345.0"
328
+ --
265
329
type Uni = Fixed E0
266
330
331
+ -- | Resolution of 10^-1 = .1
267
332
data E1
268
333
269
334
-- | @since 4.1.0.0
270
335
instance HasResolution E1 where
271
336
resolution _ = 10
272
- -- | resolution of 10^-1 = .1
337
+
338
+ -- | Resolution of 10^-1 = .1
339
+ --
340
+ -- === __Examples__
341
+ --
342
+ -- >>> show (MkFixed 12345 :: Fixed E1)
343
+ -- "1234.5"
344
+ --
345
+ -- >>> show (MkFixed 12345 :: Deci)
346
+ -- "1234.5"
347
+ --
273
348
type Deci = Fixed E1
274
349
350
+ -- | Resolution of 10^-2 = .01, useful for many monetary currencies
275
351
data E2
276
352
277
353
-- | @since 4.1.0.0
278
354
instance HasResolution E2 where
279
355
resolution _ = 100
280
- -- | resolution of 10^-2 = .01, useful for many monetary currencies
356
+
357
+ -- | Resolution of 10^-2 = .01, useful for many monetary currencies
358
+ --
359
+ -- === __Examples__
360
+ --
361
+ -- >>> show (MkFixed 12345 :: Fixed E2)
362
+ -- "123.45"
363
+ --
364
+ -- >>> show (MkFixed 12345 :: Centi)
365
+ -- "123.45"
366
+ --
281
367
type Centi = Fixed E2
282
368
369
+ -- | Resolution of 10^-3 = .001
283
370
data E3
284
371
285
372
-- | @since 4.1.0.0
286
373
instance HasResolution E3 where
287
374
resolution _ = 1000
288
- -- | resolution of 10^-3 = .001
375
+
376
+ -- | Resolution of 10^-3 = .001
377
+ --
378
+ -- === __Examples__
379
+ --
380
+ -- >>> show (MkFixed 12345 :: Fixed E3)
381
+ -- "12.345"
382
+ --
383
+ -- >>> show (MkFixed 12345 :: Milli)
384
+ -- "12.345"
385
+ --
289
386
type Milli = Fixed E3
290
387
388
+ -- | Resolution of 10^-6 = .000001
291
389
data E6
292
390
293
391
-- | @since 2.01
294
392
instance HasResolution E6 where
295
393
resolution _ = 1000000
296
- -- | resolution of 10^-6 = .000001
394
+
395
+ -- | Resolution of 10^-6 = .000001
396
+ --
397
+ -- === __Examples__
398
+ --
399
+ -- >>> show (MkFixed 12345 :: Fixed E6)
400
+ -- "0.012345"
401
+ --
402
+ -- >>> show (MkFixed 12345 :: Micro)
403
+ -- "0.012345"
404
+ --
297
405
type Micro = Fixed E6
298
406
407
+ -- | Resolution of 10^-9 = .000000001
299
408
data E9
300
409
301
410
-- | @since 4.1.0.0
302
411
instance HasResolution E9 where
303
412
resolution _ = 1000000000
304
- -- | resolution of 10^-9 = .000000001
413
+
414
+ -- | Resolution of 10^-9 = .000000001
415
+ --
416
+ -- === __Examples__
417
+ --
418
+ -- >>> show (MkFixed 12345 :: Fixed E9)
419
+ -- "0.000012345"
420
+ --
421
+ -- >>> show (MkFixed 12345 :: Nano)
422
+ -- "0.000012345"
423
+ --
305
424
type Nano = Fixed E9
306
425
426
+ -- | Resolution of 10^-12 = .000000000001
307
427
data E12
308
428
309
429
-- | @since 2.01
310
430
instance HasResolution E12 where
311
431
resolution _ = 1000000000000
312
- -- | resolution of 10^-12 = .000000000001
432
+
433
+ -- | Resolution of 10^-12 = .000000000001
434
+ --
435
+ -- === __Examples__
436
+ --
437
+ -- >>> show (MkFixed 12345 :: Fixed E12)
438
+ -- "0.000000012345"
439
+ --
440
+ -- >>> show (MkFixed 12345 :: Pico)
441
+ -- "0.000000012345"
442
+ --
313
443
type Pico = Fixed E12
0 commit comments