{-# LINE 1 "src/Bindings/Gsl/Interpolation.hsc" #-}

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

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

{-# LINE 4 "src/Bindings/Gsl/Interpolation.hsc" #-}

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

module Bindings.Gsl.Interpolation 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.Alloc (alloca)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word

{-# LINE 9 "src/Bindings/Gsl/Interpolation.hsc" #-}


{-# LINE 11 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 12 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 13 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 14 "src/Bindings/Gsl/Interpolation.hsc" #-}
data C'gsl_interp_accel = C'gsl_interp_accel{
  c'gsl_interp_accel'cache :: CSize,
  c'gsl_interp_accel'miss_count :: CSize,
  c'gsl_interp_accel'hit_count :: CSize
} deriving (Eq,Show)
p'gsl_interp_accel'cache p = plusPtr p 0
p'gsl_interp_accel'cache :: Ptr (C'gsl_interp_accel) -> Ptr (CSize)
p'gsl_interp_accel'miss_count p = plusPtr p 4
p'gsl_interp_accel'miss_count :: Ptr (C'gsl_interp_accel) -> Ptr (CSize)
p'gsl_interp_accel'hit_count p = plusPtr p 8
p'gsl_interp_accel'hit_count :: Ptr (C'gsl_interp_accel) -> Ptr (CSize)
instance Storable C'gsl_interp_accel where
  sizeOf _ = 12
  alignment _ = 4
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    return $ C'gsl_interp_accel v0 v1 v2
  poke p (C'gsl_interp_accel v0 v1 v2) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    return ()

{-# LINE 15 "src/Bindings/Gsl/Interpolation.hsc" #-}


{-# LINE 17 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 18 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 19 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 20 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 21 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 22 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 23 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 24 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 25 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 26 "src/Bindings/Gsl/Interpolation.hsc" #-}
data C'gsl_interp_type = C'gsl_interp_type{
  c'gsl_interp_type'name :: CString,
  c'gsl_interp_type'min_size :: CUInt,
  c'gsl_interp_type'alloc :: FunPtr (CSize -> IO (Ptr ())),
  c'gsl_interp_type'init :: FunPtr (Ptr () -> Ptr CDouble -> Ptr CDouble -> CSize -> IO CInt),
  c'gsl_interp_type'eval :: FunPtr ( Ptr () -> Ptr CDouble -> Ptr CDouble -> CSize -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt),
  c'gsl_interp_type'eval_deriv :: FunPtr ( Ptr () -> Ptr CDouble -> Ptr CDouble -> CSize -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt),
  c'gsl_interp_type'eval_deriv2 :: FunPtr ( Ptr () -> Ptr CDouble -> Ptr CDouble -> CSize -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt),
  c'gsl_interp_type'eval_integ :: FunPtr ( Ptr () -> Ptr CDouble -> Ptr CDouble -> CSize -> Ptr C'gsl_interp_accel -> CDouble -> CDouble -> Ptr CDouble -> IO CInt),
  c'gsl_interp_type'free :: FunPtr (Ptr () -> IO ())
} deriving (Eq,Show)
p'gsl_interp_type'name p = plusPtr p 0
p'gsl_interp_type'name :: Ptr (C'gsl_interp_type) -> Ptr (CString)
p'gsl_interp_type'min_size p = plusPtr p 4
p'gsl_interp_type'min_size :: Ptr (C'gsl_interp_type) -> Ptr (CUInt)
p'gsl_interp_type'alloc p = plusPtr p 8
p'gsl_interp_type'alloc :: Ptr (C'gsl_interp_type) -> Ptr (FunPtr (CSize -> IO (Ptr ())))
p'gsl_interp_type'init p = plusPtr p 12
p'gsl_interp_type'init :: Ptr (C'gsl_interp_type) -> Ptr (FunPtr (Ptr () -> Ptr CDouble -> Ptr CDouble -> CSize -> IO CInt))
p'gsl_interp_type'eval p = plusPtr p 16
p'gsl_interp_type'eval :: Ptr (C'gsl_interp_type) -> Ptr (FunPtr ( Ptr () -> Ptr CDouble -> Ptr CDouble -> CSize -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt))
p'gsl_interp_type'eval_deriv p = plusPtr p 20
p'gsl_interp_type'eval_deriv :: Ptr (C'gsl_interp_type) -> Ptr (FunPtr ( Ptr () -> Ptr CDouble -> Ptr CDouble -> CSize -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt))
p'gsl_interp_type'eval_deriv2 p = plusPtr p 24
p'gsl_interp_type'eval_deriv2 :: Ptr (C'gsl_interp_type) -> Ptr (FunPtr ( Ptr () -> Ptr CDouble -> Ptr CDouble -> CSize -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt))
p'gsl_interp_type'eval_integ p = plusPtr p 28
p'gsl_interp_type'eval_integ :: Ptr (C'gsl_interp_type) -> Ptr (FunPtr ( Ptr () -> Ptr CDouble -> Ptr CDouble -> CSize -> Ptr C'gsl_interp_accel -> CDouble -> CDouble -> Ptr CDouble -> IO CInt))
p'gsl_interp_type'free p = plusPtr p 32
p'gsl_interp_type'free :: Ptr (C'gsl_interp_type) -> Ptr (FunPtr (Ptr () -> IO ()))
instance Storable C'gsl_interp_type where
  sizeOf _ = 36
  alignment _ = 4
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    v8 <- peekByteOff p 32
    return $ C'gsl_interp_type v0 v1 v2 v3 v4 v5 v6 v7 v8
  poke p (C'gsl_interp_type v0 v1 v2 v3 v4 v5 v6 v7 v8) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    pokeByteOff p 32 v8
    return ()

{-# LINE 27 "src/Bindings/Gsl/Interpolation.hsc" #-}


{-# LINE 29 "src/Bindings/Gsl/Interpolation.hsc" #-}

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

{-# LINE 31 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 32 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 33 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 34 "src/Bindings/Gsl/Interpolation.hsc" #-}
data C'gsl_interp = C'gsl_interp{
  c'gsl_interp'type :: Ptr C'gsl_interp_type,
  c'gsl_interp'xmin :: CDouble,
  c'gsl_interp'xmax :: CDouble,
  c'gsl_interp'size :: CSize,
  c'gsl_interp'state :: Ptr ()
} deriving (Eq,Show)
p'gsl_interp'type p = plusPtr p 0
p'gsl_interp'type :: Ptr (C'gsl_interp) -> Ptr (Ptr C'gsl_interp_type)
p'gsl_interp'xmin p = plusPtr p 4
p'gsl_interp'xmin :: Ptr (C'gsl_interp) -> Ptr (CDouble)
p'gsl_interp'xmax p = plusPtr p 12
p'gsl_interp'xmax :: Ptr (C'gsl_interp) -> Ptr (CDouble)
p'gsl_interp'size p = plusPtr p 20
p'gsl_interp'size :: Ptr (C'gsl_interp) -> Ptr (CSize)
p'gsl_interp'state p = plusPtr p 24
p'gsl_interp'state :: Ptr (C'gsl_interp) -> Ptr (Ptr ())
instance Storable C'gsl_interp where
  sizeOf _ = 28
  alignment _ = 4
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 12
    v3 <- peekByteOff p 20
    v4 <- peekByteOff p 24
    return $ C'gsl_interp v0 v1 v2 v3 v4
  poke p (C'gsl_interp v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 12 v2
    pokeByteOff p 20 v3
    pokeByteOff p 24 v4
    return ()

{-# LINE 35 "src/Bindings/Gsl/Interpolation.hsc" #-}

foreign import ccall "&gsl_interp_linear" p'gsl_interp_linear
  :: Ptr (Ptr gsl_interp_type)

{-# LINE 37 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "&gsl_interp_polynomial" p'gsl_interp_polynomial
  :: Ptr (Ptr gsl_interp_type)

{-# LINE 38 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "&gsl_interp_cspline" p'gsl_interp_cspline
  :: Ptr (Ptr gsl_interp_type)

{-# LINE 39 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "&gsl_interp_cspline_periodic" p'gsl_interp_cspline_periodic
  :: Ptr (Ptr gsl_interp_type)

{-# LINE 40 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "&gsl_interp_akima" p'gsl_interp_akima
  :: Ptr (Ptr gsl_interp_type)

{-# LINE 41 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "&gsl_interp_akima_periodic" p'gsl_interp_akima_periodic
  :: Ptr (Ptr gsl_interp_type)

{-# LINE 42 "src/Bindings/Gsl/Interpolation.hsc" #-}

foreign import ccall "gsl_interp_accel_alloc" c'gsl_interp_accel_alloc
  :: IO (Ptr C'gsl_interp_accel)
foreign import ccall "&gsl_interp_accel_alloc" p'gsl_interp_accel_alloc
  :: FunPtr (IO (Ptr C'gsl_interp_accel))

{-# LINE 44 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_accel_reset" c'gsl_interp_accel_reset
  :: Ptr C'gsl_interp_accel -> IO CInt
foreign import ccall "&gsl_interp_accel_reset" p'gsl_interp_accel_reset
  :: FunPtr (Ptr C'gsl_interp_accel -> IO CInt)

{-# LINE 45 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_accel_free" c'gsl_interp_accel_free
  :: Ptr C'gsl_interp_accel -> IO ()
foreign import ccall "&gsl_interp_accel_free" p'gsl_interp_accel_free
  :: FunPtr (Ptr C'gsl_interp_accel -> IO ())

{-# LINE 46 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_alloc" c'gsl_interp_alloc
  :: Ptr C'gsl_interp_type -> CSize -> IO (Ptr C'gsl_interp)
foreign import ccall "&gsl_interp_alloc" p'gsl_interp_alloc
  :: FunPtr (Ptr C'gsl_interp_type -> CSize -> IO (Ptr C'gsl_interp))

{-# LINE 47 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_init" c'gsl_interp_init
  :: Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CSize -> IO CInt
foreign import ccall "&gsl_interp_init" p'gsl_interp_init
  :: FunPtr (Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CSize -> IO CInt)

{-# LINE 48 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_name" c'gsl_interp_name
  :: Ptr C'gsl_interp -> IO CString
foreign import ccall "&gsl_interp_name" p'gsl_interp_name
  :: FunPtr (Ptr C'gsl_interp -> IO CString)

{-# LINE 49 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_min_size" c'gsl_interp_min_size
  :: Ptr C'gsl_interp -> IO CUInt
foreign import ccall "&gsl_interp_min_size" p'gsl_interp_min_size
  :: FunPtr (Ptr C'gsl_interp -> IO CUInt)

{-# LINE 50 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_type_min_size" c'gsl_interp_type_min_size
  :: Ptr C'gsl_interp_type -> IO CUInt
foreign import ccall "&gsl_interp_type_min_size" p'gsl_interp_type_min_size
  :: FunPtr (Ptr C'gsl_interp_type -> IO CUInt)

{-# LINE 51 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_eval_e" c'gsl_interp_eval_e
  :: Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_interp_eval_e" p'gsl_interp_eval_e
  :: FunPtr (Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt)

{-# LINE 52 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_eval" c'gsl_interp_eval
  :: Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble
foreign import ccall "&gsl_interp_eval" p'gsl_interp_eval
  :: FunPtr (Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble)

{-# LINE 53 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_eval_deriv_e" c'gsl_interp_eval_deriv_e
  :: Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_interp_eval_deriv_e" p'gsl_interp_eval_deriv_e
  :: FunPtr (Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt)

{-# LINE 54 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_eval_deriv" c'gsl_interp_eval_deriv
  :: Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble
foreign import ccall "&gsl_interp_eval_deriv" p'gsl_interp_eval_deriv
  :: FunPtr (Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble)

{-# LINE 55 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_eval_deriv2_e" c'gsl_interp_eval_deriv2_e
  :: Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_interp_eval_deriv2_e" p'gsl_interp_eval_deriv2_e
  :: FunPtr (Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt)

{-# LINE 56 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_eval_deriv2" c'gsl_interp_eval_deriv2
  :: Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble
foreign import ccall "&gsl_interp_eval_deriv2" p'gsl_interp_eval_deriv2
  :: FunPtr (Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble)

{-# LINE 57 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_eval_integ_e" c'gsl_interp_eval_integ_e
  :: Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_interp_eval_integ_e" p'gsl_interp_eval_integ_e
  :: FunPtr (Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt)

{-# LINE 58 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_eval_integ" c'gsl_interp_eval_integ
  :: Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble
foreign import ccall "&gsl_interp_eval_integ" p'gsl_interp_eval_integ
  :: FunPtr (Ptr C'gsl_interp -> Ptr CDouble -> Ptr CDouble -> CDouble -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble)

{-# LINE 59 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_free" c'gsl_interp_free
  :: Ptr C'gsl_interp -> IO ()
foreign import ccall "&gsl_interp_free" p'gsl_interp_free
  :: FunPtr (Ptr C'gsl_interp -> IO ())

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

{-# LINE 61 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_interp_accel_find" c'gsl_interp_accel_find
  :: Ptr C'gsl_interp_accel -> Ptr CDouble -> CSize -> CDouble -> IO CSize
foreign import ccall "&gsl_interp_accel_find" p'gsl_interp_accel_find
  :: FunPtr (Ptr C'gsl_interp_accel -> Ptr CDouble -> CSize -> CDouble -> IO CSize)

{-# LINE 62 "src/Bindings/Gsl/Interpolation.hsc" #-}


{-# LINE 64 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 65 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 66 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 67 "src/Bindings/Gsl/Interpolation.hsc" #-}

{-# LINE 68 "src/Bindings/Gsl/Interpolation.hsc" #-}
data C'gsl_spline = C'gsl_spline{
  c'gsl_spline'interp :: Ptr C'gsl_interp,
  c'gsl_spline'x :: Ptr CDouble,
  c'gsl_spline'y :: Ptr CDouble,
  c'gsl_spline'size :: CSize
} deriving (Eq,Show)
p'gsl_spline'interp p = plusPtr p 0
p'gsl_spline'interp :: Ptr (C'gsl_spline) -> Ptr (Ptr C'gsl_interp)
p'gsl_spline'x p = plusPtr p 4
p'gsl_spline'x :: Ptr (C'gsl_spline) -> Ptr (Ptr CDouble)
p'gsl_spline'y p = plusPtr p 8
p'gsl_spline'y :: Ptr (C'gsl_spline) -> Ptr (Ptr CDouble)
p'gsl_spline'size p = plusPtr p 12
p'gsl_spline'size :: Ptr (C'gsl_spline) -> Ptr (CSize)
instance Storable C'gsl_spline where
  sizeOf _ = 16
  alignment _ = 4
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    return $ C'gsl_spline v0 v1 v2 v3
  poke p (C'gsl_spline v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    return ()

{-# LINE 69 "src/Bindings/Gsl/Interpolation.hsc" #-}

foreign import ccall "gsl_spline_alloc" c'gsl_spline_alloc
  :: Ptr C'gsl_interp_type -> CSize -> IO (Ptr C'gsl_spline)
foreign import ccall "&gsl_spline_alloc" p'gsl_spline_alloc
  :: FunPtr (Ptr C'gsl_interp_type -> CSize -> IO (Ptr C'gsl_spline))

{-# LINE 71 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_init" c'gsl_spline_init
  :: Ptr C'gsl_spline -> Ptr CDouble -> Ptr CDouble -> CSize -> IO CInt
foreign import ccall "&gsl_spline_init" p'gsl_spline_init
  :: FunPtr (Ptr C'gsl_spline -> Ptr CDouble -> Ptr CDouble -> CSize -> IO CInt)

{-# LINE 72 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_name" c'gsl_spline_name
  :: Ptr C'gsl_spline -> IO CString
foreign import ccall "&gsl_spline_name" p'gsl_spline_name
  :: FunPtr (Ptr C'gsl_spline -> IO CString)

{-# LINE 73 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_min_size" c'gsl_spline_min_size
  :: Ptr C'gsl_spline -> IO CUInt
foreign import ccall "&gsl_spline_min_size" p'gsl_spline_min_size
  :: FunPtr (Ptr C'gsl_spline -> IO CUInt)

{-# LINE 74 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_eval_e" c'gsl_spline_eval_e
  :: Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_spline_eval_e" p'gsl_spline_eval_e
  :: FunPtr (Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt)

{-# LINE 75 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_eval" c'gsl_spline_eval
  :: Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble
foreign import ccall "&gsl_spline_eval" p'gsl_spline_eval
  :: FunPtr (Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble)

{-# LINE 76 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_eval_deriv_e" c'gsl_spline_eval_deriv_e
  :: Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_spline_eval_deriv_e" p'gsl_spline_eval_deriv_e
  :: FunPtr (Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt)

{-# LINE 77 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_eval_deriv" c'gsl_spline_eval_deriv
  :: Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble
foreign import ccall "&gsl_spline_eval_deriv" p'gsl_spline_eval_deriv
  :: FunPtr (Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble)

{-# LINE 78 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_eval_deriv2_e" c'gsl_spline_eval_deriv2_e
  :: Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_spline_eval_deriv2_e" p'gsl_spline_eval_deriv2_e
  :: FunPtr (Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt)

{-# LINE 79 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_eval_deriv2" c'gsl_spline_eval_deriv2
  :: Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble
foreign import ccall "&gsl_spline_eval_deriv2" p'gsl_spline_eval_deriv2
  :: FunPtr (Ptr C'gsl_spline -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble)

{-# LINE 80 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_eval_integ_e" c'gsl_spline_eval_integ_e
  :: Ptr C'gsl_spline -> CDouble -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_spline_eval_integ_e" p'gsl_spline_eval_integ_e
  :: FunPtr (Ptr C'gsl_spline -> CDouble -> CDouble -> Ptr C'gsl_interp_accel -> Ptr CDouble -> IO CInt)

{-# LINE 81 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_eval_integ" c'gsl_spline_eval_integ
  :: Ptr C'gsl_spline -> CDouble -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble
foreign import ccall "&gsl_spline_eval_integ" p'gsl_spline_eval_integ
  :: FunPtr (Ptr C'gsl_spline -> CDouble -> CDouble -> Ptr C'gsl_interp_accel -> IO CDouble)

{-# LINE 82 "src/Bindings/Gsl/Interpolation.hsc" #-}
foreign import ccall "gsl_spline_free" c'gsl_spline_free
  :: Ptr C'gsl_spline -> IO ()
foreign import ccall "&gsl_spline_free" p'gsl_spline_free
  :: FunPtr (Ptr C'gsl_spline -> IO ())

{-# LINE 83 "src/Bindings/Gsl/Interpolation.hsc" #-}