Skip to content

Commit 795cebb

Browse files
committed
defining followAddrInfo for NonEmpty
1 parent c3fbccc commit 795cebb

File tree

1 file changed

+24
-17
lines changed

1 file changed

+24
-17
lines changed

Diff for: Network/Socket/Info.hsc

+24-17
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77

88
module Network.Socket.Info where
99

10+
import Data.List.NonEmpty (NonEmpty(..))
1011
import qualified Data.List.NonEmpty as NE
1112
import Foreign.Marshal.Alloc (alloca, allocaBytes)
1213
import Foreign.Marshal.Utils (maybeWith, with)
@@ -255,12 +256,12 @@ instance GetAddrInfo [] where
255256
instance GetAddrInfo NE.NonEmpty where
256257
getAddrInfo = getAddrInfoNE
257258

258-
getAddrInfoList
259+
getAddrInfoNE
259260
:: Maybe AddrInfo -- ^ preferred socket type or protocol
260261
-> Maybe HostName -- ^ host name to look up
261262
-> Maybe ServiceName -- ^ service name to look up
262-
-> IO [AddrInfo] -- ^ resolved addresses, with "best" first
263-
getAddrInfoList hints node service = alloc getaddrinfo
263+
-> IO (NonEmpty AddrInfo) -- ^ resolved addresses, with "best" first
264+
getAddrInfoNE hints node service = alloc getaddrinfo
264265
where
265266
alloc body = withSocketsDo $ maybeWith withCString node $ \c_node ->
266267
maybeWith withCString service $ \c_service ->
@@ -271,13 +272,10 @@ getAddrInfoList hints node service = alloc getaddrinfo
271272
ret <- c_getaddrinfo c_node c_service c_hints ptr_ptr_addrs
272273
if ret == 0 then do
273274
ptr_addrs <- peek ptr_ptr_addrs
274-
ais <- followAddrInfo ptr_addrs
275-
c_freeaddrinfo ptr_addrs
276275
-- POSIX requires that getaddrinfo(3) returns at least one addrinfo.
277276
-- See: http://pubs.opengroup.org/onlinepubs/9699919799/functions/getaddrinfo.html
278-
case ais of
279-
[] -> ioError $ mkIOError NoSuchThing message Nothing Nothing
280-
_ -> return ais
277+
ais <- followAddrInfo ptr_addrs
278+
return ais
281279
else do
282280
err <- gai_strerror ret
283281
ioError $ ioeSetErrorString
@@ -304,22 +302,31 @@ getAddrInfoList hints node service = alloc getaddrinfo
304302
filteredHints = hints
305303
#endif
306304

307-
getAddrInfoNE
305+
getAddrInfoList
308306
:: Maybe AddrInfo
309307
-> Maybe HostName
310308
-> Maybe ServiceName
311-
-> IO (NE.NonEmpty AddrInfo)
312-
getAddrInfoNE hints node service =
309+
-> IO [AddrInfo]
310+
getAddrInfoList hints node service =
313311
-- getAddrInfo never returns an empty list.
314-
NE.fromList <$> getAddrInfo hints node service
312+
NE.toList <$> getAddrInfoNE hints node service
315313

316-
followAddrInfo :: Ptr AddrInfo -> IO [AddrInfo]
314+
followAddrInfo :: Ptr AddrInfo -> IO (NonEmpty AddrInfo)
317315
followAddrInfo ptr_ai
318-
| ptr_ai == nullPtr = return []
316+
| ptr_ai == nullPtr = error "fixme"
319317
| otherwise = do
320-
a <- peek ptr_ai
321-
as <- (# peek struct addrinfo, ai_next) ptr_ai >>= followAddrInfo
322-
return (a : as)
318+
a <- peek ptr_ai
319+
ptr <- (# peek struct addrinfo, ai_next) ptr_ai
320+
go ptr a
321+
where
322+
go :: Ptr AddrInfo -> AddrInfo -> IO (NonEmpty AddrInfo)
323+
go ptr a
324+
| ptr == nullPtr = return $ NE.singleton a
325+
| otherwise = do
326+
a' <- peek ptr
327+
ptr' <- (# peek struct addrinfo, ai_next) ptr
328+
as <- go ptr' a'
329+
return $ NE.cons a as
323330

324331
foreign import ccall safe "hsnet_getaddrinfo"
325332
c_getaddrinfo :: CString -> CString -> Ptr AddrInfo -> Ptr (Ptr AddrInfo)

0 commit comments

Comments
 (0)