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

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

Enhanced checksum for serial communications, much better at detecting single bit errors.

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