{-# INCLUDE <bindings.dsl.h> #-}
{-# INCLUDE <gsl/gsl_block.h> #-}
{-# INCLUDE <gsl/gsl_vector.h> #-}
{-# INCLUDE <gsl/gsl_matrix.h> #-}
{-# LINE 1 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

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

{-# LINE 4 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

{-# LINE 5 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

module Bindings.Gsl.VectorsAndMatrices.DataTypes 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 10 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block = C'gsl_block{
{-# LINE 12 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block'size :: CSize
{-# LINE 13 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block'data :: Ptr CDouble
{-# LINE 14 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 15 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_char = C'gsl_block_char{
{-# LINE 17 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_char'size :: CSize
{-# LINE 18 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_char'data :: CString
{-# LINE 19 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 20 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_complex = C'gsl_block_complex{
{-# LINE 22 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_complex'size :: CSize
{-# LINE 23 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_complex'data :: Ptr CDouble
{-# LINE 24 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 25 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_complex_float = C'gsl_block_complex_float{
{-# LINE 27 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_complex_float'size :: CSize
{-# LINE 28 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_complex_float'data :: Ptr CFloat
{-# LINE 29 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 30 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_complex_long_double = C'gsl_block_complex_long_double{
{-# LINE 32 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_complex_long_double'size :: CSize
{-# LINE 33 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_complex_long_double'data :: Ptr CLDouble
{-# LINE 34 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 35 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_float = C'gsl_block_float{
{-# LINE 37 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_float'size :: CSize
{-# LINE 38 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_float'data :: Ptr CFloat
{-# LINE 39 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 40 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_int = C'gsl_block_int{
{-# LINE 42 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_int'size :: CSize
{-# LINE 43 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_int'data :: Ptr CInt
{-# LINE 44 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 45 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_long = C'gsl_block_long{
{-# LINE 47 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_long'size :: CSize
{-# LINE 48 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_long'data :: Ptr CLong
{-# LINE 49 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 50 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_long_double = C'gsl_block_long_double{
{-# LINE 52 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_long_double'size :: CSize
{-# LINE 53 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_long_double'data :: Ptr CLDouble
{-# LINE 54 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 55 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_short = C'gsl_block_short{
{-# LINE 57 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_short'size :: CSize
{-# LINE 58 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_short'data :: Ptr CShort
{-# LINE 59 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 60 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_uchar = C'gsl_block_uchar{
{-# LINE 62 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_uchar'size :: CSize
{-# LINE 63 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_uchar'data :: Ptr CUChar
{-# LINE 64 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 65 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_uint = C'gsl_block_uint{
{-# LINE 67 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_uint'size :: CSize
{-# LINE 68 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_uint'data :: Ptr CUInt
{-# LINE 69 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 70 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_ulong = C'gsl_block_ulong{
{-# LINE 72 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_ulong'size :: CSize
{-# LINE 73 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_ulong'data :: Ptr CULong
{-# LINE 74 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 75 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_block_ushort = C'gsl_block_ushort{
{-# LINE 77 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_block_ushort'size :: CSize
{-# LINE 78 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_block_ushort'data :: Ptr CUShort
{-# LINE 79 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 80 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix = C'gsl_matrix{
{-# LINE 82 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix'size1 :: CSize
{-# LINE 83 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix'size2 :: CSize
{-# LINE 84 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix'tda :: CSize
{-# LINE 85 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix'data :: Ptr CDouble
{-# LINE 86 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix'block :: Ptr C'gsl_block
{-# LINE 87 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix'owner :: CInt
{-# LINE 88 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 89 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_char = C'gsl_matrix_char{
{-# LINE 91 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_char'size1 :: CSize
{-# LINE 92 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_char'size2 :: CSize
{-# LINE 93 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_char'tda :: CSize
{-# LINE 94 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_char'data :: CString
{-# LINE 95 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_char'block :: Ptr C'gsl_block_char
{-# LINE 96 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_char'owner :: CInt
{-# LINE 97 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_char where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_char v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_char v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 98 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_char_const_view = C'gsl_matrix_char_const_view{
{-# LINE 100 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_char_const_view'matrix :: C'gsl_matrix_char
{-# LINE 101 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 102 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_char_view = C'gsl_matrix_char_view{
{-# LINE 104 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_char_view'matrix :: C'gsl_matrix_char
{-# LINE 105 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 106 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_complex = C'gsl_matrix_complex{
{-# LINE 108 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_complex'size1 :: CSize
{-# LINE 109 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex'size2 :: CSize
{-# LINE 110 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex'tda :: CSize
{-# LINE 111 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex'data :: Ptr CDouble
{-# LINE 112 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex'block :: Ptr C'gsl_block_complex
{-# LINE 113 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex'owner :: CInt
{-# LINE 114 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_complex where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_complex v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_complex v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 115 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_complex_const_view = C'gsl_matrix_complex_const_view{
{-# LINE 117 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_complex_const_view'matrix :: C'gsl_matrix_complex
{-# LINE 118 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 119 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_complex_float = C'gsl_matrix_complex_float{
{-# LINE 121 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_complex_float'size1 :: CSize
{-# LINE 122 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex_float'size2 :: CSize
{-# LINE 123 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex_float'tda :: CSize
{-# LINE 124 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex_float'data :: Ptr CFloat
{-# LINE 125 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex_float'block :: Ptr C'gsl_block_complex_float
{-# LINE 126 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex_float'owner :: CInt
{-# LINE 127 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_complex_float where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_complex_float v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_complex_float v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 128 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_complex_float_const_view = C'gsl_matrix_complex_float_const_view{
{-# LINE 130 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_complex_float_const_view'matrix :: C'gsl_matrix_complex_float
{-# LINE 131 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 132 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_complex_float_view = C'gsl_matrix_complex_float_view{
{-# LINE 134 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_complex_float_view'matrix :: C'gsl_matrix_complex_float
{-# LINE 135 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 136 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_complex_long_double = C'gsl_matrix_complex_long_double{
{-# LINE 138 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_complex_long_double'size1 :: CSize
{-# LINE 139 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex_long_double'size2 :: CSize
{-# LINE 140 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex_long_double'tda :: CSize
{-# LINE 141 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex_long_double'data :: Ptr CLDouble
{-# LINE 142 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex_long_double'block :: Ptr C'gsl_block_complex_long_double
{-# LINE 143 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_complex_long_double'owner :: CInt
{-# LINE 144 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_complex_long_double where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_complex_long_double v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_complex_long_double v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 145 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_complex_long_double_const_view = C'gsl_matrix_complex_long_double_const_view{
{-# LINE 147 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_complex_long_double_const_view'matrix :: C'gsl_matrix_complex_long_double
{-# LINE 148 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 149 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_complex_long_double_view = C'gsl_matrix_complex_long_double_view{
{-# LINE 151 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_complex_long_double_view'matrix :: C'gsl_matrix_complex_long_double
{-# LINE 152 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 153 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_complex_view = C'gsl_matrix_complex_view{
{-# LINE 155 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_complex_view'matrix :: C'gsl_matrix_complex
{-# LINE 156 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 157 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_const_view = C'gsl_matrix_const_view{
{-# LINE 159 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_const_view'matrix :: C'gsl_matrix
{-# LINE 160 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 161 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_float = C'gsl_matrix_float{
{-# LINE 163 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_float'size1 :: CSize
{-# LINE 164 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_float'size2 :: CSize
{-# LINE 165 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_float'tda :: CSize
{-# LINE 166 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_float'data :: Ptr CFloat
{-# LINE 167 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_float'block :: Ptr C'gsl_block_float
{-# LINE 168 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_float'owner :: CInt
{-# LINE 169 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_float where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_float v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_float v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 170 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_float_const_view = C'gsl_matrix_float_const_view{
{-# LINE 172 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_float_const_view'matrix :: C'gsl_matrix_float
{-# LINE 173 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 174 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_float_view = C'gsl_matrix_float_view{
{-# LINE 176 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_float_view'matrix :: C'gsl_matrix_float
{-# LINE 177 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 178 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_int = C'gsl_matrix_int{
{-# LINE 180 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_int'size1 :: CSize
{-# LINE 181 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_int'size2 :: CSize
{-# LINE 182 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_int'tda :: CSize
{-# LINE 183 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_int'data :: Ptr CInt
{-# LINE 184 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_int'block :: Ptr C'gsl_block_int
{-# LINE 185 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_int'owner :: CInt
{-# LINE 186 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_int where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_int v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_int v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 187 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_int_const_view = C'gsl_matrix_int_const_view{
{-# LINE 189 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_int_const_view'matrix :: C'gsl_matrix_int
{-# LINE 190 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 191 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_int_view = C'gsl_matrix_int_view{
{-# LINE 193 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_int_view'matrix :: C'gsl_matrix_int
{-# LINE 194 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 195 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_long = C'gsl_matrix_long{
{-# LINE 197 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_long'size1 :: CSize
{-# LINE 198 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_long'size2 :: CSize
{-# LINE 199 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_long'tda :: CSize
{-# LINE 200 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_long'data :: Ptr CLong
{-# LINE 201 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_long'block :: Ptr C'gsl_block_long
{-# LINE 202 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_long'owner :: CInt
{-# LINE 203 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_long where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_long v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_long v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 204 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_long_const_view = C'gsl_matrix_long_const_view{
{-# LINE 206 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_long_const_view'matrix :: C'gsl_matrix_long
{-# LINE 207 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 208 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_long_double = C'gsl_matrix_long_double{
{-# LINE 210 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_long_double'size1 :: CSize
{-# LINE 211 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_long_double'size2 :: CSize
{-# LINE 212 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_long_double'tda :: CSize
{-# LINE 213 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_long_double'data :: Ptr CLDouble
{-# LINE 214 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_long_double'block :: Ptr C'gsl_block_long_double
{-# LINE 215 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_long_double'owner :: CInt
{-# LINE 216 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_long_double where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_long_double v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_long_double v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 217 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_long_double_const_view = C'gsl_matrix_long_double_const_view{
{-# LINE 219 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_long_double_const_view'matrix :: C'gsl_matrix_long_double
{-# LINE 220 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 221 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_long_double_view = C'gsl_matrix_long_double_view{
{-# LINE 223 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_long_double_view'matrix :: C'gsl_matrix_long_double
{-# LINE 224 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 225 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_long_view = C'gsl_matrix_long_view{
{-# LINE 227 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_long_view'matrix :: C'gsl_matrix_long
{-# LINE 228 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 229 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_short = C'gsl_matrix_short{
{-# LINE 231 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_short'size1 :: CSize
{-# LINE 232 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_short'size2 :: CSize
{-# LINE 233 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_short'tda :: CSize
{-# LINE 234 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_short'data :: Ptr CShort
{-# LINE 235 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_short'block :: Ptr C'gsl_block_short
{-# LINE 236 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_short'owner :: CInt
{-# LINE 237 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_short where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_short v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_short v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 238 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_short_const_view = C'gsl_matrix_short_const_view{
{-# LINE 240 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_short_const_view'matrix :: C'gsl_matrix_short
{-# LINE 241 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 242 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_short_view = C'gsl_matrix_short_view{
{-# LINE 244 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_short_view'matrix :: C'gsl_matrix_short
{-# LINE 245 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 246 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_uchar = C'gsl_matrix_uchar{
{-# LINE 248 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_uchar'size1 :: CSize
{-# LINE 249 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_uchar'size2 :: CSize
{-# LINE 250 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_uchar'tda :: CSize
{-# LINE 251 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_uchar'data :: Ptr CUChar
{-# LINE 252 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_uchar'block :: Ptr C'gsl_block_uchar
{-# LINE 253 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_uchar'owner :: CInt
{-# LINE 254 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_uchar where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_uchar v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_uchar v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 255 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_uchar_const_view = C'gsl_matrix_uchar_const_view{
{-# LINE 257 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_uchar_const_view'matrix :: C'gsl_matrix_uchar
{-# LINE 258 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 259 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_uchar_view = C'gsl_matrix_uchar_view{
{-# LINE 261 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_uchar_view'matrix :: C'gsl_matrix_uchar
{-# LINE 262 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 263 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_uint = C'gsl_matrix_uint{
{-# LINE 265 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_uint'size1 :: CSize
{-# LINE 266 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_uint'size2 :: CSize
{-# LINE 267 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_uint'tda :: CSize
{-# LINE 268 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_uint'data :: Ptr CUInt
{-# LINE 269 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_uint'block :: Ptr C'gsl_block_uint
{-# LINE 270 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_uint'owner :: CInt
{-# LINE 271 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_uint where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_uint v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_uint v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 272 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_uint_const_view = C'gsl_matrix_uint_const_view{
{-# LINE 274 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_uint_const_view'matrix :: C'gsl_matrix_uint
{-# LINE 275 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 276 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_uint_view = C'gsl_matrix_uint_view{
{-# LINE 278 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_uint_view'matrix :: C'gsl_matrix_uint
{-# LINE 279 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 280 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_ulong = C'gsl_matrix_ulong{
{-# LINE 282 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_ulong'size1 :: CSize
{-# LINE 283 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_ulong'size2 :: CSize
{-# LINE 284 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_ulong'tda :: CSize
{-# LINE 285 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_ulong'data :: Ptr CULong
{-# LINE 286 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_ulong'block :: Ptr C'gsl_block_ulong
{-# LINE 287 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_ulong'owner :: CInt
{-# LINE 288 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_ulong where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_ulong v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_ulong v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 289 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_ulong_const_view = C'gsl_matrix_ulong_const_view{
{-# LINE 291 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_ulong_const_view'matrix :: C'gsl_matrix_ulong
{-# LINE 292 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 293 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_ulong_view = C'gsl_matrix_ulong_view{
{-# LINE 295 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_ulong_view'matrix :: C'gsl_matrix_ulong
{-# LINE 296 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 297 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_ushort = C'gsl_matrix_ushort{
{-# LINE 299 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_ushort'size1 :: CSize
{-# LINE 300 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_ushort'size2 :: CSize
{-# LINE 301 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_ushort'tda :: CSize
{-# LINE 302 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_ushort'data :: Ptr CUShort
{-# LINE 303 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_ushort'block :: Ptr C'gsl_block_ushort
{-# LINE 304 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_matrix_ushort'owner :: CInt
{-# LINE 305 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_matrix_ushort where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'gsl_matrix_ushort v0 v1 v2 v3 v4 v5
  poke p (C'gsl_matrix_ushort v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 306 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_ushort_const_view = C'gsl_matrix_ushort_const_view{
{-# LINE 308 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_ushort_const_view'matrix :: C'gsl_matrix_ushort
{-# LINE 309 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 310 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_ushort_view = C'gsl_matrix_ushort_view{
{-# LINE 312 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_ushort_view'matrix :: C'gsl_matrix_ushort
{-# LINE 313 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 314 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_matrix_view = C'gsl_matrix_view{
{-# LINE 316 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_matrix_view'matrix :: C'gsl_matrix
{-# LINE 317 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 318 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector = C'gsl_vector{
{-# LINE 320 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector'size :: CSize
{-# LINE 321 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector'stride :: CSize
{-# LINE 322 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector'data :: Ptr CDouble
{-# LINE 323 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector'block :: Ptr C'gsl_block
{-# LINE 324 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector'owner :: CInt
{-# LINE 325 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector v0 v1 v2 v3 v4
  poke p (C'gsl_vector v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 326 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_char = C'gsl_vector_char{
{-# LINE 328 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_char'size :: CSize
{-# LINE 329 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_char'stride :: CSize
{-# LINE 330 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_char'data :: CString
{-# LINE 331 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_char'block :: Ptr C'gsl_block_char
{-# LINE 332 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_char'owner :: CInt
{-# LINE 333 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_char where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_char v0 v1 v2 v3 v4
  poke p (C'gsl_vector_char v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 334 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_char_const_view = C'gsl_vector_char_const_view{
{-# LINE 336 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_char_const_view'vector :: C'gsl_vector_char
{-# LINE 337 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 338 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_char_view = C'gsl_vector_char_view{
{-# LINE 340 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_char_view'vector :: C'gsl_vector_char
{-# LINE 341 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 342 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_complex = C'gsl_vector_complex{
{-# LINE 344 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_complex'size :: CSize
{-# LINE 345 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex'stride :: CSize
{-# LINE 346 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex'data :: Ptr CDouble
{-# LINE 347 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex'block :: Ptr C'gsl_block_complex
{-# LINE 348 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex'owner :: CInt
{-# LINE 349 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_complex where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_complex v0 v1 v2 v3 v4
  poke p (C'gsl_vector_complex v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 350 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_complex_const_view = C'gsl_vector_complex_const_view{
{-# LINE 352 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_complex_const_view'vector :: C'gsl_vector_complex
{-# LINE 353 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 354 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_complex_float = C'gsl_vector_complex_float{
{-# LINE 356 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_complex_float'size :: CSize
{-# LINE 357 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex_float'stride :: CSize
{-# LINE 358 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex_float'data :: Ptr CFloat
{-# LINE 359 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex_float'block :: Ptr C'gsl_block_complex_float
{-# LINE 360 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex_float'owner :: CInt
{-# LINE 361 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_complex_float where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_complex_float v0 v1 v2 v3 v4
  poke p (C'gsl_vector_complex_float v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 362 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_complex_float_const_view = C'gsl_vector_complex_float_const_view{
{-# LINE 364 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_complex_float_const_view'vector :: C'gsl_vector_complex_float
{-# LINE 365 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 366 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_complex_float_view = C'gsl_vector_complex_float_view{
{-# LINE 368 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_complex_float_view'vector :: C'gsl_vector_complex_float
{-# LINE 369 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 370 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_complex_long_double = C'gsl_vector_complex_long_double{
{-# LINE 372 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_complex_long_double'size :: CSize
{-# LINE 373 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex_long_double'stride :: CSize
{-# LINE 374 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex_long_double'data :: Ptr CLDouble
{-# LINE 375 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex_long_double'block :: Ptr C'gsl_block_complex_long_double
{-# LINE 376 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_complex_long_double'owner :: CInt
{-# LINE 377 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_complex_long_double where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_complex_long_double v0 v1 v2 v3 v4
  poke p (C'gsl_vector_complex_long_double v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 378 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_complex_long_double_const_view = C'gsl_vector_complex_long_double_const_view{
{-# LINE 380 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_complex_long_double_const_view'vector :: C'gsl_vector_complex_long_double
{-# LINE 381 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 382 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_complex_long_double_view = C'gsl_vector_complex_long_double_view{
{-# LINE 384 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_complex_long_double_view'vector :: C'gsl_vector_complex_long_double
{-# LINE 385 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 386 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_complex_view = C'gsl_vector_complex_view{
{-# LINE 388 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_complex_view'vector :: C'gsl_vector_complex
{-# LINE 389 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 390 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_const_view = C'gsl_vector_const_view{
{-# LINE 392 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_const_view'vector :: C'gsl_vector
{-# LINE 393 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 394 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_float = C'gsl_vector_float{
{-# LINE 396 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_float'size :: CSize
{-# LINE 397 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_float'stride :: CSize
{-# LINE 398 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_float'data :: Ptr CFloat
{-# LINE 399 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_float'block :: Ptr C'gsl_block_float
{-# LINE 400 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_float'owner :: CInt
{-# LINE 401 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_float where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_float v0 v1 v2 v3 v4
  poke p (C'gsl_vector_float v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 402 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_float_const_view = C'gsl_vector_float_const_view{
{-# LINE 404 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_float_const_view'vector :: C'gsl_vector_float
{-# LINE 405 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 406 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_float_view = C'gsl_vector_float_view{
{-# LINE 408 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_float_view'vector :: C'gsl_vector_float
{-# LINE 409 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 410 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_int = C'gsl_vector_int{
{-# LINE 412 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_int'size :: CSize
{-# LINE 413 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_int'stride :: CSize
{-# LINE 414 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_int'data :: Ptr CInt
{-# LINE 415 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_int'block :: Ptr C'gsl_block_int
{-# LINE 416 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_int'owner :: CInt
{-# LINE 417 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_int where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_int v0 v1 v2 v3 v4
  poke p (C'gsl_vector_int v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 418 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_int_const_view = C'gsl_vector_int_const_view{
{-# LINE 420 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_int_const_view'vector :: C'gsl_vector_int
{-# LINE 421 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 422 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_int_view = C'gsl_vector_int_view{
{-# LINE 424 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_int_view'vector :: C'gsl_vector_int
{-# LINE 425 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 426 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_long = C'gsl_vector_long{
{-# LINE 428 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_long'size :: CSize
{-# LINE 429 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_long'stride :: CSize
{-# LINE 430 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_long'data :: Ptr CLong
{-# LINE 431 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_long'block :: Ptr C'gsl_block_long
{-# LINE 432 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_long'owner :: CInt
{-# LINE 433 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_long where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_long v0 v1 v2 v3 v4
  poke p (C'gsl_vector_long v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 434 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_long_const_view = C'gsl_vector_long_const_view{
{-# LINE 436 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_long_const_view'vector :: C'gsl_vector_long
{-# LINE 437 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 438 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_long_double = C'gsl_vector_long_double{
{-# LINE 440 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_long_double'size :: CSize
{-# LINE 441 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_long_double'stride :: CSize
{-# LINE 442 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_long_double'data :: Ptr CLDouble
{-# LINE 443 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_long_double'block :: Ptr C'gsl_block_long_double
{-# LINE 444 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_long_double'owner :: CInt
{-# LINE 445 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_long_double where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_long_double v0 v1 v2 v3 v4
  poke p (C'gsl_vector_long_double v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 446 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_long_double_const_view = C'gsl_vector_long_double_const_view{
{-# LINE 448 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_long_double_const_view'vector :: C'gsl_vector_long_double
{-# LINE 449 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 450 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_long_double_view = C'gsl_vector_long_double_view{
{-# LINE 452 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_long_double_view'vector :: C'gsl_vector_long_double
{-# LINE 453 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 454 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_long_view = C'gsl_vector_long_view{
{-# LINE 456 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_long_view'vector :: C'gsl_vector_long
{-# LINE 457 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 458 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_short = C'gsl_vector_short{
{-# LINE 460 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_short'size :: CSize
{-# LINE 461 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_short'stride :: CSize
{-# LINE 462 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_short'data :: Ptr CShort
{-# LINE 463 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_short'block :: Ptr C'gsl_block_short
{-# LINE 464 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_short'owner :: CInt
{-# LINE 465 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_short where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_short v0 v1 v2 v3 v4
  poke p (C'gsl_vector_short v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 466 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_short_const_view = C'gsl_vector_short_const_view{
{-# LINE 468 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_short_const_view'vector :: C'gsl_vector_short
{-# LINE 469 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 470 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_short_view = C'gsl_vector_short_view{
{-# LINE 472 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_short_view'vector :: C'gsl_vector_short
{-# LINE 473 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 474 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_uchar = C'gsl_vector_uchar{
{-# LINE 476 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_uchar'size :: CSize
{-# LINE 477 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_uchar'stride :: CSize
{-# LINE 478 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_uchar'data :: Ptr CUChar
{-# LINE 479 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_uchar'block :: Ptr C'gsl_block_uchar
{-# LINE 480 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_uchar'owner :: CInt
{-# LINE 481 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_uchar where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_uchar v0 v1 v2 v3 v4
  poke p (C'gsl_vector_uchar v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 482 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_uchar_const_view = C'gsl_vector_uchar_const_view{
{-# LINE 484 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_uchar_const_view'vector :: C'gsl_vector_uchar
{-# LINE 485 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 486 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_uchar_view = C'gsl_vector_uchar_view{
{-# LINE 488 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_uchar_view'vector :: C'gsl_vector_uchar
{-# LINE 489 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 490 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_uint = C'gsl_vector_uint{
{-# LINE 492 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_uint'size :: CSize
{-# LINE 493 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_uint'stride :: CSize
{-# LINE 494 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_uint'data :: Ptr CUInt
{-# LINE 495 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_uint'block :: Ptr C'gsl_block_uint
{-# LINE 496 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_uint'owner :: CInt
{-# LINE 497 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_uint where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_uint v0 v1 v2 v3 v4
  poke p (C'gsl_vector_uint v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 498 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_uint_const_view = C'gsl_vector_uint_const_view{
{-# LINE 500 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_uint_const_view'vector :: C'gsl_vector_uint
{-# LINE 501 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 502 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_uint_view = C'gsl_vector_uint_view{
{-# LINE 504 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_uint_view'vector :: C'gsl_vector_uint
{-# LINE 505 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 506 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_ulong = C'gsl_vector_ulong{
{-# LINE 508 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_ulong'size :: CSize
{-# LINE 509 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_ulong'stride :: CSize
{-# LINE 510 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_ulong'data :: Ptr CULong
{-# LINE 511 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_ulong'block :: Ptr C'gsl_block_ulong
{-# LINE 512 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_ulong'owner :: CInt
{-# LINE 513 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_ulong where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_ulong v0 v1 v2 v3 v4
  poke p (C'gsl_vector_ulong v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 514 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_ulong_const_view = C'gsl_vector_ulong_const_view{
{-# LINE 516 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_ulong_const_view'vector :: C'gsl_vector_ulong
{-# LINE 517 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 518 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_ulong_view = C'gsl_vector_ulong_view{
{-# LINE 520 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_ulong_view'vector :: C'gsl_vector_ulong
{-# LINE 521 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 522 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_ushort = C'gsl_vector_ushort{
{-# LINE 524 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_ushort'size :: CSize
{-# LINE 525 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_ushort'stride :: CSize
{-# LINE 526 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_ushort'data :: Ptr CUShort
{-# LINE 527 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_ushort'block :: Ptr C'gsl_block_ushort
{-# LINE 528 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}
,
  c'gsl_vector_ushort'owner :: CInt
{-# LINE 529 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'gsl_vector_ushort where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'gsl_vector_ushort v0 v1 v2 v3 v4
  poke p (C'gsl_vector_ushort v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 530 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_ushort_const_view = C'gsl_vector_ushort_const_view{
{-# LINE 532 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_ushort_const_view'vector :: C'gsl_vector_ushort
{-# LINE 533 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 534 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_ushort_view = C'gsl_vector_ushort_view{
{-# LINE 536 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_ushort_view'vector :: C'gsl_vector_ushort
{-# LINE 537 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 538 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

data C'gsl_vector_view = C'gsl_vector_view{
{-# LINE 540 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

  c'gsl_vector_view'vector :: C'gsl_vector
{-# LINE 541 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}

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

{-# LINE 542 "src/Bindings/Gsl/VectorsAndMatrices/DataTypes.hsc" #-}