{-# LANGUAGE RebindableSyntax #-}
+{-# LANGUAGE ScopedTypeVariables #-}
-- | Stuff for which I'm too lazy to come up with a decent name.
module Misc
import NumericPrelude
import Algebra.Field
+import Algebra.RealRing
import Algebra.ToInteger
-- | Partition the interval [@a@, @b@] into @n@ subintervals, which we
let xj = a + (k'+1)*h ]
where
h = (b-a)/(fromIntegral $ toInteger n)
+
+
+-- | Compute the unit roundoff (machine epsilon) for this machine. We
+-- find the largest number epsilon such that 1+epsilon <= 1. If you
+-- request anything other than a Float or Double from this, expect
+-- to wait a while.
+--
+unit_roundoff :: forall a. (Algebra.RealRing.C a, Algebra.Field.C a) => a
+unit_roundoff =
+ head [ 1/2^(k-1) | k <- [0..], 1 + 1/(2^k) <= (1::a) ]