module Numeric.GSL.Root (
uniRoot, UniRootMethod(..),
uniRootJ, UniRootMethodJ(..),
root, RootMethod(..),
rootJ, RootMethodJ(..),
) where
import Numeric.LinearAlgebra.HMatrix
import Numeric.GSL.Internal
import Foreign.Ptr(FunPtr, freeHaskellFunPtr)
import Foreign.C.Types
import System.IO.Unsafe(unsafePerformIO)
type TVV = TV (TV Res)
type TVM = TV (TM Res)
data UniRootMethod = Bisection
| FalsePos
| Brent
deriving (Enum, Eq, Show, Bounded)
uniRoot :: UniRootMethod
-> Double
-> Int
-> (Double -> Double)
-> Double
-> Double
-> (Double, Matrix Double)
uniRoot method epsrel maxit fun xl xu = uniRootGen (fi (fromEnum method)) fun xl xu epsrel maxit
uniRootGen m f xl xu epsrel maxit = unsafePerformIO $ do
fp <- mkDoublefun f
rawpath <- createMIO maxit 4
(c_root m fp epsrel (fi maxit) xl xu)
"root"
let it = round (rawpath `atIndex` (maxit1,0))
path = takeRows it rawpath
[sol] = toLists $ dropRows (it1) path
freeHaskellFunPtr fp
return (sol !! 1, path)
foreign import ccall safe "root"
c_root:: CInt -> FunPtr (Double -> Double) -> Double -> CInt -> Double -> Double -> TM Res
data UniRootMethodJ = UNewton
| Secant
| Steffenson
deriving (Enum, Eq, Show, Bounded)
uniRootJ :: UniRootMethodJ
-> Double
-> Int
-> (Double -> Double)
-> (Double -> Double)
-> Double
-> (Double, Matrix Double)
uniRootJ method epsrel maxit fun dfun x = uniRootJGen (fi (fromEnum method)) fun
dfun x epsrel maxit
uniRootJGen m f df x epsrel maxit = unsafePerformIO $ do
fp <- mkDoublefun f
dfp <- mkDoublefun df
rawpath <- createMIO maxit 2
(c_rootj m fp dfp epsrel (fi maxit) x)
"rootj"
let it = round (rawpath `atIndex` (maxit1,0))
path = takeRows it rawpath
[sol] = toLists $ dropRows (it1) path
freeHaskellFunPtr fp
return (sol !! 1, path)
foreign import ccall safe "rootj"
c_rootj :: CInt -> FunPtr (Double -> Double) -> FunPtr (Double -> Double)
-> Double -> CInt -> Double -> TM Res
data RootMethod = Hybrids
| Hybrid
| DNewton
| Broyden
deriving (Enum,Eq,Show,Bounded)
root :: RootMethod
-> Double
-> Int
-> ([Double] -> [Double])
-> [Double]
-> ([Double], Matrix Double)
root method epsabs maxit fun xinit = rootGen (fi (fromEnum method)) fun xinit epsabs maxit
rootGen m f xi epsabs maxit = unsafePerformIO $ do
let xiv = fromList xi
n = size xiv
fp <- mkVecVecfun (aux_vTov (checkdim1 n . fromList . f . toList))
rawpath <- vec xiv $ \xiv' ->
createMIO maxit (2*n+1)
(c_multiroot m fp epsabs (fi maxit) // xiv')
"multiroot"
let it = round (rawpath `atIndex` (maxit1,0))
path = takeRows it rawpath
[sol] = toLists $ dropRows (it1) path
freeHaskellFunPtr fp
return (take n $ drop 1 sol, path)
foreign import ccall safe "multiroot"
c_multiroot:: CInt -> FunPtr TVV -> Double -> CInt -> TVM
data RootMethodJ = HybridsJ
| HybridJ
| Newton
| GNewton
deriving (Enum,Eq,Show,Bounded)
rootJ :: RootMethodJ
-> Double
-> Int
-> ([Double] -> [Double])
-> ([Double] -> [[Double]])
-> [Double]
-> ([Double], Matrix Double)
rootJ method epsabs maxit fun jac xinit = rootJGen (fi (fromEnum method)) fun jac xinit epsabs maxit
rootJGen m f jac xi epsabs maxit = unsafePerformIO $ do
let xiv = fromList xi
n = size xiv
fp <- mkVecVecfun (aux_vTov (checkdim1 n . fromList . f . toList))
jp <- mkVecMatfun (aux_vTom (checkdim2 n . fromLists . jac . toList))
rawpath <- vec xiv $ \xiv' ->
createMIO maxit (2*n+1)
(c_multirootj m fp jp epsabs (fi maxit) // xiv')
"multiroot"
let it = round (rawpath `atIndex` (maxit1,0))
path = takeRows it rawpath
[sol] = toLists $ dropRows (it1) path
freeHaskellFunPtr fp
freeHaskellFunPtr jp
return (take n $ drop 1 sol, path)
foreign import ccall safe "multirootj"
c_multirootj:: CInt -> FunPtr TVV -> FunPtr TVM -> Double -> CInt -> TVM
checkdim1 n v
| size v == n = v
| otherwise = error $ "Error: "++ show n
++ " components expected in the result of the function supplied to root"
checkdim2 n m
| rows m == n && cols m == n = m
| otherwise = error $ "Error: "++ show n ++ "x" ++ show n
++ " Jacobian expected in rootJ"