[Haskell-beginners] ffi woes
Jose A. Ortega Ruiz
jao at gnu.org
Thu Feb 18 20:13:11 EST 2010
Hi,
Show below is a short program using the FFI to access libiw and provide,
given an interface name such as "wlan0" the associated ESSID. One uses
iw_get_basic_config to fill a struct wireless_config (dynamically
allocated), and extract from that the desired string, which is a field
of type char[MAX_ESSID_LEN] in said struct type.
When i run this program (or call getWirelessInfo inside ghci) with an
existing network interface, it segfaults (calling it with a non-existent
one returns the expected empty string, so the problem is after the first
'if' in getWirelessInfo): can anybody spot what am i doing wrong? Or
perhaps give me any hint on how to debug the issue?
TIA!
jao
{-# LANGUAGE CPP, ForeignFunctionInterface #-}
module Main (main) where
import System.Environment
import Foreign
import Foreign.C.Types
import Foreign.C.String
#include <iwlib.h>
foreign import ccall "iwlib.h iw_sockets_open"
c_iw_open :: IO CInt
foreign import ccall "unistd.h close"
c_iw_close :: CInt -> IO ()
-- the 3rd argument is a struct wireless_config*, an input parameter
foreign import ccall "iwlib.h iw_get_basic_config"
c_iw_basic_config :: CInt -> CString -> Ptr () -> IO CInt
-- Given a network interface name, return its ESSID
getWirelessInfo :: String -> IO String
getWirelessInfo iface =
allocaBytes (#size struct wireless_config) $ \wc ->
withCString iface $ \istr -> do
i <- c_iw_open
r <- c_iw_basic_config i istr wc
c_iw_close i
if (r < 0)
then return ""
else do hase <- (#peek struct wireless_config, has_essid) wc :: IO CInt
eon <- (#peek struct wireless_config, essid_on) wc :: IO CInt
if hase > 0 && eon > 0
then do l <- (#peek struct wireless_config, essid_len) wc
e <- (#peek struct wireless_config, essid) wc
-- wireless_config.essid is a char[MAX_LEN]
peekCStringLen (e, fromIntegral (l :: CInt))
else return ""
main = (fmap head getArgs) >>= getWirelessInfo >>= print
More information about the Beginners
mailing list