{-# LANGUAGE DeriveDataTypeable #-} -- | See [zbar project home](https://github.com/mchehab/zbar) for more. module ZBar.Foreign ( -- * Types ZbarColor (..) , ZbarSymbolType (..) , ZbarError (..) , ZbarConfig (..) -- * Type synonyms , ZbarSymbolPtr , ZbarSymbolSetPtr , ZbarImagePtr , ZbarProcessorPtr , ZbarVideoPtr , ZbarWindowPtr , ZbarImageScannerPtr , ZbarScannerPtr , ZbarDecoderPtr -- * Abstract Types , ZbarSymbol , ZbarSymbolSet , ZbarImage , ZbarProcessor , ZbarVideo , ZbarWindow , ZbarImageScanner , ZbarScanner , ZbarDecoder -- * Callback types , ZbarImageCleanupHandlerT , ZbarImageDataHandlerT , ZbarDecoderHandlerT -- * Callbacks , mkCleanupCallback , mkDataCallback , mkDecoderCallback -- * Functions , zbarVersion , zbarSetVerbosity , zbarIncreaseVerbosity , zbarGetSymbolName , zbarGetAddonName , zbarParseConfig , zbarSymbolRef , zbarSymbolGetType , zbarSymbolGetData , zbarSymbolGetDataLength , zbarSymbolGetQuality , zbarSymbolGetCount , zbarSymbolGetLocSize , zbarSymbolGetLocX , zbarSymbolGetLocY , zbarSymbolNext , zbarSymbolGetComponents , zbarSymbolFirstComponent , zbarSymbolXml , zbarSymbolSetRef , zbarSymbolSetGetSize , zbarSymbolSetFirstSymbol , zbarImageCreate , zbarImageDestroy , zbarImageRef , zbarImageConvert , zbarImageConvertResize , zbarImageGetFormat , zbarImageGetSequence , zbarImageGetWidth , zbarImageGetHeight , zbarImageGetData , zbarImageGetDataLength , zbarImageGetSymbols , zbarImageSetSymbols , zbarImageFirstSymbol , zbarImageSetFormat , zbarImageSetSequence , zbarImageSetSize , zbarImageSetData , zbarImageFreeData , zbarImageSetUserdata , zbarImageGetUserdata , zbarImageWrite , zbarImageRead , zbarProcessorCreate , zbarProcessorDestroy , zbarProcessorInit , zbarProcessorRequestSize , zbarProcessorRequestInterface , zbarProcessorRequestIomode , zbarProcessorForceFormat , zbarProcessorSetDataHandler , zbarProcessorSetUserdata , zbarProcessorGetUserdata , zbarProcessorSetConfig , zbarProcessorParseConfig , zbarProcessorIsVisible , zbarProcessorSetVisible , zbarProcessorSetActive , zbarProcessorGetResults , zbarProcessorUserWait , zbarProcessOne , zbarProcessImage , zbarProcessorErrorSpew , zbarProcessorErrorString , zbarProcessorGetErrorCode , zbarVideoCreate , zbarVideoGetFd , zbarVideoRequestSize , zbarVideoRequestInterface , zbarVideoRequestIomode , zbarVideoGetWidth , zbarVideoGetHeight , zbarVideoInit , zbarVideoEnable , zbarVideoNextImage , zbarVideoErrorSpew , zbarVideoErrorString , zbarVideoGetErrorCode , zbarWindowCreate , zbarWindowDestroy , zbarWindowAttach , zbarWindowGetOverlay , zbarWindowSetOverlay , zbarWindowDraw , zbarWindowRedraw , zbarWindowResize , zbarWindowErrorSpew , zbarWindowErrorString , zbarWindowGetErrorCode , zbarNegotiateFormat , zbarImageScannerCreate , zbarImageScannerDestroy , zbarImageScannerSetDataHandler , zbarImageScannerSetConfig , zbarImageScannerParseConfig , zbarImageScannerEnableCache , zbarImageScannerRecycleImage , zbarImageScannerGetResults , zbarScanImage , zbarDecoderCreate , zbarDecoderDestroy , zbarDecoderSetConfig , zbarDecoderParseConfig , zbarDecoderReset , zbarDecoderNewScan , zbarDecodeWidth , zbarDecoderGetColor , zbarDecoderGetData , zbarDecoderGetDataLength , zbarDecoderGetType , zbarDecoderSetHandler , zbarDecoderSetUserdata , zbarDecoderGetUserdata , zbarScannerCreate , zbarScannerDestroy , zbarScannerReset , zbarScannerNewScan , zbarScannerFlush , zbarScanY , zbarScanRgb24 , zbarScannerGetWidth , zbarScannerGetEdge , zbarScannerGetColor ) where import Control.Exception (Exception) import Data.Typeable (Typeable) import Foreign.C.String (CString) import Foreign.C.Types (CInt, CUChar, CUInt, CULong) import Foreign.Marshal.Alloc (alloca) import Foreign.Ptr (castFunPtr, castPtr, FunPtr, Ptr) import Foreign.Storable (peek) #include {# enum zbar_color_e as ZbarColor {underscoreToCase} deriving (Eq) #} {# enum zbar_symbol_type_e as ZbarSymbolType {underscoreToCase} deriving (Eq) #} {# enum zbar_error_e as ZbarError {underscoreToCase} deriving (Show, Typeable) #} {# enum zbar_config_e as ZbarConfig {underscoreToCase} #} instance Exception ZbarError where {# fun pure zbar_version as ^ { alloca- `CUInt' peek*, alloca- `CUInt' peek*, alloca- `CUInt' peek*} -> `()' #} {# fun zbar_set_verbosity as ^ { `CInt' } -> `()' #} {# fun zbar_increase_verbosity as ^ { } -> `()' #} {# fun pure zbar_get_symbol_name as ^ { `ZbarSymbolType' } -> `String' #} {# fun pure zbar_get_addon_name as ^ { `ZbarSymbolType' } -> `String' #} -- abstract/opaque types data ZbarSymbol data ZbarSymbolSet data ZbarImage data ZbarProcessor data ZbarVideo data ZbarWindow data ZbarImageScanner data ZbarDecoder data ZbarScanner {# pointer *zbar_symbol_t as ZbarSymbolPtr -> ZbarSymbol #} {# pointer *zbar_symbol_set_t as ZbarSymbolSetPtr -> ZbarSymbolSet #} {# pointer *zbar_image_t as ZbarImagePtr -> ZbarImage #} {# pointer *zbar_processor_t as ZbarProcessorPtr -> ZbarProcessor #} {# pointer *zbar_video_t as ZbarVideoPtr -> ZbarVideo #} {# pointer *zbar_window_t as ZbarWindowPtr -> ZbarWindow #} {# pointer *zbar_image_scanner_t as ZbarImageScannerPtr -> ZbarImageScanner #} {# pointer *zbar_decoder_t as ZbarDecoderPtr -> ZbarDecoder #} {# pointer *zbar_scanner_t as ZbarScannerPtr -> ZbarScanner #} {# fun zbar_parse_config as ^ { `String', castPtr `Ptr ZbarSymbolType', castPtr `Ptr ZbarConfig', id `Ptr CInt' } -> `Bool' #} {# fun zbar_symbol_ref as ^ { `ZbarSymbolPtr', `CInt' } -> `()' #} {# fun zbar_symbol_get_type as ^ { `ZbarSymbolPtr' } -> `ZbarSymbolType' #} {# fun zbar_symbol_get_data as ^ { `ZbarSymbolPtr' } -> `CString' #} {# fun zbar_symbol_get_data_length as ^ { `ZbarSymbolPtr' } -> `CUInt' #} {# fun zbar_symbol_get_quality as ^ { `ZbarSymbolPtr' } -> `CInt' #} {# fun zbar_symbol_get_count as ^ { `ZbarSymbolPtr' } -> `CInt' #} {# fun zbar_symbol_get_loc_size as ^ { `ZbarSymbolPtr' } -> `CUInt' #} {# fun zbar_symbol_get_loc_x as ^ { `ZbarSymbolPtr', `CUInt' } -> `CInt' #} {# fun zbar_symbol_get_loc_y as ^ { `ZbarSymbolPtr', `CUInt' } -> `CInt' #} {# fun zbar_symbol_next as ^ { `ZbarSymbolPtr' } -> `ZbarSymbolPtr' #} {# fun zbar_symbol_get_components as ^ { `ZbarSymbolPtr' } -> `ZbarSymbolSetPtr' #} {# fun zbar_symbol_first_component as ^ { `ZbarSymbolPtr' } -> `ZbarSymbolPtr' #} {# fun zbar_symbol_xml as ^ { `ZbarSymbolPtr', castPtr `Ptr (Ptr a)', id `Ptr CUInt' } -> `Ptr a' castPtr #} {# fun zbar_symbol_set_ref as ^ { `ZbarSymbolSetPtr', `CInt' } -> `()' #} {# fun zbar_symbol_set_get_size as ^ { `ZbarSymbolSetPtr' } -> `CInt' #} {# fun zbar_symbol_set_first_symbol as ^ { `ZbarSymbolSetPtr' } -> `ZbarSymbolPtr' #} type ZbarImageCleanupHandlerT = ZbarImagePtr -> IO () type ZbarImageDataHandlerT a = ZbarImagePtr -> Ptr a -> IO () type ZbarDecoderHandlerT = ZbarDecoderPtr -> IO () foreign import ccall "wrapper" mkCleanupCallback :: ZbarImageCleanupHandlerT -> IO (FunPtr ZbarImageCleanupHandlerT) foreign import ccall "wrapper" mkDataCallback :: ZbarImageDataHandlerT a -> IO (FunPtr (ZbarImageDataHandlerT a)) foreign import ccall "wrapper" mkDecoderCallback :: ZbarDecoderHandlerT -> IO (FunPtr ZbarDecoderHandlerT) {# fun zbar_image_create as ^ { } -> `ZbarImagePtr' #} {# fun zbar_image_destroy as ^ { `ZbarImagePtr' } -> `()' #} {# fun zbar_image_ref as ^ { `ZbarImagePtr', `CInt' } -> `()' #} {# fun zbar_image_convert as ^ { `ZbarImagePtr', `CULong' } -> `ZbarImagePtr' #} {# fun zbar_image_convert_resize as ^ { `ZbarImagePtr', `CULong', `CUInt', `CUInt' } -> `ZbarImagePtr' #} {# fun zbar_image_get_format as ^ { `ZbarImagePtr' } -> `CULong' #} {# fun zbar_image_get_sequence as ^ { `ZbarImagePtr' } -> `CUInt' #} {# fun zbar_image_get_width as ^ { `ZbarImagePtr' } -> `CUInt' #} {# fun zbar_image_get_height as ^ { `ZbarImagePtr' } -> `CUInt' #} {# fun zbar_image_get_data as ^ { `ZbarImagePtr' } -> `Ptr a' castPtr #} {# fun zbar_image_get_data_length as ^ { `ZbarImagePtr' } -> `CUInt' #} {# fun zbar_image_get_symbols as ^ { `ZbarImagePtr' } -> `ZbarSymbolSetPtr' #} {# fun zbar_image_set_symbols as ^ { `ZbarImagePtr', `ZbarSymbolSetPtr' } -> `()' #} {# fun zbar_image_first_symbol as ^ { `ZbarImagePtr' } -> `ZbarSymbolPtr' #} {# fun zbar_image_set_format as ^ { `ZbarImagePtr', `CULong' } -> `()' #} {# fun zbar_image_set_sequence as ^ { `ZbarImagePtr', `CUInt' } -> `()' #} {# fun zbar_image_set_size as ^ { `ZbarImagePtr', `CUInt', `CUInt' } -> `()' #} {# fun zbar_image_set_data as ^ { `ZbarImagePtr', castPtr `Ptr a', `CULong', id `FunPtr ZbarImageCleanupHandlerT' } -> `()' #} {# fun zbar_image_free_data as ^ { `ZbarImagePtr' } -> `()' #} {# fun zbar_image_set_userdata as ^ { `ZbarImagePtr', castPtr `Ptr a' } -> `()' #} {# fun zbar_image_get_userdata as ^ { `ZbarImagePtr' } -> `Ptr a' castPtr #} {# fun zbar_image_write as ^ { `ZbarImagePtr', `String' } -> `CInt' #} {# fun zbar_image_read as ^ { `String' } -> `ZbarImagePtr' #} {# fun zbar_processor_create as ^ { `Bool' } -> `ZbarProcessorPtr' #} {# fun zbar_processor_destroy as ^ { `ZbarProcessorPtr' } -> `()' #} {# fun zbar_processor_init as ^ { `ZbarProcessorPtr', `CString', `Bool' } -> `CInt' #} {# fun zbar_processor_request_size as ^ { `ZbarProcessorPtr', `CUInt', `CUInt' } -> `CInt' #} {# fun zbar_processor_request_interface as ^ { `ZbarProcessorPtr', `CInt' } -> `CInt' #} {# fun zbar_processor_request_iomode as ^ { `ZbarProcessorPtr', `CInt' } -> `CInt' #} {# fun zbar_processor_force_format as ^ { `ZbarProcessorPtr', `CULong', `CULong' } -> `CInt' #} {# fun zbar_processor_set_data_handler as ^ { `ZbarProcessorPtr', castFunPtr `FunPtr (ZbarImageDataHandlerT a)', castPtr `Ptr a' } -> `FunPtr (ZbarImageDataHandlerT a)' castFunPtr #} {# fun zbar_processor_set_userdata as ^ { `ZbarProcessorPtr', castPtr `Ptr a' } -> `()' #} {# fun zbar_processor_get_userdata as ^ { `ZbarProcessorPtr' } -> `Ptr a' castPtr #} {# fun zbar_processor_set_config as ^ { `ZbarProcessorPtr', `ZbarSymbolType', `ZbarConfig', `CInt' } -> `Bool' #} {# fun zbar_processor_parse_config as ^ { `ZbarProcessorPtr', `String' } -> `Bool' #} {# fun zbar_processor_is_visible as ^ { `ZbarProcessorPtr' } -> `CInt' #} {# fun zbar_processor_set_visible as ^ { `ZbarProcessorPtr', `CInt' } -> `CInt' #} {# fun zbar_processor_set_active as ^ { `ZbarProcessorPtr', `CInt' } -> `CInt' #} {# fun zbar_processor_get_results as ^ { `ZbarProcessorPtr' } -> `ZbarSymbolSetPtr' #} {# fun zbar_processor_user_wait as ^ { `ZbarProcessorPtr', `CInt' } -> `CInt' #} {# fun zbar_process_one as ^ { `ZbarProcessorPtr', `CInt' } -> `CInt' #} {# fun zbar_process_image as ^ { `ZbarProcessorPtr', `ZbarImagePtr' } -> `CInt' #} {# fun zbar_processor_error_spew as ^ { `ZbarProcessorPtr', `CInt' } -> `CInt' #} {# fun zbar_processor_error_string as ^ { `ZbarProcessorPtr', `CInt' } -> `String' #} {# fun zbar_processor_get_error_code as ^ { `ZbarProcessorPtr' } -> `ZbarError' #} {# fun zbar_video_create as ^ { } -> `ZbarVideoPtr' #} {# fun zbar_video_get_fd as ^ { `ZbarVideoPtr' } -> `CInt' #} {# fun zbar_video_request_size as ^ { `ZbarVideoPtr', `CUInt', `CUInt' } -> `CInt' #} {# fun zbar_video_request_interface as ^ { `ZbarVideoPtr', `CInt' } -> `CInt' #} {# fun zbar_video_request_iomode as ^ { `ZbarVideoPtr', `CInt' } -> `CInt' #} {# fun zbar_video_get_width as ^ { `ZbarVideoPtr' } -> `CInt' #} {# fun zbar_video_get_height as ^ { `ZbarVideoPtr' } -> `CInt' #} {# fun zbar_video_init as ^ { `ZbarVideoPtr', `CULong' } -> `CInt' #} {# fun zbar_video_enable as ^ { `ZbarVideoPtr', `CInt' } -> `CInt' #} {# fun zbar_video_next_image as ^ { `ZbarVideoPtr' } -> `ZbarImagePtr' #} {# fun zbar_video_error_spew as ^ { `ZbarVideoPtr', `CInt' } -> `CInt' #} {# fun zbar_video_error_string as ^ { `ZbarVideoPtr', `CInt' } -> `String' #} {# fun zbar_video_get_error_code as ^ { `ZbarVideoPtr' } -> `ZbarError' #} {# fun zbar_window_create as ^ { } -> `ZbarWindowPtr' #} {# fun zbar_window_destroy as ^ { `ZbarWindowPtr' } -> `()' #} {# fun zbar_window_attach as ^ { `ZbarWindowPtr', castPtr `Ptr a', `CULong' } -> `CInt' #} {# fun zbar_window_set_overlay as ^ { `ZbarWindowPtr', `CInt' } -> `()' #} {# fun zbar_window_get_overlay as ^ { `ZbarWindowPtr' } -> `CInt' #} {# fun zbar_window_draw as ^ { `ZbarWindowPtr', `ZbarImagePtr' } -> `CInt' #} {# fun zbar_window_redraw as ^ { `ZbarWindowPtr' } -> `CInt' #} {# fun zbar_window_resize as ^ { `ZbarWindowPtr', `CInt', `CInt' } -> `CInt' #} {# fun zbar_window_error_spew as ^ { `ZbarWindowPtr', `CInt' } -> `CInt' #} {# fun zbar_window_error_string as ^ { `ZbarWindowPtr', `CInt' } -> `String' #} {# fun zbar_window_get_error_code as ^ { `ZbarWindowPtr' } -> `ZbarError' #} {# fun zbar_negotiate_format as ^ { `ZbarVideoPtr', `ZbarWindowPtr' } -> `CInt' #} {# fun zbar_image_scanner_create as ^ { } -> `ZbarImageScannerPtr' #} {# fun zbar_image_scanner_destroy as ^ { `ZbarImageScannerPtr' } -> `()' #} {# fun zbar_image_scanner_set_data_handler as ^ { `ZbarImageScannerPtr' , castFunPtr `FunPtr (ZbarImageDataHandlerT a)' , castPtr `Ptr a' } -> `FunPtr (ZbarImageDataHandlerT a)' castFunPtr #} {# fun zbar_image_scanner_set_config as ^ { `ZbarImageScannerPtr' , `ZbarSymbolType' , `ZbarConfig' , `CInt' } -> `CInt' #} {# fun zbar_image_scanner_parse_config as ^ { `ZbarImageScannerPtr', `String' } -> `CInt' #} {# fun zbar_image_scanner_enable_cache as ^ { `ZbarImageScannerPtr', `Bool' } -> `()' #} {# fun zbar_image_scanner_recycle_image as ^ { `ZbarImageScannerPtr', `ZbarImagePtr' } -> `()' #} {# fun zbar_image_scanner_get_results as ^ { `ZbarImageScannerPtr' } -> `ZbarSymbolSetPtr' #} {# fun zbar_scan_image as ^ { `ZbarImageScannerPtr', `ZbarImagePtr' } -> `CInt' #} {# fun zbar_decoder_create as ^ { } -> `()' #} {# fun zbar_decoder_destroy as ^ { `ZbarDecoderPtr' } -> `()' #} {# fun zbar_decoder_set_config as ^ { `ZbarDecoderPtr', `ZbarSymbolType', `ZbarConfig', `CInt' } -> `CInt' #} {# fun zbar_decoder_parse_config as ^ { `ZbarDecoderPtr', `String' } -> `CInt' #} {# fun zbar_decoder_reset as ^ { `ZbarDecoderPtr' } -> `()' #} {# fun zbar_decoder_new_scan as ^ { `ZbarDecoderPtr' } -> `()' #} {# fun zbar_decode_width as ^ { `ZbarDecoderPtr', `CUInt' } -> `ZbarSymbolType' #} {# fun zbar_decoder_get_color as ^ { `ZbarDecoderPtr' } -> `ZbarColor' #} {# fun zbar_decoder_get_data as ^ { `ZbarDecoderPtr' } -> `Ptr a' castPtr #} {# fun zbar_decoder_get_data_length as ^ { `ZbarDecoderPtr' } -> `CUInt' #} {# fun zbar_decoder_get_type as ^ { `ZbarDecoderPtr' } -> `ZbarSymbolType' #} {# fun zbar_decoder_set_handler as ^ { `ZbarDecoderPtr', id `FunPtr ZbarDecoderHandlerT' } -> `FunPtr ZbarDecoderHandlerT' id #} {# fun zbar_decoder_set_userdata as ^ { `ZbarDecoderPtr', castPtr `Ptr a' } -> `()' #} {# fun zbar_decoder_get_userdata as ^ { `ZbarDecoderPtr' } -> `Ptr a' castPtr #} {# fun zbar_scanner_create as ^ { `ZbarDecoderPtr' } -> `ZbarScannerPtr' #} {# fun zbar_scanner_destroy as ^ { `ZbarScannerPtr' } -> `()' #} {# fun zbar_scanner_reset as ^ { `ZbarScannerPtr' } -> `ZbarSymbolType' #} {# fun zbar_scanner_new_scan as ^ { `ZbarScannerPtr' } -> `ZbarSymbolType' #} {# fun zbar_scanner_flush as ^ { `ZbarScannerPtr' } -> `ZbarSymbolType' #} {# fun zbar_scan_y as ^ { `ZbarScannerPtr', `CInt' } -> `ZbarSymbolType' #} {# fun zbar_scan_rgb24 as ^ { `ZbarScannerPtr', id `Ptr CUChar' } -> `ZbarSymbolType' #} {# fun zbar_scanner_get_width as ^ { `ZbarScannerPtr' } -> `CUInt' #} {# fun zbar_scanner_get_edge as ^ { `ZbarScannerPtr', `CUInt', `CInt' } -> `CUInt' #} {# fun zbar_scanner_get_color as ^ { `ZbarScannerPtr' } -> `ZbarColor' #}