floating: Add epsilon to the RealFloat class.
[altfloat.git] / Data / Floating / Classes.hs
blobfc1561b27c23715d2ca2d70f3d1ec7c18f198114
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 -- | Generic classes for floating point types. The interface is loosely based
10 -- off of the C math library.
11 module Data.Floating.Classes where
13 import Prelude hiding (Floating(..), RealFloat(..), RealFrac(..), Ord(..))
14 import Data.Ratio
15 import Data.Poset
17 -- | Classification of floating point values.
18 data FPClassification = FPInfinite | FPNaN | FPNormal | FPSubNormal | FPZero
19 deriving (Show, Read, Eq, Enum, Bounded)
21 -- | Class for types which can be rounded to integers. The rounding functions
22 -- in the Prelude are inadequate for floating point because they shoehorn their
23 -- results into an integral type.
25 -- Minimal complete definition: 'toIntegral' and 'round'.
26 class (Fractional a, Poset a) => Roundable a where
27 -- | Discards the fractional component from a value. Results in 'Nothing'
28 -- if the result cannot be represented as an integer, such as if the input
29 -- is infinite or NaN.
30 toIntegral :: Integral b => a -> Maybe b
31 ceiling :: a -> a
32 floor :: a -> a
33 truncate :: a -> a
34 round :: a -> a
36 floor x
37 | round x == x = x
38 | otherwise = round $ x - fromRational (1%2)
39 ceiling x
40 | round x == x = x
41 | otherwise = round $ x + fromRational (1%2)
42 truncate x
43 | x < 0 = ceiling x
44 | x > 0 = floor x
45 | otherwise = x
47 -- | Class for floating point types (real or complex-valued).
49 -- Minimal complete definition: everything.
50 class Fractional a => Floating a where
51 (**) :: a -> a -> a
52 sqrt :: a -> a
53 acos :: a -> a
54 asin :: a -> a
55 atan :: a -> a
56 cos :: a -> a
57 sin :: a -> a
58 tan :: a -> a
59 acosh :: a -> a
60 asinh :: a -> a
61 atanh :: a -> a
62 cosh :: a -> a
63 sinh :: a -> a
64 tanh :: a -> a
65 exp :: a -> a
66 log :: a -> a
68 -- | Class for real-valued floating point types.
70 -- Minimal complete definition: all except 'pi', 'infinity', 'epsilon' and
71 -- 'nan'.
72 class Floating a => RealFloat a where
73 -- | Fused multiply-add.
74 fma :: a -> a -> a -> a
75 -- | @copysign x y@ computes a value with the magnitude of @x@ but the sign
76 -- of @y@.
77 copysign :: a -> a -> a
78 -- | @nextafter x y@ computes the next representable value after @x@ in the
79 -- direction of @y@.
80 nextafter :: a -> a -> a
81 -- | @atan2 y x@ computes the principal value of the arctangent of @y/x@.
82 -- The signs of the input determine the quadrant of the result.
83 atan2 :: a -> a -> a
84 -- | @fmod x y@ computes @x - n*y@, where @n@ is the integral quotient of
85 -- @x/y@, rounded towards zero.
86 fmod :: a -> a -> a
87 -- | @frem x y@ computes @x - n*y@, where @n@ is the integral quotient of
88 -- @x/y@, rounded to the nearest integer, with halfway values rounded to
89 -- even.
90 frem :: a -> a -> a
91 -- | Euclidean distance function without undue overflow.
92 hypot :: a -> a -> a
93 -- | Cube root.
94 cbrt :: a -> a
95 -- | Base-2 exponential function.
96 exp2 :: a -> a
97 -- | Computes @exp x - 1@ without undue cancellation.
98 expm1 :: a -> a
99 -- | Base-10 logarithm function.
100 log10 :: a -> a
101 -- | Computes @log (x + 1)@ without undue cancellation.
102 log1p :: a -> a
103 -- | Base-2 logarithm function.
104 log2 :: a -> a
105 -- | Error function.
106 erf :: a -> a
107 -- | Complementary error function.
108 erfc :: a -> a
109 -- | Gamma function.
110 gamma :: a -> a
111 -- | Log gamma function.
112 lgamma :: a -> a
113 -- | Round to the nearest integer according to the current rounding
114 -- direction. The default rounding direction is towards the nearest
115 -- integer with halfway values rounded to even. If the resulting value
116 -- differs from the input, the 'Inexact' exception is raised.
117 rint :: a -> a
118 -- | Same as 'rint', except that the 'Inexact' exception is not raised.
119 nearbyint :: a -> a
120 infinity :: a
121 nan :: a
122 epsilon :: a
123 pi :: a
125 infinity = 1/0
126 nan = 0/0
127 epsilon = nextafter 1 infinity - 1
128 pi = 4 * atan 1
130 -- | Class for the basic floating point types.
131 class (Roundable a, RealFloat a) => PrimFloat a where
132 -- | Radix of significand digits.
133 floatRadix :: Num b => a -> b
134 -- | Number of digits in the significand.
135 floatPrecision :: Num b => a -> b
136 -- | Minimum and maximum integers, respectively, such that the radix raised
137 -- to one less than that power is representable as a normalized, finite
138 -- floating point number.
139 floatRange :: Num b => a -> (b, b)
140 classify :: a -> FPClassification
141 -- | Extracts the exponent of a floating point value. If the value is
142 -- subnormal, the result is as if the value were normalized.
143 logb :: a -> a
144 -- | Scales a floating point value by an integral power of the radix.
145 scalb :: Integral b => a -> b -> a