summaryrefslogtreecommitdiff
path: root/Presence/GetHostByAddr.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Presence/GetHostByAddr.hs')
-rw-r--r--Presence/GetHostByAddr.hs75
1 files changed, 75 insertions, 0 deletions
diff --git a/Presence/GetHostByAddr.hs b/Presence/GetHostByAddr.hs
new file mode 100644
index 00000000..fd01108d
--- /dev/null
+++ b/Presence/GetHostByAddr.hs
@@ -0,0 +1,75 @@
1{-# LINE 1 "Presence/GetHostByAddr.hsc" #-}
2{-# LANGUAGE CPP, ForeignFunctionInterface #-}
3{-# LINE 2 "Presence/GetHostByAddr.hsc" #-}
4#include "Typeable.h"
5module GetHostByAddr where
6
7import Network.BSD
8import Foreign.Ptr
9import Foreign.C.Types
10import Foreign.Storable (Storable(..))
11import Foreign.Marshal.Utils (with)
12import Control.Concurrent
13import System.IO.Unsafe
14import System.IO.Error (ioeSetErrorString, mkIOError)
15import Network.Socket
16import GHC.IO.Exception
17import Network.Socket.Internal
18
19
20throwNoSuchThingIfNull :: String -> String -> IO (Ptr a) -> IO (Ptr a)
21throwNoSuchThingIfNull loc desc act = do
22 ptr <- act
23 if (ptr == nullPtr)
24 then ioError (ioeSetErrorString (mkIOError NoSuchThing loc Nothing Nothing) desc)
25 else return ptr
26
27{-# NOINLINE lock #-}
28lock :: MVar ()
29lock = unsafePerformIO $ newMVar ()
30
31withLock :: IO a -> IO a
32withLock act = withMVar lock (\_ -> act)
33
34trySysCall :: IO a -> IO a
35trySysCall act = act
36
37{-
38-- The locking of gethostbyaddr is similar to gethostbyname.
39-- | Get a 'HostEntry' corresponding to the given address and family.
40-- Note that only IPv4 is currently supported.
41getHostByAddr :: Family -> SockAddr -> IO HostEntry
42getHostByAddr family addr = do
43 withSockAddr addr $ \ ptr_addr len -> withLock $ do
44 throwNoSuchThingIfNull "getHostByAddr" "no such host entry"
45 $ trySysCall $ c_gethostbyaddr ptr_addr (fromIntegral len) (packFamily family)
46 >>= peek
47-}
48
49
50-- The locking of gethostbyaddr is similar to gethostbyname.
51-- | Get a 'HostEntry' corresponding to the given address and family.
52-- Note that only IPv4 is currently supported.
53-- getHostByAddr :: Family -> HostAddress -> IO HostEntry
54-- getHostByAddr family addr = do
55getHostByAddr :: SockAddr -> IO HostEntry
56getHostByAddr (SockAddrInet port addr ) = do
57 let family = AF_INET
58 with addr $ \ ptr_addr -> withLock $ do
59 throwNoSuchThingIfNull "getHostByAddr" "no such host entry"
60 $ trySysCall $ c_gethostbyaddr ptr_addr (fromIntegral (sizeOf addr)) (packFamily family)
61 >>= peek
62getHostByAddr (SockAddrInet6 port flow addr scope) = do
63 let family = AF_INET6
64 with addr $ \ ptr_addr -> withLock $ do
65 throwNoSuchThingIfNull "getHostByAddr" "no such host entry"
66 $ trySysCall $ c_gethostbyaddr ptr_addr (fromIntegral (sizeOf addr)) (packFamily family)
67 >>= peek
68
69
70foreign import ccall safe "gethostbyaddr"
71 c_gethostbyaddr :: Ptr a -> CInt -> CInt -> IO (Ptr HostEntry)
72
73
74
75-- vim:ft=haskell: