Changeset 233 in xtideuniversalbios for trunk/XTIDE_Universal_BIOS/Src


Ignore:
Timestamp:
Feb 4, 2012, 6:21:22 PM (12 years ago)
Author:
gregli@…
google:author:
gregli@hotmail.com
Message:

Serial Port: split single byte port and baud into two bytes, taking advantage of the two bytes in DPT_SERIAL, which supports more serial baud rates and in particular fixed a bug where a 4x client machine couldn't talk to a 115.2K server machine. This is a wide change, touching lots of files, but most are shallow changes. DetectPrint.asm took the most significant changes, now it calculates the baud rate to display instead of using characters provided by the Configurator. The Configurator now has a new menu flag, FLG_MENUITEM_CHOICESTRINGS, for specifying that values are not linear and they should be lookedup rather than indexed. Finally, another important bug fixed here is that in some error cases, the serial port code could get into an infinite loop waiting ont the hardware; now it has a timeout.

Location:
trunk/XTIDE_Universal_BIOS/Src
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • trunk/XTIDE_Universal_BIOS/Src/Device/IDE/IdeIrq.asm

    r161 r233  
    109109    ; Reading Status Register acknowledges IDE interrupt
    110110    call    RamVars_GetSegmentToDS
    111     call    FindDPT_ToDSDIforInterruptInService
     111    mov     bl, FLGH_DPT_INTERRUPT_IN_SERVICE
     112    call    FindDPT_ToDSDIforFlagsHighInBL
    112113    mov     dl, STATUS_REGISTER_in
    113114    call    IdeIO_InputToALfromIdeRegisterInDL
  • trunk/XTIDE_Universal_BIOS/Src/Device/Serial/SerialCommand.asm

    r226 r233  
    1717;
    1818; Values for UART_divisorLow:
    19 ; 60h = 1200, 30h = 2400, 18h = 4800, 0ch = 9600, 6 = 19200, 3 = 38400, 2 = 57600, 1 = 115200
     19; 60h = 1200, 30h = 2400, 18h = 4800, 0ch = 9600, 6 = 19200, 4 = 28800, 3 = 38400, 2 = 57600, 1 = 115200
    2020;
    2121SerialCommand_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 ;
    28 SerialCommand_UART_divisorLow_startingBaud      EQU   030h
    29 
    30 SerialCommand_UART_interruptEnable              EQU     1
    3122
    3223;
     
    9182        mov     [bp+IDEPACK.bFeatures],ah       ; store protocol command
    9283
    93         mov     dl, byte [di+DPT_SERIAL.bSerialPortAndBaud]
     84        mov     dx, [di+DPT_SERIAL.wSerialPortAndBaud]
    9485
    9586; fall-through
    9687
    9788;--------------------------------------------------------------------
    98 ; SerialCommand_OutputWithParameters_DeviceInDL
     89; SerialCommand_OutputWithParameters_DeviceInDX
    9990;   Parameters:
    10091;       AH:     Protocol Command
    101 ;       DL:     Packed I/O port and baud rate
     92;       DX:     Packed I/O port and baud rate
    10293;       ES:SI:  Ptr to buffer (for data transfer commands)
    10394;       SS:BP:  Ptr to IDEREGS_AND_INTPACK
     
    10899;       AL, BX, CX, DX, (ES:SI for data transfer commands)
    109100;--------------------------------------------------------------------
    110 SerialCommand_OutputWithParameters_DeviceInDL:
     101SerialCommand_OutputWithParameters_DeviceInDX:
    111102
    112103        push    si
     
    116107;
    117108; Unpack I/O port and baud from DPT
    118 ;       Port to DX more or less for the remainder of the routine
     109;       Port to DX for the remainder of the routine (+/- different register offsets)
    119110;       Baud in CH until UART initialization is complete
    120111;
    121         mov     dh, ((DEVICE_SERIAL_PACKEDPORTANDBAUD_STARTINGPORT & 0f00h) >> (8+1))
    122         shl     dx, 1       ; port offset already x4, needs one more shift to be x8
    123         mov     cl, dl
    124 
    125         and     cl, (DEVICE_SERIAL_PACKEDPORTANDBAUD_BAUDMASK << 1)
    126         mov     ch, SerialCommand_UART_divisorLow_startingBaud
    127         shr     ch, cl
    128         adc     ch, 0
    129 
    130         and     dl, ((DEVICE_SERIAL_PACKEDPORTANDBAUD_PORTMASK << 1) & 0ffh)
    131         add     dx, byte (DEVICE_SERIAL_PACKEDPORTANDBAUD_STARTINGPORT & 0ffh)
    132 
     112        mov     ch,dh
     113        xor     dh,dh
     114        eSHL_IM dx, 2           ; shift from one byte to two       
     115       
    133116        mov     al,[bp+IDEPACK.bSectorCount]
    134117
     
    414397; taken care of this, but I have seen cases where this is not true.
    415398;
     399        xor     cx,cx                   ; timeout this clearing routine, in case the UART isn't there
    416400.clearBuffer:
    417401        mov     dl,bh
     
    420404        test    al,08fh
    421405        jz      .clearBufferComplete
    422         shr     al,1
     406        test    al,1
    423407        in      al,dx
    424         jc      .clearBuffer    ; note CF from shr above
     408        loopnz  .clearBuffer            ; note ZF from test above
    425409
    426410.clearBufferComplete:
     
    641625;     master scan.
    642626;
    643         mov     dl,[cs:bp+IDEVARS.bSerialPackedPortAndBaud]
    644         mov     al, byte [RAMVARS.xlateVars+XLATEVARS.bLastSerial]
     627        mov     cx,1            ; 1 sector to move, 0 for non-scan
     628        mov     dx,[cs:bp+IDEVARS.wSerialPortAndBaud]
     629        xor     ax,ax
     630        push    si
     631        call    FindDPT_ToDSDIforSerialDevice
     632        pop     si
     633        jnc     .notfounddpt
     634        mov     ax,[ds:di+DPT_SERIAL.wSerialPortAndBaud]
     635.notfounddpt:   
    645636
    646637        test    bh, FLG_DRVNHEAD_DRV
    647638        jz      .master
    648639
    649         test    al,al           ; Take care of the case that is different between master and slave.
     640        test    ax,ax           ; Take care of the case that is different between master and slave.
    650641        jz      .error          ; Because we do this here, the jz after the "or" below will not be taken
    651642
    652643; fall-through
    653644.master:
    654         test    dl,dl
    655         jnz     .identifyDeviceInDL
    656 
    657         or      dl,al           ; Move bLast into position in dl, as well as test for zero
     645        test    dx,dx
     646        jnz     .identifyDeviceInDX
     647
     648        or      dx,ax           ; Move bLast into position in dl, as well as test for zero
    658649        jz      .scanSerial
    659650
    660651; fall-through
    661 .identifyDeviceInDL:
     652.identifyDeviceInDX:
    662653
    663654        push    bp              ; setup fake IDEREGS_AND_INTPACK
     
    665656        push    dx
    666657
    667         mov     cl,1            ; 1 sector to move
    668658        push    cx
    669659
     
    674664
    675665        mov     bp,sp
    676         call    SerialCommand_OutputWithParameters_DeviceInDL
     666        call    SerialCommand_OutputWithParameters_DeviceInDX
    677667
    678668        pop     bx
     
    680670        pop     cx
    681671        pop     dx
    682 
     672       
    683673        pop     bp
    684674;
    685675; place packed port/baud in RAMVARS, read by FinalizeDPT and DetectDrives
    686676;
    687 ; Note that this will be set during an int13h/25h call as well.  Which is OK since it is only used (at the
    688 ; top of this routine) for drives found during a COM scan, and we only COM scan if there were no other
    689 ; COM drives found.  So we will only reaffirm the port/baud for the one COM port/baud that has a drive.
    690 ;
    691         jc      .notFound                                           ; only store bLastSerial if success
    692         mov     byte [RAMVARS.xlateVars+XLATEVARS.bLastSerial], dl
     677        mov     [es:si+ATA6.wVendor],dx
    693678
    694679.notFound:
     
    714699.scanSerial:
    715700        mov     di,.scanPortAddresses-1
     701        mov     ch,1            ;  tell server that we are scanning
    716702
    717703.nextPort:
     
    741727
    742728;
    743 ; Pack into dl, baud rate starts at 0
    744 ;
    745         add     dx,-(DEVICE_SERIAL_PACKEDPORTANDBAUD_STARTINGPORT)
    746         shr     dx,1            ; dh is zero at this point, and will be sent to the server,
    747                                 ; so we know this is an auto detect
    748 
    749         jmp     .testFirstBaud
    750 
    751 ;
    752 ; Walk through 4 possible baud rates
    753 ;
     729; Begin baud rate scan on this port...
     730;
     731; On a scan, we support 6 baud rates, starting here and going higher by a factor of two each step, with a
     732; small jump between 9600 and 38800.  These 6 were selected since we wanted to support 9600 baud and 115200,
     733; *on the server side* if the client side had a 4x clock multiplier, a 2x clock multiplier, or no clock multiplier.
     734;
     735; Starting with 30h, that means 30h (2400 baud), 18h (4800 baud), 0ch (9600 baud), and
     736;                               04h (28800 baud), 02h (57600 baud), 01h (115200 baud)
     737;
     738; Note: hardware baud multipliers (2x, 4x) will impact the final baud rate and are not known at this level
     739;
     740        mov     dh,030h * 2     ; multiply by 2 since we are about to divide by 2
     741        mov     dl,[cs:di]      ; restore single byte port address for scan
     742
    754743.nextBaud:
    755         inc     dx
    756         test    dl,3
     744        shr     dh,1
    757745        jz      .nextPort
    758 
    759 .testFirstBaud:
    760         call    .identifyDeviceInDL
     746        cmp     dh,6            ; skip from 6 to 4, to move from the top of the 9600 baud range
     747        jnz     .testBaud       ; to the bottom of the 115200 baud range
     748        mov     dh,4
     749
     750.testBaud:
     751        call    .identifyDeviceInDX
    761752        jc      .nextBaud
    762753
  • trunk/XTIDE_Universal_BIOS/Src/Device/Serial/SerialDPT.asm

    r226 r233  
    1717SerialDPT_Finalize:
    1818        or      byte [di+DPT.bFlagsHigh], FLGH_DPT_SERIAL_DEVICE
    19         mov     al, [RAMVARS.xlateVars+XLATEVARS.bLastSerial]
    20         mov     byte [di+DPT_SERIAL.bSerialPortAndBaud], al
     19        mov     ax, [es:si+ATA6.wVendor]
     20        mov     word [di+DPT_SERIAL.wSerialPortAndBaud], ax
    2121        ret
    2222
  • trunk/XTIDE_Universal_BIOS/Src/Initialization/DetectDrives.asm

    r203 r233  
    2222
    2323.DriveDetectLoop:                           ; Loop through IDEVARS
    24     mov     si, g_szDetect                  ; Setup standard print string
     24    push    cx
     25
     26    mov     cx, g_szDetectMaster
     27    mov     bh, MASK_DRVNHEAD_SET                               ; Select Master drive
     28    call    StartDetectionWithDriveSelectByteInBHandStringInAX  ; Detect and create DPT + BOOTNFO
     29
     30    mov     cx, g_szDetectSlave
     31    mov     bh, MASK_DRVNHEAD_SET | FLG_DRVNHEAD_DRV 
     32    call    StartDetectionWithDriveSelectByteInBHandStringInAX
     33       
     34    pop     cx
     35
     36    add     bp, BYTE IDEVARS_size           ; Point to next IDEVARS
     37
    2538%ifdef MODULE_SERIAL       
    26     cmp     byte [cs:bp+IDEVARS.bDevice], DEVICE_SERIAL_PORT
    27     jnz     .DriveNotSerial                 ; Special print string for serial drives
    28     mov     si, g_szDetectCOM
    29 .DriveNotSerial:
     39    jcxz    .done                           ; Set to zero on .ideVarsSerialAuto iteration (if any)
    3040%endif
    31 
    32     call    .DetectDrives_WithIDEVARS       ; Detect Master and Slave
    33     add     bp, BYTE IDEVARS_size           ; Point to next IDEVARS
     41       
    3442    loop    .DriveDetectLoop
    3543
    3644%ifdef MODULE_SERIAL       
    3745;
    38 ; if serial drive detected, do not scan (avoids duplicate drives and isn't needed - we have a connection)
    39 ; Note that XLATEVARS.bLastSerial is zero'd in RamVars_Initialize, called in Initialize_AutoDetectDrives;
    40 ; bLastSerial it set in the detection code of SerialCommand.asm
     46; if serial drive detected, do not scan (avoids duplicate drives and isn't needed - we already have a connection)
    4147;
    42     cmp     byte [RAMVARS.xlateVars+XLATEVARS.bLastSerial],cl   ; cx = zero after the loop above
    43                                                                 ; less instruction bytes than using immediate
    44     jnz     .done                                                 
    45        
     48    call    FindDPT_ToDSDIforSerialDevice
     49    jc      .done
     50
     51    mov     bp, ROMVARS.ideVarsSerialAuto   ; Point to our special IDEVARS sructure, just for serial scans     
     52               
    4653    mov     al,[cs:ROMVARS.wFlags]          ; Configurator set to always scan?
    4754    or      al,[es:BDA.bKBFlgs1]            ; Or, did the user hold down the ALT key?
    4855    and     al,8                            ; 8 = alt key depressed, same as FLG_ROMVARS_SERIAL_ALWAYSDETECT
    49     jz      .done                           
     56    jnz     .DriveDetectLoop                           
     57%endif
    5058
    51     mov     bp, ROMVARS.ideVarsSerialAuto   ; Point to our special IDEVARS sructure, just for serial scans
    52     mov     si, g_szDetectCOMAuto           ; Special, special print string for serial drives during a scan
    53 ;;; fall-through                   
    54 %else
     59.done:
    5560    ret
    56 %endif
    5761
    5862%if FLG_ROMVARS_SERIAL_SCANDETECT != 8
     
    6064%endif
    6165
    62 ;--------------------------------------------------------------------
    63 ; Detects IDE hard disks by using information from IDEVARS.
    64 ;
    65 ; DetectDrives_WithIDEVARS
    66 ;   Parameters:
    67 ;       CS:BP:      Ptr to IDEVARS
    68 ;       DS:         RAMVARS segment
    69 ;       ES:         Zero (BDA segment)
    70 ;       SI:         Ptr to template string
    71 ;   Returns:
    72 ;       Nothing
    73 ;   Corrupts registers:
    74 ;       AX, BX, DX, SI, DI
    75 ;--------------------------------------------------------------------
    76 .DetectDrives_WithIDEVARS:
    77     push    cx
    78 
    79     push    si     
    80     mov     ax, g_szMaster
    81     mov     bh, MASK_DRVNHEAD_SET                               ; Select Master drive
    82     call    StartDetectionWithDriveSelectByteInBHandStringInAX  ; Detect and create DPT + BOOTNFO
    83     pop     si
    84 
    85     mov     ax, g_szSlave
    86     mov     bh, MASK_DRVNHEAD_SET | FLG_DRVNHEAD_DRV
    87     call    StartDetectionWithDriveSelectByteInBHandStringInAX
    88     pop     cx
    89        
    90 .done: 
    91     ret
    92 
    9366       
    9467;--------------------------------------------------------------------
    9568; StartDetectionWithDriveSelectByteInBHandStringInAX
    9669;   Parameters:
    97 ;       AX:     Offset to "Master" or "Slave" string
    9870;       BH:     Drive Select byte for Drive and Head Register
     71;       CX:     Offset to "Master" or "Slave" string
    9972;       CS:BP:  Ptr to IDEVARS for the drive
    10073;       DS:     RAMVARS segment
  • trunk/XTIDE_Universal_BIOS/Src/Initialization/DetectPrint.asm

    r203 r233  
    3030; DetectPrint_StartDetectWithMasterOrSlaveStringInAXandIdeVarsInCSBP
    3131;   Parameters:
    32 ;       CS:AX:  Ptr to "Master" or "Slave" string
     32;       CS:CX:  Ptr to "Master" or "Slave" string
    3333;       CS:BP:  Ptr to IDEVARS
    3434;       SI:     Ptr to template string
     
    3939;--------------------------------------------------------------------
    4040DetectPrint_StartDetectWithMasterOrSlaveStringInAXandIdeVarsInCSBP:
    41     push    bp
    42     mov     di, [cs:bp+IDEVARS.wPort]
    43 %ifdef MODULE_SERIAL
    44     mov     cx, [cs:bp+IDEVARS.wSerialPackedPrintBaud]
    45 %endif
     41
     42    mov     ax, [cs:bp+IDEVARS.wPort]       ; for IDE: AX=port address, DH=.bDevice
     43    mov     dx, [cs:bp+IDEVARS.bDevice-1]   ; for Serial: AL=port address>>2, AH=baud rate
     44                                            ;             DL=COM number character, DH=.bDevice
     45
     46    push    bp                              ; setup stack for call to
     47    mov     bp, sp                          ; BootMenuPrint_FormatCSSIfromParamsInSSBP
     48
     49    push    cx                              ; Push "Master" or "Slave"
    4650       
    47     mov     bp, sp
     51    mov     cl, (g_szDetectPort-$$) & 0xff  ; Setup print string for standard IDE
     52                                            ; Note that we modify only the low order bits of CX a lot here,
     53                                            ; saving code space rather than reloading CX completely.
     54                                            ; This optimization requires that all the g_szDetect* strings are
     55                                            ; on the same 256 byte page, which is checked in strings.asm.
    4856
    49     push    ax                          ; Push "Master" or "Slave"
     57    cmp     dx, DEVICE_SERIAL_PORT << 8     ; Check if this is a serial device,
     58                                            ; And also check if DL is zero, check with the jz below
     59                                            ; This optimization requires that DEVICE_SERIAL_PORT be
     60                                            ; the highest value in the DEVICE_* series, ensuring that
     61                                            ; anything less in the high order bits is a different device.
     62
     63    jl      .pushAndPrint                   ; CX = string to print, AX = port address, DX won't be used
     64
     65    mov     cl, (g_szDetectCOM-$$) & 0xff   ; Setup print string for COM ports
     66    push    cx                              ; And push now.  We use the fact that format strings can contain
     67                                            ; themselves format strings.
     68
     69    push    dx                              ; Push COM number character
     70               
     71    mov     cl, (g_szDetectCOMAuto-$$) & 0xff   ; Setup secondary print string for "Auto"
    5072       
    51     push    di                          ; Push Port address or COM port number
     73    jz      .pushAndPrint                   ; CX = string to print, AX and DX won't be used
     74       
     75    mov     cl, (g_szDetectCOMLarge-$$) & 0xff  ; Setup secondary print string for "COMn/xx.yK"
    5276
    53 %ifdef MODULE_SERIAL
    54 ;
    55 ; Print baud rate from .wSerialPackedPrintBaud, in two parts - %u and then %c
    56 ;
    57     mov     ax,cx                       ; Unpack baud rate number
    58     and     ax,DEVICE_SERIAL_PRINTBAUD_NUMBERMASK
    59     push    ax
     77    mov     al,ah                           ; baud rate divisor to AL
     78    cbw                                     ; clear AH, AL will always be less than 128
     79    xchg    si,ax                           ; move AX to SI for divide
     80    mov     ax,1152                         ; baud rate to displa is 115200/divisor, the "00" is handled
     81                                            ; in the print strings
     82    xor     dx,dx                           ; clear top 16-bits of dividend
     83    div     si                              ; and divide...  Now AX = baud rate/100, DX = 0 (always a clean divide)
     84       
     85    mov     si,10                           ; Now separate the whole portion from the fractional for "K" display
     86    div     si                              ; and divide...  Now AX = baud rate/1000, DX = low order digit
     87       
     88    cmp     ax,si                           ; <= 10: "2400", "9600", etc.; >10: "19.2K", "38.4K", etc.
     89    jae     .pushAndPrint
    6090
    61     mov     al,ch                       ; Unpack baud rate postfix ('0' or 'K')
    62     eSHR_IM al,2                        ; also effectively masks off the postfix
    63     add     al,DEVICE_SERIAL_PRINTBAUD_POSTCHARADD
    64     push    ax
    65 %endif
    66                        
     91    mov     cl, (g_szDetectCOMSmall-$$) & 0xff  ; Setup secondary print string for "COMn/XXy00"
     92       
     93.pushAndPrint: 
     94    push    cx                              ; Push print string
     95    push    ax                              ; Push high order digits, or port address, or N/A
     96    push    dx                              ; Push low order digit, or N/A
     97
     98    mov     si, g_szDetectOuter             ; Finally load SI with wrapper string "IDE %s at %s: "
     99
    67100    jmp     short DetectPrint_BootMenuPrint_FormatCSSIfromParamsInSSBP_Relay   
    68101
     
    92125
    93126
     127
  • trunk/XTIDE_Universal_BIOS/Src/Main.asm

    r229 r233  
    112112%ifdef MODULE_SERIAL
    113113    at  ROMVARS.ideVarsSerialAuto+IDEVARS.bDevice,      db  DEVICE_SERIAL_PORT
    114     at  ROMVARS.ideVarsSerialAuto+IDEVARS.drvParamsMaster+DRVPARAMS.wFlags, db  FLG_DRVPARAMS_BLOCKMODE
    115     at  ROMVARS.ideVarsSerialAuto+IDEVARS.drvParamsSlave+DRVPARAMS.wFlags,  db  FLG_DRVPARAMS_BLOCKMODE
    116114%endif
    117115%else
     
    145143%ifdef MODULE_SERIAL
    146144    at  ROMVARS.ideVarsSerialAuto+IDEVARS.bDevice,      db  DEVICE_SERIAL_PORT
    147     at  ROMVARS.ideVarsSerialAuto+IDEVARS.drvParamsMaster+DRVPARAMS.wFlags, db  FLG_DRVPARAMS_BLOCKMODE
    148     at  ROMVARS.ideVarsSerialAuto+IDEVARS.drvParamsSlave+DRVPARAMS.wFlags,  db  FLG_DRVPARAMS_BLOCKMODE
    149145%endif
    150146%endif
  • trunk/XTIDE_Universal_BIOS/Src/Strings.asm

    r197 r233  
    1212g_szRomAt:      db  "%s @ %x",LF,CR,NULL
    1313
    14 g_szMaster:             db  "IDE Master at ",NULL
    15 g_szSlave:              db  "IDE Slave  at ",NULL
    16 g_szDetect:             db  "%s%x: ",NULL                      ; IDE Master at 1F0h:
    17 g_szDetectCOM:          db  "%sCOM%c/%u%c: ",NULL              ; IDE Master at COM1/115K:       
    18 g_szDetectCOMAuto:      db  "%sCOM Detect: ",NULL              ; IDE Master at COM Detect:
     14; The following strings are used by DetectPrint_StartDetectWithMasterOrSlaveStringInAXandIdeVarsInCSBP
     15; To support an optimization in that code, these strings must start on the same 256 byte page,
     16; which is checked at assembly time below.
     17;
     18g_szDetectStart:       
     19g_szDetectMaster:       db  "Master",NULL
     20g_szDetectSlave:        db  "Slave ",NULL
     21g_szDetectOuter:        db  "IDE %s at %s: ",NULL
     22g_szDetectPort:         db  "%x",NULL                       ; IDE Master at 1F0h:
     23g_szDetectCOM:          db  "COM%c%s",NULL           
     24g_szDetectCOMAuto:      db  " Auto",NULL
     25g_szDetectCOMSmall:     db  "/%u%u00",NULL                  ; IDE Master at COM1/9600:
     26g_szDetectEnd:
     27g_szDetectCOMLarge:     db  "/%u.%uK",NULL                  ; IDE Master at COM1/19.2K:
     28       
     29%ifndef CHECK_FOR_UNUSED_ENTRYPOINTS               
     30%if ((g_szDetectEnd-$$) & 0xff00) <> ((g_szDetectStart-$$) & 0xff00)
     31%error "g_szDetect* strings must be on the same 256 byte page, required by DetectPrint_StartDetectWithMasterOrSlaveStringInAXandIdeVarsInCSBP.  Please move this block up or down within strings.asm"
     32%endif
     33%endif             
    1934               
    2035; Boot loader strings
     
    137152;$translate{200}      = 18;    # DOUBLE_BOTTOM_LEFT_CORNER
    138153;$translate{181}      = 19;    # DOUBLE_LEFT_HORIZONTAL_TO_SINGLE_VERTICAL
     154;$translate{ord('0')} = 20;    # DOUBLE_LEFT_HORIZONTAL_TO_SINGLE_VERTICAL     
    139155;
    140156; Formats begin immediately after the last Translated character (they are in the same table)
    141157;
    142 ;$format_begin = 20;
     158;$format_begin = 21;
    143159;
    144 ;$format{"s"}   = 20;        # n/a
    145160;$format{"c"}   = 21;        # n/a
    146161;$format{"2-I"} = 22;        # must be even
     
    152167;$format{"2-u"} = 28;        # must be even
    153168;$format{"A"}   = 29;        # n/a
     169;$format{"s"}   = 30;        # n/a     
    154170;
    155171; NOTE: The last $format cannot exceed 31 (stored in a 5-bit quantity).
  • trunk/XTIDE_Universal_BIOS/Src/StringsCompressed.asm

    r197 r233  
    2020g_szRomAt:      ; db    "%s @ %x",LF,CR,NULL
    2121                ; db     25h,  73h,  20h,  40h,  20h,  25h,  78h,  0ah,  0dh,  00h    ; uncompressed
    22                   db     34h,  20h, 0c6h,  39h,  1bh                                  ; compressed
    23 
    24 
    25 g_szMaster:             ; db    "IDE Master at ",NULL
    26                         ; db     49h,  44h,  45h,  20h,  4dh,  61h,  73h,  74h,  65h,  72h,  20h,  61h,  74h,  20h,  00h    ; uncompressed
    27                           db     4fh,  4ah, 0cbh,  53h,  67h,  79h,  7ah,  6bh, 0f8h,  67h,  7ah,  00h                      ; compressed
    28 
    29 g_szSlave:              ; db    "IDE Slave  at ",NULL
    30                         ; db     49h,  44h,  45h,  20h,  53h,  6ch,  61h,  76h,  65h,  20h,  20h,  61h,  74h,  20h,  00h    ; uncompressed
    31                           db     4fh,  4ah, 0cbh,  59h,  72h,  67h,  7ch, 0ebh,  20h,  67h,  7ah,  00h                      ; compressed
    32 
    33 g_szDetect:             ; db    "%s%x: ",NULL                      ; IDE Master at 1F0h:
    34                         ; db     25h,  73h,  25h,  78h,  3ah,  20h,  00h    ; uncompressed
    35                           db     34h,  39h,  40h,  00h                      ; compressed
    36 
    37 g_szDetectCOM:          ; db  "%sCOM%c/%u%c: ",NULL              ; IDE Master at COM1/115K:     
    38                         ; db   25h,  73h,  43h,  4fh,  4dh,  25h,  63h,  2fh,  25h,  75h,  25h,  63h,  3ah,  20h,  00h    ; uncompressed
    39                           db   34h,  49h,  55h,  53h,  35h,  2ah,  37h,  35h,  40h,  00h                                  ; compressed
    40 
    41 g_szDetectCOMAuto:      ; db  "%sCOM Detect: ",NULL            ; IDE Master at COM Detect:
    42                         ; db   25h,  73h,  43h,  4fh,  4dh,  20h,  44h,  65h,  74h,  65h,  63h,  74h,  3ah,  20h,  00h    ; uncompressed
    43                           db   34h,  49h,  55h, 0d3h,  4ah,  6bh,  7ah,  6bh,  69h,  7ah,  40h,  00h                      ; compressed
    44 
     22                  db     3eh,  20h, 0c6h,  39h,  1bh                                  ; compressed
     23
     24
     25; The following strings are used by DetectPrint_StartDetectWithMasterOrSlaveStringInAXandIdeVarsInCSBP
     26; To support an optimization in that code, these strings must start on the same 256 byte page,
     27; which is checked at assembly time below.
     28;
     29g_szDetectStart:       
     30g_szDetectMaster:       ; db    "Master",NULL
     31                        ; db     4dh,  61h,  73h,  74h,  65h,  72h,  00h    ; uncompressed
     32                          db     53h,  67h,  79h,  7ah,  6bh, 0b8h          ; compressed
     33
     34g_szDetectSlave:        ; db    "Slave ",NULL
     35                        ; db     53h,  6ch,  61h,  76h,  65h,  20h,  00h    ; uncompressed
     36                          db     59h,  72h,  67h,  7ch,  6bh,  00h          ; compressed
     37
     38g_szDetectOuter:        ; db    "IDE %s at %s: ",NULL
     39                        ; db     49h,  44h,  45h,  20h,  25h,  73h,  20h,  61h,  74h,  20h,  25h,  73h,  3ah,  20h,  00h    ; uncompressed
     40                          db     4fh,  4ah, 0cbh,  3eh,  20h,  67h, 0fah,  3eh,  40h,  00h                                  ; compressed
     41
     42g_szDetectPort:         ; db    "%x",NULL                       ; IDE Master at 1F0h:
     43                        ; db     25h,  78h,  00h    ; uncompressed
     44                          db     19h                ; compressed
     45
     46g_szDetectCOM:          ; db  "COM%c%s",NULL           
     47                        ; db   43h,  4fh,  4dh,  25h,  63h,  25h,  73h,  00h    ; uncompressed
     48                          db   49h,  55h,  53h,  35h,  1eh                      ; compressed
     49
     50g_szDetectCOMAuto:      ; db    " Auto",NULL
     51                        ; db     20h,  41h,  75h,  74h,  6fh,  00h    ; uncompressed
     52                          db     20h,  47h,  7bh,  7ah, 0b5h          ; compressed
     53
     54g_szDetectCOMSmall:     ; db    "/%u%u00",NULL                  ; IDE Master at COM1/9600:
     55                        ; db     2fh,  25h,  75h,  25h,  75h,  30h,  30h,  00h    ; uncompressed
     56                          db     2ah,  37h,  37h,  34h,  14h                      ; compressed
     57
     58g_szDetectEnd:
     59g_szDetectCOMLarge:     ; db    "/%u.%uK",NULL                  ; IDE Master at COM1/19.2K:
     60                        ; db     2fh,  25h,  75h,  2eh,  25h,  75h,  4bh,  00h    ; uncompressed
     61                          db     2ah,  37h,  29h,  37h,  91h                      ; compressed
     62
     63
     64%ifndef CHECK_FOR_UNUSED_ENTRYPOINTS               
     65%if ((g_szDetectEnd-$$) & 0xff00) <> ((g_szDetectStart-$$) & 0xff00)
     66%error "g_szDetect* strings must be on the same 256 byte page, required by DetectPrint_StartDetectWithMasterOrSlaveStringInAXandIdeVarsInCSBP.  Please move this block up or down within strings.asm"
     67%endif
     68%endif             
    4569
    4670; Boot loader strings
    4771g_szTryToBoot:          ; db    "Booting from %s %x",ANGLE_QUOTE_RIGHT,"%x",LF,CR,NULL
    4872                        ; db     42h,  6fh,  6fh,  74h,  69h,  6eh,  67h,  20h,  66h,  72h,  6fh,  6dh,  20h,  25h,  73h,  20h,  25h,  78h, 0afh,  25h,  78h,  0ah,  0dh,  00h    ; uncompressed
    49                           db     48h,  75h,  75h,  7ah,  6fh,  74h, 0edh,  6ch,  78h,  75h, 0f3h,  34h,  20h,  39h,  24h,  39h,  1bh                                              ; compressed
     73                          db     48h,  75h,  75h,  7ah,  6fh,  74h, 0edh,  6ch,  78h,  75h, 0f3h,  3eh,  20h,  39h,  24h,  39h,  1bh                                              ; compressed
    5074
    5175g_szBootSectorNotFound: ; db    "Boot sector "
     
    77101g_szHotkey:     ; db    "%A%c%c%A%s%A ",NULL
    78102                ; db     25h,  41h,  25h,  63h,  25h,  63h,  25h,  41h,  25h,  73h,  25h,  41h,  20h,  00h    ; uncompressed
    79                   db     3dh,  35h,  35h,  3dh,  34h,  3dh,  00h                                              ; compressed
     103                  db     3dh,  35h,  35h,  3dh,  3eh,  3dh,  00h                                              ; compressed
    80104
    81105
     
    88112g_szFDLetter:   ; db    "%s %c",NULL
    89113                ; db     25h,  73h,  20h,  25h,  63h,  00h    ; uncompressed
    90                   db     34h,  20h,  15h                      ; compressed
     114                  db     3eh,  20h,  15h                      ; compressed
    91115
    92116g_szFloppyDrv:  ; db    "Floppy Drive",NULL
     
    106130g_szSizeSingle: ; db    "%s%u.%u %ciB",NULL
    107131                ; db     25h,  73h,  25h,  75h,  2eh,  25h,  75h,  20h,  25h,  63h,  69h,  42h,  00h    ; uncompressed
    108                   db     34h,  37h,  29h,  37h,  20h,  35h,  6fh,  88h                                  ; compressed
     132                  db     3eh,  37h,  29h,  37h,  20h,  35h,  6fh,  88h                                  ; compressed
    109133
    110134g_szSizeDual:   ; db    "%s%5-u.%u %ciB /%5-u.%u %ciB",LF,CR,NULL
    111135                ; db     25h,  73h,  25h,  35h,  2dh,  75h,  2eh,  25h,  75h,  20h,  25h,  63h,  69h,  42h,  20h,  2fh,  25h,  35h,  2dh,  75h,  2eh,  25h,  75h,  20h,  25h,  63h,  69h,  42h,  0ah,  0dh,  00h    ; uncompressed
    112                   db     34h,  38h,  29h,  37h,  20h,  35h,  6fh, 0c8h,  2ah,  38h,  29h,  37h,  20h,  35h,  6fh,  48h,  1bh                                                                                        ; compressed
     136                  db     3eh,  38h,  29h,  37h,  20h,  35h,  6fh, 0c8h,  2ah,  38h,  29h,  37h,  20h,  35h,  6fh,  48h,  1bh                                                                                        ; compressed
    113137
    114138g_szCfgHeader:  ; db    "Addr.",SINGLE_VERTICAL,"Block",SINGLE_VERTICAL,"Bus",  SINGLE_VERTICAL,"IRQ",  SINGLE_VERTICAL,"Reset",LF,CR,NULL
     
    118142g_szCfgFormat:  ; db    "%s"   ,SINGLE_VERTICAL,"%5-u", SINGLE_VERTICAL,"%s",SINGLE_VERTICAL," %2-I",SINGLE_VERTICAL,"%5-x",  NULL
    119143                ; db     25h,  73h, 0b3h,  25h,  35h,  2dh,  75h, 0b3h,  25h,  73h, 0b3h,  20h,  25h,  32h,  2dh,  49h, 0b3h,  25h,  35h,  2dh,  78h,  00h    ; uncompressed
    120                   db     34h,  23h,  38h,  23h,  34h,  23h,  20h,  36h,  23h,  1ah                                                                            ; compressed
     144                  db     3eh,  23h,  38h,  23h,  3eh,  23h,  20h,  36h,  23h,  1ah                                                                            ; compressed
    121145
    122146
     
    159183g_szFddUnknown: ; db    "%sUnknown",NULL
    160184                ; db     25h,  73h,  55h,  6eh,  6bh,  6eh,  6fh,  77h,  6eh,  00h    ; uncompressed
    161                   db     34h,  5bh,  74h,  71h,  74h,  75h,  7dh, 0b4h                ; compressed
     185                  db     3eh,  5bh,  74h,  71h,  74h,  75h,  7dh, 0b4h                ; compressed
    162186
    163187g_szFddSizeOr:  ; db    "%s5",ONE_QUARTER,QUOTATION_MARK," or 3",ONE_HALF,QUOTATION_MARK," DD",NULL
    164188                ; db     25h,  73h,  35h, 0ach,  22h,  20h,  6fh,  72h,  20h,  33h, 0abh,  22h,  20h,  44h,  44h,  00h    ; uncompressed
    165                   db     34h,  2fh,  21h,  26h,  20h,  75h, 0f8h,  2dh,  22h,  26h,  20h,  4ah,  8ah                      ; compressed
     189                  db     3eh,  2fh,  21h,  26h,  20h,  75h, 0f8h,  2dh,  22h,  26h,  20h,  4ah,  8ah                      ; compressed
    166190
    167191g_szFddSize:    ; db    "%s%s",QUOTATION_MARK,", %u kiB",NULL   ; 3½", 1440 kiB
    168192                ; db     25h,  73h,  25h,  73h,  22h,  2ch,  20h,  25h,  75h,  20h,  6bh,  69h,  42h,  00h    ; uncompressed
    169                   db     34h,  34h,  26h,  27h,  20h,  37h,  20h,  71h,  6fh,  88h                            ; compressed
     193                  db     3eh,  3eh,  26h,  27h,  20h,  37h,  20h,  71h,  6fh,  88h                            ; compressed
    170194
    171195
     
    265289;$translate{200}      = 18;    # DOUBLE_BOTTOM_LEFT_CORNER    [StringsCompress Processed]
    266290;$translate{181}      = 19;    # DOUBLE_LEFT_HORIZONTAL_TO_SINGLE_VERTICAL    [StringsCompress Processed]
     291;$translate{ord('0')} = 20;    # DOUBLE_LEFT_HORIZONTAL_TO_SINGLE_VERTICAL          [StringsCompress Processed]
    267292;
    268293; Formats begin immediately after the last Translated character (they are in the same table)
    269294;
    270 ;$format_begin = 20;    [StringsCompress Processed]
    271 ;
    272 ;$format{"s"}   = 20;        # n/a    [StringsCompress Processed]
     295;$format_begin = 21;    [StringsCompress Processed]
     296;
    273297;$format{"c"}   = 21;        # n/a    [StringsCompress Processed]
    274298;$format{"2-I"} = 22;        # must be even    [StringsCompress Processed]
     
    280304;$format{"2-u"} = 28;        # must be even    [StringsCompress Processed]
    281305;$format{"A"}   = 29;        # n/a    [StringsCompress Processed]
     306;$format{"s"}   = 30;        # n/a          [StringsCompress Processed]
    282307;
    283308; NOTE: The last $format cannot exceed 31 (stored in a 5-bit quantity).
     
    299324StringsCompressed_NormalBase     equ   58
    300325
    301 StringsCompressed_FormatsBegin   equ   20
     326StringsCompressed_FormatsBegin   equ   21
    302327
    303328StringsCompressed_TranslatesAndFormats:
     
    322347        db     200  ; 18
    323348        db     181  ; 19
    324         db     (DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_s)    ; 20
     349        db     48  ; 20
    325350        db     (DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_c)    ; 21
    326351        db     (DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_2_I)    ; 22
     
    332357        db     (DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_2_u)    ; 28
    333358        db     (DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_A)    ; 29
     359        db     (DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_s)    ; 30
    334360
    335361%ifndef CHECK_FOR_UNUSED_ENTRYPOINTS
     362%if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_c || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_c > 255
     363%error "DisplayFormatCompressed_Format_c is out of range of DisplayFormatCompressed_BaseFormatOffset"
     364%endif
     365%if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_2_I || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_2_I > 255
     366%error "DisplayFormatCompressed_Format_2_I is out of range of DisplayFormatCompressed_BaseFormatOffset"
     367%endif
     368%if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_u || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_u > 255
     369%error "DisplayFormatCompressed_Format_u is out of range of DisplayFormatCompressed_BaseFormatOffset"
     370%endif
     371%if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_5_u || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_5_u > 255
     372%error "DisplayFormatCompressed_Format_5_u is out of range of DisplayFormatCompressed_BaseFormatOffset"
     373%endif
     374%if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_x || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_x > 255
     375%error "DisplayFormatCompressed_Format_x is out of range of DisplayFormatCompressed_BaseFormatOffset"
     376%endif
     377%if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_5_x || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_5_x > 255
     378%error "DisplayFormatCompressed_Format_5_x is out of range of DisplayFormatCompressed_BaseFormatOffset"
     379%endif
     380%if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_nl || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_nl > 255
     381%error "DisplayFormatCompressed_Format_nl is out of range of DisplayFormatCompressed_BaseFormatOffset"
     382%endif
     383%if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_2_u || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_2_u > 255
     384%error "DisplayFormatCompressed_Format_2_u is out of range of DisplayFormatCompressed_BaseFormatOffset"
     385%endif
     386%if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_A || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_A > 255
     387%error "DisplayFormatCompressed_Format_A is out of range of DisplayFormatCompressed_BaseFormatOffset"
     388%endif
    336389%if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_s || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_s > 255
    337390%error "DisplayFormatCompressed_Format_s is out of range of DisplayFormatCompressed_BaseFormatOffset"
    338 %endif
    339 %if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_c || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_c > 255
    340 %error "DisplayFormatCompressed_Format_c is out of range of DisplayFormatCompressed_BaseFormatOffset"
    341 %endif
    342 %if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_2_I || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_2_I > 255
    343 %error "DisplayFormatCompressed_Format_2_I is out of range of DisplayFormatCompressed_BaseFormatOffset"
    344 %endif
    345 %if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_u || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_u > 255
    346 %error "DisplayFormatCompressed_Format_u is out of range of DisplayFormatCompressed_BaseFormatOffset"
    347 %endif
    348 %if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_5_u || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_5_u > 255
    349 %error "DisplayFormatCompressed_Format_5_u is out of range of DisplayFormatCompressed_BaseFormatOffset"
    350 %endif
    351 %if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_x || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_x > 255
    352 %error "DisplayFormatCompressed_Format_x is out of range of DisplayFormatCompressed_BaseFormatOffset"
    353 %endif
    354 %if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_5_x || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_5_x > 255
    355 %error "DisplayFormatCompressed_Format_5_x is out of range of DisplayFormatCompressed_BaseFormatOffset"
    356 %endif
    357 %if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_nl || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_nl > 255
    358 %error "DisplayFormatCompressed_Format_nl is out of range of DisplayFormatCompressed_BaseFormatOffset"
    359 %endif
    360 %if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_2_u || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_2_u > 255
    361 %error "DisplayFormatCompressed_Format_2_u is out of range of DisplayFormatCompressed_BaseFormatOffset"
    362 %endif
    363 %if DisplayFormatCompressed_BaseFormatOffset < DisplayFormatCompressed_Format_A || DisplayFormatCompressed_BaseFormatOffset - DisplayFormatCompressed_Format_A > 255
    364 %error "DisplayFormatCompressed_Format_A is out of range of DisplayFormatCompressed_BaseFormatOffset"
    365391%endif
    366392%endif
     
    374400;; 5-u:3
    375401;; x:6
     402;; s:15
    376403;; 5-x:1
    377 ;; s:15
    378404;; nl:6
    379405;; 2-I:1
    380 ;; c:8
    381 ;; u:6
     406;; c:7
     407;; u:9
    382408;; total format: 10
    383409
    384410;; alphabet usage stats
    385 ;; 58,::4
     411;; 58,::2
    386412;; 59,;:
    387413;; 60,<:
     
    390416;; 63,?:
    391417;; 64,@:1
    392 ;; 65,A:3
     418;; 65,A:4
    393419;; 66,B:11
    394 ;; 67,C:5
    395 ;; 68,D:12
    396 ;; 69,E:4
     420;; 67,C:4
     421;; 68,D:10
     422;; 69,E:3
    397423;; 70,F:3
    398424;; 71,G:
    399425;; 72,H:4
    400 ;; 73,I:3
     426;; 73,I:2
    401427;; 74,J:
    402 ;; 75,K:
     428;; 75,K:1
    403429;; 76,L:3
    404 ;; 77,M:4
     430;; 77,M:3
    405431;; 78,N:
    406 ;; 79,O:3
     432;; 79,O:2
    407433;; 80,P:1
    408434;; 81,Q:1
     
    422448;; 95,_:
    423449;; 96,`:
    424 ;; 97,a:7
     450;; 97,a:6
    425451;; 98,b:
    426 ;; 99,c:5
     452;; 99,c:4
    427453;; 100,d:4
    428 ;; 101,e:11
     454;; 101,e:9
    429455;; 102,f:2
    430456;; 103,g:2
     
    436462;; 109,m:1
    437463;; 110,n:9
    438 ;; 111,o:17
     464;; 111,o:18
    439465;; 112,p:3
    440466;; 113,q:
    441467;; 114,r:11
    442468;; 115,s:6
    443 ;; 116,t:13
    444 ;; 117,u:2
     469;; 116,t:11
     470;; 117,u:3
    445471;; 118,v:2
    446472;; 119,w:1
    447473;; 120,x:
    448474;; 121,y:2
    449 ;; alphabet used count: 39
     475;; alphabet used count: 40
  • trunk/XTIDE_Universal_BIOS/Src/VariablesAndDPTs/FindDPT.asm

    r203 r233  
    124124
    125125;--------------------------------------------------------------------
    126 ; IterateToDptWithInterruptInServiceFlagSet
     126; IterateToDptWithFlagsHighInBL
    127127;   Parameters:
    128128;       DS:DI:  Ptr to DPT to examine
     129;       BL:     Bit(s) to test in DPT.bFlagsHigh
    129130;   Returns:
    130131;       CF:     Set if wanted DPT found
     
    134135;--------------------------------------------------------------------
    135136ALIGN JUMP_ALIGN
    136 IterateToDptWithInterruptInServiceFlagSet:
    137     test    BYTE [di+DPT.bFlagsHigh], FLGH_DPT_INTERRUPT_IN_SERVICE     ; Clears CF (but we need the clc
    138                                                                         ; below anyway for callers above)
     137IterateToDptWithFlagsHighInBL:     
     138    test    BYTE [di+DPT.bFlagsHigh], bl        ; Clears CF (but we need the clc
     139                                                ; below anyway for callers above)
    139140    jnz     SHORT ReturnRightDPT
    140141
     
    144145
    145146;--------------------------------------------------------------------
    146 ; FindDPT_ToDSDIforInterruptInService
     147; FindDPT_ToDSDIforSerialDevice
    147148;   Parameters:
    148149;       DS:     RAMVARS segment
     
    154155;       SI
    155156;--------------------------------------------------------------------
    156 ALIGN JUMP_ALIGN
    157 FindDPT_ToDSDIforInterruptInService:
    158     mov     si, IterateToDptWithInterruptInServiceFlagSet
     157ALIGN JUMP_ALIGN       
     158FindDPT_ToDSDIforSerialDevice:         
     159    mov     bl, FLGH_DPT_SERIAL_DEVICE
     160; fall-through
     161               
     162;--------------------------------------------------------------------
     163; FindDPT_ToDSDIforFlagsHigh
     164;   Parameters:
     165;       DS:     RAMVARS segment
     166;       BL:     Bit(s) to test in DPT.bFlagsHigh
     167;   Returns:
     168;       DS:DI:  Ptr to DPT
     169;       CF:     Set if wanted DPT found
     170;               Cleared if DPT not found
     171;   Corrupts registers:
     172;       SI
     173;--------------------------------------------------------------------
     174ALIGN JUMP_ALIGN
     175FindDPT_ToDSDIforFlagsHighInBL:     
     176    mov     si, IterateToDptWithFlagsHighInBL
    159177    ; Fall to IterateAllDPTs
    160178
Note: See TracChangeset for help on using the changeset viewer.