Calling SafeArrayDestroy on a destroyed array should be a no-op.
[wine] / dlls / winedos / int31.c
1 /*
2  * DPMI 0.9 emulation
3  *
4  * Copyright 1995 Alexandre Julliard
5  *
6  * This library is free software; you can redistribute it and/or
7  * modify it under the terms of the GNU Lesser General Public
8  * License as published by the Free Software Foundation; either
9  * version 2.1 of the License, or (at your option) any later version.
10  *
11  * This library is distributed in the hope that it will be useful,
12  * but WITHOUT ANY WARRANTY; without even the implied warranty of
13  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
14  * Lesser General Public License for more details.
15  *
16  * You should have received a copy of the GNU Lesser General Public
17  * License along with this library; if not, write to the Free Software
18  * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
19  */
20
21 #include "config.h"
22 #include "wine/port.h"
23
24 #include "windef.h"
25 #include "wine/winbase16.h"
26 #include "miscemu.h"
27 #include "task.h"
28 #include "msdos.h"
29 #include "dosexe.h"
30
31 #include "wine/debug.h"
32 #include "stackframe.h"
33 #include "toolhelp.h"
34
35 WINE_DEFAULT_DEBUG_CHANNEL(int31);
36
37 /* Structure for real-mode callbacks */
38 typedef struct
39 {
40     DWORD edi;
41     DWORD esi;
42     DWORD ebp;
43     DWORD reserved;
44     DWORD ebx;
45     DWORD edx;
46     DWORD ecx;
47     DWORD eax;
48     WORD  fl;
49     WORD  es;
50     WORD  ds;
51     WORD  fs;
52     WORD  gs;
53     WORD  ip;
54     WORD  cs;
55     WORD  sp;
56     WORD  ss;
57 } REALMODECALL;
58
59 typedef struct tagRMCB {
60     DWORD address;
61     DWORD proc_ofs,proc_sel;
62     DWORD regs_ofs,regs_sel;
63     struct tagRMCB *next;
64 } RMCB;
65
66 static RMCB *FirstRMCB = NULL;
67 static WORD dpmi_flag;
68 static void* lastvalloced = NULL;
69
70 /**********************************************************************
71  *          DOSVM_IsDos32
72  * 
73  * Return TRUE if we are in 32-bit protected mode DOS process.
74  */
75 BOOL DOSVM_IsDos32(void)
76 {
77   return (dpmi_flag & 1) ? TRUE : FALSE;
78 }
79
80
81 /**********************************************************************
82  *          INT_GetRealModeContext
83  */
84 static void INT_GetRealModeContext( REALMODECALL *call, CONTEXT86 *context )
85 {
86     context->Eax    = call->eax;
87     context->Ebx    = call->ebx;
88     context->Ecx    = call->ecx;
89     context->Edx    = call->edx;
90     context->Esi    = call->esi;
91     context->Edi    = call->edi;
92     context->Ebp    = call->ebp;
93     context->EFlags = call->fl | V86_FLAG;
94     context->Eip    = call->ip;
95     context->Esp    = call->sp;
96     context->SegCs  = call->cs;
97     context->SegDs  = call->ds;
98     context->SegEs  = call->es;
99     context->SegFs  = call->fs;
100     context->SegGs  = call->gs;
101     context->SegSs  = call->ss;
102 }
103
104
105 /**********************************************************************
106  *          INT_SetRealModeContext
107  */
108 static void INT_SetRealModeContext( REALMODECALL *call, CONTEXT86 *context )
109 {
110     call->eax = context->Eax;
111     call->ebx = context->Ebx;
112     call->ecx = context->Ecx;
113     call->edx = context->Edx;
114     call->esi = context->Esi;
115     call->edi = context->Edi;
116     call->ebp = context->Ebp;
117     call->fl  = LOWORD(context->EFlags);
118     call->ip  = LOWORD(context->Eip);
119     call->sp  = LOWORD(context->Esp);
120     call->cs  = context->SegCs;
121     call->ds  = context->SegDs;
122     call->es  = context->SegEs;
123     call->fs  = context->SegFs;
124     call->gs  = context->SegGs;
125     call->ss  = context->SegSs;
126 }
127
128 /**********************************************************************
129  *          DPMI_xalloc
130  * special virtualalloc, allocates lineary monoton growing memory.
131  * (the usual VirtualAlloc does not satisfy that restriction)
132  */
133 static LPVOID DPMI_xalloc( DWORD len ) 
134 {
135     LPVOID  ret;
136     LPVOID  oldlastv = lastvalloced;
137
138     if (lastvalloced) 
139     {
140         int xflag = 0;
141
142         ret = NULL;
143         while (!ret) 
144         {
145             ret = VirtualAlloc( lastvalloced, len,
146                                 MEM_COMMIT|MEM_RESERVE, PAGE_EXECUTE_READWRITE );
147             if (!ret)
148                 lastvalloced = (char *) lastvalloced + 0x10000;
149
150             /* we failed to allocate one in the first round.
151              * try non-linear
152              */
153             if (!xflag && (lastvalloced<oldlastv)) 
154             { 
155                 /* wrapped */
156                 FIXME( "failed to allocate linearly growing memory (%ld bytes), "
157                        "using non-linear growing...\n", len );
158                 xflag++;
159             }
160
161             /* if we even fail to allocate something in the next
162              * round, return NULL
163              */
164             if ((xflag==1) && (lastvalloced >= oldlastv))
165                 xflag++;
166
167             if ((xflag==2) && (lastvalloced < oldlastv)) {
168                 FIXME( "failed to allocate any memory of %ld bytes!\n", len );
169                 return NULL;
170             }
171         }
172     } 
173     else
174     {
175         ret = VirtualAlloc( NULL, len, 
176                             MEM_COMMIT|MEM_RESERVE, PAGE_EXECUTE_READWRITE );
177     }
178
179     lastvalloced = (LPVOID)(((DWORD)ret+len+0xffff)&~0xffff);
180     return ret;
181 }
182
183 /**********************************************************************
184  *          DPMI_xfree
185  */
186 static void DPMI_xfree( LPVOID ptr ) 
187 {
188     VirtualFree( ptr, 0, MEM_RELEASE );
189 }
190
191 /**********************************************************************
192  *          DPMI_xrealloc
193  *
194  * FIXME: perhaps we could grow this mapped area... 
195  */
196 static LPVOID DPMI_xrealloc( LPVOID ptr, DWORD newsize ) 
197 {
198     MEMORY_BASIC_INFORMATION        mbi;
199     LPVOID                          newptr;
200
201     newptr = DPMI_xalloc( newsize );
202     if (ptr) 
203     {
204         if (!VirtualQuery(ptr,&mbi,sizeof(mbi))) 
205         {
206             FIXME( "realloc of DPMI_xallocd region %p?\n", ptr );
207             return NULL;
208         }
209
210         if (mbi.State == MEM_FREE) 
211         {
212             FIXME( "realloc of DPMI_xallocd region %p?\n", ptr );
213             return NULL;
214         }
215
216         /* We do not shrink allocated memory. most reallocs
217          * only do grows anyway
218          */
219         if (newsize <= mbi.RegionSize)
220             return ptr;
221
222         memcpy( newptr, ptr, mbi.RegionSize );
223         DPMI_xfree( ptr );
224     }
225
226     return newptr;
227 }
228
229
230 #ifdef __i386__
231
232 void DPMI_CallRMCB32(RMCB *rmcb, UINT16 ss, DWORD esp, UINT16*es, DWORD*edi)
233 #if 0 /* original code, which early gccs puke on */
234 {
235     int _clobber;
236     __asm__ __volatile__(
237         "pushl %%ebp\n"
238         "pushl %%ebx\n"
239         "pushl %%es\n"
240         "pushl %%ds\n"
241         "pushfl\n"
242         "mov %7,%%es\n"
243         "mov %5,%%ds\n"
244         ".byte 0x36, 0xff, 0x18\n" /* lcall *%ss:(%eax) */
245         "popl %%ds\n"
246         "mov %%es,%0\n"
247         "popl %%es\n"
248         "popl %%ebx\n"
249         "popl %%ebp\n"
250     : "=d" (*es), "=D" (*edi), "=S" (_clobber), "=a" (_clobber), "=c" (_clobber)
251     : "0" (ss), "2" (esp),
252       "4" (rmcb->regs_sel), "1" (rmcb->regs_ofs),
253       "3" (&rmcb->proc_ofs) );
254 }
255 #else /* code generated by a gcc new enough */
256 ;
257 __ASM_GLOBAL_FUNC(DPMI_CallRMCB32,
258     "pushl %ebp\n\t"
259     "movl %esp,%ebp\n\t"
260     "pushl %edi\n\t"
261     "pushl %esi\n\t"
262     "movl 0x8(%ebp),%eax\n\t"
263     "movl 0x10(%ebp),%esi\n\t"
264     "movl 0xc(%ebp),%edx\n\t"
265     "movl 0x10(%eax),%ecx\n\t"
266     "movl 0xc(%eax),%edi\n\t"
267     "addl $0x4,%eax\n\t"
268     "pushl %ebp\n\t"
269     "pushl %ebx\n\t"
270     "pushl %es\n\t"
271     "pushl %ds\n\t"
272     "pushfl\n\t"
273     "mov %cx,%es\n\t"
274     "mov %dx,%ds\n\t"
275     ".byte 0x36, 0xff, 0x18\n\t" /* lcall *%ss:(%eax) */
276     "popl %ds\n\t"
277     "mov %es,%dx\n\t"
278     "popl %es\n\t"
279     "popl %ebx\n\t"
280     "popl %ebp\n\t"
281     "movl 0x14(%ebp),%eax\n\t"
282     "movw %dx,(%eax)\n\t"
283     "movl 0x18(%ebp),%edx\n\t"
284     "movl %edi,(%edx)\n\t"
285     "popl %esi\n\t"
286     "popl %edi\n\t"
287     "leave\n\t"
288     "ret")
289 #endif
290
291 #endif /* __i386__ */
292
293 /**********************************************************************
294  *          DPMI_CallRMCBProc
295  *
296  * This routine does the hard work of calling a callback procedure.
297  */
298 static void DPMI_CallRMCBProc( CONTEXT86 *context, RMCB *rmcb, WORD flag )
299 {
300     if (IS_SELECTOR_SYSTEM( rmcb->proc_sel )) {
301         /* Wine-internal RMCB, call directly */
302         ((RMCBPROC)rmcb->proc_ofs)(context);
303     } else {
304 #ifdef __i386__
305         UINT16 ss,es;
306         DWORD esp,edi;
307
308         INT_SetRealModeContext(MapSL(MAKESEGPTR( rmcb->regs_sel, rmcb->regs_ofs )), context);
309         ss = SELECTOR_AllocBlock( (void *)(context->SegSs<<4), 0x10000, WINE_LDT_FLAGS_DATA );
310         esp = context->Esp;
311
312         FIXME("untested!\n");
313
314         /* The called proc ends with an IRET, and takes these parameters:
315          * DS:ESI = pointer to real-mode SS:SP
316          * ES:EDI = pointer to real-mode call structure
317          * It returns:
318          * ES:EDI = pointer to real-mode call structure (may be a copy)
319          * It is the proc's responsibility to change the return CS:IP in the
320          * real-mode call structure. */
321         if (flag & 1) {
322             /* 32-bit DPMI client */
323             DPMI_CallRMCB32(rmcb, ss, esp, &es, &edi);
324         } else {
325             /* 16-bit DPMI client */
326             CONTEXT86 ctx = *context;
327             ctx.SegCs = rmcb->proc_sel;
328             ctx.Eip   = rmcb->proc_ofs;
329             ctx.SegDs = ss;
330             ctx.Esi   = esp;
331             ctx.SegEs = rmcb->regs_sel;
332             ctx.Edi   = rmcb->regs_ofs;
333             /* FIXME: I'm pretty sure this isn't right - should push flags first */
334             wine_call_to_16_regs_short(&ctx, 0);
335             es = ctx.SegEs;
336             edi = ctx.Edi;
337         }
338         FreeSelector16(ss);
339         INT_GetRealModeContext( MapSL( MAKESEGPTR( es, edi )), context);
340 #else
341         ERR("RMCBs only implemented for i386\n");
342 #endif
343     }
344 }
345
346
347 /**********************************************************************
348  *          DPMI_CallRMProc
349  *
350  * This routine does the hard work of calling a real mode procedure.
351  */
352 int DPMI_CallRMProc( CONTEXT86 *context, LPWORD stack, int args, int iret )
353 {
354     LPWORD stack16;
355     LPVOID addr = NULL; /* avoid gcc warning */
356     RMCB *CurrRMCB;
357     int alloc = 0, already = 0;
358     BYTE *code;
359
360     TRACE("EAX=%08lx EBX=%08lx ECX=%08lx EDX=%08lx\n",
361                  context->Eax, context->Ebx, context->Ecx, context->Edx );
362     TRACE("ESI=%08lx EDI=%08lx ES=%04lx DS=%04lx CS:IP=%04lx:%04x, %d WORD arguments, %s\n",
363                  context->Esi, context->Edi, context->SegEs, context->SegDs,
364                  context->SegCs, LOWORD(context->Eip), args, iret?"IRET":"FAR" );
365
366 callrmproc_again:
367
368 /* there might be some code that just jumps to RMCBs or the like,
369    in which case following the jumps here might get us to a shortcut */
370     code = CTX_SEG_OFF_TO_LIN(context, context->SegCs, context->Eip);
371     switch (*code) {
372     case 0xe9: /* JMP NEAR */
373       context->Eip += 3 + *(WORD *)(code+1);
374       /* yeah, I know these gotos don't look good... */
375       goto callrmproc_again;
376     case 0xea: /* JMP FAR */
377       context->Eip = *(WORD *)(code+1);
378       context->SegCs = *(WORD *)(code+3);
379       /* ...but since the label is there anyway... */
380       goto callrmproc_again;
381     case 0xeb: /* JMP SHORT */
382       context->Eip += 2 + *(signed char *)(code+1);
383       /* ...because of other gotos below, so... */
384       goto callrmproc_again;
385     }
386
387 /* shortcut for chaining to internal interrupt handlers */
388     if ((context->SegCs == 0xF000) && iret)
389     {
390         DOSVM_RealModeInterrupt( LOWORD(context->Eip)/4, context);
391         return 0;
392     }
393
394 /* shortcut for RMCBs */
395     CurrRMCB = FirstRMCB;
396
397     while (CurrRMCB && (HIWORD(CurrRMCB->address) != context->SegCs))
398         CurrRMCB = CurrRMCB->next;
399
400     if (!CurrRMCB && !MZ_Current())
401     {
402         FIXME("DPMI real-mode call using DOS VM task system, not fully tested!\n");
403         TRACE("creating VM86 task\n");
404         MZ_AllocDPMITask();
405     }
406     if (!already) {
407         if (!context->SegSs) {
408             alloc = 1; /* allocate default stack */
409             stack16 = addr = DOSMEM_GetBlock( 64, (UINT16 *)&(context->SegSs) );
410             context->Esp = 64-2;
411             stack16 += 32-1;
412             if (!addr) {
413                 ERR("could not allocate default stack\n");
414                 return 1;
415             }
416         } else {
417             stack16 = CTX_SEG_OFF_TO_LIN(context, context->SegSs, context->Esp);
418         }
419         context->Esp -= (args + (iret?1:0)) * sizeof(WORD);
420         stack16 -= args;
421         if (args) memcpy(stack16, stack, args*sizeof(WORD) );
422         /* push flags if iret */
423         if (iret) {
424             stack16--; args++;
425             *stack16 = LOWORD(context->EFlags);
426         }
427         /* push return address (return to interrupt wrapper) */
428         *(--stack16) = DOSVM_dpmi_segments->wrap_seg;
429         *(--stack16) = 0;
430         /* adjust stack */
431         context->Esp -= 2*sizeof(WORD);
432         already = 1;
433     }
434
435     if (CurrRMCB) {
436         /* RMCB call, invoke protected-mode handler directly */
437         DPMI_CallRMCBProc(context, CurrRMCB, dpmi_flag);
438         /* check if we returned to where we thought we would */
439         if ((context->SegCs != DOSVM_dpmi_segments->wrap_seg) ||
440             (LOWORD(context->Eip) != 0)) {
441             /* we need to continue at different address in real-mode space,
442                so we need to set it all up for real mode again */
443             goto callrmproc_again;
444         }
445     } else {
446         TRACE("entering real mode...\n");
447         DOSVM_Enter( context );
448         TRACE("returned from real-mode call\n");
449     }
450     if (alloc) DOSMEM_FreeBlock( addr );
451     return 0;
452 }
453
454
455 /**********************************************************************
456  *          CallRMInt   (WINEDOS.@)
457  */
458 void WINAPI DOSVM_CallRMInt( CONTEXT86 *context )
459 {
460     CONTEXT86 realmode_ctx;
461     FARPROC16 rm_int = DOSVM_GetRMHandler( BL_reg(context) );
462     REALMODECALL *call = CTX_SEG_OFF_TO_LIN( context, 
463                                              context->SegEs, 
464                                              context->Edi );
465     INT_GetRealModeContext( call, &realmode_ctx );
466
467     /* we need to check if a real-mode program has hooked the interrupt */
468     if (HIWORD(rm_int)!=0xF000) {
469         /* yup, which means we need to switch to real mode... */
470         realmode_ctx.SegCs = HIWORD(rm_int);
471         realmode_ctx.Eip   = LOWORD(rm_int);
472         if (DPMI_CallRMProc( &realmode_ctx, NULL, 0, TRUE))
473           SET_CFLAG(context);
474     } else {
475         RESET_CFLAG(context);
476         /* use the IP we have instead of BL_reg, in case some apps
477            decide to move interrupts around for whatever reason... */
478         DOSVM_RealModeInterrupt( LOWORD(rm_int)/4, &realmode_ctx );
479     }
480     INT_SetRealModeContext( call, &realmode_ctx );
481 }
482
483
484 /**********************************************************************
485  *          CallRMProc   (WINEDOS.@)
486  */
487 void WINAPI DOSVM_CallRMProc( CONTEXT86 *context, int iret )
488 {
489     REALMODECALL *p = CTX_SEG_OFF_TO_LIN( context, 
490                                           context->SegEs, 
491                                           context->Edi );
492     CONTEXT86 context16;
493
494     TRACE("RealModeCall: EAX=%08lx EBX=%08lx ECX=%08lx EDX=%08lx\n",
495           p->eax, p->ebx, p->ecx, p->edx);
496     TRACE("              ESI=%08lx EDI=%08lx ES=%04x DS=%04x CS:IP=%04x:%04x, %d WORD arguments, %s\n",
497           p->esi, p->edi, p->es, p->ds, p->cs, p->ip, CX_reg(context), iret?"IRET":"FAR" );
498
499     if (!(p->cs) && !(p->ip)) { /* remove this check
500                                    if Int21/6501 case map function
501                                    has been implemented */
502         SET_CFLAG(context);
503         return;
504      }
505     INT_GetRealModeContext(p, &context16);
506     DPMI_CallRMProc( &context16, ((LPWORD)MapSL(MAKESEGPTR(context->SegSs, LOWORD(context->Esp))))+3,
507                      CX_reg(context), iret );
508     INT_SetRealModeContext(p, &context16);
509 }
510
511
512 /* (see dosmem.c, function DOSMEM_InitDPMI) */
513 static void StartPM( CONTEXT86 *context )
514 {
515     UINT16 cs, ss, ds, es;
516     CONTEXT86 pm_ctx;
517     DWORD psp_ofs = (DWORD)(DOSVM_psp<<4);
518     PDB16 *psp = (PDB16 *)psp_ofs;
519     HANDLE16 env_seg = psp->environment;
520     unsigned char selflags = WINE_LDT_FLAGS_DATA;
521
522     RESET_CFLAG(context);
523     dpmi_flag = AX_reg(context);
524 /* our mode switch wrapper have placed the desired CS into DX */
525     cs = SELECTOR_AllocBlock( (void *)(DX_reg(context)<<4), 0x10000, WINE_LDT_FLAGS_CODE );
526 /* due to a flaw in some CPUs (at least mine), it is best to mark stack segments as 32-bit if they
527    can be used in 32-bit code. Otherwise, these CPUs may not set the high word of esp during a
528    ring transition (from kernel code) to the 16-bit stack, and this causes trouble if executing
529    32-bit code using this stack. */
530     if (dpmi_flag & 1) selflags |= WINE_LDT_FLAGS_32BIT;
531     ss = SELECTOR_AllocBlock( (void *)(context->SegSs<<4), 0x10000, selflags );
532 /* do the same for the data segments, just in case */
533     if (context->SegDs == context->SegSs) ds = ss;
534     else ds = SELECTOR_AllocBlock( (void *)(context->SegDs<<4), 0x10000, selflags );
535     es = SELECTOR_AllocBlock( psp, 0x100, selflags );
536 /* convert environment pointer, as the spec says, but we're a bit lazy about the size here... */
537     psp->environment = SELECTOR_AllocBlock( (void *)(env_seg<<4), 0x10000, WINE_LDT_FLAGS_DATA );
538
539     pm_ctx = *context;
540     pm_ctx.SegCs = DOSVM_dpmi_segments->dpmi_sel;
541 /* our mode switch wrapper expects the new CS in DX, and the new SS in AX */
542     pm_ctx.Eax   = ss;
543     pm_ctx.Edx   = cs;
544     pm_ctx.SegDs = ds;
545     pm_ctx.SegEs = es;
546     pm_ctx.SegFs = 0;
547     pm_ctx.SegGs = 0;
548
549     TRACE("DOS program is now entering %d-bit protected mode\n", 
550           DOSVM_IsDos32() ? 32 : 16);
551     wine_call_to_16_regs_short(&pm_ctx, 0);
552
553     /* in the current state of affairs, we won't ever actually return here... */
554     /* we should have int21/ah=4c do it someday, though... */
555
556     FreeSelector16(psp->environment);
557     psp->environment = env_seg;
558     FreeSelector16(es);
559     if (ds != ss) FreeSelector16(ds);
560     FreeSelector16(ss);
561     FreeSelector16(cs);
562 }
563
564 static RMCB *DPMI_AllocRMCB( void )
565 {
566     RMCB *NewRMCB = HeapAlloc(GetProcessHeap(), 0, sizeof(RMCB));
567     UINT16 uParagraph;
568
569     if (NewRMCB)
570     {
571         LPVOID RMCBmem = DOSMEM_GetBlock(4, &uParagraph);
572         LPBYTE p = RMCBmem;
573
574         *p++ = 0xcd; /* RMCB: */
575         *p++ = 0x31; /* int $0x31 */
576 /* it is the called procedure's task to change the return CS:EIP
577    the DPMI 0.9 spec states that if it doesn't, it will be called again */
578         *p++ = 0xeb;
579         *p++ = 0xfc; /* jmp RMCB */
580         NewRMCB->address = MAKELONG(0, uParagraph);
581         NewRMCB->next = FirstRMCB;
582         FirstRMCB = NewRMCB;
583     }
584     return NewRMCB;
585 }
586
587
588 FARPROC16 WINAPI DPMI_AllocInternalRMCB( RMCBPROC proc )
589 {
590     RMCB *NewRMCB = DPMI_AllocRMCB();
591
592     if (NewRMCB) {
593         NewRMCB->proc_ofs = (DWORD)proc;
594         NewRMCB->proc_sel = 0;
595         NewRMCB->regs_ofs = 0;
596         NewRMCB->regs_sel = 0;
597         return (FARPROC16)(NewRMCB->address);
598     }
599     return NULL;
600 }
601
602
603 static int DPMI_FreeRMCB( DWORD address )
604 {
605     RMCB *CurrRMCB = FirstRMCB;
606     RMCB *PrevRMCB = NULL;
607
608     while (CurrRMCB && (CurrRMCB->address != address))
609     {
610         PrevRMCB = CurrRMCB;
611         CurrRMCB = CurrRMCB->next;
612     }
613     if (CurrRMCB)
614     {
615         if (PrevRMCB)
616         PrevRMCB->next = CurrRMCB->next;
617             else
618         FirstRMCB = CurrRMCB->next;
619         DOSMEM_FreeBlock(PTR_REAL_TO_LIN(SELECTOROF(CurrRMCB->address),OFFSETOF(CurrRMCB->address)));
620         HeapFree(GetProcessHeap(), 0, CurrRMCB);
621         return 0;
622     }
623     return 1;
624 }
625
626
627 void WINAPI DPMI_FreeInternalRMCB( FARPROC16 proc )
628 {
629     DPMI_FreeRMCB( (DWORD)proc );
630 }
631
632
633 /**********************************************************************
634  *          RawModeSwitch   (WINEDOS.@)
635  *
636  * DPMI Raw Mode Switch handler
637  */
638 void WINAPI DOSVM_RawModeSwitch( CONTEXT86 *context )
639 {
640   CONTEXT86 rm_ctx;
641   int ret;
642
643   /* initialize real-mode context as per spec */
644   memset(&rm_ctx, 0, sizeof(rm_ctx));
645   rm_ctx.SegDs  = AX_reg(context);
646   rm_ctx.SegEs  = CX_reg(context);
647   rm_ctx.SegSs  = DX_reg(context);
648   rm_ctx.Esp    = context->Ebx;
649   rm_ctx.SegCs  = SI_reg(context);
650   rm_ctx.Eip    = context->Edi;
651   rm_ctx.Ebp    = context->Ebp;
652   rm_ctx.SegFs  = 0;
653   rm_ctx.SegGs  = 0;
654   rm_ctx.EFlags = context->EFlags; /* at least we need the IF flag */
655
656   /* enter real mode again */
657   TRACE("re-entering real mode at %04lx:%04lx\n",rm_ctx.SegCs,rm_ctx.Eip);
658   ret = DOSVM_Enter( &rm_ctx );
659   /* when the real-mode stuff call its mode switch address,
660      DOSVM_Enter will return and we will continue here */
661
662   if (ret<0) {
663     ERR("Sync lost!\n");
664     /* if the sync was lost, there's no way to recover */
665     ExitProcess(1);
666   }
667
668   /* alter protected-mode context as per spec */
669   context->SegDs   = LOWORD(rm_ctx.Eax);
670   context->SegEs   = LOWORD(rm_ctx.Ecx);
671   context->SegSs   = LOWORD(rm_ctx.Edx);
672   context->Esp     = rm_ctx.Ebx;
673   context->SegCs   = LOWORD(rm_ctx.Esi);
674   context->Eip     = rm_ctx.Edi;
675   context->Ebp     = rm_ctx.Ebp;
676   context->SegFs   = 0;
677   context->SegGs   = 0;
678
679   /* Return to new address and hope that we didn't mess up */
680   TRACE("re-entering protected mode at %04lx:%08lx\n",
681       context->SegCs, context->Eip);
682 }
683
684
685 /**********************************************************************
686  *          AllocRMCB   (WINEDOS.@)
687  */
688 void WINAPI DOSVM_AllocRMCB( CONTEXT86 *context )
689 {
690     RMCB *NewRMCB = DPMI_AllocRMCB();
691
692     TRACE("Function to call: %04x:%04x\n", (WORD)context->SegDs, SI_reg(context) );
693
694     if (NewRMCB)
695     {
696        NewRMCB->proc_ofs = DOSVM_IsDos32() ? context->Esi : LOWORD(context->Esi);
697         NewRMCB->proc_sel = context->SegDs;
698        NewRMCB->regs_ofs = DOSVM_IsDos32() ? context->Edi : LOWORD(context->Edi);
699         NewRMCB->regs_sel = context->SegEs;
700         SET_CX( context, HIWORD(NewRMCB->address) );
701         SET_DX( context, LOWORD(NewRMCB->address) );
702     }
703     else
704     {
705         SET_AX( context, 0x8015 ); /* callback unavailable */
706         SET_CFLAG(context);
707     }
708 }
709
710
711 /**********************************************************************
712  *          FreeRMCB   (WINEDOS.@)
713  */
714 void WINAPI DOSVM_FreeRMCB( CONTEXT86 *context )
715 {
716     FIXME("callback address: %04x:%04x\n",
717           CX_reg(context), DX_reg(context));
718
719     if (DPMI_FreeRMCB(MAKELONG(DX_reg(context), CX_reg(context)))) {
720         SET_AX( context, 0x8024 ); /* invalid callback address */
721         SET_CFLAG(context);
722     }
723 }
724
725 /**********************************************************************
726  *          DOSVM_RawModeSwitchWrapper
727  *
728  * DPMI Raw Mode Switch wrapper.
729  * This routine does all the stack manipulation tricks needed
730  * to return from protected mode interrupt using modified 
731  * code and stack pointers.
732  */
733 static void DOSVM_RawModeSwitchWrapper( CONTEXT86 *context )
734 {
735     /*
736      * FIXME: This routine will not work if it is called
737      *        from 32 bit DPMI program and the program returns
738      *        to protected mode while ESP or EIP is over 0xffff.
739      * FIXME: This routine will not work if it is not called
740      *        using 16-bit-to-Wine callback glue function.
741      */
742     STACK16FRAME frame = *CURRENT_STACK16;
743   
744     DOSVM_RawModeSwitch( context );
745
746     /*
747      * After this function returns to relay code, protected mode
748      * 16 bit stack will contain STACK16FRAME and single WORD
749      * (EFlags, see next comment).
750      */
751     NtCurrentTeb()->cur_stack =
752         MAKESEGPTR( context->SegSs,
753                     context->Esp - sizeof(STACK16FRAME) - sizeof(WORD) );
754   
755     /*
756      * After relay code returns to glue function, protected
757      * mode 16 bit stack will contain interrupt return record:
758      * IP, CS and EFlags. Since EFlags is ignored, it won't
759      * need to be initialized.
760      */
761     context->Esp -= 3 * sizeof(WORD);
762
763     /*
764      * Restore stack frame so that relay code won't be confused.
765      * It should be noted that relay code overwrites IP and CS
766      * in STACK16FRAME with values taken from current CONTEXT86.
767      * These values are what is returned to glue function
768      * (see previous comment).
769      */
770     *CURRENT_STACK16 = frame;
771 }
772
773
774 /**********************************************************************
775  *         DOSVM_CheckWrappers
776  *
777  * Check if this was really a wrapper call instead of an interrupt.
778  * FIXME: Protected mode stuff does not work in 32-bit DPMI.
779  * FIXME: If int31 is called asynchronously (unlikely) 
780  *        wrapper checks are wrong (CS/IP must not be used).
781  */
782 static BOOL DOSVM_CheckWrappers( CONTEXT86 *context )
783 {
784     /* Handle protected mode interrupts. */
785     if (!ISV86(context)) {
786         if (context->SegCs == DOSVM_dpmi_segments->dpmi_sel) {
787             DOSVM_RawModeSwitchWrapper( context );
788             return TRUE;
789         }
790         return FALSE;
791     }
792
793     /* check if it's our wrapper */
794     TRACE("called from real mode\n");
795     if (context->SegCs==DOSVM_dpmi_segments->dpmi_seg) {
796         /* This is the protected mode switch */
797         StartPM(context);
798         return TRUE;
799     }
800     else if (context->SegCs==DOSVM_dpmi_segments->xms_seg)
801     {
802         /* This is the XMS driver entry point */
803         XMS_Handler(context);
804         return TRUE;
805     }
806     else
807     {
808         /* Check for RMCB */
809         RMCB *CurrRMCB = FirstRMCB;
810
811         while (CurrRMCB && (HIWORD(CurrRMCB->address) != context->SegCs))
812             CurrRMCB = CurrRMCB->next;
813
814         if (CurrRMCB) {
815             /* RMCB call, propagate to protected-mode handler */
816             DPMI_CallRMCBProc(context, CurrRMCB, dpmi_flag);
817             return TRUE;
818         }
819     }
820
821     return FALSE;
822 }
823
824 /**********************************************************************
825  *         DOSVM_Int31Handler (WINEDOS16.149)
826  *
827  * Handler for int 31h (DPMI).
828  */
829 void WINAPI DOSVM_Int31Handler( CONTEXT86 *context )
830 {
831     if (DOSVM_CheckWrappers(context))
832         return;
833
834     RESET_CFLAG(context);
835     switch(AX_reg(context))
836     {
837     case 0x0000:  /* Allocate LDT descriptors */
838         TRACE( "allocate LDT descriptors (%d)\n", CX_reg(context) );
839         {
840             WORD sel =  AllocSelectorArray16( CX_reg(context) );
841             if(!sel) 
842             {
843                TRACE( "failed\n" );
844                SET_AX( context, 0x8011 ); /* descriptor unavailable */
845                SET_CFLAG( context );
846             } 
847             else 
848             { 
849                 TRACE( "success, array starts at 0x%04x\n", sel );
850                 SET_AX( context, sel );      
851             }
852         }
853         break;
854
855     case 0x0001:  /* Free LDT descriptor */
856         TRACE( "free LDT descriptor (0x%04x)\n", BX_reg(context) );
857         if (FreeSelector16( BX_reg(context) ))
858         {
859             SET_AX( context, 0x8022 );  /* invalid selector */
860             SET_CFLAG( context );
861         }
862         else
863         {
864             /* If a segment register contains the selector being freed, */
865             /* set it to zero. */
866             if (!((context->SegDs^BX_reg(context)) & ~3)) context->SegDs = 0;
867             if (!((context->SegEs^BX_reg(context)) & ~3)) context->SegEs = 0;
868             if (!((context->SegFs^BX_reg(context)) & ~3)) context->SegFs = 0;
869             if (!((context->SegGs^BX_reg(context)) & ~3)) context->SegGs = 0;
870         }
871         break;
872
873     case 0x0002:  /* Real mode segment to descriptor */
874         TRACE( "real mode segment to descriptor (0x%04x)\n", BX_reg(context) );
875         {
876             WORD entryPoint = 0;  /* KERNEL entry point for descriptor */
877             switch(BX_reg(context))
878             {
879             case 0x0000: entryPoint = 183; break;  /* __0000H */
880             case 0x0040: entryPoint = 193; break;  /* __0040H */
881             case 0xa000: entryPoint = 174; break;  /* __A000H */
882             case 0xb000: entryPoint = 181; break;  /* __B000H */
883             case 0xb800: entryPoint = 182; break;  /* __B800H */
884             case 0xc000: entryPoint = 195; break;  /* __C000H */
885             case 0xd000: entryPoint = 179; break;  /* __D000H */
886             case 0xe000: entryPoint = 190; break;  /* __E000H */
887             case 0xf000: entryPoint = 194; break;  /* __F000H */
888             default:
889                 SET_AX( context, DOSMEM_AllocSelector(BX_reg(context)) );
890                 break;
891             }
892             if (entryPoint)
893             {
894                 FARPROC16 proc = GetProcAddress16( GetModuleHandle16( "KERNEL" ),
895                                                    (LPCSTR)(ULONG_PTR)entryPoint );
896                 SET_AX( context, LOWORD(proc) );
897             }
898         }
899         break;
900
901     case 0x0003:  /* Get next selector increment */
902         TRACE("get selector increment (__AHINCR)\n");
903         context->Eax = __AHINCR;
904         break;
905
906     case 0x0004:  /* Lock selector (not supported) */
907         FIXME("lock selector not supported\n");
908         context->Eax = 0;  /* FIXME: is this a correct return value? */
909         break;
910
911     case 0x0005:  /* Unlock selector (not supported) */
912         FIXME("unlock selector not supported\n");
913         context->Eax = 0;  /* FIXME: is this a correct return value? */
914         break;
915
916     case 0x0006:  /* Get selector base address */
917         TRACE( "get selector base address (0x%04x)\n", BX_reg(context) );
918         {
919             WORD sel = BX_reg(context);
920             if (IS_SELECTOR_SYSTEM(sel) || IS_SELECTOR_FREE(sel))
921             {
922                 context->Eax = 0x8022;  /* invalid selector */
923                 SET_CFLAG(context);
924             }
925             else
926             {
927                 DWORD base = GetSelectorBase( sel );
928                 SET_CX( context, HIWORD(base) );
929                 SET_DX( context, LOWORD(base) );
930             }
931         }
932         break;
933
934     case 0x0007:  /* Set selector base address */
935         {
936             DWORD base = MAKELONG( DX_reg(context), CX_reg(context) );
937             WORD  sel = BX_reg(context);
938             TRACE( "set selector base address (0x%04x,0x%08lx)\n", sel, base );
939
940             /* check if Win16 app wants to access lower 64K of DOS memory */
941             if (base < 0x10000 && DOSVM_IsWin16())
942                 DOSMEM_Init(TRUE);
943
944             SetSelectorBase( sel, base );
945         }
946         break;
947
948     case 0x0008:  /* Set selector limit */
949         {
950             DWORD limit = MAKELONG( DX_reg(context), CX_reg(context) );
951             TRACE( "set selector limit (0x%04x,0x%08lx)\n",
952                    BX_reg(context), limit );
953             SetSelectorLimit16( BX_reg(context), limit );
954         }
955         break;
956
957     case 0x0009:  /* Set selector access rights */
958         TRACE( "set selector access rights(0x%04x,0x%04x)\n",
959                BX_reg(context), CX_reg(context) );
960         SelectorAccessRights16( BX_reg(context), 1, CX_reg(context) );
961         break;
962
963     case 0x000a:  /* Allocate selector alias */
964         TRACE( "allocate selector alias (0x%04x)\n", BX_reg(context) );
965         if (!SET_AX( context, AllocCStoDSAlias16( BX_reg(context) )))
966         {
967             SET_AX( context, 0x8011 );  /* descriptor unavailable */
968             SET_CFLAG(context);
969         }
970         break;
971
972     case 0x000b:  /* Get descriptor */
973         TRACE( "get descriptor (0x%04x)\n", BX_reg(context) );
974         {
975             LDT_ENTRY *entry = (LDT_ENTRY*)CTX_SEG_OFF_TO_LIN( context,
976                                                                context->SegEs, 
977                                                                context->Edi );
978             wine_ldt_get_entry( BX_reg(context), entry );
979         }
980         break;
981
982     case 0x000c:  /* Set descriptor */
983         TRACE( "set descriptor (0x%04x)\n", BX_reg(context) );
984         {
985             LDT_ENTRY *entry = (LDT_ENTRY*)CTX_SEG_OFF_TO_LIN( context,
986                                                                context->SegEs, 
987                                                                context->Edi );
988             wine_ldt_set_entry( BX_reg(context), entry );
989         }
990         break;
991
992     case 0x000d:  /* Allocate specific LDT descriptor */
993         FIXME( "allocate descriptor (0x%04x), stub!\n", BX_reg(context) );
994         SET_AX( context, 0x8011 ); /* descriptor unavailable */
995         SET_CFLAG( context );
996         break;
997
998     case 0x000e:  /* Get Multiple Descriptors (1.0) */
999         FIXME( "get multiple descriptors - unimplemented\n" );
1000         break;
1001
1002     case 0x000f:  /* Set Multiple Descriptors (1.0) */
1003         FIXME( "set multiple descriptors - unimplemented\n" );
1004         break;
1005
1006     case 0x0100:  /* Allocate DOS memory block */
1007         TRACE( "allocate DOS memory block (0x%x paragraphs)\n", BX_reg(context) );
1008         {
1009             DWORD dw = GlobalDOSAlloc16( (DWORD)BX_reg(context) << 4 );
1010             if (dw) {
1011                 SET_AX( context, HIWORD(dw) );
1012                 SET_DX( context, LOWORD(dw) );
1013             } else {
1014                 SET_AX( context, 0x0008 ); /* insufficient memory */
1015                 SET_BX( context, DOSMEM_Available() >> 4 );
1016                 SET_CFLAG(context);
1017             }
1018             break;
1019         }
1020
1021     case 0x0101:  /* Free DOS memory block */
1022         TRACE( "free DOS memory block (0x%04x)\n", DX_reg(context) );
1023         {
1024             WORD error = GlobalDOSFree16( DX_reg(context) );
1025             if (error) {
1026                 SET_AX( context, 0x0009 ); /* memory block address invalid */
1027                 SET_CFLAG( context );
1028             }
1029         }
1030         break;
1031
1032     case 0x0102: /* Resize DOS Memory Block */
1033         FIXME( "resize DOS memory block (0x%04x, 0x%x paragraphs) - unimplemented\n", 
1034                DX_reg(context), BX_reg(context) );
1035         break;
1036
1037     case 0x0200: /* get real mode interrupt vector */
1038         TRACE( "get realmode interupt vector (0x%02x)\n",
1039                BL_reg(context) );
1040         {
1041             FARPROC16 proc = DOSVM_GetRMHandler( BL_reg(context) );
1042             SET_CX( context, SELECTOROF(proc) );
1043             SET_DX( context, OFFSETOF(proc) );
1044         }
1045         break;
1046
1047     case 0x0201: /* set real mode interrupt vector */
1048         TRACE( "set realmode interrupt vector (0x%02x, 0x%04x:0x%04x)\n", 
1049                BL_reg(context), CX_reg(context), DX_reg(context) );
1050         DOSVM_SetRMHandler( BL_reg(context), 
1051                             (FARPROC16)MAKESEGPTR(CX_reg(context), DX_reg(context)) );
1052         break;
1053
1054     case 0x0202:  /* Get Processor Exception Handler Vector */
1055         FIXME( "Get Processor Exception Handler Vector (0x%02x)\n",
1056                BL_reg(context) );
1057         if (DOSVM_IsDos32()) 
1058         {
1059             SET_CX( context, 0 );
1060             context->Edx = 0;
1061         } 
1062         else 
1063         {
1064             SET_CX( context, 0 );
1065             SET_DX( context, 0 );
1066         }
1067         break;
1068
1069     case 0x0203:  /* Set Processor Exception Handler Vector */
1070          FIXME( "Set Processor Exception Handler Vector (0x%02x)\n",
1071                 BL_reg(context) );
1072          break;
1073
1074     case 0x0204:  /* Get protected mode interrupt vector */
1075         TRACE("get protected mode interrupt handler (0x%02x)\n",
1076               BL_reg(context));
1077         if (DOSVM_IsDos32()) 
1078         {
1079             FARPROC48 handler = DOSVM_GetPMHandler48( BL_reg(context) );
1080             SET_CX( context, handler.selector );
1081             context->Edx = handler.offset;
1082         } 
1083         else 
1084         {
1085             FARPROC16 handler = DOSVM_GetPMHandler16( BL_reg(context) );
1086             SET_CX( context, SELECTOROF(handler) );
1087             SET_DX( context, OFFSETOF(handler) );
1088         }
1089         break;
1090
1091     case 0x0205:  /* Set protected mode interrupt vector */
1092         TRACE("set protected mode interrupt handler (0x%02x,0x%04x:0x%08lx)\n",
1093               BL_reg(context), CX_reg(context), context->Edx);
1094         if (DOSVM_IsDos32()) 
1095         {
1096             FARPROC48 handler;
1097             handler.selector = CX_reg(context);
1098             handler.offset = context->Edx;
1099             DOSVM_SetPMHandler48( BL_reg(context), handler );
1100         } 
1101         else 
1102         {
1103             FARPROC16 handler;
1104             handler = (FARPROC16)MAKESEGPTR( CX_reg(context), DX_reg(context)); 
1105             DOSVM_SetPMHandler16( BL_reg(context), handler );
1106         }
1107         break;
1108
1109     case 0x0300:  /* Simulate real mode interrupt */
1110         DOSVM_CallRMInt( context );
1111         break;
1112
1113     case 0x0301:  /* Call real mode procedure with far return */
1114         DOSVM_CallRMProc( context, FALSE );
1115         break;
1116
1117     case 0x0302:  /* Call real mode procedure with interrupt return */
1118         DOSVM_CallRMProc( context, TRUE );
1119         break;
1120
1121     case 0x0303:  /* Allocate Real Mode Callback Address */
1122         DOSVM_AllocRMCB( context );
1123         break;
1124
1125     case 0x0304:  /* Free Real Mode Callback Address */
1126         DOSVM_FreeRMCB( context );
1127         break;
1128
1129     case 0x0305:  /* Get State Save/Restore Addresses */
1130         TRACE("get state save/restore addresses\n");
1131         /* we probably won't need this kind of state saving */
1132         SET_AX( context, 0 );
1133
1134         /* real mode: just point to the lret */
1135         SET_BX( context, DOSVM_dpmi_segments->wrap_seg );
1136         SET_CX( context, 2 );
1137
1138         /* protected mode: don't have any handler yet... */
1139         /* FIXME: Use DI in 16-bit DPMI and EDI in 32-bit DPMI */
1140         FIXME("no protected-mode dummy state save/restore handler yet\n");
1141         SET_SI( context, 0 );
1142         context->Edi = 0;
1143         break;
1144
1145     case 0x0306:  /* Get Raw Mode Switch Addresses */
1146         TRACE("get raw mode switch addresses\n");
1147
1148         /* real mode, point to standard DPMI return wrapper */
1149         SET_BX( context, DOSVM_dpmi_segments->wrap_seg );
1150         SET_CX( context, 0 );
1151
1152         /* protected mode, point to DPMI call wrapper */
1153         /* FIXME: Use DI in 16-bit DPMI and EDI in 32-bit DPMI */
1154         /* FIXME: Doesn't work in DPMI32... */
1155         SET_SI( context, DOSVM_dpmi_segments->dpmi_sel );
1156         context->Edi = 8; /* offset of the INT 0x31 call */
1157         break;
1158
1159     case 0x0400:  /* Get DPMI version */
1160         TRACE("get DPMI version\n");
1161         {
1162             SYSTEM_INFO si;
1163
1164             GetSystemInfo(&si);
1165             SET_AX( context, 0x005a );  /* DPMI version 0.90 */
1166             SET_BX( context, 0x0005 );  /* Flags: 32-bit, virtual memory */
1167             SET_CL( context, si.wProcessorLevel );
1168             SET_DX( context, 0x0102 );  /* Master/slave interrupt controller base */
1169         }
1170         break;
1171
1172     case 0x0401:  /* Get DPMI Capabilities (1.0) */
1173         FIXME( "get dpmi capabilities - unimplemented\n");
1174         break;
1175
1176     case 0x0500:  /* Get free memory information */
1177         TRACE("get free memory information\n");
1178         {
1179             MEMMANINFO mmi;
1180             void *ptr = CTX_SEG_OFF_TO_LIN( context,
1181                                             context->SegEs, 
1182                                             context->Edi );
1183
1184             mmi.dwSize = sizeof( mmi );
1185             MemManInfo16( &mmi );
1186
1187             /* the layout is just the same as MEMMANINFO, but without
1188              * the dwSize entry.
1189              */
1190             memcpy( ptr, ((char*)&mmi)+4, sizeof(mmi)-4 );
1191             break;
1192         }
1193
1194     case 0x0501:  /* Allocate memory block */
1195         {
1196             DWORD size = MAKELONG( CX_reg(context), BX_reg(context) );
1197             BYTE *ptr;
1198
1199             TRACE( "allocate memory block (%ld bytes)\n", size );
1200
1201             ptr = (BYTE *)DPMI_xalloc( size );
1202             if (!ptr)
1203             {
1204                 SET_AX( context, 0x8012 );  /* linear memory not available */
1205                 SET_CFLAG(context);
1206             } 
1207             else 
1208             {
1209                 SET_BX( context, HIWORD(ptr) );
1210                 SET_CX( context, LOWORD(ptr) );
1211                 SET_SI( context, HIWORD(ptr) );
1212                 SET_DI( context, LOWORD(ptr) );
1213             }
1214             break;
1215         }
1216
1217     case 0x0502:  /* Free memory block */
1218         {
1219             DWORD handle = MAKELONG( DI_reg(context), SI_reg(context) );
1220             TRACE( "free memory block (0x%08lx)\n", handle );
1221             DPMI_xfree( (void *)handle );
1222         }
1223         break;
1224
1225     case 0x0503:  /* Resize memory block */
1226         {
1227             DWORD size = MAKELONG( CX_reg(context), BX_reg(context) );
1228             DWORD handle = MAKELONG( DI_reg(context), SI_reg(context) );
1229             BYTE *ptr;
1230
1231             TRACE( "resize memory block (0x%08lx, %ld bytes)\n", handle, size );
1232
1233             ptr = (BYTE *)DPMI_xrealloc( (void *)handle, size );
1234             if (!ptr)
1235             {
1236                 SET_AX( context, 0x8012 );  /* linear memory not available */
1237                 SET_CFLAG(context);
1238             } else {
1239                 SET_BX( context, HIWORD(ptr) );
1240                 SET_CX( context, LOWORD(ptr) );
1241                 SET_SI( context, HIWORD(ptr) );
1242                 SET_DI( context, LOWORD(ptr) );
1243             }
1244         }
1245         break;
1246
1247     case 0x0507:  /* Set page attributes (1.0) */
1248         FIXME("set page attributes unimplemented\n");
1249         break;  /* Just ignore it */
1250
1251     case 0x0600:  /* Lock linear region */
1252         FIXME("lock linear region unimplemented\n");
1253         break;  /* Just ignore it */
1254
1255     case 0x0601:  /* Unlock linear region */
1256         FIXME("unlock linear region unimplemented\n");
1257         break;  /* Just ignore it */
1258
1259     case 0x0602:  /* Unlock real-mode region */
1260         FIXME("unlock realmode region unimplemented\n");
1261         break;  /* Just ignore it */
1262
1263     case 0x0603:  /* Lock real-mode region */
1264         FIXME("lock realmode region unimplemented\n");
1265         break;  /* Just ignore it */
1266
1267     case 0x0604:  /* Get page size */
1268         TRACE("get pagesize\n");
1269         SET_BX( context, HIWORD(getpagesize()) );
1270         SET_CX( context, LOWORD(getpagesize()) );
1271         break;
1272
1273     case 0x0702:  /* Mark page as demand-paging candidate */
1274         FIXME("mark page as demand-paging candidate\n");
1275         break;  /* Just ignore it */
1276
1277     case 0x0703:  /* Discard page contents */
1278         FIXME("discard page contents\n");
1279         break;  /* Just ignore it */
1280
1281     case 0x0800:  /* Physical address mapping */
1282         FIXME( "physical address mapping (0x%08lx) - unimplemented\n", 
1283                MAKELONG(CX_reg(context),BX_reg(context)) );
1284         break;
1285
1286     default:
1287         INT_BARF( context, 0x31 );
1288         SET_AX( context, 0x8001 );  /* unsupported function */
1289         SET_CFLAG(context);
1290         break;
1291     }  
1292 }