#if defined(__GLASGOW_HASKELL) && __GLASGOW_HASKELL__ >= 704
#endif
module Numeric.Interval.Kaucher
( Interval(..)
, (...)
, interval
, whole
, empty
, null
, singleton
, elem
, notElem
, inf
, sup
, singular
, width
, midpoint
, intersection
, hull
, bisect
, magnitude
, mignitude
, distance
, contains
, isSubsetOf
, certainly, (<!), (<=!), (==!), (>=!), (>!)
, possibly, (<?), (<=?), (==?), (>=?), (>?)
, clamp
, idouble
, ifloat
) where
import Control.Applicative hiding (empty)
import Control.Exception as Exception
import Data.Data
import Data.Distributive
import Data.Foldable hiding (minimum, maximum, elem, notElem)
import Data.Function (on)
import Data.Monoid
import Data.Traversable
#if defined(__GLASGOW_HASKELL) && __GLASGOW_HASKELL__ >= 704
import GHC.Generics
#endif
import Numeric.Interval.Exception
import Prelude hiding (null, elem, notElem)
data Interval a = I !a !a deriving
( Data
, Typeable
#if defined(__GLASGOW_HASKELL) && __GLASGOW_HASKELL__ >= 704
, Generic
#if __GLASGOW_HASKELL__ >= 706
, Generic1
#endif
#endif
)
instance Functor Interval where
fmap f (I a b) = I (f a) (f b)
instance Foldable Interval where
foldMap f (I a b) = f a `mappend` f b
instance Traversable Interval where
traverse f (I a b) = I <$> f a <*> f b
instance Applicative Interval where
pure a = I a a
I f g <*> I a b = I (f a) (g b)
instance Monad Interval where
return a = I a a
I a b >>= f = I a' b' where
I a' _ = f a
I _ b' = f b
instance Distributive Interval where
distribute f = fmap inf f ... fmap sup f
infix 3 ...
negInfinity :: Fractional a => a
negInfinity = (1)/0
posInfinity :: Fractional a => a
posInfinity = 1/0
nan :: Fractional a => a
nan = 0/0
fmod :: RealFrac a => a -> a -> a
fmod a b = a q*b where
q = realToFrac (truncate $ a / b :: Integer)
(...) :: a -> a -> Interval a
(...) = I
interval :: Ord a => a -> a -> Maybe (Interval a)
interval a b
| a <= b = Just $ I a b
| otherwise = Nothing
whole :: Fractional a => Interval a
whole = negInfinity ... posInfinity
empty :: Fractional a => Interval a
empty = nan ... nan
null :: Ord a => Interval a -> Bool
null x = not (inf x <= sup x)
singleton :: a -> Interval a
singleton a = a ... a
inf :: Interval a -> a
inf (I a _) = a
sup :: Interval a -> a
sup (I _ b) = b
singular :: Ord a => Interval a -> Bool
singular x = not (null x) && inf x == sup x
instance Eq a => Eq (Interval a) where
(==) = (==!)
instance Show a => Show (Interval a) where
showsPrec n (I a b) =
showParen (n > 3) $
showsPrec 3 a .
showString " ... " .
showsPrec 3 b
width :: Num a => Interval a -> a
width (I a b) = b a
magnitude :: (Num a, Ord a) => Interval a -> a
magnitude = sup . abs
mignitude :: (Num a, Ord a) => Interval a -> a
mignitude = inf . abs
distance :: (Num a, Ord a) => Interval a -> Interval a -> a
distance i1 i2 = mignitude (i1 i2)
instance (Num a, Ord a) => Num (Interval a) where
I a b + I a' b' = (a + a') ... (b + b')
I a b I a' b' = (a b') ... (b a')
I a b * I a' b' =
minimum [a * a', a * b', b * a', b * b']
...
maximum [a * a', a * b', b * a', b * b']
abs x@(I a b)
| a >= 0 = x
| b <= 0 = negate x
| b > 0 && a < 0 = 0 ... max ( a) b
| otherwise = x
signum = increasing signum
fromInteger i = singleton (fromInteger i)
bisect :: Fractional a => Interval a -> (Interval a, Interval a)
bisect x = (inf x ... m, m ... sup x) where m = midpoint x
midpoint :: Fractional a => Interval a -> a
midpoint x = inf x + (sup x inf x) / 2
elem :: Ord a => a -> Interval a -> Bool
elem x xs = x >= inf xs && x <= sup xs
notElem :: Ord a => a -> Interval a -> Bool
notElem x xs = not (elem x xs)
instance Real a => Real (Interval a) where
toRational x
| null x = Exception.throw EmptyInterval
| otherwise = a + (b a) / 2
where
a = toRational (inf x)
b = toRational (sup x)
instance Ord a => Ord (Interval a) where
compare x y
| sup x < inf y = LT
| inf x > sup y = GT
| sup x == inf y && inf x == sup y = EQ
| otherwise = Exception.throw AmbiguousComparison
max (I a b) (I a' b') = max a a' ... max b b'
min (I a b) (I a' b') = min a a' ... min b b'
divNonZero :: (Fractional a, Ord a) => Interval a -> Interval a -> Interval a
divNonZero (I a b) (I a' b') =
minimum [a / a', a / b', b / a', b / b']
...
maximum [a / a', a / b', b / a', b / b']
divPositive :: (Fractional a, Ord a) => Interval a -> a -> Interval a
divPositive x@(I a b) y
| a == 0 && b == 0 = x
| b < 0 = negInfinity ... ( b / y)
| a < 0 = whole
| otherwise = (a / y) ... posInfinity
divNegative :: (Fractional a, Ord a) => Interval a -> a -> Interval a
divNegative x@(I a b) y
| a == 0 && b == 0 = x
| b < 0 = (b / y) ... posInfinity
| a < 0 = whole
| otherwise = negInfinity ... (a / y)
divZero :: (Fractional a, Ord a) => Interval a -> Interval a
divZero x
| inf x == 0 && sup x == 0 = x
| otherwise = whole
instance (Fractional a, Ord a) => Fractional (Interval a) where
x / y
| 0 `notElem` y = divNonZero x y
| iz && sz = empty
| iz = divPositive x (inf y)
| sz = divNegative x (sup y)
| otherwise = divZero x
where
iz = inf y == 0
sz = sup y == 0
recip (I a b) = on min recip a b ... on max recip a b
fromRational r = let r' = fromRational r in r' ... r'
instance RealFrac a => RealFrac (Interval a) where
properFraction x = (b, x fromIntegral b)
where
b = truncate (midpoint x)
ceiling x = ceiling (sup x)
floor x = floor (inf x)
round x = round (midpoint x)
truncate x = truncate (midpoint x)
instance (RealFloat a, Ord a) => Floating (Interval a) where
pi = singleton pi
exp = increasing exp
log (I a b) = (if a > 0 then log a else negInfinity) ... log b
cos x
| null x = empty
| width t >= pi = (1) ... 1
| inf t >= pi = cos (t pi)
| sup t <= pi = decreasing cos t
| sup t <= 2 * pi = (1) ... cos ((pi * 2 sup t) `min` inf t)
| otherwise = (1) ... 1
where
t = fmod x (pi * 2)
sin x
| null x = empty
| otherwise = cos (x pi / 2)
tan x
| null x = empty
| inf t' <= pi / 2 || sup t' >= pi / 2 = whole
| otherwise = increasing tan x
where
t = x `fmod` pi
t' | t >= pi / 2 = t pi
| otherwise = t
asin x@(I a b)
| null x || b < 1 || a > 1 = empty
| otherwise =
(if a <= 1 then halfPi else asin a)
...
(if b >= 1 then halfPi else asin b)
where
halfPi = pi / 2
acos x@(I a b)
| null x || b < 1 || a > 1 = empty
| otherwise =
(if b >= 1 then 0 else acos b)
...
(if a < 1 then pi else acos a)
atan = increasing atan
sinh = increasing sinh
cosh x@(I a b)
| null x = empty
| b < 0 = decreasing cosh x
| a >= 0 = increasing cosh x
| otherwise = I 0 $ cosh $ if a > b
then a
else b
tanh = increasing tanh
asinh = increasing asinh
acosh x@(I a b)
| null x || b < 1 = empty
| otherwise = I lo $ acosh b
where lo | a <= 1 = 0
| otherwise = acosh a
atanh x@(I a b)
| null x || b < 1 || a > 1 = empty
| otherwise =
(if a <= 1 then negInfinity else atanh a)
...
(if b >= 1 then posInfinity else atanh b)
increasing :: (a -> b) -> Interval a -> Interval b
increasing f (I a b) = f a ... f b
decreasing :: (a -> b) -> Interval a -> Interval b
decreasing f (I a b) = f b ... f a
instance RealFloat a => RealFloat (Interval a) where
floatRadix = floatRadix . midpoint
floatDigits = floatDigits . midpoint
floatRange = floatRange . midpoint
decodeFloat = decodeFloat . midpoint
encodeFloat m e = singleton (encodeFloat m e)
exponent = exponent . midpoint
significand x = min a b ... max a b
where
(_ ,em) = decodeFloat (midpoint x)
(mi,ei) = decodeFloat (inf x)
(ms,es) = decodeFloat (sup x)
a = encodeFloat mi (ei em floatDigits x)
b = encodeFloat ms (es em floatDigits x)
scaleFloat n x = scaleFloat n (inf x) ... scaleFloat n (sup x)
isNaN x = isNaN (inf x) || isNaN (sup x)
isInfinite x = isInfinite (inf x) || isInfinite (sup x)
isDenormalized x = isDenormalized (inf x) || isDenormalized (sup x)
isNegativeZero x = not (inf x > 0)
&& not (sup x < 0)
&& ( (sup x == 0 && (inf x < 0 || isNegativeZero (inf x)))
|| (inf x == 0 && isNegativeZero (inf x))
|| (inf x < 0 && sup x >= 0))
isIEEE x = isIEEE (inf x) && isIEEE (sup x)
atan2 = error "unimplemented"
intersection :: (Fractional a, Ord a) => Interval a -> Interval a -> Interval a
intersection x@(I a b) y@(I a' b')
| x /=! y = empty
| otherwise = max a a' ... min b b'
hull :: Ord a => Interval a -> Interval a -> Interval a
hull x@(I a b) y@(I a' b')
| null x = y
| null y = x
| otherwise = min a a' ... max b b'
(<!) :: Ord a => Interval a -> Interval a -> Bool
x <! y = sup x < inf y
(<=!) :: Ord a => Interval a -> Interval a -> Bool
x <=! y = sup x <= inf y
(==!) :: Eq a => Interval a -> Interval a -> Bool
x ==! y = sup x == inf y && inf x == sup y
(/=!) :: Ord a => Interval a -> Interval a -> Bool
x /=! y = sup x < inf y || inf x > sup y
(>!) :: Ord a => Interval a -> Interval a -> Bool
x >! y = inf x > sup y
(>=!) :: Ord a => Interval a -> Interval a -> Bool
x >=! y = inf x >= sup y
certainly :: Ord a => (forall b. Ord b => b -> b -> Bool) -> Interval a -> Interval a -> Bool
certainly cmp l r
| lt && eq && gt = True
| lt && eq = l <=! r
| lt && gt = l /=! r
| lt = l <! r
| eq && gt = l >=! r
| eq = l ==! r
| gt = l >! r
| otherwise = False
where
lt = cmp LT EQ
eq = cmp EQ EQ
gt = cmp GT EQ
contains :: Ord a => Interval a -> Interval a -> Bool
contains x y = null y
|| (not (null x) && inf x <= inf y && sup y <= sup x)
isSubsetOf :: Ord a => Interval a -> Interval a -> Bool
isSubsetOf = flip contains
(<?) :: Ord a => Interval a -> Interval a -> Bool
x <? y = inf x < sup y
(<=?) :: Ord a => Interval a -> Interval a -> Bool
x <=? y = inf x <= sup y
(==?) :: Ord a => Interval a -> Interval a -> Bool
x ==? y = inf x <= sup y && sup x >= inf y
(/=?) :: Eq a => Interval a -> Interval a -> Bool
x /=? y = inf x /= sup y || sup x /= inf y
(>?) :: Ord a => Interval a -> Interval a -> Bool
x >? y = sup x > inf y
(>=?) :: Ord a => Interval a -> Interval a -> Bool
x >=? y = sup x >= inf y
possibly :: Ord a => (forall b. Ord b => b -> b -> Bool) -> Interval a -> Interval a -> Bool
possibly cmp l r
| lt && eq && gt = True
| lt && eq = l <=? r
| lt && gt = l /=? r
| lt = l <? r
| eq && gt = l >=? r
| eq = l ==? r
| gt = l >? r
| otherwise = False
where
lt = cmp LT EQ
eq = cmp EQ EQ
gt = cmp GT EQ
clamp :: Ord a => Interval a -> a -> a
clamp (I a b) x | x < a = a
| x > b = b
| otherwise = x
idouble :: Interval Double -> Interval Double
idouble = id
ifloat :: Interval Float -> Interval Float
ifloat = id
default (Integer,Double)