{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE TypeFamilies #-}
module Numeric.RootFinding
(
Root(..)
, fromRoot
, Tolerance(..)
, withinTolerance
, IterationStep(..)
, findRoot
, RiddersParam(..)
, ridders
, riddersIterations
, RiddersStep(..)
, NewtonParam(..)
, newtonRaphson
, newtonRaphsonIterations
, NewtonStep(..)
) where
import Control.Applicative (Alternative(..), Applicative(..))
import Control.Monad (MonadPlus(..), ap)
import Control.DeepSeq (NFData(..))
import Data.Data (Data, Typeable)
import Data.Monoid (Monoid(..))
import Data.Foldable (Foldable)
import Data.Traversable (Traversable)
import Data.Default.Class
#if __GLASGOW_HASKELL__ > 704
import GHC.Generics (Generic)
#endif
import Numeric.MathFunctions.Comparison (within,eqRelErr)
import Numeric.MathFunctions.Constants (m_epsilon)
data Root a = NotBracketed
| SearchFailed
| Root !a
deriving (Root a -> Root a -> Bool
(Root a -> Root a -> Bool)
-> (Root a -> Root a -> Bool) -> Eq (Root a)
forall a. Eq a => Root a -> Root a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Root a -> Root a -> Bool
$c/= :: forall a. Eq a => Root a -> Root a -> Bool
== :: Root a -> Root a -> Bool
$c== :: forall a. Eq a => Root a -> Root a -> Bool
Eq, ReadPrec [Root a]
ReadPrec (Root a)
Int -> ReadS (Root a)
ReadS [Root a]
(Int -> ReadS (Root a))
-> ReadS [Root a]
-> ReadPrec (Root a)
-> ReadPrec [Root a]
-> Read (Root a)
forall a. Read a => ReadPrec [Root a]
forall a. Read a => ReadPrec (Root a)
forall a. Read a => Int -> ReadS (Root a)
forall a. Read a => ReadS [Root a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Root a]
$creadListPrec :: forall a. Read a => ReadPrec [Root a]
readPrec :: ReadPrec (Root a)
$creadPrec :: forall a. Read a => ReadPrec (Root a)
readList :: ReadS [Root a]
$creadList :: forall a. Read a => ReadS [Root a]
readsPrec :: Int -> ReadS (Root a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Root a)
Read, Int -> Root a -> ShowS
[Root a] -> ShowS
Root a -> String
(Int -> Root a -> ShowS)
-> (Root a -> String) -> ([Root a] -> ShowS) -> Show (Root a)
forall a. Show a => Int -> Root a -> ShowS
forall a. Show a => [Root a] -> ShowS
forall a. Show a => Root a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Root a] -> ShowS
$cshowList :: forall a. Show a => [Root a] -> ShowS
show :: Root a -> String
$cshow :: forall a. Show a => Root a -> String
showsPrec :: Int -> Root a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Root a -> ShowS
Show, Typeable, Typeable (Root a)
DataType
Constr
Typeable (Root a)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Root a -> c (Root a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Root a))
-> (Root a -> Constr)
-> (Root a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Root a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Root a)))
-> ((forall b. Data b => b -> b) -> Root a -> Root a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Root a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Root a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Root a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Root a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Root a -> m (Root a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Root a -> m (Root a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Root a -> m (Root a))
-> Data (Root a)
Root a -> DataType
Root a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (Root a))
(forall b. Data b => b -> b) -> Root a -> Root a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Root a -> c (Root a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Root a)
forall a. Data a => Typeable (Root a)
forall a. Data a => Root a -> DataType
forall a. Data a => Root a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> Root a -> Root a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Root a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> Root a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Root a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Root a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Root a -> m (Root a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Root a -> m (Root a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Root a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Root a -> c (Root a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Root a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Root a))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Root a -> u
forall u. (forall d. Data d => d -> u) -> Root a -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Root a -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Root a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Root a -> m (Root a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Root a -> m (Root a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Root a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Root a -> c (Root a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Root a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Root a))
$cRoot :: Constr
$cSearchFailed :: Constr
$cNotBracketed :: Constr
$tRoot :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Root a -> m (Root a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Root a -> m (Root a)
gmapMp :: (forall d. Data d => d -> m d) -> Root a -> m (Root a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Root a -> m (Root a)
gmapM :: (forall d. Data d => d -> m d) -> Root a -> m (Root a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Root a -> m (Root a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> Root a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Root a -> u
gmapQ :: (forall d. Data d => d -> u) -> Root a -> [u]
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> Root a -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Root a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Root a -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Root a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Root a -> r
gmapT :: (forall b. Data b => b -> b) -> Root a -> Root a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Root a -> Root a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Root a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Root a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (Root a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Root a))
dataTypeOf :: Root a -> DataType
$cdataTypeOf :: forall a. Data a => Root a -> DataType
toConstr :: Root a -> Constr
$ctoConstr :: forall a. Data a => Root a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Root a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Root a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Root a -> c (Root a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Root a -> c (Root a)
$cp1Data :: forall a. Data a => Typeable (Root a)
Data, Root a -> Bool
(a -> m) -> Root a -> m
(a -> b -> b) -> b -> Root a -> b
(forall m. Monoid m => Root m -> m)
-> (forall m a. Monoid m => (a -> m) -> Root a -> m)
-> (forall m a. Monoid m => (a -> m) -> Root a -> m)
-> (forall a b. (a -> b -> b) -> b -> Root a -> b)
-> (forall a b. (a -> b -> b) -> b -> Root a -> b)
-> (forall b a. (b -> a -> b) -> b -> Root a -> b)
-> (forall b a. (b -> a -> b) -> b -> Root a -> b)
-> (forall a. (a -> a -> a) -> Root a -> a)
-> (forall a. (a -> a -> a) -> Root a -> a)
-> (forall a. Root a -> [a])
-> (forall a. Root a -> Bool)
-> (forall a. Root a -> Int)
-> (forall a. Eq a => a -> Root a -> Bool)
-> (forall a. Ord a => Root a -> a)
-> (forall a. Ord a => Root a -> a)
-> (forall a. Num a => Root a -> a)
-> (forall a. Num a => Root a -> a)
-> Foldable Root
forall a. Eq a => a -> Root a -> Bool
forall a. Num a => Root a -> a
forall a. Ord a => Root a -> a
forall m. Monoid m => Root m -> m
forall a. Root a -> Bool
forall a. Root a -> Int
forall a. Root a -> [a]
forall a. (a -> a -> a) -> Root a -> a
forall m a. Monoid m => (a -> m) -> Root a -> m
forall b a. (b -> a -> b) -> b -> Root a -> b
forall a b. (a -> b -> b) -> b -> Root a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Root a -> a
$cproduct :: forall a. Num a => Root a -> a
sum :: Root a -> a
$csum :: forall a. Num a => Root a -> a
minimum :: Root a -> a
$cminimum :: forall a. Ord a => Root a -> a
maximum :: Root a -> a
$cmaximum :: forall a. Ord a => Root a -> a
elem :: a -> Root a -> Bool
$celem :: forall a. Eq a => a -> Root a -> Bool
length :: Root a -> Int
$clength :: forall a. Root a -> Int
null :: Root a -> Bool
$cnull :: forall a. Root a -> Bool
toList :: Root a -> [a]
$ctoList :: forall a. Root a -> [a]
foldl1 :: (a -> a -> a) -> Root a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Root a -> a
foldr1 :: (a -> a -> a) -> Root a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Root a -> a
foldl' :: (b -> a -> b) -> b -> Root a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Root a -> b
foldl :: (b -> a -> b) -> b -> Root a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Root a -> b
foldr' :: (a -> b -> b) -> b -> Root a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Root a -> b
foldr :: (a -> b -> b) -> b -> Root a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Root a -> b
foldMap' :: (a -> m) -> Root a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Root a -> m
foldMap :: (a -> m) -> Root a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Root a -> m
fold :: Root m -> m
$cfold :: forall m. Monoid m => Root m -> m
Foldable, Functor Root
Foldable Root
Functor Root
-> Foldable Root
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Root a -> f (Root b))
-> (forall (f :: * -> *) a.
Applicative f =>
Root (f a) -> f (Root a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Root a -> m (Root b))
-> (forall (m :: * -> *) a. Monad m => Root (m a) -> m (Root a))
-> Traversable Root
(a -> f b) -> Root a -> f (Root b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Root (m a) -> m (Root a)
forall (f :: * -> *) a. Applicative f => Root (f a) -> f (Root a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Root a -> m (Root b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Root a -> f (Root b)
sequence :: Root (m a) -> m (Root a)
$csequence :: forall (m :: * -> *) a. Monad m => Root (m a) -> m (Root a)
mapM :: (a -> m b) -> Root a -> m (Root b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Root a -> m (Root b)
sequenceA :: Root (f a) -> f (Root a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Root (f a) -> f (Root a)
traverse :: (a -> f b) -> Root a -> f (Root b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Root a -> f (Root b)
$cp2Traversable :: Foldable Root
$cp1Traversable :: Functor Root
Traversable
#if __GLASGOW_HASKELL__ > 704
, (forall x. Root a -> Rep (Root a) x)
-> (forall x. Rep (Root a) x -> Root a) -> Generic (Root a)
forall x. Rep (Root a) x -> Root a
forall x. Root a -> Rep (Root a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Root a) x -> Root a
forall a x. Root a -> Rep (Root a) x
$cto :: forall a x. Rep (Root a) x -> Root a
$cfrom :: forall a x. Root a -> Rep (Root a) x
Generic
#endif
)
instance (NFData a) => NFData (Root a) where
rnf :: Root a -> ()
rnf Root a
NotBracketed = ()
rnf Root a
SearchFailed = ()
rnf (Root a
a) = a -> ()
forall a. NFData a => a -> ()
rnf a
a
instance Functor Root where
fmap :: (a -> b) -> Root a -> Root b
fmap a -> b
_ Root a
NotBracketed = Root b
forall a. Root a
NotBracketed
fmap a -> b
_ Root a
SearchFailed = Root b
forall a. Root a
SearchFailed
fmap a -> b
f (Root a
a) = b -> Root b
forall a. a -> Root a
Root (a -> b
f a
a)
instance Applicative Root where
pure :: a -> Root a
pure = a -> Root a
forall (m :: * -> *) a. Monad m => a -> m a
return
<*> :: Root (a -> b) -> Root a -> Root b
(<*>) = Root (a -> b) -> Root a -> Root b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
instance Monad Root where
Root a
NotBracketed >>= :: Root a -> (a -> Root b) -> Root b
>>= a -> Root b
_ = Root b
forall a. Root a
NotBracketed
Root a
SearchFailed >>= a -> Root b
_ = Root b
forall a. Root a
SearchFailed
Root a
a >>= a -> Root b
f = a -> Root b
f a
a
return :: a -> Root a
return = a -> Root a
forall a. a -> Root a
Root
instance MonadPlus Root where
mzero :: Root a
mzero = Root a
forall (f :: * -> *) a. Alternative f => f a
empty
mplus :: Root a -> Root a -> Root a
mplus = Root a -> Root a -> Root a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)
instance Alternative Root where
empty :: Root a
empty = Root a
forall a. Root a
NotBracketed
r :: Root a
r@Root{} <|> :: Root a -> Root a -> Root a
<|> Root a
_ = Root a
r
Root a
_ <|> r :: Root a
r@Root{} = Root a
r
Root a
NotBracketed <|> Root a
r = Root a
r
Root a
r <|> Root a
NotBracketed = Root a
r
Root a
_ <|> Root a
r = Root a
r
fromRoot :: a
-> Root a
-> a
fromRoot :: a -> Root a -> a
fromRoot a
_ (Root a
a) = a
a
fromRoot a
a Root a
_ = a
a
data Tolerance
= RelTol !Double
| AbsTol !Double
deriving (Tolerance -> Tolerance -> Bool
(Tolerance -> Tolerance -> Bool)
-> (Tolerance -> Tolerance -> Bool) -> Eq Tolerance
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tolerance -> Tolerance -> Bool
$c/= :: Tolerance -> Tolerance -> Bool
== :: Tolerance -> Tolerance -> Bool
$c== :: Tolerance -> Tolerance -> Bool
Eq, ReadPrec [Tolerance]
ReadPrec Tolerance
Int -> ReadS Tolerance
ReadS [Tolerance]
(Int -> ReadS Tolerance)
-> ReadS [Tolerance]
-> ReadPrec Tolerance
-> ReadPrec [Tolerance]
-> Read Tolerance
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Tolerance]
$creadListPrec :: ReadPrec [Tolerance]
readPrec :: ReadPrec Tolerance
$creadPrec :: ReadPrec Tolerance
readList :: ReadS [Tolerance]
$creadList :: ReadS [Tolerance]
readsPrec :: Int -> ReadS Tolerance
$creadsPrec :: Int -> ReadS Tolerance
Read, Int -> Tolerance -> ShowS
[Tolerance] -> ShowS
Tolerance -> String
(Int -> Tolerance -> ShowS)
-> (Tolerance -> String)
-> ([Tolerance] -> ShowS)
-> Show Tolerance
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tolerance] -> ShowS
$cshowList :: [Tolerance] -> ShowS
show :: Tolerance -> String
$cshow :: Tolerance -> String
showsPrec :: Int -> Tolerance -> ShowS
$cshowsPrec :: Int -> Tolerance -> ShowS
Show, Typeable, Typeable Tolerance
DataType
Constr
Typeable Tolerance
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tolerance -> c Tolerance)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tolerance)
-> (Tolerance -> Constr)
-> (Tolerance -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Tolerance))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tolerance))
-> ((forall b. Data b => b -> b) -> Tolerance -> Tolerance)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Tolerance -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Tolerance -> r)
-> (forall u. (forall d. Data d => d -> u) -> Tolerance -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Tolerance -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Tolerance -> m Tolerance)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tolerance -> m Tolerance)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tolerance -> m Tolerance)
-> Data Tolerance
Tolerance -> DataType
Tolerance -> Constr
(forall b. Data b => b -> b) -> Tolerance -> Tolerance
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tolerance -> c Tolerance
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tolerance
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Tolerance -> u
forall u. (forall d. Data d => d -> u) -> Tolerance -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Tolerance -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Tolerance -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Tolerance -> m Tolerance
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tolerance -> m Tolerance
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tolerance
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tolerance -> c Tolerance
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Tolerance)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tolerance)
$cAbsTol :: Constr
$cRelTol :: Constr
$tTolerance :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Tolerance -> m Tolerance
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tolerance -> m Tolerance
gmapMp :: (forall d. Data d => d -> m d) -> Tolerance -> m Tolerance
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Tolerance -> m Tolerance
gmapM :: (forall d. Data d => d -> m d) -> Tolerance -> m Tolerance
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Tolerance -> m Tolerance
gmapQi :: Int -> (forall d. Data d => d -> u) -> Tolerance -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Tolerance -> u
gmapQ :: (forall d. Data d => d -> u) -> Tolerance -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Tolerance -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Tolerance -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Tolerance -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Tolerance -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Tolerance -> r
gmapT :: (forall b. Data b => b -> b) -> Tolerance -> Tolerance
$cgmapT :: (forall b. Data b => b -> b) -> Tolerance -> Tolerance
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tolerance)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tolerance)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Tolerance)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Tolerance)
dataTypeOf :: Tolerance -> DataType
$cdataTypeOf :: Tolerance -> DataType
toConstr :: Tolerance -> Constr
$ctoConstr :: Tolerance -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tolerance
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Tolerance
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tolerance -> c Tolerance
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Tolerance -> c Tolerance
$cp1Data :: Typeable Tolerance
Data
#if __GLASGOW_HASKELL__ > 704
, (forall x. Tolerance -> Rep Tolerance x)
-> (forall x. Rep Tolerance x -> Tolerance) -> Generic Tolerance
forall x. Rep Tolerance x -> Tolerance
forall x. Tolerance -> Rep Tolerance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tolerance x -> Tolerance
$cfrom :: forall x. Tolerance -> Rep Tolerance x
Generic
#endif
)
withinTolerance :: Tolerance -> Double -> Double -> Bool
withinTolerance :: Tolerance -> Double -> Double -> Bool
withinTolerance Tolerance
_ Double
a Double
b
| Int -> Double -> Double -> Bool
within Int
1 Double
a Double
b = Bool
True
withinTolerance (RelTol Double
eps) Double
a Double
b = Double -> Double -> Double -> Bool
eqRelErr Double
eps Double
a Double
b
withinTolerance (AbsTol Double
tol) Double
a Double
b = Double -> Double
forall a. Num a => a -> a
abs (Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
b) Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
tol
class IterationStep a where
matchRoot :: Tolerance -> a -> Maybe (Root Double)
findRoot :: IterationStep a
=> Int
-> Tolerance
-> [a]
-> Root Double
findRoot :: Int -> Tolerance -> [a] -> Root Double
findRoot Int
maxN Tolerance
tol = Int -> [a] -> Root Double
go Int
0
where
go :: Int -> [a] -> Root Double
go !Int
i [a]
_ | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
maxN = Root Double
forall a. Root a
SearchFailed
go !Int
_ [] = Root Double
forall a. Root a
SearchFailed
go Int
i (a
x:[a]
xs) = case Tolerance -> a -> Maybe (Root Double)
forall a. IterationStep a => Tolerance -> a -> Maybe (Root Double)
matchRoot Tolerance
tol a
x of
Just Root Double
r -> Root Double
r
Maybe (Root Double)
Nothing -> Int -> [a] -> Root Double
go (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) [a]
xs
{-# INLINABLE findRoot #-}
{-# SPECIALIZE findRoot :: Int -> Tolerance -> [RiddersStep] -> Root Double #-}
{-# SPECIALIZE findRoot :: Int -> Tolerance -> [NewtonStep] -> Root Double #-}
data RiddersParam = RiddersParam
{ RiddersParam -> Int
riddersMaxIter :: !Int
, RiddersParam -> Tolerance
riddersTol :: !Tolerance
}
deriving (RiddersParam -> RiddersParam -> Bool
(RiddersParam -> RiddersParam -> Bool)
-> (RiddersParam -> RiddersParam -> Bool) -> Eq RiddersParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RiddersParam -> RiddersParam -> Bool
$c/= :: RiddersParam -> RiddersParam -> Bool
== :: RiddersParam -> RiddersParam -> Bool
$c== :: RiddersParam -> RiddersParam -> Bool
Eq, ReadPrec [RiddersParam]
ReadPrec RiddersParam
Int -> ReadS RiddersParam
ReadS [RiddersParam]
(Int -> ReadS RiddersParam)
-> ReadS [RiddersParam]
-> ReadPrec RiddersParam
-> ReadPrec [RiddersParam]
-> Read RiddersParam
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RiddersParam]
$creadListPrec :: ReadPrec [RiddersParam]
readPrec :: ReadPrec RiddersParam
$creadPrec :: ReadPrec RiddersParam
readList :: ReadS [RiddersParam]
$creadList :: ReadS [RiddersParam]
readsPrec :: Int -> ReadS RiddersParam
$creadsPrec :: Int -> ReadS RiddersParam
Read, Int -> RiddersParam -> ShowS
[RiddersParam] -> ShowS
RiddersParam -> String
(Int -> RiddersParam -> ShowS)
-> (RiddersParam -> String)
-> ([RiddersParam] -> ShowS)
-> Show RiddersParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RiddersParam] -> ShowS
$cshowList :: [RiddersParam] -> ShowS
show :: RiddersParam -> String
$cshow :: RiddersParam -> String
showsPrec :: Int -> RiddersParam -> ShowS
$cshowsPrec :: Int -> RiddersParam -> ShowS
Show, Typeable, Typeable RiddersParam
DataType
Constr
Typeable RiddersParam
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RiddersParam -> c RiddersParam)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RiddersParam)
-> (RiddersParam -> Constr)
-> (RiddersParam -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RiddersParam))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RiddersParam))
-> ((forall b. Data b => b -> b) -> RiddersParam -> RiddersParam)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RiddersParam -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RiddersParam -> r)
-> (forall u. (forall d. Data d => d -> u) -> RiddersParam -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> RiddersParam -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RiddersParam -> m RiddersParam)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RiddersParam -> m RiddersParam)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RiddersParam -> m RiddersParam)
-> Data RiddersParam
RiddersParam -> DataType
RiddersParam -> Constr
(forall b. Data b => b -> b) -> RiddersParam -> RiddersParam
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RiddersParam -> c RiddersParam
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RiddersParam
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> RiddersParam -> u
forall u. (forall d. Data d => d -> u) -> RiddersParam -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RiddersParam -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RiddersParam -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RiddersParam -> m RiddersParam
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RiddersParam -> m RiddersParam
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RiddersParam
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RiddersParam -> c RiddersParam
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RiddersParam)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RiddersParam)
$cRiddersParam :: Constr
$tRiddersParam :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> RiddersParam -> m RiddersParam
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RiddersParam -> m RiddersParam
gmapMp :: (forall d. Data d => d -> m d) -> RiddersParam -> m RiddersParam
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RiddersParam -> m RiddersParam
gmapM :: (forall d. Data d => d -> m d) -> RiddersParam -> m RiddersParam
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RiddersParam -> m RiddersParam
gmapQi :: Int -> (forall d. Data d => d -> u) -> RiddersParam -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RiddersParam -> u
gmapQ :: (forall d. Data d => d -> u) -> RiddersParam -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RiddersParam -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RiddersParam -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RiddersParam -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RiddersParam -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RiddersParam -> r
gmapT :: (forall b. Data b => b -> b) -> RiddersParam -> RiddersParam
$cgmapT :: (forall b. Data b => b -> b) -> RiddersParam -> RiddersParam
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RiddersParam)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RiddersParam)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RiddersParam)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RiddersParam)
dataTypeOf :: RiddersParam -> DataType
$cdataTypeOf :: RiddersParam -> DataType
toConstr :: RiddersParam -> Constr
$ctoConstr :: RiddersParam -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RiddersParam
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RiddersParam
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RiddersParam -> c RiddersParam
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RiddersParam -> c RiddersParam
$cp1Data :: Typeable RiddersParam
Data
#if __GLASGOW_HASKELL__ > 704
, (forall x. RiddersParam -> Rep RiddersParam x)
-> (forall x. Rep RiddersParam x -> RiddersParam)
-> Generic RiddersParam
forall x. Rep RiddersParam x -> RiddersParam
forall x. RiddersParam -> Rep RiddersParam x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RiddersParam x -> RiddersParam
$cfrom :: forall x. RiddersParam -> Rep RiddersParam x
Generic
#endif
)
instance Default RiddersParam where
def :: RiddersParam
def = RiddersParam :: Int -> Tolerance -> RiddersParam
RiddersParam
{ riddersMaxIter :: Int
riddersMaxIter = Int
100
, riddersTol :: Tolerance
riddersTol = Double -> Tolerance
RelTol (Double
4 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
m_epsilon)
}
data
= !Double !Double
| RiddersBisect !Double !Double
| RiddersRoot !Double
| RiddersNoBracket
deriving (RiddersStep -> RiddersStep -> Bool
(RiddersStep -> RiddersStep -> Bool)
-> (RiddersStep -> RiddersStep -> Bool) -> Eq RiddersStep
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RiddersStep -> RiddersStep -> Bool
$c/= :: RiddersStep -> RiddersStep -> Bool
== :: RiddersStep -> RiddersStep -> Bool
$c== :: RiddersStep -> RiddersStep -> Bool
Eq, ReadPrec [RiddersStep]
ReadPrec RiddersStep
Int -> ReadS RiddersStep
ReadS [RiddersStep]
(Int -> ReadS RiddersStep)
-> ReadS [RiddersStep]
-> ReadPrec RiddersStep
-> ReadPrec [RiddersStep]
-> Read RiddersStep
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RiddersStep]
$creadListPrec :: ReadPrec [RiddersStep]
readPrec :: ReadPrec RiddersStep
$creadPrec :: ReadPrec RiddersStep
readList :: ReadS [RiddersStep]
$creadList :: ReadS [RiddersStep]
readsPrec :: Int -> ReadS RiddersStep
$creadsPrec :: Int -> ReadS RiddersStep
Read, Int -> RiddersStep -> ShowS
[RiddersStep] -> ShowS
RiddersStep -> String
(Int -> RiddersStep -> ShowS)
-> (RiddersStep -> String)
-> ([RiddersStep] -> ShowS)
-> Show RiddersStep
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RiddersStep] -> ShowS
$cshowList :: [RiddersStep] -> ShowS
show :: RiddersStep -> String
$cshow :: RiddersStep -> String
showsPrec :: Int -> RiddersStep -> ShowS
$cshowsPrec :: Int -> RiddersStep -> ShowS
Show, Typeable,
#if __GLASGOW_HASKELL__ > 704
, (forall x. RiddersStep -> Rep RiddersStep x)
-> (forall x. Rep RiddersStep x -> RiddersStep)
-> Generic RiddersStep
forall x. Rep RiddersStep x -> RiddersStep
forall x. RiddersStep -> Rep RiddersStep x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RiddersStep x -> RiddersStep
$cfrom :: forall x. RiddersStep -> Rep RiddersStep x
Generic
#endif
)
instance NFData RiddersStep where
rnf :: RiddersStep -> ()
rnf RiddersStep
x = RiddersStep
x RiddersStep -> () -> ()
`seq` ()
instance IterationStep RiddersStep where
matchRoot :: Tolerance -> RiddersStep -> Maybe (Root Double)
matchRoot Tolerance
tol RiddersStep
r = case RiddersStep
r of
RiddersRoot Double
x -> Root Double -> Maybe (Root Double)
forall a. a -> Maybe a
Just (Root Double -> Maybe (Root Double))
-> Root Double -> Maybe (Root Double)
forall a b. (a -> b) -> a -> b
$ Double -> Root Double
forall a. a -> Root a
Root Double
x
RiddersStep
RiddersNoBracket -> Root Double -> Maybe (Root Double)
forall a. a -> Maybe a
Just Root Double
forall a. Root a
NotBracketed
RiddersStep Double
a Double
b
| Tolerance -> Double -> Double -> Bool
withinTolerance Tolerance
tol Double
a Double
b -> Root Double -> Maybe (Root Double)
forall a. a -> Maybe a
Just (Root Double -> Maybe (Root Double))
-> Root Double -> Maybe (Root Double)
forall a b. (a -> b) -> a -> b
$ Double -> Root Double
forall a. a -> Root a
Root ((Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
b) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2)
| Bool
otherwise -> Maybe (Root Double)
forall a. Maybe a
Nothing
RiddersBisect Double
a Double
b
| Tolerance -> Double -> Double -> Bool
withinTolerance Tolerance
tol Double
a Double
b -> Root Double -> Maybe (Root Double)
forall a. a -> Maybe a
Just (Root Double -> Maybe (Root Double))
-> Root Double -> Maybe (Root Double)
forall a b. (a -> b) -> a -> b
$ Double -> Root Double
forall a. a -> Root a
Root ((Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
b) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2)
| Bool
otherwise -> Maybe (Root Double)
forall a. Maybe a
Nothing
ridders
:: RiddersParam
-> (Double,Double)
-> (Double -> Double)
-> Root Double
ridders :: RiddersParam
-> (Double, Double) -> (Double -> Double) -> Root Double
ridders RiddersParam
p (Double, Double)
bracket Double -> Double
fun
= Int -> Tolerance -> [RiddersStep] -> Root Double
forall a. IterationStep a => Int -> Tolerance -> [a] -> Root Double
findRoot (RiddersParam -> Int
riddersMaxIter RiddersParam
p) (RiddersParam -> Tolerance
riddersTol RiddersParam
p)
([RiddersStep] -> Root Double) -> [RiddersStep] -> Root Double
forall a b. (a -> b) -> a -> b
$ (Double, Double) -> (Double -> Double) -> [RiddersStep]
riddersIterations (Double, Double)
bracket Double -> Double
fun
riddersIterations :: (Double,Double) -> (Double -> Double) -> [RiddersStep]
riddersIterations :: (Double, Double) -> (Double -> Double) -> [RiddersStep]
riddersIterations (Double
lo,Double
hi) Double -> Double
f
| Double
flo Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 = [Double -> RiddersStep
RiddersRoot Double
lo]
| Double
fhi Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 = [Double -> RiddersStep
RiddersRoot Double
hi]
| Double
floDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
fhi Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 = [RiddersStep
RiddersNoBracket]
| Double
lo Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
hi = Double -> Double -> RiddersStep
RiddersStep Double
lo Double
hi RiddersStep -> [RiddersStep] -> [RiddersStep]
forall a. a -> [a] -> [a]
: Double -> Double -> Double -> Double -> [RiddersStep]
go Double
lo Double
flo Double
hi Double
fhi
| Bool
otherwise = Double -> Double -> RiddersStep
RiddersStep Double
lo Double
hi RiddersStep -> [RiddersStep] -> [RiddersStep]
forall a. a -> [a] -> [a]
: Double -> Double -> Double -> Double -> [RiddersStep]
go Double
hi Double
fhi Double
lo Double
flo
where
flo :: Double
flo = Double -> Double
f Double
lo
fhi :: Double
fhi = Double -> Double
f Double
hi
go :: Double -> Double -> Double -> Double -> [RiddersStep]
go !Double
a !Double
fa !Double
b !Double
fb
| Double
fm Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 = [Double -> RiddersStep
RiddersRoot Double
m]
| Double
fn Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 = [Double -> RiddersStep
RiddersRoot Double
n]
| Double
n Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
a Bool -> Bool -> Bool
|| Double
n Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
b = case () of
()
_| Double
fmDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
fa Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 -> Double -> Double -> Double -> Double -> [RiddersStep]
recBisect Double
a Double
fa Double
m Double
fm
| Bool
otherwise -> Double -> Double -> Double -> Double -> [RiddersStep]
recBisect Double
m Double
fm Double
b Double
fb
| Double
fnDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
fm Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 = Double -> Double -> Double -> Double -> [RiddersStep]
recRidders Double
n Double
fn Double
m Double
fm
| Double
fnDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
fa Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 = Double -> Double -> Double -> Double -> [RiddersStep]
recRidders Double
a Double
fa Double
n Double
fn
| Bool
otherwise = Double -> Double -> Double -> Double -> [RiddersStep]
recRidders Double
n Double
fn Double
b Double
fb
where
recBisect :: Double -> Double -> Double -> Double -> [RiddersStep]
recBisect Double
x Double
fx Double
y Double
fy = Double -> Double -> RiddersStep
RiddersBisect Double
x Double
y RiddersStep -> [RiddersStep] -> [RiddersStep]
forall a. a -> [a] -> [a]
: Double -> Double -> Double -> Double -> [RiddersStep]
go Double
x Double
fx Double
y Double
fy
recRidders :: Double -> Double -> Double -> Double -> [RiddersStep]
recRidders Double
x Double
fx Double
y Double
fy = Double -> Double -> RiddersStep
RiddersStep Double
x Double
y RiddersStep -> [RiddersStep] -> [RiddersStep]
forall a. a -> [a] -> [a]
: Double -> Double -> Double -> Double -> [RiddersStep]
go Double
x Double
fx Double
y Double
fy
dm :: Double
dm = (Double
b Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
a) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
0.5
m :: Double
m = (Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
b) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2
fm :: Double
fm = Double -> Double
f Double
m
n :: Double
n = Double
m Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double -> Double
forall a. Num a => a -> a
signum (Double
fb Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
fa) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
dm Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
fm Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double -> Double
forall a. Floating a => a -> a
sqrt(Double
fmDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
fm Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
faDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
fb)
fn :: Double
fn = Double -> Double
f Double
n
data NewtonParam = NewtonParam
{ NewtonParam -> Int
newtonMaxIter :: !Int
, NewtonParam -> Tolerance
newtonTol :: !Tolerance
}
deriving (NewtonParam -> NewtonParam -> Bool
(NewtonParam -> NewtonParam -> Bool)
-> (NewtonParam -> NewtonParam -> Bool) -> Eq NewtonParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewtonParam -> NewtonParam -> Bool
$c/= :: NewtonParam -> NewtonParam -> Bool
== :: NewtonParam -> NewtonParam -> Bool
$c== :: NewtonParam -> NewtonParam -> Bool
Eq, ReadPrec [NewtonParam]
ReadPrec NewtonParam
Int -> ReadS NewtonParam
ReadS [NewtonParam]
(Int -> ReadS NewtonParam)
-> ReadS [NewtonParam]
-> ReadPrec NewtonParam
-> ReadPrec [NewtonParam]
-> Read NewtonParam
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NewtonParam]
$creadListPrec :: ReadPrec [NewtonParam]
readPrec :: ReadPrec NewtonParam
$creadPrec :: ReadPrec NewtonParam
readList :: ReadS [NewtonParam]
$creadList :: ReadS [NewtonParam]
readsPrec :: Int -> ReadS NewtonParam
$creadsPrec :: Int -> ReadS NewtonParam
Read, Int -> NewtonParam -> ShowS
[NewtonParam] -> ShowS
NewtonParam -> String
(Int -> NewtonParam -> ShowS)
-> (NewtonParam -> String)
-> ([NewtonParam] -> ShowS)
-> Show NewtonParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewtonParam] -> ShowS
$cshowList :: [NewtonParam] -> ShowS
show :: NewtonParam -> String
$cshow :: NewtonParam -> String
showsPrec :: Int -> NewtonParam -> ShowS
$cshowsPrec :: Int -> NewtonParam -> ShowS
Show, Typeable, Typeable NewtonParam
DataType
Constr
Typeable NewtonParam
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewtonParam -> c NewtonParam)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewtonParam)
-> (NewtonParam -> Constr)
-> (NewtonParam -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewtonParam))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewtonParam))
-> ((forall b. Data b => b -> b) -> NewtonParam -> NewtonParam)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonParam -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonParam -> r)
-> (forall u. (forall d. Data d => d -> u) -> NewtonParam -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> NewtonParam -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewtonParam -> m NewtonParam)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewtonParam -> m NewtonParam)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewtonParam -> m NewtonParam)
-> Data NewtonParam
NewtonParam -> DataType
NewtonParam -> Constr
(forall b. Data b => b -> b) -> NewtonParam -> NewtonParam
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewtonParam -> c NewtonParam
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewtonParam
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> NewtonParam -> u
forall u. (forall d. Data d => d -> u) -> NewtonParam -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonParam -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonParam -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewtonParam -> m NewtonParam
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewtonParam -> m NewtonParam
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewtonParam
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewtonParam -> c NewtonParam
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewtonParam)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewtonParam)
$cNewtonParam :: Constr
$tNewtonParam :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> NewtonParam -> m NewtonParam
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewtonParam -> m NewtonParam
gmapMp :: (forall d. Data d => d -> m d) -> NewtonParam -> m NewtonParam
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewtonParam -> m NewtonParam
gmapM :: (forall d. Data d => d -> m d) -> NewtonParam -> m NewtonParam
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewtonParam -> m NewtonParam
gmapQi :: Int -> (forall d. Data d => d -> u) -> NewtonParam -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewtonParam -> u
gmapQ :: (forall d. Data d => d -> u) -> NewtonParam -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NewtonParam -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonParam -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonParam -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonParam -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonParam -> r
gmapT :: (forall b. Data b => b -> b) -> NewtonParam -> NewtonParam
$cgmapT :: (forall b. Data b => b -> b) -> NewtonParam -> NewtonParam
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewtonParam)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewtonParam)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c NewtonParam)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewtonParam)
dataTypeOf :: NewtonParam -> DataType
$cdataTypeOf :: NewtonParam -> DataType
toConstr :: NewtonParam -> Constr
$ctoConstr :: NewtonParam -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewtonParam
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewtonParam
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewtonParam -> c NewtonParam
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewtonParam -> c NewtonParam
$cp1Data :: Typeable NewtonParam
Data
#if __GLASGOW_HASKELL__ > 704
, (forall x. NewtonParam -> Rep NewtonParam x)
-> (forall x. Rep NewtonParam x -> NewtonParam)
-> Generic NewtonParam
forall x. Rep NewtonParam x -> NewtonParam
forall x. NewtonParam -> Rep NewtonParam x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NewtonParam x -> NewtonParam
$cfrom :: forall x. NewtonParam -> Rep NewtonParam x
Generic
#endif
)
instance Default NewtonParam where
def :: NewtonParam
def = NewtonParam :: Int -> Tolerance -> NewtonParam
NewtonParam
{ newtonMaxIter :: Int
newtonMaxIter = Int
50
, newtonTol :: Tolerance
newtonTol = Double -> Tolerance
RelTol (Double
4 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
m_epsilon)
}
data NewtonStep
= NewtonStep !Double !Double
| NewtonBisection !Double !Double
| NewtonRoot !Double
| NewtonNoBracket
deriving (NewtonStep -> NewtonStep -> Bool
(NewtonStep -> NewtonStep -> Bool)
-> (NewtonStep -> NewtonStep -> Bool) -> Eq NewtonStep
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewtonStep -> NewtonStep -> Bool
$c/= :: NewtonStep -> NewtonStep -> Bool
== :: NewtonStep -> NewtonStep -> Bool
$c== :: NewtonStep -> NewtonStep -> Bool
Eq, ReadPrec [NewtonStep]
ReadPrec NewtonStep
Int -> ReadS NewtonStep
ReadS [NewtonStep]
(Int -> ReadS NewtonStep)
-> ReadS [NewtonStep]
-> ReadPrec NewtonStep
-> ReadPrec [NewtonStep]
-> Read NewtonStep
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NewtonStep]
$creadListPrec :: ReadPrec [NewtonStep]
readPrec :: ReadPrec NewtonStep
$creadPrec :: ReadPrec NewtonStep
readList :: ReadS [NewtonStep]
$creadList :: ReadS [NewtonStep]
readsPrec :: Int -> ReadS NewtonStep
$creadsPrec :: Int -> ReadS NewtonStep
Read, Int -> NewtonStep -> ShowS
[NewtonStep] -> ShowS
NewtonStep -> String
(Int -> NewtonStep -> ShowS)
-> (NewtonStep -> String)
-> ([NewtonStep] -> ShowS)
-> Show NewtonStep
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewtonStep] -> ShowS
$cshowList :: [NewtonStep] -> ShowS
show :: NewtonStep -> String
$cshow :: NewtonStep -> String
showsPrec :: Int -> NewtonStep -> ShowS
$cshowsPrec :: Int -> NewtonStep -> ShowS
Show, Typeable, Typeable NewtonStep
DataType
Constr
Typeable NewtonStep
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewtonStep -> c NewtonStep)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewtonStep)
-> (NewtonStep -> Constr)
-> (NewtonStep -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewtonStep))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewtonStep))
-> ((forall b. Data b => b -> b) -> NewtonStep -> NewtonStep)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonStep -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonStep -> r)
-> (forall u. (forall d. Data d => d -> u) -> NewtonStep -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> NewtonStep -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewtonStep -> m NewtonStep)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewtonStep -> m NewtonStep)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewtonStep -> m NewtonStep)
-> Data NewtonStep
NewtonStep -> DataType
NewtonStep -> Constr
(forall b. Data b => b -> b) -> NewtonStep -> NewtonStep
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewtonStep -> c NewtonStep
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewtonStep
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> NewtonStep -> u
forall u. (forall d. Data d => d -> u) -> NewtonStep -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonStep -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonStep -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewtonStep -> m NewtonStep
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewtonStep -> m NewtonStep
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewtonStep
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewtonStep -> c NewtonStep
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewtonStep)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewtonStep)
$cNewtonNoBracket :: Constr
$cNewtonRoot :: Constr
$cNewtonBisection :: Constr
$cNewtonStep :: Constr
$tNewtonStep :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> NewtonStep -> m NewtonStep
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewtonStep -> m NewtonStep
gmapMp :: (forall d. Data d => d -> m d) -> NewtonStep -> m NewtonStep
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewtonStep -> m NewtonStep
gmapM :: (forall d. Data d => d -> m d) -> NewtonStep -> m NewtonStep
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewtonStep -> m NewtonStep
gmapQi :: Int -> (forall d. Data d => d -> u) -> NewtonStep -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewtonStep -> u
gmapQ :: (forall d. Data d => d -> u) -> NewtonStep -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NewtonStep -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonStep -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonStep -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonStep -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewtonStep -> r
gmapT :: (forall b. Data b => b -> b) -> NewtonStep -> NewtonStep
$cgmapT :: (forall b. Data b => b -> b) -> NewtonStep -> NewtonStep
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewtonStep)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewtonStep)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c NewtonStep)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewtonStep)
dataTypeOf :: NewtonStep -> DataType
$cdataTypeOf :: NewtonStep -> DataType
toConstr :: NewtonStep -> Constr
$ctoConstr :: NewtonStep -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewtonStep
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewtonStep
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewtonStep -> c NewtonStep
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewtonStep -> c NewtonStep
$cp1Data :: Typeable NewtonStep
Data
#if __GLASGOW_HASKELL__ > 704
, (forall x. NewtonStep -> Rep NewtonStep x)
-> (forall x. Rep NewtonStep x -> NewtonStep) -> Generic NewtonStep
forall x. Rep NewtonStep x -> NewtonStep
forall x. NewtonStep -> Rep NewtonStep x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NewtonStep x -> NewtonStep
$cfrom :: forall x. NewtonStep -> Rep NewtonStep x
Generic
#endif
)
instance NFData NewtonStep where
rnf :: NewtonStep -> ()
rnf NewtonStep
x = NewtonStep
x NewtonStep -> () -> ()
`seq` ()
instance IterationStep NewtonStep where
matchRoot :: Tolerance -> NewtonStep -> Maybe (Root Double)
matchRoot Tolerance
tol NewtonStep
r = case NewtonStep
r of
NewtonRoot Double
x -> Root Double -> Maybe (Root Double)
forall a. a -> Maybe a
Just (Double -> Root Double
forall a. a -> Root a
Root Double
x)
NewtonStep
NewtonNoBracket -> Root Double -> Maybe (Root Double)
forall a. a -> Maybe a
Just Root Double
forall a. Root a
NotBracketed
NewtonStep Double
x Double
x'
| Tolerance -> Double -> Double -> Bool
withinTolerance Tolerance
tol Double
x Double
x' -> Root Double -> Maybe (Root Double)
forall a. a -> Maybe a
Just (Double -> Root Double
forall a. a -> Root a
Root Double
x')
| Bool
otherwise -> Maybe (Root Double)
forall a. Maybe a
Nothing
NewtonBisection Double
a Double
b
| Tolerance -> Double -> Double -> Bool
withinTolerance Tolerance
tol Double
a Double
b -> Root Double -> Maybe (Root Double)
forall a. a -> Maybe a
Just (Double -> Root Double
forall a. a -> Root a
Root ((Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
b) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2))
| Bool
otherwise -> Maybe (Root Double)
forall a. Maybe a
Nothing
{-# INLINE matchRoot #-}
newtonRaphson
:: NewtonParam
-> (Double,Double,Double)
-> (Double -> (Double,Double))
-> Root Double
newtonRaphson :: NewtonParam
-> (Double, Double, Double)
-> (Double -> (Double, Double))
-> Root Double
newtonRaphson NewtonParam
p (Double, Double, Double)
guess Double -> (Double, Double)
fun
= Int -> Tolerance -> [NewtonStep] -> Root Double
forall a. IterationStep a => Int -> Tolerance -> [a] -> Root Double
findRoot (NewtonParam -> Int
newtonMaxIter NewtonParam
p) (NewtonParam -> Tolerance
newtonTol NewtonParam
p)
([NewtonStep] -> Root Double) -> [NewtonStep] -> Root Double
forall a b. (a -> b) -> a -> b
$ (Double, Double, Double)
-> (Double -> (Double, Double)) -> [NewtonStep]
newtonRaphsonIterations (Double, Double, Double)
guess Double -> (Double, Double)
fun
newtonRaphsonIterations :: (Double,Double,Double) -> (Double -> (Double,Double)) -> [NewtonStep]
newtonRaphsonIterations :: (Double, Double, Double)
-> (Double -> (Double, Double)) -> [NewtonStep]
newtonRaphsonIterations (Double
lo,Double
guess,Double
hi) Double -> (Double, Double)
function
| Double
flo Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 = [Double -> NewtonStep
NewtonRoot Double
lo]
| Double
fhi Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 = [Double -> NewtonStep
NewtonRoot Double
hi]
| Double
floDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
fhi Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 = [NewtonStep
NewtonNoBracket]
| Double
flo Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 = Double -> Double -> Double -> [NewtonStep]
go Double
hi Double
guess' Double
lo
| Bool
otherwise = Double -> Double -> Double -> [NewtonStep]
go Double
lo Double
guess Double
hi
where
(Double
flo,Double
_) = Double -> (Double, Double)
function Double
lo
(Double
fhi,Double
_) = Double -> (Double, Double)
function Double
hi
guess' :: Double
guess'
| Double
guess Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
lo Bool -> Bool -> Bool
&& Double
guess Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
hi = Double
guess
| Double
guess Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
hi Bool -> Bool -> Bool
&& Double
guess Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
lo = Double
guess
| Bool
otherwise = (Double
lo Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
hi) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2
go :: Double -> Double -> Double -> [NewtonStep]
go Double
xA Double
x Double
xB
| Double
f Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 = [Double -> NewtonStep
NewtonRoot Double
x]
| Double
f' Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 = [NewtonStep]
bisectionStep
| (Double
x' Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
xA) Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
x' Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
xB) Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 = [NewtonStep]
newtonStep
| Bool
otherwise = [NewtonStep]
bisectionStep
where
(Double
f,Double
f') = Double -> (Double, Double)
function Double
x
x' :: Double
x' = Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
f Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
f'
newtonStep :: [NewtonStep]
newtonStep
| Double
f Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 = Double -> Double -> NewtonStep
NewtonStep Double
x Double
x' NewtonStep -> [NewtonStep] -> [NewtonStep]
forall a. a -> [a] -> [a]
: Double -> Double -> Double -> [NewtonStep]
go Double
xA Double
x' Double
x
| Bool
otherwise = Double -> Double -> NewtonStep
NewtonStep Double
x Double
x' NewtonStep -> [NewtonStep] -> [NewtonStep]
forall a. a -> [a] -> [a]
: Double -> Double -> Double -> [NewtonStep]
go Double
x Double
x' Double
xB
bisectionStep :: [NewtonStep]
bisectionStep
| Double
f Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 = Double -> Double -> NewtonStep
NewtonBisection Double
xA Double
x NewtonStep -> [NewtonStep] -> [NewtonStep]
forall a. a -> [a] -> [a]
: Double -> Double -> Double -> [NewtonStep]
go Double
xA ((Double
xA Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
x) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2) Double
x
| Bool
otherwise = Double -> Double -> NewtonStep
NewtonBisection Double
x Double
xB NewtonStep -> [NewtonStep] -> [NewtonStep]
forall a. a -> [a] -> [a]
: Double -> Double -> Double -> [NewtonStep]
go Double
x ((Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
xB) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2) Double
xB