floating: Merge Data.Floating.Types and Data.Floating.Classes.
[altfloat.git] / Data / Floating / Types / Core.hs
blob909376ccada7b529660dd59cb6c16bfc5065f9de
1 {-
2 - Copyright (C) 2009-2010 Nick Bowler.
4 - License BSD2: 2-clause BSD license. See LICENSE for full terms.
5 - This is free software: you are free to change and redistribute it.
6 - There is NO WARRANTY, to the extent permitted by law.
7 -}
9 -- | Core floating point types and classes.
10 {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, OverlappingInstances #-}
11 {-# LANGUAGE MagicHash #-}
12 module Data.Floating.Types.Core where
14 import Prelude hiding
15 (Double, Float, Ord(..), RealFrac(..), Floating(..), RealFloat(..))
16 import Data.Ratio
17 import Data.Poset
19 import GHC.Integer
20 import GHC.Prim
21 import Foreign.C
22 import Unsafe.Coerce
24 -- | The Double type. This is expected to be an identical declaration to
25 -- the one found in "GHC.Types". We redefine it in order to replace all its
26 -- instances.
27 data Double = D# Double#
29 -- | The Float type.
30 data Float = F# Float#
32 -- | Classification of floating point values.
33 data FPClassification = FPInfinite | FPNaN | FPNormal | FPSubNormal | FPZero
34 deriving (Show, Read, Eq, Enum, Bounded)
36 -- | Class for types which can be rounded to integers. The rounding functions
37 -- in the Prelude are inadequate for floating point because they shoehorn their
38 -- results into an integral type.
40 -- Minimal complete definition: 'toIntegral' and 'round'.
41 class (Fractional a, Poset a) => Roundable a where
42 -- | Discards the fractional component from a value. Results in 'Nothing'
43 -- if the result cannot be represented as an integer, such as if the input
44 -- is infinite or NaN.
45 toIntegral :: Integral b => a -> Maybe b
46 ceiling :: a -> a
47 floor :: a -> a
48 truncate :: a -> a
49 round :: a -> a
51 floor x
52 | round x == x = x
53 | otherwise = round $ x - fromRational (1%2)
54 ceiling x
55 | round x == x = x
56 | otherwise = round $ x + fromRational (1%2)
57 truncate x
58 | x < 0 = ceiling x
59 | x > 0 = floor x
60 | otherwise = x
62 -- | Class for floating point types (real or complex-valued).
64 -- Minimal complete definition: everything.
65 class Fractional a => Floating a where
66 (**) :: a -> a -> a
67 sqrt :: a -> a
68 acos :: a -> a
69 asin :: a -> a
70 atan :: a -> a
71 cos :: a -> a
72 sin :: a -> a
73 tan :: a -> a
74 acosh :: a -> a
75 asinh :: a -> a
76 atanh :: a -> a
77 cosh :: a -> a
78 sinh :: a -> a
79 tanh :: a -> a
80 exp :: a -> a
81 log :: a -> a
83 -- | Class for real-valued floating point types.
85 -- Minimal complete definition: all except 'pi', 'infinity', 'epsilon' and
86 -- 'nan'.
87 class Floating a => RealFloat a where
88 -- | Fused multiply-add.
89 fma :: a -> a -> a -> a
90 -- | @copysign x y@ computes a value with the magnitude of @x@ but the sign
91 -- of @y@.
92 copysign :: a -> a -> a
93 -- | @nextafter x y@ computes the next representable value after @x@ in the
94 -- direction of @y@.
95 nextafter :: a -> a -> a
96 -- | @atan2 y x@ computes the principal value of the arctangent of @y/x@.
97 -- The signs of the input determine the quadrant of the result.
98 atan2 :: a -> a -> a
99 -- | @fmod x y@ computes @x - n*y@, where @n@ is the integral quotient of
100 -- @x/y@, rounded towards zero.
101 fmod :: a -> a -> a
102 -- | @frem x y@ computes @x - n*y@, where @n@ is the integral quotient of
103 -- @x/y@, rounded to the nearest integer, with halfway values rounded to
104 -- even.
105 frem :: a -> a -> a
106 -- | Euclidean distance function without undue overflow.
107 hypot :: a -> a -> a
108 -- | Cube root.
109 cbrt :: a -> a
110 -- | Base-2 exponential function.
111 exp2 :: a -> a
112 -- | Computes @exp x - 1@ without undue cancellation.
113 expm1 :: a -> a
114 -- | Base-10 logarithm function.
115 log10 :: a -> a
116 -- | Computes @log (x + 1)@ without undue cancellation.
117 log1p :: a -> a
118 -- | Base-2 logarithm function.
119 log2 :: a -> a
120 -- | Error function.
121 erf :: a -> a
122 -- | Complementary error function.
123 erfc :: a -> a
124 -- | Gamma function.
125 gamma :: a -> a
126 -- | Log gamma function.
127 lgamma :: a -> a
128 -- | Round to the nearest integer according to the current rounding
129 -- direction. The default rounding direction is towards the nearest
130 -- integer with halfway values rounded to even. If the resulting value
131 -- differs from the input, the 'Inexact' exception is raised.
132 rint :: a -> a
133 -- | Same as 'rint', except that the 'Inexact' exception is not raised.
134 nearbyint :: a -> a
135 infinity :: a
136 nan :: a
137 epsilon :: a
138 pi :: a
140 infinity = 1/0
141 nan = 0/0
142 epsilon = nextafter 1 infinity - 1
143 pi = 4 * atan 1
145 -- | Class for the basic floating point types.
146 class (Roundable a, RealFloat a) => PrimFloat a where
147 -- | Radix of significand digits.
148 floatRadix :: Num b => a -> b
149 -- | Number of digits in the significand.
150 floatPrecision :: Num b => a -> b
151 -- | Minimum and maximum integers, respectively, such that the radix raised
152 -- to one less than that power is representable as a normalized, finite
153 -- floating point number.
154 floatRange :: Num b => a -> (b, b)
155 classify :: a -> FPClassification
156 -- | Extracts the exponent of a floating point value. If the value is
157 -- subnormal, the result is as if the value were normalized.
158 logb :: a -> a
159 -- | Scales a floating point value by an integral power of the radix.
160 scalb :: Integral b => a -> b -> a
162 infix 6 :+
163 -- | Complex numbers.
164 data (PrimFloat a) => Complex a = !a :+ !a
165 deriving Eq
167 -- | Coercion to floating point types.
168 class FloatConvert a b where
169 -- | Convert to a floating point type. Conversions from integers and real
170 -- types are provided, as well as conversions between floating point types.
171 -- Conversions between floating point types preserve infinities, negative
172 -- zeros and NaNs.
173 toFloating :: a -> b
175 instance FloatConvert Double CDouble where
176 toFloating = unsafeCoerce
178 instance FloatConvert CDouble Double where
179 toFloating = unsafeCoerce
181 instance FloatConvert Float CFloat where
182 toFloating = unsafeCoerce
184 instance FloatConvert CFloat Float where
185 toFloating = unsafeCoerce
187 instance FloatConvert Double Float where
188 toFloating (D# x) = F# (double2Float# x)
190 instance FloatConvert Float Double where
191 toFloating (F# x) = D# (float2Double# x)
193 instance FloatConvert Integer Double where
194 toFloating x = D# (doubleFromInteger x)
196 instance FloatConvert Integer Float where
197 toFloating x = F# (floatFromInteger x)
199 instance Real a => FloatConvert a Double where
200 toFloating x = D# (num /## denom) where
201 !(D# num) = toFloating . numerator . toRational $ x
202 !(D# denom) = toFloating . denominator . toRational $ x
204 instance Real a => FloatConvert a Float where
205 toFloating x = F# (divideFloat# num denom) where
206 !(F# num) = toFloating . numerator . toRational $ x
207 !(F# denom) = toFloating . denominator . toRational $ x
209 instance FloatConvert a a where
210 toFloating = id