7
7
8
8
module Network.Socket.Info where
9
9
10
+ import Data.List.NonEmpty (NonEmpty (.. ))
11
+ import qualified Data.List.NonEmpty as NE
10
12
import Foreign.Marshal.Alloc (alloca , allocaBytes )
11
13
import Foreign.Marshal.Utils (maybeWith , with )
12
14
import GHC.IO.Exception (IOErrorType (NoSuchThing ))
@@ -200,53 +202,72 @@ defaultHints = AddrInfo {
200
202
, addrCanonName = Nothing
201
203
}
202
204
203
- -----------------------------------------------------------------------------
204
- -- | Resolve a host or service name to one or more addresses.
205
- -- The 'AddrInfo' values that this function returns contain 'SockAddr'
206
- -- values that you can pass directly to 'connect' or
207
- -- 'bind'.
208
- --
209
- -- This function is protocol independent. It can return both IPv4 and
210
- -- IPv6 address information.
211
- --
212
- -- The 'AddrInfo' argument specifies the preferred query behaviour,
213
- -- socket options, or protocol. You can override these conveniently
214
- -- using Haskell's record update syntax on 'defaultHints', for example
215
- -- as follows:
216
- --
217
- -- >>> let hints = defaultHints { addrFlags = [AI_NUMERICHOST], addrSocketType = Stream }
218
- --
219
- -- You must provide a 'Just' value for at least one of the 'HostName'
220
- -- or 'ServiceName' arguments. 'HostName' can be either a numeric
221
- -- network address (dotted quad for IPv4, colon-separated hex for
222
- -- IPv6) or a hostname. In the latter case, its addresses will be
223
- -- looked up unless 'AI_NUMERICHOST' is specified as a hint. If you
224
- -- do not provide a 'HostName' value /and/ do not set 'AI_PASSIVE' as
225
- -- a hint, network addresses in the result will contain the address of
226
- -- the loopback interface.
227
- --
228
- -- If the query fails, this function throws an IO exception instead of
229
- -- returning an empty list. Otherwise, it returns a non-empty list
230
- -- of 'AddrInfo' values.
231
- --
232
- -- There are several reasons why a query might result in several
233
- -- values. For example, the queried-for host could be multihomed, or
234
- -- the service might be available via several protocols.
235
- --
236
- -- Note: the order of arguments is slightly different to that defined
237
- -- for @getaddrinfo@ in RFC 2553. The 'AddrInfo' parameter comes first
238
- -- to make partial application easier.
239
- --
240
- -- >>> addr:_ <- getAddrInfo (Just hints) (Just "127.0.0.1") (Just "http")
241
- -- >>> addrAddress addr
242
- -- 127.0.0.1:80
243
-
244
- getAddrInfo
205
+ class GetAddrInfo t where
206
+ -----------------------------------------------------------------------------
207
+ -- | Resolve a host or service name to one or more addresses.
208
+ -- The 'AddrInfo' values that this function returns contain 'SockAddr'
209
+ -- values that you can pass directly to 'connect' or
210
+ -- 'bind'.
211
+ --
212
+ -- This function calls @getaddrinfo(3)@, which never successfully returns
213
+ -- with an empty list. If the query fails, 'getAddrInfo' throws an IO
214
+ -- exception.
215
+ --
216
+ -- For backwards-compatibility reasons, a hidden 'GetAddrInfo' class is used
217
+ -- to make the result polymorphic. It only has instances for @[]@ (lists)
218
+ -- and 'NonEmpty'. Use of 'NonEmpty' is recommended.
219
+ --
220
+ -- This function is protocol independent. It can return both IPv4 and
221
+ -- IPv6 address information.
222
+ --
223
+ -- The 'AddrInfo' argument specifies the preferred query behaviour,
224
+ -- socket options, or protocol. You can override these conveniently
225
+ -- using Haskell's record update syntax on 'defaultHints', for example
226
+ -- as follows:
227
+ --
228
+ -- >>> let hints = defaultHints { addrFlags = [AI_NUMERICHOST], addrSocketType = Stream }
229
+ --
230
+ -- You must provide a 'Just' value for at least one of the 'HostName'
231
+ -- or 'ServiceName' arguments. 'HostName' can be either a numeric
232
+ -- network address (dotted quad for IPv4, colon-separated hex for
233
+ -- IPv6) or a hostname. In the latter case, its addresses will be
234
+ -- looked up unless 'AI_NUMERICHOST' is specified as a hint. If you
235
+ -- do not provide a 'HostName' value /and/ do not set 'AI_PASSIVE' as
236
+ -- a hint, network addresses in the result will contain the address of
237
+ -- the loopback interface.
238
+ --
239
+ -- There are several reasons why a query might result in several
240
+ -- values. For example, the queried-for host could be multihomed, or
241
+ -- the service might be available via several protocols.
242
+ --
243
+ -- Note: the order of arguments is slightly different to that defined
244
+ -- for @getaddrinfo@ in RFC 2553. The 'AddrInfo' parameter comes first
245
+ -- to make partial application easier.
246
+ --
247
+ -- >>> import qualified Data.List.NonEmpty as NE
248
+ -- >>> addr <- NE.head <$> getAddrInfo (Just hints) (Just "127.0.0.1") (Just "http")
249
+ -- >>> addrAddress addr
250
+ -- 127.0.0.1:80
251
+ --
252
+ -- Polymorphic version: @since 3.2.3.0
253
+ getAddrInfo
254
+ :: Maybe AddrInfo -- ^ preferred socket type or protocol
255
+ -> Maybe HostName -- ^ host name to look up
256
+ -> Maybe ServiceName -- ^ service name to look up
257
+ -> IO (t AddrInfo ) -- ^ resolved addresses, with "best" first
258
+
259
+ instance GetAddrInfo [] where
260
+ getAddrInfo = getAddrInfoList
261
+
262
+ instance GetAddrInfo NE. NonEmpty where
263
+ getAddrInfo = getAddrInfoNE
264
+
265
+ getAddrInfoNE
245
266
:: Maybe AddrInfo -- ^ preferred socket type or protocol
246
267
-> Maybe HostName -- ^ host name to look up
247
268
-> Maybe ServiceName -- ^ service name to look up
248
- -> IO [ AddrInfo ] -- ^ resolved addresses, with "best" first
249
- getAddrInfo hints node service = alloc getaddrinfo
269
+ -> IO ( NonEmpty AddrInfo ) -- ^ resolved addresses, with "best" first
270
+ getAddrInfoNE hints node service = alloc getaddrinfo
250
271
where
251
272
alloc body = withSocketsDo $ maybeWith withCString node $ \ c_node ->
252
273
maybeWith withCString service $ \ c_service ->
@@ -258,12 +279,7 @@ getAddrInfo hints node service = alloc getaddrinfo
258
279
if ret == 0 then do
259
280
ptr_addrs <- peek ptr_ptr_addrs
260
281
ais <- followAddrInfo ptr_addrs
261
- c_freeaddrinfo ptr_addrs
262
- -- POSIX requires that getaddrinfo(3) returns at least one addrinfo.
263
- -- See: http://pubs.opengroup.org/onlinepubs/9699919799/functions/getaddrinfo.html
264
- case ais of
265
- [] -> ioError $ mkIOError NoSuchThing message Nothing Nothing
266
- _ -> return ais
282
+ return ais
267
283
else do
268
284
err <- gai_strerror ret
269
285
ioError $ ioeSetErrorString
@@ -290,13 +306,33 @@ getAddrInfo hints node service = alloc getaddrinfo
290
306
filteredHints = hints
291
307
#endif
292
308
293
- followAddrInfo :: Ptr AddrInfo -> IO [AddrInfo ]
309
+ getAddrInfoList
310
+ :: Maybe AddrInfo
311
+ -> Maybe HostName
312
+ -> Maybe ServiceName
313
+ -> IO [AddrInfo ]
314
+ getAddrInfoList hints node service =
315
+ -- getAddrInfo never returns an empty list.
316
+ NE. toList <$> getAddrInfoNE hints node service
317
+
318
+ followAddrInfo :: Ptr AddrInfo -> IO (NonEmpty AddrInfo )
294
319
followAddrInfo ptr_ai
295
- | ptr_ai == nullPtr = return []
320
+ -- POSIX requires that getaddrinfo(3) returns at least one addrinfo.
321
+ -- See: http://pubs.opengroup.org/onlinepubs/9699919799/functions/getaddrinfo.html
322
+ | ptr_ai == nullPtr = ioError $ mkIOError NoSuchThing " getaddrinfo must return at least one addrinfo" Nothing Nothing
296
323
| otherwise = do
297
- a <- peek ptr_ai
298
- as <- (# peek struct addrinfo, ai_next) ptr_ai >>= followAddrInfo
299
- return (a : as)
324
+ a <- peek ptr_ai
325
+ ptr <- (# peek struct addrinfo, ai_next) ptr_ai
326
+ (a :| ) <$> go ptr
327
+ where
328
+ go :: Ptr AddrInfo -> IO [AddrInfo ]
329
+ go ptr
330
+ | ptr == nullPtr = return []
331
+ | otherwise = do
332
+ a' <- peek ptr
333
+ ptr' <- (# peek struct addrinfo, ai_next) ptr
334
+ as' <- go ptr'
335
+ return (a': as')
300
336
301
337
foreign import ccall safe " hsnet_getaddrinfo"
302
338
c_getaddrinfo :: CString -> CString -> Ptr AddrInfo -> Ptr (Ptr AddrInfo )
0 commit comments