source: xtideuniversalbios/trunk/XTIDE_Universal_BIOS/Src/Device/Serial/SerialCommand.asm @ 214

Last change on this file since 214 was 214, checked in by gregli@…, 12 years ago

Rework of the serial write loop and read/write timeout code, resulting in significant throughput gains (increase from 8K bytes to 36K bytes, over a 460K baud link connected to a 4.77MHz 8088)

File size: 20.5 KB
Line 
1; Project name  :   XTIDE Universal BIOS
2; Description   :   Serial Device Command functions.
3
4; Section containing code
5SECTION .text
6
7;--------------- UART Equates -----------------------------
8;
9; Serial Programming References:
10;    http://en.wikibooks.org/wiki/Serial_Programming
11;
12
13SerialCommand_UART_base                         EQU     0
14SerialCommand_UART_transmitByte                 EQU     0
15SerialCommand_UART_receiveByte                  EQU     0
16SerialCommand_UART_divisorLow                   EQU     0
17; Values for UART_divisorLow:
18; 60h = 1200, 30h = 2400, 18h = 4800, 0ch = 9600, 6 = 19200, 3 = 38400, 2 = 57600, 1 = 115200
19
20SerialCommand_UART_divisorLow_startingBaud      EQU   030h
21; We support 4 baud rates, starting here going higher and skipping every other baud rate
22; Starting with 30h, that means 30h (1200 baud), 0ch (9600 baud), 3 (38400 baud), and 1 (115200 baud)
23; Note: hardware baud multipliers (2x, 4x) will impact the final baud rate and are not known at this level
24
25SerialCommand_UART_interruptEnable              EQU     1
26SerialCommand_UART_divisorHigh                  EQU     1
27; UART_divisorHigh is zero for all speeds including and above 1200 baud
28
29SerialCommand_UART_interruptIdent               EQU     2
30SerialCommand_UART_FIFOControl                  EQU     2
31
32SerialCommand_UART_lineControl                  EQU     3
33
34SerialCommand_UART_modemControl                 EQU     4
35
36SerialCommand_UART_lineStatus                   EQU     5
37
38SerialCommand_UART_modemStatus                  EQU     6
39
40SerialCommand_UART_scratch                      EQU     7
41
42SerialCommand_Protocol_Write                    EQU     3
43SerialCommand_Protocol_Read                     EQU     2
44SerialCommand_Protocol_Inquire                  EQU     0
45SerialCommand_Protocol_Header                   EQU     0a0h
46
47;--------------------------------------------------------------------
48; SerialCommand_OutputWithParameters
49;   Parameters:
50;       BH:     Non-zero if 48-bit addressing used
51;               (ignored at present as 48-bit addressing is not supported)
52;       BL:     IDE Status Register bit to poll after command
53;               (ignored at present, since there is no IDE status register to poll)
54;       ES:SI:  Ptr to buffer (for data transfer commands)
55;       DS:DI:  Ptr to DPT (in RAMVARS segment)
56;       SS:BP:  Ptr to IDEREGS_AND_INTPACK
57;   Returns:
58;       AH:     INT 13h Error Code
59;       CF:     Cleared if success, Set if error
60;   Corrupts registers:
61;       AL, BX, CX, DX, (ES:SI for data transfer commands)
62;--------------------------------------------------------------------
63ALIGN JUMP_ALIGN
64SerialCommand_OutputWithParameters:
65
66        mov     ah,(SerialCommand_Protocol_Header | SerialCommand_Protocol_Read)
67
68        mov     al,[bp+IDEPACK.bCommand]
69
70        cmp     al,20h          ; Read Sectors IDE command
71        jz      .readOrWrite
72        inc     ah              ; now SerialCommand_Protocol_Write
73        cmp     al,30h          ; Write Sectors IDE command
74        jz      .readOrWrite
75
76;  all other commands return success
77;  including function 0ech which should return drive information, this is handled with the identify functions
78        xor     ah,ah           ;  also clears carry
79        ret
80
81.readOrWrite:
82        mov     [bp+IDEPACK.bFeatures],ah       ; store protocol command
83
84        mov     dl, byte [di+DPT.bSerialPortAndBaud]
85
86; fall-through
87
88;--------------------------------------------------------------------
89; SerialCommand_OutputWithParameters_DeviceInDL
90;   Parameters:
91;       AH:     Protocol Command
92;       DL:     Packed I/O port and baud rate
93;       ES:SI:  Ptr to buffer (for data transfer commands)
94;       SS:BP:  Ptr to IDEREGS_AND_INTPACK
95;   Returns:
96;       AH:     INT 13h Error Code
97;       CF:     Cleared if success, Set if error
98;   Corrupts registers:
99;       AL, BX, CX, DX, (ES:SI for data transfer commands)
100;--------------------------------------------------------------------
101SerialCommand_OutputWithParameters_DeviceInDL:
102
103        push    si
104        push    di
105        push    bp
106        push    es
107
108;
109; Unpack I/O port and baud from DPT
110;       Port to DX more or less for the remainder of the routine
111;       Baud in CH until UART initialization is complete
112;
113        mov     dh, ((DEVICE_SERIAL_PACKEDPORTANDBAUD_STARTINGPORT & 0f00h) >> (8+1))
114        shl     dx, 1       ; port offset already x4, needs one more shift to be x8
115        mov     cl, dl
116
117        and     cl, (DEVICE_SERIAL_PACKEDPORTANDBAUD_BAUDMASK << 1)
118        mov     ch, SerialCommand_UART_divisorLow_startingBaud
119        shr     ch, cl
120        adc     ch, 0
121
122        and     dl, ((DEVICE_SERIAL_PACKEDPORTANDBAUD_PORTMASK << 1) & 0ffh)
123        add     dx, byte (DEVICE_SERIAL_PACKEDPORTANDBAUD_STARTINGPORT & 0ffh)
124
125        mov     al,[bp+IDEPACK.bSectorCount]
126
127;
128; Command byte and sector count live at the top of the stack, pop/push are used to access
129;
130        push    ax
131
132;       cld     ; Shouldn't be needed. DF has already been cleared (line 24, Int13h.asm)
133
134;----------------------------------------------------------------------
135;
136; Initialize UART
137;
138; We do this each time since DOS (at boot) or another program may have
139; decided to reprogram the UART
140;
141        mov     bl,dl           ; setup BL with proper values for read/write loops (BH comes later)
142       
143        mov     al,83h
144        add     dl,SerialCommand_UART_lineControl
145        out     dx,al
146
147        mov     al,ch
148        mov     dl,bl           ; divisor low
149        out     dx,al
150
151        xor     ax,ax
152        inc     dx              ; divisor high
153        push    dx
154        out     dx,al
155
156        mov     al,047h
157        inc     dx              ;  fifo
158        out     dx,al
159
160        mov     al,03h
161        inc     dx              ;  linecontrol
162        out     dx,al
163
164        mov     al,0bh
165        inc     dx              ;  modemcontrol
166        out     dx,al
167
168        inc     dx              ;  linestatus (no output now, just setting up BH for later use)
169        mov     bh,dl
170
171        pop     dx              ; base, interrupts disabled
172        xor     ax,ax
173        out     dx,al
174
175;----------------------------------------------------------------------
176;
177; Send Command
178;
179; Sends first six bytes of IDEREGS_AND_INTPACK as the command
180;
181        push    es              ; save off real buffer location
182        push    si
183
184        mov     si,bp           ; point to IDEREGS for command dispatch;
185        push    ss
186        pop     es
187
188        mov     di,0ffffh       ; initialize checksum for write
189        mov     bp,di
190
191        mov     cx,4            ; writing 3 words (plus 1)
192
193        cli                     ; interrupts off... 
194
195        call    SerialCommand_WriteProtocol.entry
196
197        pop     di              ; restore real buffer location (note change from SI to DI)
198                                ; Buffer is primarily referenced through ES:DI throughout, since
199                                ; we need to store (read sector) faster than we read (write sector)
200        pop     es
201
202.nextSectorNormalize:           
203
204        call    Registers_NormalizeESDI 
205       
206        pop     ax              ; load command byte (done before call to .nextSector on subsequent iterations)
207        push    ax
208
209;
210; Top of the read/write loop, one iteration per sector
211;
212.nextSector:
213        mov     si,0ffffh       ; initialize checksum for read or write
214        mov     bp,si
215
216        mov     cx,0101h        ; writing 256 words (plus 1)
217
218        shr     ah,1            ; command byte, are we doing a write?
219        jnc     .readEntry
220
221        xchg    si,di
222        call    SerialCommand_WriteProtocol.entry
223        xchg    si,di
224
225        inc     cx              ; CX = 1 now (0 out of WriteProtocol)
226        jmp     .readEntry
227
228;----------------------------------------------------------------------
229;
230; Timeout
231;
232; To save code space, we use the contents of DL to decide which byte in the word to return for reading.
233;
234.readTimeout:
235        push    ax              ; not only does this push preserve AX (which we need), but it also
236                                ; means the stack has the same number of bytes on it as when we are 
237                                ; sending a packet, important for error cleanup and exit
238        mov     ah,1
239        call    SerialCommand_WaitAndPoll_Read
240        pop     ax
241        test    dl,1
242        jz      .readByte1Ready
243        jmp     .readByte2Ready     
244
245;----------------------------------------------------------------------------
246;
247; Read Block (without interrupts, used when there is a FIFO, high speed)
248;
249; NOTE: This loop is very time sensitive.  Literally, another instruction
250; cannot be inserted into this loop without us falling behind at high
251; speed (460.8K baud) on a 4.77Mhz 8088, making it hard to receive
252; a full 512 byte block.
253;
254.readLoop:
255        stosw                   ; store word in caller's data buffer
256
257        add     bp, ax          ; update Fletcher's checksum
258        adc     bp, 0
259        add     si, bp
260        adc     si, 0
261
262.readEntry:     
263        mov     dl,bh
264        in      al,dx
265        shr     al,1            ; data ready (byte 1)?
266        mov     dl,bl           ; get ready to read data
267        jnc     .readTimeout    ; nope not ready, update timeouts
268
269;
270; Entry point after initial timeout.  We enter here so that the checksum word
271; is not stored (and is left in AX after the loop is complete).
272;
273.readByte1Ready:
274        in      al, dx          ; read data byte 1
275
276        mov     ah, al          ; store byte in ah for now
277
278;
279; note the placement of this reset of dl to bh, and that it is
280; before the return, which is assymetric with where this is done
281; above for byte 1.  The value of dl is used by the timeout routine
282; to know which byte to return to (.read_byte1_ready or
283; .read_byte2_ready)
284;
285        mov     dl,bh
286
287        in      al,dx
288        shr     al,1            ; data ready (byte 2)?
289        jnc     .readTimeout
290.readByte2Ready:
291        mov     dl,bl
292        in      al, dx          ; read data byte 2
293
294        xchg    al, ah          ; ah was holding byte 1, reverse byte order
295
296        loop    .readLoop
297
298        sti                     ; interrupts back on ASAP, between packets
299
300;
301; Compare checksums
302;
303        xchg    ax,bp
304        xor     ah,al
305        mov     cx,si
306        xor     cl,ch
307        mov     al,cl
308        cmp     ax,bp
309        jnz     SerialCommand_OutputWithParameters_Error
310
311;----------------------------------------------------------------------
312;
313; Clear read buffer
314;
315; In case there are extra characters or an error in the FIFO, clear it out.
316; In theory the initialization of the UART registers above should have
317; taken care of this, but I have seen cases where this is not true.
318;
319.clearBuffer:
320        mov     dl,bh
321        in      al,dx
322        mov     dl,bl
323        test    al,08fh
324        jz      .clearBufferComplete
325        shr     al,1
326        in      al,dx
327        jc      .clearBuffer    ; note CF from shr above
328        jmp     SerialCommand_OutputWithParameters_Error
329
330.clearBufferComplete:
331
332        pop     ax              ; sector count and command byte
333        dec     al              ; decrememnt sector count
334        push    ax              ; save
335        jz      SerialCommand_OutputWithParameters_ReturnCodeInALCF    ; CF clear from .clearBuffer test above
336
337        cli                     ; interrupts back off for ACK byte to host
338                                ; (host could start sending data immediately)
339        out     dx,al           ; ACK with next sector number
340
341;
342; Normalize buffer pointer for next go round, if needed
343;
344        test    di,di
345        jns     short .nextSector
346        jmp     short .nextSectorNormalize
347
348;---------------------------------------------------------------------------
349;
350; Cleanup, error reporting, and exit
351;
352
353;
354; Used in situations where a call is underway, such as with SerialCommand_WaitAndPoll
355;
356ALIGN JUMP_ALIGN
357SerialCommand_OutputWithParameters_ErrorAndPop4Words:
358        add     sp,8
359
360ALIGN JUMP_ALIGN
361SerialCommand_OutputWithParameters_Error:
362        stc
363        mov     al,1
364
365ALIGN JUMP_ALIGN
366SerialCommand_OutputWithParameters_ReturnCodeInALCF:
367        sti
368        mov     ah,al
369
370        pop     bp              ;  recover ax (command and count) from stack, throw away
371
372        pop     es
373        pop     bp
374        pop     di
375        pop     si
376
377        ret
378
379;--------------------------------------------------------------------
380; SerialCommand_WriteProtocol
381;
382; NOTE: As with its read counterpart, this loop is very time sensitive. 
383; Although it will still function, adding additional instructions will 
384; impact the write througput, especially on slower machines. 
385;
386;   Parameters:
387;       ES:SI:  Ptr to buffer
388;       CX:     Words to write, plus 1
389;       BP/DI:  Initialized for Checksum (-1 in each)
390;       DH:     I/O Port high byte
391;       BX:     LineStatus Register address (BH) and Receive/Transmit Register address (BL)
392;   Returns:
393;       BP/DI:  Checksum for written bytes, compared against ACK from server in .readLoop
394;       CX:     Zero
395;       DL:     Receive/Transmit Register address
396;   Corrupts registers:
397;       AX
398;--------------------------------------------------------------------
399ALIGN JUMP_ALIGN
400SerialCommand_WriteProtocol:
401.writeLoop:
402        es lodsw                ; fetch next word
403
404        out     dx,al           ; output first byte
405
406        add     bp,ax           ; update checksum
407        adc     bp,0
408        add     di,bp
409        adc     di,0
410
411        mov     dl,bh           ; transmit buffer empty?
412        in      al,dx
413        test    al,20h
414        jz      .writeTimeout2  ; nope, use our polling routine
415
416.writeByte2Ready:
417        mov     dl,bl
418        mov     al,ah           ; output second byte
419        out     dx,al
420
421.entry:
422        mov     dl,bh           ; transmit buffer empty?
423        in      al,dx
424        test    al,20h
425        mov     dl,bl
426        jz      .writeTimeout1  ; nope, use our polling routine
427
428.writeByte1Ready:
429        loop    .writeLoop
430
431        mov     ax,di           ; fold Fletcher's checksum and output
432        xor     al,ah
433        out     dx,al           ; byte 1
434
435        call    SerialCommand_WaitAndPoll_Write
436
437        mov     ax,bp
438        xor     al,ah
439        out     dx,al           ; byte 2
440
441        ret
442
443.writeTimeout2:
444        mov     dl,ah           ; need to preserve AH, but don't need DL (will be reset upon return)
445        call    SerialCommand_WaitAndPoll_Write
446        mov     ah,dl
447        jmp     .writeByte2Ready
448       
449.writeTimeout1:
450        mov     ax,.writeByte1Ready
451        push    ax              ; return address for ret at end of SC_writeTimeout2
452;;; fall-through
453
454;--------------------------------------------------------------------
455; SerialCommand_WaitAndPoll
456;
457;   Parameters:
458;       AH:     UART_LineStatus bit to test (20h for write, or 1h for read)
459;               One entry point fills in AH with 20h for write
460;       DX:     Port address (OK if already incremented to UART_lineStatus)
461;       BX:   
462;       Stack:  2 words on the stack below the command/count word
463;   Returns:
464;       Returns when desired UART_LineStatus bit is cleared
465;       Jumps directly to error exit if timeout elapses (and cleans up stack)
466;   Corrupts registers:
467;       AX
468;--------------------------------------------------------------------
469
470SerialCommand_WaitAndPoll_SoftDelayTicks   EQU   20
471
472ALIGN JUMP_ALIGN
473SerialCommand_WaitAndPoll_Write:
474        mov     ah,20h
475;;; fall-through
476
477ALIGN JUMP_ALIGN
478SerialCommand_WaitAndPoll_Read:
479        push    cx
480        push    dx
481
482;
483; We first poll in a tight loop, interrupts off, for the next character to come in/be sent
484;
485        xor     cx,cx
486.readTimeoutLoop:
487        mov     dl,bh               
488        in      al,dx
489        test    al,ah
490        jnz     .readTimeoutComplete
491        loop    .readTimeoutLoop
492
493;
494; If that loop completes, then we assume there is a long delay involved, turn interrupts back on
495; and wait for a given number of timer ticks to pass.
496;
497        sti
498        mov     cl,SerialCommand_WaitAndPoll_SoftDelayTicks
499        call    Timer_InitializeTimeoutWithTicksInCL
500.WaitAndPoll:
501        call    Timer_SetCFifTimeout
502        jc      SerialCommand_OutputWithParameters_ErrorAndPop4Words
503        in      al,dx
504        test    al,ah
505        jz      .WaitAndPoll
506        cli
507
508.readTimeoutComplete:
509        pop     dx
510        pop     cx
511        ret
512
513;--------------------------------------------------------------------
514; SerialCommand_IdentifyDeviceToBufferInESSIwithDriveSelectByteInBH
515;   Parameters:
516;       BH:     Drive Select byte for Drive and Head Select Register
517;       DS:     Segment to RAMVARS
518;       ES:SI:  Ptr to buffer to receive 512-byte IDE Information
519;       CS:BP:  Ptr to IDEVARS
520;   Returns:
521;       AH:     INT 13h Error Code
522;               NOTE: Not set (or checked) during drive detection 
523;       CF:     Cleared if success, Set if error
524;   Corrupts registers:
525;       AL, BL, CX, DX, SI, DI, ES
526;--------------------------------------------------------------------
527ALIGN JUMP_ALIGN
528SerialCommand_IdentifyDeviceToBufferInESSIwithDriveSelectByteInBH:
529;
530; To improve boot time, we do our best to avoid looking for slave serial drives when we already know the results 
531; from the looking for a master.  This is particuarly true when doing a COM port scan, as we will end up running
532; through all the COM ports and baud rates a second time. 
533;
534; But drive detection isn't the only case - we also need to get the right drive when called on int13h/25h. 
535;
536; The decision tree:
537;
538;    Master:
539;          bSerialPackedPortAndBaud Non-Zero:   -> Continue with bSerialPackedAndBaud (1)
540;          bSerialPackedPortAndBaud Zero: 
541;                         bLastSerial Zero:     -> Scan (2)
542;                         bLastSerial Non-Zero: -> Continue with bLastSerial (3)
543;                                   
544;    Slave:
545;          bSerialPackedPortAndBaud Non-Zero: 
546;                         bLastSerial Zero:     -> Error - Not Found (4)
547;                         bLastSerial Non-Zero: -> Continue with bSerialPackedAndBaud (5)
548;          bSerialPackedPortAndBaud Zero:     
549;                         bLastSerial Zero:     -> Error - Not Found (4)
550;                         bLastSerial Non-Zero: -> Continue with bLastSerial (6)
551;
552; (1) This was a port/baud that was explicilty set with the configurator.  In the drive detection case, as this 
553;     is the Master, we are checking out a new controller, and so don't care about the value of bLastSerial. 
554;     And as with the int13h/25h case, we just go off and get the needed information using the user's setting.
555; (2) We are using the special .ideVarsSerialAuto strucutre.  During drive detection, we would only be here
556;     if bLastSerial is zero (since we only scan if no explicit drives are set), so we go off to scan.
557; (3) We are using the special .ideVarsSerialAuto strucutre.  We won't get here during drive detection, but
558;     we might get here on an int13h/25h call.  If we have scanned COM drives, they are the ONLY serial drives
559;     in use, and so bLastSerial will reflect the port/baud setting for the scanned COM drives.
560; (4) No master has been found yet, therefore no slave should be found.  Avoiding the slave reduces boot time, 
561;     especially in the full COM port scan case.  Note that this is different from the hardware IDE, where we
562;     will scan for a slave even if a master is not present.  Note that if ANY master had been previously found,
563;     we will do the slave scan, which isn't harmful, it just wates time.  But the most common case (by a wide
564;     margin) will be just one serial controller.
565; (5) A COM port scan for a master had been previously completed, and a drive was found.  In a multiple serial
566;     controller scenario being called with int13h/25h, we need to use the value in bSerialPackedPortAndBaud 
567;     to make sure we get the proper drive.
568; (6) A COM port scan for a master had been previously completed, and a drive was found.  We would only get here 
569;     if no serial drive was explicitly set by the user in the configurator or that drive had not been found. 
570;     Instead of performing the full COM port scan for the slave, use the port/baud value stored during the 
571;     master scan.
572;       
573        mov     dl,[cs:bp+IDEVARS.bSerialPackedPortAndBaud]     
574        mov     al, byte [RAMVARS.xlateVars+XLATEVARS.bLastSerial]
575               
576        test    bh, FLG_DRVNHEAD_DRV
577        jz      .master
578
579        test    al,al           ; Take care of the case that is different between master and slave. 
580        jz      .error          ; Because we do this here, the jz after the "or" below will not be taken
581
582; fall-through
583.master:       
584        test    dl,dl
585        jnz     .identifyDeviceInDL
586
587        or      dl,al           ; Move bLast into position in dl, as well as test for zero
588        jz      .scanSerial
589       
590; fall-through
591.identifyDeviceInDL:   
592
593        push    bp              ; setup fake IDEREGS_AND_INTPACK
594
595        push    dx
596
597        mov     cl,1            ; 1 sector to move
598        push    cx
599
600        mov     bl,0a0h         ; protocol command to ah and onto stack with bh
601        mov     ah,bl
602
603        push    bx
604
605        mov     bp,sp
606        call    SerialCommand_OutputWithParameters_DeviceInDL
607
608        pop     bx
609
610        pop     cx
611        pop     dx
612
613        pop     bp
614; 
615; place packed port/baud in RAMVARS, read by FinalizeDPT and DetectDrives
616;
617; Note that this will be set during an int13h/25h call as well.  Which is OK since it is only used (at the
618; top of this routine) for drives found during a COM scan, and we only COM scan if there were no other 
619; COM drives found.  So we will only reaffirm the port/baud for the one COM port/baud that has a drive.
620; 
621        jc      .notFound                                           ; only store bLastSerial if success
622        mov     byte [RAMVARS.xlateVars+XLATEVARS.bLastSerial], dl
623
624.notFound:     
625        ret
626
627;----------------------------------------------------------------------
628;
629; SerialCommand_AutoSerial
630;
631; When the SerialAuto IDEVARS entry is used, scans the COM ports on the machine for a possible serial connection.
632;
633
634.scanPortAddresses: db  DEVICE_SERIAL_COM7 >> 2
635                    db  DEVICE_SERIAL_COM6 >> 2
636                    db  DEVICE_SERIAL_COM5 >> 2
637                    db  DEVICE_SERIAL_COM4 >> 2
638                    db  DEVICE_SERIAL_COM3 >> 2
639                    db  DEVICE_SERIAL_COM2 >> 2
640                    db  DEVICE_SERIAL_COM1 >> 2
641                    db  0
642
643ALIGN JUMP_ALIGN
644.scanSerial:
645        mov     di,.scanPortAddresses-1
646
647.nextPort:
648        inc     di              ; load next port address
649        mov     dl,[cs:di]
650
651        mov     dh,0            ; shift from one byte to two
652        eSHL_IM dx, 2
653        jz      .error
654
655;
656; Test for COM port presence, write to and read from registers
657;
658        push    dx
659        add     dl,SerialCommand_UART_lineControl
660        mov     al, 09ah
661        out     dx, al
662        in      al, dx
663        pop     dx
664        cmp     al, 09ah
665        jnz     .nextPort
666
667        mov     al, 0ch
668        out     dx, al
669        in      al, dx
670        cmp     al, 0ch
671        jnz     .nextPort
672
673;
674; Pack into dl, baud rate starts at 0
675;
676        add     dx,-(DEVICE_SERIAL_PACKEDPORTANDBAUD_STARTINGPORT)
677        shr     dx,1            ; dh is zero at this point, and will be sent to the server,
678                                ; so we know this is an auto detect
679
680        jmp     .testFirstBaud
681
682;
683; Walk through 4 possible baud rates
684;
685.nextBaud:
686        inc     dx
687        test    dl,3
688        jz      .nextPort
689
690.testFirstBaud:
691        call    .identifyDeviceInDL
692        jc      .nextBaud
693
694        ret
695
696.error: 
697        stc
698        ; mov       ah,1        ; setting the error code is unnecessary as this path can only be taken during
699                                ; drive detection, and drive detection works off CF and does not check AH
700        ret
701
702
Note: See TracBrowser for help on using the repository browser.