Skip to content

Commit c9f8b93

Browse files
committed
refactor: Use apigen to generate the foreign imports and enums.
1 parent 6a20b48 commit c9f8b93

File tree

13 files changed

+1110
-931
lines changed

13 files changed

+1110
-931
lines changed

Diff for: src/FFI/Tox/Tox.hs

+886
Large diffs are not rendered by default.

Diff for: src/Network/Tox/C/CEnum.hs renamed to src/Foreign/C/Enum.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
22
{-# LANGUAGE ScopedTypeVariables #-}
33
{-# LANGUAGE StrictData #-}
4-
module Network.Tox.C.CEnum where
4+
module Foreign.C.Enum where
55

66
import Foreign.C.Types (CInt)
77
import Foreign.Marshal.Alloc (alloca)

Diff for: src/Network/Tox/C.hs

+30
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,36 @@ module Network.Tox.C
22
( module M
33
) where
44

5+
import FFI.Tox.Tox as M (Connection (..),
6+
ErrBootstrap (..),
7+
ErrConferenceDelete (..),
8+
ErrConferenceGetType (..),
9+
ErrConferenceInvite (..),
10+
ErrConferenceJoin (..),
11+
ErrConferenceNew (..),
12+
ErrConferencePeerQuery (..),
13+
ErrConferenceSendMessage (..),
14+
ErrConferenceTitle (..),
15+
ErrFileControl (..),
16+
ErrFileGet (..),
17+
ErrFileSeek (..),
18+
ErrFileSend (..),
19+
ErrFileSendChunk (..),
20+
ErrFriendAdd (..),
21+
ErrFriendByPublicKey (..),
22+
ErrFriendCustomPacket (..),
23+
ErrFriendDelete (..),
24+
ErrFriendGetLastOnline (..),
25+
ErrFriendGetPublicKey (..),
26+
ErrFriendQuery (..),
27+
ErrFriendSendMessage (..),
28+
ErrGetPort (..), ErrNew (..),
29+
ErrSetInfo (..),
30+
ErrSetTyping (..),
31+
FileKind (..), LogLevel (..),
32+
MessageType (..),
33+
ProxyType (..),
34+
SavedataType (..), ToxPtr)
535
import Network.Tox.C.Constants as M
636
import Network.Tox.C.Options as M
737
import Network.Tox.C.Tox as M

Diff for: src/Network/Tox/C/Options.hs

+34-73
Original file line numberDiff line numberDiff line change
@@ -3,16 +3,40 @@
33
{-# LANGUAGE StrictData #-}
44
module Network.Tox.C.Options where
55

6-
import Control.Exception (bracket)
7-
import Data.ByteString (ByteString)
8-
import qualified Data.ByteString as BS
9-
import Data.Word (Word16, Word32)
10-
import Foreign.C.String (CString, peekCString, withCString)
11-
import Foreign.C.Types (CInt (..), CSize (..))
12-
import Foreign.Ptr (FunPtr, Ptr, nullPtr)
13-
import GHC.Generics (Generic)
14-
15-
import Network.Tox.C.CEnum
6+
import Control.Exception (bracket)
7+
import Data.ByteString (ByteString)
8+
import qualified Data.ByteString as BS
9+
import Data.Word (Word16)
10+
import Foreign.C.Enum
11+
import Foreign.C.String (peekCString, withCString)
12+
import Foreign.Ptr (nullPtr)
13+
import GHC.Generics (Generic)
14+
15+
import FFI.Tox.Tox (LogCb, LogLevel (..), OptionsPtr,
16+
ProxyType (..), SavedataType (..),
17+
tox_options_get_end_port,
18+
tox_options_get_ipv6_enabled,
19+
tox_options_get_proxy_host,
20+
tox_options_get_proxy_port,
21+
tox_options_get_proxy_type,
22+
tox_options_get_savedata_data,
23+
tox_options_get_savedata_length,
24+
tox_options_get_savedata_type,
25+
tox_options_get_start_port,
26+
tox_options_get_tcp_port,
27+
tox_options_get_udp_enabled,
28+
tox_options_set_end_port,
29+
tox_options_set_ipv6_enabled,
30+
tox_options_set_log_callback,
31+
tox_options_set_proxy_host,
32+
tox_options_set_proxy_port,
33+
tox_options_set_proxy_type,
34+
tox_options_set_savedata_data,
35+
tox_options_set_savedata_length,
36+
tox_options_set_savedata_type,
37+
tox_options_set_start_port,
38+
tox_options_set_tcp_port,
39+
tox_options_set_udp_enabled, wrapLogCb)
1640

1741
--------------------------------------------------------------------------------
1842
--
@@ -21,28 +45,6 @@ import Network.Tox.C.CEnum
2145
--------------------------------------------------------------------------------
2246

2347

24-
-- | Type of proxy used to connect to TCP relays.
25-
data ProxyType
26-
= ProxyTypeNone
27-
-- Don't use a proxy.
28-
| ProxyTypeHttp
29-
-- HTTP proxy using CONNECT.
30-
| ProxyTypeSocks5
31-
-- SOCKS proxy for simple socket pipes.
32-
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
33-
34-
35-
-- Type of savedata to create the Tox instance from.
36-
data SavedataType
37-
= SavedataTypeNone
38-
-- No savedata.
39-
| SavedataTypeToxSave
40-
-- Savedata is one that was obtained from tox_get_savedata
41-
| SavedataTypeSecretKey
42-
-- Savedata is a secret key of length 'tox_secret_key_size'
43-
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
44-
45-
4648
-- This struct contains all the startup options for Tox. You can either allocate
4749
-- this object yourself, and pass it to tox_options_default, or call
4850
-- tox_options_new to get a new default options object.
@@ -132,54 +134,13 @@ defaultOptions = Options
132134
}
133135

134136

135-
data OptionsStruct
136-
type OptionsPtr = Ptr OptionsStruct
137-
138-
139-
foreign import ccall tox_options_get_ipv6_enabled :: OptionsPtr -> IO Bool
140-
foreign import ccall tox_options_get_udp_enabled :: OptionsPtr -> IO Bool
141-
foreign import ccall tox_options_get_proxy_type :: OptionsPtr -> IO (CEnum ProxyType)
142-
foreign import ccall tox_options_get_proxy_host :: OptionsPtr -> IO CString
143-
foreign import ccall tox_options_get_proxy_port :: OptionsPtr -> IO Word16
144-
foreign import ccall tox_options_get_start_port :: OptionsPtr -> IO Word16
145-
foreign import ccall tox_options_get_end_port :: OptionsPtr -> IO Word16
146-
foreign import ccall tox_options_get_tcp_port :: OptionsPtr -> IO Word16
147-
foreign import ccall tox_options_get_savedata_type :: OptionsPtr -> IO (CEnum SavedataType)
148-
foreign import ccall tox_options_get_savedata_data :: OptionsPtr -> IO CString
149-
foreign import ccall tox_options_get_savedata_length :: OptionsPtr -> IO CSize
150-
151-
foreign import ccall tox_options_set_ipv6_enabled :: OptionsPtr -> Bool -> IO ()
152-
foreign import ccall tox_options_set_udp_enabled :: OptionsPtr -> Bool -> IO ()
153-
foreign import ccall tox_options_set_proxy_type :: OptionsPtr -> CEnum ProxyType -> IO ()
154-
foreign import ccall tox_options_set_proxy_host :: OptionsPtr -> CString -> IO ()
155-
foreign import ccall tox_options_set_proxy_port :: OptionsPtr -> Word16 -> IO ()
156-
foreign import ccall tox_options_set_start_port :: OptionsPtr -> Word16 -> IO ()
157-
foreign import ccall tox_options_set_end_port :: OptionsPtr -> Word16 -> IO ()
158-
foreign import ccall tox_options_set_tcp_port :: OptionsPtr -> Word16 -> IO ()
159-
foreign import ccall tox_options_set_savedata_type :: OptionsPtr -> CEnum SavedataType -> IO ()
160-
foreign import ccall tox_options_set_savedata_data :: OptionsPtr -> CString -> CSize -> IO ()
161-
foreign import ccall tox_options_set_savedata_length :: OptionsPtr -> CSize -> IO ()
162-
163-
164-
data LogLevel
165-
= LogLevelTrace
166-
| LogLevelDebug
167-
| LogLevelInfo
168-
| LogLevelWarning
169-
| LogLevelError
170-
deriving (Eq, Ord, Enum, Bounded, Read, Show)
171-
172137
logLevelName :: LogLevel -> Char
173138
logLevelName LogLevelTrace = 'T'
174139
logLevelName LogLevelDebug = 'D'
175140
logLevelName LogLevelInfo = 'I'
176141
logLevelName LogLevelWarning = 'W'
177142
logLevelName LogLevelError = 'E'
178143

179-
type LogCb = Ptr () -> CEnum LogLevel -> CString -> Word32 -> CString -> CString -> Ptr () -> IO ()
180-
foreign import ccall tox_options_set_log_callback :: OptionsPtr -> FunPtr LogCb -> IO ()
181-
foreign import ccall "wrapper" wrapLogCb :: LogCb -> IO (FunPtr LogCb)
182-
183144
logHandler :: LogCb
184145
logHandler _ cLevel cFile line cFunc cMsg _ = do
185146
let level = fromCEnum cLevel

0 commit comments

Comments
 (0)