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

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

Serial port code - improved pointer re-normalization.

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