Moved Data.Poset to ordered; reflect this change.
[altfloat.git] / Data / Floating / Types / Core.hs
blobcc4bfef43ffa4501d8abb68b00326d85521f43e9
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, RealFrac(..), Floating(..), RealFloat(..))
17 import Data.Ratio
18 import Data.Roundable
19 import Data.Poset
21 import GHC.Integer
22 import GHC.Prim
23 import Foreign.C
24 import Unsafe.Coerce
26 -- | The Double type. This is expected to be an identical declaration to
27 -- the one found in "GHC.Types". We redefine it in order to replace all its
28 -- instances.
29 data Double = D# Double#
31 -- | The Float type.
32 data Float = F# Float#
34 -- | Classification of floating point values.
35 data FPClassification = FPInfinite | FPNaN | FPNormal | FPSubNormal | FPZero
36 deriving (Show, Read, Eq, Enum, Bounded)
38 -- | Class for floating point types (real or complex-valued).
40 -- Minimal complete definition: everything.
41 class Fractional a => Floating a where
42 (**) :: a -> a -> a
43 sqrt :: a -> a
44 acos :: a -> a
45 asin :: a -> a
46 atan :: a -> a
47 cos :: a -> a
48 sin :: a -> a
49 tan :: a -> a
50 acosh :: a -> a
51 asinh :: a -> a
52 atanh :: a -> a
53 cosh :: a -> a
54 sinh :: a -> a
55 tanh :: a -> a
56 exp :: a -> a
57 log :: a -> a
59 -- | Class for real-valued floating point types.
61 -- Minimal complete definition: all except 'pi', 'infinity', 'epsilon' and
62 -- 'nan'.
63 class Floating a => RealFloat a where
64 -- | Fused multiply-add.
65 fma :: a -> a -> a -> a
66 -- | @copysign x y@ computes a value with the magnitude of @x@ but the sign
67 -- of @y@.
68 copysign :: a -> a -> a
69 -- | @nextafter x y@ computes the next representable value after @x@ in the
70 -- direction of @y@.
71 nextafter :: a -> a -> a
72 -- | @atan2 y x@ computes the principal value of the arctangent of @y/x@.
73 -- The signs of the input determine the quadrant of the result.
74 atan2 :: a -> a -> a
75 -- | @fmod x y@ computes @x - n*y@, where @n@ is the integral quotient of
76 -- @x/y@, rounded towards zero.
77 fmod :: a -> a -> a
78 -- | @frem x y@ computes @x - n*y@, where @n@ is the integral quotient of
79 -- @x/y@, rounded to the nearest integer, with halfway values rounded to
80 -- even.
81 frem :: a -> a -> a
82 -- | Euclidean distance function without undue overflow.
83 hypot :: a -> a -> a
84 -- | Cube root.
85 cbrt :: a -> a
86 -- | Base-2 exponential function.
87 exp2 :: a -> a
88 -- | Computes @exp x - 1@ without undue cancellation.
89 expm1 :: a -> a
90 -- | Base-10 logarithm function.
91 log10 :: a -> a
92 -- | Computes @log (x + 1)@ without undue cancellation.
93 log1p :: a -> a
94 -- | Base-2 logarithm function.
95 log2 :: a -> a
96 -- | Error function.
97 erf :: a -> a
98 -- | Complementary error function.
99 erfc :: a -> a
100 -- | Gamma function.
101 gamma :: a -> a
102 -- | Log gamma function.
103 lgamma :: a -> a
104 -- | Round to the nearest integer according to the current rounding
105 -- direction. The default rounding direction is towards the nearest
106 -- integer with halfway values rounded to even. If the resulting value
107 -- differs from the input, the 'Inexact' exception is raised.
108 rint :: a -> a
109 -- | Same as 'rint', except that the 'Inexact' exception is not raised.
110 nearbyint :: a -> a
111 infinity :: a
112 nan :: a
113 epsilon :: a
114 pi :: a
116 infinity = 1/0
117 nan = 0/0
118 epsilon = nextafter 1 infinity - 1
119 pi = 4 * atan 1
121 -- | Class for the basic floating point types.
122 class (Roundable a, RealFloat a) => PrimFloat a where
123 -- | Radix of significand digits.
124 floatRadix :: Num b => a -> b
125 -- | Number of digits in the significand.
126 floatPrecision :: Num b => a -> b
127 -- | Minimum and maximum integers, respectively, such that the radix raised
128 -- to one less than that power is representable as a normalized, finite
129 -- floating point number.
130 floatRange :: Num b => a -> (b, b)
131 classify :: a -> FPClassification
132 -- | Extracts the exponent of a floating point value. If the value is
133 -- subnormal, the result is as if the value were normalized.
134 logb :: a -> a
135 -- | Scales a floating point value by an integral power of the radix.
136 scalb :: Integral b => a -> b -> a
138 infix 6 :+
139 -- | Complex numbers.
140 data (PrimFloat a) => Complex a = !a :+ !a
141 deriving Eq
143 -- | Coercion to floating point types.
144 class FloatConvert a b where
145 -- | Convert to a floating point type. Conversions from integers and real
146 -- types are provided, as well as conversions between floating point types.
147 -- Conversions between floating point types preserve infinities, negative
148 -- zeros and NaNs.
149 toFloating :: a -> b
151 instance FloatConvert Double CDouble where
152 toFloating = unsafeCoerce
154 instance FloatConvert CDouble Double where
155 toFloating = unsafeCoerce
157 instance FloatConvert Float CFloat where
158 toFloating = unsafeCoerce
160 instance FloatConvert CFloat Float where
161 toFloating = unsafeCoerce
163 instance FloatConvert Double Float where
164 toFloating (D# x) = F# (double2Float# x)
166 instance FloatConvert Float Double where
167 toFloating (F# x) = D# (float2Double# x)
169 instance FloatConvert Integer Double where
170 toFloating x = D# (doubleFromInteger x)
172 instance FloatConvert Integer Float where
173 toFloating x = F# (floatFromInteger x)
175 instance Real a => FloatConvert a Double where
176 toFloating x = D# (num /## denom) where
177 !(D# num) = toFloating . numerator . toRational $ x
178 !(D# denom) = toFloating . denominator . toRational $ x
180 instance Real a => FloatConvert a Float where
181 toFloating x = F# (divideFloat# num denom) where
182 !(F# num) = toFloating . numerator . toRational $ x
183 !(F# denom) = toFloating . denominator . toRational $ x
185 instance FloatConvert a a where
186 toFloating = id