Skip to content

Commit a7b15f8

Browse files
Merge pull request #587 from kazu-yamamoto/non-empty
Making getAddrInfo polymorphic
2 parents a521e19 + b7ba6ee commit a7b15f8

File tree

8 files changed

+106
-64
lines changed

8 files changed

+106
-64
lines changed

Network/Socket.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@
3333
-- > import qualified Control.Exception as E
3434
-- > import Control.Monad (unless, forever, void)
3535
-- > import qualified Data.ByteString as S
36+
-- > import qualified Data.List.NonEmpty as NE
3637
-- > import Network.Socket
3738
-- > import Network.Socket.ByteString (recv, sendAll)
3839
-- >
@@ -56,7 +57,7 @@
5657
-- > addrFlags = [AI_PASSIVE]
5758
-- > , addrSocketType = Stream
5859
-- > }
59-
-- > head <$> getAddrInfo (Just hints) mhost (Just port)
60+
-- > NE.head <$> getAddrInfo (Just hints) mhost (Just port)
6061
-- > open addr = E.bracketOnError (openSocket addr) close $ \sock -> do
6162
-- > setSocketOption sock ReuseAddr 1
6263
-- > withFdSocket sock setCloseOnExecIfNeeded
@@ -77,6 +78,7 @@
7778
-- >
7879
-- > import qualified Control.Exception as E
7980
-- > import qualified Data.ByteString.Char8 as C
81+
-- > import qualified Data.List.NonEmpty as NE
8082
-- > import Network.Socket
8183
-- > import Network.Socket.ByteString (recv, sendAll)
8284
-- >
@@ -95,7 +97,7 @@
9597
-- > where
9698
-- > resolve = do
9799
-- > let hints = defaultHints { addrSocketType = Stream }
98-
-- > head <$> getAddrInfo (Just hints) (Just host) (Just port)
100+
-- > NE.head <$> getAddrInfo (Just hints) (Just host) (Just port)
99101
-- > open addr = E.bracketOnError (openSocket addr) close $ \sock -> do
100102
-- > connect sock $ addrAddress addr
101103
-- > return sock

Network/Socket/Info.hsc

Lines changed: 91 additions & 55 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,8 @@
77

88
module Network.Socket.Info where
99

10+
import Data.List.NonEmpty (NonEmpty(..))
11+
import qualified Data.List.NonEmpty as NE
1012
import Foreign.Marshal.Alloc (alloca, allocaBytes)
1113
import Foreign.Marshal.Utils (maybeWith, with)
1214
import GHC.IO.Exception (IOErrorType(NoSuchThing))
@@ -200,53 +202,72 @@ defaultHints = AddrInfo {
200202
, addrCanonName = Nothing
201203
}
202204

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
245266
:: Maybe AddrInfo -- ^ preferred socket type or protocol
246267
-> Maybe HostName -- ^ host name to look up
247268
-> 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
250271
where
251272
alloc body = withSocketsDo $ maybeWith withCString node $ \c_node ->
252273
maybeWith withCString service $ \c_service ->
@@ -258,12 +279,7 @@ getAddrInfo hints node service = alloc getaddrinfo
258279
if ret == 0 then do
259280
ptr_addrs <- peek ptr_ptr_addrs
260281
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
267283
else do
268284
err <- gai_strerror ret
269285
ioError $ ioeSetErrorString
@@ -290,13 +306,33 @@ getAddrInfo hints node service = alloc getaddrinfo
290306
filteredHints = hints
291307
#endif
292308

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)
294319
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
296323
| 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')
300336

301337
foreign import ccall safe "hsnet_getaddrinfo"
302338
c_getaddrinfo :: CString -> CString -> Ptr AddrInfo -> Ptr (Ptr AddrInfo)

Network/Socket/Syscall.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -63,8 +63,9 @@ import Network.Socket.Types
6363
-- can be handled with one socket.
6464
--
6565
-- >>> import Network.Socket
66+
-- >>> import qualified Data.List.NonEmpty as NE
6667
-- >>> let hints = defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV], addrSocketType = Stream }
67-
-- >>> addr:_ <- getAddrInfo (Just hints) (Just "127.0.0.1") (Just "5000")
68+
-- >>> addr <- NE.head <$> getAddrInfo (Just hints) (Just "127.0.0.1") (Just "5000")
6869
-- >>> sock <- socket (addrFamily addr) (addrSocketType addr) (addrProtocol addr)
6970
-- >>> Network.Socket.bind sock (addrAddress addr)
7071
-- >>> getSocketName sock

examples/EchoClient.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module Main (main) where
55

66
import qualified Control.Exception as E
77
import qualified Data.ByteString.Char8 as C
8+
import qualified Data.List.NonEmpty as NE
89
import Network.Socket
910
import Network.Socket.ByteString (recv, sendAll)
1011

@@ -23,7 +24,7 @@ runTCPClient host port client = withSocketsDo $ do
2324
where
2425
resolve = do
2526
let hints = defaultHints{addrSocketType = Stream}
26-
head <$> getAddrInfo (Just hints) (Just host) (Just port)
27+
NE.head <$> getAddrInfo (Just hints) (Just host) (Just port)
2728
open addr = E.bracketOnError (openSocket addr) close $ \sock -> do
2829
connect sock $ addrAddress addr
2930
return sock

examples/EchoServer.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ import Control.Concurrent (forkFinally)
55
import qualified Control.Exception as E
66
import Control.Monad (forever, unless, void)
77
import qualified Data.ByteString as S
8+
import qualified Data.List.NonEmpty as NE
89
import Network.Socket
910
import Network.Socket.ByteString (recv, sendAll)
1011

@@ -29,7 +30,7 @@ runTCPServer mhost port server = withSocketsDo $ do
2930
{ addrFlags = [AI_PASSIVE]
3031
, addrSocketType = Stream
3132
}
32-
head <$> getAddrInfo (Just hints) mhost (Just port)
33+
NE.head <$> getAddrInfo (Just hints) mhost (Just port)
3334
open addr = E.bracketOnError (openSocket addr) close $ \sock -> do
3435
setSocketOption sock ReuseAddr 1
3536
withFdSocket sock setCloseOnExecIfNeeded

network.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
cabal-version: 1.18
22
name: network
3-
version: 3.2.2.0
3+
version: 3.2.3.0
44
license: BSD3
55
license-file: LICENSE
66
maintainer: Kazu Yamamoto, Tamar Christina

tests/Network/SocketSpec.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -118,7 +118,7 @@ spec = do
118118

119119
it "does not cause segfault on macOS 10.8.2 due to AI_NUMERICSERV" $ do
120120
let hints = defaultHints { addrFlags = [AI_NUMERICSERV] }
121-
void $ getAddrInfo (Just hints) (Just "localhost") Nothing
121+
void (getAddrInfo (Just hints) (Just "localhost") Nothing :: IO [AddrInfo])
122122

123123
#if defined(mingw32_HOST_OS)
124124
let lpdevname = "loopback_0"

tests/Network/Test/Common.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,7 @@ import qualified Control.Exception as E
3535
import Control.Monad
3636
import Data.ByteString (ByteString)
3737
import qualified Data.ByteString.Lazy as L
38+
import qualified Data.List.NonEmpty as NE
3839
import Network.Socket
3940
import System.Directory
4041
import System.Timeout (timeout)
@@ -244,7 +245,7 @@ bracketWithReraise tid setup teardown thing =
244245

245246
resolveClient :: SocketType -> HostName -> PortNumber -> IO AddrInfo
246247
resolveClient socketType host port =
247-
head <$> getAddrInfo (Just hints) (Just host) (Just $ show port)
248+
NE.head <$> getAddrInfo (Just hints) (Just host) (Just $ show port)
248249
where
249250
hints = defaultHints {
250251
addrSocketType = socketType
@@ -253,7 +254,7 @@ resolveClient socketType host port =
253254

254255
resolveServer :: SocketType -> HostName -> IO AddrInfo
255256
resolveServer socketType host =
256-
head <$> getAddrInfo (Just hints) (Just host) Nothing
257+
NE.head <$> getAddrInfo (Just hints) (Just host) Nothing
257258
where
258259
hints = defaultHints {
259260
addrSocketType = socketType

0 commit comments

Comments
 (0)