module Numeric.Eps
( Epsilon(..), nearZero, isNz, roundZero, roundOne, roundZeroOne
) where
import Foreign.C.Types (CFloat, CDouble)
class Num a => Epsilon a where
nearZero :: a -> Bool
instance Epsilon Float where
nearZero a = abs a <= 1e-6
instance Epsilon Double where
nearZero a = abs a <= 1e-12
instance Epsilon CFloat where
nearZero a = abs a <= 1e-6
instance Epsilon CDouble where
nearZero a = abs a <= 1e-12
almostZero, almostOne, isNz :: Epsilon a => a -> Bool
almostZero = nearZero
almostOne x = nearZero (1 x)
isNz x = not (almostZero x)
withDefault :: (t -> Bool) -> t -> t -> t
withDefault q d x | q x = d
| otherwise = x
roundZero, roundOne, roundZeroOne :: Epsilon a => a -> a
roundZero = withDefault almostZero (fromIntegral 0)
roundOne = withDefault almostOne (fromIntegral 1)
with2Defaults :: (t -> Bool) -> (t -> Bool) -> t -> t -> t -> t
with2Defaults q1 q2 d1 d2 x | q1 x = d1
| q2 x = d2
| otherwise = x
roundZeroOne = with2Defaults almostZero almostOne (fromIntegral 0) (fromIntegral 1)