Question

I'm trying to write bindings to some of the win32 API functions not included in the win32 package, but running into a bit of a difficultly. In the following code the bindings for EnumWindows and GetWindow work fine, but those for GetWindowText and GetWindowTextLength do not:

{-# LANGUAGE ForeignFunctionInterface #-}

import Foreign.Ptr
import Graphics.Win32.GDI.Types (HWND)
import System.Win32.Types (ptrToMaybe)
import Foreign.C
import Foreign.Marshal.Alloc (free)
import Control.Applicative ((<$>))

gW_CHILD = 5::CInt

getWindow :: HWND -> CInt -> IO (Maybe HWND)
getWindow hwnd cint = ptrToMaybe <$> (c_getWindow hwnd cint)
foreign import stdcall "windows.h GetWindow"
  c_getWindow :: HWND -> CInt -> IO HWND

foreign import stdcall "windows.h EnumWindows"
  enumWindows :: (FunPtr (HWND -> Ptr b -> IO a)) -> CInt -> IO CInt  

foreign import stdcall "windows.h GetWindowText"
  getWindowText ::  HWND -> CString -> CInt -> IO CInt 

foreign import stdcall "windows.h GetWindowTextLength"
  getWindowTextLength ::  HWND -> IO CInt 

foreign import ccall "wrapper"
  wrapEnumWindowsProc :: (HWND -> Ptr a -> IO CInt) -> IO (FunPtr (HWND -> Ptr a-> IO CInt))

findFirstNamedChildWindow :: HWND -> Ptr a -> IO CInt
findFirstNamedChildWindow hwnd _ = do
      mchild <- getWindow hwnd gW_CHILD
      case mchild of 
            Just hchwnd -> do                
                  clen <- getWindowTextLength (hchwnd)
                  case clen of 
                         0 -> return 1 
                         _ -> do
                              str <- newCString (replicate (fromEnum clen) ' ')
                              getWindowText hwnd str $ clen+1
                              print =<< peekCString str
                              free str >> return 0                                          
            Nothing -> return 1
main = do
      enptr <- wrapEnumWindowsProc findFirstNamedChildWindow
      enumWindows enptr 0
      return ()

I get the following error message:

C:\Users\me>ghc nc.hs
Linking nc.exe ...
nc.o:fake:(.text+0x958): undefined reference to `GetWindowText@12'
nc.o:fake:(.text+0xe12): undefined reference to `GetWindowTextLength@4'
collect2: ld returned 1 exit status

All 4 functions are in the User32.dll. GHC version is 7.8.2 (32 bit), OS is Windows 7 (64).

If I add this C file:

#include <windows.h>

int getWindowText (HWND hwnd, char* str, int len) {
    return GetWindowText (hwnd, str, len);
    }
int getWindowTextLength (HWND hwnd) {
    return GetWindowTextLength (hwnd);
    }

and change the import calls

foreign import call "getWindowText"

foreign import call "getWindowTextLength" 

everything works as expected. What is going on? Something about implicit casts or something like that? I tried the wide string functions from Foreign.C.String but that didn't change anything. (Also is that the intended way to pass a string buffer for C to write to or is there a better method?)

Was it helpful?

Solution

Most Windows functions that handle strings come in two versions, an ANSI version with an A suffix and a Unicode version with a W suffix.

For example, GetWindowText is actually exported as two functions, GetWindowTextA and GetWindowTextW. These names appear near the bottom of the documentation.

An LPTSTR parameter is interpreted as LPSTR for the A version and LPWSTR for the W version. You can use either function, but clearly you have to use the appropriate string type to go with it.

The C version works because GetWindowText is actually a C macro that expands to either GetWindowTextA or GetWindowTextW depending on whether you have the UNICODE macro defined.

Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top