{-# LANGUAGE CPP #-}
#include "HsNetDef.h"
module Network.Socket.If (
ifNameToIndex
, ifIndexToName
) where
import Foreign.Marshal.Alloc (allocaBytes)
import Network.Socket.Imports
ifNameToIndex :: String -> IO (Maybe Int)
ifNameToIndex :: String -> IO (Maybe Int)
ifNameToIndex String
ifname = do
index <- String -> (CString -> IO CUInt) -> IO CUInt
forall a. String -> (CString -> IO a) -> IO a
withCString String
ifname CString -> IO CUInt
c_if_nametoindex
return $ if index == 0 then Nothing else Just $ fromIntegral index
ifIndexToName :: Int -> IO (Maybe String)
ifIndexToName :: Int -> IO (Maybe String)
ifIndexToName Int
ifn = Int -> (CString -> IO (Maybe String)) -> IO (Maybe String)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
16 ((CString -> IO (Maybe String)) -> IO (Maybe String))
-> (CString -> IO (Maybe String)) -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$ \CString
ptr -> do
r <- CUInt -> CString -> IO CString
c_if_indextoname (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ifn) CString
ptr
if r == nullPtr then
return Nothing
else
Just <$> peekCString ptr
foreign import CALLCONV safe "if_nametoindex"
c_if_nametoindex :: CString -> IO CUInt
foreign import CALLCONV safe "if_indextoname"
c_if_indextoname :: CUInt -> CString -> IO CString