roundable: Split out the Roundable class.
[altfloat.git] / Data / Floating / Types / Core.hs
blobd3c2ff3911f17f07588f9cb77ea3e5d6af5bbbbc
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.Roundable
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 floating point types (real or complex-valued).
38 -- Minimal complete definition: everything.
39 class Fractional a => Floating a where
40 (**) :: a -> a -> a
41 sqrt :: a -> a
42 acos :: a -> a
43 asin :: a -> a
44 atan :: a -> a
45 cos :: a -> a
46 sin :: a -> a
47 tan :: a -> a
48 acosh :: a -> a
49 asinh :: a -> a
50 atanh :: a -> a
51 cosh :: a -> a
52 sinh :: a -> a
53 tanh :: a -> a
54 exp :: a -> a
55 log :: a -> a
57 -- | Class for real-valued floating point types.
59 -- Minimal complete definition: all except 'pi', 'infinity', 'epsilon' and
60 -- 'nan'.
61 class Floating a => RealFloat a where
62 -- | Fused multiply-add.
63 fma :: a -> a -> a -> a
64 -- | @copysign x y@ computes a value with the magnitude of @x@ but the sign
65 -- of @y@.
66 copysign :: a -> a -> a
67 -- | @nextafter x y@ computes the next representable value after @x@ in the
68 -- direction of @y@.
69 nextafter :: a -> a -> a
70 -- | @atan2 y x@ computes the principal value of the arctangent of @y/x@.
71 -- The signs of the input determine the quadrant of the result.
72 atan2 :: a -> a -> a
73 -- | @fmod x y@ computes @x - n*y@, where @n@ is the integral quotient of
74 -- @x/y@, rounded towards zero.
75 fmod :: a -> a -> a
76 -- | @frem x y@ computes @x - n*y@, where @n@ is the integral quotient of
77 -- @x/y@, rounded to the nearest integer, with halfway values rounded to
78 -- even.
79 frem :: a -> a -> a
80 -- | Euclidean distance function without undue overflow.
81 hypot :: a -> a -> a
82 -- | Cube root.
83 cbrt :: a -> a
84 -- | Base-2 exponential function.
85 exp2 :: a -> a
86 -- | Computes @exp x - 1@ without undue cancellation.
87 expm1 :: a -> a
88 -- | Base-10 logarithm function.
89 log10 :: a -> a
90 -- | Computes @log (x + 1)@ without undue cancellation.
91 log1p :: a -> a
92 -- | Base-2 logarithm function.
93 log2 :: a -> a
94 -- | Error function.
95 erf :: a -> a
96 -- | Complementary error function.
97 erfc :: a -> a
98 -- | Gamma function.
99 gamma :: a -> a
100 -- | Log gamma function.
101 lgamma :: a -> a
102 -- | Round to the nearest integer according to the current rounding
103 -- direction. The default rounding direction is towards the nearest
104 -- integer with halfway values rounded to even. If the resulting value
105 -- differs from the input, the 'Inexact' exception is raised.
106 rint :: a -> a
107 -- | Same as 'rint', except that the 'Inexact' exception is not raised.
108 nearbyint :: a -> a
109 infinity :: a
110 nan :: a
111 epsilon :: a
112 pi :: a
114 infinity = 1/0
115 nan = 0/0
116 epsilon = nextafter 1 infinity - 1
117 pi = 4 * atan 1
119 -- | Class for the basic floating point types.
120 class (Roundable a, RealFloat a) => PrimFloat a where
121 -- | Radix of significand digits.
122 floatRadix :: Num b => a -> b
123 -- | Number of digits in the significand.
124 floatPrecision :: Num b => a -> b
125 -- | Minimum and maximum integers, respectively, such that the radix raised
126 -- to one less than that power is representable as a normalized, finite
127 -- floating point number.
128 floatRange :: Num b => a -> (b, b)
129 classify :: a -> FPClassification
130 -- | Extracts the exponent of a floating point value. If the value is
131 -- subnormal, the result is as if the value were normalized.
132 logb :: a -> a
133 -- | Scales a floating point value by an integral power of the radix.
134 scalb :: Integral b => a -> b -> a
136 infix 6 :+
137 -- | Complex numbers.
138 data (PrimFloat a) => Complex a = !a :+ !a
139 deriving Eq
141 -- | Coercion to floating point types.
142 class FloatConvert a b where
143 -- | Convert to a floating point type. Conversions from integers and real
144 -- types are provided, as well as conversions between floating point types.
145 -- Conversions between floating point types preserve infinities, negative
146 -- zeros and NaNs.
147 toFloating :: a -> b
149 instance FloatConvert Double CDouble where
150 toFloating = unsafeCoerce
152 instance FloatConvert CDouble Double where
153 toFloating = unsafeCoerce
155 instance FloatConvert Float CFloat where
156 toFloating = unsafeCoerce
158 instance FloatConvert CFloat Float where
159 toFloating = unsafeCoerce
161 instance FloatConvert Double Float where
162 toFloating (D# x) = F# (double2Float# x)
164 instance FloatConvert Float Double where
165 toFloating (F# x) = D# (float2Double# x)
167 instance FloatConvert Integer Double where
168 toFloating x = D# (doubleFromInteger x)
170 instance FloatConvert Integer Float where
171 toFloating x = F# (floatFromInteger x)
173 instance Real a => FloatConvert a Double where
174 toFloating x = D# (num /## denom) where
175 !(D# num) = toFloating . numerator . toRational $ x
176 !(D# denom) = toFloating . denominator . toRational $ x
178 instance Real a => FloatConvert a Float where
179 toFloating x = F# (divideFloat# num denom) where
180 !(F# num) = toFloating . numerator . toRational $ x
181 !(F# denom) = toFloating . denominator . toRational $ x
183 instance FloatConvert a a where
184 toFloating = id