{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
{-# HLINT ignore "Use camelCase" #-}
module Asapo.Raw.Common
( AsapoBool,
AsapoSourceCredentialsHandle (AsapoSourceCredentialsHandle),
AsapoMessageDataHandle (AsapoMessageDataHandle),
asapo_is_error,
AsapoSourceType,
asapo_string_c_str,
mkAsapoFreeWrapper,
asapo_message_data_get_as_chars,
asapo_free_stream_infos_handle,
asapo_new_string_handle,
asapo_free_string_handle,
asapo_free_stream_info_handle,
asapo_free_message_data_handle,
asapo_error_explain,
asapo_string_size,
AsapoErrorHandle (AsapoErrorHandle),
AsapoStreamInfosHandle (AsapoStreamInfosHandle),
AsapoStringHandle (AsapoStringHandle),
ConstCString,
asapo_free_source_credentials,
asapo_new_error_handle,
asapo_free_error_handle,
asapo_string_from_c_str,
asapo_new_handle,
asapo_free_handle,
asapo_new_message_data_handle,
asapo_create_source_credentials,
AsapoStreamInfoHandle (AsapoStreamInfoHandle),
asapo_stream_infos_get_item,
asapo_stream_info_get_last_id,
asapo_stream_info_get_name,
asapo_stream_info_get_finished,
asapo_stream_info_get_next_stream,
asapo_stream_info_get_timestamp_created,
asapo_stream_info_get_timestamp_last_entry,
kProcessed,
kRaw,
)
where
import Data.Functor ((<$>))
import Foreign (FunPtr, with)
import Foreign.C.ConstPtr (ConstPtr (ConstPtr))
import Foreign.C.String (CString)
import Foreign.C.Types (CChar, CInt (CInt), CSize (CSize), CULong (CULong))
import Foreign.Ptr (Ptr)
import Foreign.Storable (Storable)
import System.Clock (TimeSpec)
import System.IO (IO)
import Prelude ()
type ConstCString = ConstPtr CChar
type AsapoBool = CInt
newtype {-# CTYPE "asapo/common/common_c.h" "AsapoSourceCredentialsHandle" #-} AsapoSourceCredentialsHandle = AsapoSourceCredentialsHandle (Ptr ()) deriving (Ptr AsapoSourceCredentialsHandle -> IO AsapoSourceCredentialsHandle
Ptr AsapoSourceCredentialsHandle
-> Int -> IO AsapoSourceCredentialsHandle
Ptr AsapoSourceCredentialsHandle
-> Int -> AsapoSourceCredentialsHandle -> IO ()
Ptr AsapoSourceCredentialsHandle
-> AsapoSourceCredentialsHandle -> IO ()
AsapoSourceCredentialsHandle -> Int
(AsapoSourceCredentialsHandle -> Int)
-> (AsapoSourceCredentialsHandle -> Int)
-> (Ptr AsapoSourceCredentialsHandle
-> Int -> IO AsapoSourceCredentialsHandle)
-> (Ptr AsapoSourceCredentialsHandle
-> Int -> AsapoSourceCredentialsHandle -> IO ())
-> (forall b. Ptr b -> Int -> IO AsapoSourceCredentialsHandle)
-> (forall b.
Ptr b -> Int -> AsapoSourceCredentialsHandle -> IO ())
-> (Ptr AsapoSourceCredentialsHandle
-> IO AsapoSourceCredentialsHandle)
-> (Ptr AsapoSourceCredentialsHandle
-> AsapoSourceCredentialsHandle -> IO ())
-> Storable AsapoSourceCredentialsHandle
forall b. Ptr b -> Int -> IO AsapoSourceCredentialsHandle
forall b. Ptr b -> Int -> AsapoSourceCredentialsHandle -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: AsapoSourceCredentialsHandle -> Int
sizeOf :: AsapoSourceCredentialsHandle -> Int
$calignment :: AsapoSourceCredentialsHandle -> Int
alignment :: AsapoSourceCredentialsHandle -> Int
$cpeekElemOff :: Ptr AsapoSourceCredentialsHandle
-> Int -> IO AsapoSourceCredentialsHandle
peekElemOff :: Ptr AsapoSourceCredentialsHandle
-> Int -> IO AsapoSourceCredentialsHandle
$cpokeElemOff :: Ptr AsapoSourceCredentialsHandle
-> Int -> AsapoSourceCredentialsHandle -> IO ()
pokeElemOff :: Ptr AsapoSourceCredentialsHandle
-> Int -> AsapoSourceCredentialsHandle -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AsapoSourceCredentialsHandle
peekByteOff :: forall b. Ptr b -> Int -> IO AsapoSourceCredentialsHandle
$cpokeByteOff :: forall b. Ptr b -> Int -> AsapoSourceCredentialsHandle -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> AsapoSourceCredentialsHandle -> IO ()
$cpeek :: Ptr AsapoSourceCredentialsHandle -> IO AsapoSourceCredentialsHandle
peek :: Ptr AsapoSourceCredentialsHandle -> IO AsapoSourceCredentialsHandle
$cpoke :: Ptr AsapoSourceCredentialsHandle
-> AsapoSourceCredentialsHandle -> IO ()
poke :: Ptr AsapoSourceCredentialsHandle
-> AsapoSourceCredentialsHandle -> IO ()
Storable)
newtype {-# CTYPE "asapo/common/common_c.h" "AsapoErrorHandle" #-} AsapoErrorHandle = AsapoErrorHandle (Ptr ()) deriving (Ptr AsapoErrorHandle -> IO AsapoErrorHandle
Ptr AsapoErrorHandle -> Int -> IO AsapoErrorHandle
Ptr AsapoErrorHandle -> Int -> AsapoErrorHandle -> IO ()
Ptr AsapoErrorHandle -> AsapoErrorHandle -> IO ()
AsapoErrorHandle -> Int
(AsapoErrorHandle -> Int)
-> (AsapoErrorHandle -> Int)
-> (Ptr AsapoErrorHandle -> Int -> IO AsapoErrorHandle)
-> (Ptr AsapoErrorHandle -> Int -> AsapoErrorHandle -> IO ())
-> (forall b. Ptr b -> Int -> IO AsapoErrorHandle)
-> (forall b. Ptr b -> Int -> AsapoErrorHandle -> IO ())
-> (Ptr AsapoErrorHandle -> IO AsapoErrorHandle)
-> (Ptr AsapoErrorHandle -> AsapoErrorHandle -> IO ())
-> Storable AsapoErrorHandle
forall b. Ptr b -> Int -> IO AsapoErrorHandle
forall b. Ptr b -> Int -> AsapoErrorHandle -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: AsapoErrorHandle -> Int
sizeOf :: AsapoErrorHandle -> Int
$calignment :: AsapoErrorHandle -> Int
alignment :: AsapoErrorHandle -> Int
$cpeekElemOff :: Ptr AsapoErrorHandle -> Int -> IO AsapoErrorHandle
peekElemOff :: Ptr AsapoErrorHandle -> Int -> IO AsapoErrorHandle
$cpokeElemOff :: Ptr AsapoErrorHandle -> Int -> AsapoErrorHandle -> IO ()
pokeElemOff :: Ptr AsapoErrorHandle -> Int -> AsapoErrorHandle -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AsapoErrorHandle
peekByteOff :: forall b. Ptr b -> Int -> IO AsapoErrorHandle
$cpokeByteOff :: forall b. Ptr b -> Int -> AsapoErrorHandle -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> AsapoErrorHandle -> IO ()
$cpeek :: Ptr AsapoErrorHandle -> IO AsapoErrorHandle
peek :: Ptr AsapoErrorHandle -> IO AsapoErrorHandle
$cpoke :: Ptr AsapoErrorHandle -> AsapoErrorHandle -> IO ()
poke :: Ptr AsapoErrorHandle -> AsapoErrorHandle -> IO ()
Storable)
newtype {-# CTYPE "asapo/common/common_c.h" "AsapoStringHandle" #-} AsapoStringHandle = AsapoStringHandle (Ptr ()) deriving (Ptr AsapoStringHandle -> IO AsapoStringHandle
Ptr AsapoStringHandle -> Int -> IO AsapoStringHandle
Ptr AsapoStringHandle -> Int -> AsapoStringHandle -> IO ()
Ptr AsapoStringHandle -> AsapoStringHandle -> IO ()
AsapoStringHandle -> Int
(AsapoStringHandle -> Int)
-> (AsapoStringHandle -> Int)
-> (Ptr AsapoStringHandle -> Int -> IO AsapoStringHandle)
-> (Ptr AsapoStringHandle -> Int -> AsapoStringHandle -> IO ())
-> (forall b. Ptr b -> Int -> IO AsapoStringHandle)
-> (forall b. Ptr b -> Int -> AsapoStringHandle -> IO ())
-> (Ptr AsapoStringHandle -> IO AsapoStringHandle)
-> (Ptr AsapoStringHandle -> AsapoStringHandle -> IO ())
-> Storable AsapoStringHandle
forall b. Ptr b -> Int -> IO AsapoStringHandle
forall b. Ptr b -> Int -> AsapoStringHandle -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: AsapoStringHandle -> Int
sizeOf :: AsapoStringHandle -> Int
$calignment :: AsapoStringHandle -> Int
alignment :: AsapoStringHandle -> Int
$cpeekElemOff :: Ptr AsapoStringHandle -> Int -> IO AsapoStringHandle
peekElemOff :: Ptr AsapoStringHandle -> Int -> IO AsapoStringHandle
$cpokeElemOff :: Ptr AsapoStringHandle -> Int -> AsapoStringHandle -> IO ()
pokeElemOff :: Ptr AsapoStringHandle -> Int -> AsapoStringHandle -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AsapoStringHandle
peekByteOff :: forall b. Ptr b -> Int -> IO AsapoStringHandle
$cpokeByteOff :: forall b. Ptr b -> Int -> AsapoStringHandle -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> AsapoStringHandle -> IO ()
$cpeek :: Ptr AsapoStringHandle -> IO AsapoStringHandle
peek :: Ptr AsapoStringHandle -> IO AsapoStringHandle
$cpoke :: Ptr AsapoStringHandle -> AsapoStringHandle -> IO ()
poke :: Ptr AsapoStringHandle -> AsapoStringHandle -> IO ()
Storable)
asapo_new_string_handle :: IO AsapoStringHandle
asapo_new_string_handle :: IO AsapoStringHandle
asapo_new_string_handle = Ptr () -> AsapoStringHandle
AsapoStringHandle (Ptr () -> AsapoStringHandle)
-> IO (Ptr ()) -> IO AsapoStringHandle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (Ptr ())
asapo_new_handle
asapo_free_string_handle :: AsapoStringHandle -> IO ()
asapo_free_string_handle :: AsapoStringHandle -> IO ()
asapo_free_string_handle (AsapoStringHandle Ptr ()
ptr) = Ptr () -> (Ptr (Ptr ()) -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Ptr ()
ptr Ptr (Ptr ()) -> IO ()
asapo_free_handle
newtype {-# CTYPE "asapo/common/common_c.h" "AsapoStreamInfoHandle" #-} AsapoStreamInfoHandle = AsapoStreamInfoHandle (Ptr ()) deriving (Ptr AsapoStreamInfoHandle -> IO AsapoStreamInfoHandle
Ptr AsapoStreamInfoHandle -> Int -> IO AsapoStreamInfoHandle
Ptr AsapoStreamInfoHandle -> Int -> AsapoStreamInfoHandle -> IO ()
Ptr AsapoStreamInfoHandle -> AsapoStreamInfoHandle -> IO ()
AsapoStreamInfoHandle -> Int
(AsapoStreamInfoHandle -> Int)
-> (AsapoStreamInfoHandle -> Int)
-> (Ptr AsapoStreamInfoHandle -> Int -> IO AsapoStreamInfoHandle)
-> (Ptr AsapoStreamInfoHandle
-> Int -> AsapoStreamInfoHandle -> IO ())
-> (forall b. Ptr b -> Int -> IO AsapoStreamInfoHandle)
-> (forall b. Ptr b -> Int -> AsapoStreamInfoHandle -> IO ())
-> (Ptr AsapoStreamInfoHandle -> IO AsapoStreamInfoHandle)
-> (Ptr AsapoStreamInfoHandle -> AsapoStreamInfoHandle -> IO ())
-> Storable AsapoStreamInfoHandle
forall b. Ptr b -> Int -> IO AsapoStreamInfoHandle
forall b. Ptr b -> Int -> AsapoStreamInfoHandle -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: AsapoStreamInfoHandle -> Int
sizeOf :: AsapoStreamInfoHandle -> Int
$calignment :: AsapoStreamInfoHandle -> Int
alignment :: AsapoStreamInfoHandle -> Int
$cpeekElemOff :: Ptr AsapoStreamInfoHandle -> Int -> IO AsapoStreamInfoHandle
peekElemOff :: Ptr AsapoStreamInfoHandle -> Int -> IO AsapoStreamInfoHandle
$cpokeElemOff :: Ptr AsapoStreamInfoHandle -> Int -> AsapoStreamInfoHandle -> IO ()
pokeElemOff :: Ptr AsapoStreamInfoHandle -> Int -> AsapoStreamInfoHandle -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AsapoStreamInfoHandle
peekByteOff :: forall b. Ptr b -> Int -> IO AsapoStreamInfoHandle
$cpokeByteOff :: forall b. Ptr b -> Int -> AsapoStreamInfoHandle -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> AsapoStreamInfoHandle -> IO ()
$cpeek :: Ptr AsapoStreamInfoHandle -> IO AsapoStreamInfoHandle
peek :: Ptr AsapoStreamInfoHandle -> IO AsapoStreamInfoHandle
$cpoke :: Ptr AsapoStreamInfoHandle -> AsapoStreamInfoHandle -> IO ()
poke :: Ptr AsapoStreamInfoHandle -> AsapoStreamInfoHandle -> IO ()
Storable)
asapo_free_stream_info_handle :: AsapoStreamInfoHandle -> IO ()
asapo_free_stream_info_handle :: AsapoStreamInfoHandle -> IO ()
asapo_free_stream_info_handle (AsapoStreamInfoHandle Ptr ()
ptr) = Ptr () -> (Ptr (Ptr ()) -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Ptr ()
ptr Ptr (Ptr ()) -> IO ()
asapo_free_handle
asapo_free_stream_infos_handle :: AsapoStreamInfosHandle -> IO ()
asapo_free_stream_infos_handle :: AsapoStreamInfosHandle -> IO ()
asapo_free_stream_infos_handle (AsapoStreamInfosHandle Ptr ()
ptr) = Ptr () -> (Ptr (Ptr ()) -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Ptr ()
ptr Ptr (Ptr ()) -> IO ()
asapo_free_handle
newtype {-# CTYPE "asapo/common/common_c.h" "AsapoStreamInfosHandle" #-} AsapoStreamInfosHandle = AsapoStreamInfosHandle (Ptr ()) deriving (Ptr AsapoStreamInfosHandle -> IO AsapoStreamInfosHandle
Ptr AsapoStreamInfosHandle -> Int -> IO AsapoStreamInfosHandle
Ptr AsapoStreamInfosHandle
-> Int -> AsapoStreamInfosHandle -> IO ()
Ptr AsapoStreamInfosHandle -> AsapoStreamInfosHandle -> IO ()
AsapoStreamInfosHandle -> Int
(AsapoStreamInfosHandle -> Int)
-> (AsapoStreamInfosHandle -> Int)
-> (Ptr AsapoStreamInfosHandle -> Int -> IO AsapoStreamInfosHandle)
-> (Ptr AsapoStreamInfosHandle
-> Int -> AsapoStreamInfosHandle -> IO ())
-> (forall b. Ptr b -> Int -> IO AsapoStreamInfosHandle)
-> (forall b. Ptr b -> Int -> AsapoStreamInfosHandle -> IO ())
-> (Ptr AsapoStreamInfosHandle -> IO AsapoStreamInfosHandle)
-> (Ptr AsapoStreamInfosHandle -> AsapoStreamInfosHandle -> IO ())
-> Storable AsapoStreamInfosHandle
forall b. Ptr b -> Int -> IO AsapoStreamInfosHandle
forall b. Ptr b -> Int -> AsapoStreamInfosHandle -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: AsapoStreamInfosHandle -> Int
sizeOf :: AsapoStreamInfosHandle -> Int
$calignment :: AsapoStreamInfosHandle -> Int
alignment :: AsapoStreamInfosHandle -> Int
$cpeekElemOff :: Ptr AsapoStreamInfosHandle -> Int -> IO AsapoStreamInfosHandle
peekElemOff :: Ptr AsapoStreamInfosHandle -> Int -> IO AsapoStreamInfosHandle
$cpokeElemOff :: Ptr AsapoStreamInfosHandle
-> Int -> AsapoStreamInfosHandle -> IO ()
pokeElemOff :: Ptr AsapoStreamInfosHandle
-> Int -> AsapoStreamInfosHandle -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AsapoStreamInfosHandle
peekByteOff :: forall b. Ptr b -> Int -> IO AsapoStreamInfosHandle
$cpokeByteOff :: forall b. Ptr b -> Int -> AsapoStreamInfosHandle -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> AsapoStreamInfosHandle -> IO ()
$cpeek :: Ptr AsapoStreamInfosHandle -> IO AsapoStreamInfosHandle
peek :: Ptr AsapoStreamInfosHandle -> IO AsapoStreamInfosHandle
$cpoke :: Ptr AsapoStreamInfosHandle -> AsapoStreamInfosHandle -> IO ()
poke :: Ptr AsapoStreamInfosHandle -> AsapoStreamInfosHandle -> IO ()
Storable)
newtype {-# CTYPE "asapo/consumer_c.h" "AsapoMessageDataHandle" #-} AsapoMessageDataHandle = AsapoMessageDataHandle (Ptr ()) deriving (Ptr AsapoMessageDataHandle -> IO AsapoMessageDataHandle
Ptr AsapoMessageDataHandle -> Int -> IO AsapoMessageDataHandle
Ptr AsapoMessageDataHandle
-> Int -> AsapoMessageDataHandle -> IO ()
Ptr AsapoMessageDataHandle -> AsapoMessageDataHandle -> IO ()
AsapoMessageDataHandle -> Int
(AsapoMessageDataHandle -> Int)
-> (AsapoMessageDataHandle -> Int)
-> (Ptr AsapoMessageDataHandle -> Int -> IO AsapoMessageDataHandle)
-> (Ptr AsapoMessageDataHandle
-> Int -> AsapoMessageDataHandle -> IO ())
-> (forall b. Ptr b -> Int -> IO AsapoMessageDataHandle)
-> (forall b. Ptr b -> Int -> AsapoMessageDataHandle -> IO ())
-> (Ptr AsapoMessageDataHandle -> IO AsapoMessageDataHandle)
-> (Ptr AsapoMessageDataHandle -> AsapoMessageDataHandle -> IO ())
-> Storable AsapoMessageDataHandle
forall b. Ptr b -> Int -> IO AsapoMessageDataHandle
forall b. Ptr b -> Int -> AsapoMessageDataHandle -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: AsapoMessageDataHandle -> Int
sizeOf :: AsapoMessageDataHandle -> Int
$calignment :: AsapoMessageDataHandle -> Int
alignment :: AsapoMessageDataHandle -> Int
$cpeekElemOff :: Ptr AsapoMessageDataHandle -> Int -> IO AsapoMessageDataHandle
peekElemOff :: Ptr AsapoMessageDataHandle -> Int -> IO AsapoMessageDataHandle
$cpokeElemOff :: Ptr AsapoMessageDataHandle
-> Int -> AsapoMessageDataHandle -> IO ()
pokeElemOff :: Ptr AsapoMessageDataHandle
-> Int -> AsapoMessageDataHandle -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AsapoMessageDataHandle
peekByteOff :: forall b. Ptr b -> Int -> IO AsapoMessageDataHandle
$cpokeByteOff :: forall b. Ptr b -> Int -> AsapoMessageDataHandle -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> AsapoMessageDataHandle -> IO ()
$cpeek :: Ptr AsapoMessageDataHandle -> IO AsapoMessageDataHandle
peek :: Ptr AsapoMessageDataHandle -> IO AsapoMessageDataHandle
$cpoke :: Ptr AsapoMessageDataHandle -> AsapoMessageDataHandle -> IO ()
poke :: Ptr AsapoMessageDataHandle -> AsapoMessageDataHandle -> IO ()
Storable)
asapo_new_message_data_handle :: IO AsapoMessageDataHandle
asapo_new_message_data_handle :: IO AsapoMessageDataHandle
asapo_new_message_data_handle = Ptr () -> AsapoMessageDataHandle
AsapoMessageDataHandle (Ptr () -> AsapoMessageDataHandle)
-> IO (Ptr ()) -> IO AsapoMessageDataHandle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (Ptr ())
asapo_new_handle
asapo_free_message_data_handle :: AsapoMessageDataHandle -> IO ()
asapo_free_message_data_handle :: AsapoMessageDataHandle -> IO ()
asapo_free_message_data_handle (AsapoMessageDataHandle Ptr ()
ptr) = Ptr () -> (Ptr (Ptr ()) -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Ptr ()
ptr Ptr (Ptr ()) -> IO ()
asapo_free_handle
type AsapoSourceType = CInt
foreign import capi "asapo/common/common_c.h value kProcessed" kProcessed :: AsapoSourceType
foreign import capi "asapo/common/common_c.h value kRaw" kRaw :: AsapoSourceType
foreign import capi "asapo/common/common_c.h asapo_free_handle__" asapo_free_handle :: Ptr (Ptr ()) -> IO ()
foreign import ccall "wrapper" mkAsapoFreeWrapper :: (Ptr () -> IO ()) -> IO (FunPtr (Ptr () -> IO ()))
foreign import capi "asapo/common/common_c.h asapo_new_handle" asapo_new_handle :: IO (Ptr ())
asapo_new_error_handle :: IO AsapoErrorHandle
asapo_new_error_handle :: IO AsapoErrorHandle
asapo_new_error_handle = Ptr () -> AsapoErrorHandle
AsapoErrorHandle (Ptr () -> AsapoErrorHandle) -> IO (Ptr ()) -> IO AsapoErrorHandle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (Ptr ())
asapo_new_handle
asapo_free_error_handle :: AsapoErrorHandle -> IO ()
asapo_free_error_handle :: AsapoErrorHandle -> IO ()
asapo_free_error_handle (AsapoErrorHandle Ptr ()
ptr) = Ptr () -> (Ptr (Ptr ()) -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Ptr ()
ptr Ptr (Ptr ()) -> IO ()
asapo_free_handle
foreign import capi "asapo/common/common_c.h asapo_error_explain" asapo_error_explain :: AsapoErrorHandle -> CString -> CSize -> IO ()
foreign import capi "asapo/common/common_c.h asapo_is_error" asapo_is_error :: AsapoErrorHandle -> IO AsapoBool
foreign import capi "asapo/common/common_c.h asapo_string_from_c_str" asapo_string_from_c_str :: ConstCString -> IO AsapoStringHandle
foreign import capi "asapo/common/common_c.h asapo_string_c_str" asapo_string_c_str :: AsapoStringHandle -> IO ConstCString
foreign import capi "asapo/common/common_c.h asapo_string_size" asapo_string_size :: AsapoStringHandle -> IO CSize
foreign import capi "asapo/common/common_c.h asapo_stream_infos_get_item"
asapo_stream_infos_get_item ::
AsapoStreamInfosHandle ->
CSize ->
IO AsapoStreamInfoHandle
foreign import capi "asapo/common/common_c.h asapo_stream_info_get_last_id" asapo_stream_info_get_last_id :: AsapoStreamInfoHandle -> IO CULong
foreign import capi "asapo/common/common_c.h asapo_stream_info_get_name" asapo_stream_info_get_name :: AsapoStreamInfoHandle -> IO ConstCString
foreign import capi "asapo/common/common_c.h asapo_stream_info_get_ffinished" asapo_stream_info_get_finished :: AsapoStreamInfoHandle -> IO AsapoBool
foreign import capi "asapo/common/common_c.h asapo_stream_info_get_next_stream" asapo_stream_info_get_next_stream :: AsapoStreamInfoHandle -> IO ConstCString
foreign import capi "asapo/common/common_c.h asapo_stream_info_get_timestamp_created" asapo_stream_info_get_timestamp_created :: AsapoStreamInfoHandle -> Ptr TimeSpec -> IO ()
foreign import capi "asapo/common/common_c.h asapo_stream_info_get_timestamp_last_entry" asapo_stream_info_get_timestamp_last_entry :: AsapoStreamInfoHandle -> Ptr TimeSpec -> IO ()
foreign import capi "asapo/common/common_c.h asapo_create_source_credentials"
asapo_create_source_credentials ::
AsapoSourceType ->
CString ->
CString ->
CString ->
CString ->
CString ->
CString ->
IO AsapoSourceCredentialsHandle
asapo_free_source_credentials :: AsapoSourceCredentialsHandle -> IO ()
asapo_free_source_credentials :: AsapoSourceCredentialsHandle -> IO ()
asapo_free_source_credentials (AsapoSourceCredentialsHandle Ptr ()
ptr) = Ptr () -> (Ptr (Ptr ()) -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Ptr ()
ptr Ptr (Ptr ()) -> IO ()
asapo_free_handle
foreign import capi "asapo/common/common_c.h asapo_message_data_get_as_chars" asapo_message_data_get_as_chars :: AsapoMessageDataHandle -> IO ConstCString