{-# INCLUDE <bindings.macros.h> #-}
{-# INCLUDE <gsl/gsl_fit.h> #-}
{-# LINE 1 "src/Bindings/Gsl/LeastSquaresFitting.hsc" #-}

{-# LINE 2 "src/Bindings/Gsl/LeastSquaresFitting.hsc" #-}

{-# LINE 3 "src/Bindings/Gsl/LeastSquaresFitting.hsc" #-}

-- | <http://www.gnu.org/software/gsl/manual/html_node/Least_002dSquares-Fitting.html>

module Bindings.Gsl.LeastSquaresFitting where
import Foreign.Ptr (Ptr,FunPtr,plusPtr)
import Foreign.Ptr (wordPtrToPtr,castPtrToFunPtr)
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String (CString,CStringLen,CWString,CWStringLen)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word

{-# LINE 8 "src/Bindings/Gsl/LeastSquaresFitting.hsc" #-}

foreign import ccall "gsl_fit_linear" c'gsl_fit_linear
  :: Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> CSize -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_fit_linear" p'gsl_fit_linear
  :: FunPtr (Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> CSize -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 13 "src/Bindings/Gsl/LeastSquaresFitting.hsc" #-}
foreign import ccall "gsl_fit_wlinear" c'gsl_fit_wlinear
  :: Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> CSize -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_fit_wlinear" p'gsl_fit_wlinear
  :: FunPtr (Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> CSize -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 18 "src/Bindings/Gsl/LeastSquaresFitting.hsc" #-}
foreign import ccall "gsl_fit_linear_est" c'gsl_fit_linear_est
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_fit_linear_est" p'gsl_fit_linear_est
  :: FunPtr (CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 21 "src/Bindings/Gsl/LeastSquaresFitting.hsc" #-}
foreign import ccall "gsl_fit_mul" c'gsl_fit_mul
  :: Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> CSize -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_fit_mul" p'gsl_fit_mul
  :: FunPtr (Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> CSize -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 24 "src/Bindings/Gsl/LeastSquaresFitting.hsc" #-}
foreign import ccall "gsl_fit_wmul" c'gsl_fit_wmul
  :: Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> CSize -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_fit_wmul" p'gsl_fit_wmul
  :: FunPtr (Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> Ptr CDouble -> CSize -> CSize -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 28 "src/Bindings/Gsl/LeastSquaresFitting.hsc" #-}
foreign import ccall "gsl_fit_mul_est" c'gsl_fit_mul_est
  :: CDouble -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_fit_mul_est" p'gsl_fit_mul_est
  :: FunPtr (CDouble -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 30 "src/Bindings/Gsl/LeastSquaresFitting.hsc" #-}