{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RebindableSyntax #-}
+
-- | The 'Normed' class represents elements of a normed vector
-- space. We define instances for all common numeric types.
module Normed
import BigFloat
import NumericPrelude hiding (abs)
-import Algebra.Absolute
-import Algebra.Field
-import Algebra.Ring
-import Algebra.ToInteger
+import Algebra.Absolute (abs)
+import qualified Algebra.Absolute as Absolute
+import qualified Algebra.Algebraic as Algebraic
+import qualified Algebra.RealField as RealField
+import qualified Algebra.RealRing as RealRing
+import qualified Algebra.ToInteger as ToInteger
-- Since the norm is defined on a vector space, we should be able to
-- add and subtract anything on which a norm is defined. Of course
-- 'Num' is a bad choice here, but we really prefer to use the normal
-- addition and subtraction operators.
-class (Algebra.Ring.C a, Algebra.Absolute.C a) => Normed a where
- norm_p :: (Algebra.ToInteger.C c,
- Algebra.Field.C b,
- Algebra.Absolute.C b)
- => c -> a -> b
-
- norm_infty :: (Algebra.Field.C b,
- Algebra.Absolute.C b)
- => a -> b
+class Normed a where
+ norm_p :: (ToInteger.C c, Algebraic.C b, Absolute.C b) => c -> a -> b
+ norm_infty :: (RealField.C b) => a -> b
-- | The "usual" norm. Defaults to the Euclidean norm.
- norm :: (Algebra.Field.C b, Algebra.Absolute.C b) => a -> b
+ norm :: (Algebraic.C b, Absolute.C b) => a -> b
norm = norm_p (2 :: Integer)
-- Define instances for common numeric types.
import NumericPrelude hiding (abs)
import qualified Algebra.Absolute as Absolute
+import qualified Algebra.Additive as Additive
+import qualified Algebra.Algebraic as Algebraic
import qualified Algebra.Field as Field
import qualified Algebra.RealRing as RealRing
import qualified Algebra.RealField as RealField
-- We also return the number of iterations required.
--
fixed_point_with_iterations :: (Normed a,
- Field.C b,
- Absolute.C b,
- Ord b)
+ Algebraic.C a,
+ RealField.C b,
+ Algebraic.C b)
=> (a -> a) -- ^ The function @f@ to iterate.
-> b -- ^ The tolerance, @epsilon@.
-> a -- ^ The initial value @x0@.
import NumericPrelude hiding (abs)
import qualified Algebra.Absolute as Absolute
import Algebra.Absolute (abs)
+import qualified Algebra.Additive as Additive
+import qualified Algebra.Algebraic as Algebraic
import qualified Algebra.Field as Field
import qualified Algebra.RealField as RealField
import qualified Algebra.RealRing as RealRing
-- at x0. We delegate to the version that returns the number of
-- iterations and simply discard the number of iterations.
--
-fixed_point :: (Normed a, RealField.C b)
+fixed_point :: (Normed a, Algebraic.C a, Algebraic.C b, RealField.C b)
=> (a -> a) -- ^ The function @f@ to iterate.
-> b -- ^ The tolerance, @epsilon@.
-> a -- ^ The initial value @x0@.
-- the function @f@ with the search starting at x0 and tolerance
-- @epsilon@. We delegate to the version that returns the number of
-- iterations and simply discard the fixed point.
-fixed_point_iteration_count :: (Normed a, RealField.C b)
+fixed_point_iteration_count :: (Normed a,
+ Algebraic.C a,
+ RealField.C b,
+ Algebraic.C b)
=> (a -> a) -- ^ The function @f@ to iterate.
-> b -- ^ The tolerance, @epsilon@.
-> a -- ^ The initial value @x0@.
--
-- This is used to determine the rate of convergence.
--
-fixed_point_error_ratios :: (Normed a, RealField.C b)
+fixed_point_error_ratios :: (Normed a,
+ Additive.C a,
+ RealField.C b,
+ Algebraic.C b)
=> (a -> a) -- ^ The function @f@ to iterate.
-> a -- ^ The initial value @x0@.
-> a -- ^ The true solution, @x_star@.