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

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

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

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

module Bindings.Gsl.VectorsAndMatrices.Vectors 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/VectorsAndMatrices/Vectors.hsc" #-}
import Bindings.Gsl.VectorsAndMatrices.DataTypes
import Bindings.Gsl.ComplexNumbers

foreign import ccall "&gsl_check_range" p'gsl_check_range
  :: Ptr (CInt)

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

foreign import ccall "gsl_vector_add" c'gsl_vector_add
  :: Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_add" p'gsl_vector_add
  :: FunPtr (Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 14 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_add_constant" c'gsl_vector_add_constant
  :: Ptr C'gsl_vector -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_add_constant" p'gsl_vector_add_constant
  :: FunPtr (Ptr C'gsl_vector -> CDouble -> IO CInt)

{-# LINE 15 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_alloc" c'gsl_vector_alloc
  :: CSize -> IO (Ptr C'gsl_vector)
foreign import ccall "&gsl_vector_alloc" p'gsl_vector_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector))

{-# LINE 16 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_alloc_col_from_matrix" c'gsl_vector_alloc_col_from_matrix
  :: Ptr C'gsl_matrix -> CSize -> IO (Ptr C'gsl_vector)
foreign import ccall "&gsl_vector_alloc_col_from_matrix" p'gsl_vector_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix -> CSize -> IO (Ptr C'gsl_vector))

{-# LINE 17 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_alloc_from_block" c'gsl_vector_alloc_from_block
  :: Ptr C'gsl_block -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector)
foreign import ccall "&gsl_vector_alloc_from_block" p'gsl_vector_alloc_from_block
  :: FunPtr (Ptr C'gsl_block -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector))

{-# LINE 18 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_alloc_from_vector" c'gsl_vector_alloc_from_vector
  :: Ptr C'gsl_vector -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector)
foreign import ccall "&gsl_vector_alloc_from_vector" p'gsl_vector_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector))

{-# LINE 19 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_alloc_row_from_matrix" c'gsl_vector_alloc_row_from_matrix
  :: Ptr C'gsl_matrix -> CSize -> IO (Ptr C'gsl_vector)
foreign import ccall "&gsl_vector_alloc_row_from_matrix" p'gsl_vector_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix -> CSize -> IO (Ptr C'gsl_vector))

{-# LINE 20 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_calloc" c'gsl_vector_calloc
  :: CSize -> IO (Ptr C'gsl_vector)
foreign import ccall "&gsl_vector_calloc" p'gsl_vector_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector))

{-# LINE 21 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_add" c'gsl_vector_char_add
  :: Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_add" p'gsl_vector_char_add
  :: FunPtr (Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 22 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_add_constant" c'gsl_vector_char_add_constant
  :: Ptr C'gsl_vector_char -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_char_add_constant" p'gsl_vector_char_add_constant
  :: FunPtr (Ptr C'gsl_vector_char -> CDouble -> IO CInt)

{-# LINE 23 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_alloc" c'gsl_vector_char_alloc
  :: CSize -> IO (Ptr C'gsl_vector_char)
foreign import ccall "&gsl_vector_char_alloc" p'gsl_vector_char_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_char))

{-# LINE 24 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_alloc_col_from_matrix" c'gsl_vector_char_alloc_col_from_matrix
  :: Ptr C'gsl_matrix_char -> CSize -> IO (Ptr C'gsl_vector_char)
foreign import ccall "&gsl_vector_char_alloc_col_from_matrix" p'gsl_vector_char_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_char -> CSize -> IO (Ptr C'gsl_vector_char))

{-# LINE 25 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_alloc_from_block" c'gsl_vector_char_alloc_from_block
  :: Ptr C'gsl_block_char -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_char)
foreign import ccall "&gsl_vector_char_alloc_from_block" p'gsl_vector_char_alloc_from_block
  :: FunPtr (Ptr C'gsl_block_char -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_char))

{-# LINE 26 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_alloc_from_vector" c'gsl_vector_char_alloc_from_vector
  :: Ptr C'gsl_vector_char -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_char)
foreign import ccall "&gsl_vector_char_alloc_from_vector" p'gsl_vector_char_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector_char -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_char))

{-# LINE 27 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_alloc_row_from_matrix" c'gsl_vector_char_alloc_row_from_matrix
  :: Ptr C'gsl_matrix_char -> CSize -> IO (Ptr C'gsl_vector_char)
foreign import ccall "&gsl_vector_char_alloc_row_from_matrix" p'gsl_vector_char_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_char -> CSize -> IO (Ptr C'gsl_vector_char))

{-# LINE 28 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_calloc" c'gsl_vector_char_calloc
  :: CSize -> IO (Ptr C'gsl_vector_char)
foreign import ccall "&gsl_vector_char_calloc" p'gsl_vector_char_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_char))

{-# LINE 29 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_const_ptr" c'gsl_vector_char_const_ptr
  :: Ptr C'gsl_vector_char -> CSize -> IO CString
foreign import ccall "&gsl_vector_char_const_ptr" p'gsl_vector_char_const_ptr
  :: FunPtr (Ptr C'gsl_vector_char -> CSize -> IO CString)

{-# LINE 30 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_char_const_subvector , Ptr <gsl_vector_char> -> CSize -> CSize -> IO <gsl_vector_char_const_view>
-- ccall gsl_vector_char_const_subvector_with_stride , Ptr <gsl_vector_char> -> CSize -> CSize -> CSize -> IO <gsl_vector_char_const_view>
-- ccall gsl_vector_char_const_view_array , CString -> CSize -> IO <gsl_vector_char_const_view>
-- ccall gsl_vector_char_const_view_array_with_stride , CString -> CSize -> CSize -> IO <gsl_vector_char_const_view>
foreign import ccall "gsl_vector_char_div" c'gsl_vector_char_div
  :: Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_div" p'gsl_vector_char_div
  :: FunPtr (Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 35 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_fprintf" c'gsl_vector_char_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector_char -> CString -> IO CInt
foreign import ccall "&gsl_vector_char_fprintf" p'gsl_vector_char_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_char -> CString -> IO CInt)

{-# LINE 36 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_fread" c'gsl_vector_char_fread
  :: Ptr CFile -> Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_fread" p'gsl_vector_char_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 37 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_free" c'gsl_vector_char_free
  :: Ptr C'gsl_vector_char -> IO ()
foreign import ccall "&gsl_vector_char_free" p'gsl_vector_char_free
  :: FunPtr (Ptr C'gsl_vector_char -> IO ())

{-# LINE 38 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_fscanf" c'gsl_vector_char_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_fscanf" p'gsl_vector_char_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 39 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_fwrite" c'gsl_vector_char_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_fwrite" p'gsl_vector_char_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 40 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_get" c'gsl_vector_char_get
  :: Ptr C'gsl_vector_char -> CSize -> IO CChar
foreign import ccall "&gsl_vector_char_get" p'gsl_vector_char_get
  :: FunPtr (Ptr C'gsl_vector_char -> CSize -> IO CChar)

{-# LINE 41 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_isneg" c'gsl_vector_char_isneg
  :: Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_isneg" p'gsl_vector_char_isneg
  :: FunPtr (Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 42 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_isnonneg" c'gsl_vector_char_isnonneg
  :: Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_isnonneg" p'gsl_vector_char_isnonneg
  :: FunPtr (Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 43 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_isnull" c'gsl_vector_char_isnull
  :: Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_isnull" p'gsl_vector_char_isnull
  :: FunPtr (Ptr C'gsl_vector_char -> IO CInt)

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

{-# LINE 45 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_max" c'gsl_vector_char_max
  :: Ptr C'gsl_vector_char -> IO CChar
foreign import ccall "&gsl_vector_char_max" p'gsl_vector_char_max
  :: FunPtr (Ptr C'gsl_vector_char -> IO CChar)

{-# LINE 46 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_max_index" c'gsl_vector_char_max_index
  :: Ptr C'gsl_vector_char -> IO CSize
foreign import ccall "&gsl_vector_char_max_index" p'gsl_vector_char_max_index
  :: FunPtr (Ptr C'gsl_vector_char -> IO CSize)

{-# LINE 47 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_memcpy" c'gsl_vector_char_memcpy
  :: Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_memcpy" p'gsl_vector_char_memcpy
  :: FunPtr (Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 48 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_min" c'gsl_vector_char_min
  :: Ptr C'gsl_vector_char -> IO CChar
foreign import ccall "&gsl_vector_char_min" p'gsl_vector_char_min
  :: FunPtr (Ptr C'gsl_vector_char -> IO CChar)

{-# LINE 49 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_min_index" c'gsl_vector_char_min_index
  :: Ptr C'gsl_vector_char -> IO CSize
foreign import ccall "&gsl_vector_char_min_index" p'gsl_vector_char_min_index
  :: FunPtr (Ptr C'gsl_vector_char -> IO CSize)

{-# LINE 50 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_minmax" c'gsl_vector_char_minmax
  :: Ptr C'gsl_vector_char -> CString -> CString -> IO ()
foreign import ccall "&gsl_vector_char_minmax" p'gsl_vector_char_minmax
  :: FunPtr (Ptr C'gsl_vector_char -> CString -> CString -> IO ())

{-# LINE 51 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_minmax_index" c'gsl_vector_char_minmax_index
  :: Ptr C'gsl_vector_char -> Ptr CSize -> Ptr CSize -> IO ()
foreign import ccall "&gsl_vector_char_minmax_index" p'gsl_vector_char_minmax_index
  :: FunPtr (Ptr C'gsl_vector_char -> Ptr CSize -> Ptr CSize -> IO ())

{-# LINE 52 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_mul" c'gsl_vector_char_mul
  :: Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_mul" p'gsl_vector_char_mul
  :: FunPtr (Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 53 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_ptr" c'gsl_vector_char_ptr
  :: Ptr C'gsl_vector_char -> CSize -> IO CString
foreign import ccall "&gsl_vector_char_ptr" p'gsl_vector_char_ptr
  :: FunPtr (Ptr C'gsl_vector_char -> CSize -> IO CString)

{-# LINE 54 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_reverse" c'gsl_vector_char_reverse
  :: Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_reverse" p'gsl_vector_char_reverse
  :: FunPtr (Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 55 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_scale" c'gsl_vector_char_scale
  :: Ptr C'gsl_vector_char -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_char_scale" p'gsl_vector_char_scale
  :: FunPtr (Ptr C'gsl_vector_char -> CDouble -> IO CInt)

{-# LINE 56 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_set" c'gsl_vector_char_set
  :: Ptr C'gsl_vector_char -> CSize -> CChar -> IO ()
foreign import ccall "&gsl_vector_char_set" p'gsl_vector_char_set
  :: FunPtr (Ptr C'gsl_vector_char -> CSize -> CChar -> IO ())

{-# LINE 57 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_set_all" c'gsl_vector_char_set_all
  :: Ptr C'gsl_vector_char -> CChar -> IO ()
foreign import ccall "&gsl_vector_char_set_all" p'gsl_vector_char_set_all
  :: FunPtr (Ptr C'gsl_vector_char -> CChar -> IO ())

{-# LINE 58 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_set_basis" c'gsl_vector_char_set_basis
  :: Ptr C'gsl_vector_char -> CSize -> IO CInt
foreign import ccall "&gsl_vector_char_set_basis" p'gsl_vector_char_set_basis
  :: FunPtr (Ptr C'gsl_vector_char -> CSize -> IO CInt)

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

{-# LINE 60 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_sub" c'gsl_vector_char_sub
  :: Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_sub" p'gsl_vector_char_sub
  :: FunPtr (Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 61 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_char_subvector , Ptr <gsl_vector_char> -> CSize -> CSize -> IO <gsl_vector_char_view>
-- ccall gsl_vector_char_subvector_with_stride , Ptr <gsl_vector_char> -> CSize -> CSize -> CSize -> IO <gsl_vector_char_view>
foreign import ccall "gsl_vector_char_swap" c'gsl_vector_char_swap
  :: Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_vector_char_swap" p'gsl_vector_char_swap
  :: FunPtr (Ptr C'gsl_vector_char -> Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 64 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_char_swap_elements" c'gsl_vector_char_swap_elements
  :: Ptr C'gsl_vector_char -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_char_swap_elements" p'gsl_vector_char_swap_elements
  :: FunPtr (Ptr C'gsl_vector_char -> CSize -> CSize -> IO CInt)

{-# LINE 65 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_char_view_array , CString -> CSize -> IO <gsl_vector_char_view>
-- ccall gsl_vector_char_view_array_with_stride , CString -> CSize -> CSize -> IO <gsl_vector_char_view>
foreign import ccall "gsl_vector_complex_add" c'gsl_vector_complex_add
  :: Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_add" p'gsl_vector_complex_add
  :: FunPtr (Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 68 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_add_constant , Ptr <gsl_vector_complex> -> <gsl_complex> -> IO CInt
foreign import ccall "gsl_vector_complex_alloc" c'gsl_vector_complex_alloc
  :: CSize -> IO (Ptr C'gsl_vector_complex)
foreign import ccall "&gsl_vector_complex_alloc" p'gsl_vector_complex_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_complex))

{-# LINE 70 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_alloc_col_from_matrix" c'gsl_vector_complex_alloc_col_from_matrix
  :: Ptr C'gsl_matrix_complex -> CSize -> IO (Ptr C'gsl_vector_complex)
foreign import ccall "&gsl_vector_complex_alloc_col_from_matrix" p'gsl_vector_complex_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_complex -> CSize -> IO (Ptr C'gsl_vector_complex))

{-# LINE 71 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_alloc_from_block" c'gsl_vector_complex_alloc_from_block
  :: Ptr C'gsl_block_complex -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_complex)
foreign import ccall "&gsl_vector_complex_alloc_from_block" p'gsl_vector_complex_alloc_from_block
  :: FunPtr (Ptr C'gsl_block_complex -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_complex))

{-# LINE 72 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_alloc_from_vector" c'gsl_vector_complex_alloc_from_vector
  :: Ptr C'gsl_vector_complex -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_complex)
foreign import ccall "&gsl_vector_complex_alloc_from_vector" p'gsl_vector_complex_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector_complex -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_complex))

{-# LINE 73 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_alloc_row_from_matrix" c'gsl_vector_complex_alloc_row_from_matrix
  :: Ptr C'gsl_matrix_complex -> CSize -> IO (Ptr C'gsl_vector_complex)
foreign import ccall "&gsl_vector_complex_alloc_row_from_matrix" p'gsl_vector_complex_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_complex -> CSize -> IO (Ptr C'gsl_vector_complex))

{-# LINE 74 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_calloc" c'gsl_vector_complex_calloc
  :: CSize -> IO (Ptr C'gsl_vector_complex)
foreign import ccall "&gsl_vector_complex_calloc" p'gsl_vector_complex_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_complex))

{-# LINE 75 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_const_imag , Ptr <gsl_vector_complex> -> IO <gsl_vector_const_view>
foreign import ccall "gsl_vector_complex_const_ptr" c'gsl_vector_complex_const_ptr
  :: Ptr C'gsl_vector_complex -> CSize -> IO (Ptr C'gsl_complex)
foreign import ccall "&gsl_vector_complex_const_ptr" p'gsl_vector_complex_const_ptr
  :: FunPtr (Ptr C'gsl_vector_complex -> CSize -> IO (Ptr C'gsl_complex))

{-# LINE 77 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_const_real , Ptr <gsl_vector_complex> -> IO <gsl_vector_const_view>
-- ccall gsl_vector_complex_const_subvector , Ptr <gsl_vector_complex> -> CSize -> CSize -> IO <gsl_vector_complex_const_view>
-- ccall gsl_vector_complex_const_subvector_with_stride , Ptr <gsl_vector_complex> -> CSize -> CSize -> CSize -> IO <gsl_vector_complex_const_view>
-- ccall gsl_vector_complex_const_view_array , Ptr CDouble -> CSize -> IO <gsl_vector_complex_const_view>
-- ccall gsl_vector_complex_const_view_array_with_stride , Ptr CDouble -> CSize -> CSize -> IO <gsl_vector_complex_const_view>
foreign import ccall "gsl_vector_complex_div" c'gsl_vector_complex_div
  :: Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_div" p'gsl_vector_complex_div
  :: FunPtr (Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 83 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_add" c'gsl_vector_complex_float_add
  :: Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_add" p'gsl_vector_complex_float_add
  :: FunPtr (Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 84 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_float_add_constant , Ptr <gsl_vector_complex_float> -> <gsl_complex_float> -> IO CInt
foreign import ccall "gsl_vector_complex_float_alloc" c'gsl_vector_complex_float_alloc
  :: CSize -> IO (Ptr C'gsl_vector_complex_float)
foreign import ccall "&gsl_vector_complex_float_alloc" p'gsl_vector_complex_float_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_complex_float))

{-# LINE 86 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_alloc_col_from_matrix" c'gsl_vector_complex_float_alloc_col_from_matrix
  :: Ptr C'gsl_matrix_complex_float -> CSize -> IO (Ptr C'gsl_vector_complex_float)
foreign import ccall "&gsl_vector_complex_float_alloc_col_from_matrix" p'gsl_vector_complex_float_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_complex_float -> CSize -> IO (Ptr C'gsl_vector_complex_float))

{-# LINE 87 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_alloc_from_block" c'gsl_vector_complex_float_alloc_from_block
  :: Ptr C'gsl_block_complex_float -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_complex_float)
foreign import ccall "&gsl_vector_complex_float_alloc_from_block" p'gsl_vector_complex_float_alloc_from_block
  :: FunPtr (Ptr C'gsl_block_complex_float -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_complex_float))

{-# LINE 88 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_alloc_from_vector" c'gsl_vector_complex_float_alloc_from_vector
  :: Ptr C'gsl_vector_complex_float -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_complex_float)
foreign import ccall "&gsl_vector_complex_float_alloc_from_vector" p'gsl_vector_complex_float_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector_complex_float -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_complex_float))

{-# LINE 89 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_alloc_row_from_matrix" c'gsl_vector_complex_float_alloc_row_from_matrix
  :: Ptr C'gsl_matrix_complex_float -> CSize -> IO (Ptr C'gsl_vector_complex_float)
foreign import ccall "&gsl_vector_complex_float_alloc_row_from_matrix" p'gsl_vector_complex_float_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_complex_float -> CSize -> IO (Ptr C'gsl_vector_complex_float))

{-# LINE 90 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_calloc" c'gsl_vector_complex_float_calloc
  :: CSize -> IO (Ptr C'gsl_vector_complex_float)
foreign import ccall "&gsl_vector_complex_float_calloc" p'gsl_vector_complex_float_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_complex_float))

{-# LINE 91 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_float_const_imag , Ptr <gsl_vector_complex_float> -> IO <gsl_vector_float_const_view>
foreign import ccall "gsl_vector_complex_float_const_ptr" c'gsl_vector_complex_float_const_ptr
  :: Ptr C'gsl_vector_complex_float -> CSize -> IO (Ptr C'gsl_complex_float)
foreign import ccall "&gsl_vector_complex_float_const_ptr" p'gsl_vector_complex_float_const_ptr
  :: FunPtr (Ptr C'gsl_vector_complex_float -> CSize -> IO (Ptr C'gsl_complex_float))

{-# LINE 93 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_float_const_real , Ptr <gsl_vector_complex_float> -> IO <gsl_vector_float_const_view>
-- ccall gsl_vector_complex_float_const_subvector , Ptr <gsl_vector_complex_float> -> CSize -> CSize -> IO <gsl_vector_complex_float_const_view>
-- ccall gsl_vector_complex_float_const_subvector_with_stride , Ptr <gsl_vector_complex_float> -> CSize -> CSize -> CSize -> IO <gsl_vector_complex_float_const_view>
-- ccall gsl_vector_complex_float_const_view_array , Ptr CFloat -> CSize -> IO <gsl_vector_complex_float_const_view>
-- ccall gsl_vector_complex_float_const_view_array_with_stride , Ptr CFloat -> CSize -> CSize -> IO <gsl_vector_complex_float_const_view>
foreign import ccall "gsl_vector_complex_float_div" c'gsl_vector_complex_float_div
  :: Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_div" p'gsl_vector_complex_float_div
  :: FunPtr (Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 99 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_fprintf" c'gsl_vector_complex_float_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector_complex_float -> CString -> IO CInt
foreign import ccall "&gsl_vector_complex_float_fprintf" p'gsl_vector_complex_float_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_complex_float -> CString -> IO CInt)

{-# LINE 100 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_fread" c'gsl_vector_complex_float_fread
  :: Ptr CFile -> Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_fread" p'gsl_vector_complex_float_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 101 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_free" c'gsl_vector_complex_float_free
  :: Ptr C'gsl_vector_complex_float -> IO ()
foreign import ccall "&gsl_vector_complex_float_free" p'gsl_vector_complex_float_free
  :: FunPtr (Ptr C'gsl_vector_complex_float -> IO ())

{-# LINE 102 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_fscanf" c'gsl_vector_complex_float_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_fscanf" p'gsl_vector_complex_float_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 103 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_fwrite" c'gsl_vector_complex_float_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_fwrite" p'gsl_vector_complex_float_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 104 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_float_get , Ptr <gsl_vector_complex_float> -> CSize -> IO <gsl_complex_float>
-- ccall gsl_vector_complex_float_imag , Ptr <gsl_vector_complex_float> -> IO <gsl_vector_float_view>
foreign import ccall "gsl_vector_complex_float_isneg" c'gsl_vector_complex_float_isneg
  :: Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_isneg" p'gsl_vector_complex_float_isneg
  :: FunPtr (Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 107 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_isnonneg" c'gsl_vector_complex_float_isnonneg
  :: Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_isnonneg" p'gsl_vector_complex_float_isnonneg
  :: FunPtr (Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 108 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_isnull" c'gsl_vector_complex_float_isnull
  :: Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_isnull" p'gsl_vector_complex_float_isnull
  :: FunPtr (Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 109 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_ispos" c'gsl_vector_complex_float_ispos
  :: Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_ispos" p'gsl_vector_complex_float_ispos
  :: FunPtr (Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 110 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_memcpy" c'gsl_vector_complex_float_memcpy
  :: Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_memcpy" p'gsl_vector_complex_float_memcpy
  :: FunPtr (Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 111 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_mul" c'gsl_vector_complex_float_mul
  :: Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_mul" p'gsl_vector_complex_float_mul
  :: FunPtr (Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 112 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_ptr" c'gsl_vector_complex_float_ptr
  :: Ptr C'gsl_vector_complex_float -> CSize -> IO (Ptr C'gsl_complex_float)
foreign import ccall "&gsl_vector_complex_float_ptr" p'gsl_vector_complex_float_ptr
  :: FunPtr (Ptr C'gsl_vector_complex_float -> CSize -> IO (Ptr C'gsl_complex_float))

{-# LINE 113 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_float_real , Ptr <gsl_vector_complex_float> -> IO <gsl_vector_float_view>
foreign import ccall "gsl_vector_complex_float_reverse" c'gsl_vector_complex_float_reverse
  :: Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_reverse" p'gsl_vector_complex_float_reverse
  :: FunPtr (Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 115 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_float_scale , Ptr <gsl_vector_complex_float> -> <gsl_complex_float> -> IO CInt
-- ccall gsl_vector_complex_float_set , Ptr <gsl_vector_complex_float> -> CSize -> <gsl_complex_float> -> IO ()
-- ccall gsl_vector_complex_float_set_all , Ptr <gsl_vector_complex_float> -> <gsl_complex_float> -> IO ()
foreign import ccall "gsl_vector_complex_float_set_basis" c'gsl_vector_complex_float_set_basis
  :: Ptr C'gsl_vector_complex_float -> CSize -> IO CInt
foreign import ccall "&gsl_vector_complex_float_set_basis" p'gsl_vector_complex_float_set_basis
  :: FunPtr (Ptr C'gsl_vector_complex_float -> CSize -> IO CInt)

{-# LINE 119 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_set_zero" c'gsl_vector_complex_float_set_zero
  :: Ptr C'gsl_vector_complex_float -> IO ()
foreign import ccall "&gsl_vector_complex_float_set_zero" p'gsl_vector_complex_float_set_zero
  :: FunPtr (Ptr C'gsl_vector_complex_float -> IO ())

{-# LINE 120 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_sub" c'gsl_vector_complex_float_sub
  :: Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_sub" p'gsl_vector_complex_float_sub
  :: FunPtr (Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 121 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_float_subvector , Ptr <gsl_vector_complex_float> -> CSize -> CSize -> IO <gsl_vector_complex_float_view>
-- ccall gsl_vector_complex_float_subvector_with_stride , Ptr <gsl_vector_complex_float> -> CSize -> CSize -> CSize -> IO <gsl_vector_complex_float_view>
foreign import ccall "gsl_vector_complex_float_swap" c'gsl_vector_complex_float_swap
  :: Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_vector_complex_float_swap" p'gsl_vector_complex_float_swap
  :: FunPtr (Ptr C'gsl_vector_complex_float -> Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 124 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_float_swap_elements" c'gsl_vector_complex_float_swap_elements
  :: Ptr C'gsl_vector_complex_float -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_complex_float_swap_elements" p'gsl_vector_complex_float_swap_elements
  :: FunPtr (Ptr C'gsl_vector_complex_float -> CSize -> CSize -> IO CInt)

{-# LINE 125 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_float_view_array , Ptr CFloat -> CSize -> IO <gsl_vector_complex_float_view>
-- ccall gsl_vector_complex_float_view_array_with_stride , Ptr CFloat -> CSize -> CSize -> IO <gsl_vector_complex_float_view>
foreign import ccall "gsl_vector_complex_fprintf" c'gsl_vector_complex_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector_complex -> CString -> IO CInt
foreign import ccall "&gsl_vector_complex_fprintf" p'gsl_vector_complex_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_complex -> CString -> IO CInt)

{-# LINE 128 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_fread" c'gsl_vector_complex_fread
  :: Ptr CFile -> Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_fread" p'gsl_vector_complex_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 129 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_free" c'gsl_vector_complex_free
  :: Ptr C'gsl_vector_complex -> IO ()
foreign import ccall "&gsl_vector_complex_free" p'gsl_vector_complex_free
  :: FunPtr (Ptr C'gsl_vector_complex -> IO ())

{-# LINE 130 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_fscanf" c'gsl_vector_complex_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_fscanf" p'gsl_vector_complex_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 131 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_fwrite" c'gsl_vector_complex_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_fwrite" p'gsl_vector_complex_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 132 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_get , Ptr <gsl_vector_complex> -> CSize -> IO <gsl_complex>
-- ccall gsl_vector_complex_imag , Ptr <gsl_vector_complex> -> IO <gsl_vector_view>
foreign import ccall "gsl_vector_complex_isneg" c'gsl_vector_complex_isneg
  :: Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_isneg" p'gsl_vector_complex_isneg
  :: FunPtr (Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 135 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_isnonneg" c'gsl_vector_complex_isnonneg
  :: Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_isnonneg" p'gsl_vector_complex_isnonneg
  :: FunPtr (Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 136 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_isnull" c'gsl_vector_complex_isnull
  :: Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_isnull" p'gsl_vector_complex_isnull
  :: FunPtr (Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 137 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_ispos" c'gsl_vector_complex_ispos
  :: Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_ispos" p'gsl_vector_complex_ispos
  :: FunPtr (Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 138 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- #ccall gsl_vector_complex_long_double_add , Ptr <gsl_vector_complex_long_double> -> Ptr <gsl_vector_complex_long_double> -> IO CInt
-- ccall gsl_vector_complex_long_double_add_constant , Ptr <gsl_vector_complex_long_double> -> <gsl_complex_long_double> -> IO CInt
-- #ccall gsl_vector_complex_long_double_alloc , CSize -> IO (Ptr <gsl_vector_complex_long_double>)

foreign import ccall "inline_GSL_COMPLEX_AT" c'GSL_COMPLEX_AT
  :: Ptr C'gsl_vector_complex -> CSize -> IO (Ptr C'gsl_complex)

{-# LINE 143 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "inline_GSL_COMPLEX_FLOAT_AT" c'GSL_COMPLEX_FLOAT_AT
  :: Ptr C'gsl_vector_complex_float -> CSize -> IO (Ptr C'gsl_complex_float)

{-# LINE 144 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- #cinline GSL_COMPLEX_LONG_DOUBLE_AT , Ptr <gsl_vector_complex_long_double> -> CSize -> IO (Ptr <gsl_complex_long_double>)

-- #ccall gsl_vector_complex_long_double_alloc_col_from_matrix , Ptr <gsl_matrix_complex_long_double> -> CSize -> IO (Ptr <gsl_vector_complex_long_double>)
-- #ccall gsl_vector_complex_long_double_alloc_from_block , Ptr <gsl_block_complex_long_double> -> CSize -> CSize -> CSize -> IO (Ptr <gsl_vector_complex_long_double>)
-- #ccall gsl_vector_complex_long_double_alloc_from_vector , Ptr <gsl_vector_complex_long_double> -> CSize -> CSize -> CSize -> IO (Ptr <gsl_vector_complex_long_double>)
-- #ccall gsl_vector_complex_long_double_alloc_row_from_matrix , Ptr <gsl_matrix_complex_long_double> -> CSize -> IO (Ptr <gsl_vector_complex_long_double>)
-- #ccall gsl_vector_complex_long_double_calloc , CSize -> IO (Ptr <gsl_vector_complex_long_double>)
-- ccall gsl_vector_complex_long_double_const_imag , Ptr <gsl_vector_complex_long_double> -> IO <gsl_vector_long_double_const_view>
-- #ccall gsl_vector_complex_long_double_const_ptr , Ptr <gsl_vector_complex_long_double> -> CSize -> IO (Ptr <gsl_complex_long_double>)
-- ccall gsl_vector_complex_long_double_const_real , Ptr <gsl_vector_complex_long_double> -> IO <gsl_vector_long_double_const_view>
-- ccall gsl_vector_complex_long_double_const_subvector , Ptr <gsl_vector_complex_long_double> -> CSize -> CSize -> IO <gsl_vector_complex_long_double_const_view>
-- ccall gsl_vector_complex_long_double_const_subvector_with_stride , Ptr <gsl_vector_complex_long_double> -> CSize -> CSize -> CSize -> IO <gsl_vector_complex_long_double_const_view>
-- ccall gsl_vector_complex_long_double_const_view_array , Ptr CLDouble -> CSize -> IO <gsl_vector_complex_long_double_const_view>
-- ccall gsl_vector_complex_long_double_const_view_array_with_stride , Ptr CLDouble -> CSize -> CSize -> IO <gsl_vector_complex_long_double_const_view>
-- #ccall gsl_vector_complex_long_double_div , Ptr <gsl_vector_complex_long_double> -> Ptr <gsl_vector_complex_long_double> -> IO CInt
-- #ccall gsl_vector_complex_long_double_fprintf , Ptr CFile -> Ptr <gsl_vector_complex_long_double> -> CString -> IO CInt
-- #ccall gsl_vector_complex_long_double_fread , Ptr CFile -> Ptr <gsl_vector_complex_long_double> -> IO CInt
-- #ccall gsl_vector_complex_long_double_free , Ptr <gsl_vector_complex_long_double> -> IO ()
-- #ccall gsl_vector_complex_long_double_fscanf , Ptr CFile -> Ptr <gsl_vector_complex_long_double> -> IO CInt
-- #ccall gsl_vector_complex_long_double_fwrite , Ptr CFile -> Ptr <gsl_vector_complex_long_double> -> IO CInt
-- ccall gsl_vector_complex_long_double_get , Ptr <gsl_vector_complex_long_double> -> CSize -> IO <gsl_complex_long_double>
-- ccall gsl_vector_complex_long_double_imag , Ptr <gsl_vector_complex_long_double> -> IO <gsl_vector_long_double_view>
-- #ccall gsl_vector_complex_long_double_isneg , Ptr <gsl_vector_complex_long_double> -> IO CInt
-- #ccall gsl_vector_complex_long_double_isnonneg , Ptr <gsl_vector_complex_long_double> -> IO CInt
-- #ccall gsl_vector_complex_long_double_isnull , Ptr <gsl_vector_complex_long_double> -> IO CInt
-- #ccall gsl_vector_complex_long_double_ispos , Ptr <gsl_vector_complex_long_double> -> IO CInt
-- #ccall gsl_vector_complex_long_double_memcpy , Ptr <gsl_vector_complex_long_double> -> Ptr <gsl_vector_complex_long_double> -> IO CInt
-- #ccall gsl_vector_complex_long_double_mul , Ptr <gsl_vector_complex_long_double> -> Ptr <gsl_vector_complex_long_double> -> IO CInt
-- #ccall gsl_vector_complex_long_double_ptr , Ptr <gsl_vector_complex_long_double> -> CSize -> IO (Ptr <gsl_complex_long_double>)
-- ccall gsl_vector_complex_long_double_real , Ptr <gsl_vector_complex_long_double> -> IO <gsl_vector_long_double_view>
-- #ccall gsl_vector_complex_long_double_reverse , Ptr <gsl_vector_complex_long_double> -> IO CInt
-- ccall gsl_vector_complex_long_double_scale , Ptr <gsl_vector_complex_long_double> -> <gsl_complex_long_double> -> IO CInt
-- ccall gsl_vector_complex_long_double_set , Ptr <gsl_vector_complex_long_double> -> CSize -> <gsl_complex_long_double> -> IO ()
-- ccall gsl_vector_complex_long_double_set_all , Ptr <gsl_vector_complex_long_double> -> <gsl_complex_long_double> -> IO ()
-- #ccall gsl_vector_complex_long_double_set_basis , Ptr <gsl_vector_complex_long_double> -> CSize -> IO CInt
-- #ccall gsl_vector_complex_long_double_set_zero , Ptr <gsl_vector_complex_long_double> -> IO ()
-- #ccall gsl_vector_complex_long_double_sub , Ptr <gsl_vector_complex_long_double> -> Ptr <gsl_vector_complex_long_double> -> IO CInt
-- ccall gsl_vector_complex_long_double_subvector , Ptr <gsl_vector_complex_long_double> -> CSize -> CSize -> IO <gsl_vector_complex_long_double_view>
-- ccall gsl_vector_complex_long_double_subvector_with_stride , Ptr <gsl_vector_complex_long_double> -> CSize -> CSize -> CSize -> IO <gsl_vector_complex_long_double_view>
-- #ccall gsl_vector_complex_long_double_swap , Ptr <gsl_vector_complex_long_double> -> Ptr <gsl_vector_complex_long_double> -> IO CInt
-- #ccall gsl_vector_complex_long_double_swap_elements , Ptr <gsl_vector_complex_long_double> -> CSize -> CSize -> IO CInt
-- ccall gsl_vector_complex_long_double_view_array , Ptr CLDouble -> CSize -> IO <gsl_vector_complex_long_double_view>
-- ccall gsl_vector_complex_long_double_view_array_with_stride , Ptr CLDouble -> CSize -> CSize -> IO <gsl_vector_complex_long_double_view>
foreign import ccall "gsl_vector_complex_memcpy" c'gsl_vector_complex_memcpy
  :: Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_memcpy" p'gsl_vector_complex_memcpy
  :: FunPtr (Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 188 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_mul" c'gsl_vector_complex_mul
  :: Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_mul" p'gsl_vector_complex_mul
  :: FunPtr (Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 189 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_ptr" c'gsl_vector_complex_ptr
  :: Ptr C'gsl_vector_complex -> CSize -> IO (Ptr C'gsl_complex)
foreign import ccall "&gsl_vector_complex_ptr" p'gsl_vector_complex_ptr
  :: FunPtr (Ptr C'gsl_vector_complex -> CSize -> IO (Ptr C'gsl_complex))

{-# LINE 190 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_real , Ptr <gsl_vector_complex> -> IO <gsl_vector_view>
foreign import ccall "gsl_vector_complex_reverse" c'gsl_vector_complex_reverse
  :: Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_reverse" p'gsl_vector_complex_reverse
  :: FunPtr (Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 192 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_scale , Ptr <gsl_vector_complex> -> <gsl_complex> -> IO CInt
-- ccall gsl_vector_complex_set , Ptr <gsl_vector_complex> -> CSize -> <gsl_complex> -> IO ()
-- ccall gsl_vector_complex_set_all , Ptr <gsl_vector_complex> -> <gsl_complex> -> IO ()
foreign import ccall "gsl_vector_complex_set_basis" c'gsl_vector_complex_set_basis
  :: Ptr C'gsl_vector_complex -> CSize -> IO CInt
foreign import ccall "&gsl_vector_complex_set_basis" p'gsl_vector_complex_set_basis
  :: FunPtr (Ptr C'gsl_vector_complex -> CSize -> IO CInt)

{-# LINE 196 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_set_zero" c'gsl_vector_complex_set_zero
  :: Ptr C'gsl_vector_complex -> IO ()
foreign import ccall "&gsl_vector_complex_set_zero" p'gsl_vector_complex_set_zero
  :: FunPtr (Ptr C'gsl_vector_complex -> IO ())

{-# LINE 197 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_sub" c'gsl_vector_complex_sub
  :: Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_sub" p'gsl_vector_complex_sub
  :: FunPtr (Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 198 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_subvector , Ptr <gsl_vector_complex> -> CSize -> CSize -> IO <gsl_vector_complex_view>
-- ccall gsl_vector_complex_subvector_with_stride , Ptr <gsl_vector_complex> -> CSize -> CSize -> CSize -> IO <gsl_vector_complex_view>
foreign import ccall "gsl_vector_complex_swap" c'gsl_vector_complex_swap
  :: Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_vector_complex_swap" p'gsl_vector_complex_swap
  :: FunPtr (Ptr C'gsl_vector_complex -> Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 201 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_complex_swap_elements" c'gsl_vector_complex_swap_elements
  :: Ptr C'gsl_vector_complex -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_complex_swap_elements" p'gsl_vector_complex_swap_elements
  :: FunPtr (Ptr C'gsl_vector_complex -> CSize -> CSize -> IO CInt)

{-# LINE 202 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_complex_view_array , Ptr CDouble -> CSize -> IO <gsl_vector_complex_view>
-- ccall gsl_vector_complex_view_array_with_stride , Ptr CDouble -> CSize -> CSize -> IO <gsl_vector_complex_view>
foreign import ccall "gsl_vector_const_ptr" c'gsl_vector_const_ptr
  :: Ptr C'gsl_vector -> CSize -> IO (Ptr CDouble)
foreign import ccall "&gsl_vector_const_ptr" p'gsl_vector_const_ptr
  :: FunPtr (Ptr C'gsl_vector -> CSize -> IO (Ptr CDouble))

{-# LINE 205 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_const_subvector , Ptr <gsl_vector> -> CSize -> CSize -> IO <gsl_vector_const_view>
-- ccall gsl_vector_const_subvector_with_stride , Ptr <gsl_vector> -> CSize -> CSize -> CSize -> IO <gsl_vector_const_view>
-- ccall gsl_vector_const_view_array , Ptr CDouble -> CSize -> IO <gsl_vector_const_view>
-- ccall gsl_vector_const_view_array_with_stride , Ptr CDouble -> CSize -> CSize -> IO <gsl_vector_const_view>
foreign import ccall "gsl_vector_div" c'gsl_vector_div
  :: Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_div" p'gsl_vector_div
  :: FunPtr (Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 210 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_add" c'gsl_vector_float_add
  :: Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_add" p'gsl_vector_float_add
  :: FunPtr (Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 211 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_add_constant" c'gsl_vector_float_add_constant
  :: Ptr C'gsl_vector_float -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_float_add_constant" p'gsl_vector_float_add_constant
  :: FunPtr (Ptr C'gsl_vector_float -> CDouble -> IO CInt)

{-# LINE 212 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_alloc" c'gsl_vector_float_alloc
  :: CSize -> IO (Ptr C'gsl_vector_float)
foreign import ccall "&gsl_vector_float_alloc" p'gsl_vector_float_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_float))

{-# LINE 213 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_alloc_col_from_matrix" c'gsl_vector_float_alloc_col_from_matrix
  :: Ptr C'gsl_matrix_float -> CSize -> IO (Ptr C'gsl_vector_float)
foreign import ccall "&gsl_vector_float_alloc_col_from_matrix" p'gsl_vector_float_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_float -> CSize -> IO (Ptr C'gsl_vector_float))

{-# LINE 214 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_alloc_from_block" c'gsl_vector_float_alloc_from_block
  :: Ptr C'gsl_block_float -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_float)
foreign import ccall "&gsl_vector_float_alloc_from_block" p'gsl_vector_float_alloc_from_block
  :: FunPtr (Ptr C'gsl_block_float -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_float))

{-# LINE 215 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_alloc_from_vector" c'gsl_vector_float_alloc_from_vector
  :: Ptr C'gsl_vector_float -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_float)
foreign import ccall "&gsl_vector_float_alloc_from_vector" p'gsl_vector_float_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector_float -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_float))

{-# LINE 216 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_alloc_row_from_matrix" c'gsl_vector_float_alloc_row_from_matrix
  :: Ptr C'gsl_matrix_float -> CSize -> IO (Ptr C'gsl_vector_float)
foreign import ccall "&gsl_vector_float_alloc_row_from_matrix" p'gsl_vector_float_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_float -> CSize -> IO (Ptr C'gsl_vector_float))

{-# LINE 217 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_calloc" c'gsl_vector_float_calloc
  :: CSize -> IO (Ptr C'gsl_vector_float)
foreign import ccall "&gsl_vector_float_calloc" p'gsl_vector_float_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_float))

{-# LINE 218 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_const_ptr" c'gsl_vector_float_const_ptr
  :: Ptr C'gsl_vector_float -> CSize -> IO (Ptr CFloat)
foreign import ccall "&gsl_vector_float_const_ptr" p'gsl_vector_float_const_ptr
  :: FunPtr (Ptr C'gsl_vector_float -> CSize -> IO (Ptr CFloat))

{-# LINE 219 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_float_const_subvector , Ptr <gsl_vector_float> -> CSize -> CSize -> IO <gsl_vector_float_const_view>
-- ccall gsl_vector_float_const_subvector_with_stride , Ptr <gsl_vector_float> -> CSize -> CSize -> CSize -> IO <gsl_vector_float_const_view>
-- ccall gsl_vector_float_const_view_array , Ptr CFloat -> CSize -> IO <gsl_vector_float_const_view>
-- ccall gsl_vector_float_const_view_array_with_stride , Ptr CFloat -> CSize -> CSize -> IO <gsl_vector_float_const_view>
foreign import ccall "gsl_vector_float_div" c'gsl_vector_float_div
  :: Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_div" p'gsl_vector_float_div
  :: FunPtr (Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 224 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_fprintf" c'gsl_vector_float_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector_float -> CString -> IO CInt
foreign import ccall "&gsl_vector_float_fprintf" p'gsl_vector_float_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_float -> CString -> IO CInt)

{-# LINE 225 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_fread" c'gsl_vector_float_fread
  :: Ptr CFile -> Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_fread" p'gsl_vector_float_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 226 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_free" c'gsl_vector_float_free
  :: Ptr C'gsl_vector_float -> IO ()
foreign import ccall "&gsl_vector_float_free" p'gsl_vector_float_free
  :: FunPtr (Ptr C'gsl_vector_float -> IO ())

{-# LINE 227 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_fscanf" c'gsl_vector_float_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_fscanf" p'gsl_vector_float_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 228 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_fwrite" c'gsl_vector_float_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_fwrite" p'gsl_vector_float_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 229 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_get" c'gsl_vector_float_get
  :: Ptr C'gsl_vector_float -> CSize -> IO CFloat
foreign import ccall "&gsl_vector_float_get" p'gsl_vector_float_get
  :: FunPtr (Ptr C'gsl_vector_float -> CSize -> IO CFloat)

{-# LINE 230 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_isneg" c'gsl_vector_float_isneg
  :: Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_isneg" p'gsl_vector_float_isneg
  :: FunPtr (Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 231 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_isnonneg" c'gsl_vector_float_isnonneg
  :: Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_isnonneg" p'gsl_vector_float_isnonneg
  :: FunPtr (Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 232 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_isnull" c'gsl_vector_float_isnull
  :: Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_isnull" p'gsl_vector_float_isnull
  :: FunPtr (Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 233 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_ispos" c'gsl_vector_float_ispos
  :: Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_ispos" p'gsl_vector_float_ispos
  :: FunPtr (Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 234 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_max" c'gsl_vector_float_max
  :: Ptr C'gsl_vector_float -> IO CFloat
foreign import ccall "&gsl_vector_float_max" p'gsl_vector_float_max
  :: FunPtr (Ptr C'gsl_vector_float -> IO CFloat)

{-# LINE 235 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_max_index" c'gsl_vector_float_max_index
  :: Ptr C'gsl_vector_float -> IO CSize
foreign import ccall "&gsl_vector_float_max_index" p'gsl_vector_float_max_index
  :: FunPtr (Ptr C'gsl_vector_float -> IO CSize)

{-# LINE 236 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_memcpy" c'gsl_vector_float_memcpy
  :: Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_memcpy" p'gsl_vector_float_memcpy
  :: FunPtr (Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 237 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_min" c'gsl_vector_float_min
  :: Ptr C'gsl_vector_float -> IO CFloat
foreign import ccall "&gsl_vector_float_min" p'gsl_vector_float_min
  :: FunPtr (Ptr C'gsl_vector_float -> IO CFloat)

{-# LINE 238 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_min_index" c'gsl_vector_float_min_index
  :: Ptr C'gsl_vector_float -> IO CSize
foreign import ccall "&gsl_vector_float_min_index" p'gsl_vector_float_min_index
  :: FunPtr (Ptr C'gsl_vector_float -> IO CSize)

{-# LINE 239 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_minmax" c'gsl_vector_float_minmax
  :: Ptr C'gsl_vector_float -> Ptr CFloat -> Ptr CFloat -> IO ()
foreign import ccall "&gsl_vector_float_minmax" p'gsl_vector_float_minmax
  :: FunPtr (Ptr C'gsl_vector_float -> Ptr CFloat -> Ptr CFloat -> IO ())

{-# LINE 240 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_minmax_index" c'gsl_vector_float_minmax_index
  :: Ptr C'gsl_vector_float -> Ptr CSize -> Ptr CSize -> IO ()
foreign import ccall "&gsl_vector_float_minmax_index" p'gsl_vector_float_minmax_index
  :: FunPtr (Ptr C'gsl_vector_float -> Ptr CSize -> Ptr CSize -> IO ())

{-# LINE 241 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_mul" c'gsl_vector_float_mul
  :: Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_mul" p'gsl_vector_float_mul
  :: FunPtr (Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 242 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_ptr" c'gsl_vector_float_ptr
  :: Ptr C'gsl_vector_float -> CSize -> IO (Ptr CFloat)
foreign import ccall "&gsl_vector_float_ptr" p'gsl_vector_float_ptr
  :: FunPtr (Ptr C'gsl_vector_float -> CSize -> IO (Ptr CFloat))

{-# LINE 243 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_reverse" c'gsl_vector_float_reverse
  :: Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_reverse" p'gsl_vector_float_reverse
  :: FunPtr (Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 244 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_scale" c'gsl_vector_float_scale
  :: Ptr C'gsl_vector_float -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_float_scale" p'gsl_vector_float_scale
  :: FunPtr (Ptr C'gsl_vector_float -> CDouble -> IO CInt)

{-# LINE 245 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_set" c'gsl_vector_float_set
  :: Ptr C'gsl_vector_float -> CSize -> CFloat -> IO ()
foreign import ccall "&gsl_vector_float_set" p'gsl_vector_float_set
  :: FunPtr (Ptr C'gsl_vector_float -> CSize -> CFloat -> IO ())

{-# LINE 246 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_set_all" c'gsl_vector_float_set_all
  :: Ptr C'gsl_vector_float -> CFloat -> IO ()
foreign import ccall "&gsl_vector_float_set_all" p'gsl_vector_float_set_all
  :: FunPtr (Ptr C'gsl_vector_float -> CFloat -> IO ())

{-# LINE 247 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_set_basis" c'gsl_vector_float_set_basis
  :: Ptr C'gsl_vector_float -> CSize -> IO CInt
foreign import ccall "&gsl_vector_float_set_basis" p'gsl_vector_float_set_basis
  :: FunPtr (Ptr C'gsl_vector_float -> CSize -> IO CInt)

{-# LINE 248 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_set_zero" c'gsl_vector_float_set_zero
  :: Ptr C'gsl_vector_float -> IO ()
foreign import ccall "&gsl_vector_float_set_zero" p'gsl_vector_float_set_zero
  :: FunPtr (Ptr C'gsl_vector_float -> IO ())

{-# LINE 249 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_sub" c'gsl_vector_float_sub
  :: Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_sub" p'gsl_vector_float_sub
  :: FunPtr (Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 250 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_float_subvector , Ptr <gsl_vector_float> -> CSize -> CSize -> IO <gsl_vector_float_view>
-- ccall gsl_vector_float_subvector_with_stride , Ptr <gsl_vector_float> -> CSize -> CSize -> CSize -> IO <gsl_vector_float_view>
foreign import ccall "gsl_vector_float_swap" c'gsl_vector_float_swap
  :: Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_vector_float_swap" p'gsl_vector_float_swap
  :: FunPtr (Ptr C'gsl_vector_float -> Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 253 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_float_swap_elements" c'gsl_vector_float_swap_elements
  :: Ptr C'gsl_vector_float -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_float_swap_elements" p'gsl_vector_float_swap_elements
  :: FunPtr (Ptr C'gsl_vector_float -> CSize -> CSize -> IO CInt)

{-# LINE 254 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_float_view_array , Ptr CFloat -> CSize -> IO <gsl_vector_float_view>
-- ccall gsl_vector_float_view_array_with_stride , Ptr CFloat -> CSize -> CSize -> IO <gsl_vector_float_view>
foreign import ccall "gsl_vector_fprintf" c'gsl_vector_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector -> CString -> IO CInt
foreign import ccall "&gsl_vector_fprintf" p'gsl_vector_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector -> CString -> IO CInt)

{-# LINE 257 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_fread" c'gsl_vector_fread
  :: Ptr CFile -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_fread" p'gsl_vector_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 258 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_free" c'gsl_vector_free
  :: Ptr C'gsl_vector -> IO ()
foreign import ccall "&gsl_vector_free" p'gsl_vector_free
  :: FunPtr (Ptr C'gsl_vector -> IO ())

{-# LINE 259 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_fscanf" c'gsl_vector_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_fscanf" p'gsl_vector_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 260 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_fwrite" c'gsl_vector_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_fwrite" p'gsl_vector_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 261 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_get" c'gsl_vector_get
  :: Ptr C'gsl_vector -> CSize -> IO CDouble
foreign import ccall "&gsl_vector_get" p'gsl_vector_get
  :: FunPtr (Ptr C'gsl_vector -> CSize -> IO CDouble)

{-# LINE 262 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_add" c'gsl_vector_int_add
  :: Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_add" p'gsl_vector_int_add
  :: FunPtr (Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 263 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_add_constant" c'gsl_vector_int_add_constant
  :: Ptr C'gsl_vector_int -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_int_add_constant" p'gsl_vector_int_add_constant
  :: FunPtr (Ptr C'gsl_vector_int -> CDouble -> IO CInt)

{-# LINE 264 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_alloc" c'gsl_vector_int_alloc
  :: CSize -> IO (Ptr C'gsl_vector_int)
foreign import ccall "&gsl_vector_int_alloc" p'gsl_vector_int_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_int))

{-# LINE 265 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_alloc_col_from_matrix" c'gsl_vector_int_alloc_col_from_matrix
  :: Ptr C'gsl_matrix_int -> CSize -> IO (Ptr C'gsl_vector_int)
foreign import ccall "&gsl_vector_int_alloc_col_from_matrix" p'gsl_vector_int_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_int -> CSize -> IO (Ptr C'gsl_vector_int))

{-# LINE 266 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_alloc_from_block" c'gsl_vector_int_alloc_from_block
  :: Ptr C'gsl_block_int -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_int)
foreign import ccall "&gsl_vector_int_alloc_from_block" p'gsl_vector_int_alloc_from_block
  :: FunPtr (Ptr C'gsl_block_int -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_int))

{-# LINE 267 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_alloc_from_vector" c'gsl_vector_int_alloc_from_vector
  :: Ptr C'gsl_vector_int -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_int)
foreign import ccall "&gsl_vector_int_alloc_from_vector" p'gsl_vector_int_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector_int -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_int))

{-# LINE 268 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_alloc_row_from_matrix" c'gsl_vector_int_alloc_row_from_matrix
  :: Ptr C'gsl_matrix_int -> CSize -> IO (Ptr C'gsl_vector_int)
foreign import ccall "&gsl_vector_int_alloc_row_from_matrix" p'gsl_vector_int_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_int -> CSize -> IO (Ptr C'gsl_vector_int))

{-# LINE 269 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_calloc" c'gsl_vector_int_calloc
  :: CSize -> IO (Ptr C'gsl_vector_int)
foreign import ccall "&gsl_vector_int_calloc" p'gsl_vector_int_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_int))

{-# LINE 270 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_const_ptr" c'gsl_vector_int_const_ptr
  :: Ptr C'gsl_vector_int -> CSize -> IO (Ptr CInt)
foreign import ccall "&gsl_vector_int_const_ptr" p'gsl_vector_int_const_ptr
  :: FunPtr (Ptr C'gsl_vector_int -> CSize -> IO (Ptr CInt))

{-# LINE 271 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_int_const_subvector , Ptr <gsl_vector_int> -> CSize -> CSize -> IO <gsl_vector_int_const_view>
-- ccall gsl_vector_int_const_subvector_with_stride , Ptr <gsl_vector_int> -> CSize -> CSize -> CSize -> IO <gsl_vector_int_const_view>
-- ccall gsl_vector_int_const_view_array , Ptr CInt -> CSize -> IO <gsl_vector_int_const_view>
-- ccall gsl_vector_int_const_view_array_with_stride , Ptr CInt -> CSize -> CSize -> IO <gsl_vector_int_const_view>
foreign import ccall "gsl_vector_int_div" c'gsl_vector_int_div
  :: Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_div" p'gsl_vector_int_div
  :: FunPtr (Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 276 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_fprintf" c'gsl_vector_int_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector_int -> CString -> IO CInt
foreign import ccall "&gsl_vector_int_fprintf" p'gsl_vector_int_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_int -> CString -> IO CInt)

{-# LINE 277 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_fread" c'gsl_vector_int_fread
  :: Ptr CFile -> Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_fread" p'gsl_vector_int_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 278 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_free" c'gsl_vector_int_free
  :: Ptr C'gsl_vector_int -> IO ()
foreign import ccall "&gsl_vector_int_free" p'gsl_vector_int_free
  :: FunPtr (Ptr C'gsl_vector_int -> IO ())

{-# LINE 279 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_fscanf" c'gsl_vector_int_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_fscanf" p'gsl_vector_int_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 280 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_fwrite" c'gsl_vector_int_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_fwrite" p'gsl_vector_int_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 281 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_get" c'gsl_vector_int_get
  :: Ptr C'gsl_vector_int -> CSize -> IO CInt
foreign import ccall "&gsl_vector_int_get" p'gsl_vector_int_get
  :: FunPtr (Ptr C'gsl_vector_int -> CSize -> IO CInt)

{-# LINE 282 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_isneg" c'gsl_vector_int_isneg
  :: Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_isneg" p'gsl_vector_int_isneg
  :: FunPtr (Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 283 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_isnonneg" c'gsl_vector_int_isnonneg
  :: Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_isnonneg" p'gsl_vector_int_isnonneg
  :: FunPtr (Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 284 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_isnull" c'gsl_vector_int_isnull
  :: Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_isnull" p'gsl_vector_int_isnull
  :: FunPtr (Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 285 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_ispos" c'gsl_vector_int_ispos
  :: Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_ispos" p'gsl_vector_int_ispos
  :: FunPtr (Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 286 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_max" c'gsl_vector_int_max
  :: Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_max" p'gsl_vector_int_max
  :: FunPtr (Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 287 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_max_index" c'gsl_vector_int_max_index
  :: Ptr C'gsl_vector_int -> IO CSize
foreign import ccall "&gsl_vector_int_max_index" p'gsl_vector_int_max_index
  :: FunPtr (Ptr C'gsl_vector_int -> IO CSize)

{-# LINE 288 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_memcpy" c'gsl_vector_int_memcpy
  :: Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_memcpy" p'gsl_vector_int_memcpy
  :: FunPtr (Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 289 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_min" c'gsl_vector_int_min
  :: Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_min" p'gsl_vector_int_min
  :: FunPtr (Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 290 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_min_index" c'gsl_vector_int_min_index
  :: Ptr C'gsl_vector_int -> IO CSize
foreign import ccall "&gsl_vector_int_min_index" p'gsl_vector_int_min_index
  :: FunPtr (Ptr C'gsl_vector_int -> IO CSize)

{-# LINE 291 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_minmax" c'gsl_vector_int_minmax
  :: Ptr C'gsl_vector_int -> Ptr CInt -> Ptr CInt -> IO ()
foreign import ccall "&gsl_vector_int_minmax" p'gsl_vector_int_minmax
  :: FunPtr (Ptr C'gsl_vector_int -> Ptr CInt -> Ptr CInt -> IO ())

{-# LINE 292 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_minmax_index" c'gsl_vector_int_minmax_index
  :: Ptr C'gsl_vector_int -> Ptr CSize -> Ptr CSize -> IO ()
foreign import ccall "&gsl_vector_int_minmax_index" p'gsl_vector_int_minmax_index
  :: FunPtr (Ptr C'gsl_vector_int -> Ptr CSize -> Ptr CSize -> IO ())

{-# LINE 293 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_mul" c'gsl_vector_int_mul
  :: Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_mul" p'gsl_vector_int_mul
  :: FunPtr (Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 294 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_ptr" c'gsl_vector_int_ptr
  :: Ptr C'gsl_vector_int -> CSize -> IO (Ptr CInt)
foreign import ccall "&gsl_vector_int_ptr" p'gsl_vector_int_ptr
  :: FunPtr (Ptr C'gsl_vector_int -> CSize -> IO (Ptr CInt))

{-# LINE 295 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_reverse" c'gsl_vector_int_reverse
  :: Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_reverse" p'gsl_vector_int_reverse
  :: FunPtr (Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 296 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_scale" c'gsl_vector_int_scale
  :: Ptr C'gsl_vector_int -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_int_scale" p'gsl_vector_int_scale
  :: FunPtr (Ptr C'gsl_vector_int -> CDouble -> IO CInt)

{-# LINE 297 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_set" c'gsl_vector_int_set
  :: Ptr C'gsl_vector_int -> CSize -> CInt -> IO ()
foreign import ccall "&gsl_vector_int_set" p'gsl_vector_int_set
  :: FunPtr (Ptr C'gsl_vector_int -> CSize -> CInt -> IO ())

{-# LINE 298 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_set_all" c'gsl_vector_int_set_all
  :: Ptr C'gsl_vector_int -> CInt -> IO ()
foreign import ccall "&gsl_vector_int_set_all" p'gsl_vector_int_set_all
  :: FunPtr (Ptr C'gsl_vector_int -> CInt -> IO ())

{-# LINE 299 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_set_basis" c'gsl_vector_int_set_basis
  :: Ptr C'gsl_vector_int -> CSize -> IO CInt
foreign import ccall "&gsl_vector_int_set_basis" p'gsl_vector_int_set_basis
  :: FunPtr (Ptr C'gsl_vector_int -> CSize -> IO CInt)

{-# LINE 300 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_set_zero" c'gsl_vector_int_set_zero
  :: Ptr C'gsl_vector_int -> IO ()
foreign import ccall "&gsl_vector_int_set_zero" p'gsl_vector_int_set_zero
  :: FunPtr (Ptr C'gsl_vector_int -> IO ())

{-# LINE 301 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_sub" c'gsl_vector_int_sub
  :: Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_sub" p'gsl_vector_int_sub
  :: FunPtr (Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 302 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_int_subvector , Ptr <gsl_vector_int> -> CSize -> CSize -> IO <gsl_vector_int_view>
-- ccall gsl_vector_int_subvector_with_stride , Ptr <gsl_vector_int> -> CSize -> CSize -> CSize -> IO <gsl_vector_int_view>
foreign import ccall "gsl_vector_int_swap" c'gsl_vector_int_swap
  :: Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_vector_int_swap" p'gsl_vector_int_swap
  :: FunPtr (Ptr C'gsl_vector_int -> Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 305 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_int_swap_elements" c'gsl_vector_int_swap_elements
  :: Ptr C'gsl_vector_int -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_int_swap_elements" p'gsl_vector_int_swap_elements
  :: FunPtr (Ptr C'gsl_vector_int -> CSize -> CSize -> IO CInt)

{-# LINE 306 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_int_view_array , Ptr CInt -> CSize -> IO <gsl_vector_int_view>
-- ccall gsl_vector_int_view_array_with_stride , Ptr CInt -> CSize -> CSize -> IO <gsl_vector_int_view>
foreign import ccall "gsl_vector_isneg" c'gsl_vector_isneg
  :: Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_isneg" p'gsl_vector_isneg
  :: FunPtr (Ptr C'gsl_vector -> IO CInt)

{-# LINE 309 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_isnonneg" c'gsl_vector_isnonneg
  :: Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_isnonneg" p'gsl_vector_isnonneg
  :: FunPtr (Ptr C'gsl_vector -> IO CInt)

{-# LINE 310 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_isnull" c'gsl_vector_isnull
  :: Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_isnull" p'gsl_vector_isnull
  :: FunPtr (Ptr C'gsl_vector -> IO CInt)

{-# LINE 311 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ispos" c'gsl_vector_ispos
  :: Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_ispos" p'gsl_vector_ispos
  :: FunPtr (Ptr C'gsl_vector -> IO CInt)

{-# LINE 312 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_equal" c'gsl_vector_equal
  :: Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_equal" p'gsl_vector_equal
  :: FunPtr (Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 313 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_add" c'gsl_vector_long_add
  :: Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_add" p'gsl_vector_long_add
  :: FunPtr (Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 314 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_add_constant" c'gsl_vector_long_add_constant
  :: Ptr C'gsl_vector_long -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_long_add_constant" p'gsl_vector_long_add_constant
  :: FunPtr (Ptr C'gsl_vector_long -> CDouble -> IO CInt)

{-# LINE 315 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_alloc" c'gsl_vector_long_alloc
  :: CSize -> IO (Ptr C'gsl_vector_long)
foreign import ccall "&gsl_vector_long_alloc" p'gsl_vector_long_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_long))

{-# LINE 316 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_alloc_col_from_matrix" c'gsl_vector_long_alloc_col_from_matrix
  :: Ptr C'gsl_matrix_long -> CSize -> IO (Ptr C'gsl_vector_long)
foreign import ccall "&gsl_vector_long_alloc_col_from_matrix" p'gsl_vector_long_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_long -> CSize -> IO (Ptr C'gsl_vector_long))

{-# LINE 317 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_alloc_from_block" c'gsl_vector_long_alloc_from_block
  :: Ptr C'gsl_block_long -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_long)
foreign import ccall "&gsl_vector_long_alloc_from_block" p'gsl_vector_long_alloc_from_block
  :: FunPtr (Ptr C'gsl_block_long -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_long))

{-# LINE 318 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_alloc_from_vector" c'gsl_vector_long_alloc_from_vector
  :: Ptr C'gsl_vector_long -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_long)
foreign import ccall "&gsl_vector_long_alloc_from_vector" p'gsl_vector_long_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector_long -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_long))

{-# LINE 319 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_alloc_row_from_matrix" c'gsl_vector_long_alloc_row_from_matrix
  :: Ptr C'gsl_matrix_long -> CSize -> IO (Ptr C'gsl_vector_long)
foreign import ccall "&gsl_vector_long_alloc_row_from_matrix" p'gsl_vector_long_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_long -> CSize -> IO (Ptr C'gsl_vector_long))

{-# LINE 320 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_calloc" c'gsl_vector_long_calloc
  :: CSize -> IO (Ptr C'gsl_vector_long)
foreign import ccall "&gsl_vector_long_calloc" p'gsl_vector_long_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_long))

{-# LINE 321 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_const_ptr" c'gsl_vector_long_const_ptr
  :: Ptr C'gsl_vector_long -> CSize -> IO (Ptr CLong)
foreign import ccall "&gsl_vector_long_const_ptr" p'gsl_vector_long_const_ptr
  :: FunPtr (Ptr C'gsl_vector_long -> CSize -> IO (Ptr CLong))

{-# LINE 322 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_long_const_subvector , Ptr <gsl_vector_long> -> CSize -> CSize -> IO <gsl_vector_long_const_view>
-- ccall gsl_vector_long_const_subvector_with_stride , Ptr <gsl_vector_long> -> CSize -> CSize -> CSize -> IO <gsl_vector_long_const_view>
-- ccall gsl_vector_long_const_view_array , Ptr CLong -> CSize -> IO <gsl_vector_long_const_view>
-- ccall gsl_vector_long_const_view_array_with_stride , Ptr CLong -> CSize -> CSize -> IO <gsl_vector_long_const_view>
foreign import ccall "gsl_vector_long_div" c'gsl_vector_long_div
  :: Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_div" p'gsl_vector_long_div
  :: FunPtr (Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 327 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- #ccall gsl_vector_long_double_add , Ptr <gsl_vector_long_double> -> Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_add_constant , Ptr <gsl_vector_long_double> -> CDouble -> IO CInt
-- #ccall gsl_vector_long_double_alloc , CSize -> IO (Ptr <gsl_vector_long_double>)
-- #ccall gsl_vector_long_double_alloc_col_from_matrix , Ptr <gsl_matrix_long_double> -> CSize -> IO (Ptr <gsl_vector_long_double>)
-- #ccall gsl_vector_long_double_alloc_from_block , Ptr <gsl_block_long_double> -> CSize -> CSize -> CSize -> IO (Ptr <gsl_vector_long_double>)
-- #ccall gsl_vector_long_double_alloc_from_vector , Ptr <gsl_vector_long_double> -> CSize -> CSize -> CSize -> IO (Ptr <gsl_vector_long_double>)
-- #ccall gsl_vector_long_double_alloc_row_from_matrix , Ptr <gsl_matrix_long_double> -> CSize -> IO (Ptr <gsl_vector_long_double>)
-- #ccall gsl_vector_long_double_calloc , CSize -> IO (Ptr <gsl_vector_long_double>)
-- #ccall gsl_vector_long_double_const_ptr , Ptr <gsl_vector_long_double> -> CSize -> IO (Ptr CLDouble)
-- ccall gsl_vector_long_double_const_subvector , Ptr <gsl_vector_long_double> -> CSize -> CSize -> IO <gsl_vector_long_double_const_view>
-- ccall gsl_vector_long_double_const_subvector_with_stride , Ptr <gsl_vector_long_double> -> CSize -> CSize -> CSize -> IO <gsl_vector_long_double_const_view>
-- ccall gsl_vector_long_double_const_view_array , Ptr CLDouble -> CSize -> IO <gsl_vector_long_double_const_view>
-- ccall gsl_vector_long_double_const_view_array_with_stride , Ptr CLDouble -> CSize -> CSize -> IO <gsl_vector_long_double_const_view>
-- #ccall gsl_vector_long_double_div , Ptr <gsl_vector_long_double> -> Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_fprintf , Ptr CFile -> Ptr <gsl_vector_long_double> -> CString -> IO CInt
-- #ccall gsl_vector_long_double_fread , Ptr CFile -> Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_free , Ptr <gsl_vector_long_double> -> IO ()
-- #ccall gsl_vector_long_double_fscanf , Ptr CFile -> Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_fwrite , Ptr CFile -> Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_get , Ptr <gsl_vector_long_double> -> CSize -> IO CLDouble
-- #ccall gsl_vector_long_double_isneg , Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_isnonneg , Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_isnull , Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_ispos , Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_max , Ptr <gsl_vector_long_double> -> IO CLDouble
-- #ccall gsl_vector_long_double_max_index , Ptr <gsl_vector_long_double> -> IO CSize
-- #ccall gsl_vector_long_double_memcpy , Ptr <gsl_vector_long_double> -> Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_min , Ptr <gsl_vector_long_double> -> IO CLDouble
-- #ccall gsl_vector_long_double_min_index , Ptr <gsl_vector_long_double> -> IO CSize
-- #ccall gsl_vector_long_double_minmax , Ptr <gsl_vector_long_double> -> Ptr CLDouble -> Ptr CLDouble -> IO ()
-- #ccall gsl_vector_long_double_minmax_index , Ptr <gsl_vector_long_double> -> Ptr CSize -> Ptr CSize -> IO ()
-- #ccall gsl_vector_long_double_mul , Ptr <gsl_vector_long_double> -> Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_ptr , Ptr <gsl_vector_long_double> -> CSize -> IO (Ptr CLDouble)
-- #ccall gsl_vector_long_double_reverse , Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_scale , Ptr <gsl_vector_long_double> -> CDouble -> IO CInt
-- #ccall gsl_vector_long_double_set , Ptr <gsl_vector_long_double> -> CSize -> CLDouble -> IO ()
-- #ccall gsl_vector_long_double_set_all , Ptr <gsl_vector_long_double> -> CLDouble -> IO ()
-- #ccall gsl_vector_long_double_set_basis , Ptr <gsl_vector_long_double> -> CSize -> IO CInt
-- #ccall gsl_vector_long_double_set_zero , Ptr <gsl_vector_long_double> -> IO ()
-- #ccall gsl_vector_long_double_sub , Ptr <gsl_vector_long_double> -> Ptr <gsl_vector_long_double> -> IO CInt
-- ccall gsl_vector_long_double_subvector , Ptr <gsl_vector_long_double> -> CSize -> CSize -> IO <gsl_vector_long_double_view>
-- ccall gsl_vector_long_double_subvector_with_stride , Ptr <gsl_vector_long_double> -> CSize -> CSize -> CSize -> IO <gsl_vector_long_double_view>
-- #ccall gsl_vector_long_double_swap , Ptr <gsl_vector_long_double> -> Ptr <gsl_vector_long_double> -> IO CInt
-- #ccall gsl_vector_long_double_swap_elements , Ptr <gsl_vector_long_double> -> CSize -> CSize -> IO CInt
-- ccall gsl_vector_long_double_view_array , Ptr CLDouble -> CSize -> IO <gsl_vector_long_double_view>
-- ccall gsl_vector_long_double_view_array_with_stride , Ptr CLDouble -> CSize -> CSize -> IO <gsl_vector_long_double_view>
foreign import ccall "gsl_vector_long_fprintf" c'gsl_vector_long_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector_long -> CString -> IO CInt
foreign import ccall "&gsl_vector_long_fprintf" p'gsl_vector_long_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_long -> CString -> IO CInt)

{-# LINE 374 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_fread" c'gsl_vector_long_fread
  :: Ptr CFile -> Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_fread" p'gsl_vector_long_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 375 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_free" c'gsl_vector_long_free
  :: Ptr C'gsl_vector_long -> IO ()
foreign import ccall "&gsl_vector_long_free" p'gsl_vector_long_free
  :: FunPtr (Ptr C'gsl_vector_long -> IO ())

{-# LINE 376 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_fscanf" c'gsl_vector_long_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_fscanf" p'gsl_vector_long_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 377 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_fwrite" c'gsl_vector_long_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_fwrite" p'gsl_vector_long_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 378 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_get" c'gsl_vector_long_get
  :: Ptr C'gsl_vector_long -> CSize -> IO CLong
foreign import ccall "&gsl_vector_long_get" p'gsl_vector_long_get
  :: FunPtr (Ptr C'gsl_vector_long -> CSize -> IO CLong)

{-# LINE 379 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_isneg" c'gsl_vector_long_isneg
  :: Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_isneg" p'gsl_vector_long_isneg
  :: FunPtr (Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 380 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_isnonneg" c'gsl_vector_long_isnonneg
  :: Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_isnonneg" p'gsl_vector_long_isnonneg
  :: FunPtr (Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 381 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_isnull" c'gsl_vector_long_isnull
  :: Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_isnull" p'gsl_vector_long_isnull
  :: FunPtr (Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 382 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_ispos" c'gsl_vector_long_ispos
  :: Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_ispos" p'gsl_vector_long_ispos
  :: FunPtr (Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 383 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_max" c'gsl_vector_long_max
  :: Ptr C'gsl_vector_long -> IO CLong
foreign import ccall "&gsl_vector_long_max" p'gsl_vector_long_max
  :: FunPtr (Ptr C'gsl_vector_long -> IO CLong)

{-# LINE 384 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_max_index" c'gsl_vector_long_max_index
  :: Ptr C'gsl_vector_long -> IO CSize
foreign import ccall "&gsl_vector_long_max_index" p'gsl_vector_long_max_index
  :: FunPtr (Ptr C'gsl_vector_long -> IO CSize)

{-# LINE 385 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_memcpy" c'gsl_vector_long_memcpy
  :: Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_memcpy" p'gsl_vector_long_memcpy
  :: FunPtr (Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 386 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_min" c'gsl_vector_long_min
  :: Ptr C'gsl_vector_long -> IO CLong
foreign import ccall "&gsl_vector_long_min" p'gsl_vector_long_min
  :: FunPtr (Ptr C'gsl_vector_long -> IO CLong)

{-# LINE 387 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_min_index" c'gsl_vector_long_min_index
  :: Ptr C'gsl_vector_long -> IO CSize
foreign import ccall "&gsl_vector_long_min_index" p'gsl_vector_long_min_index
  :: FunPtr (Ptr C'gsl_vector_long -> IO CSize)

{-# LINE 388 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_minmax" c'gsl_vector_long_minmax
  :: Ptr C'gsl_vector_long -> Ptr CLong -> Ptr CLong -> IO ()
foreign import ccall "&gsl_vector_long_minmax" p'gsl_vector_long_minmax
  :: FunPtr (Ptr C'gsl_vector_long -> Ptr CLong -> Ptr CLong -> IO ())

{-# LINE 389 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_minmax_index" c'gsl_vector_long_minmax_index
  :: Ptr C'gsl_vector_long -> Ptr CSize -> Ptr CSize -> IO ()
foreign import ccall "&gsl_vector_long_minmax_index" p'gsl_vector_long_minmax_index
  :: FunPtr (Ptr C'gsl_vector_long -> Ptr CSize -> Ptr CSize -> IO ())

{-# LINE 390 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_mul" c'gsl_vector_long_mul
  :: Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_mul" p'gsl_vector_long_mul
  :: FunPtr (Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 391 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_ptr" c'gsl_vector_long_ptr
  :: Ptr C'gsl_vector_long -> CSize -> IO (Ptr CLong)
foreign import ccall "&gsl_vector_long_ptr" p'gsl_vector_long_ptr
  :: FunPtr (Ptr C'gsl_vector_long -> CSize -> IO (Ptr CLong))

{-# LINE 392 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_reverse" c'gsl_vector_long_reverse
  :: Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_reverse" p'gsl_vector_long_reverse
  :: FunPtr (Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 393 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_scale" c'gsl_vector_long_scale
  :: Ptr C'gsl_vector_long -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_long_scale" p'gsl_vector_long_scale
  :: FunPtr (Ptr C'gsl_vector_long -> CDouble -> IO CInt)

{-# LINE 394 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_set" c'gsl_vector_long_set
  :: Ptr C'gsl_vector_long -> CSize -> CLong -> IO ()
foreign import ccall "&gsl_vector_long_set" p'gsl_vector_long_set
  :: FunPtr (Ptr C'gsl_vector_long -> CSize -> CLong -> IO ())

{-# LINE 395 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_set_all" c'gsl_vector_long_set_all
  :: Ptr C'gsl_vector_long -> CLong -> IO ()
foreign import ccall "&gsl_vector_long_set_all" p'gsl_vector_long_set_all
  :: FunPtr (Ptr C'gsl_vector_long -> CLong -> IO ())

{-# LINE 396 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_set_basis" c'gsl_vector_long_set_basis
  :: Ptr C'gsl_vector_long -> CSize -> IO CInt
foreign import ccall "&gsl_vector_long_set_basis" p'gsl_vector_long_set_basis
  :: FunPtr (Ptr C'gsl_vector_long -> CSize -> IO CInt)

{-# LINE 397 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_set_zero" c'gsl_vector_long_set_zero
  :: Ptr C'gsl_vector_long -> IO ()
foreign import ccall "&gsl_vector_long_set_zero" p'gsl_vector_long_set_zero
  :: FunPtr (Ptr C'gsl_vector_long -> IO ())

{-# LINE 398 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_sub" c'gsl_vector_long_sub
  :: Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_sub" p'gsl_vector_long_sub
  :: FunPtr (Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 399 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_long_subvector , Ptr <gsl_vector_long> -> CSize -> CSize -> IO <gsl_vector_long_view>
-- ccall gsl_vector_long_subvector_with_stride , Ptr <gsl_vector_long> -> CSize -> CSize -> CSize -> IO <gsl_vector_long_view>
foreign import ccall "gsl_vector_long_swap" c'gsl_vector_long_swap
  :: Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_vector_long_swap" p'gsl_vector_long_swap
  :: FunPtr (Ptr C'gsl_vector_long -> Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 402 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_long_swap_elements" c'gsl_vector_long_swap_elements
  :: Ptr C'gsl_vector_long -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_long_swap_elements" p'gsl_vector_long_swap_elements
  :: FunPtr (Ptr C'gsl_vector_long -> CSize -> CSize -> IO CInt)

{-# LINE 403 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_long_view_array , Ptr CLong -> CSize -> IO <gsl_vector_long_view>
-- ccall gsl_vector_long_view_array_with_stride , Ptr CLong -> CSize -> CSize -> IO <gsl_vector_long_view>
foreign import ccall "gsl_vector_max" c'gsl_vector_max
  :: Ptr C'gsl_vector -> IO CDouble
foreign import ccall "&gsl_vector_max" p'gsl_vector_max
  :: FunPtr (Ptr C'gsl_vector -> IO CDouble)

{-# LINE 406 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_max_index" c'gsl_vector_max_index
  :: Ptr C'gsl_vector -> IO CSize
foreign import ccall "&gsl_vector_max_index" p'gsl_vector_max_index
  :: FunPtr (Ptr C'gsl_vector -> IO CSize)

{-# LINE 407 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_memcpy" c'gsl_vector_memcpy
  :: Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_memcpy" p'gsl_vector_memcpy
  :: FunPtr (Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 408 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_min" c'gsl_vector_min
  :: Ptr C'gsl_vector -> IO CDouble
foreign import ccall "&gsl_vector_min" p'gsl_vector_min
  :: FunPtr (Ptr C'gsl_vector -> IO CDouble)

{-# LINE 409 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_min_index" c'gsl_vector_min_index
  :: Ptr C'gsl_vector -> IO CSize
foreign import ccall "&gsl_vector_min_index" p'gsl_vector_min_index
  :: FunPtr (Ptr C'gsl_vector -> IO CSize)

{-# LINE 410 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_minmax" c'gsl_vector_minmax
  :: Ptr C'gsl_vector -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_vector_minmax" p'gsl_vector_minmax
  :: FunPtr (Ptr C'gsl_vector -> Ptr CDouble -> Ptr CDouble -> IO ())

{-# LINE 411 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_minmax_index" c'gsl_vector_minmax_index
  :: Ptr C'gsl_vector -> Ptr CSize -> Ptr CSize -> IO ()
foreign import ccall "&gsl_vector_minmax_index" p'gsl_vector_minmax_index
  :: FunPtr (Ptr C'gsl_vector -> Ptr CSize -> Ptr CSize -> IO ())

{-# LINE 412 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_mul" c'gsl_vector_mul
  :: Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_mul" p'gsl_vector_mul
  :: FunPtr (Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 413 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ptr" c'gsl_vector_ptr
  :: Ptr C'gsl_vector -> CSize -> IO (Ptr CDouble)
foreign import ccall "&gsl_vector_ptr" p'gsl_vector_ptr
  :: FunPtr (Ptr C'gsl_vector -> CSize -> IO (Ptr CDouble))

{-# LINE 414 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_reverse" c'gsl_vector_reverse
  :: Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_reverse" p'gsl_vector_reverse
  :: FunPtr (Ptr C'gsl_vector -> IO CInt)

{-# LINE 415 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_scale" c'gsl_vector_scale
  :: Ptr C'gsl_vector -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_scale" p'gsl_vector_scale
  :: FunPtr (Ptr C'gsl_vector -> CDouble -> IO CInt)

{-# LINE 416 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_set" c'gsl_vector_set
  :: Ptr C'gsl_vector -> CSize -> CDouble -> IO ()
foreign import ccall "&gsl_vector_set" p'gsl_vector_set
  :: FunPtr (Ptr C'gsl_vector -> CSize -> CDouble -> IO ())

{-# LINE 417 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_set_all" c'gsl_vector_set_all
  :: Ptr C'gsl_vector -> CDouble -> IO ()
foreign import ccall "&gsl_vector_set_all" p'gsl_vector_set_all
  :: FunPtr (Ptr C'gsl_vector -> CDouble -> IO ())

{-# LINE 418 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_set_basis" c'gsl_vector_set_basis
  :: Ptr C'gsl_vector -> CSize -> IO CInt
foreign import ccall "&gsl_vector_set_basis" p'gsl_vector_set_basis
  :: FunPtr (Ptr C'gsl_vector -> CSize -> IO CInt)

{-# LINE 419 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_set_zero" c'gsl_vector_set_zero
  :: Ptr C'gsl_vector -> IO ()
foreign import ccall "&gsl_vector_set_zero" p'gsl_vector_set_zero
  :: FunPtr (Ptr C'gsl_vector -> IO ())

{-# LINE 420 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_add" c'gsl_vector_short_add
  :: Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_add" p'gsl_vector_short_add
  :: FunPtr (Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 421 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_add_constant" c'gsl_vector_short_add_constant
  :: Ptr C'gsl_vector_short -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_short_add_constant" p'gsl_vector_short_add_constant
  :: FunPtr (Ptr C'gsl_vector_short -> CDouble -> IO CInt)

{-# LINE 422 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_alloc" c'gsl_vector_short_alloc
  :: CSize -> IO (Ptr C'gsl_vector_short)
foreign import ccall "&gsl_vector_short_alloc" p'gsl_vector_short_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_short))

{-# LINE 423 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_alloc_col_from_matrix" c'gsl_vector_short_alloc_col_from_matrix
  :: Ptr C'gsl_matrix_short -> CSize -> IO (Ptr C'gsl_vector_short)
foreign import ccall "&gsl_vector_short_alloc_col_from_matrix" p'gsl_vector_short_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_short -> CSize -> IO (Ptr C'gsl_vector_short))

{-# LINE 424 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_alloc_from_block" c'gsl_vector_short_alloc_from_block
  :: Ptr C'gsl_block_short -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_short)
foreign import ccall "&gsl_vector_short_alloc_from_block" p'gsl_vector_short_alloc_from_block
  :: FunPtr (Ptr C'gsl_block_short -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_short))

{-# LINE 425 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_alloc_from_vector" c'gsl_vector_short_alloc_from_vector
  :: Ptr C'gsl_vector_short -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_short)
foreign import ccall "&gsl_vector_short_alloc_from_vector" p'gsl_vector_short_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector_short -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_short))

{-# LINE 426 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_alloc_row_from_matrix" c'gsl_vector_short_alloc_row_from_matrix
  :: Ptr C'gsl_matrix_short -> CSize -> IO (Ptr C'gsl_vector_short)
foreign import ccall "&gsl_vector_short_alloc_row_from_matrix" p'gsl_vector_short_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_short -> CSize -> IO (Ptr C'gsl_vector_short))

{-# LINE 427 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_calloc" c'gsl_vector_short_calloc
  :: CSize -> IO (Ptr C'gsl_vector_short)
foreign import ccall "&gsl_vector_short_calloc" p'gsl_vector_short_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_short))

{-# LINE 428 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_const_ptr" c'gsl_vector_short_const_ptr
  :: Ptr C'gsl_vector_short -> CSize -> IO (Ptr CShort)
foreign import ccall "&gsl_vector_short_const_ptr" p'gsl_vector_short_const_ptr
  :: FunPtr (Ptr C'gsl_vector_short -> CSize -> IO (Ptr CShort))

{-# LINE 429 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_short_const_subvector , Ptr <gsl_vector_short> -> CSize -> CSize -> IO <gsl_vector_short_const_view>
-- ccall gsl_vector_short_const_subvector_with_stride , Ptr <gsl_vector_short> -> CSize -> CSize -> CSize -> IO <gsl_vector_short_const_view>
-- ccall gsl_vector_short_const_view_array , Ptr CShort -> CSize -> IO <gsl_vector_short_const_view>
-- ccall gsl_vector_short_const_view_array_with_stride , Ptr CShort -> CSize -> CSize -> IO <gsl_vector_short_const_view>
foreign import ccall "gsl_vector_short_div" c'gsl_vector_short_div
  :: Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_div" p'gsl_vector_short_div
  :: FunPtr (Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 434 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_fprintf" c'gsl_vector_short_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector_short -> CString -> IO CInt
foreign import ccall "&gsl_vector_short_fprintf" p'gsl_vector_short_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_short -> CString -> IO CInt)

{-# LINE 435 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_fread" c'gsl_vector_short_fread
  :: Ptr CFile -> Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_fread" p'gsl_vector_short_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 436 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_free" c'gsl_vector_short_free
  :: Ptr C'gsl_vector_short -> IO ()
foreign import ccall "&gsl_vector_short_free" p'gsl_vector_short_free
  :: FunPtr (Ptr C'gsl_vector_short -> IO ())

{-# LINE 437 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_fscanf" c'gsl_vector_short_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_fscanf" p'gsl_vector_short_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 438 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_fwrite" c'gsl_vector_short_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_fwrite" p'gsl_vector_short_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 439 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_get" c'gsl_vector_short_get
  :: Ptr C'gsl_vector_short -> CSize -> IO CShort
foreign import ccall "&gsl_vector_short_get" p'gsl_vector_short_get
  :: FunPtr (Ptr C'gsl_vector_short -> CSize -> IO CShort)

{-# LINE 440 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_isneg" c'gsl_vector_short_isneg
  :: Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_isneg" p'gsl_vector_short_isneg
  :: FunPtr (Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 441 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_isnonneg" c'gsl_vector_short_isnonneg
  :: Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_isnonneg" p'gsl_vector_short_isnonneg
  :: FunPtr (Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 442 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_isnull" c'gsl_vector_short_isnull
  :: Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_isnull" p'gsl_vector_short_isnull
  :: FunPtr (Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 443 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_ispos" c'gsl_vector_short_ispos
  :: Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_ispos" p'gsl_vector_short_ispos
  :: FunPtr (Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 444 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_max" c'gsl_vector_short_max
  :: Ptr C'gsl_vector_short -> IO CShort
foreign import ccall "&gsl_vector_short_max" p'gsl_vector_short_max
  :: FunPtr (Ptr C'gsl_vector_short -> IO CShort)

{-# LINE 445 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_max_index" c'gsl_vector_short_max_index
  :: Ptr C'gsl_vector_short -> IO CSize
foreign import ccall "&gsl_vector_short_max_index" p'gsl_vector_short_max_index
  :: FunPtr (Ptr C'gsl_vector_short -> IO CSize)

{-# LINE 446 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_memcpy" c'gsl_vector_short_memcpy
  :: Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_memcpy" p'gsl_vector_short_memcpy
  :: FunPtr (Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 447 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_min" c'gsl_vector_short_min
  :: Ptr C'gsl_vector_short -> IO CShort
foreign import ccall "&gsl_vector_short_min" p'gsl_vector_short_min
  :: FunPtr (Ptr C'gsl_vector_short -> IO CShort)

{-# LINE 448 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_min_index" c'gsl_vector_short_min_index
  :: Ptr C'gsl_vector_short -> IO CSize
foreign import ccall "&gsl_vector_short_min_index" p'gsl_vector_short_min_index
  :: FunPtr (Ptr C'gsl_vector_short -> IO CSize)

{-# LINE 449 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_minmax" c'gsl_vector_short_minmax
  :: Ptr C'gsl_vector_short -> Ptr CShort -> Ptr CShort -> IO ()
foreign import ccall "&gsl_vector_short_minmax" p'gsl_vector_short_minmax
  :: FunPtr (Ptr C'gsl_vector_short -> Ptr CShort -> Ptr CShort -> IO ())

{-# LINE 450 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_minmax_index" c'gsl_vector_short_minmax_index
  :: Ptr C'gsl_vector_short -> Ptr CSize -> Ptr CSize -> IO ()
foreign import ccall "&gsl_vector_short_minmax_index" p'gsl_vector_short_minmax_index
  :: FunPtr (Ptr C'gsl_vector_short -> Ptr CSize -> Ptr CSize -> IO ())

{-# LINE 451 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_mul" c'gsl_vector_short_mul
  :: Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_mul" p'gsl_vector_short_mul
  :: FunPtr (Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 452 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_ptr" c'gsl_vector_short_ptr
  :: Ptr C'gsl_vector_short -> CSize -> IO (Ptr CShort)
foreign import ccall "&gsl_vector_short_ptr" p'gsl_vector_short_ptr
  :: FunPtr (Ptr C'gsl_vector_short -> CSize -> IO (Ptr CShort))

{-# LINE 453 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_reverse" c'gsl_vector_short_reverse
  :: Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_reverse" p'gsl_vector_short_reverse
  :: FunPtr (Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 454 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_scale" c'gsl_vector_short_scale
  :: Ptr C'gsl_vector_short -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_short_scale" p'gsl_vector_short_scale
  :: FunPtr (Ptr C'gsl_vector_short -> CDouble -> IO CInt)

{-# LINE 455 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_set" c'gsl_vector_short_set
  :: Ptr C'gsl_vector_short -> CSize -> CShort -> IO ()
foreign import ccall "&gsl_vector_short_set" p'gsl_vector_short_set
  :: FunPtr (Ptr C'gsl_vector_short -> CSize -> CShort -> IO ())

{-# LINE 456 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_set_all" c'gsl_vector_short_set_all
  :: Ptr C'gsl_vector_short -> CShort -> IO ()
foreign import ccall "&gsl_vector_short_set_all" p'gsl_vector_short_set_all
  :: FunPtr (Ptr C'gsl_vector_short -> CShort -> IO ())

{-# LINE 457 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_set_basis" c'gsl_vector_short_set_basis
  :: Ptr C'gsl_vector_short -> CSize -> IO CInt
foreign import ccall "&gsl_vector_short_set_basis" p'gsl_vector_short_set_basis
  :: FunPtr (Ptr C'gsl_vector_short -> CSize -> IO CInt)

{-# LINE 458 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_set_zero" c'gsl_vector_short_set_zero
  :: Ptr C'gsl_vector_short -> IO ()
foreign import ccall "&gsl_vector_short_set_zero" p'gsl_vector_short_set_zero
  :: FunPtr (Ptr C'gsl_vector_short -> IO ())

{-# LINE 459 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_sub" c'gsl_vector_short_sub
  :: Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_sub" p'gsl_vector_short_sub
  :: FunPtr (Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 460 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_short_subvector , Ptr <gsl_vector_short> -> CSize -> CSize -> IO <gsl_vector_short_view>
-- ccall gsl_vector_short_subvector_with_stride , Ptr <gsl_vector_short> -> CSize -> CSize -> CSize -> IO <gsl_vector_short_view>
foreign import ccall "gsl_vector_short_swap" c'gsl_vector_short_swap
  :: Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_vector_short_swap" p'gsl_vector_short_swap
  :: FunPtr (Ptr C'gsl_vector_short -> Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 463 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_short_swap_elements" c'gsl_vector_short_swap_elements
  :: Ptr C'gsl_vector_short -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_short_swap_elements" p'gsl_vector_short_swap_elements
  :: FunPtr (Ptr C'gsl_vector_short -> CSize -> CSize -> IO CInt)

{-# LINE 464 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_short_view_array , Ptr CShort -> CSize -> IO <gsl_vector_short_view>
-- ccall gsl_vector_short_view_array_with_stride , Ptr CShort -> CSize -> CSize -> IO <gsl_vector_short_view>
foreign import ccall "gsl_vector_sub" c'gsl_vector_sub
  :: Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_sub" p'gsl_vector_sub
  :: FunPtr (Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 467 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_subvector , Ptr <gsl_vector> -> CSize -> CSize -> IO <gsl_vector_view>
-- ccall gsl_vector_subvector_with_stride , Ptr <gsl_vector> -> CSize -> CSize -> CSize -> IO <gsl_vector_view>
foreign import ccall "gsl_vector_swap" c'gsl_vector_swap
  :: Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_vector_swap" p'gsl_vector_swap
  :: FunPtr (Ptr C'gsl_vector -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 470 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_swap_elements" c'gsl_vector_swap_elements
  :: Ptr C'gsl_vector -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_swap_elements" p'gsl_vector_swap_elements
  :: FunPtr (Ptr C'gsl_vector -> CSize -> CSize -> IO CInt)

{-# LINE 471 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_add" c'gsl_vector_uchar_add
  :: Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_add" p'gsl_vector_uchar_add
  :: FunPtr (Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 472 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_add_constant" c'gsl_vector_uchar_add_constant
  :: Ptr C'gsl_vector_uchar -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_uchar_add_constant" p'gsl_vector_uchar_add_constant
  :: FunPtr (Ptr C'gsl_vector_uchar -> CDouble -> IO CInt)

{-# LINE 473 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_alloc" c'gsl_vector_uchar_alloc
  :: CSize -> IO (Ptr C'gsl_vector_uchar)
foreign import ccall "&gsl_vector_uchar_alloc" p'gsl_vector_uchar_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_uchar))

{-# LINE 474 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_alloc_col_from_matrix" c'gsl_vector_uchar_alloc_col_from_matrix
  :: Ptr C'gsl_matrix_uchar -> CSize -> IO (Ptr C'gsl_vector_uchar)
foreign import ccall "&gsl_vector_uchar_alloc_col_from_matrix" p'gsl_vector_uchar_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_uchar -> CSize -> IO (Ptr C'gsl_vector_uchar))

{-# LINE 475 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_alloc_from_block" c'gsl_vector_uchar_alloc_from_block
  :: Ptr C'gsl_block_uchar -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_uchar)
foreign import ccall "&gsl_vector_uchar_alloc_from_block" p'gsl_vector_uchar_alloc_from_block
  :: FunPtr (Ptr C'gsl_block_uchar -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_uchar))

{-# LINE 476 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_alloc_from_vector" c'gsl_vector_uchar_alloc_from_vector
  :: Ptr C'gsl_vector_uchar -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_uchar)
foreign import ccall "&gsl_vector_uchar_alloc_from_vector" p'gsl_vector_uchar_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector_uchar -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_uchar))

{-# LINE 477 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_alloc_row_from_matrix" c'gsl_vector_uchar_alloc_row_from_matrix
  :: Ptr C'gsl_matrix_uchar -> CSize -> IO (Ptr C'gsl_vector_uchar)
foreign import ccall "&gsl_vector_uchar_alloc_row_from_matrix" p'gsl_vector_uchar_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_uchar -> CSize -> IO (Ptr C'gsl_vector_uchar))

{-# LINE 478 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_calloc" c'gsl_vector_uchar_calloc
  :: CSize -> IO (Ptr C'gsl_vector_uchar)
foreign import ccall "&gsl_vector_uchar_calloc" p'gsl_vector_uchar_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_uchar))

{-# LINE 479 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_const_ptr" c'gsl_vector_uchar_const_ptr
  :: Ptr C'gsl_vector_uchar -> CSize -> IO (Ptr CUChar)
foreign import ccall "&gsl_vector_uchar_const_ptr" p'gsl_vector_uchar_const_ptr
  :: FunPtr (Ptr C'gsl_vector_uchar -> CSize -> IO (Ptr CUChar))

{-# LINE 480 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_uchar_const_subvector , Ptr <gsl_vector_uchar> -> CSize -> CSize -> IO <gsl_vector_uchar_const_view>
-- ccall gsl_vector_uchar_const_subvector_with_stride , Ptr <gsl_vector_uchar> -> CSize -> CSize -> CSize -> IO <gsl_vector_uchar_const_view>
-- ccall gsl_vector_uchar_const_view_array , Ptr CUChar -> CSize -> IO <gsl_vector_uchar_const_view>
-- ccall gsl_vector_uchar_const_view_array_with_stride , Ptr CUChar -> CSize -> CSize -> IO <gsl_vector_uchar_const_view>
foreign import ccall "gsl_vector_uchar_div" c'gsl_vector_uchar_div
  :: Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_div" p'gsl_vector_uchar_div
  :: FunPtr (Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 485 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_fprintf" c'gsl_vector_uchar_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector_uchar -> CString -> IO CInt
foreign import ccall "&gsl_vector_uchar_fprintf" p'gsl_vector_uchar_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_uchar -> CString -> IO CInt)

{-# LINE 486 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_fread" c'gsl_vector_uchar_fread
  :: Ptr CFile -> Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_fread" p'gsl_vector_uchar_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 487 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_free" c'gsl_vector_uchar_free
  :: Ptr C'gsl_vector_uchar -> IO ()
foreign import ccall "&gsl_vector_uchar_free" p'gsl_vector_uchar_free
  :: FunPtr (Ptr C'gsl_vector_uchar -> IO ())

{-# LINE 488 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_fscanf" c'gsl_vector_uchar_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_fscanf" p'gsl_vector_uchar_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 489 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_fwrite" c'gsl_vector_uchar_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_fwrite" p'gsl_vector_uchar_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 490 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_get" c'gsl_vector_uchar_get
  :: Ptr C'gsl_vector_uchar -> CSize -> IO CUChar
foreign import ccall "&gsl_vector_uchar_get" p'gsl_vector_uchar_get
  :: FunPtr (Ptr C'gsl_vector_uchar -> CSize -> IO CUChar)

{-# LINE 491 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_isneg" c'gsl_vector_uchar_isneg
  :: Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_isneg" p'gsl_vector_uchar_isneg
  :: FunPtr (Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 492 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_isnonneg" c'gsl_vector_uchar_isnonneg
  :: Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_isnonneg" p'gsl_vector_uchar_isnonneg
  :: FunPtr (Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 493 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_isnull" c'gsl_vector_uchar_isnull
  :: Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_isnull" p'gsl_vector_uchar_isnull
  :: FunPtr (Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 494 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_ispos" c'gsl_vector_uchar_ispos
  :: Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_ispos" p'gsl_vector_uchar_ispos
  :: FunPtr (Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 495 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_max" c'gsl_vector_uchar_max
  :: Ptr C'gsl_vector_uchar -> IO CUChar
foreign import ccall "&gsl_vector_uchar_max" p'gsl_vector_uchar_max
  :: FunPtr (Ptr C'gsl_vector_uchar -> IO CUChar)

{-# LINE 496 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_max_index" c'gsl_vector_uchar_max_index
  :: Ptr C'gsl_vector_uchar -> IO CSize
foreign import ccall "&gsl_vector_uchar_max_index" p'gsl_vector_uchar_max_index
  :: FunPtr (Ptr C'gsl_vector_uchar -> IO CSize)

{-# LINE 497 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_memcpy" c'gsl_vector_uchar_memcpy
  :: Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_memcpy" p'gsl_vector_uchar_memcpy
  :: FunPtr (Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 498 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_min" c'gsl_vector_uchar_min
  :: Ptr C'gsl_vector_uchar -> IO CUChar
foreign import ccall "&gsl_vector_uchar_min" p'gsl_vector_uchar_min
  :: FunPtr (Ptr C'gsl_vector_uchar -> IO CUChar)

{-# LINE 499 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_min_index" c'gsl_vector_uchar_min_index
  :: Ptr C'gsl_vector_uchar -> IO CSize
foreign import ccall "&gsl_vector_uchar_min_index" p'gsl_vector_uchar_min_index
  :: FunPtr (Ptr C'gsl_vector_uchar -> IO CSize)

{-# LINE 500 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_minmax" c'gsl_vector_uchar_minmax
  :: Ptr C'gsl_vector_uchar -> Ptr CUChar -> Ptr CUChar -> IO ()
foreign import ccall "&gsl_vector_uchar_minmax" p'gsl_vector_uchar_minmax
  :: FunPtr (Ptr C'gsl_vector_uchar -> Ptr CUChar -> Ptr CUChar -> IO ())

{-# LINE 501 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_minmax_index" c'gsl_vector_uchar_minmax_index
  :: Ptr C'gsl_vector_uchar -> Ptr CSize -> Ptr CSize -> IO ()
foreign import ccall "&gsl_vector_uchar_minmax_index" p'gsl_vector_uchar_minmax_index
  :: FunPtr (Ptr C'gsl_vector_uchar -> Ptr CSize -> Ptr CSize -> IO ())

{-# LINE 502 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_mul" c'gsl_vector_uchar_mul
  :: Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_mul" p'gsl_vector_uchar_mul
  :: FunPtr (Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 503 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_ptr" c'gsl_vector_uchar_ptr
  :: Ptr C'gsl_vector_uchar -> CSize -> IO (Ptr CUChar)
foreign import ccall "&gsl_vector_uchar_ptr" p'gsl_vector_uchar_ptr
  :: FunPtr (Ptr C'gsl_vector_uchar -> CSize -> IO (Ptr CUChar))

{-# LINE 504 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_reverse" c'gsl_vector_uchar_reverse
  :: Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_reverse" p'gsl_vector_uchar_reverse
  :: FunPtr (Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 505 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_scale" c'gsl_vector_uchar_scale
  :: Ptr C'gsl_vector_uchar -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_uchar_scale" p'gsl_vector_uchar_scale
  :: FunPtr (Ptr C'gsl_vector_uchar -> CDouble -> IO CInt)

{-# LINE 506 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_set" c'gsl_vector_uchar_set
  :: Ptr C'gsl_vector_uchar -> CSize -> CUChar -> IO ()
foreign import ccall "&gsl_vector_uchar_set" p'gsl_vector_uchar_set
  :: FunPtr (Ptr C'gsl_vector_uchar -> CSize -> CUChar -> IO ())

{-# LINE 507 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_set_all" c'gsl_vector_uchar_set_all
  :: Ptr C'gsl_vector_uchar -> CUChar -> IO ()
foreign import ccall "&gsl_vector_uchar_set_all" p'gsl_vector_uchar_set_all
  :: FunPtr (Ptr C'gsl_vector_uchar -> CUChar -> IO ())

{-# LINE 508 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_set_basis" c'gsl_vector_uchar_set_basis
  :: Ptr C'gsl_vector_uchar -> CSize -> IO CInt
foreign import ccall "&gsl_vector_uchar_set_basis" p'gsl_vector_uchar_set_basis
  :: FunPtr (Ptr C'gsl_vector_uchar -> CSize -> IO CInt)

{-# LINE 509 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_set_zero" c'gsl_vector_uchar_set_zero
  :: Ptr C'gsl_vector_uchar -> IO ()
foreign import ccall "&gsl_vector_uchar_set_zero" p'gsl_vector_uchar_set_zero
  :: FunPtr (Ptr C'gsl_vector_uchar -> IO ())

{-# LINE 510 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_sub" c'gsl_vector_uchar_sub
  :: Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_sub" p'gsl_vector_uchar_sub
  :: FunPtr (Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 511 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_uchar_subvector , Ptr <gsl_vector_uchar> -> CSize -> CSize -> IO <gsl_vector_uchar_view>
-- ccall gsl_vector_uchar_subvector_with_stride , Ptr <gsl_vector_uchar> -> CSize -> CSize -> CSize -> IO <gsl_vector_uchar_view>
foreign import ccall "gsl_vector_uchar_swap" c'gsl_vector_uchar_swap
  :: Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_vector_uchar_swap" p'gsl_vector_uchar_swap
  :: FunPtr (Ptr C'gsl_vector_uchar -> Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 514 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uchar_swap_elements" c'gsl_vector_uchar_swap_elements
  :: Ptr C'gsl_vector_uchar -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_uchar_swap_elements" p'gsl_vector_uchar_swap_elements
  :: FunPtr (Ptr C'gsl_vector_uchar -> CSize -> CSize -> IO CInt)

{-# LINE 515 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_uchar_view_array , Ptr CUChar -> CSize -> IO <gsl_vector_uchar_view>
-- ccall gsl_vector_uchar_view_array_with_stride , Ptr CUChar -> CSize -> CSize -> IO <gsl_vector_uchar_view>
foreign import ccall "gsl_vector_uint_add" c'gsl_vector_uint_add
  :: Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_add" p'gsl_vector_uint_add
  :: FunPtr (Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 518 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_add_constant" c'gsl_vector_uint_add_constant
  :: Ptr C'gsl_vector_uint -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_uint_add_constant" p'gsl_vector_uint_add_constant
  :: FunPtr (Ptr C'gsl_vector_uint -> CDouble -> IO CInt)

{-# LINE 519 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_alloc" c'gsl_vector_uint_alloc
  :: CSize -> IO (Ptr C'gsl_vector_uint)
foreign import ccall "&gsl_vector_uint_alloc" p'gsl_vector_uint_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_uint))

{-# LINE 520 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_alloc_col_from_matrix" c'gsl_vector_uint_alloc_col_from_matrix
  :: Ptr C'gsl_matrix_uint -> CSize -> IO (Ptr C'gsl_vector_uint)
foreign import ccall "&gsl_vector_uint_alloc_col_from_matrix" p'gsl_vector_uint_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_uint -> CSize -> IO (Ptr C'gsl_vector_uint))

{-# LINE 521 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_alloc_from_block" c'gsl_vector_uint_alloc_from_block
  :: Ptr C'gsl_block_uint -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_uint)
foreign import ccall "&gsl_vector_uint_alloc_from_block" p'gsl_vector_uint_alloc_from_block
  :: FunPtr (Ptr C'gsl_block_uint -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_uint))

{-# LINE 522 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_alloc_from_vector" c'gsl_vector_uint_alloc_from_vector
  :: Ptr C'gsl_vector_uint -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_uint)
foreign import ccall "&gsl_vector_uint_alloc_from_vector" p'gsl_vector_uint_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector_uint -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_uint))

{-# LINE 523 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_alloc_row_from_matrix" c'gsl_vector_uint_alloc_row_from_matrix
  :: Ptr C'gsl_matrix_uint -> CSize -> IO (Ptr C'gsl_vector_uint)
foreign import ccall "&gsl_vector_uint_alloc_row_from_matrix" p'gsl_vector_uint_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_uint -> CSize -> IO (Ptr C'gsl_vector_uint))

{-# LINE 524 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_calloc" c'gsl_vector_uint_calloc
  :: CSize -> IO (Ptr C'gsl_vector_uint)
foreign import ccall "&gsl_vector_uint_calloc" p'gsl_vector_uint_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_uint))

{-# LINE 525 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_const_ptr" c'gsl_vector_uint_const_ptr
  :: Ptr C'gsl_vector_uint -> CSize -> IO (Ptr CUInt)
foreign import ccall "&gsl_vector_uint_const_ptr" p'gsl_vector_uint_const_ptr
  :: FunPtr (Ptr C'gsl_vector_uint -> CSize -> IO (Ptr CUInt))

{-# LINE 526 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_uint_const_subvector , Ptr <gsl_vector_uint> -> CSize -> CSize -> IO <gsl_vector_uint_const_view>
-- ccall gsl_vector_uint_const_subvector_with_stride , Ptr <gsl_vector_uint> -> CSize -> CSize -> CSize -> IO <gsl_vector_uint_const_view>
-- ccall gsl_vector_uint_const_view_array , Ptr CUInt -> CSize -> IO <gsl_vector_uint_const_view>
-- ccall gsl_vector_uint_const_view_array_with_stride , Ptr CUInt -> CSize -> CSize -> IO <gsl_vector_uint_const_view>
foreign import ccall "gsl_vector_uint_div" c'gsl_vector_uint_div
  :: Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_div" p'gsl_vector_uint_div
  :: FunPtr (Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 531 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_fprintf" c'gsl_vector_uint_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector_uint -> CString -> IO CInt
foreign import ccall "&gsl_vector_uint_fprintf" p'gsl_vector_uint_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_uint -> CString -> IO CInt)

{-# LINE 532 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_fread" c'gsl_vector_uint_fread
  :: Ptr CFile -> Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_fread" p'gsl_vector_uint_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 533 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_free" c'gsl_vector_uint_free
  :: Ptr C'gsl_vector_uint -> IO ()
foreign import ccall "&gsl_vector_uint_free" p'gsl_vector_uint_free
  :: FunPtr (Ptr C'gsl_vector_uint -> IO ())

{-# LINE 534 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_fscanf" c'gsl_vector_uint_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_fscanf" p'gsl_vector_uint_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 535 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_fwrite" c'gsl_vector_uint_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_fwrite" p'gsl_vector_uint_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 536 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_get" c'gsl_vector_uint_get
  :: Ptr C'gsl_vector_uint -> CSize -> IO CUInt
foreign import ccall "&gsl_vector_uint_get" p'gsl_vector_uint_get
  :: FunPtr (Ptr C'gsl_vector_uint -> CSize -> IO CUInt)

{-# LINE 537 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_isneg" c'gsl_vector_uint_isneg
  :: Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_isneg" p'gsl_vector_uint_isneg
  :: FunPtr (Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 538 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_isnonneg" c'gsl_vector_uint_isnonneg
  :: Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_isnonneg" p'gsl_vector_uint_isnonneg
  :: FunPtr (Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 539 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_isnull" c'gsl_vector_uint_isnull
  :: Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_isnull" p'gsl_vector_uint_isnull
  :: FunPtr (Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 540 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_ispos" c'gsl_vector_uint_ispos
  :: Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_ispos" p'gsl_vector_uint_ispos
  :: FunPtr (Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 541 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_max" c'gsl_vector_uint_max
  :: Ptr C'gsl_vector_uint -> IO CUInt
foreign import ccall "&gsl_vector_uint_max" p'gsl_vector_uint_max
  :: FunPtr (Ptr C'gsl_vector_uint -> IO CUInt)

{-# LINE 542 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_max_index" c'gsl_vector_uint_max_index
  :: Ptr C'gsl_vector_uint -> IO CSize
foreign import ccall "&gsl_vector_uint_max_index" p'gsl_vector_uint_max_index
  :: FunPtr (Ptr C'gsl_vector_uint -> IO CSize)

{-# LINE 543 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_memcpy" c'gsl_vector_uint_memcpy
  :: Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_memcpy" p'gsl_vector_uint_memcpy
  :: FunPtr (Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 544 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_min" c'gsl_vector_uint_min
  :: Ptr C'gsl_vector_uint -> IO CUInt
foreign import ccall "&gsl_vector_uint_min" p'gsl_vector_uint_min
  :: FunPtr (Ptr C'gsl_vector_uint -> IO CUInt)

{-# LINE 545 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_min_index" c'gsl_vector_uint_min_index
  :: Ptr C'gsl_vector_uint -> IO CSize
foreign import ccall "&gsl_vector_uint_min_index" p'gsl_vector_uint_min_index
  :: FunPtr (Ptr C'gsl_vector_uint -> IO CSize)

{-# LINE 546 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_minmax" c'gsl_vector_uint_minmax
  :: Ptr C'gsl_vector_uint -> Ptr CUInt -> Ptr CUInt -> IO ()
foreign import ccall "&gsl_vector_uint_minmax" p'gsl_vector_uint_minmax
  :: FunPtr (Ptr C'gsl_vector_uint -> Ptr CUInt -> Ptr CUInt -> IO ())

{-# LINE 547 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_minmax_index" c'gsl_vector_uint_minmax_index
  :: Ptr C'gsl_vector_uint -> Ptr CSize -> Ptr CSize -> IO ()
foreign import ccall "&gsl_vector_uint_minmax_index" p'gsl_vector_uint_minmax_index
  :: FunPtr (Ptr C'gsl_vector_uint -> Ptr CSize -> Ptr CSize -> IO ())

{-# LINE 548 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_mul" c'gsl_vector_uint_mul
  :: Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_mul" p'gsl_vector_uint_mul
  :: FunPtr (Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 549 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_ptr" c'gsl_vector_uint_ptr
  :: Ptr C'gsl_vector_uint -> CSize -> IO (Ptr CUInt)
foreign import ccall "&gsl_vector_uint_ptr" p'gsl_vector_uint_ptr
  :: FunPtr (Ptr C'gsl_vector_uint -> CSize -> IO (Ptr CUInt))

{-# LINE 550 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_reverse" c'gsl_vector_uint_reverse
  :: Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_reverse" p'gsl_vector_uint_reverse
  :: FunPtr (Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 551 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_scale" c'gsl_vector_uint_scale
  :: Ptr C'gsl_vector_uint -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_uint_scale" p'gsl_vector_uint_scale
  :: FunPtr (Ptr C'gsl_vector_uint -> CDouble -> IO CInt)

{-# LINE 552 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_set" c'gsl_vector_uint_set
  :: Ptr C'gsl_vector_uint -> CSize -> CUInt -> IO ()
foreign import ccall "&gsl_vector_uint_set" p'gsl_vector_uint_set
  :: FunPtr (Ptr C'gsl_vector_uint -> CSize -> CUInt -> IO ())

{-# LINE 553 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_set_all" c'gsl_vector_uint_set_all
  :: Ptr C'gsl_vector_uint -> CUInt -> IO ()
foreign import ccall "&gsl_vector_uint_set_all" p'gsl_vector_uint_set_all
  :: FunPtr (Ptr C'gsl_vector_uint -> CUInt -> IO ())

{-# LINE 554 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_set_basis" c'gsl_vector_uint_set_basis
  :: Ptr C'gsl_vector_uint -> CSize -> IO CInt
foreign import ccall "&gsl_vector_uint_set_basis" p'gsl_vector_uint_set_basis
  :: FunPtr (Ptr C'gsl_vector_uint -> CSize -> IO CInt)

{-# LINE 555 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_set_zero" c'gsl_vector_uint_set_zero
  :: Ptr C'gsl_vector_uint -> IO ()
foreign import ccall "&gsl_vector_uint_set_zero" p'gsl_vector_uint_set_zero
  :: FunPtr (Ptr C'gsl_vector_uint -> IO ())

{-# LINE 556 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_sub" c'gsl_vector_uint_sub
  :: Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_sub" p'gsl_vector_uint_sub
  :: FunPtr (Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 557 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_uint_subvector , Ptr <gsl_vector_uint> -> CSize -> CSize -> IO <gsl_vector_uint_view>
-- ccall gsl_vector_uint_subvector_with_stride , Ptr <gsl_vector_uint> -> CSize -> CSize -> CSize -> IO <gsl_vector_uint_view>
foreign import ccall "gsl_vector_uint_swap" c'gsl_vector_uint_swap
  :: Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_vector_uint_swap" p'gsl_vector_uint_swap
  :: FunPtr (Ptr C'gsl_vector_uint -> Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 560 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_uint_swap_elements" c'gsl_vector_uint_swap_elements
  :: Ptr C'gsl_vector_uint -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_uint_swap_elements" p'gsl_vector_uint_swap_elements
  :: FunPtr (Ptr C'gsl_vector_uint -> CSize -> CSize -> IO CInt)

{-# LINE 561 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_uint_view_array , Ptr CUInt -> CSize -> IO <gsl_vector_uint_view>
-- ccall gsl_vector_uint_view_array_with_stride , Ptr CUInt -> CSize -> CSize -> IO <gsl_vector_uint_view>
foreign import ccall "gsl_vector_ulong_add" c'gsl_vector_ulong_add
  :: Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_add" p'gsl_vector_ulong_add
  :: FunPtr (Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 564 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_add_constant" c'gsl_vector_ulong_add_constant
  :: Ptr C'gsl_vector_ulong -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_ulong_add_constant" p'gsl_vector_ulong_add_constant
  :: FunPtr (Ptr C'gsl_vector_ulong -> CDouble -> IO CInt)

{-# LINE 565 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_alloc" c'gsl_vector_ulong_alloc
  :: CSize -> IO (Ptr C'gsl_vector_ulong)
foreign import ccall "&gsl_vector_ulong_alloc" p'gsl_vector_ulong_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_ulong))

{-# LINE 566 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_alloc_col_from_matrix" c'gsl_vector_ulong_alloc_col_from_matrix
  :: Ptr C'gsl_matrix_ulong -> CSize -> IO (Ptr C'gsl_vector_ulong)
foreign import ccall "&gsl_vector_ulong_alloc_col_from_matrix" p'gsl_vector_ulong_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_ulong -> CSize -> IO (Ptr C'gsl_vector_ulong))

{-# LINE 567 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_alloc_from_block" c'gsl_vector_ulong_alloc_from_block
  :: Ptr C'gsl_block_ulong -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_ulong)
foreign import ccall "&gsl_vector_ulong_alloc_from_block" p'gsl_vector_ulong_alloc_from_block
  :: FunPtr (Ptr C'gsl_block_ulong -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_ulong))

{-# LINE 568 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_alloc_from_vector" c'gsl_vector_ulong_alloc_from_vector
  :: Ptr C'gsl_vector_ulong -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_ulong)
foreign import ccall "&gsl_vector_ulong_alloc_from_vector" p'gsl_vector_ulong_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector_ulong -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_ulong))

{-# LINE 569 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_alloc_row_from_matrix" c'gsl_vector_ulong_alloc_row_from_matrix
  :: Ptr C'gsl_matrix_ulong -> CSize -> IO (Ptr C'gsl_vector_ulong)
foreign import ccall "&gsl_vector_ulong_alloc_row_from_matrix" p'gsl_vector_ulong_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_ulong -> CSize -> IO (Ptr C'gsl_vector_ulong))

{-# LINE 570 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_calloc" c'gsl_vector_ulong_calloc
  :: CSize -> IO (Ptr C'gsl_vector_ulong)
foreign import ccall "&gsl_vector_ulong_calloc" p'gsl_vector_ulong_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_ulong))

{-# LINE 571 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_const_ptr" c'gsl_vector_ulong_const_ptr
  :: Ptr C'gsl_vector_ulong -> CSize -> IO (Ptr CULong)
foreign import ccall "&gsl_vector_ulong_const_ptr" p'gsl_vector_ulong_const_ptr
  :: FunPtr (Ptr C'gsl_vector_ulong -> CSize -> IO (Ptr CULong))

{-# LINE 572 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_ulong_const_subvector , Ptr <gsl_vector_ulong> -> CSize -> CSize -> IO <gsl_vector_ulong_const_view>
-- ccall gsl_vector_ulong_const_subvector_with_stride , Ptr <gsl_vector_ulong> -> CSize -> CSize -> CSize -> IO <gsl_vector_ulong_const_view>
-- ccall gsl_vector_ulong_const_view_array , Ptr CULong -> CSize -> IO <gsl_vector_ulong_const_view>
-- ccall gsl_vector_ulong_const_view_array_with_stride , Ptr CULong -> CSize -> CSize -> IO <gsl_vector_ulong_const_view>
foreign import ccall "gsl_vector_ulong_div" c'gsl_vector_ulong_div
  :: Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_div" p'gsl_vector_ulong_div
  :: FunPtr (Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 577 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_fprintf" c'gsl_vector_ulong_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector_ulong -> CString -> IO CInt
foreign import ccall "&gsl_vector_ulong_fprintf" p'gsl_vector_ulong_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_ulong -> CString -> IO CInt)

{-# LINE 578 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_fread" c'gsl_vector_ulong_fread
  :: Ptr CFile -> Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_fread" p'gsl_vector_ulong_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 579 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_free" c'gsl_vector_ulong_free
  :: Ptr C'gsl_vector_ulong -> IO ()
foreign import ccall "&gsl_vector_ulong_free" p'gsl_vector_ulong_free
  :: FunPtr (Ptr C'gsl_vector_ulong -> IO ())

{-# LINE 580 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_fscanf" c'gsl_vector_ulong_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_fscanf" p'gsl_vector_ulong_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 581 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_fwrite" c'gsl_vector_ulong_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_fwrite" p'gsl_vector_ulong_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 582 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_get" c'gsl_vector_ulong_get
  :: Ptr C'gsl_vector_ulong -> CSize -> IO CULong
foreign import ccall "&gsl_vector_ulong_get" p'gsl_vector_ulong_get
  :: FunPtr (Ptr C'gsl_vector_ulong -> CSize -> IO CULong)

{-# LINE 583 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_isneg" c'gsl_vector_ulong_isneg
  :: Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_isneg" p'gsl_vector_ulong_isneg
  :: FunPtr (Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 584 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_isnonneg" c'gsl_vector_ulong_isnonneg
  :: Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_isnonneg" p'gsl_vector_ulong_isnonneg
  :: FunPtr (Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 585 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_isnull" c'gsl_vector_ulong_isnull
  :: Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_isnull" p'gsl_vector_ulong_isnull
  :: FunPtr (Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 586 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_ispos" c'gsl_vector_ulong_ispos
  :: Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_ispos" p'gsl_vector_ulong_ispos
  :: FunPtr (Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 587 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_max" c'gsl_vector_ulong_max
  :: Ptr C'gsl_vector_ulong -> IO CULong
foreign import ccall "&gsl_vector_ulong_max" p'gsl_vector_ulong_max
  :: FunPtr (Ptr C'gsl_vector_ulong -> IO CULong)

{-# LINE 588 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_max_index" c'gsl_vector_ulong_max_index
  :: Ptr C'gsl_vector_ulong -> IO CSize
foreign import ccall "&gsl_vector_ulong_max_index" p'gsl_vector_ulong_max_index
  :: FunPtr (Ptr C'gsl_vector_ulong -> IO CSize)

{-# LINE 589 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_memcpy" c'gsl_vector_ulong_memcpy
  :: Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_memcpy" p'gsl_vector_ulong_memcpy
  :: FunPtr (Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 590 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_min" c'gsl_vector_ulong_min
  :: Ptr C'gsl_vector_ulong -> IO CULong
foreign import ccall "&gsl_vector_ulong_min" p'gsl_vector_ulong_min
  :: FunPtr (Ptr C'gsl_vector_ulong -> IO CULong)

{-# LINE 591 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_min_index" c'gsl_vector_ulong_min_index
  :: Ptr C'gsl_vector_ulong -> IO CSize
foreign import ccall "&gsl_vector_ulong_min_index" p'gsl_vector_ulong_min_index
  :: FunPtr (Ptr C'gsl_vector_ulong -> IO CSize)

{-# LINE 592 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_minmax" c'gsl_vector_ulong_minmax
  :: Ptr C'gsl_vector_ulong -> Ptr CULong -> Ptr CULong -> IO ()
foreign import ccall "&gsl_vector_ulong_minmax" p'gsl_vector_ulong_minmax
  :: FunPtr (Ptr C'gsl_vector_ulong -> Ptr CULong -> Ptr CULong -> IO ())

{-# LINE 593 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_minmax_index" c'gsl_vector_ulong_minmax_index
  :: Ptr C'gsl_vector_ulong -> Ptr CSize -> Ptr CSize -> IO ()
foreign import ccall "&gsl_vector_ulong_minmax_index" p'gsl_vector_ulong_minmax_index
  :: FunPtr (Ptr C'gsl_vector_ulong -> Ptr CSize -> Ptr CSize -> IO ())

{-# LINE 594 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_mul" c'gsl_vector_ulong_mul
  :: Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_mul" p'gsl_vector_ulong_mul
  :: FunPtr (Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 595 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_ptr" c'gsl_vector_ulong_ptr
  :: Ptr C'gsl_vector_ulong -> CSize -> IO (Ptr CULong)
foreign import ccall "&gsl_vector_ulong_ptr" p'gsl_vector_ulong_ptr
  :: FunPtr (Ptr C'gsl_vector_ulong -> CSize -> IO (Ptr CULong))

{-# LINE 596 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_reverse" c'gsl_vector_ulong_reverse
  :: Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_reverse" p'gsl_vector_ulong_reverse
  :: FunPtr (Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 597 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_scale" c'gsl_vector_ulong_scale
  :: Ptr C'gsl_vector_ulong -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_ulong_scale" p'gsl_vector_ulong_scale
  :: FunPtr (Ptr C'gsl_vector_ulong -> CDouble -> IO CInt)

{-# LINE 598 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_set" c'gsl_vector_ulong_set
  :: Ptr C'gsl_vector_ulong -> CSize -> CULong -> IO ()
foreign import ccall "&gsl_vector_ulong_set" p'gsl_vector_ulong_set
  :: FunPtr (Ptr C'gsl_vector_ulong -> CSize -> CULong -> IO ())

{-# LINE 599 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_set_all" c'gsl_vector_ulong_set_all
  :: Ptr C'gsl_vector_ulong -> CULong -> IO ()
foreign import ccall "&gsl_vector_ulong_set_all" p'gsl_vector_ulong_set_all
  :: FunPtr (Ptr C'gsl_vector_ulong -> CULong -> IO ())

{-# LINE 600 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_set_basis" c'gsl_vector_ulong_set_basis
  :: Ptr C'gsl_vector_ulong -> CSize -> IO CInt
foreign import ccall "&gsl_vector_ulong_set_basis" p'gsl_vector_ulong_set_basis
  :: FunPtr (Ptr C'gsl_vector_ulong -> CSize -> IO CInt)

{-# LINE 601 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_set_zero" c'gsl_vector_ulong_set_zero
  :: Ptr C'gsl_vector_ulong -> IO ()
foreign import ccall "&gsl_vector_ulong_set_zero" p'gsl_vector_ulong_set_zero
  :: FunPtr (Ptr C'gsl_vector_ulong -> IO ())

{-# LINE 602 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_sub" c'gsl_vector_ulong_sub
  :: Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_sub" p'gsl_vector_ulong_sub
  :: FunPtr (Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 603 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_ulong_subvector , Ptr <gsl_vector_ulong> -> CSize -> CSize -> IO <gsl_vector_ulong_view>
-- ccall gsl_vector_ulong_subvector_with_stride , Ptr <gsl_vector_ulong> -> CSize -> CSize -> CSize -> IO <gsl_vector_ulong_view>
foreign import ccall "gsl_vector_ulong_swap" c'gsl_vector_ulong_swap
  :: Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_vector_ulong_swap" p'gsl_vector_ulong_swap
  :: FunPtr (Ptr C'gsl_vector_ulong -> Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 606 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ulong_swap_elements" c'gsl_vector_ulong_swap_elements
  :: Ptr C'gsl_vector_ulong -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_ulong_swap_elements" p'gsl_vector_ulong_swap_elements
  :: FunPtr (Ptr C'gsl_vector_ulong -> CSize -> CSize -> IO CInt)

{-# LINE 607 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_ulong_view_array , Ptr CULong -> CSize -> IO <gsl_vector_ulong_view>
-- ccall gsl_vector_ulong_view_array_with_stride , Ptr CULong -> CSize -> CSize -> IO <gsl_vector_ulong_view>
foreign import ccall "gsl_vector_ushort_add" c'gsl_vector_ushort_add
  :: Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_add" p'gsl_vector_ushort_add
  :: FunPtr (Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 610 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_add_constant" c'gsl_vector_ushort_add_constant
  :: Ptr C'gsl_vector_ushort -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_ushort_add_constant" p'gsl_vector_ushort_add_constant
  :: FunPtr (Ptr C'gsl_vector_ushort -> CDouble -> IO CInt)

{-# LINE 611 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_alloc" c'gsl_vector_ushort_alloc
  :: CSize -> IO (Ptr C'gsl_vector_ushort)
foreign import ccall "&gsl_vector_ushort_alloc" p'gsl_vector_ushort_alloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_ushort))

{-# LINE 612 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_alloc_col_from_matrix" c'gsl_vector_ushort_alloc_col_from_matrix
  :: Ptr C'gsl_matrix_ushort -> CSize -> IO (Ptr C'gsl_vector_ushort)
foreign import ccall "&gsl_vector_ushort_alloc_col_from_matrix" p'gsl_vector_ushort_alloc_col_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_ushort -> CSize -> IO (Ptr C'gsl_vector_ushort))

{-# LINE 613 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_alloc_from_block" c'gsl_vector_ushort_alloc_from_block
  :: Ptr C'gsl_block_ushort -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_ushort)
foreign import ccall "&gsl_vector_ushort_alloc_from_block" p'gsl_vector_ushort_alloc_from_block
  :: FunPtr (Ptr C'gsl_block_ushort -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_ushort))

{-# LINE 614 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_alloc_from_vector" c'gsl_vector_ushort_alloc_from_vector
  :: Ptr C'gsl_vector_ushort -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_ushort)
foreign import ccall "&gsl_vector_ushort_alloc_from_vector" p'gsl_vector_ushort_alloc_from_vector
  :: FunPtr (Ptr C'gsl_vector_ushort -> CSize -> CSize -> CSize -> IO (Ptr C'gsl_vector_ushort))

{-# LINE 615 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_alloc_row_from_matrix" c'gsl_vector_ushort_alloc_row_from_matrix
  :: Ptr C'gsl_matrix_ushort -> CSize -> IO (Ptr C'gsl_vector_ushort)
foreign import ccall "&gsl_vector_ushort_alloc_row_from_matrix" p'gsl_vector_ushort_alloc_row_from_matrix
  :: FunPtr (Ptr C'gsl_matrix_ushort -> CSize -> IO (Ptr C'gsl_vector_ushort))

{-# LINE 616 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_calloc" c'gsl_vector_ushort_calloc
  :: CSize -> IO (Ptr C'gsl_vector_ushort)
foreign import ccall "&gsl_vector_ushort_calloc" p'gsl_vector_ushort_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_vector_ushort))

{-# LINE 617 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_const_ptr" c'gsl_vector_ushort_const_ptr
  :: Ptr C'gsl_vector_ushort -> CSize -> IO (Ptr CUShort)
foreign import ccall "&gsl_vector_ushort_const_ptr" p'gsl_vector_ushort_const_ptr
  :: FunPtr (Ptr C'gsl_vector_ushort -> CSize -> IO (Ptr CUShort))

{-# LINE 618 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_ushort_const_subvector , Ptr <gsl_vector_ushort> -> CSize -> CSize -> IO <gsl_vector_ushort_const_view>
-- ccall gsl_vector_ushort_const_subvector_with_stride , Ptr <gsl_vector_ushort> -> CSize -> CSize -> CSize -> IO <gsl_vector_ushort_const_view>
-- ccall gsl_vector_ushort_const_view_array , Ptr CUShort -> CSize -> IO <gsl_vector_ushort_const_view>
-- ccall gsl_vector_ushort_const_view_array_with_stride , Ptr CUShort -> CSize -> CSize -> IO <gsl_vector_ushort_const_view>
foreign import ccall "gsl_vector_ushort_div" c'gsl_vector_ushort_div
  :: Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_div" p'gsl_vector_ushort_div
  :: FunPtr (Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 623 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_fprintf" c'gsl_vector_ushort_fprintf
  :: Ptr CFile -> Ptr C'gsl_vector_ushort -> CString -> IO CInt
foreign import ccall "&gsl_vector_ushort_fprintf" p'gsl_vector_ushort_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_ushort -> CString -> IO CInt)

{-# LINE 624 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_fread" c'gsl_vector_ushort_fread
  :: Ptr CFile -> Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_fread" p'gsl_vector_ushort_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 625 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_free" c'gsl_vector_ushort_free
  :: Ptr C'gsl_vector_ushort -> IO ()
foreign import ccall "&gsl_vector_ushort_free" p'gsl_vector_ushort_free
  :: FunPtr (Ptr C'gsl_vector_ushort -> IO ())

{-# LINE 626 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_fscanf" c'gsl_vector_ushort_fscanf
  :: Ptr CFile -> Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_fscanf" p'gsl_vector_ushort_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 627 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_fwrite" c'gsl_vector_ushort_fwrite
  :: Ptr CFile -> Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_fwrite" p'gsl_vector_ushort_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 628 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_get" c'gsl_vector_ushort_get
  :: Ptr C'gsl_vector_ushort -> CSize -> IO CUShort
foreign import ccall "&gsl_vector_ushort_get" p'gsl_vector_ushort_get
  :: FunPtr (Ptr C'gsl_vector_ushort -> CSize -> IO CUShort)

{-# LINE 629 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_isneg" c'gsl_vector_ushort_isneg
  :: Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_isneg" p'gsl_vector_ushort_isneg
  :: FunPtr (Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 630 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_isnonneg" c'gsl_vector_ushort_isnonneg
  :: Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_isnonneg" p'gsl_vector_ushort_isnonneg
  :: FunPtr (Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 631 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_isnull" c'gsl_vector_ushort_isnull
  :: Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_isnull" p'gsl_vector_ushort_isnull
  :: FunPtr (Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 632 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_ispos" c'gsl_vector_ushort_ispos
  :: Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_ispos" p'gsl_vector_ushort_ispos
  :: FunPtr (Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 633 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_max" c'gsl_vector_ushort_max
  :: Ptr C'gsl_vector_ushort -> IO CUShort
foreign import ccall "&gsl_vector_ushort_max" p'gsl_vector_ushort_max
  :: FunPtr (Ptr C'gsl_vector_ushort -> IO CUShort)

{-# LINE 634 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_max_index" c'gsl_vector_ushort_max_index
  :: Ptr C'gsl_vector_ushort -> IO CSize
foreign import ccall "&gsl_vector_ushort_max_index" p'gsl_vector_ushort_max_index
  :: FunPtr (Ptr C'gsl_vector_ushort -> IO CSize)

{-# LINE 635 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_memcpy" c'gsl_vector_ushort_memcpy
  :: Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_memcpy" p'gsl_vector_ushort_memcpy
  :: FunPtr (Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 636 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_min" c'gsl_vector_ushort_min
  :: Ptr C'gsl_vector_ushort -> IO CUShort
foreign import ccall "&gsl_vector_ushort_min" p'gsl_vector_ushort_min
  :: FunPtr (Ptr C'gsl_vector_ushort -> IO CUShort)

{-# LINE 637 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_min_index" c'gsl_vector_ushort_min_index
  :: Ptr C'gsl_vector_ushort -> IO CSize
foreign import ccall "&gsl_vector_ushort_min_index" p'gsl_vector_ushort_min_index
  :: FunPtr (Ptr C'gsl_vector_ushort -> IO CSize)

{-# LINE 638 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_minmax" c'gsl_vector_ushort_minmax
  :: Ptr C'gsl_vector_ushort -> Ptr CUShort -> Ptr CUShort -> IO ()
foreign import ccall "&gsl_vector_ushort_minmax" p'gsl_vector_ushort_minmax
  :: FunPtr (Ptr C'gsl_vector_ushort -> Ptr CUShort -> Ptr CUShort -> IO ())

{-# LINE 639 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_minmax_index" c'gsl_vector_ushort_minmax_index
  :: Ptr C'gsl_vector_ushort -> Ptr CSize -> Ptr CSize -> IO ()
foreign import ccall "&gsl_vector_ushort_minmax_index" p'gsl_vector_ushort_minmax_index
  :: FunPtr (Ptr C'gsl_vector_ushort -> Ptr CSize -> Ptr CSize -> IO ())

{-# LINE 640 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_mul" c'gsl_vector_ushort_mul
  :: Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_mul" p'gsl_vector_ushort_mul
  :: FunPtr (Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 641 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_ptr" c'gsl_vector_ushort_ptr
  :: Ptr C'gsl_vector_ushort -> CSize -> IO (Ptr CUShort)
foreign import ccall "&gsl_vector_ushort_ptr" p'gsl_vector_ushort_ptr
  :: FunPtr (Ptr C'gsl_vector_ushort -> CSize -> IO (Ptr CUShort))

{-# LINE 642 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_reverse" c'gsl_vector_ushort_reverse
  :: Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_reverse" p'gsl_vector_ushort_reverse
  :: FunPtr (Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 643 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_scale" c'gsl_vector_ushort_scale
  :: Ptr C'gsl_vector_ushort -> CDouble -> IO CInt
foreign import ccall "&gsl_vector_ushort_scale" p'gsl_vector_ushort_scale
  :: FunPtr (Ptr C'gsl_vector_ushort -> CDouble -> IO CInt)

{-# LINE 644 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_set" c'gsl_vector_ushort_set
  :: Ptr C'gsl_vector_ushort -> CSize -> CUShort -> IO ()
foreign import ccall "&gsl_vector_ushort_set" p'gsl_vector_ushort_set
  :: FunPtr (Ptr C'gsl_vector_ushort -> CSize -> CUShort -> IO ())

{-# LINE 645 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_set_all" c'gsl_vector_ushort_set_all
  :: Ptr C'gsl_vector_ushort -> CUShort -> IO ()
foreign import ccall "&gsl_vector_ushort_set_all" p'gsl_vector_ushort_set_all
  :: FunPtr (Ptr C'gsl_vector_ushort -> CUShort -> IO ())

{-# LINE 646 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_set_basis" c'gsl_vector_ushort_set_basis
  :: Ptr C'gsl_vector_ushort -> CSize -> IO CInt
foreign import ccall "&gsl_vector_ushort_set_basis" p'gsl_vector_ushort_set_basis
  :: FunPtr (Ptr C'gsl_vector_ushort -> CSize -> IO CInt)

{-# LINE 647 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_set_zero" c'gsl_vector_ushort_set_zero
  :: Ptr C'gsl_vector_ushort -> IO ()
foreign import ccall "&gsl_vector_ushort_set_zero" p'gsl_vector_ushort_set_zero
  :: FunPtr (Ptr C'gsl_vector_ushort -> IO ())

{-# LINE 648 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_sub" c'gsl_vector_ushort_sub
  :: Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_sub" p'gsl_vector_ushort_sub
  :: FunPtr (Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 649 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_ushort_subvector , Ptr <gsl_vector_ushort> -> CSize -> CSize -> IO <gsl_vector_ushort_view>
-- ccall gsl_vector_ushort_subvector_with_stride , Ptr <gsl_vector_ushort> -> CSize -> CSize -> CSize -> IO <gsl_vector_ushort_view>
foreign import ccall "gsl_vector_ushort_swap" c'gsl_vector_ushort_swap
  :: Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_vector_ushort_swap" p'gsl_vector_ushort_swap
  :: FunPtr (Ptr C'gsl_vector_ushort -> Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 652 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
foreign import ccall "gsl_vector_ushort_swap_elements" c'gsl_vector_ushort_swap_elements
  :: Ptr C'gsl_vector_ushort -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_vector_ushort_swap_elements" p'gsl_vector_ushort_swap_elements
  :: FunPtr (Ptr C'gsl_vector_ushort -> CSize -> CSize -> IO CInt)

{-# LINE 653 "src/Bindings/Gsl/VectorsAndMatrices/Vectors.hsc" #-}
-- ccall gsl_vector_ushort_view_array , Ptr CUShort -> CSize -> IO <gsl_vector_ushort_view>
-- ccall gsl_vector_ushort_view_array_with_stride , Ptr CUShort -> CSize -> CSize -> IO <gsl_vector_ushort_view>
-- ccall gsl_vector_view_array , Ptr CDouble -> CSize -> IO <gsl_vector_view>
-- ccall gsl_vector_view_array_with_stride , Ptr CDouble -> CSize -> CSize -> IO <gsl_vector_view>