{-# INCLUDE <bindings.dsl.h> #-}
{-# INCLUDE <gsl/gsl_permutation.h> #-}
{-# LINE 1 "src/Bindings/Gsl/Permutations.hsc" #-}

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

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

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

module Bindings.Gsl.Permutations 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.Array (peekArray,pokeArray)
import Data.Int
import Data.Word

{-# LINE 8 "src/Bindings/Gsl/Permutations.hsc" #-}
import Bindings.Gsl.VectorsAndMatrices.DataTypes

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

  c'gsl_permutation'size :: CSize
{-# LINE 12 "src/Bindings/Gsl/Permutations.hsc" #-}
,
  c'gsl_permutation'data :: Ptr CSize
{-# LINE 13 "src/Bindings/Gsl/Permutations.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_permutation where
  sizeOf _ = 8
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    return $ C'gsl_permutation v0 v1
  poke p (C'gsl_permutation v0 v1) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    return ()

{-# LINE 14 "src/Bindings/Gsl/Permutations.hsc" #-}

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

{-# LINE 16 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_calloc" c'gsl_permutation_calloc
  :: CSize -> IO (Ptr C'gsl_permutation)
foreign import ccall "&gsl_permutation_calloc" p'gsl_permutation_calloc
  :: FunPtr (CSize -> IO (Ptr C'gsl_permutation))

{-# LINE 17 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_init" c'gsl_permutation_init
  :: Ptr C'gsl_permutation -> IO ()
foreign import ccall "&gsl_permutation_init" p'gsl_permutation_init
  :: FunPtr (Ptr C'gsl_permutation -> IO ())

{-# LINE 18 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_free" c'gsl_permutation_free
  :: Ptr C'gsl_permutation -> IO ()
foreign import ccall "&gsl_permutation_free" p'gsl_permutation_free
  :: FunPtr (Ptr C'gsl_permutation -> IO ())

{-# LINE 19 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_memcpy" c'gsl_permutation_memcpy
  :: Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> IO CInt
foreign import ccall "&gsl_permutation_memcpy" p'gsl_permutation_memcpy
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> IO CInt)

{-# LINE 20 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_fread" c'gsl_permutation_fread
  :: Ptr CFile -> Ptr C'gsl_permutation -> IO CInt
foreign import ccall "&gsl_permutation_fread" p'gsl_permutation_fread
  :: FunPtr (Ptr CFile -> Ptr C'gsl_permutation -> IO CInt)

{-# LINE 21 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_fwrite" c'gsl_permutation_fwrite
  :: Ptr CFile -> Ptr C'gsl_permutation -> IO CInt
foreign import ccall "&gsl_permutation_fwrite" p'gsl_permutation_fwrite
  :: FunPtr (Ptr CFile -> Ptr C'gsl_permutation -> IO CInt)

{-# LINE 22 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_fscanf" c'gsl_permutation_fscanf
  :: Ptr CFile -> Ptr C'gsl_permutation -> IO CInt
foreign import ccall "&gsl_permutation_fscanf" p'gsl_permutation_fscanf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_permutation -> IO CInt)

{-# LINE 23 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_fprintf" c'gsl_permutation_fprintf
  :: Ptr CFile -> Ptr C'gsl_permutation -> CString -> IO CInt
foreign import ccall "&gsl_permutation_fprintf" p'gsl_permutation_fprintf
  :: FunPtr (Ptr CFile -> Ptr C'gsl_permutation -> CString -> IO CInt)

{-# LINE 24 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_size" c'gsl_permutation_size
  :: Ptr C'gsl_permutation -> IO CSize
foreign import ccall "&gsl_permutation_size" p'gsl_permutation_size
  :: FunPtr (Ptr C'gsl_permutation -> IO CSize)

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

{-# LINE 26 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_swap" c'gsl_permutation_swap
  :: Ptr C'gsl_permutation -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permutation_swap" p'gsl_permutation_swap
  :: FunPtr (Ptr C'gsl_permutation -> CSize -> CSize -> IO CInt)

{-# LINE 27 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_valid" c'gsl_permutation_valid
  :: Ptr C'gsl_permutation -> IO CInt
foreign import ccall "&gsl_permutation_valid" p'gsl_permutation_valid
  :: FunPtr (Ptr C'gsl_permutation -> IO CInt)

{-# LINE 28 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_reverse" c'gsl_permutation_reverse
  :: Ptr C'gsl_permutation -> IO ()
foreign import ccall "&gsl_permutation_reverse" p'gsl_permutation_reverse
  :: FunPtr (Ptr C'gsl_permutation -> IO ())

{-# LINE 29 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_inverse" c'gsl_permutation_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> IO CInt
foreign import ccall "&gsl_permutation_inverse" p'gsl_permutation_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> IO CInt)

{-# LINE 30 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_next" c'gsl_permutation_next
  :: Ptr C'gsl_permutation -> IO CInt
foreign import ccall "&gsl_permutation_next" p'gsl_permutation_next
  :: FunPtr (Ptr C'gsl_permutation -> IO CInt)

{-# LINE 31 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_prev" c'gsl_permutation_prev
  :: Ptr C'gsl_permutation -> IO CInt
foreign import ccall "&gsl_permutation_prev" p'gsl_permutation_prev
  :: FunPtr (Ptr C'gsl_permutation -> IO CInt)

{-# LINE 32 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_mul" c'gsl_permutation_mul
  :: Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> IO CInt
foreign import ccall "&gsl_permutation_mul" p'gsl_permutation_mul
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> IO CInt)

{-# LINE 33 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_linear_to_canonical" c'gsl_permutation_linear_to_canonical
  :: Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> IO CInt
foreign import ccall "&gsl_permutation_linear_to_canonical" p'gsl_permutation_linear_to_canonical
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> IO CInt)

{-# LINE 34 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_canonical_to_linear" c'gsl_permutation_canonical_to_linear
  :: Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> IO CInt
foreign import ccall "&gsl_permutation_canonical_to_linear" p'gsl_permutation_canonical_to_linear
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_permutation -> IO CInt)

{-# LINE 35 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_inversions" c'gsl_permutation_inversions
  :: Ptr C'gsl_permutation -> IO CSize
foreign import ccall "&gsl_permutation_inversions" p'gsl_permutation_inversions
  :: FunPtr (Ptr C'gsl_permutation -> IO CSize)

{-# LINE 36 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_linear_cycles" c'gsl_permutation_linear_cycles
  :: Ptr C'gsl_permutation -> IO CSize
foreign import ccall "&gsl_permutation_linear_cycles" p'gsl_permutation_linear_cycles
  :: FunPtr (Ptr C'gsl_permutation -> IO CSize)

{-# LINE 37 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_canonical_cycles" c'gsl_permutation_canonical_cycles
  :: Ptr C'gsl_permutation -> IO CSize
foreign import ccall "&gsl_permutation_canonical_cycles" p'gsl_permutation_canonical_cycles
  :: FunPtr (Ptr C'gsl_permutation -> IO CSize)

{-# LINE 38 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permutation_get" c'gsl_permutation_get
  :: Ptr C'gsl_permutation -> CSize -> IO CSize
foreign import ccall "&gsl_permutation_get" p'gsl_permutation_get
  :: FunPtr (Ptr C'gsl_permutation -> CSize -> IO CSize)

{-# LINE 39 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_char" c'gsl_permute_char
  :: Ptr CSize -> CString -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_char" p'gsl_permute_char
  :: FunPtr (Ptr CSize -> CString -> CSize -> CSize -> IO CInt)

{-# LINE 40 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_char_inverse" c'gsl_permute_char_inverse
  :: Ptr CSize -> CString -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_char_inverse" p'gsl_permute_char_inverse
  :: FunPtr (Ptr CSize -> CString -> CSize -> CSize -> IO CInt)

{-# LINE 41 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_complex" c'gsl_permute_complex
  :: Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_complex" p'gsl_permute_complex
  :: FunPtr (Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt)

{-# LINE 42 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_complex_inverse" c'gsl_permute_complex_inverse
  :: Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_complex_inverse" p'gsl_permute_complex_inverse
  :: FunPtr (Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt)

{-# LINE 43 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_complex_float" c'gsl_permute_complex_float
  :: Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_complex_float" p'gsl_permute_complex_float
  :: FunPtr (Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt)

{-# LINE 44 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_complex_float_inverse" c'gsl_permute_complex_float_inverse
  :: Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_complex_float_inverse" p'gsl_permute_complex_float_inverse
  :: FunPtr (Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt)

{-# LINE 45 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_complex_long_double" c'gsl_permute_complex_long_double
  :: Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_complex_long_double" p'gsl_permute_complex_long_double
  :: FunPtr (Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt)

{-# LINE 46 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_complex_long_double_inverse" c'gsl_permute_complex_long_double_inverse
  :: Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_complex_long_double_inverse" p'gsl_permute_complex_long_double_inverse
  :: FunPtr (Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt)

{-# LINE 47 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute" c'gsl_permute
  :: Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute" p'gsl_permute
  :: FunPtr (Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt)

{-# LINE 48 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_inverse" c'gsl_permute_inverse
  :: Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_inverse" p'gsl_permute_inverse
  :: FunPtr (Ptr CSize -> Ptr CDouble -> CSize -> CSize -> IO CInt)

{-# LINE 49 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_float" c'gsl_permute_float
  :: Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_float" p'gsl_permute_float
  :: FunPtr (Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt)

{-# LINE 50 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_float_inverse" c'gsl_permute_float_inverse
  :: Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_float_inverse" p'gsl_permute_float_inverse
  :: FunPtr (Ptr CSize -> Ptr CFloat -> CSize -> CSize -> IO CInt)

{-# LINE 51 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_int" c'gsl_permute_int
  :: Ptr CSize -> Ptr CInt -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_int" p'gsl_permute_int
  :: FunPtr (Ptr CSize -> Ptr CInt -> CSize -> CSize -> IO CInt)

{-# LINE 52 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_int_inverse" c'gsl_permute_int_inverse
  :: Ptr CSize -> Ptr CInt -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_int_inverse" p'gsl_permute_int_inverse
  :: FunPtr (Ptr CSize -> Ptr CInt -> CSize -> CSize -> IO CInt)

{-# LINE 53 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_long_double" c'gsl_permute_long_double
  :: Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_long_double" p'gsl_permute_long_double
  :: FunPtr (Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt)

{-# LINE 54 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_long_double_inverse" c'gsl_permute_long_double_inverse
  :: Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_long_double_inverse" p'gsl_permute_long_double_inverse
  :: FunPtr (Ptr CSize -> Ptr CLDouble -> CSize -> CSize -> IO CInt)

{-# LINE 55 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_long" c'gsl_permute_long
  :: Ptr CSize -> Ptr CLong -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_long" p'gsl_permute_long
  :: FunPtr (Ptr CSize -> Ptr CLong -> CSize -> CSize -> IO CInt)

{-# LINE 56 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_long_inverse" c'gsl_permute_long_inverse
  :: Ptr CSize -> Ptr CLong -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_long_inverse" p'gsl_permute_long_inverse
  :: FunPtr (Ptr CSize -> Ptr CLong -> CSize -> CSize -> IO CInt)

{-# LINE 57 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_short" c'gsl_permute_short
  :: Ptr CSize -> Ptr CShort -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_short" p'gsl_permute_short
  :: FunPtr (Ptr CSize -> Ptr CShort -> CSize -> CSize -> IO CInt)

{-# LINE 58 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_short_inverse" c'gsl_permute_short_inverse
  :: Ptr CSize -> Ptr CShort -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_short_inverse" p'gsl_permute_short_inverse
  :: FunPtr (Ptr CSize -> Ptr CShort -> CSize -> CSize -> IO CInt)

{-# LINE 59 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_uchar" c'gsl_permute_uchar
  :: Ptr CSize -> Ptr CUChar -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_uchar" p'gsl_permute_uchar
  :: FunPtr (Ptr CSize -> Ptr CUChar -> CSize -> CSize -> IO CInt)

{-# LINE 60 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_uchar_inverse" c'gsl_permute_uchar_inverse
  :: Ptr CSize -> Ptr CUChar -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_uchar_inverse" p'gsl_permute_uchar_inverse
  :: FunPtr (Ptr CSize -> Ptr CUChar -> CSize -> CSize -> IO CInt)

{-# LINE 61 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_uint" c'gsl_permute_uint
  :: Ptr CSize -> Ptr CUInt -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_uint" p'gsl_permute_uint
  :: FunPtr (Ptr CSize -> Ptr CUInt -> CSize -> CSize -> IO CInt)

{-# LINE 62 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_uint_inverse" c'gsl_permute_uint_inverse
  :: Ptr CSize -> Ptr CUInt -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_uint_inverse" p'gsl_permute_uint_inverse
  :: FunPtr (Ptr CSize -> Ptr CUInt -> CSize -> CSize -> IO CInt)

{-# LINE 63 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_ulong" c'gsl_permute_ulong
  :: Ptr CSize -> Ptr CULong -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_ulong" p'gsl_permute_ulong
  :: FunPtr (Ptr CSize -> Ptr CULong -> CSize -> CSize -> IO CInt)

{-# LINE 64 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_ulong_inverse" c'gsl_permute_ulong_inverse
  :: Ptr CSize -> Ptr CULong -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_ulong_inverse" p'gsl_permute_ulong_inverse
  :: FunPtr (Ptr CSize -> Ptr CULong -> CSize -> CSize -> IO CInt)

{-# LINE 65 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_ushort" c'gsl_permute_ushort
  :: Ptr CSize -> Ptr CUShort -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_ushort" p'gsl_permute_ushort
  :: FunPtr (Ptr CSize -> Ptr CUShort -> CSize -> CSize -> IO CInt)

{-# LINE 66 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_ushort_inverse" c'gsl_permute_ushort_inverse
  :: Ptr CSize -> Ptr CUShort -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_permute_ushort_inverse" p'gsl_permute_ushort_inverse
  :: FunPtr (Ptr CSize -> Ptr CUShort -> CSize -> CSize -> IO CInt)

{-# LINE 67 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_char" c'gsl_permute_vector_char
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_permute_vector_char" p'gsl_permute_vector_char
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 68 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_char_inverse" c'gsl_permute_vector_char_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_char -> IO CInt
foreign import ccall "&gsl_permute_vector_char_inverse" p'gsl_permute_vector_char_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_char -> IO CInt)

{-# LINE 69 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_complex" c'gsl_permute_vector_complex
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_permute_vector_complex" p'gsl_permute_vector_complex
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 70 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_complex_inverse" c'gsl_permute_vector_complex_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex -> IO CInt
foreign import ccall "&gsl_permute_vector_complex_inverse" p'gsl_permute_vector_complex_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex -> IO CInt)

{-# LINE 71 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_complex_float" c'gsl_permute_vector_complex_float
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_permute_vector_complex_float" p'gsl_permute_vector_complex_float
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 72 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_complex_float_inverse" c'gsl_permute_vector_complex_float_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex_float -> IO CInt
foreign import ccall "&gsl_permute_vector_complex_float_inverse" p'gsl_permute_vector_complex_float_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex_float -> IO CInt)

{-# LINE 73 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_complex_long_double" c'gsl_permute_vector_complex_long_double
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex_long_double -> IO CInt
foreign import ccall "&gsl_permute_vector_complex_long_double" p'gsl_permute_vector_complex_long_double
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex_long_double -> IO CInt)

{-# LINE 74 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_complex_long_double_inverse" c'gsl_permute_vector_complex_long_double_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex_long_double -> IO CInt
foreign import ccall "&gsl_permute_vector_complex_long_double_inverse" p'gsl_permute_vector_complex_long_double_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_complex_long_double -> IO CInt)

{-# LINE 75 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector" c'gsl_permute_vector
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_permute_vector" p'gsl_permute_vector
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 76 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_inverse" c'gsl_permute_vector_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector -> IO CInt
foreign import ccall "&gsl_permute_vector_inverse" p'gsl_permute_vector_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector -> IO CInt)

{-# LINE 77 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_float" c'gsl_permute_vector_float
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_permute_vector_float" p'gsl_permute_vector_float
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 78 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_float_inverse" c'gsl_permute_vector_float_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_float -> IO CInt
foreign import ccall "&gsl_permute_vector_float_inverse" p'gsl_permute_vector_float_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_float -> IO CInt)

{-# LINE 79 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_int" c'gsl_permute_vector_int
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_permute_vector_int" p'gsl_permute_vector_int
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 80 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_int_inverse" c'gsl_permute_vector_int_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_int -> IO CInt
foreign import ccall "&gsl_permute_vector_int_inverse" p'gsl_permute_vector_int_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_int -> IO CInt)

{-# LINE 81 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_long_double" c'gsl_permute_vector_long_double
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_long_double -> IO CInt
foreign import ccall "&gsl_permute_vector_long_double" p'gsl_permute_vector_long_double
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_long_double -> IO CInt)

{-# LINE 82 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_long_double_inverse" c'gsl_permute_vector_long_double_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_long_double -> IO CInt
foreign import ccall "&gsl_permute_vector_long_double_inverse" p'gsl_permute_vector_long_double_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_long_double -> IO CInt)

{-# LINE 83 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_long" c'gsl_permute_vector_long
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_permute_vector_long" p'gsl_permute_vector_long
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 84 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_long_inverse" c'gsl_permute_vector_long_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_long -> IO CInt
foreign import ccall "&gsl_permute_vector_long_inverse" p'gsl_permute_vector_long_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_long -> IO CInt)

{-# LINE 85 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_short" c'gsl_permute_vector_short
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_permute_vector_short" p'gsl_permute_vector_short
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 86 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_short_inverse" c'gsl_permute_vector_short_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_short -> IO CInt
foreign import ccall "&gsl_permute_vector_short_inverse" p'gsl_permute_vector_short_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_short -> IO CInt)

{-# LINE 87 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_uchar" c'gsl_permute_vector_uchar
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_permute_vector_uchar" p'gsl_permute_vector_uchar
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 88 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_uchar_inverse" c'gsl_permute_vector_uchar_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_uchar -> IO CInt
foreign import ccall "&gsl_permute_vector_uchar_inverse" p'gsl_permute_vector_uchar_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_uchar -> IO CInt)

{-# LINE 89 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_uint" c'gsl_permute_vector_uint
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_permute_vector_uint" p'gsl_permute_vector_uint
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 90 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_uint_inverse" c'gsl_permute_vector_uint_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_uint -> IO CInt
foreign import ccall "&gsl_permute_vector_uint_inverse" p'gsl_permute_vector_uint_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_uint -> IO CInt)

{-# LINE 91 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_ulong" c'gsl_permute_vector_ulong
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_permute_vector_ulong" p'gsl_permute_vector_ulong
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 92 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_ulong_inverse" c'gsl_permute_vector_ulong_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_ulong -> IO CInt
foreign import ccall "&gsl_permute_vector_ulong_inverse" p'gsl_permute_vector_ulong_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_ulong -> IO CInt)

{-# LINE 93 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_ushort" c'gsl_permute_vector_ushort
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_permute_vector_ushort" p'gsl_permute_vector_ushort
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 94 "src/Bindings/Gsl/Permutations.hsc" #-}
foreign import ccall "gsl_permute_vector_ushort_inverse" c'gsl_permute_vector_ushort_inverse
  :: Ptr C'gsl_permutation -> Ptr C'gsl_vector_ushort -> IO CInt
foreign import ccall "&gsl_permute_vector_ushort_inverse" p'gsl_permute_vector_ushort_inverse
  :: FunPtr (Ptr C'gsl_permutation -> Ptr C'gsl_vector_ushort -> IO CInt)

{-# LINE 95 "src/Bindings/Gsl/Permutations.hsc" #-}