ieee754-0.7.9: Utilities for dealing with IEEE floating point numbers

CopyrightCopyright (c) 2010, Patrick Perry <patperry@gmail.com>
LicenseBSD3
MaintainerPatrick Perry <patperry@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Data.AEq

Description

A type class for approximate and exact equalilty comparisons and instances for common data types.

Synopsis

Documentation

class Eq a => AEq a where Source #

Types with approximate and exact equality comparisons.

Methods

(===) :: a -> a -> Bool infix 4 Source #

An exact equality comparison.

For real IEEE types, two values are equivalent in the following cases:

  • both values are +0;
  • both values are -0;
  • both values are nonzero and equal to each other (according to ==);
  • both values are NaN with the same payload and sign.

For complex IEEE types, two values are equivalent if their real and imaginary parts are equivalent.

(~==) :: a -> a -> Bool infix 4 Source #

An approximate equality comparison operator.

For real IEEE types, two values are approximately equal in the following cases:

  • at least half of their significand bits agree;
  • both values are less than epsilon;
  • both values are NaN.

For complex IEEE types, two values are approximately equal in the followiing cases:

  • their magnitudes are approximately equal and the angle between them is less than 32*epsilon;
  • both magnitudes are less than epsilon;
  • both have a NaN real or imaginary part.

Admitedly, the 32 is a bit of a hack. Future versions of the library may switch to a more principled test of the angle.

Instances

AEq Bool Source # 

Methods

(===) :: Bool -> Bool -> Bool Source #

(~==) :: Bool -> Bool -> Bool Source #

AEq Char Source # 

Methods

(===) :: Char -> Char -> Bool Source #

(~==) :: Char -> Char -> Bool Source #

AEq Double Source # 
AEq Float Source # 

Methods

(===) :: Float -> Float -> Bool Source #

(~==) :: Float -> Float -> Bool Source #

AEq Int Source # 

Methods

(===) :: Int -> Int -> Bool Source #

(~==) :: Int -> Int -> Bool Source #

AEq Int8 Source # 

Methods

(===) :: Int8 -> Int8 -> Bool Source #

(~==) :: Int8 -> Int8 -> Bool Source #

AEq Int16 Source # 

Methods

(===) :: Int16 -> Int16 -> Bool Source #

(~==) :: Int16 -> Int16 -> Bool Source #

AEq Int32 Source # 

Methods

(===) :: Int32 -> Int32 -> Bool Source #

(~==) :: Int32 -> Int32 -> Bool Source #

AEq Int64 Source # 

Methods

(===) :: Int64 -> Int64 -> Bool Source #

(~==) :: Int64 -> Int64 -> Bool Source #

AEq Integer Source # 
AEq Ordering Source # 
AEq Word Source # 

Methods

(===) :: Word -> Word -> Bool Source #

(~==) :: Word -> Word -> Bool Source #

AEq Word8 Source # 

Methods

(===) :: Word8 -> Word8 -> Bool Source #

(~==) :: Word8 -> Word8 -> Bool Source #

AEq Word16 Source # 
AEq Word32 Source # 
AEq Word64 Source # 
AEq () Source # 

Methods

(===) :: () -> () -> Bool Source #

(~==) :: () -> () -> Bool Source #

AEq WordPtr Source # 
AEq IntPtr Source # 
AEq CChar Source # 

Methods

(===) :: CChar -> CChar -> Bool Source #

(~==) :: CChar -> CChar -> Bool Source #

AEq CSChar Source # 
AEq CUChar Source # 
AEq CShort Source # 
AEq CUShort Source # 
AEq CInt Source # 

Methods

(===) :: CInt -> CInt -> Bool Source #

(~==) :: CInt -> CInt -> Bool Source #

AEq CUInt Source # 

Methods

(===) :: CUInt -> CUInt -> Bool Source #

(~==) :: CUInt -> CUInt -> Bool Source #

AEq CLong Source # 

Methods

(===) :: CLong -> CLong -> Bool Source #

(~==) :: CLong -> CLong -> Bool Source #

AEq CULong Source # 
AEq CLLong Source # 
AEq CULLong Source # 
AEq CFloat Source # 
AEq CDouble Source # 
AEq CPtrdiff Source # 
AEq CSize Source # 

Methods

(===) :: CSize -> CSize -> Bool Source #

(~==) :: CSize -> CSize -> Bool Source #

AEq CWchar Source # 
AEq CSigAtomic Source # 
AEq CClock Source # 
AEq CTime Source # 

Methods

(===) :: CTime -> CTime -> Bool Source #

(~==) :: CTime -> CTime -> Bool Source #

AEq CIntPtr Source # 
AEq CUIntPtr Source # 
AEq CIntMax Source # 
AEq CUIntMax Source # 
AEq a => AEq [a] Source # 

Methods

(===) :: [a] -> [a] -> Bool Source #

(~==) :: [a] -> [a] -> Bool Source #

AEq a => AEq (Maybe a) Source # 

Methods

(===) :: Maybe a -> Maybe a -> Bool Source #

(~==) :: Maybe a -> Maybe a -> Bool Source #

AEq (StablePtr a) Source # 
AEq (Ptr a) Source # 

Methods

(===) :: Ptr a -> Ptr a -> Bool Source #

(~==) :: Ptr a -> Ptr a -> Bool Source #

AEq (FunPtr a) Source # 

Methods

(===) :: FunPtr a -> FunPtr a -> Bool Source #

(~==) :: FunPtr a -> FunPtr a -> Bool Source #

AEq (Complex Double) Source # 
AEq (Complex Float) Source # 
AEq (Complex CFloat) Source # 
AEq (Complex CDouble) Source # 
AEq (ForeignPtr a) Source # 
(AEq a, AEq b) => AEq (Either a b) Source # 

Methods

(===) :: Either a b -> Either a b -> Bool Source #

(~==) :: Either a b -> Either a b -> Bool Source #

(AEq a, AEq b) => AEq (a, b) Source # 

Methods

(===) :: (a, b) -> (a, b) -> Bool Source #

(~==) :: (a, b) -> (a, b) -> Bool Source #

(AEq a, AEq b, AEq c) => AEq (a, b, c) Source # 

Methods

(===) :: (a, b, c) -> (a, b, c) -> Bool Source #

(~==) :: (a, b, c) -> (a, b, c) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d) => AEq (a, b, c, d) Source # 

Methods

(===) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(~==) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d, AEq e) => AEq (a, b, c, d, e) Source # 

Methods

(===) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(~==) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d, AEq e, AEq f) => AEq (a, b, c, d, e, f) Source # 

Methods

(===) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

(~==) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d, AEq e, AEq f, AEq g) => AEq (a, b, c, d, e, f, g) Source # 

Methods

(===) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

(~==) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d, AEq e, AEq f, AEq g, AEq h) => AEq (a, b, c, d, e, f, g, h) Source # 

Methods

(===) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

(~==) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d, AEq e, AEq f, AEq g, AEq h, AEq i) => AEq (a, b, c, d, e, f, g, h, i) Source # 

Methods

(===) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

(~==) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d, AEq e, AEq f, AEq g, AEq h, AEq i, AEq j) => AEq (a, b, c, d, e, f, g, h, i, j) Source # 

Methods

(===) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

(~==) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d, AEq e, AEq f, AEq g, AEq h, AEq i, AEq j, AEq k) => AEq (a, b, c, d, e, f, g, h, i, j, k) Source # 

Methods

(===) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

(~==) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d, AEq e, AEq f, AEq g, AEq h, AEq i, AEq j, AEq k, AEq l) => AEq (a, b, c, d, e, f, g, h, i, j, k, l) Source # 

Methods

(===) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

(~==) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d, AEq e, AEq f, AEq g, AEq h, AEq i, AEq j, AEq k, AEq l, AEq m) => AEq (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 

Methods

(===) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

(~==) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d, AEq e, AEq f, AEq g, AEq h, AEq i, AEq j, AEq k, AEq l, AEq m, AEq n) => AEq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 

Methods

(===) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

(~==) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

(AEq a, AEq b, AEq c, AEq d, AEq e, AEq f, AEq g, AEq h, AEq i, AEq j, AEq k, AEq l, AEq m, AEq n, AEq o) => AEq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 

Methods

(===) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #

(~==) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #