bindings-libzip-0.11: Low level bindings to libzip.

Safe HaskellSafe-Inferred

Bindings.LibZip

Description

This module provides automatic low-level bindings to libzip library, version 0.11. See also:

Higher-level interface is provided by a separate LibZip package:

Documentation

data C'zip Source

Constructors

C'zip 

data C'zip_file Source

Constructors

C'zip_file 

data C'zip_source Source

Constructors

C'zip_source 

type C'zip_flags_t = CUIntSource

c'ZIP_CREATE :: Num a => aSource

c'ZIP_EXCL :: Num a => aSource

c'ZIP_CHECKCONS :: Num a => aSource

c'ZIP_TRUNCATE :: Num a => aSource

c'ZIP_FL_NOCASE :: Num a => aSource

c'ZIP_FL_NODIR :: Num a => aSource

c'ZIP_FL_LOCAL :: Num a => aSource

c'ZIP_ER_OK :: Num a => aSource

c'ZIP_ER_RENAME :: Num a => aSource

c'ZIP_ER_CLOSE :: Num a => aSource

c'ZIP_ER_SEEK :: Num a => aSource

c'ZIP_ER_READ :: Num a => aSource

c'ZIP_ER_WRITE :: Num a => aSource

c'ZIP_ER_CRC :: Num a => aSource

c'ZIP_ER_NOENT :: Num a => aSource

c'ZIP_ER_EXISTS :: Num a => aSource

c'ZIP_ER_OPEN :: Num a => aSource

c'ZIP_ER_ZLIB :: Num a => aSource

c'ZIP_ER_MEMORY :: Num a => aSource

c'ZIP_ER_EOF :: Num a => aSource

c'ZIP_ER_INVAL :: Num a => aSource

c'ZIP_ER_NOZIP :: Num a => aSource

c'ZIP_ER_INCONS :: Num a => aSource

c'ZIP_ER_REMOVE :: Num a => aSource

c'ZIP_ER_RDONLY :: Num a => aSource

c'ZIP_ET_NONE :: Num a => aSource

c'ZIP_ET_SYS :: Num a => aSource

c'ZIP_ET_ZLIB :: Num a => aSource

c'ZIP_CM_STORE :: Num a => aSource

c'ZIP_CM_SHRINK :: Num a => aSource

c'ZIP_CM_BZIP2 :: Num a => aSource

c'ZIP_CM_LZMA :: Num a => aSource

c'ZIP_CM_TERSE :: Num a => aSource

c'ZIP_CM_LZ77 :: Num a => aSource

c'ZIP_CM_PPMD :: Num a => aSource

c'ZIP_EM_NONE :: Num a => aSource

type C'zip_source_callback = FunPtr (Ptr () -> Ptr () -> CULLong -> C'zip_source_cmd -> IO CULLong)Source

mk'zip_source_callback :: (Ptr () -> Ptr () -> CULLong -> C'zip_source_cmd -> IO CULLong) -> IO C'zip_source_callbackSource

mK'zip_source_callback :: C'zip_source_callback -> Ptr () -> Ptr () -> CULLong -> C'zip_source_cmd -> IO CULLongSource

c'ZIP_STAT_NAME :: Num a => aSource

c'ZIP_STAT_SIZE :: Num a => aSource

c'ZIP_STAT_CRC :: Num a => aSource

data C'time_t Source

Constructors

C'time_t 

data C'zip_stat Source

Constructors

C'zip_stat 

Fields

c'zip_stat'valid :: CULLong
 
c'zip_stat'name :: Ptr CChar
 
c'zip_stat'index :: CULLong
 
c'zip_stat'size :: CULLong
 
c'zip_stat'comp_size :: CULLong
 
c'zip_stat'mtime :: CTime
 
c'zip_stat'crc :: CUInt
 
c'zip_stat'comp_method :: CUShort
 
c'zip_stat'encryption_method :: CUShort
 
c'zip_stat'flags :: CUInt
 

Instances

Eq C'zip_stat 
Show C'zip_stat 
Storable C'zip_stat 

p'zip_stat'valid :: Ptr C'zip_stat -> Ptr CULLongSource

p'zip_stat'name :: Ptr C'zip_stat -> Ptr (Ptr CChar)Source

p'zip_stat'index :: Ptr C'zip_stat -> Ptr CULLongSource

p'zip_stat'size :: Ptr C'zip_stat -> Ptr CULLongSource

p'zip_stat'crc :: Ptr C'zip_stat -> Ptr CUIntSource

c'zip_add :: Ptr C'zip -> CString -> Ptr C'zip_source -> IO CLLongSource

c'zip_add_dir :: Ptr C'zip -> CString -> IO CLLongSource

c'zip_get_file_comment :: Ptr C'zip -> CULLong -> Ptr CInt -> CInt -> IO CStringSource

p'zip_add :: FunPtr (Ptr C'zip -> CString -> Ptr C'zip_source -> IO CLLong)Source

p'zip_add_dir :: FunPtr (Ptr C'zip -> CString -> IO CLLong)Source

c'zip_rename :: Ptr C'zip -> CULLong -> CString -> IO CIntSource

p'zip_get_file_comment :: FunPtr (Ptr C'zip -> CULLong -> Ptr CInt -> CInt -> IO CString)Source

p'zip_get_num_files :: FunPtr (Ptr C'zip -> IO CInt)Source

c'zip_replace :: Ptr C'zip -> CULLong -> Ptr C'zip_source -> IO CIntSource

c'zip_set_file_comment :: Ptr C'zip -> CULLong -> CString -> CInt -> IO CIntSource

p'zip_rename :: FunPtr (Ptr C'zip -> CULLong -> CString -> IO CInt)Source

p'zip_replace :: FunPtr (Ptr C'zip -> CULLong -> Ptr C'zip_source -> IO CInt)Source

p'zip_set_file_comment :: FunPtr (Ptr C'zip -> CULLong -> CString -> CInt -> IO CInt)Source

c'zip_archive_set_tempdir :: Ptr C'zip -> CString -> IO CIntSource

c'zip_file_add :: Ptr C'zip -> CString -> Ptr C'zip_source -> C'zip_flags_t -> IO CLLongSource

p'zip_archive_set_tempdir :: FunPtr (Ptr C'zip -> CString -> IO CInt)Source

c'zip_dir_add :: Ptr C'zip -> CString -> C'zip_flags_t -> IO CLLongSource

c'zip_close :: Ptr C'zip -> IO CIntSource

p'zip_file_add :: FunPtr (Ptr C'zip -> CString -> Ptr C'zip_source -> C'zip_flags_t -> IO CLLong)Source

c'zip_discard :: Ptr C'zip -> IO ()Source

p'zip_dir_add :: FunPtr (Ptr C'zip -> CString -> C'zip_flags_t -> IO CLLong)Source

p'zip_close :: FunPtr (Ptr C'zip -> IO CInt)Source

c'zip_delete :: Ptr C'zip -> CULLong -> IO CIntSource

p'zip_discard :: FunPtr (Ptr C'zip -> IO ())Source

c'zip_file_extra_field_delete :: Ptr C'zip -> CULLong -> CUShort -> C'zip_flags_t -> IO CIntSource

p'zip_delete :: FunPtr (Ptr C'zip -> CULLong -> IO CInt)Source

c'zip_file_extra_field_delete_by_id :: Ptr C'zip -> CULLong -> CUShort -> CUShort -> C'zip_flags_t -> IO CIntSource

p'zip_file_extra_field_delete :: FunPtr (Ptr C'zip -> CULLong -> CUShort -> C'zip_flags_t -> IO CInt)Source

c'zip_error_get :: Ptr C'zip -> Ptr CInt -> Ptr CInt -> IO ()Source

p'zip_file_extra_field_delete_by_id :: FunPtr (Ptr C'zip -> CULLong -> CUShort -> CUShort -> C'zip_flags_t -> IO CInt)Source

p'zip_error_clear :: FunPtr (Ptr C'zip -> IO ())Source

c'zip_error_to_str :: Ptr CChar -> CULLong -> CInt -> CInt -> IO CIntSource

p'zip_error_get :: FunPtr (Ptr C'zip -> Ptr CInt -> Ptr CInt -> IO ())Source

p'zip_error_get_sys_type :: FunPtr (CInt -> IO CInt)Source

c'zip_fclose :: Ptr C'zip_file -> IO CIntSource

c'zip_fdopen :: CInt -> CInt -> Ptr CInt -> IO (Ptr C'zip)Source

p'zip_error_to_str :: FunPtr (Ptr CChar -> CULLong -> CInt -> CInt -> IO CInt)Source

p'zip_fclose :: FunPtr (Ptr C'zip_file -> IO CInt)Source

c'zip_file_error_get :: Ptr C'zip_file -> Ptr CInt -> Ptr CInt -> IO ()Source

p'zip_fdopen :: FunPtr (CInt -> CInt -> Ptr CInt -> IO (Ptr C'zip))Source

p'zip_file_error_clear :: FunPtr (Ptr C'zip_file -> IO ())Source

p'zip_file_error_get :: FunPtr (Ptr C'zip_file -> Ptr CInt -> Ptr CInt -> IO ())Source

c'zip_fopen :: Ptr C'zip -> CString -> C'zip_flags_t -> IO (Ptr C'zip_file)Source

p'zip_file_strerror :: FunPtr (Ptr C'zip_file -> IO CString)Source

c'zip_fopen_encrypted :: Ptr C'zip -> CString -> C'zip_flags_t -> CString -> IO (Ptr C'zip_file)Source

c'zip_fopen_index :: Ptr C'zip -> CULLong -> C'zip_flags_t -> IO (Ptr C'zip_file)Source

p'zip_fopen :: FunPtr (Ptr C'zip -> CString -> C'zip_flags_t -> IO (Ptr C'zip_file))Source

c'zip_fopen_index_encrypted :: Ptr C'zip -> CULLong -> C'zip_flags_t -> CString -> IO (Ptr C'zip_file)Source

p'zip_fopen_encrypted :: FunPtr (Ptr C'zip -> CString -> C'zip_flags_t -> CString -> IO (Ptr C'zip_file))Source

c'zip_fread :: Ptr C'zip_file -> Ptr () -> CULLong -> IO CLLongSource

p'zip_fopen_index :: FunPtr (Ptr C'zip -> CULLong -> C'zip_flags_t -> IO (Ptr C'zip_file))Source

c'zip_get_archive_comment :: Ptr C'zip -> Ptr CInt -> C'zip_flags_t -> IO CStringSource

p'zip_fopen_index_encrypted :: FunPtr (Ptr C'zip -> CULLong -> C'zip_flags_t -> CString -> IO (Ptr C'zip_file))Source

p'zip_fread :: FunPtr (Ptr C'zip_file -> Ptr () -> CULLong -> IO CLLong)Source

p'zip_get_archive_comment :: FunPtr (Ptr C'zip -> Ptr CInt -> C'zip_flags_t -> IO CString)Source

c'zip_file_get_comment :: Ptr C'zip -> CULLong -> Ptr CUInt -> C'zip_flags_t -> IO CStringSource

c'zip_file_extra_field_get :: Ptr C'zip -> CULLong -> CUShort -> Ptr CUShort -> Ptr CUShort -> C'zip_flags_t -> IO (Ptr CUChar)Source

p'zip_file_get_comment :: FunPtr (Ptr C'zip -> CULLong -> Ptr CUInt -> C'zip_flags_t -> IO CString)Source

c'zip_file_extra_field_get_by_id :: Ptr C'zip -> CULLong -> CUShort -> CUShort -> Ptr CUShort -> C'zip_flags_t -> IO (Ptr CUChar)Source

c'zip_file_extra_fields_count :: Ptr C'zip -> CULLong -> C'zip_flags_t -> IO CShortSource

p'zip_file_extra_field_get :: FunPtr (Ptr C'zip -> CULLong -> CUShort -> Ptr CUShort -> Ptr CUShort -> C'zip_flags_t -> IO (Ptr CUChar))Source

c'zip_file_extra_fields_count_by_id :: Ptr C'zip -> CULLong -> CUShort -> C'zip_flags_t -> IO CShortSource

p'zip_file_extra_field_get_by_id :: FunPtr (Ptr C'zip -> CULLong -> CUShort -> CUShort -> Ptr CUShort -> C'zip_flags_t -> IO (Ptr CUChar))Source

c'zip_get_name :: Ptr C'zip -> CULLong -> C'zip_flags_t -> IO CStringSource

p'zip_file_extra_fields_count :: FunPtr (Ptr C'zip -> CULLong -> C'zip_flags_t -> IO CShort)Source

p'zip_file_extra_fields_count_by_id :: FunPtr (Ptr C'zip -> CULLong -> CUShort -> C'zip_flags_t -> IO CShort)Source

c'zip_name_locate :: Ptr C'zip -> CString -> C'zip_flags_t -> IO CLLongSource

p'zip_get_name :: FunPtr (Ptr C'zip -> CULLong -> C'zip_flags_t -> IO CString)Source

c'zip_open :: CString -> CInt -> Ptr CInt -> IO (Ptr C'zip)Source

p'zip_get_num_entries :: FunPtr (Ptr C'zip -> C'zip_flags_t -> IO CLLong)Source

c'zip_file_rename :: Ptr C'zip -> CULLong -> CString -> C'zip_flags_t -> IO CIntSource

p'zip_name_locate :: FunPtr (Ptr C'zip -> CString -> C'zip_flags_t -> IO CLLong)Source

p'zip_open :: FunPtr (CString -> CInt -> Ptr CInt -> IO (Ptr C'zip))Source

c'zip_file_replace :: Ptr C'zip -> CULLong -> Ptr C'zip_source -> C'zip_flags_t -> IO CIntSource

c'zip_set_archive_comment :: Ptr C'zip -> CString -> CUShort -> IO CIntSource

p'zip_file_rename :: FunPtr (Ptr C'zip -> CULLong -> CString -> C'zip_flags_t -> IO CInt)Source

c'zip_set_archive_flag :: Ptr C'zip -> C'zip_flags_t -> CInt -> IO CIntSource

p'zip_file_replace :: FunPtr (Ptr C'zip -> CULLong -> Ptr C'zip_source -> C'zip_flags_t -> IO CInt)Source

c'zip_set_default_password :: Ptr C'zip -> CString -> IO CIntSource

p'zip_set_archive_comment :: FunPtr (Ptr C'zip -> CString -> CUShort -> IO CInt)Source

p'zip_set_archive_flag :: FunPtr (Ptr C'zip -> C'zip_flags_t -> CInt -> IO CInt)Source

c'zip_file_set_comment :: Ptr C'zip -> CULLong -> CString -> CUShort -> C'zip_flags_t -> IO CIntSource

p'zip_set_default_password :: FunPtr (Ptr C'zip -> CString -> IO CInt)Source

c'zip_set_file_compression :: Ptr C'zip -> CULLong -> CInt -> CUInt -> IO CIntSource

p'zip_file_set_comment :: FunPtr (Ptr C'zip -> CULLong -> CString -> CUShort -> C'zip_flags_t -> IO CInt)Source

c'zip_file_extra_field_set :: Ptr C'zip -> CULLong -> CUShort -> CUShort -> Ptr CUChar -> CUShort -> C'zip_flags_t -> IO CIntSource

p'zip_set_file_compression :: FunPtr (Ptr C'zip -> CULLong -> CInt -> CUInt -> IO CInt)Source

c'zip_source_buffer :: Ptr C'zip -> Ptr () -> CULLong -> CInt -> IO (Ptr C'zip_source)Source

c'zip_source_file :: Ptr C'zip -> CString -> CULLong -> CLLong -> IO (Ptr C'zip_source)Source

p'zip_file_extra_field_set :: FunPtr (Ptr C'zip -> CULLong -> CUShort -> CUShort -> Ptr CUChar -> CUShort -> C'zip_flags_t -> IO CInt)Source

c'zip_source_filep :: Ptr C'zip -> Ptr CFile -> CULLong -> CLLong -> IO (Ptr C'zip_source)Source

p'zip_source_buffer :: FunPtr (Ptr C'zip -> Ptr () -> CULLong -> CInt -> IO (Ptr C'zip_source))Source

p'zip_source_file :: FunPtr (Ptr C'zip -> CString -> CULLong -> CLLong -> IO (Ptr C'zip_source))Source

p'zip_source_filep :: FunPtr (Ptr C'zip -> Ptr CFile -> CULLong -> CLLong -> IO (Ptr C'zip_source))Source

p'zip_source_free :: FunPtr (Ptr C'zip_source -> IO ())Source

c'zip_source_zip :: Ptr C'zip -> Ptr C'zip -> CULLong -> C'zip_flags_t -> CULLong -> CLLong -> IO (Ptr C'zip_source)Source

c'zip_stat :: Ptr C'zip -> CString -> C'zip_flags_t -> Ptr C'zip_stat -> IO CIntSource

p'zip_source_function :: FunPtr (Ptr C'zip -> C'zip_source_callback -> Ptr () -> IO (Ptr C'zip_source))Source

c'zip_stat_index :: Ptr C'zip -> CULLong -> C'zip_flags_t -> Ptr C'zip_stat -> IO CIntSource

p'zip_source_zip :: FunPtr (Ptr C'zip -> Ptr C'zip -> CULLong -> C'zip_flags_t -> CULLong -> CLLong -> IO (Ptr C'zip_source))Source

p'zip_stat :: FunPtr (Ptr C'zip -> CString -> C'zip_flags_t -> Ptr C'zip_stat -> IO CInt)Source

c'zip_strerror :: Ptr C'zip -> IO CStringSource

p'zip_stat_index :: FunPtr (Ptr C'zip -> CULLong -> C'zip_flags_t -> Ptr C'zip_stat -> IO CInt)Source

p'zip_stat_init :: FunPtr (Ptr C'zip_stat -> IO ())Source

c'zip_unchange :: Ptr C'zip -> CULLong -> IO CIntSource

p'zip_strerror :: FunPtr (Ptr C'zip -> IO CString)Source

p'zip_unchange :: FunPtr (Ptr C'zip -> CULLong -> IO CInt)Source

p'zip_unchange_all :: FunPtr (Ptr C'zip -> IO CInt)Source

p'zip_unchange_archive :: FunPtr (Ptr C'zip -> IO CInt)Source