1313-- Stability : stable
1414-- Portability : portable
1515--
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.
2029--
2130-- This module also contains generalisations of 'div', 'mod', and 'divMod' to
2231-- work with any 'Real' instance.
3140-----------------------------------------------------------------------------
3241
3342module Data.Fixed
34- (
35- div',mod',divMod',
36-
43+ ( -- * The Fixed Type
3744 Fixed (.. ), HasResolution (.. ),
3845 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
3969 E0 ,Uni ,
70+ -- ** 1\/10
4071 E1 ,Deci ,
72+ -- ** 1\/100
4173 E2 ,Centi ,
74+ -- ** 1\/1 000
4275 E3 ,Milli ,
76+ -- ** 1\/1 000 000
4377 E6 ,Micro ,
78+ -- ** 1\/1 000 000 000
4479 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'
4686) where
4787
4888import Data.Data
@@ -67,7 +107,14 @@ mod' :: (Real a) => a -> a -> a
67107mod' n d = n - (fromInteger f) * d where
68108 f = div' n d
69109
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+ -- @
71118newtype Fixed (a :: k ) = MkFixed Integer
72119 deriving ( Eq -- ^ @since 2.01
73120 , Ord -- ^ @since 2.01
@@ -77,6 +124,7 @@ newtype Fixed (a :: k) = MkFixed Integer
77124-- Our manual instance has the more general (Typeable a) context.
78125tyFixed :: DataType
79126tyFixed = mkDataType " Data.Fixed.Fixed" [conMkFixed]
127+
80128conMkFixed :: Constr
81129conMkFixed = mkConstr tyFixed " MkFixed" [] Prefix
82130
@@ -87,7 +135,9 @@ instance (Typeable k,Typeable a) => Data (Fixed (a :: k)) where
87135 dataTypeOf _ = tyFixed
88136 toConstr _ = conMkFixed
89137
138+ -- | Types which can be used as a resolution argument to the 'Fixed' type constructor must implement the 'HasResolution' typeclass.
90139class HasResolution (a :: k ) where
140+ -- | Provide the resolution for a fixed-point fractional number.
91141 resolution :: p a -> Integer
92142
93143-- | For example, @Fixed 1000@ will give you a 'Fixed' with a resolution of 1000.
@@ -109,33 +159,26 @@ withResolution foo = withType (foo . resolution)
109159-- resolution of the 'Fixed' value. For example, when enumerating values of
110160-- resolution @10^-3@ of @type Milli = Fixed E3@,
111161--
112- -- @
113- -- succ (0.000 :: Milli) == 0.001
114- -- @
115- --
162+ -- >>> succ (0.000 :: Milli)
163+ -- 0.001
116164--
117165-- and likewise
118166--
119- -- @
120- -- pred (0.000 :: Milli) == -0.001
121- -- @
122- --
167+ -- >>> pred (0.000 :: Milli)
168+ -- -0.001
123169--
124170-- In other words, 'succ' and 'pred' increment and decrement a fixed-precision
125171-- value by the least amount such that the value's resolution is unchanged.
126172-- For example, @10^-12@ is the smallest (positive) amount that can be added to
127173-- a value of @type Pico = Fixed E12@ without changing its resolution, and so
128174--
129- -- @
130- -- succ (0.000000000000 :: Pico) == 0.000000000001
131- -- @
132- --
175+ -- >>> succ (0.000000000000 :: Pico)
176+ -- 0.000000000001
133177--
134178-- and similarly
135179--
136- -- @
137- -- pred (0.000000000000 :: Pico) == -0.000000000001
138- -- @
180+ -- >>> pred (0.000000000000 :: Pico)
181+ -- -0.000000000001
139182--
140183--
141184-- This is worth bearing in mind when defining 'Fixed' arithmetic sequences. In
@@ -175,6 +218,7 @@ instance Enum (Fixed a) where
175218--
176219-- >>> (0.2 * 0.6 :: Deci) * 0.9 == 0.2 * (0.6 * 0.9)
177220-- False
221+ --
178222-- >>> (0.1 + 0.1 :: Deci) * 0.5 == 0.1 * 0.5 + 0.1 * 0.5
179223-- False
180224instance (HasResolution a ) => Num (Fixed a ) where
@@ -223,6 +267,15 @@ withDot "" = ""
223267withDot s = ' .' : s
224268
225269-- | 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+ --
226279showFixed :: (HasResolution a ) => Bool -> Fixed a -> String
227280showFixed chopTrailingZeros fa@ (MkFixed a) | a < 0 = " -" ++ (showFixed chopTrailingZeros (asTypeOf (MkFixed (negate a)) fa))
228281showFixed chopTrailingZeros fa@ (MkFixed a) = (show i) ++ (withDot (showIntegerZeros chopTrailingZeros digits fracNum)) where
@@ -256,58 +309,135 @@ convertFixed (Number n)
256309 e = ceiling (logBase 10 (fromInteger r) :: Double )
257310convertFixed _ = pfail
258311
312+ -- | Resolution of 1, this works the same as Integer.
259313data E0
260314
261315-- | @since 4.1.0.0
262316instance HasResolution E0 where
263317 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+ --
265329type Uni = Fixed E0
266330
331+ -- | Resolution of 10^-1 = .1
267332data E1
268333
269334-- | @since 4.1.0.0
270335instance HasResolution E1 where
271336 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+ --
273348type Deci = Fixed E1
274349
350+ -- | Resolution of 10^-2 = .01, useful for many monetary currencies
275351data E2
276352
277353-- | @since 4.1.0.0
278354instance HasResolution E2 where
279355 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+ --
281367type Centi = Fixed E2
282368
369+ -- | Resolution of 10^-3 = .001
283370data E3
284371
285372-- | @since 4.1.0.0
286373instance HasResolution E3 where
287374 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+ --
289386type Milli = Fixed E3
290387
388+ -- | Resolution of 10^-6 = .000001
291389data E6
292390
293391-- | @since 2.01
294392instance HasResolution E6 where
295393 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+ --
297405type Micro = Fixed E6
298406
407+ -- | Resolution of 10^-9 = .000000001
299408data E9
300409
301410-- | @since 4.1.0.0
302411instance HasResolution E9 where
303412 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+ --
305424type Nano = Fixed E9
306425
426+ -- | Resolution of 10^-12 = .000000000001
307427data E12
308428
309429-- | @since 2.01
310430instance HasResolution E12 where
311431 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+ --
313443type Pico = Fixed E12
0 commit comments