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