]> 4ch.mooo.com Git - 16.git/blob - src/lib/doslib/hw/cpu/v86kern.asm
added a bunch of things~ and midi stuff~
[16.git] / src / lib / doslib / hw / cpu / v86kern.asm
1 ; v86kern.asm
2 ;
3 ; Test program: Proof-of-concept minimalist virtual 8086 "monitor"
4 ; (C) 2010-2012 Jonathan Campbell.
5 ; Hackipedia DOS library.
6 ;
7 ; This code is licensed under the LGPL.
8 ; <insert LGPL legal text here>
9 ;
10 ; MODE: 16-bit real mode MS-DOS .COM executable
11 ; *THIS CODE IS OBSOLETE*
12 ;       Assumes DS == ES == SS
13
14 ; NOTES:
15 ;   - This works... for the most part.
16 ;   - Somehow this works even with DOSBox's funky ROM-based interrupt emulation
17 ;   - The emulation provided is sufficient for real-mode exceptions including INT 3h debug and
18 ;     INT 1h trace. It also handles the correct exception to permit v86 programs to use the
19 ;     FPU if present.
20 ; FIXME:
21 ;   - Privileged instructions like mov cr0,<reg> trigger an exception and this program makes no
22 ;     attempt to emulate those instructions.
23 ;   - This code makes no attempt to emulate the LDT manipulation that most BIOS implementations
24 ;     apparently like to do when handling INT 15H extended memory copy. Programs that use extended
25 ;     memory via HIMEM.SYS or via INT 15H will crash.
26 ;   - For reasons unknown to me, running this under Windows 95 pure DOS mode is crashy. It will run
27 ;     for awhile but eventually, things will hang. Under QEMU, running another program or a 3rd
28 ;     will trigger a sudden reset, which mirrors behavior seen on an actual Pentium system. For
29 ;     other unknown reasons, Bochs and DOSBox run this code just fine.
30 ;   - Whatever the BIOS does in response to CTRL+ALT+DEL it doesn't work well when we are active.
31 ;
32 ; This code manages virtual 8086 mode in a suboptimal way. A better implementation is provided in
33 ; v86kern2.asm
34 ;
35 ; FIXME: Okay now this is crashing. Why?
36
37 ; Standard selectors in protected mode
38 NULL_SEL        equ             (0 << 3)
39 CODE16_SEL      equ             (1 << 3)
40 DATA16_SEL      equ             (2 << 3)
41 CODE32_SEL      equ             (3 << 3)
42 DATA32_SEL      equ             (4 << 3)
43 FLAT16_SEL      equ             (5 << 3)
44 FLAT32_SEL      equ             (6 << 3)
45 LDT_SEL         equ             (7 << 3)
46 TSS_SEL         equ             (8 << 3)
47 TSS_VM86_SEL    equ             (9 << 3)
48 MAX_SEL         equ             (10 << 3)
49
50 ; We reprogram the PIC to direct IRQ 0-15 to this base interrupt
51 IRQ_BASE_INT    equ             0x68
52 RM_INT_API      equ             0x66
53
54 ; Extensible virtual 8086 mode kernel for DOS
55 ; (C) 2011 Jonathan Campbell
56
57                 bits            16
58                 section         .code
59                 [map            v86kern.map]
60                 org             0x100
61
62 ; ============= ENTRY POINT
63                 mov             ax,cs
64                 mov             word [my_realmode_seg],ax
65                 mov             bp,stack_base
66                 mov             sp,stack_init                   ; SP is normally at 0xFFF0 so move it back down
67                 mov             word [himem_sys_buffer_handle],0
68                 mov             byte [user_req_unload],0
69                 mov             byte [user_req_iopl],3
70                 mov             byte [irq_pending],0
71                 mov             byte [i_am_tsr],0
72                 mov             byte [v86_if],0
73                 jmp             _entry
74
75 ; ============= CPU DETECT
76 cpu_is_386:     pushf
77                 pop             ax
78                 and             ax,0x0FFF
79                 push            ax
80                 popf
81                 pushf
82                 pop             ax
83                 and             ax,0xF000
84                 cmp             ax,0xF000
85                 jz              cpu_is_386_not
86 ; 286 test: EFLAGS will always have bits 12-15 clear
87                 or              ax,0xF000
88                 push            ax
89                 popf
90                 pushf
91                 pop             ax
92                 and             ax,0xF000
93                 jz              cpu_is_386_not
94 ; it's a 386
95                 xor             ax,ax                   ; ZF=1
96                 ret
97 cpu_is_386_not: mov             ax,1
98                 or              ax,ax                   ; ZF=0
99                 ret
100
101 ; ============= EXIT WITH MESSAGE ($-terminated string at DS:DX)
102 _exit_with_msg: mov             ah,9
103                 int             21h                     ; fall through to _exit
104 ; ============= EXIT
105 _exit:          mov             ax,cs
106                 mov             ds,ax
107                 cmp             word [himem_sys_buffer_handle],0 ; if there is a handle to free, then do it
108                 jz              .no_handle
109                 mov             ah,0Dh                  ; HIMEM.SYS function 0Dh unlock memory block
110                 mov             dx,word [himem_sys_buffer_handle]
111                 call far        word [himem_sys_entry]
112                 mov             ah,0Ah                  ; HIMEM.SYS function 0Ah free memory block
113                 mov             dx,word [himem_sys_buffer_handle]
114                 call far        word [himem_sys_entry]
115 .no_handle:     mov             ax,4C00h
116                 int             21h
117
118 ; ============= PROGRAM STARTS HERE
119 _entry:         call            parse_argv
120                 jz              .argv_ok
121                 mov             dx,str_help
122                 call            _exit_with_msg
123 .argv_ok:       call            cpu_is_386              ; CHECK: 386 or higher
124                 jz              .is386
125                 mov             dx,str_require_386
126                 jmp             _exit_with_msg
127 .is386:         cmp             byte [user_req_unload],0; CHECK: Did user request that we unload?
128                 jz              .not_unload
129                 jmp             unload_this_program
130 .not_unload:    smsw            ax                      ; CHECK: Virtual 8086 mode not already enabled
131                 test            al,1
132                 jz              .not_v86
133                 mov             dx,str_v86_detected
134                 jmp             _exit_with_msg
135 .not_v86:       cmp             dword [himem_sys_buffer_size],64*1024   ; CHECK: buffer size is 64KB or larger
136                 jge             .buffer_size_large_enough
137                 mov             dx,str_buffer_too_small
138                 jmp             _exit_with_msg
139 .buffer_size_large_enough:
140                 cmp             dword [himem_sys_buffer_size],16*1024*1024
141                 jle             .buffer_size_small_enough
142                 mov             dx,str_buffer_too_large
143                 jmp             _exit_with_msg
144 .buffer_size_small_enough:
145                 mov             ax,4300h                ; CHECK: HIMEM.SYS is present
146                 int             2Fh
147                 cmp             al,80h
148                 jz              .yes_himem_sys
149                 mov             dx,str_need_himem_sys
150                 jmp             _exit_with_msg
151 .yes_himem_sys: mov             ax,4310h                ; Get HIMEM.SYS entry point (cannot fail)
152                 int             2Fh
153                 mov             word [himem_sys_entry],bx
154                 mov             word [himem_sys_entry+2],es
155                 mov             ah,5h                   ; HIMEM.SYS Local Enable A20
156                 call far        word [himem_sys_entry]
157                 cmp             ax,1
158                 jz              .yes_himem_a20
159                 mov             dx,str_himem_a20_error
160                 jmp             _exit_with_msg
161 .yes_himem_a20: mov             ah,09h                  ; HIMEM.SYS allocate block
162                 cli                                     ; <- in case BIOS interrupts do not save upper 16 bits
163                 mov             edx,[himem_sys_buffer_size]
164                 add             edx,1023
165                 shr             edx,10                  ; EDX = (X BYTES+1023)/1024 KB
166                 call far        word [himem_sys_entry]
167                 cmp             ax,1
168                 jz              .yes_himem_buf
169                 mov             dx,str_himem_alloc_err
170                 jmp             _exit_with_msg
171 .yes_himem_buf: mov             word [himem_sys_buffer_handle],dx ; store memory handle
172                 mov             ah,0Ch                  ; HIMEM.SYS lock memory block
173                 call far        word [himem_sys_entry]  ; NOTE: DX = memory handle (still)
174                 cmp             ax,1
175                 jz              .yes_himem_lock
176                 mov             dx,str_himem_lock_err
177                 jmp             _exit_with_msg
178 .yes_himem_lock:mov             word [himem_sys_buffer_phys],bx ; store DX:BX physical memory address
179                 mov             word [himem_sys_buffer_phys+2],dx
180
181 ; choose where things go within the buffer
182 ;        = 104 bytes for main TSS
183                 mov             eax,[himem_sys_buffer_phys]
184                 mov             [tss_phys_base],eax
185                 add             eax,128
186 ;        = 8192+104 bytes for VM86 TSS
187                 mov             [tss_vm86_phys_base],eax
188                 add             eax,8192+128
189 ;        = 4096 for kernel 32 stack
190                 mov             [kern32_stack_base],eax
191                 add             eax,4096
192                 lea             ebx,[eax-8]
193                 mov             [kern32_stack_top],ebx
194 ;        = store it for future allocation
195                 mov             [buffer_alloc],eax
196
197 ; PRINT "BUFFER AT: " + *((DWORD*)himem_sys_buffer_phys) + "\n"
198                 mov             dx,str_buffer_at
199                 call            dos_puts
200                 cli
201                 mov             eax,[himem_sys_buffer_phys]
202                 mov             di,scratch_str
203                 call            eax_to_hex_16_dos
204                 mov             dx,di
205                 call            dos_puts
206
207                 cli
208                 mov             eax,[himem_sys_buffer_phys]
209                 add             eax,[himem_sys_buffer_size]
210                 dec             eax
211                 mov             byte [scratch_str],'-'
212                 mov             di,scratch_str+1
213                 call            eax_to_hex_16_dos
214                 mov             dx,scratch_str
215                 call            dos_puts
216
217                 mov             dx,str_crlf
218                 call            dos_puts
219
220                 xor             eax,eax
221                 mov             ax,cs
222                 mov             es,ax
223                 shl             eax,4
224                 mov             dword [my_phys_base],eax
225
226 ; clear the IDT and GDT
227                 cld
228                 xor             ax,ax
229
230                 mov             cx,MAX_SEL / 2
231                 mov             di,gdt
232                 rep             stosw
233
234 ; prepare the IDTR and GDTR.
235 ; real mode versions: limit=0xFFFF base=0
236                 xor             eax,eax
237                 dec             ax                      ; AX = 0xFFFF
238                 mov             word [idtr_real],ax
239                 mov             word [gdtr_real],ax
240                 inc             ax
241                 mov             dword [idtr_real+2],eax
242                 mov             dword [gdtr_real+2],eax
243 ; protected mode GDTR limit=MAX_SEL-1 base=(code segment)+var
244                 mov             word [gdtr_pmode],MAX_SEL - 1
245                 mov             word [idtr_pmode],(256 << 3) - 1
246                 mov             eax,[my_phys_base]
247                 add             eax,gdt
248                 mov             dword [gdtr_pmode+2],eax
249                 mov             eax,[my_phys_base]
250                 add             eax,idt
251                 mov             dword [idtr_pmode+2],eax
252
253 ; build the GDT
254                 cld
255                 lea             di,[gdt+CODE16_SEL]
256 ; Code selector (CODE_16SEL)
257                 dec             ax                      ; 0x0000 - 1 = 0xFFFF
258                 stosw                                   ; LIMIT
259                 mov             ax,[my_phys_base]
260                 stosw                                   ; BASE[15:0]
261                 mov             al,[my_phys_base+2]
262                 mov             ah,0x9A
263                 stosw                                   ; BASE[23:16] access byte=executable readable
264                 mov             al,0x0F
265                 mov             ah,[my_phys_base+3]     ; LIMIT[19:16] flags=0 BASE[31:24]
266                 stosw
267 ; Data selector (DATA16_SEL)
268                 xor             ax,ax
269                 dec             ax                      ; 0xFFFF
270                 stosw                                   ; LIMIT
271                 mov             ax,[my_phys_base]
272                 stosw                                   ; BASE[15:0]
273                 mov             al,[my_phys_base+2]
274                 mov             ah,0x92
275                 stosw                                   ; BASE[23:16] access byte=data writeable
276                 mov             al,0x0F
277                 mov             ah,[my_phys_base+3]     ; LIMIT[19:16] flags=0 BASE[31:24]
278                 stosw
279 ; Code selector (CODE_32SEL)
280                 dec             ax                      ; 0x0000 - 1 = 0xFFFF
281                 stosw                                   ; LIMIT
282                 mov             ax,[my_phys_base]
283                 stosw                                   ; BASE[15:0]
284                 mov             al,[my_phys_base+2]
285                 mov             ah,0x9A
286                 stosw                                   ; BASE[23:16] access byte=executable readable
287                 mov             al,0xCF
288                 mov             ah,[my_phys_base+3]     ; LIMIT[19:16] flags=0 BASE[31:24]
289                 stosw
290 ; Data selector (DATA32_SEL)
291                 xor             ax,ax
292                 dec             ax                      ; 0xFFFF
293                 stosw                                   ; LIMIT
294                 mov             ax,[my_phys_base]
295                 stosw                                   ; BASE[15:0]
296                 mov             al,[my_phys_base+2]
297                 mov             ah,0x92
298                 stosw                                   ; BASE[23:16] access byte=data writeable
299                 mov             al,0xCF
300                 mov             ah,[my_phys_base+3]     ; LIMIT[19:16] flags=0 BASE[31:24]
301                 stosw
302 ; Data selector (FLAT16_SEL)
303                 xor             ax,ax
304                 dec             ax                      ; 0xFFFF
305                 stosw                                   ; LIMIT
306                 xor             ax,ax
307                 stosw                                   ; BASE[15:0]
308                 mov             ah,0x92
309                 stosw                                   ; BASE[23:16] access byte=data writeable
310                 mov             al,0x8F
311                 xor             ah,ah
312                 stosw
313 ; Data selector (FLAT32_SEL)
314                 xor             ax,ax
315                 dec             ax                      ; 0xFFFF
316                 stosw                                   ; LIMIT
317                 xor             ax,ax
318                 stosw                                   ; BASE[15:0]
319                 mov             ah,0x92
320                 stosw                                   ; BASE[23:16] access byte=data writeable
321                 mov             al,0xCF
322                 xor             ah,ah
323                 stosw
324 ; LDT selector (LDT_SEL)
325                 mov             ax,7                    ; I have no use for the LDT
326                 stosw                                   ; LIMIT
327                 mov             ax,[my_phys_base]
328                 stosw                                   ; BASE[15:0]
329                 mov             al,[my_phys_base+2]
330                 mov             ah,0x82
331                 stosw                                   ; BASE[23:16] access byte=data writeable LDT type 2
332                 mov             al,0x0F
333                 mov             ah,[my_phys_base+3]     ; LIMIT[19:16] flags=0 BASE[31:24]
334                 stosw
335 ; TSS selector (TSS_SEL)
336                 mov             ax,104-1
337                 stosw                                   ; LIMIT
338                 mov             ax,[tss_phys_base]
339                 stosw                                   ; BASE[15:0]
340                 mov             al,[tss_phys_base+2]
341                 mov             ah,0x89
342                 stosw                                   ; BASE[23:16] access byte=data writeable non-busy TSS type 9
343                 mov             al,0x0F
344                 mov             ah,[tss_phys_base+3]    ; LIMIT[19:16] flags=0 BASE[31:24]
345                 stosw
346 ; TSS selector (TSS_VM86_SEL)
347                 mov             ax,104+8192-1
348                 stosw                                   ; LIMIT
349                 mov             ax,[tss_vm86_phys_base]
350                 stosw                                   ; BASE[15:0]
351                 mov             al,[tss_vm86_phys_base+2]
352                 mov             ah,0x89
353                 stosw                                   ; BASE[23:16] access byte=data writeable non-busy TSS type 9
354                 mov             al,0x0F
355                 mov             ah,[tss_vm86_phys_base+3] ; LIMIT[19:16] flags=0 BASE[31:24]
356                 stosw
357
358 ; prepare the CPU registers
359                 lidt            [idtr_pmode]
360                 lgdt            [gdtr_pmode]
361
362 ; enter protected mode
363                 mov             eax,1
364                 mov             cr0,eax
365                 jmp             CODE16_SEL:pmode16_entry
366 pmode16_entry:  mov             ax,DATA16_SEL
367                 mov             ds,ax
368                 mov             es,ax
369                 mov             fs,ax
370                 mov             gs,ax
371                 mov             ss,ax
372                 mov             sp,stack_init
373
374 ; load task register
375                 mov             ax,TSS_SEL
376                 ltr             ax
377
378 ; load LDT
379                 mov             ax,LDT_SEL
380                 lldt            ax
381
382 ; now enter 32-bit protected mode
383                 jmp             CODE32_SEL:pmode32_entry
384                 bits            32
385 pmode32_entry:  mov             ax,DATA32_SEL
386                 mov             ds,ax
387                 mov             es,ax
388                 mov             ss,ax
389                 mov             ax,FLAT32_SEL
390                 mov             fs,ax
391                 mov             gs,ax
392                 mov             esp,stack_init
393 ; at this point: we are in 32-bit protected mode!
394
395 ; ============= setup the TSS representing our task (for when we return)
396                 cld
397                 mov             edi,[tss_phys_base]
398                 sub             edi,[my_phys_base]
399
400                 xor             eax,eax                                 ; TSS+0x00 = no backlink
401                 stosd
402                 mov             eax,[kern32_stack_top]                  ; TSS+0x04 = ESP for CPL0
403                 sub             eax,[my_phys_base]
404                 stosd
405                 mov             eax,DATA32_SEL                          ; TSS+0x08 = SS for CPL0
406                 stosd
407                 mov             eax,[kern32_stack_top]                  ; TSS+0x0C = ESP for CPL1
408                 sub             eax,[my_phys_base]
409                 stosd
410                 mov             eax,DATA32_SEL                          ; TSS+0x10 = SS for CPL1
411                 stosd
412                 mov             eax,[kern32_stack_top]                  ; TSS+0x14 = ESP for CPL2
413                 sub             eax,[my_phys_base]
414                 stosd
415                 mov             eax,DATA32_SEL                          ; TSS+0x18 = SS for CPL2
416                 stosd
417                 xor             eax,eax                                 ; TSS+0x1C = CR3
418                 stosd
419                 mov             eax,vm86_entry                          ; TSS+0x20 = EIP
420                 stosd
421                 mov             eax,0x00000002                          ; TSS+0x24 = EFLAGS VM=0
422                 stosd
423                 xor             eax,eax                                 ; TSS+0x28 = EAX
424                 stosd
425                 xor             eax,eax                                 ; TSS+0x2C = ECX
426                 stosd
427                 xor             eax,eax                                 ; TSS+0x30 = EDX
428                 stosd
429                 xor             eax,eax                                 ; TSS+0x34 = EBX
430                 stosd
431                 mov             eax,stack_init_vm86                     ; TSS+0x38 = ESP
432                 stosd
433                 xor             eax,eax                                 ; TSS+0x3C = EBP
434                 stosd
435                 xor             eax,eax                                 ; TSS+0x40 = ESI
436                 stosd
437                 xor             eax,eax                                 ; TSS+0x44 = EDI
438                 stosd
439                 mov             ax,DATA32_SEL                           ; TSS+0x48 = ES
440                 stosd
441                 mov             ax,CODE32_SEL                           ; TSS+0x4C = CS
442                 stosd
443                 mov             ax,DATA32_SEL                           ; TSS+0x50 = SS
444                 stosd
445                 mov             ax,DATA32_SEL                           ; TSS+0x54 = DS
446                 stosd
447                 mov             ax,DATA32_SEL                           ; TSS+0x58 = FS
448                 stosd
449                 mov             ax,DATA32_SEL                           ; TSS+0x5C = GS
450                 stosd
451                 xor             eax,eax                                 ; TSS+0x60 = LDTR
452                 stosd
453                 mov             eax,(104 << 16)                         ; TSS+0x64 = I/O map base
454                 stosd
455
456 ; ============= setup the TSS representing the virtual 8086 mode task
457                 cld
458                 mov             edi,[tss_vm86_phys_base]
459                 sub             edi,[my_phys_base]
460
461                 xor             eax,eax                                 ; TSS+0x00 = no backlink
462                 stosd
463                 mov             eax,[kern32_stack_top]                  ; TSS+0x04 = ESP for CPL0
464                 sub             eax,[my_phys_base]
465                 stosd
466                 mov             eax,DATA32_SEL                          ; TSS+0x08 = SS for CPL0
467                 stosd
468                 mov             eax,[kern32_stack_top]                  ; TSS+0x0C = ESP for CPL1
469                 sub             eax,[my_phys_base]
470                 stosd
471                 mov             eax,DATA32_SEL                          ; TSS+0x10 = SS for CPL1
472                 stosd
473                 mov             eax,[kern32_stack_top]                  ; TSS+0x14 = ESP for CPL2
474                 sub             eax,[my_phys_base]
475                 stosd
476                 mov             eax,DATA32_SEL                          ; TSS+0x18 = SS for CPL2
477                 stosd
478                 xor             eax,eax                                 ; TSS+0x1C = CR3
479                 stosd
480                 mov             eax,vm86_entry                          ; TSS+0x20 = EIP
481                 stosd
482                 mov             eax,0x00020202                          ; TSS+0x24 = EFLAGS VM=1 IOPL=N IF=1
483                 movzx           ebx,byte [user_req_iopl]
484                 and             bl,3
485                 shl             ebx,12
486                 or              eax,ebx                                 ; EFLAGS |= user_req_iopl << 12
487                 stosd
488                 xor             eax,eax                                 ; TSS+0x28 = EAX
489                 stosd
490                 xor             eax,eax                                 ; TSS+0x2C = ECX
491                 stosd
492                 xor             eax,eax                                 ; TSS+0x30 = EDX
493                 stosd
494                 xor             eax,eax                                 ; TSS+0x34 = EBX
495                 stosd
496                 mov             eax,stack_init                          ; TSS+0x38 = ESP
497                 stosd
498                 xor             eax,eax                                 ; TSS+0x3C = EBP
499                 stosd
500                 xor             eax,eax                                 ; TSS+0x40 = ESI
501                 stosd
502                 xor             eax,eax                                 ; TSS+0x44 = EDI
503                 stosd
504                 mov             ax,[my_realmode_seg]                    ; TSS+0x48 = ES
505                 stosd
506                 mov             ax,[my_realmode_seg]                    ; TSS+0x4C = CS
507                 stosd
508                 mov             ax,[my_realmode_seg]                    ; TSS+0x50 = SS
509                 stosd
510                 mov             ax,[my_realmode_seg]                    ; TSS+0x54 = DS
511                 stosd
512                 mov             ax,[my_realmode_seg]                    ; TSS+0x58 = FS
513                 stosd
514                 mov             ax,[my_realmode_seg]                    ; TSS+0x5C = GS
515                 stosd
516                 xor             eax,eax                                 ; TSS+0x60 = LDTR
517                 stosd
518                 mov             eax,(104 << 16)                         ; TSS+0x64 = I/O map base
519                 stosd
520                 xor             eax,eax
521                 mov             ecx,8192 >> 2                           ; TSS+0x68 = I/O permission map (pre-set to all open)
522                 rep             stosd
523
524 ; set up the IDT
525                 cld
526
527                 mov             ecx,0x100
528                 mov             edi,idt
529 .idtdef:        mov             ax,fault_no_int         ; no interrupt assigned procedure
530                 stosw                                   ; base[15:0]
531                 mov             ax,CODE32_SEL
532                 stosw
533                 mov             ax,0x8E00               ; DPL=3
534                 stosw
535                 xor             ax,ax
536                 stosw
537                 loop            .idtdef
538
539                 mov             esi,fault_routines
540                 mov             ecx,0x20
541                 mov             edi,idt
542 .idtsetup:      lodsw
543                 stosw                                   ; base[15:0]
544                 mov             ax,CODE32_SEL
545                 stosw
546                 mov             ax,0x8E00               ; DPL=3
547                 stosw
548                 xor             ax,ax
549                 stosw
550                 loop            .idtsetup
551
552                 cld
553                 mov             esi,irq_routines
554                 mov             ecx,0x10
555                 mov             edi,idt + (IRQ_BASE_INT*8)
556 .idtsetup2:     lodsw
557                 stosw                                   ; base[15:0]
558                 mov             ax,CODE32_SEL
559                 stosw
560                 mov             ax,0x8E00               ; you must set DPL=3
561                 stosw
562                 xor             ax,ax
563                 stosw
564                 loop            .idtsetup2
565
566 ; next we need to reprogram the PIC so that IRQ 0-7 do not conflict with the CPU exceptions.
567 ; note for stability we only reprogram first PIC, since we do not relocate the 2nd PIC.
568                 mov             al,0x10                 ; ICW1 A0=0
569                 out             20h,al
570                 mov             al,IRQ_BASE_INT         ; ICW2 A0=1
571                 out             21h,al
572                 mov             al,0x04                 ; ICW3 A0=1 slave on IRQ 2
573                 out             21h,al
574
575 ; jump into virtual 8086 mode
576                 jmp             TSS_VM86_SEL:0
577
578 ; =============== IRQ handler code
579
580 int_rm_map:     db              0x08,0x09,0x0A,0x0B,0x0C,0x0D,0x0E,0x0F
581                 db              0x70,0x71,0x72,0x73,0x74,0x75,0x76,0x77
582
583 irq_priority:   db              0,1,8,9,10,11,12,13,14,15,2,3,4,5,6,7
584         ; ^ 16 entries, reflecting IRQ 8-15 -> IRQ 2 (slave PIC) and IRQ 0-7 (master PIC) cascade
585
586 ; EAX = IRQ that fired
587 ;  [ESP+0] = old EAX
588 ;  [ESP+4] = EIP
589 ;  [ESP+8] = CS
590 ;  [ESP+12] = EFLAGS
591 ;  [ESP+16] = ESP
592 ;  [ESP+20] = SS
593 ;  [ESP+24] = ES
594 ;  [ESP+28] = DS
595 ;  [ESP+32] = FS
596 ;  [ESP+36] = GS
597 irq_general:    test            dword [esp+12],0x20000  ; did the interrupt happen while in v86 mode?
598                 jnz             .reflect_v86
599 ; this happened while NOT in v86 mode. We should still reflect it back to v86 mode.
600 ;   ----------------------TODO--------------------
601                 call            fault_collect_regs
602                 mov             edx,0x00
603                 mov             esi,str_irq_1
604                 jmp             fault_jmp_unhandled
605 ;   ----------------------------------------------
606 ; CPU was in v86 mode. Modify stack pointer to reflect the interrupt.
607 .reflect_v86:   test            dword [esp+12],0x200    ; are interrupts enabled in the vm?
608                 jz              .reflect_v86_pending    ; if not, then we need to note it and reflect later
609                 push            ebx
610                 push            ecx
611                 mov             bx,FLAT32_SEL           ; NTS: Don't worry about saving ES. The CPU saved
612                 mov             ds,bx                   ; it as part of the v86 -> interrupt transition.
613                 xor             ebx,ebx
614                 mov             ecx,ebx
615                 mov             bl,[cs:int_rm_map+eax]  ; IRQ -> interrupt
616                 mov             ebx,[ebx*4]             ; interrupt -> realmode vector
617                 mov             ax,[esp+20+8]           ; fetch SS
618                 shl             eax,4                   ; EAX = SS*16
619                 mov             cx,[esp+16+8]           ; fetch SP
620                 sub             cx,6                    ; SP -= 6
621                 add             eax,ecx                 ; EAX = SS*16 + SP
622                 mov             [esp+16+8],cx           ; store modified SP back
623 ; EBX = realmode interrupt vector
624 ; EAX = stack pointer (physical mem addr)
625                 mov             cx,[esp+4+8]            ; fetch EIP
626                 mov             word [eax+0],cx         ; SS:SP = offset
627                 mov             cx,[esp+8+8]            ; fetch CS
628                 mov             word [eax+2],cx         ; SS:SP+2 = segment
629                 mov             cx,[esp+12+8]           ; fetch FLAGS
630                 mov             word [eax+4],cx         ; SS:SP+4 = flags
631                 mov             [esp+4+8],bx            ; overwrite IP = offset of vector
632                 shr             ebx,16
633                 mov             [esp+8+8],bx            ; overwrite CS = segment of vector
634
635 ; *DEBUG*
636                 inc             word [0xB8000]
637
638                 pop             ecx
639                 pop             ebx
640                 pop             eax
641                 iret
642 ; v86 mode, but interrupts are disabled
643 .reflect_v86_pending:
644                 push            ebx
645                 push            ecx
646                 mov             bx,DATA32_SEL
647                 mov             ds,bx
648                 mov             cl,al                   ; CL = IRQ
649                 mov             eax,1
650                 shl             eax,cl                  ; EAX = 1 << IRQ
651                 or              word [irq_pending],ax   ; irq_pending |= 1 << IRQ
652                 pop             ecx
653                 pop             ebx
654                 pop             eax
655                 iret
656
657 irq_0:          push            eax
658                 mov             eax,0
659                 jmp             irq_general
660
661 irq_1:          push            eax
662                 mov             eax,1
663                 jmp             irq_general
664
665 irq_2:          push            eax
666                 mov             eax,2
667                 jmp             irq_general
668
669 irq_3:          push            eax
670                 mov             eax,3
671                 jmp             irq_general
672
673 irq_4:          push            eax
674                 mov             eax,4
675                 jmp             irq_general
676
677 irq_5:          push            eax
678                 mov             eax,5
679                 jmp             irq_general
680
681 irq_6:          push            eax
682                 mov             eax,6
683                 jmp             irq_general
684
685 irq_7:          push            eax
686                 mov             eax,7
687                 jmp             irq_general
688
689 irq_8:          push            eax
690                 mov             eax,8
691                 jmp             irq_general
692
693 irq_9:          push            eax
694                 mov             eax,9
695                 jmp             irq_general
696
697 irq_10:         push            eax
698                 mov             eax,10
699                 jmp             irq_general
700
701 irq_11:         push            eax
702                 mov             eax,11
703                 jmp             irq_general
704
705 irq_12:         push            eax
706                 mov             eax,12
707                 jmp             irq_general
708
709 irq_13:         push            eax
710                 mov             eax,13
711                 jmp             irq_general
712
713 irq_14:         push            eax
714                 mov             eax,14
715                 jmp             irq_general
716
717 irq_15:         push            eax
718                 mov             eax,15
719                 jmp             irq_general
720
721 ; =============== GENERAL PURPOSE "NO INTERRUPT ASSIGNED" HANDLER
722 fault_no_int:   iret
723
724 fault_x86_vector:db             0
725 ; =============== REFLECT EXCEPTION TO REAL MODE
726 fault_v86_reflect:
727                 push            eax
728                 push            ebx
729                 push            ecx
730                 mov             bx,FLAT32_SEL           ; NTS: Don't worry about saving ES. The CPU saved
731                 mov             ds,bx                   ; it as part of the v86 -> interrupt transition.
732                 xor             ebx,ebx
733                 mov             ecx,ebx
734                 mov             bl,[cs:fault_x86_vector]; what interrupt is involved?
735                 mov             ebx,[ebx*4]             ; interrupt -> realmode vector
736                 mov             ax,[esp+20+8]           ; fetch SS
737                 shl             eax,4                   ; EAX = SS*16
738                 mov             cx,[esp+16+8]           ; fetch SP
739                 sub             cx,6                    ; SP -= 6
740                 add             eax,ecx                 ; EAX = SS*16 + SP
741                 mov             [esp+16+8],cx           ; store modified SP back
742 ; EBX = realmode interrupt vector
743 ; EAX = stack pointer (physical mem addr)
744                 mov             cx,[esp+4+8]            ; fetch EIP
745                 mov             word [eax+0],cx         ; SS:SP = offset
746                 mov             cx,[esp+8+8]            ; fetch CS
747                 mov             word [eax+2],cx         ; SS:SP+2 = segment
748                 mov             cx,[esp+12+8]           ; fetch FLAGS
749                 mov             word [eax+4],cx         ; SS:SP+4 = flags
750                 mov             [esp+4+8],bx            ; overwrite IP = offset of vector
751                 shr             ebx,16
752                 mov             [esp+8+8],bx            ; overwrite CS = segment of vector
753 ; if this is INT 0x01 we also need to clear the TF bit
754                 cmp             byte [cs:fault_x86_vector],1
755                 jnz             .not_int1
756                 and             word [esp+12+8],~0x100  ; clear TF
757 .not_int1:
758
759 ; *DEBUG*
760                 inc             word [0xB8002]
761
762                 pop             ecx
763                 pop             ebx
764                 pop             eax
765                 iret
766
767 ; =============== FAULT HANDLER CODE
768 fault_0x00:     push            dword 0 ; ERROR CODE
769                 call            fault_collect_regs
770                 mov             edx,0x00
771                 mov             esi,str_fault_0x00
772                 jmp             fault_jmp_unhandled
773
774 fault_0x01:     test            dword [esp+8],0x20000   ; did it happen from within v86 mode?
775                 jnz             .reflect_v86
776                 push            dword 0 ; ERROR CODE
777                 call            fault_collect_regs
778                 mov             edx,0x01
779                 mov             esi,str_fault_0x01
780                 jmp             fault_jmp_unhandled
781 .reflect_v86:   mov             byte [ss:fault_x86_vector],0x01 ; reflect to INT 0x01
782                 jmp             fault_v86_reflect
783
784 fault_0x02:     push            dword 0 ; ERROR CODE
785                 call            fault_collect_regs
786                 mov             edx,0x02
787                 mov             esi,str_fault_0x02
788                 jmp             fault_jmp_unhandled
789
790 fault_0x03:     test            dword [esp+8],0x20000   ; did it happen from within v86 mode?
791                 jnz             .reflect_v86
792                 push            dword 0 ; ERROR CODE
793                 call            fault_collect_regs
794                 mov             edx,0x03
795                 mov             esi,str_fault_0x03
796                 jmp             fault_jmp_unhandled
797 .reflect_v86:   mov             byte [ss:fault_x86_vector],0x03 ; reflect to INT 0x03
798                 jmp             fault_v86_reflect
799
800 fault_0x04:     push            dword 0 ; ERROR CODE
801                 call            fault_collect_regs
802                 mov             edx,0x04
803                 mov             esi,str_fault_0x04
804                 jmp             fault_jmp_unhandled
805
806 fault_0x05:     push            dword 0 ; ERROR CODE
807                 call            fault_collect_regs
808                 mov             edx,0x05
809                 mov             esi,str_fault_0x05
810                 jmp             fault_jmp_unhandled
811
812 fault_0x06:     push            dword 0 ; ERROR CODE
813                 call            fault_collect_regs
814                 mov             edx,0x06
815                 mov             esi,str_fault_0x06
816                 jmp             fault_jmp_unhandled
817
818 fault_0x07:     push            eax
819                 mov             eax,cr0
820                 test            eax,0x08                ; is this a result of CR0.TS being set?
821                 pop             eax
822                 jz              .not_cr0_ts
823 ; very likely a real-mode DOS application executed floating point instructions, and
824 ; the task switch into vm86 mode left bit 3 (CR0.TS) set. Clear it and return. This
825 ; is necessary to allow the DOS system to use floating point, even on 486/Pentium and
826 ; higher systems where the FPU is integral to the CPU. Even for simple instructions
827 ; like FSTSW/FNSTSW.
828                 clts
829                 iret
830 ; if the exception did NOT involve that bit, then yes, it's something to halt on
831 .not_cr0_ts:    push            dword 0 ; ERROR CODE
832                 call            fault_collect_regs
833                 mov             edx,0x07
834                 mov             esi,str_fault_0x07
835                 jmp             fault_jmp_unhandled
836
837 fault_0x08:     call            fault_collect_regs
838                 mov             edx,0x08
839                 mov             esi,str_fault_0x08
840                 jmp             fault_jmp_unhandled
841
842 fault_0x09:     push            dword 0 ; ERROR CODE
843                 call            fault_collect_regs
844                 mov             edx,0x09
845                 mov             esi,str_fault_0x09
846                 jmp             fault_jmp_unhandled
847
848 fault_0x0A:     call            fault_collect_regs
849                 mov             edx,0x0A
850                 mov             esi,str_fault_0x0A
851                 jmp             fault_jmp_unhandled
852
853 fault_0x0B:     call            fault_collect_regs
854                 mov             edx,0x0B
855                 mov             esi,str_fault_0x0B
856                 jmp             fault_jmp_unhandled
857
858 fault_0x0C:     call            fault_collect_regs
859                 mov             edx,0x0C
860                 mov             esi,str_fault_0x0C
861                 jmp             fault_jmp_unhandled
862
863 fault_0x0E:     call            fault_collect_regs
864                 mov             edx,0x0E
865                 mov             esi,str_fault_0x0E
866                 jmp             fault_jmp_unhandled
867
868 fault_0x0F:     push            dword 0 ; ERROR CODE
869                 call            fault_collect_regs
870                 mov             edx,0x0F
871                 mov             esi,str_fault_0x0F
872                 jmp             fault_jmp_unhandled
873
874 fault_0x10:     push            dword 0 ; ERROR CODE
875                 call            fault_collect_regs
876                 mov             edx,0x10
877                 mov             esi,str_fault_0x10
878                 jmp             fault_jmp_unhandled
879
880 fault_0x11:     push            dword 0 ; ERROR CODE
881                 call            fault_collect_regs
882                 mov             edx,0x11
883                 mov             esi,str_fault_0x11
884                 jmp             fault_jmp_unhandled
885
886 fault_0x12:     push            dword 0 ; ERROR CODE
887                 call            fault_collect_regs
888                 mov             edx,0x12
889                 mov             esi,str_fault_0x12
890                 jmp             fault_jmp_unhandled
891
892 fault_0x13:     push            dword 0 ; ERROR CODE
893                 call            fault_collect_regs
894                 mov             edx,0x13
895                 mov             esi,str_fault_0x13
896                 jmp             fault_jmp_unhandled
897
898 fault_0x14:     call            fault_collect_regs
899                 mov             edx,0x14
900                 jmp             fault_jmp_unhandled_unknown
901
902 fault_0x15:     call            fault_collect_regs
903                 mov             edx,0x15
904                 jmp             fault_jmp_unhandled_unknown
905
906 fault_0x16:     call            fault_collect_regs
907                 mov             edx,0x16
908                 jmp             fault_jmp_unhandled_unknown
909
910 fault_0x17:     call            fault_collect_regs
911                 mov             edx,0x17
912                 jmp             fault_jmp_unhandled_unknown
913
914 fault_0x18:     call            fault_collect_regs
915                 mov             edx,0x18
916                 jmp             fault_jmp_unhandled_unknown
917
918 fault_0x19:     call            fault_collect_regs
919                 mov             edx,0x19
920                 jmp             fault_jmp_unhandled_unknown
921
922 fault_0x1A:     call            fault_collect_regs
923                 mov             edx,0x1A
924                 jmp             fault_jmp_unhandled_unknown
925
926 fault_0x1B:     call            fault_collect_regs
927                 mov             edx,0x1B
928                 jmp             fault_jmp_unhandled_unknown
929
930 fault_0x1C:     call            fault_collect_regs
931                 mov             edx,0x1C
932                 jmp             fault_jmp_unhandled_unknown
933
934 fault_0x1D:     call            fault_collect_regs
935                 mov             edx,0x1D
936                 jmp             fault_jmp_unhandled_unknown
937
938 fault_0x1E:     call            fault_collect_regs
939                 mov             edx,0x1E
940                 jmp             fault_jmp_unhandled_unknown
941
942 fault_0x1F:     call            fault_collect_regs
943                 mov             edx,0x1F
944                 jmp             fault_jmp_unhandled_unknown
945
946 fault_jmp_unhandled_unknown:
947                 mov             esi,str_fault_unknown
948                 jmp             fault_jmp_unhandled
949
950 ; ============= EXCEPTION HANDLER: INT 0x0D GENERAL PROTECTION FAULT
951 ; If caused by v8086 mode:
952 ;  [ESP+0] = error code
953 ;  [ESP+4] = EIP
954 ;  [ESP+8] = CS
955 ;  [ESP+12] = EFLAGS
956 ;  [ESP+16] = ESP
957 ;  [ESP+20] = SS
958 ;  [ESP+24] = ES
959 ;  [ESP+28] = DS
960 ;  [ESP+32] = FS
961 ;  [ESP+36] = GS
962 ; Else, only the error code, EIP, CS, EFLAGS fields are present.
963 ; If not from ring 0, then ESP, SS are as well.
964 fault_0x0D:     test            dword [esp+12],0x20000                  ; [ESP+12] = EFLAGS. Is bit 17 (VM) set?
965                 jz              .not_vm86_related
966
967 ; at this point, we know this is the processor trapping CLI/STI or anything that a v86 monitor needs to know.
968 ; so the next thing we do is examine the opcode at CS:IP to determine what the code is trying to do, and how
969 ; to emulate it. Note the CS:IP off stack are REAL MODE addresses.
970                 pushad
971                 mov             ax,DATA32_SEL
972                 mov             ds,ax
973                 mov             es,ax
974
975                 xor             eax,eax
976                 mov             ebx,eax
977                 mov             ax,[esp+0x20+8]                         ; CS ON STACK
978                 shl             eax,4
979                 add             bx,[esp+0x20+4]                         ; EIP ON STACK
980                 add             eax,ebx
981                 sub             eax,[my_phys_base]                      ; REMEMBER our data segment is relative to the COM.
982                                                                         ; ALSO KNOW most x86 processors will wrap addresses like
983                                                                         ; 0xFFFFF000 back around to 0 (32-bit overflow) with nonzero
984                                                                         ; segment bases.
985
986                 mov             eax,[eax]                               ; fetch 4 bytes at CS:IP
987                 mov             [v86_raw_opcode],eax                    ; store for reference
988
989                 cmp             al,0xFA                                 ; CLI?
990                 jz              .v86_cli
991                 cmp             al,0xFB                                 ; STI?
992                 jz              .v86_sti
993                 cmp             al,0xF4                                 ; HLT? (apparently, yes, that causes a GPF from v86 mode)
994                 jz              .v86_hlt
995                 cmp             al,0xCD                                 ; INT X (AH=interrupt)
996                 jz              .v86_int
997                 cmp             al,0xCC                                 ; INT 3
998                 jz              .v86_int3
999                 cmp             al,0xCF                                 ; IRET
1000                 jz              .v86_iret
1001                 cmp             al,0x9C                                 ; PUSHF 16-bit
1002                 jz              .v86_pushf
1003                 cmp             al,0x9D                                 ; POPF 16-bit
1004                 jz              .v86_popf
1005                 cmp             ax,0x9C66                               ; PUSHFD 32-bit
1006                 jz              .v86_pushfd
1007                 cmp             ax,0x9D66                               ; POPFD 32-bit
1008                 jz              .v86_popfd
1009                 jmp             .v86_unknown
1010
1011 .v86_complete_and_check_pending_irq: ; <----------- COMPLETION, PLUS CHECK IF INTERRUPTS ENABLED, PENDING IRQs
1012                 test            word [esp+0x20+12],0x200                ; are interrupts enabled (IF=1)
1013                 jz              .v86_complete
1014 ; interrupts enabled, are there pending IRQs?
1015                 cmp             word [irq_pending],0
1016                 jz              .v86_complete
1017 ; for each pending IRQ, stuff the stack with an interrupt frame.
1018 ; this must be done in the order the PIC would do based on IRQ priority.
1019                 cld
1020                 mov             ecx,16
1021                 mov             esi,irq_priority
1022 .v86_complete_and_check_pending_irq_scan:
1023                 xor             eax,eax
1024                 lodsb
1025                 mov             ebx,1
1026                 push            ecx
1027                 mov             cl,al   ; <- NTS: bits 8-31 should be zero because we inited ECX == 16
1028                 shl             ebx,cl
1029                 pop             ecx
1030                 test            word [irq_pending],bx                   ; if (irq_pending & (1 << AL)) ...
1031                 jnz             .v86_complete_and_check_pending_irq_found
1032                 loop            .v86_complete_and_check_pending_irq_scan
1033 ; FALL THROUGH TO COMPLETION
1034 .v86_complete:  popad
1035 .v86_complete_no_popad:
1036                 add             esp,4                                   ; dump error code (usually zero)
1037                 iret
1038
1039 ; we found a pending IRQ. EBX = 1 << IRQ, EAX = IRQ
1040 .v86_complete_and_check_pending_irq_found:
1041                 push            ecx
1042                 xor             word [irq_pending],bx                   ; clear the bit
1043
1044                 movzx           ebx,al                                  ; EBX = interrupt number
1045                 mov             eax,FLAT32_SEL
1046                 mov             es,ax                                   ; we'll need flat mode for this
1047                 mov             bl,[int_rm_map+ebx]                     ; IRQ -> interrupt
1048                 ; store CS:IP and FLAGS on 16-bit stack, decrement stack pointer. DO NOT MODIFY EBX
1049                 sub             word [esp+0x20+4+16],6                  ; (E)SP -= 6
1050                 mov             ax,word [esp+0x20+4+20]                 ; AX = SS (upper bits should be zero)
1051                 shl             eax,4                                   ; AX *= 16
1052                 xor             ecx,ecx
1053                 mov             cx,word [esp+0x20+4+16]                 ; CX = SP
1054                 add             eax,ecx                                 ; AX += SP  AX = (SS*16)+SP
1055                 mov             cx,word [esp+0x20+4+4]                  ; IP
1056                 mov             word [es:eax],cx                        ; SS:SP+0 = IP
1057                 mov             cx,word [esp+0x20+4+8]                  ; CS
1058                 mov             word [es:eax+2],cx                      ; SS:SP+2 = CS
1059                 mov             cx,word [esp+0x20+4+12]                 ; FLAGS
1060                 mov             word [es:eax+4],cx                      ; SS:SP+4 = FLAGS
1061                 ; replace CS:IP with values from real-mode interrupt table (EBX = interrupt vector)
1062                 mov             ax,[es:(ebx*4)]                         ; read from real-mode interrupt table (offset)
1063                 mov             word [esp+0x20+4+4],ax                  ; replace EIP
1064                 mov             ax,[es:(ebx*4)+2]                       ;  .... (segment)
1065                 mov             word [esp+0x20+4+8],ax                  ; replace CS
1066
1067                 pop             ecx
1068                 dec             ecx
1069                 jz              .v86_complete
1070                 jmp             .v86_complete_and_check_pending_irq_scan
1071
1072 ;   EXCEPTION HANDLING REACHES HERE IF IT TURNS OUT VM86 MODE WAS NOT INVOLVED
1073 .not_vm86_related:
1074                 call            fault_collect_regs
1075                 mov             edx,0x0D                                ; INT 0x0D General Protection Fault
1076                 mov             esi,str_fault_0x0D
1077                 jmp             fault_jmp_unhandled
1078 ;   V86 IRET
1079 .v86_iret:      mov             eax,FLAT32_SEL
1080                 mov             es,ax                                   ; we'll need flat mode for this
1081                 ; retrieve CS:IP and FLAGS from 16-bit stack, increment stack pointer
1082                 mov             ax,word [esp+0x20+20]                   ; AX = SS (upper bits should be zero)
1083                 shl             eax,4                                   ; AX *= 16
1084                 xor             ecx,ecx
1085                 mov             cx,word [esp+0x20+16]                   ; CX = SP
1086                 add             eax,ecx                                 ; AX += SP  AX = (SS*16)+SP
1087
1088                 mov             cx,word [es:eax]                        ; IP = SS:SP+0
1089                 mov             word [esp+0x20+4],cx                    ; IP
1090
1091                 mov             cx,word [es:eax+2]                      ; CS = SS:SP+2
1092                 mov             word [esp+0x20+8],cx                    ; CS
1093
1094                 mov             cx,word [es:eax+4]                      ; FLAGS = SS:SP+4
1095                 mov             word [esp+0x20+12],cx                   ; FLAGS
1096
1097                 add             word [esp+0x20+16],6                    ; (E)SP += 6
1098                 jmp             .v86_complete
1099 ;   V86 INT 66h
1100 .v86_int_api:   popad
1101                 cmp             eax,0xAABBAA55
1102                 jz              .v86_int_api_detect
1103                 cmp             eax,0xAABBAABB
1104                 jz              .v86_int_api_unload
1105                 int             3
1106 .v86_int_api_detect:
1107                 mov             eax,0xBBAABB33
1108                 jmp             .v86_complete_no_popad
1109 .v86_int_api_unload:
1110                 mov             ax,word [esp+4]                         ; save IP
1111                 mov             bx,word [esp+8]                         ; save CS
1112                 mov             [unload_int_ret+0],ax
1113                 mov             [unload_int_ret+2],bx
1114
1115                 mov             ax,word [esp+16]                        ; save SP
1116                 mov             bx,word [esp+20]                        ; save SS
1117                 mov             [unload_int_stk+0],ax
1118                 mov             [unload_int_stk+2],bx
1119
1120                 jmp             v86_api_exit
1121 ;   V86 INT 3 (AL = 0xCC)
1122 .v86_int3:      mov             ah,0x03                                 ; convert to INT 3 (CD 03)
1123                 inc             dword [esp+0x20+4]                      ; step past (EIP++)
1124                 jmp             short .v86_int_n
1125 ;   V86 INT x (AL = 0xCD   AH = N)
1126 .v86_int:       add             dword [esp+0x20+4],2                    ; EIP += 2
1127 ;   V86 INT REFLECTION TO REAL MODE
1128 .v86_int_n:     movzx           ebx,ah                                  ; EBX = interrupt number
1129                 ; *DEBUG*
1130                 cmp             bl,RM_INT_API
1131                 jz              .v86_int_api
1132                 ; *END DEBUG*
1133                 mov             eax,FLAT32_SEL
1134                 mov             es,ax                                   ; we'll need flat mode for this
1135                 ; store CS:IP and FLAGS on 16-bit stack, decrement stack pointer. DO NOT MODIFY EBX
1136                 sub             word [esp+0x20+16],6                    ; (E)SP -= 6
1137                 mov             ax,word [esp+0x20+20]                   ; AX = SS (upper bits should be zero)
1138                 shl             eax,4                                   ; AX *= 16
1139                 xor             ecx,ecx
1140                 mov             cx,word [esp+0x20+16]                   ; CX = SP
1141                 add             eax,ecx                                 ; AX += SP  AX = (SS*16)+SP
1142                 mov             cx,word [esp+0x20+4]                    ; IP
1143                 mov             word [es:eax],cx                        ; SS:SP+0 = IP
1144                 mov             cx,word [esp+0x20+8]                    ; CS
1145                 mov             word [es:eax+2],cx                      ; SS:SP+2 = CS
1146                 mov             cx,word [esp+0x20+12]                   ; FLAGS
1147                 mov             word [es:eax+4],cx                      ; SS:SP+4 = FLAGS
1148                 ; replace CS:IP with values from real-mode interrupt table (EBX = interrupt vector)
1149                 mov             ax,[es:(ebx*4)]                         ; read from real-mode interrupt table (offset)
1150                 mov             word [esp+0x20+4],ax                    ; replace EIP
1151                 mov             ax,[es:(ebx*4)+2]                       ;  .... (segment)
1152                 mov             word [esp+0x20+8],ax                    ; replace CS
1153                 jmp             .v86_complete
1154 ;   V86 CLI
1155 .v86_cli:       inc             dword [esp+0x20+4]                      ; step past (EIP++)
1156                 and             word [esp+0x20+12],~0x200
1157                 jmp             .v86_complete_and_check_pending_irq
1158 ;   V86 STI
1159 .v86_sti:       inc             dword [esp+0x20+4]                      ; step past (EIP++)
1160                 or              word [esp+0x20+12],0x200
1161                 jmp             .v86_complete_and_check_pending_irq
1162 ;   V86 HLT
1163 .v86_hlt:       inc             dword [esp+0x20+4]                      ; step past (EIP++)
1164                 test            word [esp+0x20+12],0x200
1165                 jz              .v86_hlt_with_cli
1166                 jmp             .v86_complete_and_check_pending_irq
1167 ;   V86 HLT with interrupts disabled
1168 .v86_hlt_with_cli:
1169                 popad                                                   ; undo v86 check stack
1170                 call            fault_collect_regs
1171                 mov             edx,0x0D
1172                 mov             esi,str_v86_hlt_cli
1173                 jmp             fault_jmp_unhandled
1174 ;   V86 PUSHF
1175 .v86_pushf:     mov             eax,FLAT32_SEL
1176                 mov             es,ax
1177                 inc             dword [esp+0x20+4]                      ; step past (EIP++)
1178                 sub             word [esp+0x20+16],2                    ; (E)SP -= 2
1179                 mov             ax,word [esp+0x20+20]                   ; AX = SS (upper bits should be zero)
1180                 shl             eax,4                                   ; AX *= 16
1181                 xor             ecx,ecx
1182                 mov             cx,word [esp+0x20+16]                   ; CX = SP
1183                 add             eax,ecx                                 ; AX += SP  AX = (SS*16)+SP
1184                 mov             cx,word [esp+0x20+12]                   ; FLAGS
1185                 mov             word [es:eax],cx                        ; SS:SP+0 = FLAGS
1186                 jmp             .v86_complete
1187 ;   V86 PUSHFD
1188 .v86_pushfd:    mov             eax,FLAT32_SEL
1189                 mov             es,ax
1190                 add             dword [esp+0x20+4],2                    ; step past (EIP += 2)
1191                 sub             word [esp+0x20+16],4                    ; (E)SP -= 4
1192                 mov             ax,word [esp+0x20+20]                   ; AX = SS (upper bits should be zero)
1193                 shl             eax,4                                   ; AX *= 16
1194                 xor             ecx,ecx
1195                 mov             cx,word [esp+0x20+16]                   ; CX = SP
1196                 add             eax,ecx                                 ; AX += SP  AX = (SS*16)+SP
1197                 mov             ecx,dword [esp+0x20+12]                 ; EFLAGS
1198                 mov             dword [es:eax],ecx                      ; SS:SP+0 = FLAGS
1199                 jmp             .v86_complete
1200 ;   V86 POPF
1201 .v86_popf:      mov             eax,FLAT32_SEL
1202                 mov             es,ax
1203                 inc             dword [esp+0x20+4]                      ; step past (EIP++)
1204                 mov             ax,word [esp+0x20+20]                   ; AX = SS (upper bits should be zero)
1205                 shl             eax,4                                   ; AX *= 16
1206                 xor             ecx,ecx
1207                 mov             cx,word [esp+0x20+16]                   ; CX = SP
1208                 add             eax,ecx                                 ; AX += SP  AX = (SS*16)+SP
1209                 mov             cx,word [es:eax]                        ; FLAGS = SS:SP+0
1210                 mov             word [esp+0x20+12],cx                   ; FLAGS
1211                 add             word [esp+0x20+16],2                    ; (E)SP += 2
1212                 jmp             .v86_complete_and_check_pending_irq
1213 ;   V86 POPFD
1214 .v86_popfd:     mov             eax,FLAT32_SEL
1215                 mov             es,ax
1216                 add             dword [esp+0x20+4],2                    ; step past (EIP += 2)
1217                 mov             ax,word [esp+0x20+20]                   ; AX = SS (upper bits should be zero)
1218                 shl             eax,4                                   ; AX *= 16
1219                 xor             ecx,ecx
1220                 mov             cx,word [esp+0x20+16]                   ; CX = SP
1221                 add             eax,ecx                                 ; AX += SP  AX = (SS*16)+SP
1222                 mov             ecx,dword [es:eax]                      ; EFLAGS = SS:SP+0
1223                 or              ecx,0x20000                             ; make sure the VM bit is set
1224                 mov             dword [esp+0x20+12],ecx                 ; EFLAGS
1225                 add             word [esp+0x20+16],4                    ; (E)SP += 4
1226                 jmp             .v86_complete_and_check_pending_irq
1227 ;   UNKNOWN OPCODE AT CS:IP in V8086 MODE
1228 .v86_unknown:   popad                                                   ; undo v86 check stack
1229                 add             esp,4                                   ; toss real error code
1230                 push            dword [v86_raw_opcode]                  ; the "ERROR CODE" are the 4 bytes at CS:IP
1231                 call            fault_collect_regs
1232                 mov             edx,0x0D
1233                 mov             esi,str_v86_unknown
1234                 jmp             fault_jmp_unhandled
1235 ;   API CALL TO SHUTDOWN VM86 MONITOR
1236 v86_api_exit:   mov             ax,FLAT32_SEL
1237                 mov             es,ax
1238                 mov             ax,DATA32_SEL
1239                 mov             ds,ax
1240 ; FIXME: I give up... why does JMPing to TSS_SEL:0 cause random crashes in VirtualBox?
1241                 jmp             _exit_from_prot32                       ; and then begin shutdown of this program
1242
1243 ; ========== FAULT COLLECTION ROUTINE. SS:ESP should point to fault. If the exception does not push an error code,
1244 ;    then the caller must push a dummy error code
1245 fault_collect_regs:
1246                 push            ds
1247                 push            eax
1248                 push            ebx
1249                 mov             ax,ds
1250                 mov             bx,ax
1251                 mov             ax,DATA32_SEL
1252                 mov             ds,ax
1253                 mov             word [unhandled_fault_var_ds],bx
1254                 pop             ebx
1255
1256                 mov             eax,[esp+4+8+0]                         ; ERROR CODE ON STACK +2 DWORDs PUSHED
1257                 mov             dword [unhandled_fault_var_errcode],eax
1258
1259                 mov             eax,[esp+4+8+4]                         ; EIP ON STACK
1260                 mov             dword [unhandled_fault_var_eip],eax
1261
1262                 mov             eax,[esp+4+8+8]                         ; CS ON STACK
1263                 mov             word [unhandled_fault_var_cs],ax
1264
1265                 mov             eax,[esp+4+8+12]                        ; EFLAGS ON STACK
1266                 mov             dword [unhandled_fault_var_eflags],eax
1267
1268                 call            .retr_stack_ptr
1269
1270                 pop             eax
1271
1272                 mov             dword [unhandled_fault_var_eax],eax
1273                 mov             dword [unhandled_fault_var_ebx],ebx
1274                 mov             dword [unhandled_fault_var_ecx],ecx
1275                 mov             dword [unhandled_fault_var_edx],edx
1276                 mov             dword [unhandled_fault_var_esi],esi
1277                 mov             dword [unhandled_fault_var_edi],edi
1278                 mov             dword [unhandled_fault_var_ebp],ebp
1279
1280                 mov             eax,cr0
1281                 mov             dword [unhandled_fault_var_cr0],eax
1282                 mov             eax,cr3
1283                 mov             dword [unhandled_fault_var_cr3],eax
1284                 mov             eax,cr4
1285                 mov             dword [unhandled_fault_var_cr4],eax
1286                 mov             ax,es
1287                 mov             word [unhandled_fault_var_es],ax
1288                 mov             ax,fs
1289                 mov             word [unhandled_fault_var_fs],ax
1290                 mov             ax,gs
1291                 mov             word [unhandled_fault_var_gs],ax
1292                 pop             ds
1293                 ret
1294 ; if privilege escalation was involved (stack switching) then retrieve SS:ESP at fault from the stack frame.
1295 ; else retrieve from actual SS:ESP registers
1296 .retr_stack_ptr:
1297                 test            word [unhandled_fault_var_cs],3         ; if code segment is nonzero
1298                 jz              .retr_stack_ptr_ring_0
1299
1300                 mov             eax,[esp+4+4+8+16]                      ; ESP ON STACK
1301                 mov             dword [unhandled_fault_var_esp],eax
1302
1303                 mov             eax,[esp+4+4+8+20]                      ; SS ON STACK
1304                 mov             word [unhandled_fault_var_ss],ax
1305
1306                 ret
1307 .retr_stack_ptr_ring_0:
1308                 lea             eax,[esp+4+4+8+16]                      ; +4 our call frame, +8 PUSH DS,EAX +16 GPF stack frame
1309                 mov             dword [unhandled_fault_var_esp],eax
1310
1311                 mov             eax,ss                                  ; SS ON STACK
1312                 mov             word [unhandled_fault_var_ss],ax
1313
1314                 ret
1315
1316 fault_jmp_unhandled:
1317                 jmp             CODE16_SEL:.thunk16
1318                 bits            16
1319 .thunk16:       mov             ax,DATA16_SEL
1320                 mov             ds,ax
1321                 mov             es,ax
1322                 mov             ss,ax
1323                 mov             sp,stack_init
1324                 jmp             unhandled_fault_errcode
1325                 bits            32
1326
1327 ; ============= cleanup, exit to DOS (from 32-bit protected mode)
1328 _exit_from_prot32:
1329                 jmp             CODE16_SEL:.entry16
1330                 bits            16
1331 .entry16:       mov             ax,DATA16_SEL
1332                 mov             ds,ax
1333                 mov             es,ax
1334                 mov             fs,ax
1335                 mov             gs,ax
1336                 mov             ss,ax
1337                 mov             esp,stack_init
1338
1339 ; ============= cleanup, exit to DOS (from 16-bit protected mode)
1340 _exit_from_prot16:
1341                 mov             ax,DATA16_SEL
1342                 mov             ds,ax
1343                 mov             es,ax
1344                 mov             fs,ax
1345                 mov             gs,ax
1346                 mov             ss,ax
1347                 mov             sp,stack_init
1348                 ; overwrite the far jmp's segment value
1349                 mov             ax,[my_realmode_seg]
1350                 mov             word [.real_hackme+3],ax
1351                 lidt            [idtr_real]
1352                 lgdt            [gdtr_real]
1353                 xor             eax,eax
1354                 mov             cr0,eax
1355 .real_hackme:   jmp             0:.real_entry
1356 .real_entry:    mov             ax,[my_realmode_seg]
1357                 mov             ds,ax
1358                 mov             es,ax
1359                 mov             fs,ax
1360                 mov             gs,ax
1361                 mov             ss,ax
1362                 mov             sp,stack_init
1363
1364 ; reprogram the PIC back to what normal DOS expects: IRQ 0-7 => INT 8-15
1365                 mov             al,0x10                 ; ICW1 A0=0
1366                 out             20h,al
1367                 mov             al,0x08                 ; ICW2 A0=1
1368                 out             21h,al
1369                 mov             al,0x04                 ; ICW3 A0=1 slave on IRQ 2
1370                 out             21h,al
1371
1372 ; remove our INT 66h API
1373                 xor             ax,ax
1374                 mov             es,ax
1375                 mov             word [es:(RM_INT_API*4)],ax
1376                 mov             word [es:(RM_INT_API*4)+2],ax
1377
1378 ; free HIMEM.SYS blocks
1379                 mov             ah,0Dh                  ; HIMEM.SYS function 0Dh unlock memory block
1380                 mov             dx,word [himem_sys_buffer_handle]
1381                 call far        word [himem_sys_entry]
1382                 mov             ah,0Ah                  ; HIMEM.SYS function 0Ah free memory block
1383                 mov             dx,word [himem_sys_buffer_handle]
1384                 call far        word [himem_sys_entry]
1385
1386 ; if we already exited as a TSR...
1387                 test            byte [i_am_tsr],1
1388                 jnz             .tsr_exit
1389
1390 ; time to exit to DOS
1391                 mov             dx,str_exit_to_dos
1392                 jmp             _exit_with_msg
1393
1394 ; ============= ALTERNATE EXIT IF WE ALREADY EXITED AS TSR
1395 .tsr_exit:      
1396                 mov             ax,cs
1397                 mov             es,ax                   ; ES = our code segment which is also our PSP segment
1398                 mov             ah,0x49                 ; function 49h free memory block
1399                 clc
1400                 int             21h
1401                 jnc             .tsr_exit_free_ok
1402                 mov             dx,str_cannot_free_self
1403                 call            dos_puts
1404 .tsr_exit_free_ok:
1405                 cli
1406                 mov             ax,[cs:unload_int_stk+0]        ; offset
1407                 add             ax,6                            ; discard prior frame
1408                 mov             sp,ax
1409                 mov             ax,[cs:unload_int_stk+2]        ; segment
1410                 mov             ss,ax
1411
1412                 mov             dx,str_exit_to_dos
1413                 call            dos_puts
1414
1415                 jmp far         word [cs:unload_int_ret]
1416
1417 ; ============= UNHANDLED FAULT HANDLER (16-bit code)
1418 ;   input: EDX = Number of interrupt
1419 ;          DS:SI = Textual string of fault
1420 ;          ESP = Stack containing:
1421 ;                  
1422 unhandled_fault_errcode:
1423                 cli
1424                 mov             ax,DATA16_SEL
1425                 mov             ds,ax
1426
1427                 mov             ax,[cs:my_realmode_seg]
1428                 mov             word [.real16jmp+3],ax
1429
1430                 mov             ax,FLAT16_SEL
1431                 mov             ds,ax
1432                 mov             es,ax
1433                 mov             ss,ax
1434
1435                 lgdt            [cs:gdtr_real]
1436                 lidt            [cs:idtr_real]
1437
1438                 ; crash-thunk to real mode
1439                 xor             eax,eax
1440                 mov             cr0,eax
1441 .real16jmp:     jmp             0:.real16
1442 .real16:        mov             ax,[cs:my_realmode_seg]
1443                 mov             ds,ax
1444                 mov             ss,ax
1445                 xor             ax,ax
1446                 mov             es,ax
1447
1448                 mov             ax,3
1449                 int             10h
1450
1451                 cld
1452                 mov             ax,0x4E20
1453                 mov             ecx,80*25
1454                 mov             edi,0xB8000
1455                 a32 rep         stosw
1456
1457                 ; print exception name on screen
1458                 mov             edi,0xB8000
1459                 call            .unhandled_print
1460                 mov             al,' '          ; +space plus AH still contains upper byte from .unhandled_print
1461                 a32 stosw
1462
1463                 ; then the number (in EDX) write to DS:DI
1464                 mov             eax,edx
1465                 push            edi
1466                 mov             edi,scratch_str
1467                 call            eax_to_hex_16_dos
1468                 lea             si,[di+6]       ; only the last two hex digits
1469                 pop             edi
1470                 call            .unhandled_print
1471
1472                 ; print the registers.
1473                 ; during this loop: SI = print list  EDI = location on screen to draw   [ESP] = location on screen of row start
1474                 mov             edi,0xB8000+(160*2)     ; two lines down
1475                 push            edi
1476                 mov             si,printlist_32
1477 .regprint32:    lodsw
1478                 or              ax,ax
1479                 jz              .regprint32e            ; AX=0 STOP
1480                 dec             ax
1481                 jz              .regprint32nl           ; AX=1 GO TO NEW LINE
1482                 push            si
1483                 mov             si,ax                   ; SI=AX=address of variable name
1484                 inc             si
1485                 call            .unhandled_print
1486                 pop             si
1487                 mov             ax,0x4E00 | (':')
1488                 a32 stosw
1489                 lodsw                                   ; SI=address of variable
1490                 push            si
1491                 mov             si,ax
1492                 mov             eax,[si]
1493                 push            edi
1494                 mov             edi,scratch_str
1495                 call            eax_to_hex_16_dos
1496                 mov             esi,edi
1497                 pop             edi
1498                 call            .unhandled_print
1499                 pop             si
1500                 mov             ax,0x4E00 | (' ')
1501                 a32 stosw
1502                 jmp             .regprint32
1503 .regprint32nl:  pop             edi
1504                 add             edi,160                 ; move to next line, save back to [ESP]
1505                 push            edi
1506                 jmp             .regprint32
1507 .regprint32e:   pop             edi
1508
1509                 add             edi,160                 ; next line...
1510
1511                 mov             si,printlist_16
1512 .regprint16:    lodsw
1513                 or              ax,ax
1514                 jz              .regprint16e            ; AX=0 STOP
1515                 dec             ax
1516                 jz              .regprint16nl           ; AX=1 GO TO NEW LINE
1517                 push            si
1518                 mov             si,ax                   ; SI=AX=address of variable name
1519                 inc             si
1520                 call            .unhandled_print
1521                 pop             si
1522                 mov             ax,0x4E00 | (':')
1523                 a32 stosw
1524                 lodsw                                   ; SI=address of variable
1525                 push            si
1526                 mov             si,ax
1527                 xor             eax,eax
1528                 mov             ax,[si]
1529                 push            edi
1530                 mov             edi,scratch_str
1531                 call            eax_to_hex_16_dos
1532                 lea             esi,[edi+4]
1533                 pop             edi
1534                 call            .unhandled_print
1535                 pop             si
1536                 mov             ax,0x4E00 | (' ')
1537                 a32 stosw
1538                 jmp             .regprint16
1539 .regprint16nl:  pop             edi
1540                 add             edi,160                 ; move to next line, save back to [ESP]
1541                 push            edi
1542                 jmp             .regprint16
1543 .regprint16e:   mov             si,str_mode_prot        ; CPU mode
1544                 test            dword [unhandled_fault_var_eflags],0x20000
1545                 jz              .regprint_cpu_mode_not_v86
1546                 mov             si,str_mode_v86
1547 .regprint_cpu_mode_not_v86:
1548                 call            .unhandled_print
1549                 pop             edi
1550
1551                 mov             al,020h
1552
1553                 out             20h,al
1554                 out             20h,al
1555                 out             20h,al
1556                 out             20h,al
1557                 out             20h,al
1558                 out             20h,al
1559                 out             20h,al
1560                 out             20h,al
1561
1562                 out             0A0h,al
1563                 out             0A0h,al
1564                 out             0A0h,al
1565                 out             0A0h,al
1566                 out             0A0h,al
1567                 out             0A0h,al
1568                 out             0A0h,al
1569                 out             0A0h,al
1570
1571                 sti
1572                 jmp             short $
1573 ; ===== print on screen from DS:SI to ES:EDI
1574 .unhandled_print:
1575                 lodsb
1576                 cmp             al,'$'
1577                 jz              .unhandled_printe
1578                 mov             ah,0x4E
1579                 a32 stosw
1580                 jmp             .unhandled_print
1581 .unhandled_printe:
1582                 ret
1583
1584 ; ============= Entry point (virtual 8086 mode)
1585 vm86_entry:     cli                             ; make sure the v86 monitor handles CLI
1586                 sti                             ; ...and STI
1587                 pushf                           ; ...and PUSHF
1588                 popf                            ; ...and POPF
1589                 pushfd                          ; ...32-bit PUSHF
1590                 popfd                           ; ...32-bit POPF
1591                 in              al,21h          ; ...IN?
1592                 out             21h,al          ; ...OUT?
1593
1594                 ; NOW MAKE SURE PUSHF/POPF STORE THE VALUE ON-STACK LIKE THEY'RE SUPPOSED TO
1595                 mov             bx,sp
1596                 mov             word [ss:bx-2],0x5A5A
1597                 pushf
1598                 mov             bx,sp
1599                 cmp             word [ss:bx],0x5A5A
1600                 jnz             .pushf_ok       ; if the value DIDN'T CHANGE then the monitor failed to write FLAGS to stack
1601                 mov             ax,0
1602                 jmp             vm86_errcode
1603 .pushf_ok:
1604
1605                 ; DOES POPF WORK?
1606                 mov             ax,0x492
1607                 push            ax
1608                 popf
1609                 pushf
1610                 pop             ax
1611                 and             ax,0xFD6
1612                 cmp             ax,0x492
1613                 jz              .popf_ok
1614                 mov             ax,1
1615                 jmp             vm86_errcode
1616 .popf_ok:
1617
1618                 ; TEST 32-bit PUSHF
1619                 mov             bx,sp
1620                 mov             dword [ss:bx-4],0x5A5A5A5A
1621                 pushfd
1622                 mov             bx,sp
1623                 cmp             dword [ss:bx],0x5A5A5A5A
1624                 jnz             .pushfd_ok      ; if the value DIDN'T CHANGE then the monitor failed to write FLAGS to stack
1625                 mov             ax,2
1626                 jmp             vm86_errcode
1627 .pushfd_ok:
1628
1629                 ; DOES POPFD WORK?
1630                 mov             eax,0x492
1631                 push            eax
1632                 popfd
1633                 pushfd
1634                 pop             eax
1635                 and             eax,0xFD6
1636                 cmp             eax,0x492
1637                 jz              .popfd_ok
1638                 mov             ax,3
1639                 jmp             vm86_errcode
1640 .popfd_ok:
1641
1642                 ; IF I CLEAR INTERRUPT (CLI) AND THEN EXECUTE AN INTERRUPT, DOES IT COME BACK ENABLED?
1643                 cli
1644                 mov             ah,0x0F                 ; INT 10 AH=0x0F which has no visisible effect
1645                 int             10h
1646                 pushf
1647                 pop             ax
1648                 test            ax,0x200
1649                 jz              .int_doesnt_enable
1650                 mov             ax,4
1651                 jmp             vm86_errcode
1652 .int_doesnt_enable:
1653
1654                 ; HELLO WORLD!
1655                 mov             si,str_vm86_hello
1656                 call            bios_puts
1657
1658                 ; TEST DEFERRED IRQ MECHANISM BY DELIBERATLEY HALTING FOR AWHILE
1659                 cli
1660                 mov             ecx,0x1000000           ; delibrate slow countdown loop
1661 .l1:            dec             ecx
1662                 jnz             .l1
1663                 sti
1664
1665                 ; for my next trick, I will exit to DOS as a TSR
1666                 ; and allow the user to run the whole DOS kernel this way :)
1667                 mov             es,[cs:0x2C]            ; locate our environment block and free it
1668                 mov             ah,0x49                 ; function 49h free memory block
1669                 int             21h
1670                 jnc             .env_free_ok
1671                 mov             ax,4
1672                 jmp             vm86_errcode
1673 .env_free_ok:   mov             word [cs:0x2C],0        ; rub out the ENV block
1674
1675                 ; setup our INT 66h API
1676                 xor             ax,ax
1677                 mov             es,ax
1678                 mov             word [es:(RM_INT_API*4)],realmode_api_entry
1679                 mov             ax,cs
1680                 mov             word [es:(RM_INT_API*4)+2],ax
1681
1682                 ; finally, terminate and stay resident
1683                 mov             byte [i_am_tsr],1
1684                 mov             edx,the_end             ; DX = memory in paragraphs to save
1685                 add             edx,15
1686                 shr             edx,4
1687                 add             edx,16                  ; <-- FIXME: IS THIS NECESSARY
1688                 mov             ah,0x31                 ; function 31h terminate and stay resident
1689                 int             21h
1690
1691 ; ============= "Secret Handshake" to exit back into the v86 monitor and shutdown the program (virtual 8086 mode)
1692 ; TODO: Remove this, call into RM_INT_API instead
1693 vm86_exit:      mov             eax,0xAABBAABB
1694                 int             RM_INT_API
1695                 hlt
1696
1697 ; ============= If any of our self-test fails, we draw DIRECTLY ON VGA RAM and hike back into the vm86 monitor ASAP.
1698 ;   if self-tests fail chances are calling the BIOS/DOS will cause major problems. AX=CODE
1699 vm86_errcode:   mov             bx,0xB800
1700                 mov             es,bx
1701                 and             ax,0xF
1702                 or              ax,0x4E30       ; AX = VGA alphanumeric code for that number
1703                 mov             [es:160],ax
1704                 jmp             vm86_exit
1705
1706 ; ============= Real-mode API entry (reflect to v86 monitor by executing an INT)
1707 ;    this would allow the trick to work even for programs that direct-call instead
1708 realmode_api_entry:
1709                 int             RM_INT_API
1710                 iret
1711
1712 ; ============= Parse command line (from PSP segment)
1713 parse_argv:     cld
1714                 mov             si,81h
1715 .scan:          lodsb
1716                 or              al,al
1717                 jz              .done
1718                 cmp             al,0Dh
1719                 jz              .done
1720                 cmp             al,20h
1721                 jz              .scan
1722                 cmp             al,'-'
1723                 jz              .switch
1724                 cmp             al,'/'
1725                 jz              .switch
1726                 ; FALL THROUGH WITH ZF=0 to return
1727 .done:          ret
1728                 ; AT THIS POINT: SI = just after the / or - in the switch
1729 .switch:        lodsb
1730                 cmp             al,'?'
1731                 jz              .help
1732                 cmp             al,'A'
1733                 jb              .unknown_switch
1734                 cmp             al,'Z'
1735                 ja              .unknown_switch
1736                 ; the A-Z switches are allowed to have "=NNNN" after them where N is some integer in hex or decimal
1737                 sub             al,'A'
1738                 mov             bl,al
1739                 xor             bh,bh           ; BX = index into lookup table
1740                 add             bx,bx
1741                 jmp             word [bx+.switch_az]
1742 .fail:          mov             al,1
1743 .help:          or              al,al           ; AL != 0 => ZF=0
1744                 ret
1745 .unknown_switch:mov             dx,str_unknown_switch
1746                 call            dos_puts
1747                 lea             dx,[si-2]       ; step back two chars
1748                 mov             byte [si],'$'
1749                 call            dos_puts
1750                 mov             dx,str_crlf
1751                 call            dos_puts
1752                 jmp             .fail
1753 ; ========== Switches CALL here if they need a numeric value to follow.
1754 ; returns to caller if so, parsing as 16-bit integer returned in EAX. Else,
1755 ; it discards the return address and jumps to the 'needs param' error message.
1756 .switch_needs_equ_check:
1757                 cmp             byte [si],'='
1758                 jnz             .switch_needs_equ_check_fail
1759                 inc             si
1760                 cli
1761                 xor             eax,eax
1762                 call            ax_strtol_16
1763                 ret
1764 .switch_needs_equ_check_fail:
1765                 add             sp,2            ; fall through
1766 .switch_needs_equ:
1767                 mov             dx,str_needs_equals
1768                 call            dos_puts
1769                 jmp             .fail
1770 ; ========== /B=<number>
1771 .switch_buffer_size:
1772                 call            .switch_needs_equ_check
1773                 shl             eax,10
1774                 mov             [himem_sys_buffer_size],eax
1775                 jmp             .scan
1776 ; ========== /U
1777 .switch_unload: mov             byte [user_req_unload],1
1778                 jmp             .scan
1779 ; ========== /I
1780 .switch_iopl:   mov             byte [user_req_iopl],0
1781                 jmp             .scan
1782 ; switch A-Z jump table
1783 .switch_az:     dw              .unknown_switch                 ; /A
1784                 dw              .switch_buffer_size             ; /B=<number>
1785                 dw              .unknown_switch                 ; /C
1786                 dw              .unknown_switch                 ; /D
1787                 dw              .unknown_switch                 ; /E
1788                 dw              .unknown_switch                 ; /F
1789                 dw              .unknown_switch                 ; /G
1790                 dw              .unknown_switch                 ; /H
1791                 dw              .switch_iopl                    ; /I
1792                 dw              .unknown_switch                 ; /J
1793                 dw              .unknown_switch                 ; /K
1794                 dw              .unknown_switch                 ; /L
1795                 dw              .unknown_switch                 ; /M
1796                 dw              .unknown_switch                 ; /N
1797                 dw              .unknown_switch                 ; /O
1798                 dw              .unknown_switch                 ; /P
1799                 dw              .unknown_switch                 ; /Q
1800                 dw              .unknown_switch                 ; /R
1801                 dw              .unknown_switch                 ; /S
1802                 dw              .unknown_switch                 ; /T
1803                 dw              .switch_unload                  ; /U
1804                 dw              .unknown_switch                 ; /V
1805                 dw              .unknown_switch                 ; /W
1806                 dw              .unknown_switch                 ; /X
1807                 dw              .unknown_switch                 ; /Y
1808                 dw              .unknown_switch                 ; /Z
1809
1810 irq_routines:   dw              irq_0
1811                 dw              irq_1
1812                 dw              irq_2
1813                 dw              irq_3
1814                 dw              irq_4
1815                 dw              irq_5
1816                 dw              irq_6
1817                 dw              irq_7
1818                 dw              irq_8
1819                 dw              irq_9
1820                 dw              irq_10
1821                 dw              irq_11
1822                 dw              irq_12
1823                 dw              irq_13
1824                 dw              irq_14
1825                 dw              irq_15
1826
1827 fault_routines: dw              fault_0x00
1828                 dw              fault_0x01
1829                 dw              fault_0x02
1830                 dw              fault_0x03
1831                 dw              fault_0x04
1832                 dw              fault_0x05
1833                 dw              fault_0x06
1834                 dw              fault_0x07
1835                 dw              fault_0x08
1836                 dw              fault_0x09
1837                 dw              fault_0x0A
1838                 dw              fault_0x0B
1839                 dw              fault_0x0C
1840                 dw              fault_0x0D
1841                 dw              fault_0x0E
1842                 dw              fault_0x0F
1843                 dw              fault_0x10
1844                 dw              fault_0x11
1845                 dw              fault_0x12
1846                 dw              fault_0x13
1847                 dw              fault_0x14
1848                 dw              fault_0x15
1849                 dw              fault_0x16
1850                 dw              fault_0x17
1851                 dw              fault_0x18
1852                 dw              fault_0x19
1853                 dw              fault_0x1A
1854                 dw              fault_0x1B
1855                 dw              fault_0x1C
1856                 dw              fault_0x1D
1857                 dw              fault_0x1E
1858                 dw              fault_0x1F
1859
1860
1861 ; register print list
1862 printlist_32:   dw              str_eax,        unhandled_fault_var_eax
1863                 dw              str_ebx,        unhandled_fault_var_ebx
1864                 dw              str_ecx,        unhandled_fault_var_ecx
1865                 dw              str_edx,        unhandled_fault_var_edx
1866                 dw              str_esi,        unhandled_fault_var_esi
1867                 dw              str_edi,        unhandled_fault_var_edi
1868                 dw              1
1869                 dw              str_ebp,        unhandled_fault_var_ebp
1870                 dw              str_esp,        unhandled_fault_var_esp
1871                 dw              str_eip,        unhandled_fault_var_eip
1872                 dw              str_eflags,     unhandled_fault_var_eflags
1873                 dw              str_errcode,    unhandled_fault_var_errcode
1874                 dw              str_cr0,        unhandled_fault_var_cr0
1875                 dw              1
1876                 dw              str_cr3,        unhandled_fault_var_cr3
1877                 dw              str_cr4,        unhandled_fault_var_cr4
1878                 dw              0
1879 printlist_16:   dw              str_cs,         unhandled_fault_var_cs
1880                 dw              str_ds,         unhandled_fault_var_ds
1881                 dw              str_es,         unhandled_fault_var_es
1882                 dw              str_fs,         unhandled_fault_var_fs
1883                 dw              str_gs,         unhandled_fault_var_gs
1884                 dw              str_ss,         unhandled_fault_var_ss
1885                 dw              0
1886
1887 ; ============= bios_puts (print $-terminated string at DS:SI)
1888 bios_puts:      cli
1889                 cld
1890                 push            ax
1891                 push            bx
1892 .putsloop:      lodsb
1893                 cmp             al,'$'
1894                 jz              .putsend
1895                 mov             ah,0x0E
1896                 xor             bx,bx
1897                 int             10h
1898                 jmp             .putsloop
1899 .putsend:       pop             bx
1900                 pop             ax
1901                 ret
1902
1903 ; ============= dos_puts (print $-terminated string at DS:DX)
1904 dos_puts:       mov             ah,09h
1905                 int             21h
1906                 ret
1907
1908 ; ============= read one digit from DS:SI return in AX (16-bit code)
1909 ax_strtol_16_single:mov         al,[si]
1910                 cmp             al,'0'
1911                 jb              .no
1912                 cmp             al,'9'
1913                 ja              .no
1914                 sub             al,'0'
1915                 xor             ah,ah
1916                 inc             si
1917                 clc
1918                 ret
1919 .no:            stc
1920                 ret
1921
1922 ; ============= read from DS:SI and convert numerical string to integer value return in AX (16-bit code)
1923 ax_strtol_16:   xor             cx,cx
1924 .loop:          push            cx
1925                 call            ax_strtol_16_single
1926                 pop             cx
1927                 jc              .done
1928                 mov             bx,cx
1929                 add             bx,bx
1930                 shl             cx,3            ; BX = CX * 2,  CX *= 8
1931                 add             cx,bx           ; CX = (CX * 8) + (CX * 2) = CX * 10
1932                 add             cx,ax           ; CX += new digit
1933                 jmp             .loop
1934 .done:          mov             ax,cx
1935                 ret
1936
1937 ; ============= take AX and write to buffer (DS:SI) as hexadecimal string (16-bit code)
1938 al_to_hex_16_dos:mov            byte [di+2],'$'
1939                 jmp             al_to_hex_16
1940 al_to_hex_16_nul:mov            byte [di+2],0
1941 al_to_hex_16:   push            di
1942                 push            bx
1943                 push            ax
1944                 xor             bh,bh
1945                 mov             ah,al
1946                 and             al,0xF
1947                 mov             bl,al
1948                 mov             al,[bx+str_hex]         ; AL' = str_hex[al]
1949                 shr             ah,4
1950                 mov             bl,ah
1951                 mov             ah,[bx+str_hex]         ; AH' = str_hex[ah]
1952                 mov             [di+0],ah
1953                 mov             [di+1],al
1954                 pop             ax
1955                 pop             bx
1956                 pop             di
1957                 ret
1958
1959 ; ============= take AX and write to buffer (DS:SI) as hexadecimal string (16-bit code)
1960 ax_to_hex_16_dos:mov            byte [di+4],'$'
1961                 jmp             ax_to_hex_16
1962 ax_to_hex_16_nul:mov            byte [di+4],0
1963 ax_to_hex_16:   push            di
1964                 push            ax
1965                 mov             al,ah
1966                 call            al_to_hex_16
1967                 pop             ax
1968                 add             di,2
1969                 call            al_to_hex_16
1970                 pop             di
1971                 ret
1972
1973 ; ============= take EAX and write to buffer (DS:DI) as hexadecimal string (16-bit code)
1974 eax_to_hex_16_dos:mov           byte [di+8],'$'
1975                 jmp             eax_to_hex_16
1976 eax_to_hex_16_nul:mov           byte [di+8],0
1977 eax_to_hex_16:  push            di
1978                 push            eax
1979                 shr             eax,16
1980                 call            ax_to_hex_16
1981                 pop             eax
1982                 add             di,4
1983                 call            ax_to_hex_16
1984                 pop             di
1985                 ret
1986
1987 ; ============= /U Unloading the resident copy of this program
1988 unload_this_program:
1989                 smsw            ax
1990                 test            al,1
1991                 jnz             .v86_active
1992                 mov             dx,str_not_loaded
1993                 jmp             _exit_with_msg
1994 .v86_active:
1995                 xor             ax,ax
1996                 mov             es,ax
1997                 mov             bx,[es:(RM_INT_API*4)]
1998                 or              cx,[es:(RM_INT_API*4)+2]
1999                 cmp             cx,0            ; if pointer is 0000:0000
2000                 jz              .v86_not_me
2001                 mov             eax,0xAABBAA55
2002                 int             RM_INT_API
2003                 cmp             eax,0xBBAABB33
2004                 jnz             .v86_not_me
2005 .v86_is_me:     mov             ax,cs
2006                 mov             ds,ax
2007                 mov             es,ax
2008                 mov             fs,ax
2009                 mov             gs,ax
2010                 mov             dx,str_removing_self
2011                 call            dos_puts
2012 ; instruct it to remove itself
2013                 mov             eax,0xAABBAABB
2014                 int             RM_INT_API
2015 ; exit, having done our job
2016                 mov             dx,str_crlf
2017                 call            dos_puts
2018                 mov             dx,str_unloaded
2019                 jmp             _exit_with_msg
2020 .v86_not_me:    mov             dx,str_v86_but_not_me
2021                 jmp             _exit_with_msg
2022
2023 ; ============= DATA: THESE EXIST IN THE .COM BINARY IMAGE
2024                 section         .data align=2
2025 himem_sys_buffer_size:dd        (256*1024)      ; DWORD [amount of extended memory to allocate]
2026 str_require_386:db              '386 or higher required$'
2027 str_removing_self:db            'Removing from memory',13,10,'$'
2028 str_v86_detected:db             'Virtual 8086 mode already active$'
2029 str_v86_but_not_me:db           'Virtual 8086 active, and its not me$'
2030 str_not_loaded: db              'Not resident in memory$'
2031 str_cannot_free_self:db         'Cannot free self from memory$'
2032 str_need_himem_sys:db           'HIMEM.SYS not installed$'
2033 str_himem_a20_error:db          'HIMEM.SYS failed to enable A20$'
2034 str_himem_alloc_err:db          'Unable to alloc extended memory$'
2035 str_himem_lock_err:db           'Unable to lock extended memory$'
2036 str_buffer_too_small:db         'Buffer too small$'
2037 str_buffer_too_large:db         'Buffer too large$'
2038 str_unloaded:   db              'Unloaded',13,10,'$'
2039 str_buffer_at:  db              'Buffer at: $'
2040 str_crlf:       db              13,10,'$'
2041 str_hex:        db              '0123456789ABCDEF'
2042 str_help:       db              'V86KERN [options]',13,10
2043                 db              'Demonstration Virtual 8086 kernel/monitor',13,10
2044                 db              13,10
2045                 db              'Options start with - or /',13,10
2046                 db              '  /?      Show this help',13,10
2047                 db              '  /B=...  Set buffer size (in KB)',13,10
2048                 db              '  /U      Unload the kernel',13,10
2049                 db              '  /I      Run with IOPL=3 (trap CLI/STI/etc)',13,10
2050                 db              '$'
2051 str_unknown_switch:db           'Unknown switch $'
2052 str_needs_equals:db             'Switch missing =...$'
2053 str_eax:        db              'EAX$'
2054 str_ebx:        db              'EBX$'
2055 str_ecx:        db              'ECX$'
2056 str_edx:        db              'EDX$'
2057 str_esi:        db              'ESI$'
2058 str_edi:        db              'EDI$'
2059 str_ebp:        db              'EBP$'
2060 str_esp:        db              'ESP$'
2061 str_eip:        db              'EIP$'
2062 str_errcode:    db              'ERR$'
2063 str_eflags:     db              'FLG$'
2064 str_cr0:        db              'CR0$'
2065 str_cr3:        db              'CR3$'
2066 str_cr4:        db              'CR4$'
2067 str_cs:         db              'CS$'
2068 str_ds:         db              'DS$'
2069 str_es:         db              'ES$'
2070 str_fs:         db              'FS$'
2071 str_gs:         db              'GS$'
2072 str_ss:         db              'SS$'
2073 str_mode_prot:  db              'Protected mode$'
2074 str_mode_v86:   db              'Virtual 8086 mode$'
2075 str_vm86_hello: db              'This text was printed by the Virtual 8086 mode component of this program',13,10,'$'
2076 str_fault_0x00: db              'Divide by Zero$'
2077 str_fault_0x01: db              'Debug$'
2078 str_fault_0x02: db              'NMI$'
2079 str_fault_0x03: db              'Breakpoint$'
2080 str_fault_0x04: db              'Overflow$'
2081 str_fault_0x05: db              'Boundary Check$'
2082 str_fault_0x06: db              'Invalid Opcode$'
2083 str_fault_0x07: db              'Coprocessor N/A$'
2084 str_fault_0x08: db              'Double Fault$'
2085 str_fault_0x09: db              'Coprocessor Segment Overrun$'
2086 str_fault_0x0A: db              'Invalid TSS$'
2087 str_fault_0x0B: db              'Segment Not Present$'
2088 str_fault_0x0C: db              'Stack Fault$'
2089 str_fault_0x0D: db              'General Protection Fault$'
2090 str_fault_0x0E: db              'Page Fault$'
2091 str_fault_0x0F: db              'Exception F$'
2092 str_fault_0x10: db              'FPU Error$'
2093 str_fault_0x11: db              'Alignment Check$'
2094 str_fault_0x12: db              'Machine Check$'
2095 str_fault_0x13: db              'SIMD/SSE Exception$'
2096 str_fault_unknown:db            'Unknown exception$'
2097 str_v86_unknown:db              'Unknown instruction in v86 mode$'
2098 str_v86_hlt_cli:db              'v86 halt with interrupts disabled$'
2099 str_v86_secret: db              'Inappropriate use of v86 secret handshake$'
2100 str_exit_to_dos:db              'Shutdown successful, exiting to DOS$'
2101 str_irq_deferred:db             'Deferred IRQ$'
2102 str_irq_1:      db              'IRQ #1$'
2103
2104 ; ============= VARIABLES: THESE DO NOT EXIST IN THE .COM FILE THEY EXIST IN MEMORY FOLLOWING THE BINARY IMAGE
2105                 section         .bss align=2
2106 ; ---------------------- STACK
2107 stack_base:     resb            4096            ; char[4096+4]
2108 stack_init:     resd            1               ; DWORD
2109 stack_top:
2110 scratch_str:    resb            64              ; char[64]
2111 ; ---------------------- STACK
2112 stack_base_vm86:resb            4096            ; char[4096+4]
2113 stack_init_vm86:resd            2               ; DWORD
2114 stack_top_vm86:
2115 ; ---------------------- HIMEM.SYS state
2116 himem_sys_entry:resd            1               ; FAR POINTER
2117 himem_sys_buffer_phys:resd      1               ; DWORD [physical memory address]
2118 himem_sys_buffer_handle:resw    1               ; WORD [HIMEM.SYS handle]
2119 ; ---------------------- my real mode segment
2120 my_realmode_seg:resw            1               ; WORD
2121 my_phys_base:   resd            1               ; DWORD
2122 tss_phys_base:  resd            1               ; DWORD base logical address of TSS
2123 tss_vm86_phys_base:resd         1               ; DWORD base logical address of TSS
2124 buffer_alloc:   resd            1               ; DWORD
2125 kern32_stack_base:resd          1               ; DWORD
2126 kern32_stack_top:resd           1               ; DWORD
2127 v86_raw_opcode: resd            1               ; DWORD
2128                 resd            1               ; *PADDING*
2129 ; ---------------------- GDTR/IDTR
2130 gdtr_pmode:     resq            1               ; LIMIT. BASE
2131 gdtr_real:      resq            1               ; LIMIT, BASE
2132 idtr_pmode:     resq            1               ; LIMIT, BASE
2133 idtr_real:      resq            1               ; LIMIT, BASE
2134 ; ---------------------- GLOBAL DESCRIPTOR TABLE
2135                 align           8
2136 gdt:            resq            (MAX_SEL/8)     ; 16 GDT entries
2137 ; ---------------------- INTERRUPT DESCRIPTOR TABLE
2138                 align           8
2139 idt:            resq            256             ; all 256
2140 ; ---------------------- STATE
2141 irq_pending:    resw            1
2142 v86_if:         resb            1
2143 user_req_unload:resb            1
2144 user_req_iopl:  resb            1
2145 i_am_tsr:       resb            1
2146 unload_int_ret: resd            1
2147 unload_int_stk: resd            1
2148 ; ---------------------- WHEN DISPLAYING THE UNHANDLED FAULT DIALOG
2149 unhandled_fault_var_errcode:resd        1
2150 unhandled_fault_var_eax:resd            1
2151 unhandled_fault_var_ebx:resd            1
2152 unhandled_fault_var_ecx:resd            1
2153 unhandled_fault_var_edx:resd            1
2154 unhandled_fault_var_esi:resd            1
2155 unhandled_fault_var_edi:resd            1
2156 unhandled_fault_var_ebp:resd            1
2157 unhandled_fault_var_esp:resd            1
2158 unhandled_fault_var_eip:resd            1
2159 unhandled_fault_var_eflags:resd         1
2160 unhandled_fault_var_cr0:resd            1
2161 unhandled_fault_var_cr3:resd            1
2162 unhandled_fault_var_cr4:resd            1
2163 unhandled_fault_var_cs:resw             1
2164 unhandled_fault_var_ds:resw             1
2165 unhandled_fault_var_es:resw             1
2166 unhandled_fault_var_fs:resw             1
2167 unhandled_fault_var_gs:resw             1
2168 unhandled_fault_var_ss:resw             1
2169 ; ---------------------------------------------------------------------
2170 ;                       END POINTER
2171 ; ---------------------------------------------------------------------
2172 padding:        resq            2               ; SAFETY PADDING
2173 the_end: