{-# OPTIONS_GHC -fglasgow-exts #-} ----------------------------------------------------------------------------- -- | -- Module : Numeric.GSL.Fitting.Linear -- Copyright : (c) Alexander Vivian Hugh McPhail 2010 -- License : GPL-style -- -- Maintainer : haskell.vivian.mcphail gmail com -- Stability : provisional -- Portability : uses ffi -- -- GSL linear regression functions -- ----------------------------------------------------------------------------- module Numeric.GSL.Fitting.Linear ( linear, linear_w ) where ----------------------------------------------------------------------------- import Data.Packed.Vector import Data.Packed.Matrix import Data.Packed.Development --import Numeric.LinearAlgebra.Linear --import Control.Monad(when) import Foreign import Foreign.ForeignPtr --import Foreign.Marshal.Alloc(alloca) import Foreign.C.Types(CInt) --import Foreign.C.String(newCString,peekCString) --import GHC.ForeignPtr (mallocPlainForeignPtrBytes) --import GHC.Base --import GHC.IOBase --import Prelude hiding(reverse) ----------------------------------------------------------------------------- -- | fits the model Y = C X linear :: Vector Double -- ^ x data -> Vector Double -- ^ y data -> (Vector Double,Vector Double,Matrix Double,Matrix Double,Matrix Double,Matrix Double) -- ^ (c_0,c_1,cov_00,cov_01,cov_11,chi_sq) linear x y = unsafePerformIO $ do let s = dim x c0 <- createVector 1 c1 <- createVector 1 cov00 <- createMatrix RowMajor s s cov01 <- createMatrix RowMajor s s cov11 <- createMatrix RowMajor s s chi_sq <- createMatrix RowMajor s s app8 fitting_linear vec x vec y vec c0 vec c1 mat cov00 mat cov01 mat cov11 mat chi_sq "linear" return (c0,c1,cov00,cov01,cov11,chi_sq) ----------------------------------------------------------------------------- foreign import ccall "fitting-aux.h linear" fitting_linear :: CInt -> Ptr Double -> CInt -> Ptr Double -> CInt -> Ptr Double -> CInt -> Ptr Double -> CInt -> CInt -> Ptr Double -> CInt -> CInt -> Ptr Double -> CInt -> CInt -> Ptr Double -> CInt -> CInt -> Ptr Double -> IO CInt ----------------------------------------------------------------------------- -- | fits the model Y = C X, with x data weighted linear_w :: Vector Double -- ^ x data -> Vector Double -- ^ x weights -> Vector Double -- ^ y data -> (Vector Double,Vector Double,Matrix Double,Matrix Double,Matrix Double,Matrix Double) -- ^ (c_0,c_1,cov_00,cov_01,cov_11,chi_sq) linear_w x w y = unsafePerformIO $ do let s = dim x c0 <- createVector 1 c1 <- createVector 1 cov00 <- createMatrix RowMajor s s cov01 <- createMatrix RowMajor s s cov11 <- createMatrix RowMajor s s chi_sq <- createMatrix RowMajor s s app9 fitting_linear_w vec x vec w vec y vec c0 vec c1 mat cov00 mat cov01 mat cov11 mat chi_sq "linear_w" return (c0,c1,cov00,cov01,cov11,chi_sq) ----------------------------------------------------------------------------- foreign import ccall "fitting-aux.h linear_weighted" fitting_linear_w :: CInt -> Ptr Double -> CInt -> Ptr Double -> CInt -> Ptr Double -> CInt -> Ptr Double -> CInt -> Ptr Double -> CInt -> CInt -> Ptr Double -> CInt -> CInt -> Ptr Double -> CInt -> CInt -> Ptr Double -> CInt -> CInt -> Ptr Double -> IO CInt -----------------------------------------------------------------------------