#include #include -- | module Bindings.Gsl.VectorsAndMatrices.Blocks where #strict_import import Bindings.Gsl.VectorsAndMatrices.DataTypes #ccall gsl_block_alloc , CSize -> IO (Ptr ) #ccall gsl_block_calloc , CSize -> IO (Ptr ) #ccall gsl_block_char_alloc , CSize -> IO (Ptr ) #ccall gsl_block_char_calloc , CSize -> IO (Ptr ) #ccall gsl_block_char_data , Ptr -> IO CString #ccall gsl_block_char_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_char_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_char_free , Ptr -> IO () #ccall gsl_block_char_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_char_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_char_raw_fprintf , Ptr CFile -> CString -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_char_raw_fread , Ptr CFile -> CString -> CSize -> CSize -> IO CInt #ccall gsl_block_char_raw_fscanf , Ptr CFile -> CString -> CSize -> CSize -> IO CInt #ccall gsl_block_char_raw_fwrite , Ptr CFile -> CString -> CSize -> CSize -> IO CInt #ccall gsl_block_char_size , Ptr -> IO CSize #ccall gsl_block_complex_alloc , CSize -> IO (Ptr ) #ccall gsl_block_complex_calloc , CSize -> IO (Ptr ) #ccall gsl_block_complex_data , Ptr -> IO (Ptr CDouble) #ccall gsl_block_complex_float_alloc , CSize -> IO (Ptr ) #ccall gsl_block_complex_float_calloc , CSize -> IO (Ptr ) #ccall gsl_block_complex_float_data , Ptr -> IO (Ptr CFloat) #ccall gsl_block_complex_float_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_complex_float_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_complex_float_free , Ptr -> IO () #ccall gsl_block_complex_float_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_complex_float_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_complex_float_raw_fprintf , Ptr CFile -> Ptr CFloat -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_complex_float_raw_fread , Ptr CFile -> Ptr CFloat -> CSize -> CSize -> IO CInt #ccall gsl_block_complex_float_raw_fscanf , Ptr CFile -> Ptr CFloat -> CSize -> CSize -> IO CInt #ccall gsl_block_complex_float_raw_fwrite , Ptr CFile -> Ptr CFloat -> CSize -> CSize -> IO CInt #ccall gsl_block_complex_float_size , Ptr -> IO CSize #ccall gsl_block_complex_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_complex_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_complex_free , Ptr -> IO () #ccall gsl_block_complex_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_complex_fwrite , Ptr CFile -> Ptr -> IO CInt -- #ccall gsl_block_complex_long_double_alloc , CSize -> IO (Ptr ) -- #ccall gsl_block_complex_long_double_calloc , CSize -> IO (Ptr ) -- #ccall gsl_block_complex_long_double_data , Ptr -> IO (Ptr CLDouble) -- #ccall gsl_block_complex_long_double_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt -- #ccall gsl_block_complex_long_double_fread , Ptr CFile -> Ptr -> IO CInt -- #ccall gsl_block_complex_long_double_free , Ptr -> IO () -- #ccall gsl_block_complex_long_double_fscanf , Ptr CFile -> Ptr -> IO CInt -- #ccall gsl_block_complex_long_double_fwrite , Ptr CFile -> Ptr -> IO CInt -- #ccall gsl_block_complex_long_double_raw_fprintf , Ptr CFile -> Ptr CLDouble -> CSize -> CSize -> CString -> IO CInt -- #ccall gsl_block_complex_long_double_raw_fread , Ptr CFile -> Ptr CLDouble -> CSize -> CSize -> IO CInt -- #ccall gsl_block_complex_long_double_raw_fscanf , Ptr CFile -> Ptr CLDouble -> CSize -> CSize -> IO CInt -- #ccall gsl_block_complex_long_double_raw_fwrite , Ptr CFile -> Ptr CLDouble -> CSize -> CSize -> IO CInt -- #ccall gsl_block_complex_long_double_size , Ptr -> IO CSize #ccall gsl_block_complex_raw_fprintf , Ptr CFile -> Ptr CDouble -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_complex_raw_fread , Ptr CFile -> Ptr CDouble -> CSize -> CSize -> IO CInt #ccall gsl_block_complex_raw_fscanf , Ptr CFile -> Ptr CDouble -> CSize -> CSize -> IO CInt #ccall gsl_block_complex_raw_fwrite , Ptr CFile -> Ptr CDouble -> CSize -> CSize -> IO CInt #ccall gsl_block_complex_size , Ptr -> IO CSize #ccall gsl_block_data , Ptr -> IO (Ptr CDouble) #ccall gsl_block_float_alloc , CSize -> IO (Ptr ) #ccall gsl_block_float_calloc , CSize -> IO (Ptr ) #ccall gsl_block_float_data , Ptr -> IO (Ptr CFloat) #ccall gsl_block_float_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_float_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_float_free , Ptr -> IO () #ccall gsl_block_float_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_float_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_float_raw_fprintf , Ptr CFile -> Ptr CFloat -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_float_raw_fread , Ptr CFile -> Ptr CFloat -> CSize -> CSize -> IO CInt #ccall gsl_block_float_raw_fscanf , Ptr CFile -> Ptr CFloat -> CSize -> CSize -> IO CInt #ccall gsl_block_float_raw_fwrite , Ptr CFile -> Ptr CFloat -> CSize -> CSize -> IO CInt #ccall gsl_block_float_size , Ptr -> IO CSize #ccall gsl_block_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_free , Ptr -> IO () #ccall gsl_block_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_int_alloc , CSize -> IO (Ptr ) #ccall gsl_block_int_calloc , CSize -> IO (Ptr ) #ccall gsl_block_int_data , Ptr -> IO (Ptr CInt) #ccall gsl_block_int_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_int_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_int_free , Ptr -> IO () #ccall gsl_block_int_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_int_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_int_raw_fprintf , Ptr CFile -> Ptr CInt -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_int_raw_fread , Ptr CFile -> Ptr CInt -> CSize -> CSize -> IO CInt #ccall gsl_block_int_raw_fscanf , Ptr CFile -> Ptr CInt -> CSize -> CSize -> IO CInt #ccall gsl_block_int_raw_fwrite , Ptr CFile -> Ptr CInt -> CSize -> CSize -> IO CInt #ccall gsl_block_int_size , Ptr -> IO CSize #ccall gsl_block_long_alloc , CSize -> IO (Ptr ) #ccall gsl_block_long_calloc , CSize -> IO (Ptr ) #ccall gsl_block_long_data , Ptr -> IO (Ptr CLong) -- #ccall gsl_block_long_double_alloc , CSize -> IO (Ptr ) -- #ccall gsl_block_long_double_calloc , CSize -> IO (Ptr ) -- #ccall gsl_block_long_double_data , Ptr -> IO (Ptr CLDouble) -- #ccall gsl_block_long_double_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt -- #ccall gsl_block_long_double_fread , Ptr CFile -> Ptr -> IO CInt -- #ccall gsl_block_long_double_free , Ptr -> IO () -- #ccall gsl_block_long_double_fscanf , Ptr CFile -> Ptr -> IO CInt -- #ccall gsl_block_long_double_fwrite , Ptr CFile -> Ptr -> IO CInt -- #ccall gsl_block_long_double_raw_fprintf , Ptr CFile -> Ptr CLDouble -> CSize -> CSize -> CString -> IO CInt -- #ccall gsl_block_long_double_raw_fread , Ptr CFile -> Ptr CLDouble -> CSize -> CSize -> IO CInt -- #ccall gsl_block_long_double_raw_fscanf , Ptr CFile -> Ptr CLDouble -> CSize -> CSize -> IO CInt -- #ccall gsl_block_long_double_raw_fwrite , Ptr CFile -> Ptr CLDouble -> CSize -> CSize -> IO CInt -- #ccall gsl_block_long_double_size , Ptr -> IO CSize #ccall gsl_block_long_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_long_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_long_free , Ptr -> IO () #ccall gsl_block_long_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_long_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_long_raw_fprintf , Ptr CFile -> Ptr CLong -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_long_raw_fread , Ptr CFile -> Ptr CLong -> CSize -> CSize -> IO CInt #ccall gsl_block_long_raw_fscanf , Ptr CFile -> Ptr CLong -> CSize -> CSize -> IO CInt #ccall gsl_block_long_raw_fwrite , Ptr CFile -> Ptr CLong -> CSize -> CSize -> IO CInt #ccall gsl_block_long_size , Ptr -> IO CSize #ccall gsl_block_raw_fprintf , Ptr CFile -> Ptr CDouble -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_raw_fread , Ptr CFile -> Ptr CDouble -> CSize -> CSize -> IO CInt #ccall gsl_block_raw_fscanf , Ptr CFile -> Ptr CDouble -> CSize -> CSize -> IO CInt #ccall gsl_block_raw_fwrite , Ptr CFile -> Ptr CDouble -> CSize -> CSize -> IO CInt #ccall gsl_block_short_alloc , CSize -> IO (Ptr ) #ccall gsl_block_short_calloc , CSize -> IO (Ptr ) #ccall gsl_block_short_data , Ptr -> IO (Ptr CShort) #ccall gsl_block_short_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_short_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_short_free , Ptr -> IO () #ccall gsl_block_short_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_short_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_short_raw_fprintf , Ptr CFile -> Ptr CShort -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_short_raw_fread , Ptr CFile -> Ptr CShort -> CSize -> CSize -> IO CInt #ccall gsl_block_short_raw_fscanf , Ptr CFile -> Ptr CShort -> CSize -> CSize -> IO CInt #ccall gsl_block_short_raw_fwrite , Ptr CFile -> Ptr CShort -> CSize -> CSize -> IO CInt #ccall gsl_block_short_size , Ptr -> IO CSize #ccall gsl_block_size , Ptr -> IO CSize #ccall gsl_block_uchar_alloc , CSize -> IO (Ptr ) #ccall gsl_block_uchar_calloc , CSize -> IO (Ptr ) #ccall gsl_block_uchar_data , Ptr -> IO (Ptr CUChar) #ccall gsl_block_uchar_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_uchar_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_uchar_free , Ptr -> IO () #ccall gsl_block_uchar_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_uchar_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_uchar_raw_fprintf , Ptr CFile -> Ptr CUChar -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_uchar_raw_fread , Ptr CFile -> Ptr CUChar -> CSize -> CSize -> IO CInt #ccall gsl_block_uchar_raw_fscanf , Ptr CFile -> Ptr CUChar -> CSize -> CSize -> IO CInt #ccall gsl_block_uchar_raw_fwrite , Ptr CFile -> Ptr CUChar -> CSize -> CSize -> IO CInt #ccall gsl_block_uchar_size , Ptr -> IO CSize #ccall gsl_block_uint_alloc , CSize -> IO (Ptr ) #ccall gsl_block_uint_calloc , CSize -> IO (Ptr ) #ccall gsl_block_uint_data , Ptr -> IO (Ptr CUInt) #ccall gsl_block_uint_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_uint_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_uint_free , Ptr -> IO () #ccall gsl_block_uint_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_uint_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_uint_raw_fprintf , Ptr CFile -> Ptr CUInt -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_uint_raw_fread , Ptr CFile -> Ptr CUInt -> CSize -> CSize -> IO CInt #ccall gsl_block_uint_raw_fscanf , Ptr CFile -> Ptr CUInt -> CSize -> CSize -> IO CInt #ccall gsl_block_uint_raw_fwrite , Ptr CFile -> Ptr CUInt -> CSize -> CSize -> IO CInt #ccall gsl_block_uint_size , Ptr -> IO CSize #ccall gsl_block_ulong_alloc , CSize -> IO (Ptr ) #ccall gsl_block_ulong_calloc , CSize -> IO (Ptr ) #ccall gsl_block_ulong_data , Ptr -> IO (Ptr CULong) #ccall gsl_block_ulong_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_ulong_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_ulong_free , Ptr -> IO () #ccall gsl_block_ulong_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_ulong_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_ulong_raw_fprintf , Ptr CFile -> Ptr CULong -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_ulong_raw_fread , Ptr CFile -> Ptr CULong -> CSize -> CSize -> IO CInt #ccall gsl_block_ulong_raw_fscanf , Ptr CFile -> Ptr CULong -> CSize -> CSize -> IO CInt #ccall gsl_block_ulong_raw_fwrite , Ptr CFile -> Ptr CULong -> CSize -> CSize -> IO CInt #ccall gsl_block_ulong_size , Ptr -> IO CSize #ccall gsl_block_ushort_alloc , CSize -> IO (Ptr ) #ccall gsl_block_ushort_calloc , CSize -> IO (Ptr ) #ccall gsl_block_ushort_data , Ptr -> IO (Ptr CUShort) #ccall gsl_block_ushort_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_block_ushort_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_ushort_free , Ptr -> IO () #ccall gsl_block_ushort_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_ushort_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_block_ushort_raw_fprintf , Ptr CFile -> Ptr CUShort -> CSize -> CSize -> CString -> IO CInt #ccall gsl_block_ushort_raw_fread , Ptr CFile -> Ptr CUShort -> CSize -> CSize -> IO CInt #ccall gsl_block_ushort_raw_fscanf , Ptr CFile -> Ptr CUShort -> CSize -> CSize -> IO CInt #ccall gsl_block_ushort_raw_fwrite , Ptr CFile -> Ptr CUShort -> CSize -> CSize -> IO CInt #ccall gsl_block_ushort_size , Ptr -> IO CSize