]> 4ch.mooo.com Git - 16.git/blob - src/lib/doslib/hw/cpu/v86.asm
added a bunch of things~ and midi stuff~
[16.git] / src / lib / doslib / hw / cpu / v86.asm
1 ; v86.asm
2 ;
3 ; Test program: 80386 virtual 8086 mode
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 ; proot of concept:
11 ; switching the CPU into 386 16-bit protected mode (and back)
12 ; while playing with the Task State Segment mechanism to
13 ; demonstrate hopping between "ring 0" and "ring 3".
14 ; also to play around with "virtual 8086" mode.
15 bits 16                 ; 16-bit real mode
16 org 0x100               ; MS-DOS .COM style
17
18 ; assume ES == DS and SS == DS and DS == CS
19
20 ; SELECTORS
21 NULL_SEL        equ             0
22 CODE_SEL        equ             8
23 DATA_SEL        equ             16
24 VIDEO_SEL       equ             24
25 CODE32_SEL      equ             32
26 DATA32_SEL      equ             40
27 TSS_SEL         equ             48
28 TSS_2_SEL       equ             56
29 TSS_3_SEL       equ             64
30 LDT_SEL         equ             72
31 CODE_SEL3       equ             80
32 DATA_SEL3       equ             88
33 VIDEO_SEL3      equ             96
34 MAX_SEL         equ             104
35
36 ; ===== ENTRY POINT
37                 call            cpu_is_386
38                 je              is_386
39                 mov             dx,str_cpu_not_386
40                 jmp             exit2dos_with_message
41 is_386:
42
43 ; ===== CHECK FOR VIRTUAL 8086 MODE
44                 smsw            ax                      ; 386 or higher: If we're in real mode
45                 test            al,1                    ; and bit 0 is already set, we're in virtual 8086
46                 jz              is_realmode             ; and our switch to prot mode will cause problems.
47                 mov             dx,str_cpu_v86_mode
48                 jmp             exit2dos_with_message
49 is_realmode:
50
51 ; ===== WE NEED TO PATCH SOME OF OUR OWN CODE
52                 mov             ax,cs
53                 mov             word [real_entry_patch+3],ax    ; overwrite segment field of JMP SEG:OFF
54
55 ; ===== BUILD THE GLOBAL DESCRIPTOR TABLE AND GDTR REGISTER
56                 mov             ax,cs
57                 mov             bx,ax
58                 shr             bx,12
59                 shl             ax,4                    ; BX:AX = 32-bit physical addr of our segment
60                 mov             word [MY_PHYS_BASE],ax
61                 mov             word [MY_PHYS_BASE+2],bx
62
63                 add             ax,GDT
64                 adc             bx,0                    ; BX:AX += offset of GDT
65
66                 mov             word [GDTR],MAX_SEL - 1
67                 mov             word [GDTR+2],ax
68                 mov             word [GDTR+4],bx        ; GDTR: limit MAX_SEL-1 base=physical mem addr of GDT
69
70                 mov             ax,word [MY_PHYS_BASE]
71                 mov             bx,word [MY_PHYS_BASE+2]
72                 add             ax,IDT
73                 adc             bx,0
74
75                 mov             word [IDTR],2047
76                 mov             word [IDTR+2],ax
77                 mov             word [IDTR+4],bx
78
79                 cld
80
81 ;     zero IDT
82                 mov             di,IDT
83                 mov             cx,1023
84                 xor             ax,ax
85                 rep             stosw
86
87                 mov             di,GDT
88 ;     NULL selector (NULL_SEL)
89                 xor             ax,ax
90                 stosw
91                 stosw
92                 stosw
93                 stosw
94 ;     Code selector (CODE_SEL)
95                 dec             ax                      ; 0x0000 - 1 = 0xFFFF
96                 stosw                                   ; LIMIT
97                 mov             ax,[MY_PHYS_BASE]
98                 stosw                                   ; BASE[15:0]
99                 mov             al,[MY_PHYS_BASE+2]
100                 mov             ah,0x9A
101                 stosw                                   ; BASE[23:16] access byte=executable readable
102                 mov             al,0x0F
103                 mov             ah,[MY_PHYS_BASE+3]     ; LIMIT[19:16] flags=0 BASE[31:24]
104                 stosw
105 ;     Data selector (DATA_SEL)
106                 xor             ax,ax
107                 dec             ax                      ; 0xFFFF
108                 stosw                                   ; LIMIT
109                 mov             ax,[MY_PHYS_BASE]
110                 stosw                                   ; BASE[15:0]
111                 mov             al,[MY_PHYS_BASE+2]
112                 mov             ah,0x92
113                 stosw                                   ; BASE[23:16] access byte=data writeable
114                 mov             al,0x0F
115                 mov             ah,[MY_PHYS_BASE+3]     ; LIMIT[19:16] flags=0 BASE[31:24]
116                 stosw
117 ;     Data selector (VIDEO_SEL)
118                 xor             ax,ax
119                 dec             ax                      ; 0xFFFF
120                 stosw                                   ; LIMIT
121                 mov             ax,0x8000
122                 stosw                                   ; BASE[15:0]
123                 mov             al,0x0B                 ; BASE=0xB8000
124                 mov             ah,0x92
125                 stosw                                   ; BASE[23:16] access byte=data writeable
126                 mov             al,0x0F
127                 mov             ah,[MY_PHYS_BASE+3]     ; LIMIT[19:16] flags=0 BASE[31:24]
128                 stosw
129 ;     Code selector (32-bit) (CODE32_SEL)
130                 dec             ax                      ; 0x0000 - 1 = 0xFFFF
131                 stosw                                   ; LIMIT
132                 mov             ax,[MY_PHYS_BASE]
133                 stosw                                   ; BASE[15:0]
134                 mov             al,[MY_PHYS_BASE+2]
135                 mov             ah,0x9E
136                 stosw                                   ; BASE[23:16] access byte=executable readable conforming
137                 mov             al,0xCF
138                 mov             ah,[MY_PHYS_BASE+3]     ; LIMIT[19:16] flags=granular 32-bit BASE[31:24]
139                 stosw
140 ;     Data selector (32-bit) (DATA32_SEL)
141                 xor             ax,ax
142                 dec             ax                      ; 0xFFFF
143                 stosw                                   ; LIMIT
144                 mov             ax,[MY_PHYS_BASE]
145                 stosw                                   ; BASE[15:0]
146                 mov             al,[MY_PHYS_BASE+2]
147                 mov             ah,0x92
148                 stosw                                   ; BASE[23:16] access byte=data writeable
149                 mov             al,0xCF
150                 mov             ah,[MY_PHYS_BASE+3]     ; LIMIT[19:16] flags=granular 32-bit BASE[31:24]
151                 stosw
152 ;     TSS selector (32-bit) (TSS_SEL)
153                 mov             ax,TSS_AREA_SIZE - 1
154                 stosw                                   ; LIMIT
155                 mov             ax,[MY_PHYS_BASE]
156                 mov             bx,[MY_PHYS_BASE+2]
157                 add             ax,TSS_AREA
158                 adc             bx,0
159                 stosw                                   ; BASE[15:0]
160                 mov             al,bl
161                 mov             ah,0x89                 ; present, non-segment, type=9 (TSS busy)
162                 stosw                                   ; BASE[23:16] access byte=data writeable
163                 mov             al,0x00
164                 mov             ah,bh                   ; LIMIT[19:16] flags=granular BASE[31:24]
165                 stosw
166 ;     TSS selector (32-bit) (TSS_2_SEL)
167                 mov             ax,TSS_AREA_2_SIZE - 1
168                 stosw                                   ; LIMIT
169                 mov             ax,[MY_PHYS_BASE]
170                 mov             bx,[MY_PHYS_BASE+2]
171                 add             ax,TSS_AREA_2
172                 adc             bx,0
173                 stosw                                   ; BASE[15:0]
174                 mov             al,bl
175                 mov             ah,0x89                 ; present, non-segment, type=9 (TSS non busy)
176                 stosw                                   ; BASE[23:16] access byte=data writeable
177                 mov             al,0x00
178                 mov             ah,bh                   ; LIMIT[19:16] flags=granular BASE[31:24]
179                 stosw
180 ;     TSS selector (32-bit) (TSS_3_SEL)
181                 mov             ax,TSS_AREA_3_SIZE - 1
182                 stosw                                   ; LIMIT
183                 mov             ax,[MY_PHYS_BASE]
184                 mov             bx,[MY_PHYS_BASE+2]
185                 add             ax,TSS_AREA_3
186                 adc             bx,0
187                 stosw                                   ; BASE[15:0]
188                 mov             al,bl
189                 mov             ah,0x89                 ; present, non-segment, type=9 (TSS non busy)
190                 stosw                                   ; BASE[23:16] access byte=data writeable
191                 mov             al,0x00
192                 mov             ah,bh                   ; LIMIT[19:16] flags=granular BASE[31:24]
193                 stosw
194 ;     LDT selector (32-bit) (LDT_SEL)
195                 mov             ax,LDT_AREA_SIZE - 1
196                 stosw                                   ; LIMIT
197                 mov             ax,[MY_PHYS_BASE]
198                 mov             bx,[MY_PHYS_BASE+2]
199                 add             ax,LDT_AREA
200                 adc             bx,0
201                 stosw                                   ; BASE[15:0]
202                 mov             al,bl
203                 mov             ah,0x82                 ; present, non-segment, type=2 (LDT)
204                 stosw                                   ; BASE[23:16] access byte=data writeable
205                 mov             al,0x00
206                 mov             ah,bh                   ; LIMIT[19:16] flags=granular BASE[31:24]
207                 stosw
208 ;     Code selector (CODE_SEL3)
209                 dec             ax                      ; 0x0000 - 1 = 0xFFFF
210                 stosw                                   ; LIMIT
211                 mov             ax,[MY_PHYS_BASE]
212                 stosw                                   ; BASE[15:0]
213                 mov             al,[MY_PHYS_BASE+2]
214                 mov             ah,0xFA
215                 stosw                                   ; BASE[23:16] access byte=executable readable DPL=3
216                 mov             al,0x0F
217                 mov             ah,[MY_PHYS_BASE+3]     ; LIMIT[19:16] flags=0 BASE[31:24]
218                 stosw
219 ;     Data selector (DATA_SEL3)
220                 xor             ax,ax
221                 dec             ax                      ; 0xFFFF
222                 stosw                                   ; LIMIT
223                 mov             ax,[MY_PHYS_BASE]
224                 stosw                                   ; BASE[15:0]
225                 mov             al,[MY_PHYS_BASE+2]
226                 mov             ah,0xF2
227                 stosw                                   ; BASE[23:16] access byte=data writeable DPL=3
228                 mov             al,0x0F
229                 mov             ah,[MY_PHYS_BASE+3]     ; LIMIT[19:16] flags=0 BASE[31:24]
230                 stosw
231 ;     Data selector (VIDEO_SEL3)
232                 xor             ax,ax
233                 dec             ax                      ; 0xFFFF
234                 stosw                                   ; LIMIT
235                 mov             ax,0x8000
236                 stosw                                   ; BASE[15:0]
237                 mov             al,0x0B                 ; BASE=0xB8000
238                 mov             ah,0xF2
239                 stosw                                   ; BASE[23:16] access byte=data writeable
240                 mov             al,0x0F
241                 mov             ah,[MY_PHYS_BASE+3]     ; LIMIT[19:16] flags=0 BASE[31:24]
242                 stosw
243
244 ; load CPU registers
245                 cli                                     ; disable interrupts
246                 lgdt            [GDTR]                  ; load into processor GDTR
247                 lidt            [IDTR]
248
249 ; switch into protected mode
250                 mov             eax,0x00000001
251                 mov             cr0,eax
252                 jmp             CODE_SEL:prot_entry
253 prot_entry:     mov             ax,DATA_SEL             ; now reload the segment registers
254                 mov             ds,ax
255                 mov             es,ax
256                 mov             fs,ax
257                 mov             gs,ax
258                 mov             ss,ax
259                 mov             sp,0xFFF0
260                 
261 ; load LDT
262                 mov             ax,LDT_SEL
263                 lldt            ax
264                 
265 ; zero the first TSS
266                 cld
267                 mov             edi,TSS_AREA
268                 mov             ecx,TSS_AREA_SIZE / 4
269                 xor             eax,eax
270                 rep             stosd
271
272 ; zero the second TSS
273                 cld
274                 mov             edi,TSS_AREA_2
275                 mov             ecx,TSS_AREA_2_SIZE / 4
276                 xor             eax,eax
277                 rep             stosd
278
279 ; set up the task register. for now, leave it at the first one.
280                 mov             ax,TSS_SEL
281                 ltr             ax
282
283 ; prepare the second one
284                 cld
285                 xor             eax,eax         ; prepare EAX=0
286                 mov             ebx,eax
287                 mov             ecx,0x12345678  ; check value
288                 mov             edi,TSS_AREA_2
289                 stosd                           ; TSS+0x00 = back link
290                 mov             ax,0xF000
291                 stosd                           ; TSS+0x04 = ESP0
292                 mov             ax,DATA_SEL
293                 stosd                           ; TSS+0x08 = SS0
294                 mov             ax,0xF000
295                 stosd                           ; TSS+0x0C = ESP1
296                 mov             ax,DATA_SEL
297                 stosd                           ; TSS+0x10 = SS1
298                 mov             ax,0xF000
299                 stosd                           ; TSS+0x14 = ESP2
300                 mov             ax,DATA_SEL
301                 stosd                           ; TSS+0x18 = SS2
302                 xor             ax,ax
303                 stosd                           ; TSS+0x1C = CR3
304                 mov             eax,tss_jump_1
305                 stosd                           ; TSS+0x20 = EIP
306                 pushfd
307                 pop             eax
308                 stosd                           ; TSS+0x24 = EFLAGS
309                 xor             eax,eax
310                 stosd                           ; TSS+0x28 = EAX
311                 stosd                           ; TSS+0x2C = ECX
312                 stosd                           ; TSS+0x30 = EDX
313                 stosd                           ; TSS+0x34 = EBX
314                 mov             ax,0xF000
315                 stosd                           ; TSS+0x38 = ESP
316                 xor             ax,ax
317                 stosd                           ; TSS+0x3C = EBP
318                 stosd                           ; TSS+0x40 = ESI
319                 stosd                           ; TSS+0x44 = EDI
320                 mov             ax,DATA_SEL
321                 stosd                           ; TSS+0x48 = ES
322                 mov             ax,CODE_SEL
323                 stosd                           ; TSS+0x4C = CS
324                 mov             ax,DATA_SEL
325                 stosd                           ; TSS+0x50 = SS
326                 stosd                           ; TSS+0x54 = DS
327                 stosd                           ; TSS+0x58 = FS
328                 stosd                           ; TSS+0x5C = GS
329                 mov             ax,LDT_SEL
330                 stosd                           ; TSS+0x60 = LDT selector (meh, I don't use it anyway)
331                 xor             ax,ax
332                 stosd                           ; TSS+0x64 = I/O map base=0, T=0
333
334 ; now, SWITCH!
335                 jmp             TSS_2_SEL:0
336
337 ; TSS switch should end up HERE.
338 ; Task register now points to TSS_2_SEL as active task.
339 ; TEST: If the CPU truly loaded state from TSS_2_SEL, all general regs should be zero
340 tss_jump_1:     or              eax,ebx
341                 or              eax,ecx
342                 or              eax,edx
343                 or              eax,esi
344                 or              eax,edi
345                 jz              tss_jump_1_zero
346                 
347                 mov             ax,VIDEO_SEL
348                 mov             es,ax
349                 mov             word [es:0],0x4E30      ; '0'
350                 mov             al,3
351                 out             61h,al                  ; turn on bell
352                 hlt
353 tss_jump_1_zero:
354 ; TEST: All segment registers except CS should be DATA_SEL
355                 mov             ax,ds
356                 sub             ax,DATA_SEL
357                 
358                 mov             bx,es
359                 sub             bx,DATA_SEL
360                 or              ax,bx
361                 
362                 mov             bx,fs
363                 sub             bx,DATA_SEL
364                 or              ax,bx
365                 
366                 mov             bx,gs
367                 sub             bx,DATA_SEL
368                 or              ax,bx
369                 
370                 mov             bx,ss
371                 sub             bx,DATA_SEL
372                 or              ax,bx
373                 
374                 jz              tss_jump_1_sreg_ok
375                 
376                 mov             ax,VIDEO_SEL
377                 mov             es,ax
378                 mov             word [es:0],0x4E31      ; '1'
379                 mov             al,3
380                 out             61h,al                  ; turn on bell
381                 hlt
382 tss_jump_1_sreg_ok:
383
384 ; if the CPU truly saved state into TSS_SEL, the memory location
385 ; corresponding to ECX should be 0x12345678 (because we loaded ECX
386 ; with that value prior to switching state, remember?)
387                 cmp             dword [TSS_AREA+0x2C],0x12345678
388                 jz              tss_jump_1_ecx_ok
389                 
390                 mov             ax,VIDEO_SEL
391                 mov             es,ax
392                 mov             word [es:0],0x4E32      ; '2'
393                 mov             al,3
394                 out             61h,al                  ; turn on bell
395                 hlt
396 tss_jump_1_ecx_ok:
397
398 ; draw directly onto VGA alphanumeric RAM at 0xB8000
399                 cld
400                 push            es
401                 mov             ax,VIDEO_SEL
402                 mov             es,ax
403                 mov             si,vdraw_msg
404                 xor             di,di
405 vdraw1:         lodsb                                   ; AL = DS:SI++
406                 or              al,al
407                 jz              vdraw1e
408                 mov             ah,0x1E
409                 stosw                                   ; ES:DI = AX, DI += 2
410                 jmp             vdraw1
411 vdraw1e:        pop             es
412
413 ; now, jump into 32-bit protected mode
414                 jmp             CODE32_SEL:prot32_entry
415 bits 32
416 prot32_entry:   mov             ax,DATA32_SEL
417                 mov             ds,ax
418                 mov             es,ax
419                 mov             fs,ax
420                 mov             gs,ax
421                 mov             ss,ax
422                 mov             esp,0xFFF0
423
424 ; draw directly onto VGA alphanumeric RAM at 0xB8000
425                 cld
426                 mov             esi,vdraw32_msg
427                 mov             edi,0xB8000+(80*2)
428                 sub             edi,[MY_PHYS_BASE]
429 vdraw321:       lodsb                                   ; AL = DS:SI++
430                 or              al,al
431                 jz              vdraw321e
432                 mov             ah,0x1E
433                 stosw                                   ; ES:DI = AX, DI += 2
434                 jmp             vdraw321
435 vdraw321e:
436
437 ; jump 32-bit to 16-bit
438                 jmp             CODE_SEL:prot32_to_prot
439 bits 16
440 prot32_to_prot: mov             ax,DATA_SEL
441                 mov             ds,ax
442                 mov             es,ax
443                 mov             fs,ax
444                 mov             gs,ax
445                 mov             ss,ax
446
447 ; prepare IDT for our virtual 8086 shenanigans ahead
448                 mov             si,IDT + (0x3*8)        ; INT 3h in case v86 mode doesn't trigger GPF
449                 mov             word [si+0],tss_3_fail  ; base[15:0]
450                 mov             word [si+2],CODE_SEL
451                 mov             word [si+4],0x8E00      ; P=1 DPL=0 32-bit interrupt gate
452                 mov             word [si+6],0x0000      ; base[31:16]
453
454                 mov             si,IDT + (0xD*8)        ; INT Dh for v86 GPF fault
455                 mov             word [si+0],tss_3_complete ; base[15:0]
456                 mov             word [si+2],CODE_SEL
457                 mov             word [si+4],0x8E00      ; P=1 DPL=0 32-bit interrupt gate
458                 mov             word [si+6],0x0000      ; base[31:16]
459
460 ; prepare the third one---ring 3. it will be virtual 8086 mode.
461                 cld
462                 xor             eax,eax         ; prepare EAX=0
463                 mov             ebx,eax
464                 mov             ecx,0x12345678  ; check value
465                 mov             edi,TSS_AREA_3
466                 stosd                           ; TSS+0x00 = back link
467                 mov             ax,0xF000
468                 stosd                           ; TSS+0x04 = ESP0
469                 mov             ax,DATA_SEL
470                 stosd                           ; TSS+0x08 = SS0
471                 mov             ax,0xF000
472                 stosd                           ; TSS+0x0C = ESP1
473                 mov             ax,DATA_SEL
474                 stosd                           ; TSS+0x10 = SS1
475                 mov             ax,0xF000
476                 stosd                           ; TSS+0x14 = ESP2
477                 mov             ax,DATA_SEL
478                 stosd                           ; TSS+0x18 = SS2
479                 xor             ax,ax
480                 stosd                           ; TSS+0x1C = CR3
481                 mov             eax,tss_jump_3
482                 stosd                           ; TSS+0x20 = EIP
483                 pushfd
484                 pop             eax
485                 or              eax,0x20000     ; set bit 17 = VM
486                 stosd                           ; TSS+0x24 = EFLAGS
487                 xor             eax,eax
488                 stosd                           ; TSS+0x28 = EAX
489                 stosd                           ; TSS+0x2C = ECX
490                 stosd                           ; TSS+0x30 = EDX
491                 stosd                           ; TSS+0x34 = EBX
492                 mov             ax,0xF000
493                 stosd                           ; TSS+0x38 = ESP
494                 xor             ax,ax
495                 stosd                           ; TSS+0x3C = EBP
496                 stosd                           ; TSS+0x40 = ESI
497                 stosd                           ; TSS+0x44 = EDI
498                 mov             ax,word [real_entry_patch+3]            ; our real-mode segment
499                 stosd                           ; TSS+0x48 = ES
500                 stosd                           ; TSS+0x4C = CS
501                 stosd                           ; TSS+0x50 = SS
502                 stosd                           ; TSS+0x54 = DS
503                 stosd                           ; TSS+0x58 = FS
504                 stosd                           ; TSS+0x5C = GS
505                 xor             ax,ax
506                 stosd                           ; TSS+0x60 = LDT selector (meh, I don't use it anyway)
507                 xor             ax,ax
508                 stosd                           ; TSS+0x64 = I/O map base=0, T=0
509 ; Call the TSS, so that we can IRET to return to RING 0
510                 jmp             TSS_3_SEL:0
511
512 ; now we are 16-bit RING 3 virtual 8086 mode
513 tss_jump_3:     mov             ax,0xB800       ; PROVE IT
514                 mov             es,ax           ; BY WRITING TO SCREEN
515                 mov             si,vdraw3_msg
516                 mov             di,80*4
517                 cld
518 vdraw3:         lodsb                                   ; AL = DS:SI++
519                 or              al,al
520                 jz              vdraw3e
521                 mov             ah,0x1E
522                 stosw                                   ; ES:DI = AX, DI += 2
523                 jmp             vdraw3
524 vdraw3e:
525
526 ; cause an interrupt exception to jump back into protected mode
527                 int             3                       ; will cause INT 0x0D not INT 0x03 due to virtual 8086 mode
528                 jmp             short $
529 ; if INT 3 actually fired execution will land here---because it's WRONG
530 tss_3_fail:
531                 mov             ax,DATA_SEL
532                 mov             es,ax
533                 mov             word [es:0],0x4E39      ; '9'
534                 mov             al,3
535                 out             61h,al
536                 jmp             short $
537
538 ; TSS RING-3 test COMPLETE (back into 16-bit protected mode). Switch back to TSS_2.
539 ; NOTE this is where execution is directed for a GPF, But instead of cleaning up
540 ; the stack we just discard it all and continue on. A real v86 monitor would
541 ; return execution to whatever real-mode code they want to execute and handle all
542 ; traps to I/O and interrupt.
543 tss_3_complete:
544                 mov             ax,DATA_SEL
545                 mov             ds,ax
546                 mov             es,ax
547                 mov             dword [TSS_AREA_2+0x20],tss_3_complete_2
548                 jmp             TSS_2_SEL:0
549 tss_3_complete_2:
550
551 ; active task is TSS_2_SEL. Prove we can switch tasks again by modifying
552 ; EIP in TSS_SEL, then switching tasks.
553                 mov             dword [TSS_AREA+0x20],tss_jump_2
554                 jmp             TSS_SEL:0
555 tss_jump_2:
556
557 ; having switched back to TSS_SEL, the value we left in ECX should still
558 ; be there.
559                 cmp             ecx,0x12345678
560                 jz              tss_jump_2_ecx_ok
561                 
562                 mov             ax,VIDEO_SEL
563                 mov             es,ax
564                 mov             word [es:0],0x4E33      ; '3'
565                 mov             al,3
566                 out             61h,al                  ; turn on bell
567                 hlt
568 tss_jump_2_ecx_ok:
569
570 ; switch back to real mode.
571 ; unlike the 286, switching back means clearing bit 0 of CR0
572                 xor             eax,eax                 ; clear bit 0
573                 mov             cr0,eax
574
575 real_entry_patch:jmp            0x0000:real_entry       ; the segment field is patched by code above
576 real_entry:     mov             ax,cs
577                 mov             ds,ax
578                 mov             es,ax
579                 mov             fs,ax
580                 mov             ss,ax
581                 mov             sp,0xFFF0
582
583 ; ===== REBUILD GDTR FOR PROPER REAL MODE OPERATION
584                 mov             word [GDTR],0xFFFF
585                 mov             word [GDTR+2],0
586                 mov             word [GDTR+4],0         ; GDTR: limit 0xFFFF base 0x00000000
587                 lgdt            [GDTR]                  ; load into processor GDTR
588
589                 mov             word [IDTR],0xFFFF
590                 mov             word [IDTR+2],0
591                 mov             word [IDTR+4],0         ; IDTR: limit 0xFFFF base 0x00000000
592                 lidt            [IDTR]
593
594 ; ====== PROVE WE MADE IT TO REAL MODE
595                 mov             si,vdraw2_msg
596                 mov             ax,0xB800
597                 mov             es,ax
598                 mov             di,80*6
599 vdraw2:         lodsb                                   ; AL = DS:SI++
600                 or              al,al
601                 jz              vdraw2e
602                 mov             ah,0x1E
603                 stosw                                   ; ES:DI = AX, DI += 2
604                 jmp             vdraw2
605 vdraw2e:        mov             ax,cs
606                 mov             es,ax
607
608                 sti
609
610 ; ===== DONE
611                 jmp             exit2dos
612
613 ; ===== EXIT TO DOS WITH ERROR MESSAGE DS:DX
614 exit2dos_with_message:
615                 mov             ah,9
616                 int             21h
617 ; ===== EXIT TO DOS
618 exit2dos:       mov             ax,4C00h
619                 int             21h
620
621 ; 8086 test: EFLAGS will always have bits 12-15 set
622 cpu_is_386:     pushf
623                 pop             ax
624                 and             ax,0x0FFF
625                 push            ax
626                 popf
627                 pushf
628                 pop             ax
629                 and             ax,0xF000
630                 cmp             ax,0xF000
631                 jz              cpu_is_386_not
632 ; 286 test: EFLAGS will always have bits 12-15 clear
633                 or              ax,0xF000
634                 push            ax
635                 popf
636                 pushf
637                 pop             ax
638                 and             ax,0xF000
639                 jz              cpu_is_386_not
640 ; it's a 386
641                 xor             ax,ax                   ; ZF=1
642                 ret
643 cpu_is_386_not: mov             ax,1
644                 or              ax,ax                   ; ZF=0
645                 ret
646
647 ; strings
648 str_cpu_not_386: db             "386 or higher required$"
649 str_cpu_v86_mode: db            "Virtual 8086 mode detected$"
650 vdraw2_msg:     db              "This message was drawn on screen back from real mode!",0
651 vdraw3_msg:     db              "This message was drawn on screen from virtual 8086 mode!",0
652 vdraw_msg:      db              "This message was drawn on screen from 386 16-bit protected mode!",0
653 vdraw32_msg:    db              "This message was drawn on screen from 386 32-bit protected mode!",0
654
655 ; THESE VARIABLES DO NOT EXIST IN THE ACTUAL .COM FILE.
656 ; They exist in the yet-uninitialized area of RAM just beyond the
657 ; end of the loaded COM file image.
658                 align           8
659 RALLOC:         db              0xAA
660 GDTR            equ             RALLOC+0
661 IDTR            equ             GDTR+8
662 MY_PHYS_BASE    equ             IDTR+8
663 GDT             equ             MY_PHYS_BASE+8
664 IDT             equ             GDT+MAX_SEL
665   IDT_SIZE      equ             2048
666 TSS_AREA        equ             IDT+IDT_SIZE
667   TSS_AREA_SIZE equ             2048
668 TSS_AREA_2      equ             TSS_AREA+TSS_AREA_SIZE
669   TSS_AREA_2_SIZE equ           2048
670 TSS_AREA_3      equ             TSS_AREA_2+TSS_AREA_2_SIZE
671   TSS_AREA_3_SIZE equ           2048
672 LDT_AREA        equ             TSS_AREA_3+TSS_AREA_3_SIZE
673   LDT_AREA_SIZE equ             64
674