]> gitweb.michael.orlitzky.com - numerical-analysis.git/blobdiff - src/Misc.hs
Clean up imports everywhere.
[numerical-analysis.git] / src / Misc.hs
index 4d8f3e7f10f81f2abdd7e0fd9379e9192bc4b897..c81d3594fad218bd6d76d224e3aa942071c0a1cf 100644 (file)
@@ -1,7 +1,15 @@
+{-# LANGUAGE RebindableSyntax #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
 -- | Stuff for which I'm too lazy to come up with a decent name.
 module Misc
 where
 
+import NumericPrelude
+import Algebra.Field ( C )
+import Algebra.RealRing ( C )
+import Algebra.ToInteger ( C )
+
 -- | Partition the interval [@a@, @b@] into @n@ subintervals, which we
 --   then return as a list of pairs.
 --
@@ -13,7 +21,7 @@ where
 --   >>> partition 4 (-1) 1
 --   [(-1.0,-0.5),(-0.5,0.0),(0.0,0.5),(0.5,1.0)]
 --
-partition :: (RealFrac a, Integral b)
+partition :: (Algebra.Field.C a, Algebra.ToInteger.C b, Enum b)
           => b -- ^ The number of subintervals to use, @n@
           -> a -- ^ The \"left\" endpoint of the interval, @a@
           -> a -- ^ The \"right\" endpoint of the interval, @b@
@@ -28,4 +36,15 @@ partition n a b
                  let xi = a + k'*h,
                  let xj = a + (k'+1)*h ]
     where
-      h = fromRational $ (toRational (b-a))/(toRational n)
+      coerced_n = fromIntegral $ toInteger n
+      h = (b-a)/coerced_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) ]