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

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

Changes:

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