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

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

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

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

module Bindings.Gsl.NumericalIntegration 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 8 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
import Bindings.Gsl.MathematicalFunctions

data C'gsl_integration_workspace = C'gsl_integration_workspace{
{-# LINE 11 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

  c'gsl_integration_workspace'limit :: CSize
{-# LINE 12 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_workspace'size :: CSize
{-# LINE 13 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_workspace'nrmax :: CSize
{-# LINE 14 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_workspace'i :: CSize
{-# LINE 15 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_workspace'maximum_level :: CSize
{-# LINE 16 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_workspace'alist :: Ptr CDouble
{-# LINE 17 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_workspace'blist :: Ptr CDouble
{-# LINE 18 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_workspace'rlist :: Ptr CDouble
{-# LINE 19 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_workspace'elist :: Ptr CDouble
{-# LINE 20 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_workspace'order :: Ptr CSize
{-# LINE 21 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_workspace'level :: Ptr CSize
{-# LINE 22 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_integration_workspace where
  sizeOf _ = 44
  alignment = sizeOf
  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
    v9 <- peekByteOff p 36
    v10 <- peekByteOff p 40
    return $ C'gsl_integration_workspace v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10
  poke p (C'gsl_integration_workspace v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10) = 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
    pokeByteOff p 36 v9
    pokeByteOff p 40 v10
    return ()

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

foreign import ccall "gsl_integration_workspace_alloc" c'gsl_integration_workspace_alloc
  :: CSize -> IO (Ptr C'gsl_integration_workspace)
foreign import ccall "&gsl_integration_workspace_alloc" p'gsl_integration_workspace_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_integration_workspace))

{-# LINE 25 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_workspace_free" c'gsl_integration_workspace_free
  :: Ptr C'gsl_integration_workspace -> IO ()
foreign import ccall "&gsl_integration_workspace_free" p'gsl_integration_workspace_free
  :: FunPtr (Ptr C'gsl_integration_workspace -> IO ())

{-# LINE 26 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

data C'gsl_integration_qaws_table = C'gsl_integration_qaws_table{
{-# LINE 28 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

  c'gsl_integration_qaws_table'alpha :: CDouble
{-# LINE 29 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qaws_table'beta :: CDouble
{-# LINE 30 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qaws_table'mu :: CInt
{-# LINE 31 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qaws_table'nu :: CInt
{-# LINE 32 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qaws_table'ri :: [CDouble]
{-# LINE 33 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qaws_table'rj :: [CDouble]
{-# LINE 34 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qaws_table'rg :: [CDouble]
{-# LINE 35 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qaws_table'rh :: [CDouble]
{-# LINE 36 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_integration_qaws_table where
  sizeOf _ = 824
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 8
    v2 <- peekByteOff p 16
    v3 <- peekByteOff p 20
    v4 <- peekArray 25 (plusPtr p 24)
    v5 <- peekArray 25 (plusPtr p 224)
    v6 <- peekArray 25 (plusPtr p 424)
    v7 <- peekArray 25 (plusPtr p 624)
    return $ C'gsl_integration_qaws_table v0 v1 v2 v3 v4 v5 v6 v7
  poke p (C'gsl_integration_qaws_table v0 v1 v2 v3 v4 v5 v6 v7) = do
    pokeByteOff p 0 v0
    pokeByteOff p 8 v1
    pokeByteOff p 16 v2
    pokeByteOff p 20 v3
    pokeArray (plusPtr p 24) (take 25 v4)
    pokeArray (plusPtr p 224) (take 25 v5)
    pokeArray (plusPtr p 424) (take 25 v6)
    pokeArray (plusPtr p 624) (take 25 v7)
    return ()

{-# LINE 37 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

foreign import ccall "gsl_integration_qaws_table_alloc" c'gsl_integration_qaws_table_alloc
  :: CDouble -> CDouble -> CInt -> CInt -> CInt -> IO (Ptr C'gsl_integration_qaws_table)
foreign import ccall "&gsl_integration_qaws_table_alloc" p'gsl_integration_qaws_table_alloc
  :: FunPtr (CDouble -> CDouble -> CInt -> CInt -> CInt -> IO (Ptr C'gsl_integration_qaws_table))

{-# LINE 39 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qaws_table_set" c'gsl_integration_qaws_table_set
  :: Ptr C'gsl_integration_qaws_table -> CDouble -> CDouble -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "&gsl_integration_qaws_table_set" p'gsl_integration_qaws_table_set
  :: FunPtr (Ptr C'gsl_integration_qaws_table -> CDouble -> CDouble -> CInt -> CInt -> CInt -> IO CInt)

{-# LINE 40 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qaws_table_free" c'gsl_integration_qaws_table_free
  :: Ptr C'gsl_integration_qaws_table -> IO ()
foreign import ccall "&gsl_integration_qaws_table_free" p'gsl_integration_qaws_table_free
  :: FunPtr (Ptr C'gsl_integration_qaws_table -> IO ())

{-# LINE 41 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

type C'gsl_integration_qawo_enum = CUInt

{-# LINE 43 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
c'GSL_INTEG_COSINE = 0
c'GSL_INTEG_COSINE :: (Num a) => a

{-# LINE 44 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
c'GSL_INTEG_SINE = 1
c'GSL_INTEG_SINE :: (Num a) => a

{-# LINE 45 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

data C'gsl_integration_qawo_table = C'gsl_integration_qawo_table{
{-# LINE 47 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

  c'gsl_integration_qawo_table'n :: CSize
{-# LINE 48 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qawo_table'omega :: CDouble
{-# LINE 49 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qawo_table'L :: CDouble
{-# LINE 50 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qawo_table'par :: CDouble
{-# LINE 51 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qawo_table'sine :: C'gsl_integration_qawo_enum
{-# LINE 52 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
,
  c'gsl_integration_qawo_table'chebmo :: Ptr CDouble
{-# LINE 53 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_integration_qawo_table where
  sizeOf _ = 36
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 12
    v3 <- peekByteOff p 20
    v4 <- peekByteOff p 28
    v5 <- peekByteOff p 32
    return $ C'gsl_integration_qawo_table v0 v1 v2 v3 v4 v5
  poke p (C'gsl_integration_qawo_table v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 12 v2
    pokeByteOff p 20 v3
    pokeByteOff p 28 v4
    pokeByteOff p 32 v5
    return ()

{-# LINE 54 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

foreign import ccall "gsl_integration_qawo_table_alloc" c'gsl_integration_qawo_table_alloc
  :: CDouble -> CDouble -> C'gsl_integration_qawo_enum -> CSize -> IO (Ptr C'gsl_integration_qawo_table)
foreign import ccall "&gsl_integration_qawo_table_alloc" p'gsl_integration_qawo_table_alloc
  :: FunPtr (CDouble -> CDouble -> C'gsl_integration_qawo_enum -> CSize -> IO (Ptr C'gsl_integration_qawo_table))

{-# LINE 56 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qawo_table_set" c'gsl_integration_qawo_table_set
  :: Ptr C'gsl_integration_qawo_table -> CDouble -> CDouble -> C'gsl_integration_qawo_enum -> IO CInt
foreign import ccall "&gsl_integration_qawo_table_set" p'gsl_integration_qawo_table_set
  :: FunPtr (Ptr C'gsl_integration_qawo_table -> CDouble -> CDouble -> C'gsl_integration_qawo_enum -> IO CInt)

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

{-# LINE 58 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qawo_table_free" c'gsl_integration_qawo_table_free
  :: Ptr C'gsl_integration_qawo_table -> IO ()
foreign import ccall "&gsl_integration_qawo_table_free" p'gsl_integration_qawo_table_free
  :: FunPtr (Ptr C'gsl_integration_qawo_table -> IO ())

{-# LINE 59 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

type C'gsl_integration_rule = FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())
foreign import ccall "wrapper" mk'gsl_integration_rule
  :: (Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()) -> IO C'gsl_integration_rule
foreign import ccall "dynamic" mK'gsl_integration_rule
  :: C'gsl_integration_rule -> (Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())

{-# LINE 61 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

foreign import ccall "gsl_integration_qk15" c'gsl_integration_qk15
  :: Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_integration_qk15" p'gsl_integration_qk15
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())

{-# LINE 63 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qk21" c'gsl_integration_qk21
  :: Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_integration_qk21" p'gsl_integration_qk21
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())

{-# LINE 64 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qk31" c'gsl_integration_qk31
  :: Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_integration_qk31" p'gsl_integration_qk31
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())

{-# LINE 65 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qk41" c'gsl_integration_qk41
  :: Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_integration_qk41" p'gsl_integration_qk41
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())

{-# LINE 66 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qk51" c'gsl_integration_qk51
  :: Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_integration_qk51" p'gsl_integration_qk51
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())

{-# LINE 67 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qk61" c'gsl_integration_qk61
  :: Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_integration_qk61" p'gsl_integration_qk61
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())

{-# LINE 68 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qcheb" c'gsl_integration_qcheb
  :: Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_integration_qcheb" p'gsl_integration_qcheb
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())

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

c'GSL_INTEG_GAUSS15 = 1
c'GSL_INTEG_GAUSS15 :: (Num a) => a

{-# LINE 71 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
c'GSL_INTEG_GAUSS21 = 2
c'GSL_INTEG_GAUSS21 :: (Num a) => a

{-# LINE 72 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
c'GSL_INTEG_GAUSS31 = 3
c'GSL_INTEG_GAUSS31 :: (Num a) => a

{-# LINE 73 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
c'GSL_INTEG_GAUSS41 = 4
c'GSL_INTEG_GAUSS41 :: (Num a) => a

{-# LINE 74 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
c'GSL_INTEG_GAUSS51 = 5
c'GSL_INTEG_GAUSS51 :: (Num a) => a

{-# LINE 75 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
c'GSL_INTEG_GAUSS61 = 6
c'GSL_INTEG_GAUSS61 :: (Num a) => a

{-# LINE 76 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}

foreign import ccall "gsl_integration_qk" c'gsl_integration_qk
  :: CInt -> CInt -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_integration_qk" p'gsl_integration_qk
  :: FunPtr (CInt -> CInt -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr C'gsl_function -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())

{-# LINE 78 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qng" c'gsl_integration_qng
  :: Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CSize -> IO CInt
foreign import ccall "&gsl_integration_qng" p'gsl_integration_qng
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CSize -> IO CInt)

{-# LINE 79 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qag" c'gsl_integration_qag
  :: Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CDouble -> CSize -> CInt -> CInt -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_integration_qag" p'gsl_integration_qag
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CDouble -> CSize -> CInt -> CInt -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 80 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qagi" c'gsl_integration_qagi
  :: Ptr C'gsl_function -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_integration_qagi" p'gsl_integration_qagi
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 81 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qagiu" c'gsl_integration_qagiu
  :: Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_integration_qagiu" p'gsl_integration_qagiu
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 82 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qagil" c'gsl_integration_qagil
  :: Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_integration_qagil" p'gsl_integration_qagil
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 83 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qags" c'gsl_integration_qags
  :: Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_integration_qags" p'gsl_integration_qags
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 84 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qagp" c'gsl_integration_qagp
  :: Ptr C'gsl_function -> Ptr CDouble -> CSize -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_integration_qagp" p'gsl_integration_qagp
  :: FunPtr (Ptr C'gsl_function -> Ptr CDouble -> CSize -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 85 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qawc" c'gsl_integration_qawc
  :: Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_integration_qawc" p'gsl_integration_qawc
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 86 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qaws" c'gsl_integration_qaws
  :: Ptr C'gsl_function -> CDouble -> CDouble -> Ptr C'gsl_integration_qaws_table -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_integration_qaws" p'gsl_integration_qaws
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> Ptr C'gsl_integration_qaws_table -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 87 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qawo" c'gsl_integration_qawo
  :: Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr C'gsl_integration_qawo_table -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_integration_qawo" p'gsl_integration_qawo
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr C'gsl_integration_qawo_table -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 88 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}
foreign import ccall "gsl_integration_qawf" c'gsl_integration_qawf
  :: Ptr C'gsl_function -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr C'gsl_integration_workspace -> Ptr C'gsl_integration_qawo_table -> Ptr CDouble -> Ptr CDouble -> IO CInt
foreign import ccall "&gsl_integration_qawf" p'gsl_integration_qawf
  :: FunPtr (Ptr C'gsl_function -> CDouble -> CDouble -> CSize -> Ptr C'gsl_integration_workspace -> Ptr C'gsl_integration_workspace -> Ptr C'gsl_integration_qawo_table -> Ptr CDouble -> Ptr CDouble -> IO CInt)

{-# LINE 89 "src/Bindings/Gsl/NumericalIntegration.hsc" #-}