Replaced CreateDCA by CreateDCW in LoadImageW.
[wine] / windows / winproc.c
1 /*
2  * Window procedure callbacks
3  *
4  * Copyright 1995 Martin von Loewis
5  * Copyright 1996 Alexandre Julliard
6  *
7  * This library is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU Lesser General Public
9  * License as published by the Free Software Foundation; either
10  * version 2.1 of the License, or (at your option) any later version.
11  *
12  * This library is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
15  * Lesser General Public License for more details.
16  *
17  * You should have received a copy of the GNU Lesser General Public
18  * License along with this library; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
20  */
21
22 #include "config.h"
23 #include "wine/port.h"
24
25 #include <string.h>
26
27 #include "windef.h"
28 #include "winbase.h"
29 #include "wingdi.h"
30 #include "wownt32.h"
31 #include "wine/winbase16.h"
32 #include "wine/winuser16.h"
33 #include "stackframe.h"
34 #include "selectors.h"
35 #include "controls.h"
36 #include "heap.h"
37 #include "struct32.h"
38 #include "win.h"
39 #include "winproc.h"
40 #include "wine/debug.h"
41 #include "spy.h"
42 #include "thread.h"
43 #include "dde.h"
44
45 WINE_DECLARE_DEBUG_CHANNEL(msg);
46 WINE_DECLARE_DEBUG_CHANNEL(relay);
47 WINE_DECLARE_DEBUG_CHANNEL(win);
48
49 #include "pshpack1.h"
50
51 /* Window procedure 16-to-32-bit thunk */
52 typedef struct
53 {
54     BYTE       popl_eax;             /* popl  %eax (return address) */
55     BYTE       pushl_func;           /* pushl $proc */
56     WNDPROC    proc;
57     BYTE       pushl_eax;            /* pushl %eax */
58     BYTE       ljmp;                 /* ljmp relay*/
59     DWORD      relay_offset;         /* __wine_call_wndproc_32A/W */
60     WORD       relay_sel;
61 } WINPROC_THUNK_FROM16;
62
63 /* Window procedure 32-to-16-bit thunk */
64 typedef struct
65 {
66     BYTE       popl_eax;             /* popl  %eax (return address) */
67     BYTE       pushl_func;           /* pushl $proc */
68     WNDPROC16  proc;
69     BYTE       pushl_eax;            /* pushl %eax */
70     BYTE       jmp;                  /* jmp   relay (relative jump)*/
71     void     (*relay)();             /* WINPROC_CallProc32ATo16() */
72 } WINPROC_THUNK_FROM32;
73
74 /* Simple jmp to call 32-bit procedure directly */
75 typedef struct
76 {
77     BYTE       jmp;                  /* jmp  proc (relative jump) */
78     WNDPROC    proc;
79 } WINPROC_JUMP;
80 #include "poppack.h"
81
82 typedef union
83 {
84     WINPROC_THUNK_FROM16  t_from16;
85     WINPROC_THUNK_FROM32  t_from32;
86 } WINPROC_THUNK;
87
88 typedef struct tagWINDOWPROC
89 {
90     WINPROC_THUNK         thunk;    /* Thunk */
91     WINPROC_JUMP          jmp;      /* Jump */
92     struct tagWINDOWPROC *next;     /* Next window proc */
93     UINT                magic;    /* Magic number */
94     WINDOWPROCTYPE        type;     /* Function type */
95     WINDOWPROCUSER        user;     /* Function user */
96 } WINDOWPROC;
97
98 #define WINPROC_MAGIC  ('W' | ('P' << 8) | ('R' << 16) | ('C' << 24))
99
100 #define WINPROC_THUNKPROC(pproc) \
101     (((pproc)->type == WIN_PROC_16) ? \
102           (WNDPROC16)((pproc)->thunk.t_from32.proc) : \
103           (WNDPROC16)((pproc)->thunk.t_from16.proc))
104
105 static LRESULT WINAPI WINPROC_CallProc32ATo16( WNDPROC16 func, HWND hwnd,
106                                                UINT msg, WPARAM wParam,
107                                                LPARAM lParam );
108 static LRESULT WINAPI WINPROC_CallProc32WTo16( WNDPROC16 func, HWND hwnd,
109                                                UINT msg, WPARAM wParam,
110                                                LPARAM lParam );
111
112 static HANDLE WinProcHeap;
113 static WORD WinProcSel;
114
115
116 /**********************************************************************
117  *           WINPROC_Init
118  */
119 BOOL WINPROC_Init(void)
120 {
121     WinProcHeap = HeapCreate( 0, 0x10000, 0x10000 );
122     WinProcSel = SELECTOR_AllocBlock( (void *)WinProcHeap, 0x10000,
123                                       WINE_LDT_FLAGS_CODE | WINE_LDT_FLAGS_32BIT );
124     if (!WinProcHeap || !WinProcSel)
125     {
126         WARN_(relay)("Unable to create winproc heap\n" );
127         return FALSE;
128     }
129     return TRUE;
130 }
131
132
133 #ifdef __i386__
134 /* Some window procedures modify register they shouldn't, or are not
135  * properly declared stdcall; so we need a small assembly wrapper to
136  * call them. */
137 extern LRESULT WINPROC_wrapper( WNDPROC proc, HWND hwnd, UINT msg,
138                                 WPARAM wParam, LPARAM lParam );
139 __ASM_GLOBAL_FUNC( WINPROC_wrapper,
140                    "pushl %ebp\n\t"
141                    "movl %esp,%ebp\n\t"
142                    "pushl %edi\n\t"
143                    "pushl %esi\n\t"
144                    "pushl %ebx\n\t"
145                    "pushl 24(%ebp)\n\t"
146                    "pushl 20(%ebp)\n\t"
147                    "pushl 16(%ebp)\n\t"
148                    "pushl 12(%ebp)\n\t"
149                    "movl 8(%ebp),%eax\n\t"
150                    "call *%eax\n\t"
151                    "leal -12(%ebp),%esp\n\t"
152                    "popl %ebx\n\t"
153                    "popl %esi\n\t"
154                    "popl %edi\n\t"
155                    "leave\n\t"
156                    "ret" );
157 #else
158 static inline LRESULT WINPROC_wrapper( WNDPROC proc, HWND hwnd, UINT msg,
159                                        WPARAM wParam, LPARAM lParam )
160 {
161     return proc( hwnd, msg, wParam, lParam );
162 }
163 #endif  /* __i386__ */
164
165 /**********************************************************************
166  *           WINPROC_CallWndProc32
167  *
168  * Call a 32-bit WndProc.
169  */
170 static LRESULT WINPROC_CallWndProc( WNDPROC proc, HWND hwnd, UINT msg,
171                                       WPARAM wParam, LPARAM lParam )
172 {
173     LRESULT retvalue;
174     int iWndsLocks;
175
176     hwnd = WIN_GetFullHandle( hwnd );
177     if (TRACE_ON(relay))
178         DPRINTF( "%08lx:Call window proc %p (hwnd=%08x,msg=%s,wp=%08x,lp=%08lx)\n",
179                  GetCurrentThreadId(), proc, hwnd, SPY_GetMsgName(msg, hwnd), wParam, lParam );
180     /* To avoid any deadlocks, all the locks on the windows structures
181        must be suspended before the control is passed to the application */
182     iWndsLocks = WIN_SuspendWndsLock();
183     retvalue = WINPROC_wrapper( proc, hwnd, msg, wParam, lParam );
184     WIN_RestoreWndsLock(iWndsLocks);
185
186     if (TRACE_ON(relay))
187         DPRINTF( "%08lx:Ret  window proc %p (hwnd=%08x,msg=%s,wp=%08x,lp=%08lx) retval=%08lx\n",
188                  GetCurrentThreadId(), proc, hwnd, SPY_GetMsgName(msg, hwnd), wParam, lParam, retvalue );
189     return retvalue;
190 }
191
192 /***********************************************************************
193  *           WINPROC_CallWndProc16
194  *
195  * Call a 16-bit window procedure
196  */
197 static LRESULT WINAPI WINPROC_CallWndProc16( WNDPROC16 proc, HWND16 hwnd,
198                                              UINT16 msg, WPARAM16 wParam,
199                                              LPARAM lParam )
200 {
201     CONTEXT86 context;
202     LRESULT ret;
203     WORD *args;
204     DWORD offset = 0;
205     TEB *teb = NtCurrentTeb();
206     int iWndsLocks;
207
208     /* Window procedures want ax = hInstance, ds = es = ss */
209
210     memset(&context, '\0', sizeof(context));
211     context.SegDs = context.SegEs = SELECTOROF(teb->cur_stack);
212     if (!(context.Eax = GetWindowWord( HWND_32(hwnd), GWL_HINSTANCE ))) context.Eax = context.SegDs;
213     context.SegCs = SELECTOROF(proc);
214     context.Eip   = OFFSETOF(proc);
215     context.Ebp   = OFFSETOF(teb->cur_stack)
216                         + (WORD)&((STACK16FRAME*)0)->bp;
217
218     if (lParam)
219     {
220         /* Some programs (eg. the "Undocumented Windows" examples, JWP) only
221            work if structures passed in lParam are placed in the stack/data
222            segment. Programmers easily make the mistake of converting lParam
223            to a near rather than a far pointer, since Windows apparently
224            allows this. We copy the structures to the 16 bit stack; this is
225            ugly but makes these programs work. */
226         switch (msg)
227         {
228           case WM_CREATE:
229           case WM_NCCREATE:
230             offset = sizeof(CREATESTRUCT16); break;
231           case WM_DRAWITEM:
232             offset = sizeof(DRAWITEMSTRUCT16); break;
233           case WM_COMPAREITEM:
234             offset = sizeof(COMPAREITEMSTRUCT16); break;
235         }
236         if (offset)
237         {
238             void *s = MapSL(lParam);
239             lParam = stack16_push( offset );
240             memcpy( MapSL(lParam), s, offset );
241         }
242     }
243
244     iWndsLocks = WIN_SuspendWndsLock();
245
246     args = (WORD *)THREAD_STACK16(teb) - 5;
247     args[0] = LOWORD(lParam);
248     args[1] = HIWORD(lParam);
249     args[2] = wParam;
250     args[3] = msg;
251     args[4] = hwnd;
252
253     wine_call_to_16_regs_short( &context, 5 * sizeof(WORD) );
254     ret = MAKELONG( LOWORD(context.Eax), LOWORD(context.Edx) );
255     if (offset) stack16_pop( offset );
256
257     WIN_RestoreWndsLock(iWndsLocks);
258
259     return ret;
260 }
261
262
263 /**********************************************************************
264  *           WINPROC_GetPtr
265  *
266  * Return a pointer to the win proc.
267  */
268 static WINDOWPROC *WINPROC_GetPtr( WNDPROC16 handle )
269 {
270     BYTE *ptr;
271     WINDOWPROC *proc;
272
273     /* ptr cannot be < 64K */
274     if (!HIWORD(handle)) return NULL;
275
276     /* Check for a linear pointer */
277
278     ptr = (BYTE *)handle;
279     /* First check if it is the jmp address */
280     proc = (WINDOWPROC *)(ptr - (int)&((WINDOWPROC *)0)->jmp);
281     if (HeapValidate( WinProcHeap, 0, proc ) && (proc->magic == WINPROC_MAGIC))
282         return proc;
283     /* Now it must be the thunk address */
284     proc = (WINDOWPROC *)(ptr - (int)&((WINDOWPROC *)0)->thunk);
285     if (HeapValidate( WinProcHeap, 0, proc ) && (proc->magic == WINPROC_MAGIC))
286         return proc;
287
288     /* Check for a segmented pointer */
289
290     if (!IsBadReadPtr16( (SEGPTR)handle, sizeof(proc->thunk) ))
291     {
292         ptr = MapSL( (SEGPTR)handle );
293         /* It must be the thunk address */
294         proc = (WINDOWPROC *)(ptr - (int)&((WINDOWPROC *)0)->thunk);
295         if (HeapValidate( WinProcHeap, 0, proc ) && (proc->magic == WINPROC_MAGIC))
296             return proc;
297     }
298
299     return NULL;
300 }
301
302
303 /**********************************************************************
304  *           WINPROC_AllocWinProc
305  *
306  * Allocate a new window procedure.
307  */
308 static WINDOWPROC *WINPROC_AllocWinProc( WNDPROC16 func, WINDOWPROCTYPE type,
309                                          WINDOWPROCUSER user )
310 {
311     static FARPROC16 relay_32A, relay_32W;
312
313     WINDOWPROC *proc, *oldproc;
314
315     /* Allocate a window procedure */
316
317     if (!(proc = HeapAlloc( WinProcHeap, 0, sizeof(WINDOWPROC) ))) return 0;
318
319     /* Check if the function is already a win proc */
320
321     if ((oldproc = WINPROC_GetPtr( func )))
322     {
323         *proc = *oldproc;
324     }
325     else
326     {
327         switch(type)
328         {
329         case WIN_PROC_16:
330             proc->thunk.t_from32.popl_eax    = 0x58;   /* popl  %eax */
331             proc->thunk.t_from32.pushl_func  = 0x68;   /* pushl $proc */
332             proc->thunk.t_from32.proc        = func;
333             proc->thunk.t_from32.pushl_eax   = 0x50;   /* pushl %eax */
334             proc->thunk.t_from32.jmp         = 0xe9;   /* jmp   relay*/
335             proc->thunk.t_from32.relay =  /* relative jump */
336                 (void(*)())((DWORD)WINPROC_CallProc32ATo16 -
337                                      (DWORD)(&proc->thunk.t_from32.relay + 1));
338             break;
339         case WIN_PROC_32A:
340             if (!relay_32A) relay_32A = GetProcAddress16( GetModuleHandle16("user"),
341                                                           "__wine_call_wndproc_32A" );
342             proc->thunk.t_from16.popl_eax     = 0x58;   /* popl  %eax */
343             proc->thunk.t_from16.pushl_func   = 0x68;   /* pushl $proc */
344             proc->thunk.t_from16.proc         = (WNDPROC)func;
345             proc->thunk.t_from16.pushl_eax    = 0x50;   /* pushl %eax */
346             proc->thunk.t_from16.ljmp         = 0xea;   /* ljmp   relay*/
347             proc->thunk.t_from16.relay_offset = OFFSETOF(relay_32A);
348             proc->thunk.t_from16.relay_sel    = SELECTOROF(relay_32A);
349             proc->jmp.jmp  = 0xe9;
350             /* Fixup relative jump */
351             proc->jmp.proc = (WNDPROC)((DWORD)func - (DWORD)(&proc->jmp.proc + 1));
352             break;
353         case WIN_PROC_32W:
354             if (!relay_32W) relay_32W = GetProcAddress16( GetModuleHandle16("user"),
355                                                           "__wine_call_wndproc_32W" );
356             proc->thunk.t_from16.popl_eax     = 0x58;   /* popl  %eax */
357             proc->thunk.t_from16.pushl_func   = 0x68;   /* pushl $proc */
358             proc->thunk.t_from16.proc         = (WNDPROC)func;
359             proc->thunk.t_from16.pushl_eax    = 0x50;   /* pushl %eax */
360             proc->thunk.t_from16.ljmp         = 0xea;   /* ljmp   relay*/
361             proc->thunk.t_from16.relay_offset = OFFSETOF(relay_32W);
362             proc->thunk.t_from16.relay_sel    = SELECTOROF(relay_32W);
363             proc->jmp.jmp  = 0xe9;
364             /* Fixup relative jump */
365             proc->jmp.proc = (WNDPROC)((DWORD)func - (DWORD)(&proc->jmp.proc + 1));
366             break;
367         default:
368             /* Should not happen */
369             break;
370         }
371         proc->magic = WINPROC_MAGIC;
372         proc->type  = type;
373         proc->user  = user;
374     }
375     proc->next  = NULL;
376     TRACE_(win)("(%08x,%d): returning %08x\n",
377                  (UINT)func, type, (UINT)proc );
378     return proc;
379 }
380
381
382 /**********************************************************************
383  *           WINPROC_GetProc
384  *
385  * Get a window procedure pointer that can be passed to the Windows program.
386  */
387 WNDPROC16 WINPROC_GetProc( HWINDOWPROC proc, WINDOWPROCTYPE type )
388 {
389     WINDOWPROC *ptr = (WINDOWPROC *)proc;
390
391     if (!proc) return NULL;
392     if (type == WIN_PROC_16)  /* We want a 16:16 address */
393     {
394         if (ptr->type == WIN_PROC_16)
395             return ptr->thunk.t_from32.proc;
396         else
397             return (WNDPROC16)MAKESEGPTR( WinProcSel, (char *)&ptr->thunk - (char *)WinProcHeap );
398     }
399     else  /* We want a 32-bit address */
400     {
401         if (ptr->type == WIN_PROC_16)
402             return (WNDPROC16)&ptr->thunk;
403         else if (type != ptr->type)
404             /* Have to return the jmp address if types don't match */
405             return (WNDPROC16)&ptr->jmp;
406         else
407             /* Some Win16 programs want to get back the proc they set */
408             return (WNDPROC16)ptr->thunk.t_from16.proc;
409     }
410 }
411
412
413 /**********************************************************************
414  *           WINPROC_SetProc
415  *
416  * Set the window procedure for a window or class. There are
417  * three tree classes of winproc callbacks:
418  *
419  * 1) class  -> wp                      -       not subclassed
420  *    class  -> wp -> wp -> wp -> wp    -       SetClassLong()
421  *             /           /
422  * 2) window -'           /             -       not subclassed
423  *    window -> wp -> wp '              -       SetWindowLong()
424  *
425  * 3) timer  -> wp                      -       SetTimer()
426  *
427  * Initially, winproc of the window points to the current winproc
428  * thunk of its class. Subclassing prepends a new thunk to the
429  * window winproc chain at the head of the list. Thus, window thunk
430  * list includes class thunks and the latter are preserved when the
431  * window is destroyed.
432  *
433  */
434 BOOL WINPROC_SetProc( HWINDOWPROC *pFirst, WNDPROC16 func,
435                         WINDOWPROCTYPE type, WINDOWPROCUSER user )
436 {
437     BOOL bRecycle = FALSE;
438     WINDOWPROC *proc, **ppPrev;
439
440     /* Check if function is already in the list */
441
442     ppPrev = (WINDOWPROC **)pFirst;
443     proc = WINPROC_GetPtr( func );
444     while (*ppPrev)
445     {
446         if (proc)
447         {
448             if (*ppPrev == proc)
449             {
450                 if ((*ppPrev)->user != user)
451                 {
452                     /* terminal thunk is being restored */
453
454                     WINPROC_FreeProc( *pFirst, (*ppPrev)->user );
455                     *(WINDOWPROC **)pFirst = *ppPrev;
456                     return TRUE;
457                 }
458                 bRecycle = TRUE;
459                 break;
460             }
461         }
462         else
463         {
464             if (((*ppPrev)->type == type) &&
465                 (func == WINPROC_THUNKPROC(*ppPrev)))
466             {
467                 if((*ppPrev)->user == user)
468                 {
469                     bRecycle = TRUE;
470                 }
471                 else
472                 {
473                     WINPROC_FreeProc( *ppPrev, user );
474                     *ppPrev = NULL;
475                 }
476                 break;
477             }
478         }
479
480         /* WPF_CLASS thunk terminates window thunk list */
481         if ((*ppPrev)->user != user) break;
482         ppPrev = &(*ppPrev)->next;
483     }
484
485     if (bRecycle)
486     {
487         /* Extract this thunk from the list */
488         proc = *ppPrev;
489         *ppPrev = proc->next;
490     }
491     else  /* Allocate a new one */
492     {
493         if (proc)  /* Was already a win proc */
494         {
495             type = proc->type;
496             func = WINPROC_THUNKPROC(proc);
497         }
498         proc = WINPROC_AllocWinProc( func, type, user );
499         if (!proc) return FALSE;
500     }
501
502     /* Add the win proc at the head of the list */
503
504     TRACE_(win)("(%08x,%08x,%d): res=%08x\n",
505                  (UINT)*pFirst, (UINT)func, type, (UINT)proc );
506     proc->next  = *(WINDOWPROC **)pFirst;
507     *(WINDOWPROC **)pFirst = proc;
508     return TRUE;
509 }
510
511
512 /**********************************************************************
513  *           WINPROC_FreeProc
514  *
515  * Free a list of win procs.
516  */
517 void WINPROC_FreeProc( HWINDOWPROC proc, WINDOWPROCUSER user )
518 {
519     while (proc)
520     {
521         WINDOWPROC *next = ((WINDOWPROC *)proc)->next;
522         if (((WINDOWPROC *)proc)->user != user) break;
523         TRACE_(win)("freeing %08x (%d)\n", (UINT)proc, user);
524         HeapFree( WinProcHeap, 0, proc );
525         proc = next;
526     }
527 }
528
529
530 /**********************************************************************
531  *           WINPROC_GetProcType
532  *
533  * Return the window procedure type.
534  */
535 WINDOWPROCTYPE WINPROC_GetProcType( HWINDOWPROC proc )
536 {
537     if (!proc ||
538         (((WINDOWPROC *)proc)->magic != WINPROC_MAGIC))
539         return WIN_PROC_INVALID;
540     return ((WINDOWPROC *)proc)->type;
541 }
542 /**********************************************************************
543  *           WINPROC_TestCBForStr
544  *
545  * Return TRUE if the lparam is a string
546  */
547 inline static BOOL WINPROC_TestCBForStr( HWND hwnd )
548 {
549     DWORD style = GetWindowLongA( hwnd, GWL_STYLE );
550     return (!(style & (CBS_OWNERDRAWFIXED | CBS_OWNERDRAWVARIABLE)) || (style & CBS_HASSTRINGS));
551 }
552 /**********************************************************************
553  *           WINPROC_TestLBForStr
554  *
555  * Return TRUE if the lparam is a string
556  */
557 inline static BOOL WINPROC_TestLBForStr( HWND hwnd )
558 {
559     DWORD style = GetWindowLongA( hwnd, GWL_STYLE );
560     return (!(style & (LBS_OWNERDRAWFIXED | LBS_OWNERDRAWVARIABLE)) || (style & LBS_HASSTRINGS));
561
562 }
563 /**********************************************************************
564  *           WINPROC_MapMsg32ATo32W
565  *
566  * Map a message from Ansi to Unicode.
567  * Return value is -1 on error, 0 if OK, 1 if an UnmapMsg call is needed.
568  *
569  * FIXME:
570  *  WM_GETTEXT/WM_SETTEXT and static control with SS_ICON style:
571  *  the first four bytes are the handle of the icon
572  *  when the WM_SETTEXT message has been used to set the icon
573  */
574 INT WINPROC_MapMsg32ATo32W( HWND hwnd, UINT msg, WPARAM *pwparam, LPARAM *plparam )
575 {
576     switch(msg)
577     {
578     case WM_GETTEXT:
579     case WM_ASKCBFORMATNAME:
580         {
581             LPARAM *ptr = (LPARAM *)HeapAlloc( GetProcessHeap(), 0,
582                                      *pwparam * sizeof(WCHAR) + sizeof(LPARAM) );
583             if (!ptr) return -1;
584             *ptr++ = *plparam;  /* Store previous lParam */
585             *plparam = (LPARAM)ptr;
586         }
587         return 1;
588     /* lparam is string (0-terminated) */
589     case WM_SETTEXT:
590     case WM_WININICHANGE:
591     case WM_DEVMODECHANGE:
592     case CB_DIR:
593     case LB_DIR:
594     case LB_ADDFILE:
595     case EM_REPLACESEL:
596         if(!*plparam) return 0;
597         *plparam = (LPARAM)HEAP_strdupAtoW( GetProcessHeap(), 0, (LPCSTR)*plparam );
598         return (*plparam ? 1 : -1);
599     case WM_GETTEXTLENGTH:
600     case CB_GETLBTEXTLEN:
601     case LB_GETTEXTLEN:
602         return 1;  /* need to map result */
603     case WM_NCCREATE:
604     case WM_CREATE:
605         {
606             struct s
607             { CREATESTRUCTW cs;         /* new structure */
608               LPCWSTR lpszName;         /* allocated Name */
609               LPCWSTR lpszClass;        /* allocated Class */
610             };
611
612             struct s *xs = HeapAlloc( GetProcessHeap(), HEAP_ZERO_MEMORY, sizeof(struct s));
613             if (!xs) return -1;
614             xs->cs = *(CREATESTRUCTW *)*plparam;
615             if (HIWORD(xs->cs.lpszName))
616                 xs->lpszName = xs->cs.lpszName = HEAP_strdupAtoW( GetProcessHeap(), 0,
617                                                                   (LPCSTR)xs->cs.lpszName );
618             if (HIWORD(xs->cs.lpszClass))
619                 xs->lpszClass = xs->cs.lpszClass = HEAP_strdupAtoW( GetProcessHeap(), 0,
620                                                                     (LPCSTR)xs->cs.lpszClass );
621             *plparam = (LPARAM)xs;
622         }
623         return 1;
624     case WM_MDICREATE:
625         {
626             MDICREATESTRUCTW *cs =
627                 (MDICREATESTRUCTW *)HeapAlloc( GetProcessHeap(), 0, sizeof(*cs) );
628             if (!cs) return -1;
629             *cs = *(MDICREATESTRUCTW *)*plparam;
630             if (HIWORD(cs->szClass))
631                 cs->szClass = HEAP_strdupAtoW( GetProcessHeap(), 0,
632                                                (LPCSTR)cs->szClass );
633             if (HIWORD(cs->szTitle))
634                 cs->szTitle = HEAP_strdupAtoW( GetProcessHeap(), 0,
635                                                (LPCSTR)cs->szTitle );
636             *plparam = (LPARAM)cs;
637         }
638         return 1;
639
640 /* Listbox */
641     case LB_ADDSTRING:
642     case LB_INSERTSTRING:
643     case LB_FINDSTRING:
644     case LB_FINDSTRINGEXACT:
645     case LB_SELECTSTRING:
646         if(!*plparam) return 0;
647         if ( WINPROC_TestLBForStr( hwnd ))
648           *plparam = (LPARAM)HEAP_strdupAtoW( GetProcessHeap(), 0, (LPCSTR)*plparam );
649         return (*plparam ? 1 : -1);
650
651     case LB_GETTEXT:                /* FIXME: fixed sized buffer */
652         { if ( WINPROC_TestLBForStr( hwnd ))
653           { LPARAM *ptr = (LPARAM *)HeapAlloc( GetProcessHeap(), 0, 256 * sizeof(WCHAR) + sizeof(LPARAM) );
654             if (!ptr) return -1;
655             *ptr++ = *plparam;  /* Store previous lParam */
656             *plparam = (LPARAM)ptr;
657           }
658         }
659         return 1;
660
661 /* Combobox */
662     case CB_ADDSTRING:
663     case CB_INSERTSTRING:
664     case CB_FINDSTRINGEXACT:
665     case CB_FINDSTRING:
666     case CB_SELECTSTRING:
667         if(!*plparam) return 0;
668         if ( WINPROC_TestCBForStr( hwnd ))
669           *plparam = (LPARAM)HEAP_strdupAtoW( GetProcessHeap(), 0, (LPCSTR)*plparam );
670         return (*plparam ? 1 : -1);
671
672     case CB_GETLBTEXT:    /* FIXME: fixed sized buffer */
673         { if ( WINPROC_TestCBForStr( hwnd ))
674           { LPARAM *ptr = (LPARAM *)HeapAlloc( GetProcessHeap(), 0, 256 * sizeof(WCHAR) + sizeof(LPARAM) );
675             if (!ptr) return -1;
676             *ptr++ = *plparam;  /* Store previous lParam */
677             *plparam = (LPARAM)ptr;
678           }
679         }
680         return 1;
681
682 /* Multiline edit */
683     case EM_GETLINE:
684         { WORD len = (WORD)*plparam;
685           LPARAM *ptr = (LPARAM *) HeapAlloc( GetProcessHeap(), 0, sizeof(LPARAM) + sizeof (WORD) + len*sizeof(WCHAR) );
686           if (!ptr) return -1;
687           *ptr++ = *plparam;  /* Store previous lParam */
688           *((WORD *) ptr) = len;   /* Store the length */
689           *plparam = (LPARAM)ptr;
690         }
691         return 1;
692
693     case WM_CHARTOITEM:
694     case WM_MENUCHAR:
695     case WM_CHAR:
696     case WM_DEADCHAR:
697     case WM_SYSCHAR:
698     case WM_SYSDEADCHAR:
699     case EM_SETPASSWORDCHAR:
700         {
701             BYTE ch = LOWORD(*pwparam);
702             WCHAR wch;
703             MultiByteToWideChar(CP_ACP, 0, &ch, 1, &wch, 1);
704             *pwparam = MAKEWPARAM( wch, HIWORD(*pwparam) );
705         }
706         return 0;
707
708     case WM_PAINTCLIPBOARD:
709     case WM_SIZECLIPBOARD:
710         FIXME_(msg)("message %s (0x%x) needs translation, please report\n", SPY_GetMsgName(msg, hwnd), msg );
711         return -1;
712     default:  /* No translation needed */
713         return 0;
714     }
715 }
716
717
718 /**********************************************************************
719  *           WINPROC_UnmapMsg32ATo32W
720  *
721  * Unmap a message that was mapped from Ansi to Unicode.
722  */
723 LRESULT WINPROC_UnmapMsg32ATo32W( HWND hwnd, UINT msg, WPARAM wParam, LPARAM lParam,
724                                   LRESULT result )
725 {
726     switch(msg)
727     {
728     case WM_GETTEXT:
729     case WM_ASKCBFORMATNAME:
730         {
731             LPARAM *ptr = (LPARAM *)lParam - 1;
732             if (wParam > 0 && !WideCharToMultiByte( CP_ACP, 0, (LPWSTR)lParam, -1,
733                                                     (LPSTR)*ptr, wParam, NULL, NULL ))
734                 ((LPSTR)*ptr)[wParam-1] = 0;
735             HeapFree( GetProcessHeap(), 0, ptr );
736         }
737         break;
738     case WM_GETTEXTLENGTH:
739     case CB_GETLBTEXTLEN:
740     case LB_GETTEXTLEN:
741         /* there may be one DBCS char for each Unicode char */
742         return result * 2;
743     case WM_NCCREATE:
744     case WM_CREATE:
745         {
746             struct s
747             { CREATESTRUCTW cs;         /* new structure */
748               LPWSTR lpszName;          /* allocated Name */
749               LPWSTR lpszClass;         /* allocated Class */
750             };
751             struct s *xs = (struct s *)lParam;
752             if (xs->lpszName)  HeapFree( GetProcessHeap(), 0, xs->lpszName );
753             if (xs->lpszClass) HeapFree( GetProcessHeap(), 0, xs->lpszClass );
754             HeapFree( GetProcessHeap(), 0, xs );
755         }
756         break;
757
758     case WM_MDICREATE:
759         {
760             MDICREATESTRUCTW *cs = (MDICREATESTRUCTW *)lParam;
761             if (HIWORD(cs->szTitle))
762                 HeapFree( GetProcessHeap(), 0, (LPVOID)cs->szTitle );
763             if (HIWORD(cs->szClass))
764                 HeapFree( GetProcessHeap(), 0, (LPVOID)cs->szClass );
765             HeapFree( GetProcessHeap(), 0, cs );
766         }
767         break;
768
769     case WM_SETTEXT:
770     case WM_WININICHANGE:
771     case WM_DEVMODECHANGE:
772     case CB_DIR:
773     case LB_DIR:
774     case LB_ADDFILE:
775     case EM_REPLACESEL:
776         HeapFree( GetProcessHeap(), 0, (void *)lParam );
777         break;
778
779 /* Listbox */
780     case LB_ADDSTRING:
781     case LB_INSERTSTRING:
782     case LB_FINDSTRING:
783     case LB_FINDSTRINGEXACT:
784     case LB_SELECTSTRING:
785         if ( WINPROC_TestLBForStr( hwnd ))
786           HeapFree( GetProcessHeap(), 0, (void *)lParam );
787         break;
788
789     case LB_GETTEXT:
790         { if ( WINPROC_TestLBForStr( hwnd ))
791           { LPARAM *ptr = (LPARAM *)lParam - 1;
792             WideCharToMultiByte( CP_ACP, 0, (LPWSTR)lParam, -1, (LPSTR)*ptr, 0x7fffffff, NULL, NULL );
793             HeapFree( GetProcessHeap(), 0, ptr );
794           }
795         }
796         break;
797
798 /* Combobox */
799     case CB_ADDSTRING:
800     case CB_INSERTSTRING:
801     case CB_FINDSTRING:
802     case CB_FINDSTRINGEXACT:
803     case CB_SELECTSTRING:
804         if ( WINPROC_TestCBForStr( hwnd ))
805           HeapFree( GetProcessHeap(), 0, (void *)lParam );
806         break;
807
808     case CB_GETLBTEXT:
809         { if ( WINPROC_TestCBForStr( hwnd ))
810           { LPARAM *ptr = (LPARAM *)lParam - 1;
811             WideCharToMultiByte( CP_ACP, 0, (LPWSTR)lParam, -1, (LPSTR)*ptr, 0x7fffffff, NULL, NULL );
812             HeapFree( GetProcessHeap(), 0, ptr );
813           }
814         }
815         break;
816
817 /* Multiline edit */
818     case EM_GETLINE:
819         { LPARAM * ptr = (LPARAM *)lParam - 1;  /* get the old lParam */
820           WORD len = *(WORD *) lParam;
821           if (len > 0 && !WideCharToMultiByte( CP_ACP, 0, (LPWSTR)lParam, -1,
822                                                (LPSTR)*ptr, len, NULL, NULL ))
823               ((LPSTR)*ptr)[len-1] = 0;
824           HeapFree( GetProcessHeap(), 0, ptr );
825         }
826         break;
827     }
828     return result;
829 }
830
831
832 /**********************************************************************
833  *           WINPROC_MapMsg32WTo32A
834  *
835  * Map a message from Unicode to Ansi.
836  * Return value is -1 on error, 0 if OK, 1 if an UnmapMsg call is needed.
837  */
838 INT WINPROC_MapMsg32WTo32A( HWND hwnd, UINT msg, WPARAM *pwparam, LPARAM *plparam )
839 {
840     switch(msg)
841     {
842     case WM_GETTEXT:
843     case WM_ASKCBFORMATNAME:
844         {
845             LPARAM *ptr = (LPARAM *)HeapAlloc( GetProcessHeap(), 0,
846                                                *pwparam + sizeof(LPARAM) );
847             if (!ptr) return -1;
848             *ptr++ = *plparam;  /* Store previous lParam */
849             *plparam = (LPARAM)ptr;
850         }
851         return 1;
852
853     case WM_SETTEXT:
854     case WM_WININICHANGE:
855     case WM_DEVMODECHANGE:
856     case CB_DIR:
857     case LB_DIR:
858     case LB_ADDFILE:
859     case EM_REPLACESEL:
860         if(!*plparam) return 0;
861         *plparam = (LPARAM)HEAP_strdupWtoA( GetProcessHeap(), 0, (LPCWSTR)*plparam );
862         return (*plparam ? 1 : -1);
863
864     case WM_NCCREATE:
865     case WM_CREATE:
866         {
867             CREATESTRUCTA *cs = (CREATESTRUCTA *)HeapAlloc( GetProcessHeap(), 0,
868                                                                 sizeof(*cs) );
869             if (!cs) return -1;
870             *cs = *(CREATESTRUCTA *)*plparam;
871             if (HIWORD(cs->lpszName))
872                 cs->lpszName  = HEAP_strdupWtoA( GetProcessHeap(), 0,
873                                                  (LPCWSTR)cs->lpszName );
874             if (HIWORD(cs->lpszClass))
875                 cs->lpszClass = HEAP_strdupWtoA( GetProcessHeap(), 0,
876                                                  (LPCWSTR)cs->lpszClass);
877             *plparam = (LPARAM)cs;
878         }
879         return 1;
880     case WM_MDICREATE:
881         {
882             MDICREATESTRUCTA *cs =
883                 (MDICREATESTRUCTA *)HeapAlloc( GetProcessHeap(), 0, sizeof(*cs) );
884             if (!cs) return -1;
885             *cs = *(MDICREATESTRUCTA *)*plparam;
886             if (HIWORD(cs->szTitle))
887                 cs->szTitle = HEAP_strdupWtoA( GetProcessHeap(), 0,
888                                                (LPCWSTR)cs->szTitle );
889             if (HIWORD(cs->szClass))
890                 cs->szClass = HEAP_strdupWtoA( GetProcessHeap(), 0,
891                                                (LPCWSTR)cs->szClass );
892             *plparam = (LPARAM)cs;
893         }
894         return 1;
895
896 /* Listbox */
897     case LB_ADDSTRING:
898     case LB_INSERTSTRING:
899     case LB_FINDSTRING:
900     case LB_FINDSTRINGEXACT:
901     case LB_SELECTSTRING:
902         if(!*plparam) return 0;
903         if ( WINPROC_TestLBForStr( hwnd ))
904           *plparam = (LPARAM)HEAP_strdupWtoA( GetProcessHeap(), 0, (LPCWSTR)*plparam );
905         return (*plparam ? 1 : -1);
906
907     case LB_GETTEXT:                    /* FIXME: fixed sized buffer */
908         { if ( WINPROC_TestLBForStr( hwnd ))
909           { LPARAM *ptr = (LPARAM *)HeapAlloc( GetProcessHeap(), 0, 256 + sizeof(LPARAM) );
910             if (!ptr) return -1;
911             *ptr++ = *plparam;  /* Store previous lParam */
912             *plparam = (LPARAM)ptr;
913           }
914         }
915         return 1;
916
917 /* Combobox */
918     case CB_ADDSTRING:
919     case CB_INSERTSTRING:
920     case CB_FINDSTRING:
921     case CB_FINDSTRINGEXACT:
922     case CB_SELECTSTRING:
923         if(!*plparam) return 0;
924         if ( WINPROC_TestCBForStr( hwnd ))
925           *plparam = (LPARAM)HEAP_strdupWtoA( GetProcessHeap(), 0, (LPCWSTR)*plparam );
926         return (*plparam ? 1 : -1);
927
928     case CB_GETLBTEXT:          /* FIXME: fixed sized buffer */
929         { if ( WINPROC_TestCBForStr( hwnd ))
930           { LPARAM *ptr = (LPARAM *)HeapAlloc( GetProcessHeap(), 0, 256 + sizeof(LPARAM) );
931             if (!ptr) return -1;
932             *ptr++ = *plparam;  /* Store previous lParam */
933             *plparam = (LPARAM)ptr;
934           }
935         }
936         return 1;
937
938 /* Multiline edit */
939     case EM_GETLINE:
940         { WORD len = (WORD)*plparam;
941           LPARAM *ptr = (LPARAM *) HeapAlloc( GetProcessHeap(), 0, sizeof(LPARAM) + sizeof (WORD) + len*sizeof(CHAR) );
942           if (!ptr) return -1;
943           *ptr++ = *plparam;  /* Store previous lParam */
944           *((WORD *) ptr) = len;   /* Store the length */
945           *plparam = (LPARAM)ptr;
946         }
947         return 1;
948
949     case WM_CHARTOITEM:
950     case WM_MENUCHAR:
951     case WM_CHAR:
952     case WM_DEADCHAR:
953     case WM_SYSCHAR:
954     case WM_SYSDEADCHAR:
955     case EM_SETPASSWORDCHAR:
956         {
957             WCHAR wch = LOWORD(*pwparam);
958             BYTE ch;
959             WideCharToMultiByte( CP_ACP, 0, &wch, 1, &ch, 1, NULL, NULL );
960             *pwparam = MAKEWPARAM( ch, HIWORD(*pwparam) );
961         }
962         return 0;
963
964     case WM_PAINTCLIPBOARD:
965     case WM_SIZECLIPBOARD:
966         FIXME_(msg)("message %s (%04x) needs translation, please report\n",SPY_GetMsgName(msg, hwnd),msg );
967         return -1;
968     default:  /* No translation needed */
969         return 0;
970     }
971 }
972
973
974 /**********************************************************************
975  *           WINPROC_UnmapMsg32WTo32A
976  *
977  * Unmap a message that was mapped from Unicode to Ansi.
978  */
979 void WINPROC_UnmapMsg32WTo32A( HWND hwnd, UINT msg, WPARAM wParam, LPARAM lParam )
980 {
981     switch(msg)
982     {
983     case WM_GETTEXT:
984     case WM_ASKCBFORMATNAME:
985         {
986             LPARAM *ptr = (LPARAM *)lParam - 1;
987             if (wParam)
988             {
989                 if (!MultiByteToWideChar( CP_ACP, 0, (LPSTR)lParam, -1, (LPWSTR)*ptr, wParam ))
990                     ((LPWSTR)*ptr)[wParam-1] = 0;
991             }
992             HeapFree( GetProcessHeap(), 0, ptr );
993         }
994         break;
995
996     case WM_SETTEXT:
997     case WM_WININICHANGE:
998     case WM_DEVMODECHANGE:
999     case CB_DIR:
1000     case LB_DIR:
1001     case LB_ADDFILE:
1002     case EM_REPLACESEL:
1003         HeapFree( GetProcessHeap(), 0, (void *)lParam );
1004         break;
1005
1006     case WM_NCCREATE:
1007     case WM_CREATE:
1008         {
1009             CREATESTRUCTA *cs = (CREATESTRUCTA *)lParam;
1010             if (HIWORD(cs->lpszName))
1011                 HeapFree( GetProcessHeap(), 0, (LPVOID)cs->lpszName );
1012             if (HIWORD(cs->lpszClass))
1013                 HeapFree( GetProcessHeap(), 0, (LPVOID)cs->lpszClass );
1014             HeapFree( GetProcessHeap(), 0, cs );
1015         }
1016         break;
1017
1018     case WM_MDICREATE:
1019         {
1020             MDICREATESTRUCTA *cs = (MDICREATESTRUCTA *)lParam;
1021             if (HIWORD(cs->szTitle))
1022                 HeapFree( GetProcessHeap(), 0, (LPVOID)cs->szTitle );
1023             if (HIWORD(cs->szClass))
1024                 HeapFree( GetProcessHeap(), 0, (LPVOID)cs->szClass );
1025             HeapFree( GetProcessHeap(), 0, cs );
1026         }
1027         break;
1028
1029 /* Listbox */
1030     case LB_ADDSTRING:
1031     case LB_INSERTSTRING:
1032     case LB_FINDSTRING:
1033     case LB_FINDSTRINGEXACT:
1034     case LB_SELECTSTRING:
1035         if ( WINPROC_TestLBForStr( hwnd ))
1036           HeapFree( GetProcessHeap(), 0, (void *)lParam );
1037         break;
1038
1039     case LB_GETTEXT:
1040         if ( WINPROC_TestLBForStr( hwnd ))
1041         {
1042             LPARAM *ptr = (LPARAM *)lParam - 1;
1043             MultiByteToWideChar( CP_ACP, 0, (LPSTR)lParam, -1, (LPWSTR)*ptr, 0x7fffffff );
1044             HeapFree( GetProcessHeap(), 0, ptr );
1045         }
1046         break;
1047
1048 /* Combobox */
1049     case CB_ADDSTRING:
1050     case CB_INSERTSTRING:
1051     case CB_FINDSTRING:
1052     case CB_FINDSTRINGEXACT:
1053     case CB_SELECTSTRING:
1054         if ( WINPROC_TestCBForStr( hwnd ))
1055           HeapFree( GetProcessHeap(), 0, (void *)lParam );
1056         break;
1057
1058     case CB_GETLBTEXT:
1059         if ( WINPROC_TestCBForStr( hwnd ))
1060         {
1061             LPARAM *ptr = (LPARAM *)lParam - 1;
1062             MultiByteToWideChar( CP_ACP, 0, (LPSTR)lParam, -1, (LPWSTR)*ptr, 0x7fffffff );
1063             HeapFree( GetProcessHeap(), 0, ptr );
1064         }
1065         break;
1066
1067 /* Multiline edit */
1068     case EM_GETLINE:
1069         { LPARAM * ptr = (LPARAM *)lParam - 1;  /* get the old lparam */
1070           WORD len = *(WORD *)ptr;
1071           if (len)
1072           {
1073               if (!MultiByteToWideChar( CP_ACP, 0, (LPSTR)lParam, -1, (LPWSTR)*ptr, len ))
1074                   ((LPWSTR)*ptr)[len-1] = 0;
1075           }
1076           HeapFree( GetProcessHeap(), 0, ptr );
1077         }
1078         break;
1079     }
1080 }
1081
1082 static HANDLE convert_handle_16_to_32(HANDLE16 src, unsigned int flags)
1083 {
1084     HANDLE      dst;
1085     UINT        sz = GlobalSize16(src);
1086     LPSTR       ptr16, ptr32;
1087
1088     if (!(dst = GlobalAlloc(flags, sz)))
1089         return 0;
1090     ptr16 = GlobalLock16(src);
1091     ptr32 = GlobalLock(dst);
1092     if (ptr16 != NULL && ptr32 != NULL) memcpy(ptr32, ptr16, sz);
1093     GlobalUnlock16(src);
1094     GlobalUnlock(dst);
1095
1096     return dst;
1097 }
1098
1099 /**********************************************************************
1100  *           WINPROC_MapMsg16To32A
1101  *
1102  * Map a message from 16- to 32-bit Ansi.
1103  * Return value is -1 on error, 0 if OK, 1 if an UnmapMsg call is needed.
1104  */
1105 INT WINPROC_MapMsg16To32A( HWND hwnd, UINT16 msg16, WPARAM16 wParam16, UINT *pmsg32,
1106                              WPARAM *pwparam32, LPARAM *plparam )
1107 {
1108     *pmsg32 = (UINT)msg16;
1109     *pwparam32 = (WPARAM)wParam16;
1110     switch(msg16)
1111     {
1112     case WM_ACTIVATE:
1113     case WM_CHARTOITEM:
1114     case WM_COMMAND:
1115     case WM_VKEYTOITEM:
1116         *pwparam32 = MAKEWPARAM( wParam16, HIWORD(*plparam) );
1117         *plparam   = (LPARAM)WIN_Handle32( LOWORD(*plparam) );
1118         return 0;
1119     case WM_HSCROLL:
1120     case WM_VSCROLL:
1121         *pwparam32 = MAKEWPARAM( wParam16, LOWORD(*plparam) );
1122         *plparam   = (LPARAM)WIN_Handle32( HIWORD(*plparam) );
1123         return 0;
1124     case WM_CTLCOLOR:
1125         if ( HIWORD(*plparam) > CTLCOLOR_STATIC ) return -1;
1126         *pmsg32    = WM_CTLCOLORMSGBOX + HIWORD(*plparam);
1127         *pwparam32 = (WPARAM)HDC_32(wParam16);
1128         *plparam   = (LPARAM)WIN_Handle32( LOWORD(*plparam) );
1129         return 0;
1130     case WM_COMPAREITEM:
1131         {
1132             COMPAREITEMSTRUCT16* cis16 = MapSL(*plparam);
1133             COMPAREITEMSTRUCT *cis = (COMPAREITEMSTRUCT *)
1134                                         HeapAlloc(GetProcessHeap(), 0, sizeof(*cis));
1135             if (!cis) return -1;
1136             cis->CtlType    = cis16->CtlType;
1137             cis->CtlID      = cis16->CtlID;
1138             cis->hwndItem   = WIN_Handle32( cis16->hwndItem );
1139             cis->itemID1    = cis16->itemID1;
1140             cis->itemData1  = cis16->itemData1;
1141             cis->itemID2    = cis16->itemID2;
1142             cis->itemData2  = cis16->itemData2;
1143             cis->dwLocaleId = 0;  /* FIXME */
1144             *plparam = (LPARAM)cis;
1145         }
1146         return 1;
1147     case WM_DELETEITEM:
1148         {
1149             DELETEITEMSTRUCT16* dis16 = MapSL(*plparam);
1150             DELETEITEMSTRUCT *dis = (DELETEITEMSTRUCT *)
1151                                         HeapAlloc(GetProcessHeap(), 0, sizeof(*dis));
1152             if (!dis) return -1;
1153             dis->CtlType  = dis16->CtlType;
1154             dis->CtlID    = dis16->CtlID;
1155             dis->hwndItem = WIN_Handle32( dis16->hwndItem );
1156             dis->itemData = dis16->itemData;
1157             *plparam = (LPARAM)dis;
1158         }
1159         return 1;
1160     case WM_MEASUREITEM:
1161         {
1162             MEASUREITEMSTRUCT16* mis16 = MapSL(*plparam);
1163             MEASUREITEMSTRUCT *mis = (MEASUREITEMSTRUCT *)
1164                                         HeapAlloc(GetProcessHeap(), 0,
1165                                                 sizeof(*mis) + sizeof(LPARAM));
1166             if (!mis) return -1;
1167             mis->CtlType    = mis16->CtlType;
1168             mis->CtlID      = mis16->CtlID;
1169             mis->itemID     = mis16->itemID;
1170             mis->itemWidth  = mis16->itemWidth;
1171             mis->itemHeight = mis16->itemHeight;
1172             mis->itemData   = mis16->itemData;
1173             *(LPARAM *)(mis + 1) = *plparam;  /* Store the previous lParam */
1174             *plparam = (LPARAM)mis;
1175         }
1176         return 1;
1177     case WM_DRAWITEM:
1178         {
1179             DRAWITEMSTRUCT16* dis16 = MapSL(*plparam);
1180             DRAWITEMSTRUCT *dis = (DRAWITEMSTRUCT*)HeapAlloc(GetProcessHeap(), 0,
1181                                                                  sizeof(*dis));
1182             if (!dis) return -1;
1183             dis->CtlType    = dis16->CtlType;
1184             dis->CtlID      = dis16->CtlID;
1185             dis->itemID     = dis16->itemID;
1186             dis->itemAction = dis16->itemAction;
1187             dis->itemState  = dis16->itemState;
1188             dis->hwndItem   = (dis->CtlType == ODT_MENU) ? (HWND)HMENU_32(dis16->hwndItem)
1189                                                          : WIN_Handle32( dis16->hwndItem );
1190             dis->hDC        = dis16->hDC;
1191             dis->itemData   = dis16->itemData;
1192             CONV_RECT16TO32( &dis16->rcItem, &dis->rcItem );
1193             *plparam = (LPARAM)dis;
1194         }
1195         return 1;
1196     case WM_GETMINMAXINFO:
1197         {
1198             MINMAXINFO *mmi = (MINMAXINFO *)HeapAlloc( GetProcessHeap(), 0,
1199                                                 sizeof(*mmi) + sizeof(LPARAM));
1200             if (!mmi) return -1;
1201             STRUCT32_MINMAXINFO16to32( MapSL(*plparam), mmi );
1202             *(LPARAM *)(mmi + 1) = *plparam;  /* Store the previous lParam */
1203             *plparam = (LPARAM)mmi;
1204         }
1205         return 1;
1206     case WM_GETTEXT:
1207     case WM_SETTEXT:
1208     case WM_WININICHANGE:
1209     case WM_DEVMODECHANGE:
1210     case WM_ASKCBFORMATNAME:
1211         *plparam = (LPARAM)MapSL(*plparam);
1212         return 0;
1213     case WM_MDICREATE:
1214         {
1215             MDICREATESTRUCT16 *cs16 = MapSL(*plparam);
1216             MDICREATESTRUCTA *cs = HeapAlloc( GetProcessHeap(), 0, sizeof(*cs) + sizeof(LPARAM) );
1217             if (!cs) return -1;
1218             STRUCT32_MDICREATESTRUCT16to32A( cs16, cs );
1219             cs->szTitle = MapSL(cs16->szTitle);
1220             cs->szClass = MapSL(cs16->szClass);
1221             *(LPARAM *)(cs + 1) = *plparam;  /* Store the previous lParam */
1222             *plparam = (LPARAM)cs;
1223         }
1224         return 1;
1225     case WM_MDIGETACTIVE:
1226         *plparam = (LPARAM)HeapAlloc( GetProcessHeap(), 0, sizeof(BOOL) );
1227         *(BOOL*)(*plparam) = 0;
1228         return 1;
1229     case WM_MDISETMENU:
1230         if(wParam16==TRUE)
1231            *pmsg32=WM_MDIREFRESHMENU;
1232         *pwparam32 = (WPARAM)HMENU_32(LOWORD(*plparam));
1233         *plparam   = (LPARAM)HMENU_32(HIWORD(*plparam));
1234         return 0;
1235     case WM_MENUCHAR:
1236         *pwparam32 = MAKEWPARAM( wParam16, LOWORD(*plparam) );
1237         *plparam   = (LPARAM)HMENU_32(HIWORD(*plparam));
1238         return 0;
1239     case WM_MENUSELECT:
1240         if((LOWORD(*plparam) & MF_POPUP) && (LOWORD(*plparam) != 0xFFFF))
1241         {
1242             HMENU hmenu=HMENU_32(HIWORD(*plparam));
1243             UINT Pos=MENU_FindSubMenu( &hmenu, wParam16);
1244             if(Pos==0xFFFF) Pos=0; /* NO_SELECTED_ITEM */
1245             *pwparam32 = MAKEWPARAM( Pos, LOWORD(*plparam) );
1246         }
1247         else *pwparam32 = MAKEWPARAM( wParam16, LOWORD(*plparam) );
1248         *plparam   = (LPARAM)HMENU_32(HIWORD(*plparam));
1249         return 0;
1250     case WM_MDIACTIVATE:
1251         if( *plparam )
1252         {
1253             *pwparam32 = (WPARAM)WIN_Handle32( HIWORD(*plparam) );
1254             *plparam   = (LPARAM)WIN_Handle32( LOWORD(*plparam) );
1255         }
1256         else /* message sent to MDI client */
1257             *pwparam32 = wParam16;
1258         return 0;
1259     case WM_NCCALCSIZE:
1260         {
1261             NCCALCSIZE_PARAMS16 *nc16;
1262             NCCALCSIZE_PARAMS *nc;
1263
1264             nc = (NCCALCSIZE_PARAMS *)HeapAlloc( GetProcessHeap(), 0,
1265                                                 sizeof(*nc) + sizeof(LPARAM) );
1266             if (!nc) return -1;
1267             nc16 = MapSL(*plparam);
1268             CONV_RECT16TO32( &nc16->rgrc[0], &nc->rgrc[0] );
1269             if (wParam16)
1270             {
1271                 nc->lppos = (WINDOWPOS *)HeapAlloc( GetProcessHeap(), 0,
1272                                                       sizeof(*nc->lppos) );
1273                 CONV_RECT16TO32( &nc16->rgrc[1], &nc->rgrc[1] );
1274                 CONV_RECT16TO32( &nc16->rgrc[2], &nc->rgrc[2] );
1275                 if (nc->lppos) STRUCT32_WINDOWPOS16to32( MapSL(nc16->lppos), nc->lppos );
1276             }
1277             *(LPARAM *)(nc + 1) = *plparam;  /* Store the previous lParam */
1278             *plparam = (LPARAM)nc;
1279         }
1280         return 1;
1281     case WM_NCCREATE:
1282     case WM_CREATE:
1283         {
1284             CREATESTRUCT16 *cs16 = MapSL(*plparam);
1285             CREATESTRUCTA *cs = (CREATESTRUCTA *)HeapAlloc( GetProcessHeap(), 0,
1286                                                 sizeof(*cs) + sizeof(LPARAM) );
1287             if (!cs) return -1;
1288             STRUCT32_CREATESTRUCT16to32A( cs16, cs );
1289             cs->lpszName  = MapSL(cs16->lpszName);
1290             cs->lpszClass = MapSL(cs16->lpszClass);
1291             *(LPARAM *)(cs + 1) = *plparam;  /* Store the previous lParam */
1292             *plparam = (LPARAM)cs;
1293         }
1294         return 1;
1295     case WM_PARENTNOTIFY:
1296         if ((wParam16 == WM_CREATE) || (wParam16 == WM_DESTROY))
1297         {
1298             *pwparam32 = MAKEWPARAM( wParam16, HIWORD(*plparam) );
1299             *plparam   = (LPARAM)WIN_Handle32( LOWORD(*plparam) );
1300         }
1301         return 0;
1302     case WM_WINDOWPOSCHANGING:
1303     case WM_WINDOWPOSCHANGED:
1304         {
1305             WINDOWPOS *wp = (WINDOWPOS *)HeapAlloc( GetProcessHeap(), 0,
1306                                                 sizeof(*wp) + sizeof(LPARAM) );
1307             if (!wp) return -1;
1308             STRUCT32_WINDOWPOS16to32( MapSL(*plparam), wp );
1309             *(LPARAM *)(wp + 1) = *plparam;  /* Store the previous lParam */
1310             *plparam = (LPARAM)wp;
1311         }
1312         return 1;
1313     case WM_GETDLGCODE:
1314         if (*plparam)
1315         {
1316             LPMSG16 msg16 = MapSL(*plparam);
1317             LPMSG msg32 = (LPMSG)HeapAlloc( GetProcessHeap(), 0, sizeof(MSG) );
1318
1319             if (!msg32) return -1;
1320             msg32->hwnd = WIN_Handle32( msg16->hwnd );
1321             msg32->lParam = msg16->lParam;
1322             msg32->time = msg16->time;
1323             CONV_POINT16TO32(&msg16->pt,&msg32->pt);
1324             /* this is right, right? */
1325             if (WINPROC_MapMsg16To32A( msg32->hwnd, msg16->message,msg16->wParam,
1326                                      &msg32->message,&msg32->wParam,
1327                                      &msg32->lParam)<0) {
1328                 HeapFree( GetProcessHeap(), 0, msg32 );
1329                 return -1;
1330             }
1331             *plparam = (LPARAM)msg32;
1332             return 1;
1333         }
1334         else return 0;
1335     case WM_NOTIFY:
1336         *plparam = (LPARAM)MapSL(*plparam);
1337         return 0;
1338     case WM_ACTIVATEAPP:
1339         /* We need this when SetActiveWindow sends a Sendmessage16() to
1340          * a 32bit window. Might be superflous with 32bit interprocess
1341          * message queues. */
1342         if (*plparam) *plparam = HTASK_32( *plparam );
1343         return 0;
1344     case WM_NEXTMENU:
1345         {
1346             MDINEXTMENU *next = HeapAlloc( GetProcessHeap(), 0, sizeof(*next) );
1347             if (!next) return -1;
1348             next->hmenuIn = *plparam;
1349             next->hmenuNext = 0;
1350             next->hwndNext = 0;
1351             *plparam = (LPARAM)next;
1352             return 1;
1353         }
1354     case WM_PAINTCLIPBOARD:
1355     case WM_SIZECLIPBOARD:
1356         FIXME_(msg)("message %04x needs translation\n",msg16 );
1357         return -1;
1358     case WM_DDE_INITIATE:
1359     case WM_DDE_TERMINATE:
1360     case WM_DDE_UNADVISE:
1361     case WM_DDE_REQUEST:
1362         *pwparam32 = (WPARAM)WIN_Handle32(wParam16);
1363         return 0;
1364     case WM_DDE_ADVISE:
1365     case WM_DDE_DATA:
1366     case WM_DDE_POKE:
1367         {
1368             HANDLE16    lo16;
1369             ATOM        hi;
1370             HANDLE      lo32 = 0;
1371
1372             *pwparam32 = (WPARAM)WIN_Handle32(wParam16);
1373             lo16 = LOWORD(*plparam);
1374             hi = HIWORD(*plparam);
1375             if (lo16 && !(lo32 = convert_handle_16_to_32(lo16, GMEM_DDESHARE)))
1376                 return -1;
1377             *plparam = PackDDElParam(msg16, lo32, hi);
1378         }
1379         return 0; /* FIXME don't know how to free allocated memory (handle)  !! */
1380     case WM_DDE_ACK:
1381         {
1382             UINT        lo, hi;
1383             int         flag = 0;
1384             char        buf[2];
1385
1386             *pwparam32 = (WPARAM)WIN_Handle32(wParam16);
1387
1388             lo = LOWORD(*plparam);
1389             hi = HIWORD(*plparam);
1390
1391             if (GlobalGetAtomNameA(hi, buf, 2) > 0) flag |= 1;
1392             if (GlobalSize16(hi) != 0) flag |= 2;
1393             switch (flag)
1394             {
1395             case 0:
1396                 if (hi)
1397                 {
1398                     MESSAGE("DDE_ACK: neither atom nor handle!!!\n");
1399                     hi = 0;
1400                 }
1401                 break;
1402             case 1:
1403                 break; /* atom, nothing to do */
1404             case 3:
1405                 MESSAGE("DDE_ACK: %x both atom and handle... choosing handle\n", hi);
1406                 /* fall thru */
1407             case 2:
1408                 hi = convert_handle_16_to_32(hi, GMEM_DDESHARE);
1409                 break;
1410             }
1411             *plparam = PackDDElParam(WM_DDE_ACK, lo, hi);
1412         }
1413         return 0; /* FIXME don't know how to free allocated memory (handle) !! */
1414     case WM_DDE_EXECUTE:
1415         *plparam = convert_handle_16_to_32(*plparam, GMEM_DDESHARE);
1416         return 0; /* FIXME don't know how to free allocated memory (handle) !! */
1417     default:  /* No translation needed */
1418         return 0;
1419     }
1420 }
1421
1422
1423 /**********************************************************************
1424  *           WINPROC_UnmapMsg16To32A
1425  *
1426  * Unmap a message that was mapped from 16- to 32-bit Ansi.
1427  */
1428 LRESULT WINPROC_UnmapMsg16To32A( HWND hwnd, UINT msg, WPARAM wParam, LPARAM lParam,
1429                                  LRESULT result )
1430 {
1431     switch(msg)
1432     {
1433     case WM_COMPAREITEM:
1434     case WM_DELETEITEM:
1435     case WM_DRAWITEM:
1436         HeapFree( GetProcessHeap(), 0, (LPVOID)lParam );
1437         break;
1438     case WM_MEASUREITEM:
1439         {
1440             MEASUREITEMSTRUCT16 *mis16;
1441             MEASUREITEMSTRUCT *mis = (MEASUREITEMSTRUCT *)lParam;
1442             lParam = *(LPARAM *)(mis + 1);
1443             mis16 = MapSL(lParam);
1444             mis16->itemWidth  = (UINT16)mis->itemWidth;
1445             mis16->itemHeight = (UINT16)mis->itemHeight;
1446             HeapFree( GetProcessHeap(), 0, mis );
1447         }
1448         break;
1449     case WM_GETMINMAXINFO:
1450         {
1451             MINMAXINFO *mmi = (MINMAXINFO *)lParam;
1452             lParam = *(LPARAM *)(mmi + 1);
1453             STRUCT32_MINMAXINFO32to16( mmi, MapSL(lParam));
1454             HeapFree( GetProcessHeap(), 0, mmi );
1455         }
1456         break;
1457     case WM_MDICREATE:
1458         {
1459             MDICREATESTRUCTA *cs = (MDICREATESTRUCTA *)lParam;
1460             lParam = *(LPARAM *)(cs + 1);
1461             STRUCT32_MDICREATESTRUCT32Ato16( cs, MapSL(lParam) );
1462             HeapFree( GetProcessHeap(), 0, cs );
1463         }
1464         break;
1465     case WM_MDIGETACTIVE:
1466         result = MAKELONG( LOWORD(result), (BOOL16)(*(BOOL *)lParam) );
1467         HeapFree( GetProcessHeap(), 0, (BOOL *)lParam );
1468         break;
1469     case WM_NCCALCSIZE:
1470         {
1471             NCCALCSIZE_PARAMS16 *nc16;
1472             NCCALCSIZE_PARAMS *nc = (NCCALCSIZE_PARAMS *)lParam;
1473             lParam = *(LPARAM *)(nc + 1);
1474             nc16 = MapSL(lParam);
1475             CONV_RECT32TO16( &nc->rgrc[0], &nc16->rgrc[0] );
1476             if (wParam)
1477             {
1478                 CONV_RECT32TO16( &nc->rgrc[1], &nc16->rgrc[1] );
1479                 CONV_RECT32TO16( &nc->rgrc[2], &nc16->rgrc[2] );
1480                 if (nc->lppos)
1481                 {
1482                     STRUCT32_WINDOWPOS32to16( nc->lppos, MapSL(nc16->lppos));
1483                     HeapFree( GetProcessHeap(), 0, nc->lppos );
1484                 }
1485             }
1486             HeapFree( GetProcessHeap(), 0, nc );
1487         }
1488         break;
1489     case WM_NCCREATE:
1490     case WM_CREATE:
1491         {
1492             CREATESTRUCTA *cs = (CREATESTRUCTA *)lParam;
1493             lParam = *(LPARAM *)(cs + 1);
1494             STRUCT32_CREATESTRUCT32Ato16( cs, MapSL(lParam) );
1495             HeapFree( GetProcessHeap(), 0, cs );
1496         }
1497         break;
1498     case WM_WINDOWPOSCHANGING:
1499     case WM_WINDOWPOSCHANGED:
1500         {
1501             WINDOWPOS *wp = (WINDOWPOS *)lParam;
1502             lParam = *(LPARAM *)(wp + 1);
1503             STRUCT32_WINDOWPOS32to16(wp, MapSL(lParam));
1504             HeapFree( GetProcessHeap(), 0, wp );
1505         }
1506         break;
1507     case WM_GETDLGCODE:
1508         if (lParam)
1509         {
1510             LPMSG msg32 = (LPMSG)lParam;
1511
1512             WINPROC_UnmapMsg16To32A( hwnd, msg32->message, msg32->wParam, msg32->lParam,
1513                                      result);
1514             HeapFree( GetProcessHeap(), 0, msg32 );
1515         }
1516         break;
1517     case WM_NEXTMENU:
1518         {
1519             MDINEXTMENU *next = (MDINEXTMENU *)lParam;
1520             result = MAKELONG( HMENU_16(next->hmenuNext), HWND_16(next->hwndNext) );
1521             HeapFree( GetProcessHeap(), 0, next );
1522         }
1523         break;
1524     }
1525     return result;
1526 }
1527
1528
1529 /**********************************************************************
1530  *           WINPROC_MapMsg16To32W
1531  *
1532  * Map a message from 16- to 32-bit Unicode.
1533  * Return value is -1 on error, 0 if OK, 1 if an UnmapMsg call is needed.
1534  */
1535 INT WINPROC_MapMsg16To32W( HWND hwnd, UINT16 msg16, WPARAM16 wParam16, UINT *pmsg32,
1536                            WPARAM *pwparam32, LPARAM *plparam )
1537 {
1538     BYTE ch;
1539     WCHAR wch;
1540
1541     *pmsg32=(UINT)msg16;
1542     *pwparam32 = (WPARAM)wParam16;
1543     switch(msg16)
1544     {
1545     case WM_GETTEXT:
1546     case WM_SETTEXT:
1547     case WM_WININICHANGE:
1548     case WM_DEVMODECHANGE:
1549     case WM_ASKCBFORMATNAME:
1550         *plparam = (LPARAM)MapSL(*plparam);
1551         return WINPROC_MapMsg32ATo32W( hwnd, *pmsg32, pwparam32, plparam );
1552     case WM_GETTEXTLENGTH:
1553     case CB_GETLBTEXTLEN:
1554     case LB_GETTEXTLEN:
1555         return 1;  /* need to map result */
1556     case WM_NCCREATE:
1557     case WM_CREATE:
1558         {
1559             CREATESTRUCT16 *cs16 = MapSL(*plparam);
1560             CREATESTRUCTW *cs = (CREATESTRUCTW *)HeapAlloc( GetProcessHeap(), 0,
1561                                                 sizeof(*cs) + sizeof(LPARAM) );
1562             if (!cs) return -1;
1563             STRUCT32_CREATESTRUCT16to32A( cs16, (CREATESTRUCTA *)cs );
1564             cs->lpszName  = map_str_16_to_32W(cs16->lpszName);
1565             cs->lpszClass = map_str_16_to_32W(cs16->lpszClass);
1566             *(LPARAM *)(cs + 1) = *plparam;  /* Store the previous lParam */
1567             *plparam = (LPARAM)cs;
1568         }
1569         return 1;
1570     case WM_MDICREATE:
1571         {
1572             MDICREATESTRUCT16 *cs16 = MapSL(*plparam);
1573             MDICREATESTRUCTW *cs =
1574                 (MDICREATESTRUCTW *)HeapAlloc( GetProcessHeap(), 0,
1575                                                 sizeof(*cs) + sizeof(LPARAM) );
1576             if (!cs) return -1;
1577             STRUCT32_MDICREATESTRUCT16to32A( cs16, (MDICREATESTRUCTA *)cs );
1578             cs->szTitle = map_str_16_to_32W(cs16->szTitle);
1579             cs->szClass = map_str_16_to_32W(cs16->szClass);
1580             *(LPARAM *)(cs + 1) = *plparam;  /* Store the previous lParam */
1581             *plparam = (LPARAM)cs;
1582         }
1583         return 1;
1584     case WM_GETDLGCODE:
1585         if (*plparam)
1586         {
1587             LPMSG16 msg16 = MapSL(*plparam);
1588             LPMSG msg32 = (LPMSG)HeapAlloc( GetProcessHeap(), 0, sizeof(MSG) );
1589
1590             if (!msg32) return -1;
1591             msg32->hwnd = WIN_Handle32( msg16->hwnd );
1592             msg32->lParam = msg16->lParam;
1593             msg32->time = msg16->time;
1594             CONV_POINT16TO32(&msg16->pt,&msg32->pt);
1595             /* this is right, right? */
1596             if (WINPROC_MapMsg16To32W(hwnd, msg16->message,msg16->wParam,
1597                                      &msg32->message,&msg32->wParam,
1598                                      &msg32->lParam)<0) {
1599                 HeapFree( GetProcessHeap(), 0, msg32 );
1600                 return -1;
1601             }
1602             *plparam = (LPARAM)msg32;
1603             return 1;
1604         }
1605         else return 0;
1606
1607     case WM_CHARTOITEM:
1608         ch = wParam16;
1609         MultiByteToWideChar( CP_ACP, 0, &ch, 1, &wch, 1);
1610         *pwparam32 = MAKEWPARAM( wch, HIWORD(*plparam) );
1611         *plparam   = (LPARAM)WIN_Handle32( LOWORD(*plparam) );
1612         return 0;
1613     case WM_MENUCHAR:
1614         ch = wParam16;
1615         MultiByteToWideChar( CP_ACP, 0, &ch, 1, &wch, 1);
1616         *pwparam32 = MAKEWPARAM( wch, LOWORD(*plparam) );
1617         *plparam   = (LPARAM)HMENU_32(HIWORD(*plparam));
1618         return 0;
1619     case WM_CHAR:
1620     case WM_DEADCHAR:
1621     case WM_SYSCHAR:
1622     case WM_SYSDEADCHAR:
1623         ch = wParam16;
1624         MultiByteToWideChar( CP_ACP, 0, &ch, 1, &wch, 1);
1625         *pwparam32 = wch;
1626         return 0;
1627
1628     default:  /* No Unicode translation needed */
1629         return WINPROC_MapMsg16To32A( hwnd, msg16, wParam16, pmsg32,
1630                                       pwparam32, plparam );
1631     }
1632 }
1633
1634
1635 /**********************************************************************
1636  *           WINPROC_UnmapMsg16To32W
1637  *
1638  * Unmap a message that was mapped from 16- to 32-bit Unicode.
1639  */
1640 LRESULT WINPROC_UnmapMsg16To32W( HWND hwnd, UINT msg, WPARAM wParam, LPARAM lParam,
1641                                  LRESULT result )
1642 {
1643     switch(msg)
1644     {
1645     case WM_GETTEXT:
1646     case WM_SETTEXT:
1647     case WM_GETTEXTLENGTH:
1648     case CB_GETLBTEXTLEN:
1649     case LB_GETTEXTLEN:
1650     case WM_ASKCBFORMATNAME:
1651         return WINPROC_UnmapMsg32ATo32W( hwnd, msg, wParam, lParam, result );
1652     case WM_NCCREATE:
1653     case WM_CREATE:
1654         {
1655             CREATESTRUCTW *cs = (CREATESTRUCTW *)lParam;
1656             lParam = *(LPARAM *)(cs + 1);
1657             STRUCT32_CREATESTRUCT32Ato16( (CREATESTRUCTA *)cs, MapSL(lParam) );
1658             unmap_str_16_to_32W( cs->lpszName );
1659             unmap_str_16_to_32W( cs->lpszClass );
1660             HeapFree( GetProcessHeap(), 0, cs );
1661         }
1662         break;
1663     case WM_MDICREATE:
1664         {
1665             MDICREATESTRUCTW *cs = (MDICREATESTRUCTW *)lParam;
1666             lParam = *(LPARAM *)(cs + 1);
1667             STRUCT32_MDICREATESTRUCT32Ato16( (MDICREATESTRUCTA *)cs, MapSL(lParam) );
1668             unmap_str_16_to_32W( cs->szTitle );
1669             unmap_str_16_to_32W( cs->szClass );
1670             HeapFree( GetProcessHeap(), 0, cs );
1671         }
1672         break;
1673     case WM_GETDLGCODE:
1674         if (lParam)
1675         {
1676             LPMSG msg32 = (LPMSG)lParam;
1677
1678             WINPROC_UnmapMsg16To32W( hwnd, msg32->message, msg32->wParam, msg32->lParam,
1679                                      result);
1680             HeapFree( GetProcessHeap(), 0, msg32 );
1681         }
1682         break;
1683     default:
1684         return WINPROC_UnmapMsg16To32A( hwnd, msg, wParam, lParam, result );
1685     }
1686     return result;
1687 }
1688
1689 static HANDLE16 convert_handle_32_to_16(HANDLE src, unsigned int flags)
1690 {
1691     HANDLE16    dst;
1692     UINT        sz = GlobalSize(src);
1693     LPSTR       ptr16, ptr32;
1694
1695     if (!(dst = GlobalAlloc16(flags, sz)))
1696         return 0;
1697     ptr32 = GlobalLock(src);
1698     ptr16 = GlobalLock16(dst);
1699     if (ptr16 != NULL && ptr32 != NULL) memcpy(ptr16, ptr32, sz);
1700     GlobalUnlock(src);
1701     GlobalUnlock16(dst);
1702
1703     return dst;
1704 }
1705
1706
1707 /**********************************************************************
1708  *           WINPROC_MapMsg32ATo16
1709  *
1710  * Map a message from 32-bit Ansi to 16-bit.
1711  * Return value is -1 on error, 0 if OK, 1 if an UnmapMsg call is needed.
1712  */
1713 INT WINPROC_MapMsg32ATo16( HWND hwnd, UINT msg32, WPARAM wParam32,
1714                              UINT16 *pmsg16, WPARAM16 *pwparam16,
1715                              LPARAM *plparam )
1716 {
1717     *pmsg16 = (UINT16)msg32;
1718     *pwparam16 = (WPARAM16)LOWORD(wParam32);
1719     switch(msg32)
1720     {
1721     case BM_GETCHECK:
1722     case BM_SETCHECK:
1723     case BM_GETSTATE:
1724     case BM_SETSTATE:
1725     case BM_SETSTYLE:
1726         *pmsg16 = (UINT16)msg32 + (BM_GETCHECK16 - BM_GETCHECK);
1727         return 0;
1728
1729     case EM_GETSEL:
1730     case EM_GETRECT:
1731     case EM_SETRECT:
1732     case EM_SETRECTNP:
1733     case EM_SCROLL:
1734     case EM_LINESCROLL:
1735     case EM_SCROLLCARET:
1736     case EM_GETMODIFY:
1737     case EM_SETMODIFY:
1738     case EM_GETLINECOUNT:
1739     case EM_LINEINDEX:
1740     case EM_SETHANDLE:
1741     case EM_GETHANDLE:
1742     case EM_GETTHUMB:
1743     case EM_LINELENGTH:
1744     case EM_REPLACESEL:
1745     case EM_GETLINE:
1746     case EM_LIMITTEXT:
1747     case EM_CANUNDO:
1748     case EM_UNDO:
1749     case EM_FMTLINES:
1750     case EM_LINEFROMCHAR:
1751     case EM_SETTABSTOPS:
1752     case EM_SETPASSWORDCHAR:
1753     case EM_EMPTYUNDOBUFFER:
1754     case EM_GETFIRSTVISIBLELINE:
1755     case EM_SETREADONLY:
1756     case EM_SETWORDBREAKPROC:
1757     case EM_GETWORDBREAKPROC:
1758     case EM_GETPASSWORDCHAR:
1759         *pmsg16 = (UINT16)msg32 + (EM_GETSEL16 - EM_GETSEL);
1760         return 0;
1761
1762     case LB_CARETOFF:
1763     case LB_CARETON:
1764     case LB_DELETESTRING:
1765     case LB_GETANCHORINDEX:
1766     case LB_GETCARETINDEX:
1767     case LB_GETCOUNT:
1768     case LB_GETCURSEL:
1769     case LB_GETHORIZONTALEXTENT:
1770     case LB_GETITEMDATA:
1771     case LB_GETITEMHEIGHT:
1772     case LB_GETSEL:
1773     case LB_GETSELCOUNT:
1774     case LB_GETTEXTLEN:
1775     case LB_GETTOPINDEX:
1776     case LB_RESETCONTENT:
1777     case LB_SELITEMRANGE:
1778     case LB_SELITEMRANGEEX:
1779     case LB_SETANCHORINDEX:
1780     case LB_SETCARETINDEX:
1781     case LB_SETCOLUMNWIDTH:
1782     case LB_SETCURSEL:
1783     case LB_SETHORIZONTALEXTENT:
1784     case LB_SETITEMDATA:
1785     case LB_SETITEMHEIGHT:
1786     case LB_SETSEL:
1787     case LB_SETTOPINDEX:
1788         *pmsg16 = (UINT16)msg32 + (LB_ADDSTRING16 - LB_ADDSTRING);
1789         return 0;
1790     case CB_DELETESTRING:
1791     case CB_GETCOUNT:
1792     case CB_GETLBTEXTLEN:
1793     case CB_LIMITTEXT:
1794     case CB_RESETCONTENT:
1795     case CB_SETEDITSEL:
1796     case CB_GETCURSEL:
1797     case CB_SETCURSEL:
1798     case CB_SHOWDROPDOWN:
1799     case CB_SETITEMDATA:
1800     case CB_SETITEMHEIGHT:
1801     case CB_GETITEMHEIGHT:
1802     case CB_SETEXTENDEDUI:
1803     case CB_GETEXTENDEDUI:
1804     case CB_GETDROPPEDSTATE:
1805         *pmsg16 = (UINT16)msg32 + (CB_GETEDITSEL16 - CB_GETEDITSEL);
1806         return 0;
1807     case CB_GETEDITSEL:
1808         *pmsg16 = CB_GETEDITSEL16;
1809         return 1;
1810
1811     case LB_ADDSTRING:
1812     case LB_FINDSTRING:
1813     case LB_FINDSTRINGEXACT:
1814     case LB_INSERTSTRING:
1815     case LB_SELECTSTRING:
1816     case LB_DIR:
1817     case LB_ADDFILE:
1818         *plparam = (LPARAM)MapLS( (LPSTR)*plparam );
1819         *pmsg16 = (UINT16)msg32 + (LB_ADDSTRING16 - LB_ADDSTRING);
1820         return 1;
1821
1822     case CB_ADDSTRING:
1823     case CB_FINDSTRING:
1824     case CB_FINDSTRINGEXACT:
1825     case CB_INSERTSTRING:
1826     case CB_SELECTSTRING:
1827     case CB_DIR:
1828         *plparam = (LPARAM)MapLS( (LPSTR)*plparam );
1829         *pmsg16 = (UINT16)msg32 + (CB_GETEDITSEL16 - CB_GETEDITSEL);
1830         return 1;
1831
1832     case LB_GETITEMRECT:
1833         {
1834             RECT16 *rect = HeapAlloc( GetProcessHeap(), 0, sizeof(RECT16) + sizeof(LPARAM) );
1835             if (!rect) return -1;
1836             *(LPARAM *)(rect + 1) = *plparam;  /* Store the previous lParam */
1837             *plparam = MapLS( rect );
1838         }
1839         *pmsg16 = LB_GETITEMRECT16;
1840         return 1;
1841     case LB_GETSELITEMS:
1842         {
1843             LPINT16 items;
1844             *pwparam16 = (WPARAM16)min( wParam32, 0x7f80 ); /* Must be < 64K */
1845             if (!(items = HeapAlloc( GetProcessHeap(), 0,
1846                                      *pwparam16 * sizeof(INT16) + sizeof(LPARAM)))) return -1;
1847             *((LPARAM *)items)++ = *plparam;  /* Store the previous lParam */
1848             *plparam = MapLS( items );
1849         }
1850         *pmsg16 = LB_GETSELITEMS16;
1851         return 1;
1852     case LB_SETTABSTOPS:
1853         if (wParam32)
1854         {
1855             INT i;
1856             LPINT16 stops;
1857             *pwparam16 = (WPARAM16)min( wParam32, 0x7f80 ); /* Must be < 64K */
1858             if (!(stops = HeapAlloc( GetProcessHeap(), 0,
1859                                      *pwparam16 * sizeof(INT16) + sizeof(LPARAM)))) return -1;
1860             for (i = 0; i < *pwparam16; i++) stops[i] = *((LPINT)*plparam+i);
1861             *plparam = MapLS( stops );
1862             return 1;
1863         }
1864         *pmsg16 = LB_SETTABSTOPS16;
1865         return 0;
1866
1867     case CB_GETDROPPEDCONTROLRECT:
1868         {
1869             RECT16 *rect = HeapAlloc( GetProcessHeap(), 0, sizeof(RECT16) + sizeof(LPARAM) );
1870             if (!rect) return -1;
1871             *(LPARAM *)(rect + 1) = *plparam;  /* Store the previous lParam */
1872             *plparam = (LPARAM)MapLS(rect);
1873         }
1874         *pmsg16 = CB_GETDROPPEDCONTROLRECT16;
1875         return 1;
1876
1877     case LB_GETTEXT:
1878         *plparam = (LPARAM)MapLS( (LPVOID)(*plparam) );
1879         *pmsg16 = LB_GETTEXT16;
1880         return 1;
1881
1882     case CB_GETLBTEXT:
1883         *plparam = (LPARAM)MapLS( (LPVOID)(*plparam) );
1884         *pmsg16 = CB_GETLBTEXT16;
1885         return 1;
1886
1887     case EM_SETSEL:
1888         *pwparam16 = 0;
1889         *plparam = MAKELONG( (INT16)(INT)wParam32, (INT16)*plparam );
1890         *pmsg16 = EM_SETSEL16;
1891         return 0;
1892
1893     case WM_ACTIVATE:
1894     case WM_CHARTOITEM:
1895     case WM_COMMAND:
1896     case WM_VKEYTOITEM:
1897         *plparam = MAKELPARAM( (HWND16)*plparam, HIWORD(wParam32) );
1898         return 0;
1899     case WM_HSCROLL:
1900     case WM_VSCROLL:
1901         *plparam = MAKELPARAM( HIWORD(wParam32), (HWND16)*plparam );
1902         return 0;
1903     case WM_CTLCOLORMSGBOX:
1904     case WM_CTLCOLOREDIT:
1905     case WM_CTLCOLORLISTBOX:
1906     case WM_CTLCOLORBTN:
1907     case WM_CTLCOLORDLG:
1908     case WM_CTLCOLORSCROLLBAR:
1909     case WM_CTLCOLORSTATIC:
1910         *pmsg16  = WM_CTLCOLOR;
1911         *plparam = MAKELPARAM( (HWND16)*plparam,
1912                                (WORD)msg32 - WM_CTLCOLORMSGBOX );
1913         return 0;
1914     case WM_COMPAREITEM:
1915         {
1916             COMPAREITEMSTRUCT *cis32 = (COMPAREITEMSTRUCT *)*plparam;
1917             COMPAREITEMSTRUCT16 *cis = HeapAlloc( GetProcessHeap(), 0, sizeof(COMPAREITEMSTRUCT16));
1918             if (!cis) return -1;
1919             cis->CtlType    = (UINT16)cis32->CtlType;
1920             cis->CtlID      = (UINT16)cis32->CtlID;
1921             cis->hwndItem   = HWND_16( cis32->hwndItem );
1922             cis->itemID1    = (UINT16)cis32->itemID1;
1923             cis->itemData1  = cis32->itemData1;
1924             cis->itemID2    = (UINT16)cis32->itemID2;
1925             cis->itemData2  = cis32->itemData2;
1926             *plparam = MapLS( cis );
1927         }
1928         return 1;
1929     case WM_DELETEITEM:
1930         {
1931             DELETEITEMSTRUCT *dis32 = (DELETEITEMSTRUCT *)*plparam;
1932             DELETEITEMSTRUCT16 *dis = HeapAlloc( GetProcessHeap(), 0, sizeof(DELETEITEMSTRUCT16) );
1933             if (!dis) return -1;
1934             dis->CtlType  = (UINT16)dis32->CtlType;
1935             dis->CtlID    = (UINT16)dis32->CtlID;
1936             dis->itemID   = (UINT16)dis32->itemID;
1937             dis->hwndItem = (dis->CtlType == ODT_MENU) ? (HWND16)LOWORD(dis32->hwndItem)
1938                                                        : HWND_16( dis32->hwndItem );
1939             dis->itemData = dis32->itemData;
1940             *plparam = MapLS( dis );
1941         }
1942         return 1;
1943     case WM_DRAWITEM:
1944         {
1945             DRAWITEMSTRUCT *dis32 = (DRAWITEMSTRUCT *)*plparam;
1946             DRAWITEMSTRUCT16 *dis = HeapAlloc( GetProcessHeap(), 0, sizeof(DRAWITEMSTRUCT16) );
1947             if (!dis) return -1;
1948             dis->CtlType    = (UINT16)dis32->CtlType;
1949             dis->CtlID      = (UINT16)dis32->CtlID;
1950             dis->itemID     = (UINT16)dis32->itemID;
1951             dis->itemAction = (UINT16)dis32->itemAction;
1952             dis->itemState  = (UINT16)dis32->itemState;
1953             dis->hwndItem   = HWND_16( dis32->hwndItem );
1954             dis->hDC        = HDC_16(dis32->hDC);
1955             dis->itemData   = dis32->itemData;
1956             CONV_RECT32TO16( &dis32->rcItem, &dis->rcItem );
1957             *plparam = MapLS( dis );
1958         }
1959         return 1;
1960     case WM_MEASUREITEM:
1961         {
1962             MEASUREITEMSTRUCT *mis32 = (MEASUREITEMSTRUCT *)*plparam;
1963             MEASUREITEMSTRUCT16 *mis = HeapAlloc( GetProcessHeap(), 0, sizeof(*mis)+sizeof(LPARAM));
1964             if (!mis) return -1;
1965             mis->CtlType    = (UINT16)mis32->CtlType;
1966             mis->CtlID      = (UINT16)mis32->CtlID;
1967             mis->itemID     = (UINT16)mis32->itemID;
1968             mis->itemWidth  = (UINT16)mis32->itemWidth;
1969             mis->itemHeight = (UINT16)mis32->itemHeight;
1970             mis->itemData   = mis32->itemData;
1971             *(LPARAM *)(mis + 1) = *plparam;  /* Store the previous lParam */
1972             *plparam = MapLS( mis );
1973         }
1974         return 1;
1975     case WM_GETMINMAXINFO:
1976         {
1977             MINMAXINFO16 *mmi = HeapAlloc( GetProcessHeap(), 0, sizeof(*mmi) + sizeof(LPARAM) );
1978             if (!mmi) return -1;
1979             STRUCT32_MINMAXINFO32to16( (MINMAXINFO *)*plparam, mmi );
1980             *(LPARAM *)(mmi + 1) = *plparam;  /* Store the previous lParam */
1981             *plparam = MapLS( mmi );
1982         }
1983         return 1;
1984     case WM_GETTEXT:
1985     case WM_ASKCBFORMATNAME:
1986         {
1987             LPSTR str;
1988             *pwparam16 = (WPARAM16)min( wParam32, 0xff80 ); /* Must be < 64K */
1989             if (!(str = HeapAlloc( GetProcessHeap(), 0, *pwparam16 + sizeof(LPARAM)))) return -1;
1990             *((LPARAM *)str)++ = *plparam;  /* Store the previous lParam */
1991             *plparam = MapLS( str );
1992         }
1993         return 1;
1994     case WM_MDICREATE:
1995         {
1996             MDICREATESTRUCT16 *cs;
1997             MDICREATESTRUCTA *cs32 = (MDICREATESTRUCTA *)*plparam;
1998
1999             if (!(cs = HeapAlloc( GetProcessHeap(), 0, sizeof(MDICREATESTRUCT16) ))) return -1;
2000             STRUCT32_MDICREATESTRUCT32Ato16( cs32, cs );
2001             cs->szTitle = MapLS( cs32->szTitle );
2002             cs->szClass = MapLS( cs32->szClass );
2003             *plparam = MapLS( cs );
2004         }
2005         return 1;
2006     case WM_MDIGETACTIVE:
2007         return 1;
2008     case WM_MDISETMENU:
2009         *plparam   = MAKELPARAM( (HMENU16)LOWORD(wParam32),
2010                                  (HMENU16)LOWORD(*plparam) );
2011         *pwparam16 = (*plparam == 0);
2012         return 0;
2013     case WM_MENUSELECT:
2014         if(HIWORD(wParam32) & MF_POPUP)
2015         {
2016             UINT16 hmenu;
2017             if (((UINT)HIWORD(wParam32) != 0xFFFF) || (*plparam))
2018             {
2019                 if((hmenu = GetSubMenu((HMENU16)*plparam, *pwparam16)))
2020                     *pwparam16=hmenu;
2021             }
2022         }
2023         /* fall through */
2024     case WM_MENUCHAR:
2025         *plparam = MAKELPARAM( HIWORD(wParam32), (HMENU16)*plparam );
2026         return 0;
2027     case WM_MDIACTIVATE:
2028         if (GetWindowLongA( hwnd, GWL_EXSTYLE ) & WS_EX_MDICHILD)
2029         {
2030             *pwparam16 = ((HWND)*plparam == hwnd);
2031             *plparam = MAKELPARAM( (HWND16)LOWORD(*plparam),
2032                                    (HWND16)LOWORD(wParam32) );
2033         }
2034         else
2035         {
2036             *pwparam16 = HWND_16( (HWND)wParam32 );
2037             *plparam = 0;
2038         }
2039         return 0;
2040     case WM_NCCALCSIZE:
2041         {
2042             NCCALCSIZE_PARAMS *nc32 = (NCCALCSIZE_PARAMS *)*plparam;
2043             NCCALCSIZE_PARAMS16 *nc = HeapAlloc( GetProcessHeap(), 0, sizeof(*nc) + sizeof(LPARAM));
2044             if (!nc) return -1;
2045
2046             CONV_RECT32TO16( &nc32->rgrc[0], &nc->rgrc[0] );
2047             if (wParam32)
2048             {
2049                 WINDOWPOS16 *wp;
2050                 CONV_RECT32TO16( &nc32->rgrc[1], &nc->rgrc[1] );
2051                 CONV_RECT32TO16( &nc32->rgrc[2], &nc->rgrc[2] );
2052                 if (!(wp = HeapAlloc( GetProcessHeap(), 0, sizeof(WINDOWPOS16) )))
2053                 {
2054                     HeapFree( GetProcessHeap(), 0, nc );
2055                     return -1;
2056                 }
2057                 STRUCT32_WINDOWPOS32to16( nc32->lppos, wp );
2058                 nc->lppos = MapLS( wp );
2059             }
2060             *(LPARAM *)(nc + 1) = *plparam;  /* Store the previous lParam */
2061             *plparam = MapLS( nc );
2062         }
2063         return 1;
2064     case WM_NCCREATE:
2065     case WM_CREATE:
2066         {
2067             CREATESTRUCT16 *cs;
2068             CREATESTRUCTA *cs32 = (CREATESTRUCTA *)*plparam;
2069
2070             if (!(cs = HeapAlloc( GetProcessHeap(), 0, sizeof(CREATESTRUCT16) ))) return -1;
2071             STRUCT32_CREATESTRUCT32Ato16( cs32, cs );
2072             cs->lpszName  = MapLS( cs32->lpszName );
2073             cs->lpszClass = MapLS( cs32->lpszClass );
2074             *plparam = MapLS( cs );
2075         }
2076         return 1;
2077     case WM_PARENTNOTIFY:
2078         if ((LOWORD(wParam32)==WM_CREATE) || (LOWORD(wParam32)==WM_DESTROY))
2079             *plparam = MAKELPARAM( (HWND16)*plparam, HIWORD(wParam32));
2080         /* else nothing to do */
2081         return 0;
2082     case WM_NOTIFY:
2083         *plparam = MapLS( (NMHDR *)*plparam ); /* NMHDR is already 32-bit */
2084         return 1;
2085     case WM_SETTEXT:
2086     case WM_WININICHANGE:
2087     case WM_DEVMODECHANGE:
2088         *plparam = MapLS( (LPSTR)*plparam );
2089         return 1;
2090     case WM_WINDOWPOSCHANGING:
2091     case WM_WINDOWPOSCHANGED:
2092         {
2093             WINDOWPOS16 *wp = HeapAlloc( GetProcessHeap(), 0, sizeof(*wp) + sizeof(LPARAM) );
2094             if (!wp) return -1;
2095             STRUCT32_WINDOWPOS32to16( (WINDOWPOS *)*plparam, wp );
2096             *(LPARAM *)(wp + 1) = *plparam;  /* Store the previous lParam */
2097             *plparam = MapLS( wp );
2098         }
2099         return 1;
2100     case WM_GETDLGCODE:
2101          if (*plparam) {
2102             LPMSG msg32 = (LPMSG) *plparam;
2103             LPMSG16 msg16 = HeapAlloc( GetProcessHeap(), 0, sizeof(MSG16) );
2104
2105             if (!msg16) return -1;
2106             msg16->hwnd = HWND_16( msg32->hwnd );
2107             msg16->lParam = msg32->lParam;
2108             msg16->time = msg32->time;
2109             CONV_POINT32TO16(&msg32->pt,&msg16->pt);
2110             /* this is right, right? */
2111             if (WINPROC_MapMsg32ATo16(msg32->hwnd,msg32->message,msg32->wParam,
2112                          &msg16->message,&msg16->wParam, &msg16->lParam)<0)
2113             {
2114                 HeapFree( GetProcessHeap(), 0, msg16 );
2115                 return -1;
2116             }
2117             *plparam = MapLS( msg16 );
2118             return 1;
2119         }
2120         return 0;
2121
2122     case WM_ACTIVATEAPP:
2123         if (*plparam) *plparam = HTASK_16( (HANDLE)*plparam );
2124         return 0;
2125     case WM_NEXTMENU:
2126         {
2127             MDINEXTMENU *next = (MDINEXTMENU *)*plparam;
2128             *plparam = next->hmenuIn;
2129             return 1;
2130         }
2131     case WM_PAINTCLIPBOARD:
2132     case WM_SIZECLIPBOARD:
2133         FIXME_(msg)("message %04x needs translation\n", msg32 );
2134         return -1;
2135     /* following messages should not be sent to 16-bit apps */
2136     case WM_SIZING:
2137     case WM_MOVING:
2138     case WM_CAPTURECHANGED:
2139     case WM_STYLECHANGING:
2140     case WM_STYLECHANGED:
2141         return -1;
2142     case WM_DDE_INITIATE:
2143     case WM_DDE_TERMINATE:
2144     case WM_DDE_UNADVISE:
2145     case WM_DDE_REQUEST:
2146         *pwparam16 = HWND_16((HWND)wParam32);
2147         return 0;
2148     case WM_DDE_ADVISE:
2149     case WM_DDE_DATA:
2150     case WM_DDE_POKE:
2151         {
2152             unsigned    lo32, hi;
2153             HANDLE16    lo16 = 0;
2154
2155             *pwparam16 = HWND_16((HWND)wParam32);
2156             UnpackDDElParam(msg32, *plparam, &lo32, &hi);
2157             if (lo32 && !(lo16 = convert_handle_32_to_16(lo32, GMEM_DDESHARE)))
2158                 return -1;
2159             *plparam = MAKELPARAM(lo16, hi);
2160         }
2161         return 0; /* FIXME don't know how to free allocated memory (handle)  !! */
2162     case WM_DDE_ACK:
2163         {
2164             UINT        lo, hi;
2165             int         flag = 0;
2166             char        buf[2];
2167
2168             *pwparam16 = HWND_16((HWND)wParam32);
2169
2170             UnpackDDElParam(msg32, *plparam, &lo, &hi);
2171
2172             if (GlobalGetAtomNameA((ATOM)hi, buf, sizeof(buf)) > 0) flag |= 1;
2173             if (GlobalSize(hi) != 0) flag |= 2;
2174             switch (flag)
2175             {
2176             case 0:
2177                 if (hi)
2178                 {
2179                     MESSAGE("DDE_ACK: neither atom nor handle!!!\n");
2180                     hi = 0;
2181                 }
2182                 break;
2183             case 1:
2184                 break; /* atom, nothing to do */
2185             case 3:
2186                 MESSAGE("DDE_ACK: %x both atom and handle... choosing handle\n", hi);
2187                 /* fall thru */
2188             case 2:
2189                 hi = convert_handle_32_to_16(hi, GMEM_DDESHARE);
2190                 break;
2191             }
2192             *plparam = MAKELPARAM(lo, hi);
2193         }
2194         return 0; /* FIXME don't know how to free allocated memory (handle) !! */
2195     case WM_DDE_EXECUTE:
2196         *plparam = convert_handle_32_to_16(*plparam, GMEM_DDESHARE);
2197         return 0; /* FIXME don't know how to free allocated memory (handle) !! */
2198     default:  /* No translation needed */
2199         return 0;
2200     }
2201 }
2202
2203
2204 /**********************************************************************
2205  *           WINPROC_UnmapMsg32ATo16
2206  *
2207  * Unmap a message that was mapped from 32-bit Ansi to 16-bit.
2208  */
2209 void WINPROC_UnmapMsg32ATo16( HWND hwnd, UINT msg, WPARAM wParam, LPARAM lParam,
2210                               MSGPARAM16* p16 )
2211 {
2212     switch(msg)
2213     {
2214     case LB_ADDFILE:
2215     case LB_ADDSTRING:
2216     case LB_DIR:
2217     case LB_FINDSTRING:
2218     case LB_FINDSTRINGEXACT:
2219     case LB_INSERTSTRING:
2220     case LB_SELECTSTRING:
2221     case LB_GETTEXT:
2222     case CB_ADDSTRING:
2223     case CB_FINDSTRING:
2224     case CB_FINDSTRINGEXACT:
2225     case CB_INSERTSTRING:
2226     case CB_SELECTSTRING:
2227     case CB_DIR:
2228     case CB_GETLBTEXT:
2229     case WM_SETTEXT:
2230     case WM_WININICHANGE:
2231     case WM_DEVMODECHANGE:
2232         UnMapLS( (SEGPTR)p16->lParam );
2233         break;
2234     case LB_SETTABSTOPS:
2235     case WM_COMPAREITEM:
2236     case WM_DELETEITEM:
2237     case WM_DRAWITEM:
2238         {
2239             void *ptr = MapSL( p16->lParam );
2240             UnMapLS( p16->lParam );
2241             HeapFree( GetProcessHeap(), 0, ptr );
2242         }
2243         break;
2244     case CB_GETDROPPEDCONTROLRECT:
2245     case LB_GETITEMRECT:
2246         {
2247             RECT16 *rect = MapSL(p16->lParam);
2248             UnMapLS( p16->lParam );
2249             p16->lParam = *(LPARAM *)(rect + 1);
2250             CONV_RECT16TO32( rect, (RECT *)(p16->lParam));
2251             HeapFree( GetProcessHeap(), 0, rect );
2252         }
2253         break;
2254     case LB_GETSELITEMS:
2255         {
2256             INT i;
2257             LPINT16 items = MapSL(p16->lParam);
2258             UnMapLS( p16->lParam );
2259             p16->lParam = *((LPARAM *)items - 1);
2260             for (i = 0; i < p16->wParam; i++) *((LPINT)(p16->lParam) + i) = items[i];
2261             HeapFree( GetProcessHeap(), 0, (LPARAM *)items - 1 );
2262         }
2263         break;
2264
2265     case CB_GETEDITSEL:
2266         if( wParam )
2267             *((PUINT)(wParam)) = LOWORD(p16->lResult);
2268         if( lParam )
2269             *((PUINT)(lParam)) = HIWORD(p16->lResult);  /* FIXME: substract 1? */
2270         break;
2271
2272     case WM_MEASUREITEM:
2273         {
2274             MEASUREITEMSTRUCT16 *mis = MapSL(p16->lParam);
2275             MEASUREITEMSTRUCT *mis32 = *(MEASUREITEMSTRUCT **)(mis + 1);
2276             mis32->itemWidth  = mis->itemWidth;
2277             mis32->itemHeight = mis->itemHeight;
2278             UnMapLS( p16->lParam );
2279             HeapFree( GetProcessHeap(), 0, mis );
2280         }
2281         break;
2282     case WM_GETMINMAXINFO:
2283         {
2284             MINMAXINFO16 *mmi = MapSL(p16->lParam);
2285             UnMapLS( p16->lParam );
2286             p16->lParam = *(LPARAM *)(mmi + 1);
2287             STRUCT32_MINMAXINFO16to32( mmi, (MINMAXINFO *)(p16->lParam) );
2288             HeapFree( GetProcessHeap(), 0, mmi );
2289         }
2290         break;
2291     case WM_GETTEXT:
2292     case WM_ASKCBFORMATNAME:
2293         {
2294             LPSTR str = MapSL(p16->lParam);
2295             UnMapLS( p16->lParam );
2296             p16->lParam = *((LPARAM *)str - 1);
2297             lstrcpynA( (LPSTR)(p16->lParam), str, p16->wParam );
2298             HeapFree( GetProcessHeap(), 0, (LPARAM *)str - 1 );
2299         }
2300         break;
2301     case WM_MDICREATE:
2302         {
2303             MDICREATESTRUCT16 *cs = MapSL(p16->lParam);
2304             UnMapLS( cs->szTitle );
2305             UnMapLS( cs->szClass );
2306             UnMapLS( p16->lParam );
2307             HeapFree( GetProcessHeap(), 0, cs );
2308         }
2309         break;
2310     case WM_MDIGETACTIVE:
2311         if (lParam) *(BOOL *)lParam = (BOOL16)HIWORD(p16->lResult);
2312         p16->lResult = (LRESULT)WIN_Handle32( LOWORD(p16->lResult) );
2313         break;
2314     case WM_NCCALCSIZE:
2315         {
2316             NCCALCSIZE_PARAMS *nc32;
2317             NCCALCSIZE_PARAMS16 *nc = MapSL(p16->lParam);
2318             UnMapLS( p16->lParam );
2319             p16->lParam = *(LPARAM *)(nc + 1);
2320             nc32 = (NCCALCSIZE_PARAMS *)(p16->lParam);
2321             CONV_RECT16TO32( &nc->rgrc[0], &nc32->rgrc[0] );
2322             if (p16->wParam)
2323             {
2324                 WINDOWPOS16 *pos = MapSL(nc->lppos);
2325                 UnMapLS( nc->lppos );
2326                 CONV_RECT16TO32( &nc->rgrc[1], &nc32->rgrc[1] );
2327                 CONV_RECT16TO32( &nc->rgrc[2], &nc32->rgrc[2] );
2328                 STRUCT32_WINDOWPOS16to32( pos, nc32->lppos );
2329                 HeapFree( GetProcessHeap(), 0, pos );
2330             }
2331             HeapFree( GetProcessHeap(), 0, nc );
2332         }
2333         break;
2334     case WM_NCCREATE:
2335     case WM_CREATE:
2336         {
2337             CREATESTRUCT16 *cs = MapSL(p16->lParam);
2338             UnMapLS( p16->lParam );
2339             UnMapLS( cs->lpszName );
2340             UnMapLS( cs->lpszClass );
2341             HeapFree( GetProcessHeap(), 0, cs );
2342         }
2343         break;
2344     case WM_WINDOWPOSCHANGING:
2345     case WM_WINDOWPOSCHANGED:
2346         {
2347             WINDOWPOS16 *wp = MapSL(p16->lParam);
2348             UnMapLS( p16->lParam );
2349             p16->lParam = *(LPARAM *)(wp + 1);
2350             STRUCT32_WINDOWPOS16to32( wp, (WINDOWPOS *)p16->lParam );
2351             HeapFree( GetProcessHeap(), 0, wp );
2352         }
2353         break;
2354     case WM_NOTIFY:
2355         UnMapLS(p16->lParam);
2356         break;
2357     case WM_GETDLGCODE:
2358         if (p16->lParam)
2359         {
2360             LPMSG16 msg16 = MapSL(p16->lParam);
2361             MSGPARAM16 msgp16;
2362             UnMapLS( p16->lParam );
2363             msgp16.wParam=msg16->wParam;
2364             msgp16.lParam=msg16->lParam;
2365             WINPROC_UnmapMsg32ATo16(((LPMSG)lParam)->hwnd, ((LPMSG)lParam)->message,
2366                     ((LPMSG)lParam)->wParam, ((LPMSG)lParam)->lParam,
2367                     &msgp16 );
2368             HeapFree( GetProcessHeap(), 0, msg16 );
2369         }
2370         break;
2371     case WM_NEXTMENU:
2372         {
2373             MDINEXTMENU *next = (MDINEXTMENU *)lParam;
2374             next->hmenuNext = LOWORD(p16->lResult);
2375             next->hwndNext = WIN_Handle32( HIWORD(p16->lResult) );
2376             p16->lResult = 0;
2377         }
2378         break;
2379     }
2380 }
2381
2382
2383 /**********************************************************************
2384  *           WINPROC_MapMsg32WTo16
2385  *
2386  * Map a message from 32-bit Unicode to 16-bit.
2387  * Return value is -1 on error, 0 if OK, 1 if an UnmapMsg call is needed.
2388  */
2389 INT WINPROC_MapMsg32WTo16( HWND hwnd, UINT msg32, WPARAM wParam32,
2390                              UINT16 *pmsg16, WPARAM16 *pwparam16,
2391                              LPARAM *plparam )
2392 {
2393     BYTE ch;
2394     WCHAR wch;
2395
2396     *pmsg16    = LOWORD(msg32);
2397     *pwparam16 = LOWORD(wParam32);
2398     switch(msg32)
2399     {
2400     case LB_ADDSTRING:
2401     case LB_FINDSTRING:
2402     case LB_FINDSTRINGEXACT:
2403     case LB_INSERTSTRING:
2404     case LB_SELECTSTRING:
2405     case LB_DIR:
2406     case LB_ADDFILE:
2407         *plparam = map_str_32W_to_16( (LPWSTR)*plparam );
2408         *pmsg16 = (UINT16)msg32 + (LB_ADDSTRING16 - LB_ADDSTRING);
2409         return 1;
2410
2411     case CB_ADDSTRING:
2412     case CB_FINDSTRING:
2413     case CB_FINDSTRINGEXACT:
2414     case CB_INSERTSTRING:
2415     case CB_SELECTSTRING:
2416     case CB_DIR:
2417         *plparam = map_str_32W_to_16( (LPWSTR)*plparam );
2418         *pmsg16 = (UINT16)msg32 + (CB_ADDSTRING16 - CB_ADDSTRING);
2419         return 1;
2420
2421     case WM_NCCREATE:
2422     case WM_CREATE:
2423         {
2424             CREATESTRUCT16 *cs;
2425             CREATESTRUCTW *cs32 = (CREATESTRUCTW *)*plparam;
2426
2427             if (!(cs = HeapAlloc( GetProcessHeap(), 0, sizeof(CREATESTRUCT16) ))) return -1;
2428             STRUCT32_CREATESTRUCT32Ato16( (CREATESTRUCTA *)cs32, cs );
2429             cs->lpszName  = map_str_32W_to_16( cs32->lpszName );
2430             cs->lpszClass = map_str_32W_to_16( cs32->lpszClass );
2431             *plparam   = MapLS(cs);
2432         }
2433         return 1;
2434     case WM_MDICREATE:
2435         {
2436             MDICREATESTRUCT16 *cs;
2437             MDICREATESTRUCTW *cs32 = (MDICREATESTRUCTW *)*plparam;
2438
2439             if (!(cs = HeapAlloc( GetProcessHeap(), 0, sizeof(MDICREATESTRUCT16) ))) return -1;
2440             STRUCT32_MDICREATESTRUCT32Ato16( (MDICREATESTRUCTA *)cs32, cs );
2441             cs->szTitle = map_str_32W_to_16( cs32->szTitle );
2442             cs->szClass = map_str_32W_to_16( cs32->szClass );
2443             *plparam   = MapLS(cs);
2444         }
2445         return 1;
2446     case WM_SETTEXT:
2447     case WM_WININICHANGE:
2448     case WM_DEVMODECHANGE:
2449         *plparam = map_str_32W_to_16( (LPWSTR)*plparam );
2450         return 1;
2451     case LB_GETTEXT:
2452     case CB_GETLBTEXT:
2453         if ( WINPROC_TestLBForStr( hwnd ))
2454         {
2455             LPSTR str = HeapAlloc( GetProcessHeap(), 0, 256 ); /* FIXME: fixed sized buffer */
2456             if (!str) return -1;
2457             *pmsg16    = (msg32 == LB_GETTEXT)? LB_GETTEXT16 : CB_GETLBTEXT16;
2458             *plparam   = (LPARAM)MapLS(str);
2459         }
2460         return 1;
2461
2462     case WM_CHARTOITEM:
2463         wch = LOWORD(wParam32);
2464         WideCharToMultiByte( CP_ACP, 0, &wch, 1, &ch, 1, NULL, NULL);
2465         *pwparam16 = ch;
2466         *plparam = MAKELPARAM( (HWND16)*plparam, HIWORD(wParam32) );
2467         return 0;
2468     case WM_MENUCHAR:
2469         wch = LOWORD(wParam32);
2470         WideCharToMultiByte( CP_ACP, 0, &wch, 1, &ch, 1, NULL, NULL);
2471         *pwparam16 = ch;
2472         *plparam = MAKELPARAM( HIWORD(wParam32), (HMENU16)*plparam );
2473         return 0;
2474     case WM_CHAR:
2475     case WM_DEADCHAR:
2476     case WM_SYSCHAR:
2477     case WM_SYSDEADCHAR:
2478         wch = wParam32;
2479         WideCharToMultiByte( CP_ACP, 0, &wch, 1, &ch, 1, NULL, NULL);
2480         *pwparam16 = ch;
2481         return 0;
2482
2483     default:  /* No Unicode translation needed (?) */
2484         return WINPROC_MapMsg32ATo16( hwnd, msg32, wParam32, pmsg16,
2485                                       pwparam16, plparam );
2486     }
2487 }
2488
2489
2490 /**********************************************************************
2491  *           WINPROC_UnmapMsg32WTo16
2492  *
2493  * Unmap a message that was mapped from 32-bit Unicode to 16-bit.
2494  */
2495 void WINPROC_UnmapMsg32WTo16( HWND hwnd, UINT msg, WPARAM wParam, LPARAM lParam,
2496                               MSGPARAM16* p16 )
2497 {
2498     switch(msg)
2499     {
2500     case LB_ADDSTRING:
2501     case LB_FINDSTRING:
2502     case LB_FINDSTRINGEXACT:
2503     case LB_INSERTSTRING:
2504     case LB_SELECTSTRING:
2505     case LB_DIR:
2506     case LB_ADDFILE:
2507     case CB_ADDSTRING:
2508     case CB_FINDSTRING:
2509     case CB_FINDSTRINGEXACT:
2510     case CB_INSERTSTRING:
2511     case CB_SELECTSTRING:
2512     case CB_DIR:
2513     case WM_SETTEXT:
2514     case WM_WININICHANGE:
2515     case WM_DEVMODECHANGE:
2516         unmap_str_32W_to_16( p16->lParam );
2517         break;
2518     case WM_NCCREATE:
2519     case WM_CREATE:
2520         {
2521             CREATESTRUCT16 *cs = MapSL(p16->lParam);
2522             UnMapLS( p16->lParam );
2523             unmap_str_32W_to_16( cs->lpszName );
2524             unmap_str_32W_to_16( cs->lpszClass );
2525             HeapFree( GetProcessHeap(), 0, cs );
2526         }
2527         break;
2528     case WM_MDICREATE:
2529         {
2530             MDICREATESTRUCT16 *cs = MapSL(p16->lParam);
2531             UnMapLS( p16->lParam );
2532             unmap_str_32W_to_16( cs->szTitle );
2533             unmap_str_32W_to_16( cs->szClass );
2534             HeapFree( GetProcessHeap(), 0, cs );
2535         }
2536         break;
2537     case WM_GETTEXT:
2538     case WM_ASKCBFORMATNAME:
2539         {
2540             LPSTR str = MapSL(p16->lParam);
2541             UnMapLS( p16->lParam );
2542             p16->lParam = *((LPARAM *)str - 1);
2543             MultiByteToWideChar( CP_ACP, 0, str, -1, (LPWSTR)p16->lParam, 0x7fffffff );
2544             HeapFree( GetProcessHeap(), 0, (LPARAM *)str - 1 );
2545         }
2546         break;
2547     case LB_GETTEXT:
2548     case CB_GETLBTEXT:
2549         if ( WINPROC_TestLBForStr( hwnd ))
2550         {
2551             LPSTR str = MapSL(p16->lParam);
2552             UnMapLS( p16->lParam );
2553             MultiByteToWideChar( CP_ACP, 0, str, -1, (LPWSTR)lParam, 0x7fffffff );
2554             HeapFree( GetProcessHeap(), 0, (LPARAM *)str );
2555         }
2556         break;
2557     default:
2558         WINPROC_UnmapMsg32ATo16( hwnd, msg, wParam, lParam, p16 );
2559         break;
2560     }
2561 }
2562
2563
2564 /**********************************************************************
2565  *           WINPROC_CallProc32ATo32W
2566  *
2567  * Call a window procedure, translating args from Ansi to Unicode.
2568  */
2569 static LRESULT WINPROC_CallProc32ATo32W( WNDPROC func, HWND hwnd,
2570                                          UINT msg, WPARAM wParam,
2571                                          LPARAM lParam )
2572 {
2573     LRESULT result;
2574     int unmap;
2575
2576     TRACE_(msg)("func %p (hwnd=%08x,msg=%s,wp=%08x,lp=%08lx)\n",
2577         func, hwnd, SPY_GetMsgName(msg, hwnd), wParam, lParam);
2578
2579     if( (unmap = WINPROC_MapMsg32ATo32W( hwnd, msg, &wParam, &lParam )) == -1) {
2580         ERR_(msg)("Message translation failed. (msg=%s,wp=%08x,lp=%08lx)\n",
2581                        SPY_GetMsgName(msg, hwnd), wParam, lParam );
2582         return 0;
2583     }
2584     result = WINPROC_CallWndProc( func, hwnd, msg, wParam, lParam );
2585     if (unmap) result = WINPROC_UnmapMsg32ATo32W( hwnd, msg, wParam, lParam, result );
2586     return result;
2587 }
2588
2589
2590 /**********************************************************************
2591  *           WINPROC_CallProc32WTo32A
2592  *
2593  * Call a window procedure, translating args from Unicode to Ansi.
2594  */
2595 static LRESULT WINPROC_CallProc32WTo32A( WNDPROC func, HWND hwnd,
2596                                          UINT msg, WPARAM wParam,
2597                                          LPARAM lParam )
2598 {
2599     LRESULT result;
2600     int unmap;
2601
2602     TRACE_(msg)("func %p (hwnd=%08x,msg=%s,wp=%08x,lp=%08lx)\n",
2603         func, hwnd, SPY_GetMsgName(msg, hwnd), wParam, lParam);
2604
2605     if ((unmap = WINPROC_MapMsg32WTo32A( hwnd, msg, &wParam, &lParam )) == -1) {
2606         ERR_(msg)("Message translation failed. (msg=%s,wp=%08x,lp=%08lx)\n",
2607                        SPY_GetMsgName(msg, hwnd), wParam, lParam );
2608         return 0;
2609     }
2610     result = WINPROC_CallWndProc( func, hwnd, msg, wParam, lParam );
2611     if( unmap ) WINPROC_UnmapMsg32WTo32A( hwnd, msg, wParam, lParam );
2612     return result;
2613 }
2614
2615
2616 /**********************************************************************
2617  *           __wine_call_wndproc_32A   (USER.1010)
2618  */
2619 LRESULT WINAPI __wine_call_wndproc_32A( HWND16 hwnd, UINT16 msg, WPARAM16 wParam, LPARAM lParam,
2620                                         WNDPROC func )
2621 {
2622     LRESULT result;
2623     UINT msg32;
2624     WPARAM wParam32;
2625     HWND hwnd32 = WIN_Handle32( hwnd );
2626
2627     if (WINPROC_MapMsg16To32A( hwnd32, msg, wParam, &msg32, &wParam32, &lParam ) == -1)
2628         return 0;
2629     result = WINPROC_CallWndProc( func, hwnd32, msg32, wParam32, lParam );
2630     return WINPROC_UnmapMsg16To32A( hwnd32, msg32, wParam32, lParam, result );
2631 }
2632
2633
2634 /**********************************************************************
2635  *           __wine_call_wndproc_32W   (USER.1011)
2636  */
2637 LRESULT WINAPI  __wine_call_wndproc_32W( HWND16 hwnd, UINT16 msg, WPARAM16 wParam, LPARAM lParam,
2638                                          WNDPROC func )
2639 {
2640     LRESULT result;
2641     UINT msg32;
2642     WPARAM wParam32;
2643     HWND hwnd32 = WIN_Handle32( hwnd );
2644
2645     if (WINPROC_MapMsg16To32W( hwnd32, msg, wParam, &msg32, &wParam32, &lParam ) == -1)
2646         return 0;
2647     result = WINPROC_CallWndProc( func, hwnd32, msg32, wParam32, lParam );
2648     return WINPROC_UnmapMsg16To32W( hwnd32, msg32, wParam32, lParam, result );
2649 }
2650
2651
2652 /**********************************************************************
2653  *           WINPROC_CallProc32ATo16
2654  *
2655  * Call a 16-bit window procedure, translating the 32-bit args.
2656  */
2657 static LRESULT WINAPI WINPROC_CallProc32ATo16( WNDPROC16 func, HWND hwnd,
2658                                                UINT msg, WPARAM wParam,
2659                                                LPARAM lParam )
2660 {
2661     UINT16 msg16;
2662     MSGPARAM16 mp16;
2663
2664     TRACE_(msg)("func %p (hwnd=%08x,msg=%s,wp=%08x,lp=%08lx)\n",
2665         func, hwnd, SPY_GetMsgName(msg, hwnd), wParam, lParam);
2666
2667     mp16.lParam = lParam;
2668     if (WINPROC_MapMsg32ATo16( hwnd, msg, wParam, &msg16, &mp16.wParam, &mp16.lParam ) == -1)
2669         return 0;
2670     mp16.lResult = WINPROC_CallWndProc16( func, HWND_16(hwnd), msg16,
2671                                           mp16.wParam, mp16.lParam );
2672     WINPROC_UnmapMsg32ATo16( hwnd, msg, wParam, lParam, &mp16 );
2673     return mp16.lResult;
2674 }
2675
2676
2677 /**********************************************************************
2678  *           WINPROC_CallProc32WTo16
2679  *
2680  * Call a 16-bit window procedure, translating the 32-bit args.
2681  */
2682 static LRESULT WINAPI WINPROC_CallProc32WTo16( WNDPROC16 func, HWND hwnd,
2683                                                UINT msg, WPARAM wParam,
2684                                                LPARAM lParam )
2685 {
2686     UINT16 msg16;
2687     MSGPARAM16 mp16;
2688
2689     TRACE_(msg)("func %p (hwnd=%08x,msg=%s,wp=%08x,lp=%08lx)\n",
2690         func, hwnd, SPY_GetMsgName(msg, hwnd), wParam, lParam);
2691
2692     mp16.lParam = lParam;
2693     if (WINPROC_MapMsg32WTo16( hwnd, msg, wParam, &msg16, &mp16.wParam,
2694                                &mp16.lParam ) == -1)
2695         return 0;
2696     mp16.lResult = WINPROC_CallWndProc16( func, HWND_16(hwnd), msg16,
2697                                           mp16.wParam, mp16.lParam );
2698     WINPROC_UnmapMsg32WTo16( hwnd, msg, wParam, lParam, &mp16 );
2699     return mp16.lResult;
2700 }
2701
2702
2703 /**********************************************************************
2704  *              CallWindowProc (USER.122)
2705  */
2706 LRESULT WINAPI CallWindowProc16( WNDPROC16 func, HWND16 hwnd, UINT16 msg,
2707                                  WPARAM16 wParam, LPARAM lParam )
2708 {
2709     WINDOWPROC *proc;
2710
2711     if (!func) return 0;
2712
2713     if (!(proc = WINPROC_GetPtr( func )))
2714         return WINPROC_CallWndProc16( func, hwnd, msg, wParam, lParam );
2715
2716 #if testing
2717     func = WINPROC_GetProc( (HWINDOWPROC)proc, WIN_PROC_16 );
2718     return WINPROC_CallWndProc16( func, hwnd, msg, wParam, lParam );
2719 #endif
2720
2721     switch(proc->type)
2722     {
2723     case WIN_PROC_16:
2724         if (!proc->thunk.t_from32.proc) return 0;
2725         return WINPROC_CallWndProc16( proc->thunk.t_from32.proc,
2726                                       hwnd, msg, wParam, lParam );
2727     case WIN_PROC_32A:
2728         if (!proc->thunk.t_from16.proc) return 0;
2729         return __wine_call_wndproc_32A( hwnd, msg, wParam, lParam, proc->thunk.t_from16.proc );
2730     case WIN_PROC_32W:
2731         if (!proc->thunk.t_from16.proc) return 0;
2732         return __wine_call_wndproc_32W( hwnd, msg, wParam, lParam, proc->thunk.t_from16.proc );
2733     default:
2734         WARN_(relay)("Invalid proc %p\n", proc );
2735         return 0;
2736     }
2737 }
2738
2739
2740 /**********************************************************************
2741  *              CallWindowProcA (USER32.@)
2742  *
2743  * The CallWindowProc() function invokes the windows procedure _func_,
2744  * with _hwnd_ as the target window, the message specified by _msg_, and
2745  * the message parameters _wParam_ and _lParam_.
2746  *
2747  * Some kinds of argument conversion may be done, I'm not sure what.
2748  *
2749  * CallWindowProc() may be used for windows subclassing. Use
2750  * SetWindowLong() to set a new windows procedure for windows of the
2751  * subclass, and handle subclassed messages in the new windows
2752  * procedure. The new windows procedure may then use CallWindowProc()
2753  * with _func_ set to the parent class's windows procedure to dispatch
2754  * the message to the superclass.
2755  *
2756  * RETURNS
2757  *
2758  *    The return value is message dependent.
2759  *
2760  * CONFORMANCE
2761  *
2762  *   ECMA-234, Win32
2763  */
2764 LRESULT WINAPI CallWindowProcA(
2765     WNDPROC func,  /* [in] window procedure */
2766     HWND hwnd,     /* [in] target window */
2767     UINT msg,      /* [in] message */
2768     WPARAM wParam, /* [in] message dependent parameter */
2769     LPARAM lParam  /* [in] message dependent parameter */
2770 ) {
2771     WINDOWPROC *proc = WINPROC_GetPtr( (WNDPROC16)func );
2772
2773     if (!proc) return WINPROC_CallWndProc( func, hwnd, msg, wParam, lParam );
2774
2775 #if testing
2776     func = WINPROC_GetProc( (HWINDOWPROC)proc, WIN_PROC_32A );
2777     return WINPROC_CallWndProc( func, hwnd, msg, wParam, lParam );
2778 #endif
2779
2780     switch(proc->type)
2781     {
2782     case WIN_PROC_16:
2783         if (!proc->thunk.t_from32.proc) return 0;
2784         return WINPROC_CallProc32ATo16( proc->thunk.t_from32.proc,
2785                                         hwnd, msg, wParam, lParam );
2786     case WIN_PROC_32A:
2787         if (!proc->thunk.t_from16.proc) return 0;
2788         return WINPROC_CallWndProc( proc->thunk.t_from16.proc,
2789                                       hwnd, msg, wParam, lParam );
2790     case WIN_PROC_32W:
2791         if (!proc->thunk.t_from16.proc) return 0;
2792         return WINPROC_CallProc32ATo32W( proc->thunk.t_from16.proc,
2793                                          hwnd, msg, wParam, lParam );
2794     default:
2795         WARN_(relay)("Invalid proc %p\n", proc );
2796         return 0;
2797     }
2798 }
2799
2800
2801 /**********************************************************************
2802  *              CallWindowProcW (USER32.@)
2803  */
2804 LRESULT WINAPI CallWindowProcW( WNDPROC func, HWND hwnd, UINT msg,
2805                                   WPARAM wParam, LPARAM lParam )
2806 {
2807     WINDOWPROC *proc = WINPROC_GetPtr( (WNDPROC16)func );
2808
2809     if (!proc) return WINPROC_CallWndProc( func, hwnd, msg, wParam, lParam );
2810
2811 #if testing
2812     func = WINPROC_GetProc( (HWINDOWPROC)proc, WIN_PROC_32W );
2813     return WINPROC_CallWndProc( func, hwnd, msg, wParam, lParam );
2814 #endif
2815
2816     switch(proc->type)
2817     {
2818     case WIN_PROC_16:
2819         if (!proc->thunk.t_from32.proc) return 0;
2820         return WINPROC_CallProc32WTo16( proc->thunk.t_from32.proc,
2821                                         hwnd, msg, wParam, lParam );
2822     case WIN_PROC_32A:
2823         if (!proc->thunk.t_from16.proc) return 0;
2824         return WINPROC_CallProc32WTo32A( proc->thunk.t_from16.proc,
2825                                          hwnd, msg, wParam, lParam );
2826     case WIN_PROC_32W:
2827         if (!proc->thunk.t_from16.proc) return 0;
2828         return WINPROC_CallWndProc( proc->thunk.t_from16.proc,
2829                                       hwnd, msg, wParam, lParam );
2830     default:
2831         WARN_(relay)("Invalid proc %p\n", proc );
2832         return 0;
2833     }
2834 }