Fix gratuitous breakage of non-GHC in Data.Fixed.
[ghc-base.git] / Data / Fixed.hs
1 {-# OPTIONS -Wall -fno-warn-unused-binds #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Data.Fixed
6 -- Copyright   :  (c) Ashley Yakeley 2005, 2006, 2009
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  Ashley Yakeley <ashley@semantic.org>
10 -- Stability   :  experimental
11 -- Portability :  portable
12 --
13 -- This module defines a \"Fixed\" type for fixed-precision arithmetic.
14 -- The parameter to Fixed is any type that's an instance of HasResolution.
15 -- HasResolution has a single method that gives the resolution of the Fixed type.
16 --
17 -- This module also contains generalisations of div, mod, and divmod to work
18 -- with any Real instance.
19 --
20 -----------------------------------------------------------------------------
21
22 module Data.Fixed
23 (
24     div',mod',divMod',
25
26     Fixed,HasResolution(..),
27     showFixed,
28     E0,Uni,
29     E1,Deci,
30     E2,Centi,
31     E3,Milli,
32     E6,Micro,
33     E9,Nano,
34     E12,Pico
35 ) where
36
37 import Prelude -- necessary to get dependencies right
38 #ifndef __NHC__
39 import Data.Typeable
40 import Data.Data
41 #endif
42
43 default () -- avoid any defaulting shenanigans
44
45 -- | generalisation of 'div' to any instance of Real
46 div' :: (Real a,Integral b) => a -> a -> b
47 div' n d = floor ((toRational n) / (toRational d))
48
49 -- | generalisation of 'divMod' to any instance of Real
50 divMod' :: (Real a,Integral b) => a -> a -> (b,a)
51 divMod' n d = (f,n - (fromIntegral f) * d) where
52     f = div' n d
53
54 -- | generalisation of 'mod' to any instance of Real
55 mod' :: (Real a) => a -> a -> a
56 mod' n d = n - (fromInteger f) * d where
57     f = div' n d
58
59 -- | The type parameter should be an instance of 'HasResolution'.
60 newtype Fixed a = MkFixed Integer
61 #ifndef __NHC__
62         deriving (Eq,Ord,Typeable)
63 #else
64         deriving (Eq,Ord)
65 #endif
66
67 #ifndef __NHC__
68 -- We do this because the automatically derived Data instance requires (Data a) context.
69 -- Our manual instance has the more general (Typeable a) context.
70 tyFixed :: DataType
71 tyFixed = mkDataType "Data.Fixed.Fixed" [conMkFixed]
72 conMkFixed :: Constr
73 conMkFixed = mkConstr tyFixed "MkFixed" [] Prefix
74 instance (Typeable a) => Data (Fixed a) where
75     gfoldl k z (MkFixed a) = k (z MkFixed) a
76     gunfold k z _ = k (z MkFixed)
77     dataTypeOf _ = tyFixed
78     toConstr _ = conMkFixed
79 #endif
80
81 class HasResolution a where
82     resolution :: p a -> Integer
83
84 withType :: (p a -> f a) -> f a
85 withType foo = foo undefined
86
87 withResolution :: (HasResolution a) => (Integer -> f a) -> f a
88 withResolution foo = withType (foo . resolution)
89
90 instance Enum (Fixed a) where
91     succ (MkFixed a) = MkFixed (succ a)
92     pred (MkFixed a) = MkFixed (pred a)
93     toEnum = MkFixed . toEnum
94     fromEnum (MkFixed a) = fromEnum a
95     enumFrom (MkFixed a) = fmap MkFixed (enumFrom a)
96     enumFromThen (MkFixed a) (MkFixed b) = fmap MkFixed (enumFromThen a b)
97     enumFromTo (MkFixed a) (MkFixed b) = fmap MkFixed (enumFromTo a b)
98     enumFromThenTo (MkFixed a) (MkFixed b) (MkFixed c) = fmap MkFixed (enumFromThenTo a b c)
99
100 instance (HasResolution a) => Num (Fixed a) where
101     (MkFixed a) + (MkFixed b) = MkFixed (a + b)
102     (MkFixed a) - (MkFixed b) = MkFixed (a - b)
103     fa@(MkFixed a) * (MkFixed b) = MkFixed (div (a * b) (resolution fa))
104     negate (MkFixed a) = MkFixed (negate a)
105     abs (MkFixed a) = MkFixed (abs a)
106     signum (MkFixed a) = fromInteger (signum a)
107     fromInteger i = withResolution (\res -> MkFixed (i * res))
108
109 instance (HasResolution a) => Real (Fixed a) where
110     toRational fa@(MkFixed a) = (toRational a) / (toRational (resolution fa))
111
112 instance (HasResolution a) => Fractional (Fixed a) where
113     fa@(MkFixed a) / (MkFixed b) = MkFixed (div (a * (resolution fa)) b)
114     recip fa@(MkFixed a) = MkFixed (div (res * res) a) where
115         res = resolution fa
116     fromRational r = withResolution (\res -> MkFixed (floor (r * (toRational res))))
117
118 instance (HasResolution a) => RealFrac (Fixed a) where
119     properFraction a = (i,a - (fromIntegral i)) where
120         i = truncate a
121     truncate f = truncate (toRational f)
122     round f = round (toRational f)
123     ceiling f = ceiling (toRational f)
124     floor f = floor (toRational f)
125
126 chopZeros :: Integer -> String
127 chopZeros 0 = ""
128 chopZeros a | mod a 10 == 0 = chopZeros (div a 10)
129 chopZeros a = show a
130
131 -- only works for positive a
132 showIntegerZeros :: Bool -> Int -> Integer -> String
133 showIntegerZeros True _ 0 = ""
134 showIntegerZeros chopTrailingZeros digits a = replicate (digits - length s) '0' ++ s' where
135     s = show a
136     s' = if chopTrailingZeros then chopZeros a else s
137
138 withDot :: String -> String
139 withDot "" = ""
140 withDot s = '.':s
141
142 -- | First arg is whether to chop off trailing zeros
143 showFixed :: (HasResolution a) => Bool -> Fixed a -> String
144 showFixed chopTrailingZeros fa@(MkFixed a) | a < 0 = "-" ++ (showFixed chopTrailingZeros (asTypeOf (MkFixed (negate a)) fa))
145 showFixed chopTrailingZeros fa@(MkFixed a) = (show i) ++ (withDot (showIntegerZeros chopTrailingZeros digits fracNum)) where
146     res = resolution fa
147     (i,d) = divMod a res
148     -- enough digits to be unambiguous
149     digits = ceiling (logBase 10 (fromInteger res) :: Double)
150     maxnum = 10 ^ digits
151     fracNum = div (d * maxnum) res
152
153 instance (HasResolution a) => Show (Fixed a) where
154     show = showFixed False
155
156
157 data E0 = E0
158 #ifndef __NHC__
159      deriving (Typeable)
160 #endif
161 instance HasResolution E0 where
162     resolution _ = 1
163 -- | resolution of 1, this works the same as Integer
164 type Uni = Fixed E0
165
166 data E1 = E1
167 #ifndef __NHC__
168      deriving (Typeable)
169 #endif
170 instance HasResolution E1 where
171     resolution _ = 10
172 -- | resolution of 10^-1 = .1
173 type Deci = Fixed E1
174
175 data E2 = E2
176 #ifndef __NHC__
177      deriving (Typeable)
178 #endif
179 instance HasResolution E2 where
180     resolution _ = 100
181 -- | resolution of 10^-2 = .01, useful for many monetary currencies
182 type Centi = Fixed E2
183
184 data E3 = E3
185 #ifndef __NHC__
186      deriving (Typeable)
187 #endif
188 instance HasResolution E3 where
189     resolution _ = 1000
190 -- | resolution of 10^-3 = .001
191 type Milli = Fixed E3
192
193 data E6 = E6
194 #ifndef __NHC__
195      deriving (Typeable)
196 #endif
197 instance HasResolution E6 where
198     resolution _ = 1000000
199 -- | resolution of 10^-6 = .000001
200 type Micro = Fixed E6
201
202 data E9 = E9
203 #ifndef __NHC__
204      deriving (Typeable)
205 #endif
206 instance HasResolution E9 where
207     resolution _ = 1000000000
208 -- | resolution of 10^-9 = .000000001
209 type Nano = Fixed E9
210
211 data E12 = E12
212 #ifndef __NHC__
213      deriving (Typeable)
214 #endif
215 instance HasResolution E12 where
216     resolution _ = 1000000000000
217 -- | resolution of 10^-12 = .000000000001
218 type Pico = Fixed E12