3

I'm trying to access various bits and bobs in the XKB API. This is my test code so far:

{-# LANGUAGE ForeignFunctionInterface #-}
module Main where

import Foreign
import Foreign.C.Types

#include <X11/XKBlib.h>
#let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t (y__); }, y__)

data XkbDescRec = XkbDescRec   { names  :: Ptr XkbNamesRec } deriving (Show)

data XkbNamesRec = XkbNamesRec { groups :: Ptr Word64 } -- Ignore me

foreign import ccall unsafe "X11/XKBlib.h XkbAllocKeyboard"
  xkbAllocKeyboard :: IO (Ptr XkbDescRec)

instance Storable XkbDescRec where
  sizeOf _    = (#size XkbDescRec)
  alignment _ = (#alignment XkbDescRec)
  peek ptr = do
    names <- (#peek XkbDescRec, names) ptr
    return $ XkbDescRec names 

main = do
  xkbDescPtr <- xkbAllocKeyboard

  print xkbDescPtr           -- (1)
  peek xkbDescPtr >>= print  -- (2)

While (1) outputs 0x0000000001777d80, which sounds like a valid address, (2) emits XkbDescRec {names = 0x0000000000000000}.

I don't know if I'm using the FFI in a wrong manner or if I've misunderstood the structure of the XkbDescRec struct as detailed in the link.

Sarah
  • 6,565
  • 1
  • 33
  • 44
  • I'm starting to think I've misunderstood XkbAllocKeyboard, and that it always initializes that pointer to empty. If someone can confirm that I'll gladly accept. – Sarah Sep 04 '14 at 21:30

1 Answers1

1

XkbAllocKeyboard produces a blank XkbDescRec to be populated by the programmer. The correct method is to use XkbGetKeyboard. I did as follows, changes and necessary bits only:

import Graphics.X11.Xlib (openDisplay, Display(..))

foreign import ccall unsafe "X11/XKBlib.h XkbGetKeyboard"  
xkbGetKeyboard :: Display -> CUInt -> CUInt -> IO (Ptr XkbDescRec)

main = do
  dpy        <- openDisplay ""
  xkbDescPtr <- xkbGetKeyboard dpy 0x7f (#const XkbUseCoreKbd)

The XkbDescRep is populated correctly with the 0x7f being the mask for "everything!"

Sarah
  • 6,565
  • 1
  • 33
  • 44