#include #include -- | module Bindings.Gsl.Permutations where #strict_import import Bindings.Gsl.VectorsAndMatrices.DataTypes #starttype gsl_permutation #field size , CSize #field data , Ptr CSize #stoptype #ccall gsl_permutation_alloc , CSize -> IO (Ptr ) #ccall gsl_permutation_calloc , CSize -> IO (Ptr ) #ccall gsl_permutation_init , Ptr -> IO () #ccall gsl_permutation_free , Ptr -> IO () #ccall gsl_permutation_memcpy , Ptr -> Ptr -> IO CInt #ccall gsl_permutation_fread , Ptr CFile -> Ptr -> IO CInt #ccall gsl_permutation_fwrite , Ptr CFile -> Ptr -> IO CInt #ccall gsl_permutation_fscanf , Ptr CFile -> Ptr -> IO CInt #ccall gsl_permutation_fprintf , Ptr CFile -> Ptr -> CString -> IO CInt #ccall gsl_permutation_size , Ptr -> IO CSize #ccall gsl_permutation_data , Ptr -> IO (Ptr CSize) #ccall gsl_permutation_swap , Ptr -> CSize -> CSize -> IO CInt #ccall gsl_permutation_valid , Ptr -> IO CInt #ccall gsl_permutation_reverse , Ptr -> IO () #ccall gsl_permutation_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permutation_next , Ptr -> IO CInt #ccall gsl_permutation_prev , Ptr -> IO CInt #ccall gsl_permutation_mul , Ptr -> Ptr -> Ptr -> IO CInt #ccall gsl_permutation_linear_to_canonical , Ptr -> Ptr -> IO CInt #ccall gsl_permutation_canonical_to_linear , Ptr -> Ptr -> IO CInt #ccall gsl_permutation_inversions , Ptr -> IO CSize #ccall gsl_permutation_linear_cycles , Ptr -> IO CSize #ccall gsl_permutation_canonical_cycles , Ptr -> IO CSize #ccall gsl_permutation_get , Ptr -> CSize -> IO CSize #ccall gsl_permute_char , Ptr CSize -> CString -> CSize -> CSize -> IO CInt #ccall gsl_permute_char_inverse , Ptr CSize -> CString -> CSize -> CSize -> IO CInt #ccall gsl_permute_complex , Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt #ccall gsl_permute_complex_inverse , Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt #ccall gsl_permute_complex_float , Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt #ccall gsl_permute_complex_float_inverse , Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt -- #ccall gsl_permute_complex_long_double , Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt -- #ccall gsl_permute_complex_long_double_inverse , Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt #ccall gsl_permute , Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt #ccall gsl_permute_inverse , Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt #ccall gsl_permute_float , Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt #ccall gsl_permute_float_inverse , Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt #ccall gsl_permute_int , Ptr CSize -> Ptr CInt -> CSize -> CSize -> IO CInt #ccall gsl_permute_int_inverse , Ptr CSize -> Ptr CInt -> CSize -> CSize -> IO CInt -- #ccall gsl_permute_long_double , Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt -- #ccall gsl_permute_long_double_inverse , Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt #ccall gsl_permute_long , Ptr CSize -> Ptr CLong -> CSize -> CSize -> IO CInt #ccall gsl_permute_long_inverse , Ptr CSize -> Ptr CLong -> CSize -> CSize -> IO CInt #ccall gsl_permute_short , Ptr CSize -> Ptr CShort -> CSize -> CSize -> IO CInt #ccall gsl_permute_short_inverse , Ptr CSize -> Ptr CShort -> CSize -> CSize -> IO CInt #ccall gsl_permute_uchar , Ptr CSize -> Ptr CUChar -> CSize -> CSize -> IO CInt #ccall gsl_permute_uchar_inverse , Ptr CSize -> Ptr CUChar -> CSize -> CSize -> IO CInt #ccall gsl_permute_uint , Ptr CSize -> Ptr CUInt -> CSize -> CSize -> IO CInt #ccall gsl_permute_uint_inverse , Ptr CSize -> Ptr CUInt -> CSize -> CSize -> IO CInt #ccall gsl_permute_ulong , Ptr CSize -> Ptr CULong -> CSize -> CSize -> IO CInt #ccall gsl_permute_ulong_inverse , Ptr CSize -> Ptr CULong -> CSize -> CSize -> IO CInt #ccall gsl_permute_ushort , Ptr CSize -> Ptr CUShort -> CSize -> CSize -> IO CInt #ccall gsl_permute_ushort_inverse , Ptr CSize -> Ptr CUShort -> CSize -> CSize -> IO CInt #ccall gsl_permute_vector_char , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_char_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_complex , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_complex_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_complex_float , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_complex_float_inverse , Ptr -> Ptr -> IO CInt -- #ccall gsl_permute_vector_complex_long_double , Ptr -> Ptr -> IO CInt -- #ccall gsl_permute_vector_complex_long_double_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_float , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_float_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_int , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_int_inverse , Ptr -> Ptr -> IO CInt -- #ccall gsl_permute_vector_long_double , Ptr -> Ptr -> IO CInt -- #ccall gsl_permute_vector_long_double_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_long , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_long_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_short , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_short_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_uchar , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_uchar_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_uint , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_uint_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_ulong , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_ulong_inverse , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_ushort , Ptr -> Ptr -> IO CInt #ccall gsl_permute_vector_ushort_inverse , Ptr -> Ptr -> IO CInt