summaryrefslogtreecommitdiff
path: root/v4.0/src/DEV/XMAEM/INDEI15.ASM
diff options
context:
space:
mode:
Diffstat (limited to 'v4.0/src/DEV/XMAEM/INDEI15.ASM')
-rw-r--r--v4.0/src/DEV/XMAEM/INDEI15.ASM503
1 files changed, 503 insertions, 0 deletions
diff --git a/v4.0/src/DEV/XMAEM/INDEI15.ASM b/v4.0/src/DEV/XMAEM/INDEI15.ASM
new file mode 100644
index 0000000..047648d
--- /dev/null
+++ b/v4.0/src/DEV/XMAEM/INDEI15.ASM
@@ -0,0 +1,503 @@
1PAGE 60,132
2TITLE INDEI15 - 386 XMA Emulator - Interrupt 15 handler
3
4COMMENT #
5* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
6* *
7* MODULE NAME : INDEI15 *
8* *
9* *
10* 5669-196 (C) COPYRIGHT 1988 Microsoft Corp. *
11* *
12* DESCRIPTIVE NAME: Interrupt 15H handler for the 80386 XMA emulator *
13* *
14* STATUS (LEVEL) : Version (0) Level (2.0) *
15* *
16* FUNCTION : This module emulates the MOVEBLOCK functions of interrupt *
17* 15H. The MOVEBLOCK functions are specified by an AH value*
18* of 87H to 89H. The user can use the MOVEBLOCK functions *
19* to copy a block of memory to another block of memory. *
20* This includes copying to and from memory above 1M. This *
21* is really where this function comes in handy. The user *
22* can reserve memory above 1M for use by the MOVEBLOCK *
23* functions by specifying the number of K to be reserved as *
24* a parameter on the line to load the emulator in the *
25* CONFIG.SYS file. *
26* *
27* DEVICE=INDXMAEM.SYS bbb *
28* *
29* "bbb" is the number of K to reserve for MOVEBLOCK *
30* functions *
31* *
32* We allocate a buffer for the MOVEBLOCK functions at the *
33* top of available memory. Any functions dealing with this *
34* buffer area must be handles by us. *
35* *
36* Function 87H is the actual MOVEBLOCK function. The user *
37* passes a 32 bit source address and a 32 bit destination *
38* address in a parameter list pointed to by ES:SI. CX *
39* contains the number of words to copy. We need to *
40* intercept this call and check the source and destination *
41* addresses. If either or both of these addresses is above *
42* 1M then we need to adjust the addresses so that they *
43* access the MOVEBLOCK buffer up at the top of memory. You *
44* see, the user thinks the extended memory starts right *
45* after the 1M boundary. We want to make it look like the *
46* MOVEBLOCK buffer sits right after the 1M boundary. So we *
47* monkey with the user's addresses so that they access the *
48* MOVEBLOCK buffer instead of real memory after 1M, because *
49* that memory is us. *
50* *
51* Function 88H queries how many K are above the 1M *
52* boundary. We can't tell him how much is really there *
53* because some of it is us and our XMA pages. So for this *
54* function we will just return the size of the MOVEBLOCK *
55* buffer. This function was moved to a real mode P3C*
56* interrupt handler in module INDE15H. P3C*
57* *
58* Function 89H is reserved for the MOVEBLOCK functions but *
59* is not in use right now. So for this function we just *
60* return a bad return code in AH and set the carry flag. *
61* *
62* MODULE TYPE : ASM *
63* *
64* REGISTER USAGE : 80386 Standard *
65* *
66* RESTRICTIONS : None *
67* *
68* DEPENDENCIES : None *
69* *
70* ENTRY POINT : INT15 *
71* *
72* LINKAGE : Jumped to from INDEEXC *
73* *
74* INPUT PARMS : None *
75* *
76* RETURN PARMS : None *
77* *
78* OTHER EFFECTS : None *
79* *
80* EXIT NORMAL : Go to POPIO in INDEEMU to IRET to the V86 task *
81* *
82* EXIT ERROR : None *
83* *
84* EXTERNAL *
85* REFERENCES : EMULATE - Entry point for INDEEMU *
86* POPIO - Entry in INDEEMU to check for single step *
87* interrupts, pop the registers and IRET to the *
88* V86 task *
89* POPREGS - Entry point in INDEEXC to pop the registers *
90* off the stack and IRET to the V86 task P2C*
91* *
92* SUB-ROUTINES : None *
93* *
94* MACROS : DATAOV - Add prefix for the next instruction so that it *
95* accesses data as 32 bits wide *
96* ADDROV - Add prefix for the next instruction so that it *
97* uses addresses that are 32 bits wide *
98* *
99* CONTROL BLOCKS : INDEDAT.INC *
100* *
101* CHANGE ACTIVITY : *
102* *
103* $MOD(INDEI15) COMP(LOAD) PROD(3270PC) : *
104* *
105* $D0=D0004700 410 870603 D : NEW FOR RELEASE 1.1 *
106* $P1=P0000293 410 870731 D : LIMIT LINES TO 80 CHARACTERS *
107* $P2=P0000312 410 870804 D : CLEAN UP WARNING MESSAGES *
108* $D1=D0007100 410 870817 D : CHANGE TO EMULATE XMA 2 *
109* $P3=P0000xxx 120 880331 D : MOVE FUNCTION 88H HANDLING TO INDE15H *
110* *
111* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
112#
113
114 .286P ; Enable recognition of 286 privileged instructs.
115
116 .XLIST ; Turn off the listing
117 INCLUDE INDEDAT.INC ; Include the system data structures
118
119 IF1 ; Only include the macros on the first pass
120 INCLUDE INDEOVP.MAC
121 ENDIF
122 .LIST ; Turn on the listing
123
124PROG SEGMENT PARA PUBLIC 'PROG'
125
126 ASSUME CS:PROG
127 ASSUME DS:PROG
128 ASSUME ES:NOTHING
129 ASSUME SS:NOTHING
130
131INDEI15 LABEL NEAR
132
133 EXTRN EMULATE:NEAR ; Entry point for INDEEMU
134 EXTRN POPIO:NEAR ; Entry in INDEEMU to check for single
135 ; step interrupts and return to the
136 ; V86 task
137 EXTRN POPREGS:NEAR ; Entry in INDEEXC to return to the P2C
138 ; V86 task
139
140 PUBLIC INDEI15
141 PUBLIC INT15
142 PUBLIC TTTABLE
143
144PAGE
145
146INT15 PROC NEAR
147
148 CLD ; All string operations go forward
149
150; We handle the INT 15H functions for MOVEBLOCK interface. These functions
151; are specified by an AH value of 87H to 89H. Function 87H is the MOVEBLOCK
152; function. Function 88H queries the size of memory above 1M. Function 89H
153; is reserved but not supported so we return a return code of 86H.
154
155 CMP SS:BYTE PTR [BP+BP_AX+1],87H ; Is AH asking for function 87H?
156 JB NOTMINE ; No. It's too low. It's out of our
157 ; range so we'll pass it on to the
158 ; real vector.
159 JE MOVEBLK ; It is 87H! Let's go do the MOVEBLOCK.
160
161 CMP SS:BYTE PTR [BP+BP_AX+1],89H ; Is AH asking for function 89H?
162 JNE NOTMINE ; No. It's not our function so @P3C
163 ; so we'll pass it on to the real
164 ; vector.
165 ; @P3D
166 MOV SS:BYTE PTR [BP+BP_AX+1],86H ; It's 89H. Sorry we don't support
167 ; that function. Put an 86H return
168 ; code in AH.
169 OR WORD PTR SS:[BP+BP_FL],1 ; Set the carry flag
170 JMP POPIO ; And return to the V86 task
171
172; Hey, it's not MY interrupt.
173
174NOTMINE:
175 JMP DOINT ; Go pass the interrupt back to the
176 ; real INT 15H vector
177
178
179; Function 88H code to query the size of memory above 1M was moved to 3@P3D
180; INDE15H.
181
182PAGE
183; The user wants to move a block of memory. Now the source and target of the
184; MOVEBLOCK can each be below 1M or above 1M. For addresses above 1M we must
185; make adjustments so that the MOVEBLOCK is done to and/or from the MOVEBLOCK
186; buffer in high memory. The user passes a parameter list which is pointed
187; at by ES:SI. At offset 0EH is a 32 bit pointer to the source block. At
188; offset 1AH is a 32 bit pointer to the destination block. CX contains the
189; number of words to move. Here we go!
190
191MOVEBLK:
192 MOV AX,HUGE_PTR ; Load DS and ES with a selector that
193 MOV DS,AX ; accesses all of memory as data
194 MOV ES,AX
195
196; Get the user's ES:SI and convert it to a 32 bit offset in ESI.
197
198 DATAOV ; Purge ESI
199 SUB SI,SI
200 MOV SI,SS:[BP+BP_SI] ; Load SI with the user's SI
201
202 DATAOV ; Purge EBX
203 SUB BX,BX
204 MOV BX,10H ; Set EBX to 1M by loading it with 10H
205 DATAOV ; and shifting it left 16 bits to
206 SHL BX,16 ; multiply by 64K
207
208 DATAOV ; Sterilize EAX
209 SUB AX,AX
210 MOV AX,SS:[BP+BP_VMES] ; Load AX with the user's ES
211 DATAOV ; Shift it left four bits to convert it
212 SHL AX,4 ; to an offset
213
214 DATAOV ; Add the ES offset on to SI. Now ESI
215 ADD SI,AX ; is the offset from 0 of the user's
216 ; parameter list.
217 DATAOV ; Add 1AH to SI. Now it points to the
218 ADD SI,1AH ; 32 bit destination address.
219
220 DATAOV
221 ADDROV ; Get the 32 bit destination address
222 LODSW ; into EAX
223
224 ADDROV ; Intel bug # A0-119
225 NOP ; Intel bug # A0-119
226
227 DATAOV ; Clear the top eight bits of any
228 SHL AX,8 ; residual gunk. Only 24 bit ;P1C
229 DATAOV ; addresses (16M) are allowed anyway.
230 SHR AX,8 ; Shift the bits off the left end and
231 ; shift zeroes back in.
232 DATAOV ; Move this clean value into EDI
233 MOV DI,AX ; EDI now has the destination address
234
235 DATAOV ; Check if this address is over 1M. If
236 CMP DI,BX ; so then it's going to our MOVEBLOCK
237 ; buffer.
238 JB OK1 ; It's below 1M? OK. Leave it alone.
239
240; The destination is above 1M so we have to modify the destination address so
241; that it points to our MOVEBLOCK buffer.
242
243 PUSH DS ; Save DS
244 MOV AX,SYS_PATCH_DS ; Load DS with the selector for our data
245 MOV DS,AX ; segment
246
247 DATAOV ; Clean up EAX
248 SUB AX,AX
249 MOV AX,MAXMEM ; Load the total number of K on the box
250 SUB AX,BUFF_SIZE ; Subtract the MOVEBLOCK buffer size
251 SUB AX,1024 ; Subtract 1M (/1K) for 0 to 1M. This
252 ; leaves AX with the number of K from
253 ; 1M to the MOVEBLOCK buffer.
254 POP DS ; Restore DS
255 DATAOV ; Multiply EAX by 1K (shift left 10) to
256 SHL AX,10 ; convert it to an offset from 1M of
257 ; the MOVEBLOCK buffer
258 DATAOV ; Add this to EDI. EDI now points to
259 ADD DI,AX ; a location within (hopefully) the
260 ; MOVEBLOCK buffer as if the buffer
261 ; were located at the 1M boundary.
262
263; Now let's get the source address
264
265OK1:
266 DATAOV ; Subtract 0C from ESI to point ESI to
267 SUB SI,0CH ; offset 0E in the parameter list
268
269 DATAOV
270 ADDROV ; Get the 32 bit source address into
271 LODSW ; EAX
272
273 ADDROV ; Intel bug # A0-119
274 NOP ; Intel bug # A0-119
275
276 DATAOV ; Clear the top eight bits of any
277 SHL AX,8 ; residual gunk. Only 24 bit address
278 DATAOV ; (16M) are allowed. Shift the gunky
279 SHR AX,8 ; bits off the left end and shift
280 ; zeroes back in.
281 DATAOV ; Move this clean value into ESI
282 MOV SI,AX ; ESI now has the source address
283
284 DATAOV ; Check if this address is over 1M. If
285 CMP SI,BX ; so then it's goin' to our MOVEBLOCK
286 ; buffer.
287 JB OK2 ; It's below 1M? OK. Let it be.
288
289; The source is above 1M so we have to modify the source address so that it
290; points to our MOVEBLOCK buffer.
291
292 PUSH DS ; Save DS
293 MOV AX,SYS_PATCH_DS ; Load DS with the selector for our data
294 MOV DS,AX ; segment
295
296 DATAOV ; Sanitize up EAX
297 SUB AX,AX
298 MOV AX,MAXMEM ; Load the total number of K on the box
299 SUB AX,BUFF_SIZE ; Subtract the MOVEBLOCK buffer size
300 SUB AX,1024 ; Subtract 1M (/1K) for 0 to 1M. This
301 ; leaves AX with the number of K from
302 ; 1M to the MOVEBLOCK buffer.
303 POP DS ; Restore DS
304 DATAOV ; Multiply EAX by 1K (shift left 10) to
305 SHL AX,10 ; convert it to an offset from 1M of
306 ; the MOVEBLOCK buffer
307 DATAOV ; Add this to ESI. ESI now points to
308 ADD SI,AX ; a location within (hopefully) the
309 ; MOVEBLOCK buffer as if the buffer
310 ; were located at the 1M boundary.
311
312; Our pointers are all set. Let's get CX and do the copy for the guy.
313
314OK2:
315 MOV CX,SS:[BP+BP_CX] ; Get the user's CX
316 TEST CL,01H ; Is this an even number?
317 JZ MOV4 ; If so, we can make the copy faster
318 ; by moving double words
319 ADDROV ; Nope. It's odd. We'll just do the
320 REP MOVSW ; copy with words.
321
322 ADDROV ; Intel bug # A0-119
323 NOP ; Intel bug # A0-119
324
325 JMP MOVCOM ; Skip over the double word copy
326
327MOV4:
328 SHR CX,1 ; Divide the count by two since we'll
329 ; be copying double words
330 DATAOV ; Do it 32 bits wide
331 ADDROV ; Use the 32 bit ESI and EDI
332 REP MOVSW ; Ready? ZOOOOM!
333
334 ADDROV ; Intel bug # A0-119
335 NOP ; Intel bug # A0-119
336
337; Now let's set the flags and return code in AH to show that every thing went
338; A-OK.
339
340MOVCOM:
341 MOV SS:BYTE PTR [BP+BP_AX+1],0 ; Set a zero return code in AH
342 AND WORD PTR SS:[BP+BP_FL],0FFFEH ; Reset the carry flag
343 OR WORD PTR SS:[BP+BP_FL],40H ; Set the zero flag
344
345 JMP POPIO ; Return to the V86 task
346
347PAGE
348
349; It's not a MOVEBLOCK function so we'll just pass the interrupt on to the real
350; interrupt handler.
351
352DOINT:
353 MOV AX,HUGE_PTR ; Load ES with a selector that accesses
354 MOV ES,AX ; all of memory as data
355 DATAOV ; Load EDI with the user's ESP
356 MOV DI,SS:[BP+BP_SP]
357
358 SUB DI,6 ; Decrement "SP" by six to make room
359 ; for our simulated interrupt that
360 ; will put the flags, CS and IP on
361 ; the stack. This assumes that there
362 ; are indeed six bytes left on the
363 ; stack.
364 MOV SS:WORD PTR [BP+BP_SP],DI ; Set the user's new SP
365
366 DATAOV ; Get the user's SS into our AX
367 MOV AX,SS:[BP+BP_SS]
368 DATAOV ; Shift "SS" left four bits to convert
369 SHL AX,4 ; it to an offset
370 DATAOV ; Add this to "SP" in DI to make EDI
371 ADD DI,AX ; a 32 bit offset from 0 of the user's
372 ; stack
373
374; Now put the flags, CS and IP on the V86 task's stack. They are put on in the
375; order IP, CS, flags. This is backwards from the INT push order of flags, CS
376; and then IP. This is because we are moving forward through memory (CLD)
377; whereas the stack grows backwards through memory as things pushed on to it.
378
379 MOV AX,SS:[BP+BP_IP] ; Get the user's IP
380 ADDROV ; And put it on his stack
381 STOSW
382
383 ADDROV ; Intel bug # A0-119
384 NOP ; Intel bug # A0-119
385
386 MOV AX,SS:[BP+BP_CS] ; Get the user's CS
387 ADDROV ; And put it on his stack
388 STOSW
389
390 ADDROV ; Intel bug # A0-119
391 NOP ; Intel bug # A0-119
392
393 MOV AX,SS:[BP+BP_FL] ; Get the user's flags
394 OR AX,3000H ; Set the IOPL to 3 so we get fewer
395 ; faults
396 ADDROV ; And put them on his stack
397 STOSW
398
399 ADDROV ; Intel bug # A0-119
400 NOP ; Intel bug # A0-119
401
402 AND AX,3CFFH ; Clean up the flags for our IRET
403 MOV WORD PTR SS:[BP+BP_FL],AX ; Put them on our stack
404
405 MOV SI,SS:[BP+BP_EX] ; Get the interrupt number
406 SHL SI,2 ; Multiply by four 'cause interrupt
407 ; vectors are four bytes long
408 MOV AX,HUGE_PTR ; Load DS with a selector that accesses
409 MOV DS,AX ; all of memory as data
410 LODSW ; Get the IP of the interrupt vector
411 ; from the interrupt vector table
412 MOV WORD PTR SS:[BP+BP_IP],AX ; Put it in the IP saved on our stack
413 LODSW ; Get the CS of the interrupt vector
414 ; from the interrupt vector table
415 MOV WORD PTR SS:[BP+BP_CS],AX ; Put it in the CS saved on our stack
416
417 JMP POPREGS ; Now when we do an IRET we will @P2C
418 ; actually be giving control to the
419 ; real INT 15H vector.
420INT15 ENDP
421
422PAGE
423; Macros used to define data areas
424
425; DDL - Define a label and make it public
426
427DDL MACRO NAME,SIZE
428 PUBLIC &NAME
429&NAME LABEL &SIZE
430 ENDM
431
432
433; DDW - Define a word and make it public
434
435DDW MACRO NAME,VALUE
436 IFNB <&NAME> ;; If a name was given then make it public
437 PUBLIC &NAME
438 ENDIF
439 IFNB <&VALUE> ;; If a value was given then initialize the
440&NAME DW &VALUE ;; variable to that value
441 ELSE ;; Else initialize it to 0
442&NAME DW 0
443 ENDIF
444 ENDM
445
446
447; Now lets define some data. Remember, these are all PUBLIC even though they
448; are not listed at the top of the program as being such. It's easy to lose
449; these guys.
450
451 DDW REAL_SP,0 ; Our initial SP when we come up in real mode
452
453 DDW REAL_SS,0 ; Our initial SS when we come up in real mode
454
455 DDW REAL_CS,0 ; Our initial CS when we come up in real mode
456
457 DDW PGTBLOFF,0 ; The offset of the normal page tables
458
459 DDW SGTBLOFF,0 ; The offset of the page directory
460
461 DDW NORMPAGE,0 ; The entry for the first page directory entry
462 DDW ,0 ; which points to the first normal page table.
463 ; A 32 bit value
464 DDW XMAPAGE,7 ; Page directory entry that points to the first
465 DDW ,0011H ; XMA page table at 11000:0. Access and present
466 ; bits set. It, too, is a 32 bit value.
467 DDW BUFF_SIZE,0 ; Size of the MOVEBLOCK buffer. Initialized to 0.
468
469 DDW MAXMEM,1000H ; Total amount of K in the box. Initialized to 4M.
470
471 DDW CRT_SELECTOR,C_BWCRT_PTR ; Selector for the display buffer
472
473; And now, the world famous Translate Table!! YEAAAA!!
474;
475; The first 160 entries (0 to 640K) are initialized to blocks 0 to '9F'X. D1A
476; This is to emulate the XMA 2 device driver which uses these blocks to back D1A
477; the memory on the mother board from 0 to 640K which it disabled. It sets D1A
478; up the translate table for bank 0 such that it maps the XMA memory from 0 D1A
479; to 640K to conventional memory at 0 to 640K. So we emulate that here by D1A
480; initializing the firs 160 entries in the translate table. D1A
481
482TTTABLE:
483 BLOCK = 0 ; Start with block number 0 @D1A
484 REPT 20 ; Do 20 times (20 x 8 = 160) @D1A
485 DW BLOCK,BLOCK+1,BLOCK+2,BLOCK+3,BLOCK+4,BLOCK+5,BLOCK+6,BLOCK+7
486 ; Define eight translate table entries @D1A
487 ; initialized to the block number D1A
488 BLOCK = BLOCK + 8 ; Increment the block number to the next set @D1A
489 ENDM ; of eight translate table entries @D1A
490
491 DW 96 + 256*15 DUP(0FFFH) ; The rest of the translate table @D1C
492
493TTTABLE_END: ; Label to mark the end of the translate table
494
495
496; Define our stack for when we're in protect mode
497
498 DDW MON_STACK_BASE,<500 DUP(0)>
499 DDL SP_INIT,WORD ; Top of the stack. The initial SP points here.
500
501PROG ENDS
502
503 END