{-# LINE 1 "Codec/Archive/LibZip/LowLevel.hsc" #-}

{-# LINE 2 "Codec/Archive/LibZip/LowLevel.hsc" #-}

{-# LINE 3 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- | This module provides automatic low-level bindings to @libzip@ library.
-- See also:
--
--   * @libzip@ documention: <http://nih.at/libzip/libzip.html> and @zip.h@
--
--   * @bindings-DSL@ documentation:
--     <http://bitbucket.org/mauricio/bindings-dsl/wiki/Home>

module Codec.Archive.LibZip.LowLevel 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.Alloc (alloca)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word

{-# LINE 14 "Codec/Archive/LibZip/LowLevel.hsc" #-}

data C'zip = C'zip

{-# LINE 16 "Codec/Archive/LibZip/LowLevel.hsc" #-}
data C'zip_file = C'zip_file

{-# LINE 17 "Codec/Archive/LibZip/LowLevel.hsc" #-}
data C'zip_source = C'zip_source

{-# LINE 18 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- flags for zip_open

c'ZIP_CREATE = 1
c'ZIP_CREATE :: (Num a) => a

{-# LINE 22 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_EXCL = 2
c'ZIP_EXCL :: (Num a) => a

{-# LINE 23 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CHECKCONS = 4
c'ZIP_CHECKCONS :: (Num a) => a

{-# LINE 24 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- flags for zip_name_locate, zip_fopen, zip_stat, ...

c'ZIP_FL_NOCASE = 1
c'ZIP_FL_NOCASE :: (Num a) => a

{-# LINE 28 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_FL_NODIR = 2
c'ZIP_FL_NODIR :: (Num a) => a

{-# LINE 29 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_FL_COMPRESSED = 4
c'ZIP_FL_COMPRESSED :: (Num a) => a

{-# LINE 30 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_FL_UNCHANGED = 8
c'ZIP_FL_UNCHANGED :: (Num a) => a

{-# LINE 31 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_FL_RECOMPRESS = 16
c'ZIP_FL_RECOMPRESS :: (Num a) => a

{-# LINE 32 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- archive global flags flags

c'ZIP_AFL_TORRENT = 1
c'ZIP_AFL_TORRENT :: (Num a) => a

{-# LINE 36 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- libzip error codes

c'ZIP_ER_OK = 0
c'ZIP_ER_OK :: (Num a) => a

{-# LINE 40 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_MULTIDISK = 1
c'ZIP_ER_MULTIDISK :: (Num a) => a

{-# LINE 41 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_RENAME = 2
c'ZIP_ER_RENAME :: (Num a) => a

{-# LINE 42 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_CLOSE = 3
c'ZIP_ER_CLOSE :: (Num a) => a

{-# LINE 43 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_SEEK = 4
c'ZIP_ER_SEEK :: (Num a) => a

{-# LINE 44 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_READ = 5
c'ZIP_ER_READ :: (Num a) => a

{-# LINE 45 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_WRITE = 6
c'ZIP_ER_WRITE :: (Num a) => a

{-# LINE 46 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_CRC = 7
c'ZIP_ER_CRC :: (Num a) => a

{-# LINE 47 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_ZIPCLOSED = 8
c'ZIP_ER_ZIPCLOSED :: (Num a) => a

{-# LINE 48 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_NOENT = 9
c'ZIP_ER_NOENT :: (Num a) => a

{-# LINE 49 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_EXISTS = 10
c'ZIP_ER_EXISTS :: (Num a) => a

{-# LINE 50 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_OPEN = 11
c'ZIP_ER_OPEN :: (Num a) => a

{-# LINE 51 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_TMPOPEN = 12
c'ZIP_ER_TMPOPEN :: (Num a) => a

{-# LINE 52 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_ZLIB = 13
c'ZIP_ER_ZLIB :: (Num a) => a

{-# LINE 53 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_MEMORY = 14
c'ZIP_ER_MEMORY :: (Num a) => a

{-# LINE 54 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_CHANGED = 15
c'ZIP_ER_CHANGED :: (Num a) => a

{-# LINE 55 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_COMPNOTSUPP = 16
c'ZIP_ER_COMPNOTSUPP :: (Num a) => a

{-# LINE 56 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_EOF = 17
c'ZIP_ER_EOF :: (Num a) => a

{-# LINE 57 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_INVAL = 18
c'ZIP_ER_INVAL :: (Num a) => a

{-# LINE 58 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_NOZIP = 19
c'ZIP_ER_NOZIP :: (Num a) => a

{-# LINE 59 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_INTERNAL = 20
c'ZIP_ER_INTERNAL :: (Num a) => a

{-# LINE 60 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_INCONS = 21
c'ZIP_ER_INCONS :: (Num a) => a

{-# LINE 61 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_REMOVE = 22
c'ZIP_ER_REMOVE :: (Num a) => a

{-# LINE 62 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ER_DELETED = 23
c'ZIP_ER_DELETED :: (Num a) => a

{-# LINE 63 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- type of system error value

c'ZIP_ET_NONE = 0
c'ZIP_ET_NONE :: (Num a) => a

{-# LINE 67 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ET_SYS = 1
c'ZIP_ET_SYS :: (Num a) => a

{-# LINE 68 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_ET_ZLIB = 2
c'ZIP_ET_ZLIB :: (Num a) => a

{-# LINE 69 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- compression methods

c'ZIP_CM_DEFAULT = -1
c'ZIP_CM_DEFAULT :: (Num a) => a

{-# LINE 73 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_STORE = 0
c'ZIP_CM_STORE :: (Num a) => a

{-# LINE 74 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_SHRINK = 1
c'ZIP_CM_SHRINK :: (Num a) => a

{-# LINE 75 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_REDUCE_1 = 2
c'ZIP_CM_REDUCE_1 :: (Num a) => a

{-# LINE 76 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_REDUCE_2 = 3
c'ZIP_CM_REDUCE_2 :: (Num a) => a

{-# LINE 77 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_REDUCE_3 = 4
c'ZIP_CM_REDUCE_3 :: (Num a) => a

{-# LINE 78 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_REDUCE_4 = 5
c'ZIP_CM_REDUCE_4 :: (Num a) => a

{-# LINE 79 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_IMPLODE = 6
c'ZIP_CM_IMPLODE :: (Num a) => a

{-# LINE 80 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_DEFLATE = 8
c'ZIP_CM_DEFLATE :: (Num a) => a

{-# LINE 81 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_DEFLATE64 = 9
c'ZIP_CM_DEFLATE64 :: (Num a) => a

{-# LINE 82 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_PKWARE_IMPLODE = 10
c'ZIP_CM_PKWARE_IMPLODE :: (Num a) => a

{-# LINE 83 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_BZIP2 = 12
c'ZIP_CM_BZIP2 :: (Num a) => a

{-# LINE 84 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_LZMA = 14
c'ZIP_CM_LZMA :: (Num a) => a

{-# LINE 85 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_TERSE = 18
c'ZIP_CM_TERSE :: (Num a) => a

{-# LINE 86 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_LZ77 = 19
c'ZIP_CM_LZ77 :: (Num a) => a

{-# LINE 87 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_WAVPACK = 97
c'ZIP_CM_WAVPACK :: (Num a) => a

{-# LINE 88 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_CM_PPMD = 98
c'ZIP_CM_PPMD :: (Num a) => a

{-# LINE 89 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- encryption methods

c'ZIP_EM_NONE = 0
c'ZIP_EM_NONE :: (Num a) => a

{-# LINE 93 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_EM_TRAD_PKWARE = 1
c'ZIP_EM_TRAD_PKWARE :: (Num a) => a

{-# LINE 94 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_EM_UNKNOWN = 65535
c'ZIP_EM_UNKNOWN :: (Num a) => a

{-# LINE 95 "Codec/Archive/LibZip/LowLevel.hsc" #-}

type C'zip_source_cmd = CUInt

{-# LINE 97 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_SOURCE_OPEN = 0
c'ZIP_SOURCE_OPEN :: (Num a) => a

{-# LINE 98 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_SOURCE_READ = 1
c'ZIP_SOURCE_READ :: (Num a) => a

{-# LINE 99 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_SOURCE_CLOSE = 2
c'ZIP_SOURCE_CLOSE :: (Num a) => a

{-# LINE 100 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_SOURCE_STAT = 3
c'ZIP_SOURCE_STAT :: (Num a) => a

{-# LINE 101 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_SOURCE_ERROR = 4
c'ZIP_SOURCE_ERROR :: (Num a) => a

{-# LINE 102 "Codec/Archive/LibZip/LowLevel.hsc" #-}
c'ZIP_SOURCE_FREE = 5
c'ZIP_SOURCE_FREE :: (Num a) => a

{-# LINE 103 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- typedef ssize_t (*zip_source_callback)(void *state, void *data,
--                                        size_t len, enum zip_source_cmd cmd);
type C'zip_source_callback = FunPtr (Ptr () -> Ptr () -> CSize -> C'zip_source_cmd -> IO CSize)
foreign import ccall "wrapper" mk'zip_source_callback
  :: (Ptr () -> Ptr () -> CSize -> C'zip_source_cmd -> IO CSize) -> IO C'zip_source_callback
foreign import ccall "dynamic" mK'zip_source_callback
  :: C'zip_source_callback -> (Ptr () -> Ptr () -> CSize -> C'zip_source_cmd -> IO CSize)

{-# LINE 107 "Codec/Archive/LibZip/LowLevel.hsc" #-}

data C'time_t = C'time_t

{-# LINE 109 "Codec/Archive/LibZip/LowLevel.hsc" #-}

data C'zip_stat = C'zip_stat{
{-# LINE 111 "Codec/Archive/LibZip/LowLevel.hsc" #-}

  c'zip_stat'name :: Ptr CChar
{-# LINE 112 "Codec/Archive/LibZip/LowLevel.hsc" #-}
,
  c'zip_stat'index :: CInt
{-# LINE 113 "Codec/Archive/LibZip/LowLevel.hsc" #-}
,
  c'zip_stat'crc :: CUInt
{-# LINE 114 "Codec/Archive/LibZip/LowLevel.hsc" #-}
,
  c'zip_stat'mtime :: CTime
{-# LINE 115 "Codec/Archive/LibZip/LowLevel.hsc" #-}
,
  c'zip_stat'size :: CSize
{-# LINE 116 "Codec/Archive/LibZip/LowLevel.hsc" #-}
,
  c'zip_stat'comp_size :: CSize
{-# LINE 117 "Codec/Archive/LibZip/LowLevel.hsc" #-}
,
  c'zip_stat'comp_method :: CUShort
{-# LINE 118 "Codec/Archive/LibZip/LowLevel.hsc" #-}
,
  c'zip_stat'encryption_method :: CUShort
{-# LINE 119 "Codec/Archive/LibZip/LowLevel.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'zip_stat where
  sizeOf _ = 36
  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 24
    v6 <- peekByteOff p 32
    v7 <- peekByteOff p 34
    return $ C'zip_stat v0 v1 v2 v3 v4 v5 v6 v7
  poke p (C'zip_stat v0 v1 v2 v3 v4 v5 v6 v7) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 24 v5
    pokeByteOff p 32 v6
    pokeByteOff p 34 v7
    return ()

{-# LINE 120 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_add(struct zip *, const char *, struct zip_source *);
foreign import ccall "zip_add" c'zip_add
  :: Ptr C'zip -> CString -> Ptr C'zip_source -> IO CInt
foreign import ccall "&zip_add" p'zip_add
  :: FunPtr (Ptr C'zip -> CString -> Ptr C'zip_source -> IO CInt)

{-# LINE 123 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_add_dir(struct zip *, const char *);
foreign import ccall "zip_add_dir" c'zip_add_dir
  :: Ptr C'zip -> CString -> IO CInt
foreign import ccall "&zip_add_dir" p'zip_add_dir
  :: FunPtr (Ptr C'zip -> CString -> IO CInt)

{-# LINE 126 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_close(struct zip *);
foreign import ccall "zip_close" c'zip_close
  :: Ptr C'zip -> IO CInt
foreign import ccall "&zip_close" p'zip_close
  :: FunPtr (Ptr C'zip -> IO CInt)

{-# LINE 129 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_delete(struct zip *, int);
foreign import ccall "zip_delete" c'zip_delete
  :: Ptr C'zip -> CInt -> IO CInt
foreign import ccall "&zip_delete" p'zip_delete
  :: FunPtr (Ptr C'zip -> CInt -> IO CInt)

{-# LINE 132 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- void zip_error_clear(struct zip *);
foreign import ccall "zip_error_clear" c'zip_error_clear
  :: Ptr C'zip -> IO ()
foreign import ccall "&zip_error_clear" p'zip_error_clear
  :: FunPtr (Ptr C'zip -> IO ())

{-# LINE 135 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- void zip_error_get(struct zip *, int *, int *);
foreign import ccall "zip_error_get" c'zip_error_get
  :: Ptr C'zip -> Ptr CInt -> Ptr CInt -> IO ()
foreign import ccall "&zip_error_get" p'zip_error_get
  :: FunPtr (Ptr C'zip -> Ptr CInt -> Ptr CInt -> IO ())

{-# LINE 138 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_error_get_sys_type(int);
foreign import ccall "zip_error_get_sys_type" c'zip_error_get_sys_type
  :: CInt -> IO CInt
foreign import ccall "&zip_error_get_sys_type" p'zip_error_get_sys_type
  :: FunPtr (CInt -> IO CInt)

{-# LINE 141 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_error_to_str(char *, size_t, int, int);
foreign import ccall "zip_error_to_str" c'zip_error_to_str
  :: Ptr Char -> CSize -> CInt -> CInt -> IO CInt
foreign import ccall "&zip_error_to_str" p'zip_error_to_str
  :: FunPtr (Ptr Char -> CSize -> CInt -> CInt -> IO CInt)

{-# LINE 144 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_fclose(struct zip_file *);
foreign import ccall "zip_fclose" c'zip_fclose
  :: Ptr C'zip_file -> IO CInt
foreign import ccall "&zip_fclose" p'zip_fclose
  :: FunPtr (Ptr C'zip_file -> IO CInt)

{-# LINE 147 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- void zip_file_error_clear(struct zip_file *);
foreign import ccall "zip_file_error_clear" c'zip_file_error_clear
  :: Ptr C'zip_file -> IO ()
foreign import ccall "&zip_file_error_clear" p'zip_file_error_clear
  :: FunPtr (Ptr C'zip_file -> IO ())

{-# LINE 150 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- void zip_file_error_get(struct zip_file *, int *, int *);
foreign import ccall "zip_file_error_get" c'zip_file_error_get
  :: Ptr C'zip_file -> Ptr CInt -> Ptr CInt -> IO ()
foreign import ccall "&zip_file_error_get" p'zip_file_error_get
  :: FunPtr (Ptr C'zip_file -> Ptr CInt -> Ptr CInt -> IO ())

{-# LINE 153 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- const char *zip_file_strerror(struct zip_file *);
foreign import ccall "zip_file_strerror" c'zip_file_strerror
  :: Ptr C'zip_file -> IO CString
foreign import ccall "&zip_file_strerror" p'zip_file_strerror
  :: FunPtr (Ptr C'zip_file -> IO CString)

{-# LINE 156 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- struct zip_file *zip_fopen(struct zip *, const char *, int);
foreign import ccall "zip_fopen" c'zip_fopen
  :: Ptr C'zip -> CString -> CInt -> IO (Ptr C'zip_file)
foreign import ccall "&zip_fopen" p'zip_fopen
  :: FunPtr (Ptr C'zip -> CString -> CInt -> IO (Ptr C'zip_file))

{-# LINE 159 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- struct zip_file *zip_fopen_index(struct zip *, int, int);
foreign import ccall "zip_fopen_index" c'zip_fopen_index
  :: Ptr C'zip -> CInt -> CInt -> IO (Ptr C'zip_file)
foreign import ccall "&zip_fopen_index" p'zip_fopen_index
  :: FunPtr (Ptr C'zip -> CInt -> CInt -> IO (Ptr C'zip_file))

{-# LINE 162 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- ssize_t zip_fread(struct zip_file *, void *, size_t);
foreign import ccall "zip_fread" c'zip_fread
  :: Ptr C'zip_file -> Ptr () -> CSize -> IO CSize
foreign import ccall "&zip_fread" p'zip_fread
  :: FunPtr (Ptr C'zip_file -> Ptr () -> CSize -> IO CSize)

{-# LINE 165 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- const char *zip_get_archive_comment(struct zip *, int *, int);
foreign import ccall "zip_get_archive_comment" c'zip_get_archive_comment
  :: Ptr C'zip -> Ptr CInt -> CInt -> IO CString
foreign import ccall "&zip_get_archive_comment" p'zip_get_archive_comment
  :: FunPtr (Ptr C'zip -> Ptr CInt -> CInt -> IO CString)

{-# LINE 168 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_get_archive_flag(struct zip *, int, int);
foreign import ccall "zip_get_archive_flag" c'zip_get_archive_flag
  :: Ptr C'zip -> CInt -> CInt -> IO CInt
foreign import ccall "&zip_get_archive_flag" p'zip_get_archive_flag
  :: FunPtr (Ptr C'zip -> CInt -> CInt -> IO CInt)

{-# LINE 171 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- const char *zip_get_file_comment(struct zip *, int, int *, int);
foreign import ccall "zip_get_file_comment" c'zip_get_file_comment
  :: Ptr C'zip -> CInt -> Ptr CInt -> CInt -> IO CString
foreign import ccall "&zip_get_file_comment" p'zip_get_file_comment
  :: FunPtr (Ptr C'zip -> CInt -> Ptr CInt -> CInt -> IO CString)

{-# LINE 174 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- const char *zip_get_name(struct zip *, int, int);
foreign import ccall "zip_get_name" c'zip_get_name
  :: Ptr C'zip -> CInt -> CInt -> IO CString
foreign import ccall "&zip_get_name" p'zip_get_name
  :: FunPtr (Ptr C'zip -> CInt -> CInt -> IO CString)

{-# LINE 177 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_get_num_files(struct zip *);
foreign import ccall "zip_get_num_files" c'zip_get_num_files
  :: Ptr C'zip -> IO CInt
foreign import ccall "&zip_get_num_files" p'zip_get_num_files
  :: FunPtr (Ptr C'zip -> IO CInt)

{-# LINE 180 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_name_locate(struct zip *, const char *, int);
foreign import ccall "zip_name_locate" c'zip_name_locate
  :: Ptr C'zip -> CString -> CInt -> IO CInt
foreign import ccall "&zip_name_locate" p'zip_name_locate
  :: FunPtr (Ptr C'zip -> CString -> CInt -> IO CInt)

{-# LINE 183 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- struct zip *zip_open(const char *, int, int *);
foreign import ccall "zip_open" c'zip_open
  :: CString -> CInt -> Ptr CInt -> IO (Ptr C'zip)
foreign import ccall "&zip_open" p'zip_open
  :: FunPtr (CString -> CInt -> Ptr CInt -> IO (Ptr C'zip))

{-# LINE 186 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_rename(struct zip *, int, const char *);
foreign import ccall "zip_rename" c'zip_rename
  :: Ptr C'zip -> CInt -> CString -> IO CInt
foreign import ccall "&zip_rename" p'zip_rename
  :: FunPtr (Ptr C'zip -> CInt -> CString -> IO CInt)

{-# LINE 189 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_replace(struct zip *, int, struct zip_source *);
foreign import ccall "zip_replace" c'zip_replace
  :: Ptr C'zip -> CInt -> Ptr C'zip_source -> IO CInt
foreign import ccall "&zip_replace" p'zip_replace
  :: FunPtr (Ptr C'zip -> CInt -> Ptr C'zip_source -> IO CInt)

{-# LINE 192 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_set_archive_comment(struct zip *, const char *, int);
foreign import ccall "zip_set_archive_comment" c'zip_set_archive_comment
  :: Ptr C'zip -> CString -> CInt -> IO CInt
foreign import ccall "&zip_set_archive_comment" p'zip_set_archive_comment
  :: FunPtr (Ptr C'zip -> CString -> CInt -> IO CInt)

{-# LINE 195 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_set_archive_flag(struct zip *, int, int);
foreign import ccall "zip_set_archive_flag" c'zip_set_archive_flag
  :: Ptr C'zip -> CInt -> CInt -> IO CInt
foreign import ccall "&zip_set_archive_flag" p'zip_set_archive_flag
  :: FunPtr (Ptr C'zip -> CInt -> CInt -> IO CInt)

{-# LINE 198 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_set_file_comment(struct zip *, int, const char *, int);
foreign import ccall "zip_set_file_comment" c'zip_set_file_comment
  :: Ptr C'zip -> CInt -> CString -> CInt -> IO CInt
foreign import ccall "&zip_set_file_comment" p'zip_set_file_comment
  :: FunPtr (Ptr C'zip -> CInt -> CString -> CInt -> IO CInt)

{-# LINE 201 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- struct zip_source *zip_source_buffer(struct zip *, const void *, off_t, int);
foreign import ccall "zip_source_buffer" c'zip_source_buffer
  :: Ptr C'zip -> Ptr () -> CSize -> CInt -> IO (Ptr C'zip_source)
foreign import ccall "&zip_source_buffer" p'zip_source_buffer
  :: FunPtr (Ptr C'zip -> Ptr () -> CSize -> CInt -> IO (Ptr C'zip_source))

{-# LINE 204 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- struct zip_source *zip_source_file(struct zip *, const char *, off_t, off_t);
foreign import ccall "zip_source_file" c'zip_source_file
  :: Ptr C'zip -> CString -> CSize -> CSize -> IO (Ptr C'zip_source)
foreign import ccall "&zip_source_file" p'zip_source_file
  :: FunPtr (Ptr C'zip -> CString -> CSize -> CSize -> IO (Ptr C'zip_source))

{-# LINE 207 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- struct zip_source *zip_source_filep(struct zip *, FILE *, off_t, off_t);
foreign import ccall "zip_source_filep" c'zip_source_filep
  :: Ptr C'zip -> Ptr CFile -> CSize -> CSize -> IO (Ptr C'zip_source)
foreign import ccall "&zip_source_filep" p'zip_source_filep
  :: FunPtr (Ptr C'zip -> Ptr CFile -> CSize -> CSize -> IO (Ptr C'zip_source))

{-# LINE 210 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- void zip_source_free(struct zip_source *);
foreign import ccall "zip_source_free" c'zip_source_free
  :: Ptr C'zip_source -> IO ()
foreign import ccall "&zip_source_free" p'zip_source_free
  :: FunPtr (Ptr C'zip_source -> IO ())

{-# LINE 213 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- struct zip_source *zip_source_function(struct zip *, zip_source_callback, void *);
foreign import ccall "zip_source_function" c'zip_source_function
  :: Ptr C'zip -> C'zip_source_callback -> Ptr () -> IO (Ptr C'zip_source)
foreign import ccall "&zip_source_function" p'zip_source_function
  :: FunPtr (Ptr C'zip -> C'zip_source_callback -> Ptr () -> IO (Ptr C'zip_source))

{-# LINE 216 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- struct zip_source *zip_source_zip(struct zip *, struct zip *, int, int, off_t, off_t);
foreign import ccall "zip_source_zip" c'zip_source_zip
  :: Ptr C'zip -> Ptr C'zip -> CInt -> CInt -> CSize -> CSize -> IO (Ptr C'zip_source)
foreign import ccall "&zip_source_zip" p'zip_source_zip
  :: FunPtr (Ptr C'zip -> Ptr C'zip -> CInt -> CInt -> CSize -> CSize -> IO (Ptr C'zip_source))

{-# LINE 219 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_stat(struct zip *, const char *, int, struct zip_stat *);
foreign import ccall "zip_stat" c'zip_stat
  :: Ptr C'zip -> CString -> CInt -> Ptr C'zip_stat -> IO CInt
foreign import ccall "&zip_stat" p'zip_stat
  :: FunPtr (Ptr C'zip -> CString -> CInt -> Ptr C'zip_stat -> IO CInt)

{-# LINE 222 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_stat_index(struct zip *, int, int, struct zip_stat *);
foreign import ccall "zip_stat_index" c'zip_stat_index
  :: Ptr C'zip -> CInt -> CInt -> Ptr C'zip_stat -> IO CInt
foreign import ccall "&zip_stat_index" p'zip_stat_index
  :: FunPtr (Ptr C'zip -> CInt -> CInt -> Ptr C'zip_stat -> IO CInt)

{-# LINE 225 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- void zip_stat_init(struct zip_stat *);
foreign import ccall "zip_stat_init" c'zip_stat_init
  :: Ptr C'zip_stat -> IO ()
foreign import ccall "&zip_stat_init" p'zip_stat_init
  :: FunPtr (Ptr C'zip_stat -> IO ())

{-# LINE 228 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- const char *zip_strerror(struct zip *);
foreign import ccall "zip_strerror" c'zip_strerror
  :: Ptr C'zip -> IO CString
foreign import ccall "&zip_strerror" p'zip_strerror
  :: FunPtr (Ptr C'zip -> IO CString)

{-# LINE 231 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_unchange(struct zip *, int);
foreign import ccall "zip_unchange" c'zip_unchange
  :: Ptr C'zip -> CInt -> IO CInt
foreign import ccall "&zip_unchange" p'zip_unchange
  :: FunPtr (Ptr C'zip -> CInt -> IO CInt)

{-# LINE 234 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_unchange_all(struct zip *);
foreign import ccall "zip_unchange_all" c'zip_unchange_all
  :: Ptr C'zip -> IO CInt
foreign import ccall "&zip_unchange_all" p'zip_unchange_all
  :: FunPtr (Ptr C'zip -> IO CInt)

{-# LINE 237 "Codec/Archive/LibZip/LowLevel.hsc" #-}

-- int zip_unchange_archive(struct zip *);
foreign import ccall "zip_unchange_archive" c'zip_unchange_archive
  :: Ptr C'zip -> IO CInt
foreign import ccall "&zip_unchange_archive" p'zip_unchange_archive
  :: FunPtr (Ptr C'zip -> IO CInt)

{-# LINE 240 "Codec/Archive/LibZip/LowLevel.hsc" #-}