{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE StrictData #-}
module Network.Tox.C.Tox where
import Control.Exception (bracket)
import Control.Monad ((>=>))
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.MessagePack as MP
import Data.Word (Word16, Word32, Word64)
import Foreign.C.Enum
import Foreign.C.String (CString, withCString)
import Foreign.C.Types (CTime (..))
import Foreign.Marshal.Array (allocaArray, peekArray)
import Foreign.Ptr (Ptr, nullPtr)
import System.Posix.Types (EpochTime)
import FFI.Tox.Tox (ConferenceType, Connection,
ErrBootstrap (..),
ErrConferenceDelete (..),
ErrConferenceGetType (..),
ErrConferenceInvite (..),
ErrConferenceJoin (..),
ErrConferenceNew (..),
ErrConferencePeerQuery (..),
ErrConferenceSendMessage (..),
ErrConferenceTitle (..),
ErrFileControl (..), ErrFileGet (..),
ErrFileSeek (..), ErrFileSend (..),
ErrFileSendChunk (..),
ErrFriendAdd (..),
ErrFriendByPublicKey (..),
ErrFriendCustomPacket (..),
ErrFriendDelete (..),
ErrFriendGetLastOnline (..),
ErrFriendGetPublicKey (..),
ErrFriendQuery (..),
ErrFriendSendMessage (..),
ErrGetPort (..), ErrNew (..),
ErrSetInfo (..), ErrSetTyping (..),
FileControl, FileKind (..),
MessageType, ToxPtr, UserStatus,
tox_add_tcp_relay, tox_bootstrap,
tox_conference_delete,
tox_conference_get_chatlist,
tox_conference_get_chatlist_size,
tox_conference_get_title,
tox_conference_get_title_size,
tox_conference_get_type,
tox_conference_invite,
tox_conference_join,
tox_conference_new,
tox_conference_peer_count,
tox_conference_peer_get_name,
tox_conference_peer_get_name_size,
tox_conference_peer_get_public_key,
tox_conference_peer_number_is_ours,
tox_conference_send_message,
tox_conference_set_title,
tox_file_control,
tox_file_get_file_id, tox_file_seek,
tox_file_send, tox_file_send_chunk,
tox_friend_add,
tox_friend_add_norequest,
tox_friend_by_public_key,
tox_friend_delete, tox_friend_exists,
tox_friend_get_connection_status,
tox_friend_get_last_online,
tox_friend_get_name,
tox_friend_get_name_size,
tox_friend_get_public_key,
tox_friend_get_status_message,
tox_friend_get_status_message_size,
tox_friend_get_typing,
tox_friend_send_lossless_packet,
tox_friend_send_lossy_packet,
tox_friend_send_message,
tox_get_savedata,
tox_get_savedata_size, tox_hash,
tox_iteration_interval, tox_kill,
tox_new, tox_self_get_address,
tox_self_get_dht_id,
tox_self_get_friend_list,
tox_self_get_friend_list_size,
tox_self_get_name,
tox_self_get_name_size,
tox_self_get_nospam,
tox_self_get_public_key,
tox_self_get_secret_key,
tox_self_get_status_message,
tox_self_get_status_message_size,
tox_self_get_tcp_port,
tox_self_get_udp_port,
tox_self_set_name,
tox_self_set_nospam,
tox_self_set_status,
tox_self_set_status_message,
tox_self_set_typing)
import Network.Tox.C.Constants
import Network.Tox.C.Options
import Network.Tox.Types.Events (Event)
withTox :: Options -> (ToxPtr -> IO a) -> IO (Either ErrNew a)
withTox :: Options -> (ToxPtr -> IO a) -> IO (Either ErrNew a)
withTox Options
opts ToxPtr -> IO a
f =
(Either ErrOptionsNew (Either ErrNew a) -> Either ErrNew a)
-> IO (Either ErrOptionsNew (Either ErrNew a))
-> IO (Either ErrNew a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Either ErrOptionsNew (Either ErrNew a) -> Either ErrNew a
forall b. Either ErrOptionsNew (Either ErrNew b) -> Either ErrNew b
mapErr (IO (Either ErrOptionsNew (Either ErrNew a))
-> IO (Either ErrNew a))
-> ((OptionsPtr -> IO (Either ErrNew a))
-> IO (Either ErrOptionsNew (Either ErrNew a)))
-> (OptionsPtr -> IO (Either ErrNew a))
-> IO (Either ErrNew a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options
-> (OptionsPtr -> IO (Either ErrNew a))
-> IO (Either ErrOptionsNew (Either ErrNew a))
forall r.
Options -> (OptionsPtr -> IO r) -> IO (Either ErrOptionsNew r)
withOptions Options
opts ((OptionsPtr -> IO (Either ErrNew a)) -> IO (Either ErrNew a))
-> (OptionsPtr -> IO (Either ErrNew a)) -> IO (Either ErrNew a)
forall a b. (a -> b) -> a -> b
$ \OptionsPtr
copts -> do
Either ErrNew ToxPtr
result <- (CErr ErrNew -> IO ToxPtr) -> IO (Either ErrNew ToxPtr)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrNew -> IO ToxPtr) -> IO (Either ErrNew ToxPtr))
-> (OptionsPtr -> CErr ErrNew -> IO ToxPtr)
-> OptionsPtr
-> IO (Either ErrNew ToxPtr)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OptionsPtr -> CErr ErrNew -> IO ToxPtr
tox_new (OptionsPtr -> IO (Either ErrNew ToxPtr))
-> OptionsPtr -> IO (Either ErrNew ToxPtr)
forall a b. (a -> b) -> a -> b
$ OptionsPtr
copts
case Either ErrNew ToxPtr
result of
Left ErrNew
err ->
Either ErrNew a -> IO (Either ErrNew a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrNew a -> IO (Either ErrNew a))
-> Either ErrNew a -> IO (Either ErrNew a)
forall a b. (a -> b) -> a -> b
$ ErrNew -> Either ErrNew a
forall a b. a -> Either a b
Left ErrNew
err
Right ToxPtr
tox -> do
ToxPtr -> IO ()
tox_events_init ToxPtr
tox
a
res <- ToxPtr -> IO a
f ToxPtr
tox
ToxPtr -> IO ()
tox_kill ToxPtr
tox
Either ErrNew a -> IO (Either ErrNew a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrNew a -> IO (Either ErrNew a))
-> Either ErrNew a -> IO (Either ErrNew a)
forall a b. (a -> b) -> a -> b
$ a -> Either ErrNew a
forall a b. b -> Either a b
Right a
res
where
mapErr :: Either ErrOptionsNew (Either ErrNew b) -> Either ErrNew b
mapErr (Left ErrOptionsNew
ErrOptionsNewMalloc) = ErrNew -> Either ErrNew b
forall a b. a -> Either a b
Left ErrNew
ErrNewMalloc
mapErr (Right Either ErrNew b
ok) = Either ErrNew b
ok
toxGetSavedata :: ToxPtr -> IO BS.ByteString
toxGetSavedata :: ToxPtr -> IO ByteString
toxGetSavedata ToxPtr
tox = do
CSize
savedataLen <- ToxPtr -> IO CSize
tox_get_savedata_size ToxPtr
tox
Int -> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
savedataLen) ((Ptr CChar -> IO ByteString) -> IO ByteString)
-> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
savedataPtr -> do
ToxPtr -> Ptr CChar -> IO ()
tox_get_savedata ToxPtr
tox Ptr CChar
savedataPtr
CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
savedataPtr, CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
savedataLen)
toxBootstrap :: ToxPtr -> String -> Word16 -> BS.ByteString -> IO (Either ErrBootstrap Bool)
toxBootstrap :: ToxPtr
-> String -> Word16 -> ByteString -> IO (Either ErrBootstrap Bool)
toxBootstrap ToxPtr
tox String
address Word16
port ByteString
pubKey =
String
-> (Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool)
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
address ((Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool))
-> (Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
address' ->
ByteString
-> (Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool)
forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
BS.useAsCString ByteString
pubKey ((Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool))
-> (Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
pubKey' ->
(CErr ErrBootstrap -> IO Bool) -> IO (Either ErrBootstrap Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrBootstrap -> IO Bool) -> IO (Either ErrBootstrap Bool))
-> (CErr ErrBootstrap -> IO Bool) -> IO (Either ErrBootstrap Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Ptr CChar -> Word16 -> Ptr CChar -> CErr ErrBootstrap -> IO Bool
tox_bootstrap ToxPtr
tox Ptr CChar
address' (Word16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
port) Ptr CChar
pubKey'
toxAddTcpRelay :: ToxPtr -> String -> Word16 -> BS.ByteString -> IO (Either ErrBootstrap Bool)
toxAddTcpRelay :: ToxPtr
-> String -> Word16 -> ByteString -> IO (Either ErrBootstrap Bool)
toxAddTcpRelay ToxPtr
tox String
address Word16
port ByteString
pubKey =
String
-> (Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool)
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
address ((Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool))
-> (Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
address' ->
ByteString
-> (Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool)
forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
BS.useAsCString ByteString
pubKey ((Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool))
-> (Ptr CChar -> IO (Either ErrBootstrap Bool))
-> IO (Either ErrBootstrap Bool)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
pubKey' ->
(CErr ErrBootstrap -> IO Bool) -> IO (Either ErrBootstrap Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrBootstrap -> IO Bool) -> IO (Either ErrBootstrap Bool))
-> (CErr ErrBootstrap -> IO Bool) -> IO (Either ErrBootstrap Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Ptr CChar -> Word16 -> Ptr CChar -> CErr ErrBootstrap -> IO Bool
tox_add_tcp_relay ToxPtr
tox Ptr CChar
address' (Word16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
port) Ptr CChar
pubKey'
data ToxEventsStruct
type ToxEvents = Ptr ToxEventsStruct
data ErrEventsIterate
= ErrEventsIterateMalloc
| ErrEventsDecode
deriving (ErrEventsIterate -> ErrEventsIterate -> Bool
(ErrEventsIterate -> ErrEventsIterate -> Bool)
-> (ErrEventsIterate -> ErrEventsIterate -> Bool)
-> Eq ErrEventsIterate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ErrEventsIterate -> ErrEventsIterate -> Bool
$c/= :: ErrEventsIterate -> ErrEventsIterate -> Bool
== :: ErrEventsIterate -> ErrEventsIterate -> Bool
$c== :: ErrEventsIterate -> ErrEventsIterate -> Bool
Eq, Eq ErrEventsIterate
Eq ErrEventsIterate
-> (ErrEventsIterate -> ErrEventsIterate -> Ordering)
-> (ErrEventsIterate -> ErrEventsIterate -> Bool)
-> (ErrEventsIterate -> ErrEventsIterate -> Bool)
-> (ErrEventsIterate -> ErrEventsIterate -> Bool)
-> (ErrEventsIterate -> ErrEventsIterate -> Bool)
-> (ErrEventsIterate -> ErrEventsIterate -> ErrEventsIterate)
-> (ErrEventsIterate -> ErrEventsIterate -> ErrEventsIterate)
-> Ord ErrEventsIterate
ErrEventsIterate -> ErrEventsIterate -> Bool
ErrEventsIterate -> ErrEventsIterate -> Ordering
ErrEventsIterate -> ErrEventsIterate -> ErrEventsIterate
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ErrEventsIterate -> ErrEventsIterate -> ErrEventsIterate
$cmin :: ErrEventsIterate -> ErrEventsIterate -> ErrEventsIterate
max :: ErrEventsIterate -> ErrEventsIterate -> ErrEventsIterate
$cmax :: ErrEventsIterate -> ErrEventsIterate -> ErrEventsIterate
>= :: ErrEventsIterate -> ErrEventsIterate -> Bool
$c>= :: ErrEventsIterate -> ErrEventsIterate -> Bool
> :: ErrEventsIterate -> ErrEventsIterate -> Bool
$c> :: ErrEventsIterate -> ErrEventsIterate -> Bool
<= :: ErrEventsIterate -> ErrEventsIterate -> Bool
$c<= :: ErrEventsIterate -> ErrEventsIterate -> Bool
< :: ErrEventsIterate -> ErrEventsIterate -> Bool
$c< :: ErrEventsIterate -> ErrEventsIterate -> Bool
compare :: ErrEventsIterate -> ErrEventsIterate -> Ordering
$ccompare :: ErrEventsIterate -> ErrEventsIterate -> Ordering
$cp1Ord :: Eq ErrEventsIterate
Ord, Int -> ErrEventsIterate
ErrEventsIterate -> Int
ErrEventsIterate -> [ErrEventsIterate]
ErrEventsIterate -> ErrEventsIterate
ErrEventsIterate -> ErrEventsIterate -> [ErrEventsIterate]
ErrEventsIterate
-> ErrEventsIterate -> ErrEventsIterate -> [ErrEventsIterate]
(ErrEventsIterate -> ErrEventsIterate)
-> (ErrEventsIterate -> ErrEventsIterate)
-> (Int -> ErrEventsIterate)
-> (ErrEventsIterate -> Int)
-> (ErrEventsIterate -> [ErrEventsIterate])
-> (ErrEventsIterate -> ErrEventsIterate -> [ErrEventsIterate])
-> (ErrEventsIterate -> ErrEventsIterate -> [ErrEventsIterate])
-> (ErrEventsIterate
-> ErrEventsIterate -> ErrEventsIterate -> [ErrEventsIterate])
-> Enum ErrEventsIterate
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ErrEventsIterate
-> ErrEventsIterate -> ErrEventsIterate -> [ErrEventsIterate]
$cenumFromThenTo :: ErrEventsIterate
-> ErrEventsIterate -> ErrEventsIterate -> [ErrEventsIterate]
enumFromTo :: ErrEventsIterate -> ErrEventsIterate -> [ErrEventsIterate]
$cenumFromTo :: ErrEventsIterate -> ErrEventsIterate -> [ErrEventsIterate]
enumFromThen :: ErrEventsIterate -> ErrEventsIterate -> [ErrEventsIterate]
$cenumFromThen :: ErrEventsIterate -> ErrEventsIterate -> [ErrEventsIterate]
enumFrom :: ErrEventsIterate -> [ErrEventsIterate]
$cenumFrom :: ErrEventsIterate -> [ErrEventsIterate]
fromEnum :: ErrEventsIterate -> Int
$cfromEnum :: ErrEventsIterate -> Int
toEnum :: Int -> ErrEventsIterate
$ctoEnum :: Int -> ErrEventsIterate
pred :: ErrEventsIterate -> ErrEventsIterate
$cpred :: ErrEventsIterate -> ErrEventsIterate
succ :: ErrEventsIterate -> ErrEventsIterate
$csucc :: ErrEventsIterate -> ErrEventsIterate
Enum, ErrEventsIterate
ErrEventsIterate -> ErrEventsIterate -> Bounded ErrEventsIterate
forall a. a -> a -> Bounded a
maxBound :: ErrEventsIterate
$cmaxBound :: ErrEventsIterate
minBound :: ErrEventsIterate
$cminBound :: ErrEventsIterate
Bounded, ReadPrec [ErrEventsIterate]
ReadPrec ErrEventsIterate
Int -> ReadS ErrEventsIterate
ReadS [ErrEventsIterate]
(Int -> ReadS ErrEventsIterate)
-> ReadS [ErrEventsIterate]
-> ReadPrec ErrEventsIterate
-> ReadPrec [ErrEventsIterate]
-> Read ErrEventsIterate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ErrEventsIterate]
$creadListPrec :: ReadPrec [ErrEventsIterate]
readPrec :: ReadPrec ErrEventsIterate
$creadPrec :: ReadPrec ErrEventsIterate
readList :: ReadS [ErrEventsIterate]
$creadList :: ReadS [ErrEventsIterate]
readsPrec :: Int -> ReadS ErrEventsIterate
$creadsPrec :: Int -> ReadS ErrEventsIterate
Read, Int -> ErrEventsIterate -> ShowS
[ErrEventsIterate] -> ShowS
ErrEventsIterate -> String
(Int -> ErrEventsIterate -> ShowS)
-> (ErrEventsIterate -> String)
-> ([ErrEventsIterate] -> ShowS)
-> Show ErrEventsIterate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ErrEventsIterate] -> ShowS
$cshowList :: [ErrEventsIterate] -> ShowS
show :: ErrEventsIterate -> String
$cshow :: ErrEventsIterate -> String
showsPrec :: Int -> ErrEventsIterate -> ShowS
$cshowsPrec :: Int -> ErrEventsIterate -> ShowS
Show)
foreign import ccall tox_events_init :: ToxPtr -> IO ()
foreign import ccall tox_events_iterate :: ToxPtr -> Bool -> CErr ErrEventsIterate -> IO ToxEvents
foreign import ccall tox_events_bytes_size :: ToxEvents -> IO Word32
foreign import ccall tox_events_get_bytes :: ToxEvents -> CString -> IO ()
foreign import ccall tox_events_load :: CString -> Word32 -> IO ToxEvents
foreign import ccall tox_events_free :: ToxEvents -> IO ()
toxEventsToPtr :: [Event] -> IO ToxEvents
toxEventsToPtr :: [Event] -> IO ToxEvents
toxEventsToPtr [Event]
events =
let encoded :: ByteString
encoded = [Event] -> ByteString
forall a. MessagePack a => a -> ByteString
MP.pack [Event]
events in
ByteString -> (CStringLen -> IO ToxEvents) -> IO ToxEvents
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen (ByteString -> ByteString
LBS.toStrict ByteString
encoded) ((CStringLen -> IO ToxEvents) -> IO ToxEvents)
-> (CStringLen -> IO ToxEvents) -> IO ToxEvents
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
ptr, Int
len) ->
Ptr CChar -> Word32 -> IO ToxEvents
tox_events_load Ptr CChar
ptr (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
toxEventsFromPtr :: ToxEvents -> IO (Either String [Event])
toxEventsFromPtr :: ToxEvents -> IO (Either String [Event])
toxEventsFromPtr ToxEvents
evPtr = do
ByteString
bytes <- IO ToxEvents
-> (ToxEvents -> IO ())
-> (ToxEvents -> IO ByteString)
-> IO ByteString
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (ToxEvents -> IO ToxEvents
forall (m :: * -> *) a. Monad m => a -> m a
return ToxEvents
evPtr) ToxEvents -> IO ()
tox_events_free ((ToxEvents -> IO ByteString) -> IO ByteString)
-> (ToxEvents -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> ToxEvents -> IO ByteString
forall a b. a -> b -> a
const (IO ByteString -> ToxEvents -> IO ByteString)
-> IO ByteString -> ToxEvents -> IO ByteString
forall a b. (a -> b) -> a -> b
$ do
Word32
len <- ToxEvents -> IO Word32
tox_events_bytes_size ToxEvents
evPtr
Int -> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
len) ((Ptr CChar -> IO ByteString) -> IO ByteString)
-> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
ptr -> do
ToxEvents -> Ptr CChar -> IO ()
tox_events_get_bytes ToxEvents
evPtr Ptr CChar
ptr
CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
ptr, Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
len)
case ByteString -> Either DecodeError [Event]
forall a. MessagePack a => ByteString -> Either DecodeError a
MP.unpackEither (ByteString -> Either DecodeError [Event])
-> ByteString -> Either DecodeError [Event]
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
LBS.fromStrict ByteString
bytes of
Left DecodeError
err -> do
Either DecodeError Object -> IO ()
forall a. Show a => a -> IO ()
print (ByteString -> Either DecodeError Object
forall a. MessagePack a => ByteString -> Either DecodeError a
MP.unpackEither (ByteString -> Either DecodeError Object)
-> ByteString -> Either DecodeError Object
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
LBS.fromStrict ByteString
bytes :: Either MP.DecodeError MP.Object)
Either String [Event] -> IO (Either String [Event])
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String [Event] -> IO (Either String [Event]))
-> Either String [Event] -> IO (Either String [Event])
forall a b. (a -> b) -> a -> b
$ String -> Either String [Event]
forall a b. a -> Either a b
Left (String -> Either String [Event])
-> String -> Either String [Event]
forall a b. (a -> b) -> a -> b
$ DecodeError -> String
forall a. Show a => a -> String
show DecodeError
err
Right [Event]
ok -> Either String [Event] -> IO (Either String [Event])
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String [Event] -> IO (Either String [Event]))
-> Either String [Event] -> IO (Either String [Event])
forall a b. (a -> b) -> a -> b
$ [Event] -> Either String [Event]
forall a b. b -> Either a b
Right [Event]
ok
toxEventsIterate :: ToxPtr -> IO (Either String [Event])
toxEventsIterate :: ToxPtr -> IO (Either String [Event])
toxEventsIterate ToxPtr
tox =
(CErr ErrEventsIterate -> IO ToxEvents)
-> IO (Either ErrEventsIterate ToxEvents)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun (ToxPtr -> Bool -> CErr ErrEventsIterate -> IO ToxEvents
tox_events_iterate ToxPtr
tox Bool
True) IO (Either ErrEventsIterate ToxEvents)
-> (Either ErrEventsIterate ToxEvents
-> IO (Either String [Event]))
-> IO (Either String [Event])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left ErrEventsIterate
err -> Either String [Event] -> IO (Either String [Event])
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String [Event] -> IO (Either String [Event]))
-> Either String [Event] -> IO (Either String [Event])
forall a b. (a -> b) -> a -> b
$ String -> Either String [Event]
forall a b. a -> Either a b
Left (String -> Either String [Event])
-> String -> Either String [Event]
forall a b. (a -> b) -> a -> b
$ ErrEventsIterate -> String
forall a. Show a => a -> String
show ErrEventsIterate
err
Right ToxEvents
evPtr -> ToxEvents -> IO (Either String [Event])
toxEventsFromPtr ToxEvents
evPtr
toxIterationInterval :: ToxPtr -> IO Word32
toxIterationInterval :: ToxPtr -> IO Word32
toxIterationInterval = ToxPtr -> IO Word32
tox_iteration_interval
toxSelfGetAddress :: ToxPtr -> IO BS.ByteString
toxSelfGetAddress :: ToxPtr -> IO ByteString
toxSelfGetAddress ToxPtr
tox =
let addrLen :: Int
addrLen = Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
tox_address_size in
Int -> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
addrLen ((Ptr CChar -> IO ByteString) -> IO ByteString)
-> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
addrPtr -> do
ToxPtr -> Ptr CChar -> IO ()
tox_self_get_address ToxPtr
tox Ptr CChar
addrPtr
CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
addrPtr, Int
addrLen)
toxSelfSetNospam :: ToxPtr -> Word32 -> IO ()
toxSelfSetNospam :: ToxPtr -> Word32 -> IO ()
toxSelfSetNospam = ToxPtr -> Word32 -> IO ()
tox_self_set_nospam
toxSelfGetNospam :: ToxPtr -> IO Word32
toxSelfGetNospam :: ToxPtr -> IO Word32
toxSelfGetNospam = ToxPtr -> IO Word32
tox_self_get_nospam
toxSelfGetPublicKey :: ToxPtr -> IO BS.ByteString
toxSelfGetPublicKey :: ToxPtr -> IO ByteString
toxSelfGetPublicKey ToxPtr
tox =
let pkLen :: Int
pkLen = Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
tox_public_key_size in
Int -> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
pkLen ((Ptr CChar -> IO ByteString) -> IO ByteString)
-> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
pkPtr -> do
ToxPtr -> Ptr CChar -> IO ()
tox_self_get_public_key ToxPtr
tox Ptr CChar
pkPtr
CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
pkPtr, Int
pkLen)
toxSelfGetSecretKey :: ToxPtr -> IO BS.ByteString
toxSelfGetSecretKey :: ToxPtr -> IO ByteString
toxSelfGetSecretKey ToxPtr
tox =
let skLen :: Int
skLen = Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
tox_secret_key_size in
Int -> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
skLen ((Ptr CChar -> IO ByteString) -> IO ByteString)
-> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
skPtr -> do
ToxPtr -> Ptr CChar -> IO ()
tox_self_get_secret_key ToxPtr
tox Ptr CChar
skPtr
CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
skPtr, Int
skLen)
toxSelfSetName :: ToxPtr -> BS.ByteString -> IO (Either ErrSetInfo Bool)
toxSelfSetName :: ToxPtr -> ByteString -> IO (Either ErrSetInfo Bool)
toxSelfSetName ToxPtr
tox ByteString
name =
ByteString
-> (CStringLen -> IO (Either ErrSetInfo Bool))
-> IO (Either ErrSetInfo Bool)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
name ((CStringLen -> IO (Either ErrSetInfo Bool))
-> IO (Either ErrSetInfo Bool))
-> (CStringLen -> IO (Either ErrSetInfo Bool))
-> IO (Either ErrSetInfo Bool)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
nameStr, Int
nameLen) ->
(CErr ErrSetInfo -> IO Bool) -> IO (Either ErrSetInfo Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrSetInfo -> IO Bool) -> IO (Either ErrSetInfo Bool))
-> (CErr ErrSetInfo -> IO Bool) -> IO (Either ErrSetInfo Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Ptr CChar -> CSize -> CErr ErrSetInfo -> IO Bool
tox_self_set_name ToxPtr
tox Ptr CChar
nameStr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nameLen)
toxSelfGetName :: ToxPtr -> IO BS.ByteString
toxSelfGetName :: ToxPtr -> IO ByteString
toxSelfGetName ToxPtr
tox = do
CSize
nameLen <- ToxPtr -> IO CSize
tox_self_get_name_size ToxPtr
tox
Int -> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
nameLen) ((Ptr CChar -> IO ByteString) -> IO ByteString)
-> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
namePtr -> do
ToxPtr -> Ptr CChar -> IO ()
tox_self_get_name ToxPtr
tox Ptr CChar
namePtr
CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
namePtr, CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
nameLen)
toxSelfSetStatusMessage :: ToxPtr -> BS.ByteString -> IO (Either ErrSetInfo Bool)
toxSelfSetStatusMessage :: ToxPtr -> ByteString -> IO (Either ErrSetInfo Bool)
toxSelfSetStatusMessage ToxPtr
tox ByteString
statusMsg =
ByteString
-> (CStringLen -> IO (Either ErrSetInfo Bool))
-> IO (Either ErrSetInfo Bool)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
statusMsg ((CStringLen -> IO (Either ErrSetInfo Bool))
-> IO (Either ErrSetInfo Bool))
-> (CStringLen -> IO (Either ErrSetInfo Bool))
-> IO (Either ErrSetInfo Bool)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
statusMsgStr, Int
statusMsgLen) ->
(CErr ErrSetInfo -> IO Bool) -> IO (Either ErrSetInfo Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrSetInfo -> IO Bool) -> IO (Either ErrSetInfo Bool))
-> (CErr ErrSetInfo -> IO Bool) -> IO (Either ErrSetInfo Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Ptr CChar -> CSize -> CErr ErrSetInfo -> IO Bool
tox_self_set_status_message ToxPtr
tox Ptr CChar
statusMsgStr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
statusMsgLen)
toxSelfGetStatusMessage :: ToxPtr -> IO BS.ByteString
toxSelfGetStatusMessage :: ToxPtr -> IO ByteString
toxSelfGetStatusMessage ToxPtr
tox = do
CSize
statusMessageLen <- ToxPtr -> IO CSize
tox_self_get_status_message_size ToxPtr
tox
Int -> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
statusMessageLen) ((Ptr CChar -> IO ByteString) -> IO ByteString)
-> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
statusMessagePtr -> do
ToxPtr -> Ptr CChar -> IO ()
tox_self_get_status_message ToxPtr
tox Ptr CChar
statusMessagePtr
CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
statusMessagePtr, CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
statusMessageLen)
toxSelfSetStatus :: ToxPtr -> UserStatus -> IO ()
toxSelfSetStatus :: ToxPtr -> UserStatus -> IO ()
toxSelfSetStatus ToxPtr
tox UserStatus
userStatus =
ToxPtr -> CEnum UserStatus -> IO ()
tox_self_set_status ToxPtr
tox (CEnum UserStatus -> IO ()) -> CEnum UserStatus -> IO ()
forall a b. (a -> b) -> a -> b
$ UserStatus -> CEnum UserStatus
forall a. Enum a => a -> CEnum a
toCEnum UserStatus
userStatus
toxFriendAdd :: ToxPtr -> BS.ByteString -> BS.ByteString -> IO (Either ErrFriendAdd Word32)
toxFriendAdd :: ToxPtr
-> ByteString -> ByteString -> IO (Either ErrFriendAdd Word32)
toxFriendAdd ToxPtr
tox ByteString
address ByteString
message =
ByteString
-> (CStringLen -> IO (Either ErrFriendAdd Word32))
-> IO (Either ErrFriendAdd Word32)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
message ((CStringLen -> IO (Either ErrFriendAdd Word32))
-> IO (Either ErrFriendAdd Word32))
-> (CStringLen -> IO (Either ErrFriendAdd Word32))
-> IO (Either ErrFriendAdd Word32)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
msgStr, Int
msgLen) ->
ByteString
-> (Ptr CChar -> IO (Either ErrFriendAdd Word32))
-> IO (Either ErrFriendAdd Word32)
forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
BS.useAsCString ByteString
address ((Ptr CChar -> IO (Either ErrFriendAdd Word32))
-> IO (Either ErrFriendAdd Word32))
-> (Ptr CChar -> IO (Either ErrFriendAdd Word32))
-> IO (Either ErrFriendAdd Word32)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
addr' ->
(CErr ErrFriendAdd -> IO Word32) -> IO (Either ErrFriendAdd Word32)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendAdd -> IO Word32)
-> IO (Either ErrFriendAdd Word32))
-> (CErr ErrFriendAdd -> IO Word32)
-> IO (Either ErrFriendAdd Word32)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Ptr CChar
-> Ptr CChar
-> CSize
-> CErr ErrFriendAdd
-> IO Word32
tox_friend_add ToxPtr
tox Ptr CChar
addr' Ptr CChar
msgStr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
msgLen)
toxFriendAddNorequest :: ToxPtr -> BS.ByteString -> IO (Either ErrFriendAdd Word32)
toxFriendAddNorequest :: ToxPtr -> ByteString -> IO (Either ErrFriendAdd Word32)
toxFriendAddNorequest ToxPtr
tox ByteString
address =
ByteString
-> (Ptr CChar -> IO (Either ErrFriendAdd Word32))
-> IO (Either ErrFriendAdd Word32)
forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
BS.useAsCString ByteString
address ((Ptr CChar -> IO (Either ErrFriendAdd Word32))
-> IO (Either ErrFriendAdd Word32))
-> (Ptr CChar -> IO (Either ErrFriendAdd Word32))
-> IO (Either ErrFriendAdd Word32)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
addr' ->
(CErr ErrFriendAdd -> IO Word32) -> IO (Either ErrFriendAdd Word32)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendAdd -> IO Word32)
-> IO (Either ErrFriendAdd Word32))
-> (CErr ErrFriendAdd -> IO Word32)
-> IO (Either ErrFriendAdd Word32)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Ptr CChar -> CErr ErrFriendAdd -> IO Word32
tox_friend_add_norequest ToxPtr
tox Ptr CChar
addr'
toxFriendDelete :: ToxPtr -> Word32 -> IO (Either ErrFriendDelete Bool)
toxFriendDelete :: ToxPtr -> Word32 -> IO (Either ErrFriendDelete Bool)
toxFriendDelete ToxPtr
tox Word32
fn = (CErr ErrFriendDelete -> IO Bool)
-> IO (Either ErrFriendDelete Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendDelete -> IO Bool)
-> IO (Either ErrFriendDelete Bool))
-> (CErr ErrFriendDelete -> IO Bool)
-> IO (Either ErrFriendDelete Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> CErr ErrFriendDelete -> IO Bool
tox_friend_delete ToxPtr
tox Word32
fn
toxFriendByPublicKey :: ToxPtr -> BS.ByteString -> IO (Either ErrFriendByPublicKey Word32)
toxFriendByPublicKey :: ToxPtr -> ByteString -> IO (Either ErrFriendByPublicKey Word32)
toxFriendByPublicKey ToxPtr
tox ByteString
address =
ByteString
-> (Ptr CChar -> IO (Either ErrFriendByPublicKey Word32))
-> IO (Either ErrFriendByPublicKey Word32)
forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
BS.useAsCString ByteString
address ((Ptr CChar -> IO (Either ErrFriendByPublicKey Word32))
-> IO (Either ErrFriendByPublicKey Word32))
-> (Ptr CChar -> IO (Either ErrFriendByPublicKey Word32))
-> IO (Either ErrFriendByPublicKey Word32)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
addr' ->
(CErr ErrFriendByPublicKey -> IO Word32)
-> IO (Either ErrFriendByPublicKey Word32)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendByPublicKey -> IO Word32)
-> IO (Either ErrFriendByPublicKey Word32))
-> (CErr ErrFriendByPublicKey -> IO Word32)
-> IO (Either ErrFriendByPublicKey Word32)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Ptr CChar -> CErr ErrFriendByPublicKey -> IO Word32
tox_friend_by_public_key ToxPtr
tox Ptr CChar
addr'
toxFriendExists :: ToxPtr -> Word32 -> IO Bool
toxFriendExists :: ToxPtr -> Word32 -> IO Bool
toxFriendExists = ToxPtr -> Word32 -> IO Bool
tox_friend_exists
toxSelfGetFriendList :: ToxPtr -> IO [Word32]
toxSelfGetFriendList :: ToxPtr -> IO [Word32]
toxSelfGetFriendList ToxPtr
tox = do
CSize
friendListSize <- ToxPtr -> IO CSize
tox_self_get_friend_list_size ToxPtr
tox
Int -> (Ptr Word32 -> IO [Word32]) -> IO [Word32]
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
friendListSize) ((Ptr Word32 -> IO [Word32]) -> IO [Word32])
-> (Ptr Word32 -> IO [Word32]) -> IO [Word32]
forall a b. (a -> b) -> a -> b
$ \Ptr Word32
friendListPtr -> do
ToxPtr -> Ptr Word32 -> IO ()
tox_self_get_friend_list ToxPtr
tox Ptr Word32
friendListPtr
Int -> Ptr Word32 -> IO [Word32]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
friendListSize) Ptr Word32
friendListPtr
toxFriendGetPublicKey :: ToxPtr -> Word32 -> IO (Either ErrFriendGetPublicKey BS.ByteString)
toxFriendGetPublicKey :: ToxPtr -> Word32 -> IO (Either ErrFriendGetPublicKey ByteString)
toxFriendGetPublicKey ToxPtr
tox Word32
fn =
let pkLen :: Int
pkLen = Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
tox_public_key_size in
Int
-> (Ptr CChar -> IO (Either ErrFriendGetPublicKey ByteString))
-> IO (Either ErrFriendGetPublicKey ByteString)
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
pkLen ((Ptr CChar -> IO (Either ErrFriendGetPublicKey ByteString))
-> IO (Either ErrFriendGetPublicKey ByteString))
-> (Ptr CChar -> IO (Either ErrFriendGetPublicKey ByteString))
-> IO (Either ErrFriendGetPublicKey ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
pkPtr -> do
Either ErrFriendGetPublicKey Bool
nameRes <- (CErr ErrFriendGetPublicKey -> IO Bool)
-> IO (Either ErrFriendGetPublicKey Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendGetPublicKey -> IO Bool)
-> IO (Either ErrFriendGetPublicKey Bool))
-> (CErr ErrFriendGetPublicKey -> IO Bool)
-> IO (Either ErrFriendGetPublicKey Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32 -> Ptr CChar -> CErr ErrFriendGetPublicKey -> IO Bool
tox_friend_get_public_key ToxPtr
tox Word32
fn Ptr CChar
pkPtr
case Either ErrFriendGetPublicKey Bool
nameRes of
Left ErrFriendGetPublicKey
err -> Either ErrFriendGetPublicKey ByteString
-> IO (Either ErrFriendGetPublicKey ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrFriendGetPublicKey ByteString
-> IO (Either ErrFriendGetPublicKey ByteString))
-> Either ErrFriendGetPublicKey ByteString
-> IO (Either ErrFriendGetPublicKey ByteString)
forall a b. (a -> b) -> a -> b
$ ErrFriendGetPublicKey -> Either ErrFriendGetPublicKey ByteString
forall a b. a -> Either a b
Left ErrFriendGetPublicKey
err
Right Bool
_ -> ByteString -> Either ErrFriendGetPublicKey ByteString
forall a b. b -> Either a b
Right (ByteString -> Either ErrFriendGetPublicKey ByteString)
-> IO ByteString -> IO (Either ErrFriendGetPublicKey ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
pkPtr, Int
pkLen)
toxFriendGetLastOnline :: ToxPtr -> Word32 -> IO (Either ErrFriendGetLastOnline EpochTime)
toxFriendGetLastOnline :: ToxPtr -> Word32 -> IO (Either ErrFriendGetLastOnline EpochTime)
toxFriendGetLastOnline ToxPtr
tox Word32
fn =
(CErr ErrFriendGetLastOnline -> IO EpochTime)
-> IO (Either ErrFriendGetLastOnline EpochTime)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun (ToxPtr -> Word32 -> CErr ErrFriendGetLastOnline -> IO Word64
tox_friend_get_last_online ToxPtr
tox Word32
fn (CErr ErrFriendGetLastOnline -> IO Word64)
-> (Word64 -> IO EpochTime)
-> CErr ErrFriendGetLastOnline
-> IO EpochTime
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (EpochTime -> IO EpochTime
forall (m :: * -> *) a. Monad m => a -> m a
return (EpochTime -> IO EpochTime)
-> (Word64 -> EpochTime) -> Word64 -> IO EpochTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> EpochTime
CTime (Int64 -> EpochTime) -> (Word64 -> Int64) -> Word64 -> EpochTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral))
toxFriendGetName :: ToxPtr -> Word32 -> IO (Either ErrFriendQuery BS.ByteString)
toxFriendGetName :: ToxPtr -> Word32 -> IO (Either ErrFriendQuery ByteString)
toxFriendGetName ToxPtr
tox Word32
fn = do
Either ErrFriendQuery CSize
nameLenRes <- (CErr ErrFriendQuery -> IO CSize)
-> IO (Either ErrFriendQuery CSize)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendQuery -> IO CSize)
-> IO (Either ErrFriendQuery CSize))
-> (CErr ErrFriendQuery -> IO CSize)
-> IO (Either ErrFriendQuery CSize)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> CErr ErrFriendQuery -> IO CSize
tox_friend_get_name_size ToxPtr
tox Word32
fn
case Either ErrFriendQuery CSize
nameLenRes of
Left ErrFriendQuery
err -> Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString))
-> Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString)
forall a b. (a -> b) -> a -> b
$ ErrFriendQuery -> Either ErrFriendQuery ByteString
forall a b. a -> Either a b
Left ErrFriendQuery
err
Right CSize
nameLen -> Int
-> (Ptr CChar -> IO (Either ErrFriendQuery ByteString))
-> IO (Either ErrFriendQuery ByteString)
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
nameLen) ((Ptr CChar -> IO (Either ErrFriendQuery ByteString))
-> IO (Either ErrFriendQuery ByteString))
-> (Ptr CChar -> IO (Either ErrFriendQuery ByteString))
-> IO (Either ErrFriendQuery ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
namePtr -> do
Either ErrFriendQuery Bool
nameRes <- (CErr ErrFriendQuery -> IO Bool) -> IO (Either ErrFriendQuery Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendQuery -> IO Bool)
-> IO (Either ErrFriendQuery Bool))
-> (CErr ErrFriendQuery -> IO Bool)
-> IO (Either ErrFriendQuery Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> Ptr CChar -> CErr ErrFriendQuery -> IO Bool
tox_friend_get_name ToxPtr
tox Word32
fn Ptr CChar
namePtr
case Either ErrFriendQuery Bool
nameRes of
Left ErrFriendQuery
err -> Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString))
-> Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString)
forall a b. (a -> b) -> a -> b
$ ErrFriendQuery -> Either ErrFriendQuery ByteString
forall a b. a -> Either a b
Left ErrFriendQuery
err
Right Bool
_ -> ByteString -> Either ErrFriendQuery ByteString
forall a b. b -> Either a b
Right (ByteString -> Either ErrFriendQuery ByteString)
-> IO ByteString -> IO (Either ErrFriendQuery ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
namePtr, CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
nameLen)
toxFriendGetStatusMessage :: ToxPtr -> Word32 -> IO (Either ErrFriendQuery BS.ByteString)
toxFriendGetStatusMessage :: ToxPtr -> Word32 -> IO (Either ErrFriendQuery ByteString)
toxFriendGetStatusMessage ToxPtr
tox Word32
fn = do
Either ErrFriendQuery CSize
statusMessageLenRes <- (CErr ErrFriendQuery -> IO CSize)
-> IO (Either ErrFriendQuery CSize)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendQuery -> IO CSize)
-> IO (Either ErrFriendQuery CSize))
-> (CErr ErrFriendQuery -> IO CSize)
-> IO (Either ErrFriendQuery CSize)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> CErr ErrFriendQuery -> IO CSize
tox_friend_get_status_message_size ToxPtr
tox Word32
fn
case Either ErrFriendQuery CSize
statusMessageLenRes of
Left ErrFriendQuery
err -> Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString))
-> Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString)
forall a b. (a -> b) -> a -> b
$ ErrFriendQuery -> Either ErrFriendQuery ByteString
forall a b. a -> Either a b
Left ErrFriendQuery
err
Right CSize
statusMessageLen -> Int
-> (Ptr CChar -> IO (Either ErrFriendQuery ByteString))
-> IO (Either ErrFriendQuery ByteString)
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
statusMessageLen) ((Ptr CChar -> IO (Either ErrFriendQuery ByteString))
-> IO (Either ErrFriendQuery ByteString))
-> (Ptr CChar -> IO (Either ErrFriendQuery ByteString))
-> IO (Either ErrFriendQuery ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
statusMessagePtr -> do
Either ErrFriendQuery Bool
statusMessageRes <- (CErr ErrFriendQuery -> IO Bool) -> IO (Either ErrFriendQuery Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendQuery -> IO Bool)
-> IO (Either ErrFriendQuery Bool))
-> (CErr ErrFriendQuery -> IO Bool)
-> IO (Either ErrFriendQuery Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> Ptr CChar -> CErr ErrFriendQuery -> IO Bool
tox_friend_get_status_message ToxPtr
tox Word32
fn Ptr CChar
statusMessagePtr
case Either ErrFriendQuery Bool
statusMessageRes of
Left ErrFriendQuery
err -> Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString))
-> Either ErrFriendQuery ByteString
-> IO (Either ErrFriendQuery ByteString)
forall a b. (a -> b) -> a -> b
$ ErrFriendQuery -> Either ErrFriendQuery ByteString
forall a b. a -> Either a b
Left ErrFriendQuery
err
Right Bool
_ -> ByteString -> Either ErrFriendQuery ByteString
forall a b. b -> Either a b
Right (ByteString -> Either ErrFriendQuery ByteString)
-> IO ByteString -> IO (Either ErrFriendQuery ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
statusMessagePtr, CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
statusMessageLen)
toxFriendGetConnectionStatus :: ToxPtr -> Word32 -> IO (Either ErrFriendQuery Connection)
toxFriendGetConnectionStatus :: ToxPtr -> Word32 -> IO (Either ErrFriendQuery Connection)
toxFriendGetConnectionStatus ToxPtr
tox Word32
fn =
(CErr ErrFriendQuery -> IO Connection)
-> IO (Either ErrFriendQuery Connection)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun (ToxPtr -> Word32 -> CErr ErrFriendQuery -> IO (CEnum Connection)
tox_friend_get_connection_status ToxPtr
tox Word32
fn (CErr ErrFriendQuery -> IO (CEnum Connection))
-> (CEnum Connection -> IO Connection)
-> CErr ErrFriendQuery
-> IO Connection
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Connection -> IO Connection
forall (m :: * -> *) a. Monad m => a -> m a
return (Connection -> IO Connection)
-> (CEnum Connection -> Connection)
-> CEnum Connection
-> IO Connection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CEnum Connection -> Connection
forall a. Enum a => CEnum a -> a
fromCEnum)
toxFriendGetTyping :: ToxPtr -> Word32 -> IO (Either ErrFriendQuery Bool)
toxFriendGetTyping :: ToxPtr -> Word32 -> IO (Either ErrFriendQuery Bool)
toxFriendGetTyping ToxPtr
tox Word32
fn = (CErr ErrFriendQuery -> IO Bool) -> IO (Either ErrFriendQuery Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendQuery -> IO Bool)
-> IO (Either ErrFriendQuery Bool))
-> (CErr ErrFriendQuery -> IO Bool)
-> IO (Either ErrFriendQuery Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> CErr ErrFriendQuery -> IO Bool
tox_friend_get_typing ToxPtr
tox Word32
fn
toxSelfSetTyping :: ToxPtr -> Word32 -> Bool -> IO (Either ErrSetTyping Bool)
toxSelfSetTyping :: ToxPtr -> Word32 -> Bool -> IO (Either ErrSetTyping Bool)
toxSelfSetTyping ToxPtr
tox Word32
fn Bool
typing = (CErr ErrSetTyping -> IO Bool) -> IO (Either ErrSetTyping Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrSetTyping -> IO Bool) -> IO (Either ErrSetTyping Bool))
-> (CErr ErrSetTyping -> IO Bool) -> IO (Either ErrSetTyping Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> Bool -> CErr ErrSetTyping -> IO Bool
tox_self_set_typing ToxPtr
tox Word32
fn Bool
typing
toxFriendSendMessage :: ToxPtr -> Word32 -> MessageType -> BS.ByteString -> IO (Either ErrFriendSendMessage Word32)
toxFriendSendMessage :: ToxPtr
-> Word32
-> MessageType
-> ByteString
-> IO (Either ErrFriendSendMessage Word32)
toxFriendSendMessage ToxPtr
tox Word32
fn MessageType
messageType ByteString
message =
ByteString
-> (CStringLen -> IO (Either ErrFriendSendMessage Word32))
-> IO (Either ErrFriendSendMessage Word32)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
message ((CStringLen -> IO (Either ErrFriendSendMessage Word32))
-> IO (Either ErrFriendSendMessage Word32))
-> (CStringLen -> IO (Either ErrFriendSendMessage Word32))
-> IO (Either ErrFriendSendMessage Word32)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
msgStr, Int
msgLen) ->
(CErr ErrFriendSendMessage -> IO Word32)
-> IO (Either ErrFriendSendMessage Word32)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendSendMessage -> IO Word32)
-> IO (Either ErrFriendSendMessage Word32))
-> (CErr ErrFriendSendMessage -> IO Word32)
-> IO (Either ErrFriendSendMessage Word32)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32
-> CEnum MessageType
-> Ptr CChar
-> CSize
-> CErr ErrFriendSendMessage
-> IO Word32
tox_friend_send_message ToxPtr
tox Word32
fn (MessageType -> CEnum MessageType
forall a. Enum a => a -> CEnum a
toCEnum MessageType
messageType) Ptr CChar
msgStr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
msgLen)
toxHash :: BS.ByteString -> IO BS.ByteString
toxHash :: ByteString -> IO ByteString
toxHash ByteString
d =
let hashLen :: Int
hashLen = Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
tox_hash_length in
Int -> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
hashLen ((Ptr CChar -> IO ByteString) -> IO ByteString)
-> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
hashPtr ->
ByteString -> (CStringLen -> IO ByteString) -> IO ByteString
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
d ((CStringLen -> IO ByteString) -> IO ByteString)
-> (CStringLen -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
dataPtr, Int
dataLen) -> do
Bool
_ <- Ptr CChar -> Ptr CChar -> CSize -> IO Bool
tox_hash Ptr CChar
hashPtr Ptr CChar
dataPtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
dataLen)
CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
dataPtr, Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
dataLen)
toxFileControl :: ToxPtr -> Word32 -> Word32 -> FileControl -> IO (Either ErrFileControl Bool)
toxFileControl :: ToxPtr
-> Word32
-> Word32
-> FileControl
-> IO (Either ErrFileControl Bool)
toxFileControl ToxPtr
tox Word32
fn Word32
fileNum FileControl
control = (CErr ErrFileControl -> IO Bool) -> IO (Either ErrFileControl Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFileControl -> IO Bool)
-> IO (Either ErrFileControl Bool))
-> (CErr ErrFileControl -> IO Bool)
-> IO (Either ErrFileControl Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32
-> Word32
-> CEnum FileControl
-> CErr ErrFileControl
-> IO Bool
tox_file_control ToxPtr
tox Word32
fn Word32
fileNum (FileControl -> CEnum FileControl
forall a. Enum a => a -> CEnum a
toCEnum FileControl
control)
toxFileSeek :: ToxPtr -> Word32 -> Word32 -> Word64 -> IO (Either ErrFileSeek Bool)
toxFileSeek :: ToxPtr
-> Word32 -> Word32 -> Word64 -> IO (Either ErrFileSeek Bool)
toxFileSeek ToxPtr
tox Word32
fn Word32
fileNum Word64
pos = (CErr ErrFileSeek -> IO Bool) -> IO (Either ErrFileSeek Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFileSeek -> IO Bool) -> IO (Either ErrFileSeek Bool))
-> (CErr ErrFileSeek -> IO Bool) -> IO (Either ErrFileSeek Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> Word32 -> Word64 -> CErr ErrFileSeek -> IO Bool
tox_file_seek ToxPtr
tox Word32
fn Word32
fileNum Word64
pos
toxFileGetFileId :: ToxPtr -> Word32 -> Word32 -> IO (Either ErrFileGet BS.ByteString)
toxFileGetFileId :: ToxPtr -> Word32 -> Word32 -> IO (Either ErrFileGet ByteString)
toxFileGetFileId ToxPtr
tox Word32
fn Word32
fileNum =
let fileIdLen :: Int
fileIdLen = Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
tox_file_id_length in
Int
-> (Ptr CChar -> IO (Either ErrFileGet ByteString))
-> IO (Either ErrFileGet ByteString)
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
fileIdLen ((Ptr CChar -> IO (Either ErrFileGet ByteString))
-> IO (Either ErrFileGet ByteString))
-> (Ptr CChar -> IO (Either ErrFileGet ByteString))
-> IO (Either ErrFileGet ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
fileIdPtr -> do
Either ErrFileGet Bool
idRes <- (CErr ErrFileGet -> IO Bool) -> IO (Either ErrFileGet Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFileGet -> IO Bool) -> IO (Either ErrFileGet Bool))
-> (CErr ErrFileGet -> IO Bool) -> IO (Either ErrFileGet Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32 -> Word32 -> Ptr CChar -> CErr ErrFileGet -> IO Bool
tox_file_get_file_id ToxPtr
tox Word32
fn Word32
fileNum Ptr CChar
fileIdPtr
case Either ErrFileGet Bool
idRes of
Left ErrFileGet
err -> Either ErrFileGet ByteString -> IO (Either ErrFileGet ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrFileGet ByteString -> IO (Either ErrFileGet ByteString))
-> Either ErrFileGet ByteString
-> IO (Either ErrFileGet ByteString)
forall a b. (a -> b) -> a -> b
$ ErrFileGet -> Either ErrFileGet ByteString
forall a b. a -> Either a b
Left ErrFileGet
err
Right Bool
_ -> ByteString -> Either ErrFileGet ByteString
forall a b. b -> Either a b
Right (ByteString -> Either ErrFileGet ByteString)
-> IO ByteString -> IO (Either ErrFileGet ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
fileIdPtr, Int
fileIdLen)
toxFileSend :: ToxPtr -> Word32 -> FileKind -> Word64 -> BS.ByteString -> IO (Either ErrFileSend Word32)
toxFileSend :: ToxPtr
-> Word32
-> FileKind
-> Word64
-> ByteString
-> IO (Either ErrFileSend Word32)
toxFileSend ToxPtr
tox Word32
fn FileKind
fileKind Word64
fileSize ByteString
fileName =
ByteString
-> (CStringLen -> IO (Either ErrFileSend Word32))
-> IO (Either ErrFileSend Word32)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
fileName ((CStringLen -> IO (Either ErrFileSend Word32))
-> IO (Either ErrFileSend Word32))
-> (CStringLen -> IO (Either ErrFileSend Word32))
-> IO (Either ErrFileSend Word32)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
fileNamePtr, Int
fileNameLen) ->
(CErr ErrFileSend -> IO Word32) -> IO (Either ErrFileSend Word32)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFileSend -> IO Word32) -> IO (Either ErrFileSend Word32))
-> (CErr ErrFileSend -> IO Word32)
-> IO (Either ErrFileSend Word32)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32
-> Word32
-> Word64
-> Ptr CChar
-> Ptr CChar
-> CSize
-> CErr ErrFileSend
-> IO Word32
tox_file_send ToxPtr
tox Word32
fn (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ FileKind -> Int
forall a. Enum a => a -> Int
fromEnum FileKind
fileKind) Word64
fileSize Ptr CChar
forall a. Ptr a
nullPtr Ptr CChar
fileNamePtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
fileNameLen)
toxFileSendChunk :: ToxPtr -> Word32 -> Word32 -> Word64 -> BS.ByteString -> IO (Either ErrFileSendChunk Bool)
toxFileSendChunk :: ToxPtr
-> Word32
-> Word32
-> Word64
-> ByteString
-> IO (Either ErrFileSendChunk Bool)
toxFileSendChunk ToxPtr
tox Word32
fn Word32
fileNum Word64
pos ByteString
d =
ByteString
-> (CStringLen -> IO (Either ErrFileSendChunk Bool))
-> IO (Either ErrFileSendChunk Bool)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
d ((CStringLen -> IO (Either ErrFileSendChunk Bool))
-> IO (Either ErrFileSendChunk Bool))
-> (CStringLen -> IO (Either ErrFileSendChunk Bool))
-> IO (Either ErrFileSendChunk Bool)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
dataPtr, Int
dataLen) ->
(CErr ErrFileSendChunk -> IO Bool)
-> IO (Either ErrFileSendChunk Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFileSendChunk -> IO Bool)
-> IO (Either ErrFileSendChunk Bool))
-> (CErr ErrFileSendChunk -> IO Bool)
-> IO (Either ErrFileSendChunk Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32
-> Word32
-> Word64
-> Ptr CChar
-> CSize
-> CErr ErrFileSendChunk
-> IO Bool
tox_file_send_chunk ToxPtr
tox Word32
fn Word32
fileNum Word64
pos Ptr CChar
dataPtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
dataLen)
toxConferenceNew :: ToxPtr -> IO (Either ErrConferenceNew Word32)
toxConferenceNew :: ToxPtr -> IO (Either ErrConferenceNew Word32)
toxConferenceNew ToxPtr
tox = (CErr ErrConferenceNew -> IO Word32)
-> IO (Either ErrConferenceNew Word32)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferenceNew -> IO Word32)
-> IO (Either ErrConferenceNew Word32))
-> (CErr ErrConferenceNew -> IO Word32)
-> IO (Either ErrConferenceNew Word32)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> CErr ErrConferenceNew -> IO Word32
tox_conference_new ToxPtr
tox
toxConferenceDelete :: ToxPtr -> Word32 -> IO (Either ErrConferenceDelete Bool)
toxConferenceDelete :: ToxPtr -> Word32 -> IO (Either ErrConferenceDelete Bool)
toxConferenceDelete ToxPtr
tox Word32
gn = (CErr ErrConferenceDelete -> IO Bool)
-> IO (Either ErrConferenceDelete Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferenceDelete -> IO Bool)
-> IO (Either ErrConferenceDelete Bool))
-> (CErr ErrConferenceDelete -> IO Bool)
-> IO (Either ErrConferenceDelete Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> CErr ErrConferenceDelete -> IO Bool
tox_conference_delete ToxPtr
tox Word32
gn
toxConferencePeerCount :: ToxPtr -> Word32 -> IO (Either ErrConferencePeerQuery Word32)
toxConferencePeerCount :: ToxPtr -> Word32 -> IO (Either ErrConferencePeerQuery Word32)
toxConferencePeerCount ToxPtr
tox Word32
gn = (CErr ErrConferencePeerQuery -> IO Word32)
-> IO (Either ErrConferencePeerQuery Word32)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferencePeerQuery -> IO Word32)
-> IO (Either ErrConferencePeerQuery Word32))
-> (CErr ErrConferencePeerQuery -> IO Word32)
-> IO (Either ErrConferencePeerQuery Word32)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> CErr ErrConferencePeerQuery -> IO Word32
tox_conference_peer_count ToxPtr
tox Word32
gn
toxConferencePeerGetName :: ToxPtr -> Word32 -> Word32 -> IO (Either ErrConferencePeerQuery BS.ByteString)
toxConferencePeerGetName :: ToxPtr
-> Word32
-> Word32
-> IO (Either ErrConferencePeerQuery ByteString)
toxConferencePeerGetName ToxPtr
tox Word32
gn Word32
pn = do
Either ErrConferencePeerQuery CSize
nameLenRes <- (CErr ErrConferencePeerQuery -> IO CSize)
-> IO (Either ErrConferencePeerQuery CSize)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferencePeerQuery -> IO CSize)
-> IO (Either ErrConferencePeerQuery CSize))
-> (CErr ErrConferencePeerQuery -> IO CSize)
-> IO (Either ErrConferencePeerQuery CSize)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32 -> Word32 -> CErr ErrConferencePeerQuery -> IO CSize
tox_conference_peer_get_name_size ToxPtr
tox Word32
gn Word32
pn
case Either ErrConferencePeerQuery CSize
nameLenRes of
Left ErrConferencePeerQuery
err -> Either ErrConferencePeerQuery ByteString
-> IO (Either ErrConferencePeerQuery ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrConferencePeerQuery ByteString
-> IO (Either ErrConferencePeerQuery ByteString))
-> Either ErrConferencePeerQuery ByteString
-> IO (Either ErrConferencePeerQuery ByteString)
forall a b. (a -> b) -> a -> b
$ ErrConferencePeerQuery -> Either ErrConferencePeerQuery ByteString
forall a b. a -> Either a b
Left ErrConferencePeerQuery
err
Right CSize
nameLen -> Int
-> (Ptr CChar -> IO (Either ErrConferencePeerQuery ByteString))
-> IO (Either ErrConferencePeerQuery ByteString)
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
nameLen) ((Ptr CChar -> IO (Either ErrConferencePeerQuery ByteString))
-> IO (Either ErrConferencePeerQuery ByteString))
-> (Ptr CChar -> IO (Either ErrConferencePeerQuery ByteString))
-> IO (Either ErrConferencePeerQuery ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
namePtr -> do
Either ErrConferencePeerQuery Bool
nameRes <- (CErr ErrConferencePeerQuery -> IO Bool)
-> IO (Either ErrConferencePeerQuery Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferencePeerQuery -> IO Bool)
-> IO (Either ErrConferencePeerQuery Bool))
-> (CErr ErrConferencePeerQuery -> IO Bool)
-> IO (Either ErrConferencePeerQuery Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32
-> Word32
-> Ptr CChar
-> CErr ErrConferencePeerQuery
-> IO Bool
tox_conference_peer_get_name ToxPtr
tox Word32
gn Word32
pn Ptr CChar
namePtr
case Either ErrConferencePeerQuery Bool
nameRes of
Left ErrConferencePeerQuery
err -> Either ErrConferencePeerQuery ByteString
-> IO (Either ErrConferencePeerQuery ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrConferencePeerQuery ByteString
-> IO (Either ErrConferencePeerQuery ByteString))
-> Either ErrConferencePeerQuery ByteString
-> IO (Either ErrConferencePeerQuery ByteString)
forall a b. (a -> b) -> a -> b
$ ErrConferencePeerQuery -> Either ErrConferencePeerQuery ByteString
forall a b. a -> Either a b
Left ErrConferencePeerQuery
err
Right Bool
_ -> ByteString -> Either ErrConferencePeerQuery ByteString
forall a b. b -> Either a b
Right (ByteString -> Either ErrConferencePeerQuery ByteString)
-> IO ByteString -> IO (Either ErrConferencePeerQuery ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
namePtr, CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
nameLen)
toxConferencePeerGetPublicKey :: ToxPtr -> Word32 -> Word32 -> IO (Either ErrConferencePeerQuery BS.ByteString)
toxConferencePeerGetPublicKey :: ToxPtr
-> Word32
-> Word32
-> IO (Either ErrConferencePeerQuery ByteString)
toxConferencePeerGetPublicKey ToxPtr
tox Word32
gn Word32
pn =
let pkLen :: Int
pkLen = Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
tox_public_key_size in
Int
-> (Ptr CChar -> IO (Either ErrConferencePeerQuery ByteString))
-> IO (Either ErrConferencePeerQuery ByteString)
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
pkLen ((Ptr CChar -> IO (Either ErrConferencePeerQuery ByteString))
-> IO (Either ErrConferencePeerQuery ByteString))
-> (Ptr CChar -> IO (Either ErrConferencePeerQuery ByteString))
-> IO (Either ErrConferencePeerQuery ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
pkPtr -> do
Either ErrConferencePeerQuery Bool
nameRes <- (CErr ErrConferencePeerQuery -> IO Bool)
-> IO (Either ErrConferencePeerQuery Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferencePeerQuery -> IO Bool)
-> IO (Either ErrConferencePeerQuery Bool))
-> (CErr ErrConferencePeerQuery -> IO Bool)
-> IO (Either ErrConferencePeerQuery Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32
-> Word32
-> Ptr CChar
-> CErr ErrConferencePeerQuery
-> IO Bool
tox_conference_peer_get_public_key ToxPtr
tox Word32
gn Word32
pn Ptr CChar
pkPtr
case Either ErrConferencePeerQuery Bool
nameRes of
Left ErrConferencePeerQuery
err -> Either ErrConferencePeerQuery ByteString
-> IO (Either ErrConferencePeerQuery ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrConferencePeerQuery ByteString
-> IO (Either ErrConferencePeerQuery ByteString))
-> Either ErrConferencePeerQuery ByteString
-> IO (Either ErrConferencePeerQuery ByteString)
forall a b. (a -> b) -> a -> b
$ ErrConferencePeerQuery -> Either ErrConferencePeerQuery ByteString
forall a b. a -> Either a b
Left ErrConferencePeerQuery
err
Right Bool
_ -> ByteString -> Either ErrConferencePeerQuery ByteString
forall a b. b -> Either a b
Right (ByteString -> Either ErrConferencePeerQuery ByteString)
-> IO ByteString -> IO (Either ErrConferencePeerQuery ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
pkPtr, Int
pkLen)
toxConferencePeerNumberIsOurs :: ToxPtr -> Word32 -> Word32 -> IO (Either ErrConferencePeerQuery Bool)
toxConferencePeerNumberIsOurs :: ToxPtr
-> Word32 -> Word32 -> IO (Either ErrConferencePeerQuery Bool)
toxConferencePeerNumberIsOurs ToxPtr
tox Word32
gn Word32
pn = (CErr ErrConferencePeerQuery -> IO Bool)
-> IO (Either ErrConferencePeerQuery Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferencePeerQuery -> IO Bool)
-> IO (Either ErrConferencePeerQuery Bool))
-> (CErr ErrConferencePeerQuery -> IO Bool)
-> IO (Either ErrConferencePeerQuery Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32 -> Word32 -> CErr ErrConferencePeerQuery -> IO Bool
tox_conference_peer_number_is_ours ToxPtr
tox Word32
gn Word32
pn
toxConferenceInvite :: ToxPtr -> Word32 -> Word32 -> IO (Either ErrConferenceInvite Bool)
toxConferenceInvite :: ToxPtr -> Word32 -> Word32 -> IO (Either ErrConferenceInvite Bool)
toxConferenceInvite ToxPtr
tox Word32
fn Word32
gn = (CErr ErrConferenceInvite -> IO Bool)
-> IO (Either ErrConferenceInvite Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferenceInvite -> IO Bool)
-> IO (Either ErrConferenceInvite Bool))
-> (CErr ErrConferenceInvite -> IO Bool)
-> IO (Either ErrConferenceInvite Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> Word32 -> CErr ErrConferenceInvite -> IO Bool
tox_conference_invite ToxPtr
tox Word32
fn Word32
gn
toxConferenceJoin :: ToxPtr -> Word32 -> BS.ByteString -> IO (Either ErrConferenceJoin Word32)
toxConferenceJoin :: ToxPtr
-> Word32 -> ByteString -> IO (Either ErrConferenceJoin Word32)
toxConferenceJoin ToxPtr
tox Word32
fn ByteString
cookie =
ByteString
-> (CStringLen -> IO (Either ErrConferenceJoin Word32))
-> IO (Either ErrConferenceJoin Word32)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
cookie ((CStringLen -> IO (Either ErrConferenceJoin Word32))
-> IO (Either ErrConferenceJoin Word32))
-> (CStringLen -> IO (Either ErrConferenceJoin Word32))
-> IO (Either ErrConferenceJoin Word32)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
cookiePtr, Int
cookieLen) ->
(CErr ErrConferenceJoin -> IO Word32)
-> IO (Either ErrConferenceJoin Word32)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferenceJoin -> IO Word32)
-> IO (Either ErrConferenceJoin Word32))
-> (CErr ErrConferenceJoin -> IO Word32)
-> IO (Either ErrConferenceJoin Word32)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32
-> Ptr CChar
-> CSize
-> CErr ErrConferenceJoin
-> IO Word32
tox_conference_join ToxPtr
tox Word32
fn Ptr CChar
cookiePtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
cookieLen)
toxConferenceSendMessage :: ToxPtr -> Word32 -> MessageType -> BS.ByteString -> IO (Either ErrConferenceSendMessage Bool)
toxConferenceSendMessage :: ToxPtr
-> Word32
-> MessageType
-> ByteString
-> IO (Either ErrConferenceSendMessage Bool)
toxConferenceSendMessage ToxPtr
tox Word32
gn MessageType
messageType ByteString
message =
ByteString
-> (CStringLen -> IO (Either ErrConferenceSendMessage Bool))
-> IO (Either ErrConferenceSendMessage Bool)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
message ((CStringLen -> IO (Either ErrConferenceSendMessage Bool))
-> IO (Either ErrConferenceSendMessage Bool))
-> (CStringLen -> IO (Either ErrConferenceSendMessage Bool))
-> IO (Either ErrConferenceSendMessage Bool)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
msgPtr, Int
msgLen) ->
(CErr ErrConferenceSendMessage -> IO Bool)
-> IO (Either ErrConferenceSendMessage Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferenceSendMessage -> IO Bool)
-> IO (Either ErrConferenceSendMessage Bool))
-> (CErr ErrConferenceSendMessage -> IO Bool)
-> IO (Either ErrConferenceSendMessage Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32
-> CEnum MessageType
-> Ptr CChar
-> CSize
-> CErr ErrConferenceSendMessage
-> IO Bool
tox_conference_send_message ToxPtr
tox Word32
gn (MessageType -> CEnum MessageType
forall a. Enum a => a -> CEnum a
toCEnum MessageType
messageType) Ptr CChar
msgPtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
msgLen)
toxConferenceGetTitle :: ToxPtr -> Word32 -> IO (Either ErrConferenceTitle BS.ByteString)
toxConferenceGetTitle :: ToxPtr -> Word32 -> IO (Either ErrConferenceTitle ByteString)
toxConferenceGetTitle ToxPtr
tox Word32
gn = do
Either ErrConferenceTitle CSize
titleLenRes <- (CErr ErrConferenceTitle -> IO CSize)
-> IO (Either ErrConferenceTitle CSize)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferenceTitle -> IO CSize)
-> IO (Either ErrConferenceTitle CSize))
-> (CErr ErrConferenceTitle -> IO CSize)
-> IO (Either ErrConferenceTitle CSize)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> CErr ErrConferenceTitle -> IO CSize
tox_conference_get_title_size ToxPtr
tox Word32
gn
case Either ErrConferenceTitle CSize
titleLenRes of
Left ErrConferenceTitle
err -> Either ErrConferenceTitle ByteString
-> IO (Either ErrConferenceTitle ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrConferenceTitle ByteString
-> IO (Either ErrConferenceTitle ByteString))
-> Either ErrConferenceTitle ByteString
-> IO (Either ErrConferenceTitle ByteString)
forall a b. (a -> b) -> a -> b
$ ErrConferenceTitle -> Either ErrConferenceTitle ByteString
forall a b. a -> Either a b
Left ErrConferenceTitle
err
Right CSize
titleLen -> Int
-> (Ptr CChar -> IO (Either ErrConferenceTitle ByteString))
-> IO (Either ErrConferenceTitle ByteString)
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
titleLen) ((Ptr CChar -> IO (Either ErrConferenceTitle ByteString))
-> IO (Either ErrConferenceTitle ByteString))
-> (Ptr CChar -> IO (Either ErrConferenceTitle ByteString))
-> IO (Either ErrConferenceTitle ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
titlePtr -> do
Either ErrConferenceTitle Bool
titleRes <- (CErr ErrConferenceTitle -> IO Bool)
-> IO (Either ErrConferenceTitle Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferenceTitle -> IO Bool)
-> IO (Either ErrConferenceTitle Bool))
-> (CErr ErrConferenceTitle -> IO Bool)
-> IO (Either ErrConferenceTitle Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> Word32 -> Ptr CChar -> CErr ErrConferenceTitle -> IO Bool
tox_conference_get_title ToxPtr
tox Word32
gn Ptr CChar
titlePtr
case Either ErrConferenceTitle Bool
titleRes of
Left ErrConferenceTitle
err -> Either ErrConferenceTitle ByteString
-> IO (Either ErrConferenceTitle ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ErrConferenceTitle ByteString
-> IO (Either ErrConferenceTitle ByteString))
-> Either ErrConferenceTitle ByteString
-> IO (Either ErrConferenceTitle ByteString)
forall a b. (a -> b) -> a -> b
$ ErrConferenceTitle -> Either ErrConferenceTitle ByteString
forall a b. a -> Either a b
Left ErrConferenceTitle
err
Right Bool
_ -> ByteString -> Either ErrConferenceTitle ByteString
forall a b. b -> Either a b
Right (ByteString -> Either ErrConferenceTitle ByteString)
-> IO ByteString -> IO (Either ErrConferenceTitle ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
titlePtr, CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
titleLen)
toxConferenceSetTitle :: ToxPtr -> Word32 -> BS.ByteString -> IO (Either ErrConferenceTitle Bool)
toxConferenceSetTitle :: ToxPtr
-> Word32 -> ByteString -> IO (Either ErrConferenceTitle Bool)
toxConferenceSetTitle ToxPtr
tox Word32
gn ByteString
title =
ByteString
-> (CStringLen -> IO (Either ErrConferenceTitle Bool))
-> IO (Either ErrConferenceTitle Bool)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
title ((CStringLen -> IO (Either ErrConferenceTitle Bool))
-> IO (Either ErrConferenceTitle Bool))
-> (CStringLen -> IO (Either ErrConferenceTitle Bool))
-> IO (Either ErrConferenceTitle Bool)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
titlePtr, Int
titleLen) ->
(CErr ErrConferenceTitle -> IO Bool)
-> IO (Either ErrConferenceTitle Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrConferenceTitle -> IO Bool)
-> IO (Either ErrConferenceTitle Bool))
-> (CErr ErrConferenceTitle -> IO Bool)
-> IO (Either ErrConferenceTitle Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32
-> Ptr CChar
-> CSize
-> CErr ErrConferenceTitle
-> IO Bool
tox_conference_set_title ToxPtr
tox Word32
gn Ptr CChar
titlePtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
titleLen)
toxConferenceGetChatlist :: ToxPtr -> IO [Word32]
toxConferenceGetChatlist :: ToxPtr -> IO [Word32]
toxConferenceGetChatlist ToxPtr
tox = do
CSize
chatListSize <- ToxPtr -> IO CSize
tox_conference_get_chatlist_size ToxPtr
tox
Int -> (Ptr Word32 -> IO [Word32]) -> IO [Word32]
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
chatListSize) ((Ptr Word32 -> IO [Word32]) -> IO [Word32])
-> (Ptr Word32 -> IO [Word32]) -> IO [Word32]
forall a b. (a -> b) -> a -> b
$ \Ptr Word32
chatListPtr -> do
ToxPtr -> Ptr Word32 -> IO ()
tox_conference_get_chatlist ToxPtr
tox Ptr Word32
chatListPtr
Int -> Ptr Word32 -> IO [Word32]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
chatListSize) Ptr Word32
chatListPtr
toxConferenceGetType :: ToxPtr -> Word32 -> IO (Either ErrConferenceGetType ConferenceType)
toxConferenceGetType :: ToxPtr -> Word32 -> IO (Either ErrConferenceGetType ConferenceType)
toxConferenceGetType ToxPtr
tox Word32
gn = (CErr ErrConferenceGetType -> IO ConferenceType)
-> IO (Either ErrConferenceGetType ConferenceType)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun (ToxPtr
-> Word32 -> CErr ErrConferenceGetType -> IO (CEnum ConferenceType)
tox_conference_get_type ToxPtr
tox Word32
gn (CErr ErrConferenceGetType -> IO (CEnum ConferenceType))
-> (CEnum ConferenceType -> IO ConferenceType)
-> CErr ErrConferenceGetType
-> IO ConferenceType
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ConferenceType -> IO ConferenceType
forall (m :: * -> *) a. Monad m => a -> m a
return (ConferenceType -> IO ConferenceType)
-> (CEnum ConferenceType -> ConferenceType)
-> CEnum ConferenceType
-> IO ConferenceType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CEnum ConferenceType -> ConferenceType
forall a. Enum a => CEnum a -> a
fromCEnum))
toxFriendLossyPacket :: ToxPtr -> Word32 -> BS.ByteString -> IO (Either ErrFriendCustomPacket Bool)
toxFriendLossyPacket :: ToxPtr
-> Word32 -> ByteString -> IO (Either ErrFriendCustomPacket Bool)
toxFriendLossyPacket ToxPtr
tox Word32
fn ByteString
d =
ByteString
-> (CStringLen -> IO (Either ErrFriendCustomPacket Bool))
-> IO (Either ErrFriendCustomPacket Bool)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
d ((CStringLen -> IO (Either ErrFriendCustomPacket Bool))
-> IO (Either ErrFriendCustomPacket Bool))
-> (CStringLen -> IO (Either ErrFriendCustomPacket Bool))
-> IO (Either ErrFriendCustomPacket Bool)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
dataPtr, Int
dataLen) ->
(CErr ErrFriendCustomPacket -> IO Bool)
-> IO (Either ErrFriendCustomPacket Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendCustomPacket -> IO Bool)
-> IO (Either ErrFriendCustomPacket Bool))
-> (CErr ErrFriendCustomPacket -> IO Bool)
-> IO (Either ErrFriendCustomPacket Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32
-> Ptr CChar
-> CSize
-> CErr ErrFriendCustomPacket
-> IO Bool
tox_friend_send_lossy_packet ToxPtr
tox Word32
fn Ptr CChar
dataPtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
dataLen)
toxFriendLosslessPacket :: ToxPtr -> Word32 -> BS.ByteString -> IO (Either ErrFriendCustomPacket Bool)
toxFriendLosslessPacket :: ToxPtr
-> Word32 -> ByteString -> IO (Either ErrFriendCustomPacket Bool)
toxFriendLosslessPacket ToxPtr
tox Word32
fn ByteString
d =
ByteString
-> (CStringLen -> IO (Either ErrFriendCustomPacket Bool))
-> IO (Either ErrFriendCustomPacket Bool)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
d ((CStringLen -> IO (Either ErrFriendCustomPacket Bool))
-> IO (Either ErrFriendCustomPacket Bool))
-> (CStringLen -> IO (Either ErrFriendCustomPacket Bool))
-> IO (Either ErrFriendCustomPacket Bool)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
dataPtr, Int
dataLen) ->
(CErr ErrFriendCustomPacket -> IO Bool)
-> IO (Either ErrFriendCustomPacket Bool)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrFriendCustomPacket -> IO Bool)
-> IO (Either ErrFriendCustomPacket Bool))
-> (CErr ErrFriendCustomPacket -> IO Bool)
-> IO (Either ErrFriendCustomPacket Bool)
forall a b. (a -> b) -> a -> b
$ ToxPtr
-> Word32
-> Ptr CChar
-> CSize
-> CErr ErrFriendCustomPacket
-> IO Bool
tox_friend_send_lossless_packet ToxPtr
tox Word32
fn Ptr CChar
dataPtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
dataLen)
toxSelfGetDhtId :: ToxPtr -> IO BS.ByteString
toxSelfGetDhtId :: ToxPtr -> IO ByteString
toxSelfGetDhtId ToxPtr
tox =
let idLen :: Int
idLen = Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
tox_public_key_size in
Int -> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
idLen ((Ptr CChar -> IO ByteString) -> IO ByteString)
-> (Ptr CChar -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
idPtr -> do
ToxPtr -> Ptr CChar -> IO ()
tox_self_get_dht_id ToxPtr
tox Ptr CChar
idPtr
CStringLen -> IO ByteString
BS.packCStringLen (Ptr CChar
idPtr, Int
idLen)
toxSelfGetUdpPort :: ToxPtr -> IO (Either ErrGetPort Word16)
toxSelfGetUdpPort :: ToxPtr -> IO (Either ErrGetPort Word16)
toxSelfGetUdpPort ToxPtr
tox = (CErr ErrGetPort -> IO Word16) -> IO (Either ErrGetPort Word16)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrGetPort -> IO Word16) -> IO (Either ErrGetPort Word16))
-> (CErr ErrGetPort -> IO Word16) -> IO (Either ErrGetPort Word16)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> CErr ErrGetPort -> IO Word16
tox_self_get_udp_port ToxPtr
tox
toxSelfGetTcpPort :: ToxPtr -> IO (Either ErrGetPort Word16)
toxSelfGetTcpPort :: ToxPtr -> IO (Either ErrGetPort Word16)
toxSelfGetTcpPort ToxPtr
tox = (CErr ErrGetPort -> IO Word16) -> IO (Either ErrGetPort Word16)
forall err r.
(Eq err, Enum err, Bounded err) =>
(CErr err -> IO r) -> IO (Either err r)
callErrFun ((CErr ErrGetPort -> IO Word16) -> IO (Either ErrGetPort Word16))
-> (CErr ErrGetPort -> IO Word16) -> IO (Either ErrGetPort Word16)
forall a b. (a -> b) -> a -> b
$ ToxPtr -> CErr ErrGetPort -> IO Word16
tox_self_get_tcp_port ToxPtr
tox