#include #include -- | module Bindings.Gsl.VectorsAndMatrices.Matrices where #strict_import import Bindings.Gsl.VectorsAndMatrices.DataTypes import Bindings.Gsl.ComplexNumbers #ccall gsl_matrix_add , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_add_constant , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_add_diagonal , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_calloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_char_add , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_char_add_constant , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_char_add_diagonal , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_char_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_char_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_char_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_char_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_char_column , Ptr -> CSize -> IO -- ccall gsl_matrix_char_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_char_const_diagonal , Ptr -> IO -- ccall gsl_matrix_char_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_char_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_char_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_char_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_char_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_char_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_char_const_view_array , CString -> CSize -> CSize -> IO -- ccall gsl_matrix_char_const_view_array_with_tda , CString -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_char_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_char_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_char_diagonal , Ptr -> IO #ccall gsl_matrix_char_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_char_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_char_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_char_free , Ptr -> IO () #ccall gsl_matrix_char_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_char_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_char_isneg , Ptr -> IO CInt #ccall gsl_matrix_char_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_char_isnull , Ptr -> IO CInt #ccall gsl_matrix_char_ispos , Ptr -> IO CInt #ccall gsl_matrix_char_max , Ptr -> IO CChar #ccall gsl_matrix_char_max_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_char_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_char_min , Ptr -> IO CChar #ccall gsl_matrix_char_min_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_char_minmax , Ptr -> CString -> CString -> IO () #ccall gsl_matrix_char_minmax_index , Ptr -> Ptr CSize -> Ptr CSize -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_char_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_char_row , Ptr -> CSize -> IO #ccall gsl_matrix_char_scale , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_char_set_all , Ptr -> CChar -> IO () #ccall gsl_matrix_char_set_identity , Ptr -> IO () #ccall gsl_matrix_char_set_zero , Ptr -> IO () #ccall gsl_matrix_char_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_char_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_char_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_char_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_char_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_char_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_char_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_char_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_char_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_char_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_char_transpose , Ptr -> IO CInt #ccall gsl_matrix_char_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_char_view_array , CString -> CSize -> CSize -> IO -- ccall gsl_matrix_char_view_array_with_tda , CString -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_char_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_char_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_column , Ptr -> CSize -> IO #ccall gsl_matrix_complex_add , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_add_constant , Ptr -> -> IO CInt -- ccall gsl_matrix_complex_add_diagonal , Ptr -> -> IO CInt #ccall gsl_matrix_complex_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_complex_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_complex_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_complex_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_complex_column , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_const_diagonal , Ptr -> IO -- ccall gsl_matrix_complex_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_const_view_array , Ptr CDouble -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_const_view_array_with_tda , Ptr CDouble -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_diagonal , Ptr -> IO #ccall gsl_matrix_complex_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_complex_float_add , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_float_add_constant , Ptr -> -> IO CInt -- ccall gsl_matrix_complex_float_add_diagonal , Ptr -> -> IO CInt #ccall gsl_matrix_complex_float_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_complex_float_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_complex_float_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_complex_float_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_complex_float_column , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_float_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_float_const_diagonal , Ptr -> IO -- ccall gsl_matrix_complex_float_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_float_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_float_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_float_const_view_array , Ptr CFloat -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_const_view_array_with_tda , Ptr CFloat -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_diagonal , Ptr -> IO #ccall gsl_matrix_complex_float_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_complex_float_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_complex_float_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_complex_float_free , Ptr -> IO () #ccall gsl_matrix_complex_float_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_complex_float_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_complex_float_isneg , Ptr -> IO CInt #ccall gsl_matrix_complex_float_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_complex_float_isnull , Ptr -> IO CInt #ccall gsl_matrix_complex_float_ispos , Ptr -> IO CInt #ccall gsl_matrix_complex_float_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_complex_float_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_float_row , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_float_scale , Ptr -> -> IO CInt -- ccall gsl_matrix_complex_float_set_all , Ptr -> -> IO () #ccall gsl_matrix_complex_float_set_identity , Ptr -> IO () #ccall gsl_matrix_complex_float_set_zero , Ptr -> IO () #ccall gsl_matrix_complex_float_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_float_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_float_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_complex_float_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_complex_float_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_complex_float_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_complex_float_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_complex_float_transpose , Ptr -> IO CInt #ccall gsl_matrix_complex_float_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_float_view_array , Ptr CFloat -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_view_array_with_tda , Ptr CFloat -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_float_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO #ccall gsl_matrix_complex_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_complex_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_complex_free , Ptr -> IO () #ccall gsl_matrix_complex_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_complex_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_complex_isneg , Ptr -> IO CInt #ccall gsl_matrix_complex_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_complex_isnull , Ptr -> IO CInt #ccall gsl_matrix_complex_ispos , Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_add , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_long_double_add_constant , Ptr -> -> IO CInt -- ccall gsl_matrix_complex_long_double_add_diagonal , Ptr -> -> IO CInt #ccall gsl_matrix_complex_long_double_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_complex_long_double_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_complex_long_double_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_complex_long_double_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_complex_long_double_column , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_long_double_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_long_double_const_diagonal , Ptr -> IO -- ccall gsl_matrix_complex_long_double_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_long_double_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_long_double_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_long_double_const_view_array , Ptr CLDouble -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_const_view_array_with_tda , Ptr CLDouble -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_diagonal , Ptr -> IO #ccall gsl_matrix_complex_long_double_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_complex_long_double_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_free , Ptr -> IO () #ccall gsl_matrix_complex_long_double_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_isneg , Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_isnull , Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_ispos , Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_long_double_row , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_long_double_scale , Ptr -> -> IO CInt -- ccall gsl_matrix_complex_long_double_set_all , Ptr -> -> IO () #ccall gsl_matrix_complex_long_double_set_identity , Ptr -> IO () #ccall gsl_matrix_complex_long_double_set_zero , Ptr -> IO () #ccall gsl_matrix_complex_long_double_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_long_double_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_long_double_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_complex_long_double_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_complex_long_double_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_complex_long_double_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_complex_long_double_transpose , Ptr -> IO CInt #ccall gsl_matrix_complex_long_double_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_long_double_view_array , Ptr CLDouble -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_view_array_with_tda , Ptr CLDouble -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_long_double_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO #ccall gsl_matrix_complex_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_complex_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_row , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_scale , Ptr -> -> IO CInt -- ccall gsl_matrix_complex_set_all , Ptr -> -> IO () #ccall gsl_matrix_complex_set_identity , Ptr -> IO () #ccall gsl_matrix_complex_set_zero , Ptr -> IO () #ccall gsl_matrix_complex_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_complex_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_complex_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_complex_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_complex_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_complex_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_complex_transpose , Ptr -> IO CInt #ccall gsl_matrix_complex_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_complex_view_array , Ptr CDouble -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_view_array_with_tda , Ptr CDouble -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_complex_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_const_diagonal , Ptr -> IO -- ccall gsl_matrix_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_const_view_array , Ptr CDouble -> CSize -> CSize -> IO -- ccall gsl_matrix_const_view_array_with_tda , Ptr CDouble -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_diagonal , Ptr -> IO #ccall gsl_matrix_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_float_add , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_float_add_constant , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_float_add_diagonal , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_float_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_float_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_float_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_float_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_float_column , Ptr -> CSize -> IO -- ccall gsl_matrix_float_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_float_const_diagonal , Ptr -> IO -- ccall gsl_matrix_float_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_float_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_float_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_float_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_float_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_float_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_float_const_view_array , Ptr CFloat -> CSize -> CSize -> IO -- ccall gsl_matrix_float_const_view_array_with_tda , Ptr CFloat -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_float_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_float_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_float_diagonal , Ptr -> IO #ccall gsl_matrix_float_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_float_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_float_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_float_free , Ptr -> IO () #ccall gsl_matrix_float_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_float_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_float_isneg , Ptr -> IO CInt #ccall gsl_matrix_float_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_float_isnull , Ptr -> IO CInt #ccall gsl_matrix_float_ispos , Ptr -> IO CInt #ccall gsl_matrix_float_max , Ptr -> IO CFloat #ccall gsl_matrix_float_max_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_float_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_float_min , Ptr -> IO CFloat #ccall gsl_matrix_float_min_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_float_minmax , Ptr -> Ptr CFloat -> Ptr CFloat -> IO () #ccall gsl_matrix_float_minmax_index , Ptr -> Ptr CSize -> Ptr CSize -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_float_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_float_row , Ptr -> CSize -> IO #ccall gsl_matrix_float_scale , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_float_set_all , Ptr -> CFloat -> IO () #ccall gsl_matrix_float_set_identity , Ptr -> IO () #ccall gsl_matrix_float_set_zero , Ptr -> IO () #ccall gsl_matrix_float_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_float_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_float_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_float_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_float_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_float_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_float_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_float_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_float_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_float_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_float_transpose , Ptr -> IO CInt #ccall gsl_matrix_float_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_float_view_array , Ptr CFloat -> CSize -> CSize -> IO -- ccall gsl_matrix_float_view_array_with_tda , Ptr CFloat -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_float_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_float_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO #ccall gsl_matrix_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_free , Ptr -> IO () #ccall gsl_matrix_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_int_add , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_int_add_constant , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_int_add_diagonal , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_int_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_int_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_int_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_int_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_int_column , Ptr -> CSize -> IO -- ccall gsl_matrix_int_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_int_const_diagonal , Ptr -> IO -- ccall gsl_matrix_int_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_int_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_int_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_int_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_int_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_int_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_int_const_view_array , Ptr CInt -> CSize -> CSize -> IO -- ccall gsl_matrix_int_const_view_array_with_tda , Ptr CInt -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_int_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_int_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_int_diagonal , Ptr -> IO #ccall gsl_matrix_int_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_int_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_int_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_int_free , Ptr -> IO () #ccall gsl_matrix_int_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_int_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_int_isneg , Ptr -> IO CInt #ccall gsl_matrix_int_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_int_isnull , Ptr -> IO CInt #ccall gsl_matrix_int_ispos , Ptr -> IO CInt #ccall gsl_matrix_int_max , Ptr -> IO CInt #ccall gsl_matrix_int_max_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_int_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_int_min , Ptr -> IO CInt #ccall gsl_matrix_int_min_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_int_minmax , Ptr -> Ptr CInt -> Ptr CInt -> IO () #ccall gsl_matrix_int_minmax_index , Ptr -> Ptr CSize -> Ptr CSize -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_int_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_int_row , Ptr -> CSize -> IO #ccall gsl_matrix_int_scale , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_int_set_all , Ptr -> CInt -> IO () #ccall gsl_matrix_int_set_identity , Ptr -> IO () #ccall gsl_matrix_int_set_zero , Ptr -> IO () #ccall gsl_matrix_int_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_int_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_int_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_int_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_int_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_int_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_int_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_int_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_int_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_int_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_int_transpose , Ptr -> IO CInt #ccall gsl_matrix_int_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_int_view_array , Ptr CInt -> CSize -> CSize -> IO -- ccall gsl_matrix_int_view_array_with_tda , Ptr CInt -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_int_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_int_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO #ccall gsl_matrix_isneg , Ptr -> IO CInt #ccall gsl_matrix_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_isnull , Ptr -> IO CInt #ccall gsl_matrix_ispos , Ptr -> IO CInt #ccall gsl_matrix_long_add , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_long_add_constant , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_long_add_diagonal , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_long_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_long_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_long_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_long_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_long_column , Ptr -> CSize -> IO -- ccall gsl_matrix_long_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_long_const_diagonal , Ptr -> IO -- ccall gsl_matrix_long_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_long_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_long_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_long_const_view_array , Ptr CLong -> CSize -> CSize -> IO -- ccall gsl_matrix_long_const_view_array_with_tda , Ptr CLong -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_long_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_diagonal , Ptr -> IO #ccall gsl_matrix_long_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_long_double_add , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_long_double_add_constant , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_long_double_add_diagonal , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_long_double_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_long_double_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_long_double_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_long_double_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_long_double_column , Ptr -> CSize -> IO -- ccall gsl_matrix_long_double_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_long_double_const_diagonal , Ptr -> IO -- ccall gsl_matrix_long_double_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_long_double_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_long_double_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_long_double_const_view_array , Ptr CLDouble -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_const_view_array_with_tda , Ptr CLDouble -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_diagonal , Ptr -> IO #ccall gsl_matrix_long_double_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_long_double_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_long_double_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_long_double_free , Ptr -> IO () #ccall gsl_matrix_long_double_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_long_double_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_long_double_isneg , Ptr -> IO CInt #ccall gsl_matrix_long_double_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_long_double_isnull , Ptr -> IO CInt #ccall gsl_matrix_long_double_ispos , Ptr -> IO CInt #ccall gsl_matrix_long_double_max , Ptr -> IO CLDouble #ccall gsl_matrix_long_double_max_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_long_double_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_long_double_min , Ptr -> IO CLDouble #ccall gsl_matrix_long_double_min_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_long_double_minmax , Ptr -> Ptr CLDouble -> Ptr CLDouble -> IO () #ccall gsl_matrix_long_double_minmax_index , Ptr -> Ptr CSize -> Ptr CSize -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_long_double_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_long_double_row , Ptr -> CSize -> IO #ccall gsl_matrix_long_double_scale , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_long_double_set_all , Ptr -> CLDouble -> IO () #ccall gsl_matrix_long_double_set_identity , Ptr -> IO () #ccall gsl_matrix_long_double_set_zero , Ptr -> IO () #ccall gsl_matrix_long_double_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_long_double_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_long_double_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_long_double_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_long_double_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_long_double_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_long_double_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_long_double_transpose , Ptr -> IO CInt #ccall gsl_matrix_long_double_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_long_double_view_array , Ptr CLDouble -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_view_array_with_tda , Ptr CLDouble -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_long_double_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO #ccall gsl_matrix_long_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_long_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_long_free , Ptr -> IO () #ccall gsl_matrix_long_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_long_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_long_isneg , Ptr -> IO CInt #ccall gsl_matrix_long_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_long_isnull , Ptr -> IO CInt #ccall gsl_matrix_long_ispos , Ptr -> IO CInt #ccall gsl_matrix_long_max , Ptr -> IO CLong #ccall gsl_matrix_long_max_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_long_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_long_min , Ptr -> IO CLong #ccall gsl_matrix_long_min_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_long_minmax , Ptr -> Ptr CLong -> Ptr CLong -> IO () #ccall gsl_matrix_long_minmax_index , Ptr -> Ptr CSize -> Ptr CSize -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_long_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_long_row , Ptr -> CSize -> IO #ccall gsl_matrix_long_scale , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_long_set_all , Ptr -> CLong -> IO () #ccall gsl_matrix_long_set_identity , Ptr -> IO () #ccall gsl_matrix_long_set_zero , Ptr -> IO () #ccall gsl_matrix_long_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_long_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_long_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_long_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_long_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_long_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_long_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_long_transpose , Ptr -> IO CInt #ccall gsl_matrix_long_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_long_view_array , Ptr CLong -> CSize -> CSize -> IO -- ccall gsl_matrix_long_view_array_with_tda , Ptr CLong -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_long_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_long_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO #ccall gsl_matrix_max , Ptr -> IO CDouble #ccall gsl_matrix_max_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_min , Ptr -> IO CDouble #ccall gsl_matrix_min_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_minmax , Ptr -> Ptr CDouble -> Ptr CDouble -> IO () #ccall gsl_matrix_minmax_index , Ptr -> Ptr CSize -> Ptr CSize -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_row , Ptr -> CSize -> IO #ccall gsl_matrix_scale , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_set_all , Ptr -> CDouble -> IO () #ccall gsl_matrix_set_identity , Ptr -> IO () #ccall gsl_matrix_set_zero , Ptr -> IO () #ccall gsl_matrix_short_add , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_short_add_constant , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_short_add_diagonal , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_short_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_short_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_short_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_short_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_short_column , Ptr -> CSize -> IO -- ccall gsl_matrix_short_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_short_const_diagonal , Ptr -> IO -- ccall gsl_matrix_short_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_short_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_short_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_short_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_short_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_short_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_short_const_view_array , Ptr CShort -> CSize -> CSize -> IO -- ccall gsl_matrix_short_const_view_array_with_tda , Ptr CShort -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_short_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_short_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_short_diagonal , Ptr -> IO #ccall gsl_matrix_short_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_short_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_short_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_short_free , Ptr -> IO () #ccall gsl_matrix_short_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_short_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_short_isneg , Ptr -> IO CInt #ccall gsl_matrix_short_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_short_isnull , Ptr -> IO CInt #ccall gsl_matrix_short_ispos , Ptr -> IO CInt #ccall gsl_matrix_short_max , Ptr -> IO CShort #ccall gsl_matrix_short_max_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_short_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_short_min , Ptr -> IO CShort #ccall gsl_matrix_short_min_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_short_minmax , Ptr -> Ptr CShort -> Ptr CShort -> IO () #ccall gsl_matrix_short_minmax_index , Ptr -> Ptr CSize -> Ptr CSize -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_short_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_short_row , Ptr -> CSize -> IO #ccall gsl_matrix_short_scale , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_short_set_all , Ptr -> CShort -> IO () #ccall gsl_matrix_short_set_identity , Ptr -> IO () #ccall gsl_matrix_short_set_zero , Ptr -> IO () #ccall gsl_matrix_short_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_short_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_short_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_short_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_short_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_short_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_short_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_short_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_short_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_short_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_short_transpose , Ptr -> IO CInt #ccall gsl_matrix_short_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_short_view_array , Ptr CShort -> CSize -> CSize -> IO -- ccall gsl_matrix_short_view_array_with_tda , Ptr CShort -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_short_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_short_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO #ccall gsl_matrix_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_transpose , Ptr -> IO CInt #ccall gsl_matrix_transpose_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_uchar_add , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_uchar_add_constant , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_uchar_add_diagonal , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_uchar_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_uchar_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_uchar_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_uchar_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_uchar_column , Ptr -> CSize -> IO -- ccall gsl_matrix_uchar_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_uchar_const_diagonal , Ptr -> IO -- ccall gsl_matrix_uchar_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_uchar_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_uchar_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_uchar_const_view_array , Ptr CUChar -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_const_view_array_with_tda , Ptr CUChar -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_diagonal , Ptr -> IO #ccall gsl_matrix_uchar_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_uchar_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_uchar_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_uchar_free , Ptr -> IO () #ccall gsl_matrix_uchar_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_uchar_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_uchar_isneg , Ptr -> IO CInt #ccall gsl_matrix_uchar_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_uchar_isnull , Ptr -> IO CInt #ccall gsl_matrix_uchar_ispos , Ptr -> IO CInt #ccall gsl_matrix_uchar_max , Ptr -> IO CUChar #ccall gsl_matrix_uchar_max_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_uchar_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_uchar_min , Ptr -> IO CUChar #ccall gsl_matrix_uchar_min_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_uchar_minmax , Ptr -> Ptr CUChar -> Ptr CUChar -> IO () #ccall gsl_matrix_uchar_minmax_index , Ptr -> Ptr CSize -> Ptr CSize -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_uchar_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_uchar_row , Ptr -> CSize -> IO #ccall gsl_matrix_uchar_scale , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_uchar_set_all , Ptr -> CUChar -> IO () #ccall gsl_matrix_uchar_set_identity , Ptr -> IO () #ccall gsl_matrix_uchar_set_zero , Ptr -> IO () #ccall gsl_matrix_uchar_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_uchar_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_uchar_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_uchar_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_uchar_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_uchar_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_uchar_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_uchar_transpose , Ptr -> IO CInt #ccall gsl_matrix_uchar_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_uchar_view_array , Ptr CUChar -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_view_array_with_tda , Ptr CUChar -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_uchar_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO #ccall gsl_matrix_uint_add , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_uint_add_constant , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_uint_add_diagonal , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_uint_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_uint_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_uint_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_uint_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_uint_column , Ptr -> CSize -> IO -- ccall gsl_matrix_uint_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_uint_const_diagonal , Ptr -> IO -- ccall gsl_matrix_uint_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_uint_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_uint_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_uint_const_view_array , Ptr CUInt -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_const_view_array_with_tda , Ptr CUInt -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_diagonal , Ptr -> IO #ccall gsl_matrix_uint_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_uint_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_uint_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_uint_free , Ptr -> IO () #ccall gsl_matrix_uint_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_uint_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_uint_isneg , Ptr -> IO CInt #ccall gsl_matrix_uint_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_uint_isnull , Ptr -> IO CInt #ccall gsl_matrix_uint_ispos , Ptr -> IO CInt #ccall gsl_matrix_uint_max , Ptr -> IO CUInt #ccall gsl_matrix_uint_max_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_uint_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_uint_min , Ptr -> IO CUInt #ccall gsl_matrix_uint_min_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_uint_minmax , Ptr -> Ptr CUInt -> Ptr CUInt -> IO () #ccall gsl_matrix_uint_minmax_index , Ptr -> Ptr CSize -> Ptr CSize -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_uint_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_uint_row , Ptr -> CSize -> IO #ccall gsl_matrix_uint_scale , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_uint_set_all , Ptr -> CUInt -> IO () #ccall gsl_matrix_uint_set_identity , Ptr -> IO () #ccall gsl_matrix_uint_set_zero , Ptr -> IO () #ccall gsl_matrix_uint_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_uint_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_uint_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_uint_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_uint_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_uint_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_uint_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_uint_transpose , Ptr -> IO CInt #ccall gsl_matrix_uint_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_uint_view_array , Ptr CUInt -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_view_array_with_tda , Ptr CUInt -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_uint_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO #ccall gsl_matrix_ulong_add , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_ulong_add_constant , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_ulong_add_diagonal , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_ulong_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_ulong_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_ulong_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_ulong_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_ulong_column , Ptr -> CSize -> IO -- ccall gsl_matrix_ulong_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_ulong_const_diagonal , Ptr -> IO -- ccall gsl_matrix_ulong_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_ulong_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_ulong_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_ulong_const_view_array , Ptr CULong -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_const_view_array_with_tda , Ptr CULong -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_diagonal , Ptr -> IO #ccall gsl_matrix_ulong_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_ulong_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_ulong_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_ulong_free , Ptr -> IO () #ccall gsl_matrix_ulong_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_ulong_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_ulong_isneg , Ptr -> IO CInt #ccall gsl_matrix_ulong_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_ulong_isnull , Ptr -> IO CInt #ccall gsl_matrix_ulong_ispos , Ptr -> IO CInt #ccall gsl_matrix_ulong_max , Ptr -> IO CULong #ccall gsl_matrix_ulong_max_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_ulong_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_ulong_min , Ptr -> IO CULong #ccall gsl_matrix_ulong_min_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_ulong_minmax , Ptr -> Ptr CULong -> Ptr CULong -> IO () #ccall gsl_matrix_ulong_minmax_index , Ptr -> Ptr CSize -> Ptr CSize -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_ulong_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_ulong_row , Ptr -> CSize -> IO #ccall gsl_matrix_ulong_scale , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_ulong_set_all , Ptr -> CULong -> IO () #ccall gsl_matrix_ulong_set_identity , Ptr -> IO () #ccall gsl_matrix_ulong_set_zero , Ptr -> IO () #ccall gsl_matrix_ulong_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_ulong_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_ulong_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_ulong_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_ulong_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_ulong_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_ulong_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_ulong_transpose , Ptr -> IO CInt #ccall gsl_matrix_ulong_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_ulong_view_array , Ptr CULong -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_view_array_with_tda , Ptr CULong -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_ulong_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO #ccall gsl_matrix_ushort_add , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_ushort_add_constant , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_ushort_add_diagonal , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_ushort_alloc , CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_ushort_alloc_from_block , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_ushort_alloc_from_matrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO (Ptr ) #ccall gsl_matrix_ushort_calloc , CSize -> CSize -> IO (Ptr ) -- ccall gsl_matrix_ushort_column , Ptr -> CSize -> IO -- ccall gsl_matrix_ushort_const_column , Ptr -> CSize -> IO -- ccall gsl_matrix_ushort_const_diagonal , Ptr -> IO -- ccall gsl_matrix_ushort_const_row , Ptr -> CSize -> IO -- ccall gsl_matrix_ushort_const_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_const_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_ushort_const_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_const_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_const_superdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_ushort_const_view_array , Ptr CUShort -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_const_view_array_with_tda , Ptr CUShort -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_const_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_const_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_diagonal , Ptr -> IO #ccall gsl_matrix_ushort_div_elements , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_ushort_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_matrix_ushort_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_ushort_free , Ptr -> IO () #ccall gsl_matrix_ushort_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_ushort_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_matrix_ushort_isneg , Ptr -> IO CInt #ccall gsl_matrix_ushort_isnonneg , Ptr -> IO CInt #ccall gsl_matrix_ushort_isnull , Ptr -> IO CInt #ccall gsl_matrix_ushort_ispos , Ptr -> IO CInt #ccall gsl_matrix_ushort_max , Ptr -> IO CUShort #ccall gsl_matrix_ushort_max_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_ushort_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_ushort_min , Ptr -> IO CUShort #ccall gsl_matrix_ushort_min_index , Ptr -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_ushort_minmax , Ptr -> Ptr CUShort -> Ptr CUShort -> IO () #ccall gsl_matrix_ushort_minmax_index , Ptr -> Ptr CSize -> Ptr CSize -> Ptr CSize -> Ptr CSize -> IO () #ccall gsl_matrix_ushort_mul_elements , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_ushort_row , Ptr -> CSize -> IO #ccall gsl_matrix_ushort_scale , Ptr -> CDouble -> IO CInt #ccall gsl_matrix_ushort_set_all , Ptr -> CUShort -> IO () #ccall gsl_matrix_ushort_set_identity , Ptr -> IO () #ccall gsl_matrix_ushort_set_zero , Ptr -> IO () #ccall gsl_matrix_ushort_sub , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_ushort_subcolumn , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_subdiagonal , Ptr -> CSize -> IO -- ccall gsl_matrix_ushort_submatrix , Ptr -> CSize -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_subrow , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_superdiagonal , Ptr -> CSize -> IO #ccall gsl_matrix_ushort_swap , Ptr -> Ptr -> IO CInt #ccall gsl_matrix_ushort_swap_columns , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_ushort_swap_rowcol , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_ushort_swap_rows , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_matrix_ushort_transpose , Ptr -> IO CInt #ccall gsl_matrix_ushort_transpose_memcpy , Ptr -> Ptr -> IO CInt -- ccall gsl_matrix_ushort_view_array , Ptr CUShort -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_view_array_with_tda , Ptr CUShort -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_ushort_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_view_array , Ptr CDouble -> CSize -> CSize -> IO -- ccall gsl_matrix_view_array_with_tda , Ptr CDouble -> CSize -> CSize -> CSize -> IO -- ccall gsl_matrix_view_vector , Ptr -> CSize -> CSize -> IO -- ccall gsl_matrix_view_vector_with_tda , Ptr -> CSize -> CSize -> CSize -> IO