File: BSD.hsc

package info (click to toggle)
haskell-network-bsd 2.8.1.0-5
  • links: PTS
  • area: main
  • in suites: forky, sid, trixie
  • size: 96 kB
  • sloc: makefile: 5; haskell: 2
file content (660 lines) | stat: -rw-r--r-- 23,461 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
{-# LANGUAGE CPP, NondecreasingIndentation, DeriveDataTypeable, BangPatterns #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Network.BSD
-- Copyright   :  (c) The University of Glasgow 2001
-- SPDX-License-Identifier: BSD-3-Clause
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  experimental
-- Portability :  non-portable
--
-- The "Network.BSD" module defines Haskell bindings to network
-- programming functionality (mostly [network database operations](http://pubs.opengroup.org/onlinepubs/9699919799/basedefs/netdb.h.html))
-- provided by BSD Unix derivatives.
--
-- __NOTE__: Some of the types are reexported from "Network.Socket" in order to make the @network-bsd@ API self-contained.
--
-- == Windows compatibility
--
-- The following functions are not exported by "Network.BSD" on the
-- Windows platform:
--
-- * 'getHostEntries', 'setHostEntry', 'getHostEntry', 'endHostEntry'
-- * 'getServiceEntries', 'getServiceEntry', 'setServiceEntry', 'endServiceEntry'
-- * 'getProtocolEntries', 'setProtocolEntry', 'getProtocolEntry', 'endProtocolEntry'
-- * 'getNetworkByName', 'getNetworkByAddr', 'getNetworkEntries',
--   'setNetworkEntry', 'getNetworkEntry', 'endNetworkEntry'
--
-----------------------------------------------------------------------------

#include "HsNet.h"
##include "HsNetDef.h"

module Network.BSD
    (
    -- * Host names and network addresses
      N.HostName
    , N.HostAddress
      -- NB: We're explicit here to reduce the risk of inadvertently leaking through new constructors w/o reflecting this in @network-bsd@'s API version
    , N.Family(AF_UNSPEC, AF_UNIX, AF_INET, AF_INET6, AF_IMPLINK, AF_PUP, AF_CHAOS, AF_NS, AF_NBS, AF_ECMA, AF_DATAKIT, AF_CCITT, AF_SNA, AF_DECnet, AF_DLI, AF_LAT, AF_HYLINK, AF_APPLETALK, AF_ROUTE, AF_NETBIOS, AF_NIT, AF_802, AF_ISO, AF_OSI, AF_NETMAN, AF_X25, AF_AX25, AF_OSINET, AF_GOSSIP, AF_IPX, Pseudo_AF_XTP, AF_CTF, AF_WAN, AF_SDL, AF_NETWARE, AF_NDD, AF_INTF, AF_COIP, AF_CNT, Pseudo_AF_RTIP, Pseudo_AF_PIP, AF_SIP, AF_ISDN, Pseudo_AF_KEY, AF_NATM, AF_ARP, Pseudo_AF_HDRCMPLT, AF_ENCAP, AF_LINK, AF_RAW, AF_RIF, AF_NETROM, AF_BRIDGE, AF_ATMPVC, AF_ROSE, AF_NETBEUI, AF_SECURITY, AF_PACKET, AF_ASH, AF_ECONET, AF_ATMSVC, AF_IRDA, AF_PPPOX, AF_WANPIPE, AF_BLUETOOTH, AF_CAN)
    , getHostName

    , HostEntry(..)
    , getHostByName
    , getHostByAddr
    , hostAddress

#if defined(HAVE_GETHOSTENT) && !defined(mingw32_HOST_OS)
    , getHostEntries

    -- ** Low level functionality
    , setHostEntry
    , getHostEntry
    , endHostEntry
#endif

    -- * Service names
    , ServiceEntry(..)
    , N.ServiceName
    , N.PortNumber
    , getServiceByName
    , getServiceByPort
    , getServicePortNumber

#if !defined(mingw32_HOST_OS)
    , getServiceEntries

    -- ** Low level functionality
    , getServiceEntry
    , setServiceEntry
    , endServiceEntry
#endif

    -- * Protocol names
    , ProtocolName
    , N.ProtocolNumber
    , ProtocolEntry(..)
    , getProtocolByName
    , getProtocolByNumber
    , getProtocolNumber
    , N.defaultProtocol

#if !defined(mingw32_HOST_OS)
    , getProtocolEntries
    -- ** Low level functionality
    , setProtocolEntry
    , getProtocolEntry
    , endProtocolEntry
#endif

    -- * Network names
    , NetworkName
    , NetworkAddr
    , NetworkEntry(..)

#if !defined(mingw32_HOST_OS)
    , getNetworkByName
    , getNetworkByAddr
    , getNetworkEntries
    -- ** Low level functionality
    , setNetworkEntry
    , getNetworkEntry
    , endNetworkEntry
#endif

    -- * Interface names
    , N.ifNameToIndex

    ) where

import qualified Network.Socket as N

import Control.Concurrent (MVar, newMVar, withMVar)
import qualified Control.Exception as E
import Foreign.C.String (CString, peekCString, withCString)
#if defined(mingw32_HOST_OS)
import Foreign.C.Types ( CShort )
#endif
import Foreign.C.Types ( CInt(..), CULong(..), CSize(..) )
import Foreign.Ptr (Ptr, nullPtr)
import Foreign.Storable (Storable(..))
import Foreign.Marshal.Array (allocaArray0, peekArray0)
import Foreign.Marshal.Utils (with, fromBool)
import Data.Typeable
import System.IO.Error (ioeSetErrorString, mkIOError)
import System.IO.Unsafe (unsafePerformIO)

import GHC.IO.Exception

import Control.DeepSeq (NFData(rnf))
import Control.Monad (liftM)

import Network.Socket.Internal (throwSocketErrorIfMinus1_)

-- ---------------------------------------------------------------------------
-- Basic Types

type ProtocolName = String

-- ---------------------------------------------------------------------------
-- Service Database Access

-- Calling getServiceByName for a given service and protocol returns
-- the systems service entry.  This should be used to find the port
-- numbers for standard protocols such as SMTP and FTP.  The remaining
-- three functions should be used for browsing the service database
-- sequentially.

-- Calling setServiceEntry with True indicates that the service
-- database should be left open between calls to getServiceEntry.  To
-- close the database a call to endServiceEntry is required.  This
-- database file is usually stored in the file /etc/services.

-- | Representation of the POSIX @servent@ structure defined in [<netdb.h>](http://pubs.opengroup.org/onlinepubs/9699919799/basedefs/netdb.h.html).
data ServiceEntry  =
  ServiceEntry  {
     serviceName     :: N.ServiceName,    -- ^ Official service name
     serviceAliases  :: [N.ServiceName],  -- ^ aliases
     servicePort     :: N.PortNumber,     -- ^ Port Number
     serviceProtocol :: ProtocolName      -- ^ Protocol to use
  } deriving (Show, Typeable)

-- | @since 2.8.1.0
instance NFData ServiceEntry where
   -- TODO: PortNumber is a newtype over Word16; add NFData instance to `network`
   rnf (ServiceEntry n a !_pn pr) = rnf (n,a,pr)

instance Storable ServiceEntry where
   sizeOf    _ = #const sizeof(struct servent)
   alignment _ = alignment (undefined :: CInt) -- ???

   peek p = do
        s_name    <- (#peek struct servent, s_name) p >>= peekCString
        s_aliases <- (#peek struct servent, s_aliases) p
                           >>= peekArray0 nullPtr
                           >>= mapM peekCString
        s_port    <- (#peek struct servent, s_port) p
        s_proto   <- (#peek struct servent, s_proto) p >>= peekCString
        return (ServiceEntry {
                        serviceName     = s_name,
                        serviceAliases  = s_aliases,
#if defined(mingw32_HOST_OS)
                        servicePort     = (fromIntegral (s_port :: CShort)),
#else
                           -- s_port is already in network byte order, but it
                           -- might be the wrong size.
                        servicePort     = (fromIntegral (s_port :: CInt)),
#endif
                        serviceProtocol = s_proto
                })

   poke = throwUnsupportedOperationPoke "ServiceEntry"


-- | Get service by name.
getServiceByName :: N.ServiceName         -- Service Name
                 -> ProtocolName        -- Protocol Name
                 -> IO ServiceEntry     -- Service Entry
getServiceByName name proto = withLock $ do
 withCString name  $ \ cstr_name  -> do
 withCString proto $ \ cstr_proto -> do
 throwNoSuchThingIfNull "Network.BSD.getServiceByName" "no such service entry"
   $ c_getservbyname cstr_name cstr_proto
 >>= peek

foreign import CALLCONV unsafe "getservbyname"
  c_getservbyname :: CString -> CString -> IO (Ptr ServiceEntry)

-- | Get the service given a 'N.PortNumber' and 'ProtocolName'.
getServiceByPort :: N.PortNumber -> ProtocolName -> IO ServiceEntry
getServiceByPort port proto = withLock $ do
 withCString proto $ \ cstr_proto -> do
 throwNoSuchThingIfNull "Network.BSD.getServiceByPort" "no such service entry"
   $ c_getservbyport (fromIntegral port) cstr_proto
 >>= peek

foreign import CALLCONV unsafe "getservbyport"
  c_getservbyport :: CInt -> CString -> IO (Ptr ServiceEntry)

-- | Get the 'N.PortNumber' corresponding to the 'N.ServiceName'.
getServicePortNumber :: N.ServiceName -> IO N.PortNumber
getServicePortNumber name = do
    (ServiceEntry _ _ port _) <- getServiceByName name "tcp"
    return port

#if !defined(mingw32_HOST_OS)

-- | @getservent(3)@.
getServiceEntry :: IO ServiceEntry
getServiceEntry = withLock getServiceEntry'

getServiceEntry' :: IO ServiceEntry
getServiceEntry' = do
  throwNoSuchThingIfNull "Network.BSD.getServiceEntry" "no such service entry"
    $ c_getservent
  >>= peek

foreign import ccall unsafe "getservent" c_getservent :: IO (Ptr ServiceEntry)

-- | @setservent(3)@.
setServiceEntry :: Bool -> IO ()
setServiceEntry = withLock . setServiceEntry'

setServiceEntry' :: Bool -> IO ()
setServiceEntry' flg = c_setservent (fromBool flg)

foreign import ccall unsafe  "setservent" c_setservent :: CInt -> IO ()

-- | @endservent(3)@.
endServiceEntry :: IO ()
endServiceEntry = withLock $ c_endservent

foreign import ccall unsafe  "endservent" c_endservent :: IO ()

-- | Retrieve list of all 'ServiceEntry' via @getservent(3)@.
getServiceEntries :: Bool -> IO [ServiceEntry]
getServiceEntries stayOpen = withLock $ do
  setServiceEntry' stayOpen
  getEntries getServiceEntry' c_endservent
#endif

-- ---------------------------------------------------------------------------
-- Protocol Entries

-- The following relate directly to the corresponding UNIX C
-- calls for returning the protocol entries. The protocol entry is
-- represented by the Haskell type ProtocolEntry.

-- As for setServiceEntry above, calling setProtocolEntry.
-- determines whether or not the protocol database file, usually
-- @/etc/protocols@, is to be kept open between calls of
-- getProtocolEntry. Similarly,

-- | Representation of the POSIX @protoent@ structure defined in [<netdb.h>](http://pubs.opengroup.org/onlinepubs/9699919799/basedefs/netdb.h.html).
data ProtocolEntry =
  ProtocolEntry  {
     protoName    :: ProtocolName,      -- ^ Official name
     protoAliases :: [ProtocolName],    -- ^ aliases
     protoNumber  :: N.ProtocolNumber   -- ^ Protocol number
  } deriving (Read, Show, Typeable)

-- | @since 2.8.1.0
instance NFData ProtocolEntry where
   -- NB: deepseq-1.3 didn't have `NFData CInt` yet; but we don't need it
   rnf (ProtocolEntry na a !_nu) = rnf (na,a)

instance Storable ProtocolEntry where
   sizeOf    _ = #const sizeof(struct protoent)
   alignment _ = alignment (undefined :: CInt) -- ???

   peek p = do
        p_name    <- (#peek struct protoent, p_name) p >>= peekCString
        p_aliases <- (#peek struct protoent, p_aliases) p
                           >>= peekArray0 nullPtr
                           >>= mapM peekCString
#if defined(mingw32_HOST_OS)
         -- With WinSock, the protocol number is only a short;
         -- hoist it in as such, but represent it on the Haskell side
         -- as a CInt.
        p_proto_short  <- (#peek struct protoent, p_proto) p
        let p_proto = fromIntegral (p_proto_short :: CShort)
#else
        p_proto        <- (#peek struct protoent, p_proto) p
#endif
        return (ProtocolEntry {
                        protoName    = p_name,
                        protoAliases = p_aliases,
                        protoNumber  = p_proto
                })

   poke = throwUnsupportedOperationPoke "ProtocolEntry"


-- | @getprotobyname(3)@.
getProtocolByName :: ProtocolName -> IO ProtocolEntry
getProtocolByName name = withLock $ do
 withCString name $ \ name_cstr -> do
 throwNoSuchThingIfNull "Network.BSD.getProtocolByName" ("no such protocol name: " ++ name)
   $ c_getprotobyname name_cstr
 >>= peek

foreign import  CALLCONV unsafe  "getprotobyname"
   c_getprotobyname :: CString -> IO (Ptr ProtocolEntry)

-- | @getprotobynumber(3)@.
getProtocolByNumber :: N.ProtocolNumber -> IO ProtocolEntry
getProtocolByNumber num = withLock $ do
 throwNoSuchThingIfNull "Network.BSD.getProtocolByNumber" ("no such protocol number: " ++ show num)
   $ c_getprotobynumber (fromIntegral num)
 >>= peek

foreign import CALLCONV unsafe  "getprotobynumber"
   c_getprotobynumber :: CInt -> IO (Ptr ProtocolEntry)

-- | @getprotobyname(3)@.
getProtocolNumber :: ProtocolName -> IO N.ProtocolNumber
getProtocolNumber proto = do
 (ProtocolEntry _ _ num) <- getProtocolByName proto
 return num

#if !defined(mingw32_HOST_OS)
-- | @getprotoent(3)@.
getProtocolEntry :: IO ProtocolEntry    -- Next Protocol Entry from DB
getProtocolEntry = withLock getProtocolEntry'

getProtocolEntry' :: IO ProtocolEntry
getProtocolEntry' = do
  ent <- throwNoSuchThingIfNull "Network.BSD.getProtocolEntry" "no such protocol entry"
           $ c_getprotoent
  peek ent

foreign import ccall unsafe  "getprotoent" c_getprotoent :: IO (Ptr ProtocolEntry)

-- | @setprotoent(3)@.
setProtocolEntry :: Bool -> IO ()       -- Keep DB Open ?
setProtocolEntry = withLock . setProtocolEntry'

setProtocolEntry' :: Bool -> IO ()       -- Keep DB Open ?
setProtocolEntry' flg = c_setprotoent (fromBool flg)

foreign import ccall unsafe "setprotoent" c_setprotoent :: CInt -> IO ()

-- | @endprotoent(3)@.
endProtocolEntry :: IO ()
endProtocolEntry = withLock $ c_endprotoent

foreign import ccall unsafe "endprotoent" c_endprotoent :: IO ()

-- | Retrieve list of all 'ProtocolEntry' via @getprotoent(3)@.
getProtocolEntries :: Bool -> IO [ProtocolEntry]
getProtocolEntries stayOpen = withLock $ do
  setProtocolEntry' stayOpen
  getEntries getProtocolEntry' c_endprotoent

#endif

-- ---------------------------------------------------------------------------
-- Host lookups

-- | Representation of the POSIX @hostent@ structure defined in [<netdb.h>](http://pubs.opengroup.org/onlinepubs/9699919799/basedefs/netdb.h.html).
data HostEntry =
  HostEntry  {
     hostName      :: N.HostName,         -- ^ Official name of the host
     hostAliases   :: [N.HostName],       -- ^ Alternative names of the host
     hostFamily    :: N.Family,           -- ^ Address type (currently @AF_INET@)
     hostAddresses :: [N.HostAddress]     -- ^ Set of network addresses for the host
  } deriving (Read, Show, Typeable)

-- | @since 2.8.1.0
instance NFData HostEntry where
   -- TODO: NFData N.Family
   rnf (HostEntry n al !_f ad) = rnf (n,al,ad)

instance Storable HostEntry where
   sizeOf    _ = #const sizeof(struct hostent)
   alignment _ = alignment (undefined :: CInt) -- ???

   peek p = do
        h_name       <- (#peek struct hostent, h_name) p >>= peekCString
        h_aliases    <- (#peek struct hostent, h_aliases) p
                                >>= peekArray0 nullPtr
                                >>= mapM peekCString
        h_addrtype   <- (#peek struct hostent, h_addrtype) p
        -- h_length       <- (#peek struct hostent, h_length) p
        h_addr_list  <- (#peek struct hostent, h_addr_list) p
                                >>= peekArray0 nullPtr
                                >>= mapM peek
        return (HostEntry {
                        hostName       = h_name,
                        hostAliases    = h_aliases,
#if defined(mingw32_HOST_OS)
                        hostFamily     = N.unpackFamily (fromIntegral (h_addrtype :: CShort)),
#else
                        hostFamily     = N.unpackFamily h_addrtype,
#endif
                        hostAddresses  = h_addr_list
                })

   poke = throwUnsupportedOperationPoke "HostEntry"


-- convenience function:
-- | Convenience function extracting one address in a 'HostEntry'.
-- Returns 'error' if 'HostEntry' contains no addresses.
hostAddress :: HostEntry -> N.HostAddress
hostAddress (HostEntry nm _ _ ls) =
 case ls of
   []    -> error $ "Network.BSD.hostAddress: empty network address list for " ++ nm
   (x:_) -> x

-- getHostByName must use the same lock as the *hostent functions
-- may cause problems if called concurrently.

-- | Resolve a 'N.HostName' to IPv4 address.
getHostByName :: N.HostName -> IO HostEntry
getHostByName name = withLock $ do
  withCString name $ \ name_cstr -> do
   ent <- throwNoSuchThingIfNull "Network.BSD.getHostByName" "no such host entry"
                $ c_gethostbyname name_cstr
   peek ent

foreign import CALLCONV safe "gethostbyname"
   c_gethostbyname :: CString -> IO (Ptr HostEntry)


-- The locking of gethostbyaddr is similar to gethostbyname.
-- | Get a 'HostEntry' corresponding to the given address and family.
-- Note that only IPv4 is currently supported.
getHostByAddr :: N.Family -> N.HostAddress -> IO HostEntry
getHostByAddr family addr = do
 with addr $ \ ptr_addr -> withLock $ do
 throwNoSuchThingIfNull "Network.BSD.getHostByAddr" "no such host entry"
   $ c_gethostbyaddr ptr_addr (fromIntegral (sizeOf addr)) (N.packFamily family)
 >>= peek

foreign import CALLCONV safe "gethostbyaddr"
   c_gethostbyaddr :: Ptr N.HostAddress -> CInt -> CInt -> IO (Ptr HostEntry)

#if defined(HAVE_GETHOSTENT) && !defined(mingw32_HOST_OS)
-- | @gethostent(3)@.
getHostEntry :: IO HostEntry
getHostEntry = withLock getHostEntry

getHostEntry' :: IO HostEntry
getHostEntry' = do
  throwNoSuchThingIfNull "Network.BSD.getHostEntry" "unable to retrieve host entry"
    $ c_gethostent
  >>= peek

foreign import ccall unsafe "gethostent" c_gethostent :: IO (Ptr HostEntry)

-- | @sethostent(3)@.
setHostEntry :: Bool -> IO ()
setHostEntry = withLock . setHostEntry'

setHostEntry' :: Bool -> IO ()
setHostEntry' flg = c_sethostent (fromBool flg)

foreign import ccall unsafe "sethostent" c_sethostent :: CInt -> IO ()

-- | @endhostent(3)@.
endHostEntry :: IO ()
endHostEntry = withLock $ c_endhostent

foreign import ccall unsafe "endhostent" c_endhostent :: IO ()

-- | Retrieve list of all 'HostEntry' via @gethostent(3)@.
getHostEntries :: Bool -> IO [HostEntry]
getHostEntries stayOpen = withLock $ do
  setHostEntry' stayOpen
  getEntries getHostEntry' c_endhostent

#endif

-- ---------------------------------------------------------------------------
-- Accessing network information

-- Same set of access functions as for accessing host,protocol and
-- service system info, this time for the types of networks supported.

-- network addresses are represented in host byte order.
type NetworkAddr = CULong

type NetworkName = String

-- | Representation of the POSIX @netent@ structure defined in [<netdb.h>](http://pubs.opengroup.org/onlinepubs/9699919799/basedefs/netdb.h.html).
data NetworkEntry =
  NetworkEntry {
     networkName        :: NetworkName,   -- ^ Official network name
     networkAliases     :: [NetworkName], -- ^ aliases
     networkFamily      :: N.Family,      -- ^ Network address type
     networkAddress     :: NetworkAddr    -- ^ Network number
   } deriving (Read, Show, Typeable)

-- | @since 2.8.1.0
instance NFData NetworkEntry where
   -- NB: We avoid relying on the `NFData CULong` instance which isn't available in deepseq-1.3 yet
   rnf (NetworkEntry n al !_f !_ad) = rnf (n,al)

instance Storable NetworkEntry where
   sizeOf    _ = #const sizeof(struct hostent)
   alignment _ = alignment (undefined :: CInt) -- ???

   peek p = do
        n_name         <- (#peek struct netent, n_name) p >>= peekCString
        n_aliases      <- (#peek struct netent, n_aliases) p
                                >>= peekArray0 nullPtr
                                >>= mapM peekCString
        n_addrtype     <- (#peek struct netent, n_addrtype) p
        n_net          <- (#peek struct netent, n_net) p
        return (NetworkEntry {
                        networkName      = n_name,
                        networkAliases   = n_aliases,
                        networkFamily    = N.unpackFamily (fromIntegral (n_addrtype :: CInt)),
                        networkAddress   = n_net
                })

   poke = throwUnsupportedOperationPoke "NetworkEntry"


#if !defined(mingw32_HOST_OS)
-- | @getnetbyname(3)@.
getNetworkByName :: NetworkName -> IO NetworkEntry
getNetworkByName name = withLock $ do
 withCString name $ \ name_cstr -> do
  throwNoSuchThingIfNull "Network.BSD.getNetworkByName" "no such network entry"
    $ c_getnetbyname name_cstr
  >>= peek

foreign import ccall unsafe "getnetbyname"
   c_getnetbyname  :: CString -> IO (Ptr NetworkEntry)

-- | @getnetbyaddr(3)@.
getNetworkByAddr :: NetworkAddr -> N.Family -> IO NetworkEntry
getNetworkByAddr addr family = withLock $ do
 throwNoSuchThingIfNull "Network.BSD.getNetworkByAddr" "no such network entry"
   $ c_getnetbyaddr addr (N.packFamily family)
 >>= peek

foreign import ccall unsafe "getnetbyaddr"
   c_getnetbyaddr  :: NetworkAddr -> CInt -> IO (Ptr NetworkEntry)

-- | @getnetent(3)@.
getNetworkEntry :: IO NetworkEntry
getNetworkEntry = withLock getNetworkEntry'

getNetworkEntry' :: IO NetworkEntry
getNetworkEntry' = do
  throwNoSuchThingIfNull "Network.BSD.getNetworkEntry" "no more network entries"
    $ c_getnetent
  >>= peek

foreign import ccall unsafe "getnetent" c_getnetent :: IO (Ptr NetworkEntry)

-- | Open the network name database. The parameter specifies
-- whether a connection is maintained open between various
-- networkEntry calls
--
-- @setnetent(3)@.
setNetworkEntry :: Bool -> IO ()
setNetworkEntry = withLock . setNetworkEntry'

setNetworkEntry' :: Bool -> IO ()
setNetworkEntry' flg = c_setnetent (fromBool flg)

foreign import ccall unsafe "setnetent" c_setnetent :: CInt -> IO ()

-- | Close the connection to the network name database.
--
-- @endnetent(3)@.
endNetworkEntry :: IO ()
endNetworkEntry = withLock $ c_endnetent

foreign import ccall unsafe "endnetent" c_endnetent :: IO ()

-- | Get the list of network entries via @getnetent(3)@.
getNetworkEntries :: Bool -> IO [NetworkEntry]
getNetworkEntries stayOpen = withLock $ do
  setNetworkEntry' stayOpen
  getEntries getNetworkEntry' c_endnetent
#endif

-- Mutex for name service lockdown

{-# NOINLINE lock #-}
lock :: MVar ()
lock = unsafePerformIO $ N.withSocketsDo $ newMVar ()

withLock :: IO a -> IO a
withLock act = withMVar lock (\_ -> act)

-- ---------------------------------------------------------------------------
-- Miscellaneous Functions

-- | Calling 'getHostName' returns the standard host name for the current
-- processor, as set at boot time.
--
-- @gethostname(2)@.
getHostName :: IO N.HostName
getHostName = do
  let size = 256
  allocaArray0 size $ \ cstr -> do
    throwSocketErrorIfMinus1_ "Network.BSD.getHostName" $ c_gethostname cstr (fromIntegral size)
    peekCString cstr

foreign import CALLCONV unsafe "gethostname"
   c_gethostname :: CString -> CSize -> IO CInt

-- Helper function used by the exported functions that provides a
-- Haskellised view of the enumerator functions:

getEntries :: IO a  -- read
           -> IO () -- at end
           -> IO [a]
getEntries getOne atEnd = loop
  where
    loop = do
      vv <- E.catch (liftM Just getOne)
            (\ e -> let _types = e :: IOException in return Nothing)
      case vv of
        Nothing -> return []
        Just v  -> loop >>= \ vs -> atEnd >> return (v:vs)


throwNoSuchThingIfNull :: String -> String -> IO (Ptr a) -> IO (Ptr a)
throwNoSuchThingIfNull loc desc act = do
  ptr <- act
  if (ptr == nullPtr)
   then ioError (ioeSetErrorString (mkIOError NoSuchThing loc Nothing Nothing) desc)
   else return ptr

throwUnsupportedOperationPoke :: String -> Ptr a -> a -> IO ()
throwUnsupportedOperationPoke typ _ _ =
  ioError $ ioeSetErrorString ioe "Operation not implemented"
  where
    ioe = mkIOError UnsupportedOperation
                    ("Network.BSD: instance Storable " ++ typ ++ ": poke")
                    Nothing
                    Nothing