Hello,

       Below is a snippet of my code .... please look for the "poke" call with "<<<<<<<<<<<<<". This causes a "hang" when I run a test case. If I comment out the "poke" call then test case runs.

Vasili
 
-- |Correspond to some of the int flags from C's fcntl.h.
data MQFlags =
 MQFlags {
    append1    :: Bool, -- ^ O_APPEND
    exclusive1 :: Bool, -- ^ O_EXCL
    noctty1    :: Bool, -- ^ O_NOCTTY
    nonBlock1  :: Bool, -- ^ O_NONBLOCK
    trunc1     :: Bool  -- ^ O_TRUNC
 }


-- |Default values for the 'MQFlags' type. False for each of
-- append, exclusive, noctty, nonBlock, and trunc.
--   TBD WNH MQdefaultFileFlags :: MQFlags
defaultMQFlags =
 MQFlags {
    append1    = False,
    exclusive1 = False,
    noctty1    = False,
    nonBlock1  = False,
    trunc1     = False
  }

data MQAttributes =
 MQAttributes {
    flags      :: MQFlags,
    maxMsgNum  :: Int,
    maxMsgSize :: Int,
    curNumMsgs :: Int
 }

instance Storable MQAttributes where
     sizeOf (MQAttributes flags maxMsgNum maxMsgSize curNumMsgs) = 4

instance Storable MQFlags where
     sizeOf (MQFlags append1 exclusive1 noctty1 nonBlock1 trunc1) = 1



-- |Open and optionally create this message queue.  See 'System.Posix.Files'
-- for information on how to use the 'FileMode' type.
mqOpen :: String
       -> MQOpenMode
       -> Maybe FileMode -- ^Just x => creates the file with the given modes, Nothing => the file must exist.
       -> MQFlags
       -> MQAttributes
       -> IO Fd
mqOpen name how maybe_mode (MQFlags append1 exclusive1 noctty1
                                nonBlock1 truncate1) (MQAttributes flags maxMsgNum maxMsgSize curNumMsgs) = do
   withCString name $ \ p_name -> do
   putStrLn ("name -> " ++ name)
   allocaBytes (#const sizeof(struct mq_attr)) $ \ p_attrs -> do
    (#poke struct mq_attr, mq_flags)    p_attrs  flags     <<<<<<<<<<<<<<<<<<<


On Tue, Apr 22, 2008 at 5:05 PM, Bulat Ziganshin <bulat.ziganshin@gmail.com> wrote:
Hello Evan,

Wednesday, April 23, 2008, 1:48:30 AM, you wrote:

> The FFI doc doesn't really talk about the alignment method at all, so
> I don't really understand how to write one or how it's used.

write: easy. just specify how much data shoulkd be aligned. for
primitive datatypes this usually equals to datasize, for complex
structures this should be the same as maximum alignment of elements
involved:

instance Storable Float
 alignment = 4

instance Storable (a,b)
 alignment = maximum [alignment a, alignment b]

use: just align memory blocks allocated to store this datatype. usual
alignment technique is:

alloc a = (allocBytes (sizeOf a + alignment a - 1) + (alignment a - 1)) .&. (alignment a - 1)

well, many standard allocators such as C malloc, actually provide you
blocks with a maximum alignment required to store any (primitive)
type, so you don't need to worry about it


--
Best regards,
 Bulat                            mailto:Bulat.Ziganshin@gmail.com