[Haskell-cafe] seeking advice on my POSIX wrapper

Galchin, Vasili vigalchin at gmail.com
Sat May 10 16:47:52 EDT 2008


Hello,

     Last night I sent out an announcement about some POSIX work that I have
been doing. In any case, one of the FFI wrappers is driving me crazy, i.e.
the one for mq_receive:
http://opengroup.org/onlinepubs/007908799/xsh/mq_receive.html  . When I call
this function (mqReceive), I get "message too long". In my test cases I am
sending and receiving messages that are only 11 bytes! The wrapper seems
really straightforward. Perhaps  I am looking right at the problem and don't
see. I need other eyes on the wrapper to help me ;^). Please see below.

Regards, V.

-------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------


--  mqReceive is still being debugged!!!!!!!!!!

-- | Retrieve a message from mqueue designated by "mqd"
--
mqReceive :: Fd -> ByteCount -> Maybe Int -> IO (String, Int)
mqReceive (Fd mqd) len (Just prio) = do
    allocaBytes (fromIntegral len) $ \ p_buffer -> do
      with (fromIntegral prio) $ \ p_prio -> do
        rc <- throwErrnoIfMinus1 "mqReceive" (c_mq_receive mqd p_buffer
(fromIntegral len) p_prio)
        case fromIntegral rc of
          0 -> ioError (IOError Nothing EOF "mqReceive" "EOF" Nothing)
          n -> do
           s <- peekCStringLen (p_buffer, fromIntegral n)
           return (s, n)
mqReceive (Fd mqd) len Nothing = do
    allocaBytes (fromIntegral len) $ \ p_buffer -> do
      rc <- throwErrnoIfMinus1 "mqReceive" (c_mq_receive mqd p_buffer
(fromIntegral len) nullPtr)
      case fromIntegral rc of
        0 -> ioError (IOError Nothing EOF "mqReceive" "EOF" Nothing)
        n -> do
         s <- peekCStringLen (p_buffer, fromIntegral n)
         return (s, n)

foreign import ccall unsafe "mqueue.h mq_receive"
   c_mq_receive :: CInt -> Ptr CChar -> CSize -> Ptr CInt -> IO CInt
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080510/a74a19a2/attachment.htm


More information about the Haskell-Cafe mailing list