b72a795bfa18d657450e6b1488303d8be0647a04
[altfloat.git] / Data / Floating / Classes.hs
blobb72a795bfa18d657450e6b1488303d8be0647a04
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' and 'nan'.
71 class Floating a => RealFloat a where
72 -- | Fused multiply-add.
73 fma :: a -> a -> a -> a
74 -- | @copysign x y@ computes a value with the magnitude of @x@ but the sign
75 -- of @y@.
76 copysign :: a -> a -> a
77 -- | @nextafter x y@ computes the next representable value after @x@ in the
78 -- direction of @y@.
79 nextafter :: a -> a -> a
80 -- | @atan2 y x@ computes the principal value of the arctangent of @y/x@.
81 -- The signs of the input determine the quadrant of the result.
82 atan2 :: a -> a -> a
83 -- | @fmod x y@ computes @x - n*y@, where @n@ is the integral quotient of
84 -- @x/y@, rounded towards zero.
85 fmod :: a -> a -> a
86 -- | @frem x y@ computes @x - n*y@, where @n@ is the integral quotient of
87 -- @x/y@, rounded to the nearest integer, with halfway values rounded to
88 -- even.
89 frem :: a -> a -> a
90 -- | Euclidean distance function without undue overflow.
91 hypot :: a -> a -> a
92 -- | Cube root.
93 cbrt :: a -> a
94 -- | Base-2 exponential function.
95 exp2 :: a -> a
96 -- | Computes @exp x - 1@ without undue cancellation.
97 expm1 :: a -> a
98 -- | Base-10 logarithm function.
99 log10 :: a -> a
100 -- | Computes @log (x + 1)@ without undue cancellation.
101 log1p :: a -> a
102 -- | Base-2 logarithm function.
103 log2 :: a -> a
104 -- | Error function.
105 erf :: a -> a
106 -- | Complementary error function.
107 erfc :: a -> a
108 -- | Gamma function.
109 gamma :: a -> a
110 -- | Log gamma function.
111 lgamma :: a -> a
112 -- | Round to the nearest integer according to the current rounding
113 -- direction. The default rounding direction is towards the nearest
114 -- integer with halfway values rounded to even. If the resulting value
115 -- differs from the input, the 'Inexact' exception is raised.
116 rint :: a -> a
117 -- | Same as 'rint', except that the 'Inexact' exception is not raised.
118 nearbyint :: a -> a
119 infinity :: a
120 nan :: a
121 pi :: a
123 infinity = 1/0
124 nan = 0/0
125 pi = 4 * atan 1
127 -- | Class for the basic floating point types.
128 class (Roundable a, RealFloat a) => PrimFloat a where
129 -- | Radix of significand digits.
130 floatRadix :: Num b => a -> b
131 -- | Number of digits in the significand.
132 floatPrecision :: Num b => a -> b
133 -- | Minimum and maximum integers, respectively, such that the radix raised
134 -- to one less than that power is representable as a normalized, finite
135 -- floating point number.
136 floatRange :: Num b => a -> (b, b)
137 classify :: a -> FPClassification
138 -- | Extracts the exponent of a floating point value. If the value is
139 -- subnormal, the result is as if the value were normalized.
140 logb :: a -> a
141 -- | Scales a floating point value by an integral power of the radix.
142 scalb :: Integral b => a -> b -> a