home *** CD-ROM | disk | FTP | other *** search
-
- ;****************************************************************************
- ;*
- ;* Welcome to ASPI. The following code is provided to assist you with
- ;* writing code to the Advanced SCSI Programming Interface (ASPI). Run the
- ;* program ASPIPROG.EXE to see what the following program does when compiled.
- ;*
- ;* The only support provided for ASPI developers by Adaptec is through this
- ;* sample code and the ASPI specification, which can be ordered through
- ;* Literature at (408) 945-8600 x2579. The ASPI specification is available
- ;* for DOS, OS/2, and NetWare 386. Please do not call the Adaptec technical
- ;* support line with ASPI programming questions.
- ;*
- ;* This sample code provides examples of how to use the ASPI programming
- ;* interface. The main program obtains the ASPI entry point and calls
- ;* subroutines for the different ASPI functions.
- ;*
- ;* 1. Obtains ASPI Entry Point
- ;* 2. Executes ASPI Host Adapter Inquiry Command
- ;* 3. Executes ASPI Get Device Type Command
- ;* 4. Executes ASPI Execute SCSI I/O Command
- ;* 5. Executes ASPI Reset SCSI Device Command using Posting
- ;* 6. Executes (3) and then executes ASPI Abort SCSI I/O command
- ;*
- ;*
- ;****************************************************************************
- .286
- .xlist
- include aspidefs.inc ;include file for ASPI definitions
- include scsidefs.inc ;include file for SCSI definitions
- .list
-
- .MODEL Small
- .STACK 300h
-
- ;****************************************************************************
- ; DATA SEGMENT
- ;****************************************************************************
- .DATA
- SCSIMgrString db "SCSIMGR$" ;SCSI Mgr String (need to get entry)
- dw 0 ;NULL-Terminate String
- ASPI_Entry dd 0 ;Entry Address stored by GetASPIEntry
- SRB db 64+10+14 dup (0) ;SCSI Request Block
- SRB2 db 64+10+14 dup (0) ;SCSI Request Block 2
- Data_Buffer db 50 dup (?) ;Data Buffer for Inquiry command
- Flag db 0 ;flag used by post routine
-
- ;****************************************************************************
- ; DISPLAY STRINGS
- ;****************************************************************************
- Str_InquiryFail db "Error issuing SCSI inquiry command",CR,LF,'$'
- Str_NoASPI db "Unable to open ASPI Manager!",CR,LF,'$'
-
- Str_ASPI_Stat db " ASPI Status (HEX) : %",CR,LF,'$'
-
- Str_HA_Inquiry db CR,LF,"ASPI HOST ADAPTER INQUIRY COMMAND",CR,LF,'$'
- Str_Num_HA db " Number of Host Adapters : %",CR,LF,'$'
- Str_TID_HA db " SCSI ID of Host Adapter 0 : %",CR,LF,'$'
- Str_Mgr_ID db " SCSI Manager ID : %%%%%%%%%%%%%%%%",CR,LF,'$'
- Str_HA_ID db " Host Adapter ID : %%%%%%%%%%%%%%%%",CR,LF,'$'
-
- Str_Get_DevTyp db CR,LF,"ASPI GET DEVICE TYPE COMMAND",CR,LF,'$'
- Str_Dev_Typ db " SCSI Device Type : %",CR,LF,'$'
-
- Str_SCSI_IO db CR,LF,"ASPI SCSI I/O COMMAND (Inquiry Command)",CR,LF,'$'
- Str_PQualTyp db " Qualifier / Device Type (HEX) : %",CR,LF,'$'
- Str_Versions db " ISO / ECMA / ANSI Version (HEX) : %",CR,LF,'$'
- Str_Inq_Dat db " Inquiry Data : %%%%%%%%%%%%%%%%%%%%%%%%%%%%",CR,LF,'$'
-
- Str_Dev_Rst1 db CR,LF,"ASPI RESET DEVICE COMMAND (with Posting)",'$'
- Str_Wait4Post db ".",'$'
- Str_HA_Inq2 db CR,LF,"ASPI HOST ADAPTER INQUIRY COMMAND (Aborted)",'$'
- Str_CRLF db CR,LF,'$'
- ;****************************************************************************
- ; CODE SEGMENT
- ;****************************************************************************
- .CODE
- start: mov ax,@DATA ;initialize ds and es
- mov ds,ax
- mov es,ax
-
- ;* 1. Obtains ASPI Entry Point
- call GetASPIEntry ;Get ASPI entry point
- jc ASPI_Done ;Jump if no manager
-
- ;* 2. Executes ASPI Host Adapter Inquiry Command
- lea si,SRB ;point to SRB
- call HAInquiry ;Send ASPI HA Inquiry
- call Poll_Status ;wait for status
- call DispSRBInq ;Display Inquiry Info
-
- ;* 3. Executes ASPI Get Device Type Command
- lea si,SRB ;point to SRB
- call GetDevType ;Send ASPI Get Device Type
- call Poll_Status ;wait for status
- call DispDevTyp ;Display Device Type Info
-
- ;* 4. Executes ASPI Execute SCSI I/O Command
- lea si,SRB ;point to SRB
- call Load_Inquiry ;Load SCSI Inquiry into SRB
- call XSCSI_IO ;Execute SCSI I/O
- call Poll_Status ;wait for status
- call DispInquiry ;Display I/O results
-
- ;* 5. Executes ASPI Reset SCSI Device Command using Posting
- lea dx,Str_Dev_Rst1 ;load the string for outtext
- call outtext ;output the text
- lea si,SRB ;point to SRB
- mov Flag,0 ;reset the post flag
- call RST_SDevice ;Resets SCSI ID = 2
- lea dx,Str_Wait4Post ;point to Wait for Post String
- PostLp1:
- mov al,Flag ;get the post flag
- cmp al,1
- call outtext ;output the text
- jnz PostLp1 ;jump if not 1
- call DispStat ;Display status
-
- ;* 6. Executes (3) and then executes ASPI Abort SCSI I/O command
- lea dx,Str_HA_Inq2 ;load the string for outtext
- call outtext ;output the text
- lea si,SRB ;point to SRB
- call Load_Inquiry ;Load SCSI Inquiry into SRB
- call XSCSI_IO ;Execute SCSI I/O
- call Abort_SIO ;call abort SCSI IO
- call Poll_Status ;wait for status
- call DispStat ;Display status
-
- ASPI_Done: mov ax,ASPI_DOSExit
- int 21h
- ret ;Exit to DOS
-
- ;****************************************************************************
- ;
- ; %%% ASPIDISK SUPPORT ROUTINES %%%
- ;
- ;****************************************************************************
- ; Subroutine Name: GetASPIEntry
- ;
- ; Description: This gets the ASPI manager's entry point and stores it in
- ; 'ASPI_Entry.'
- ; If no ASPI manager is found, an appropriate error message
- ; is displayed.
- ;
- ; Entry: Nothing
- ;
- ; Exit: The memory location ASPI_Entry is loaded with entry point
- ; CF set if no ASPI manager found, else reset
- ;****************************************************************************
- GetASPIEntry proc near
- mov ax,ASPI_Open
- lea dx,SCSIMgrString
- int 21h ;Open ASPI Manager
- jc NoASPIManager ;Branch if none found
- push ax ;Save ASPI File Handle
-
- mov bx,ax ;BX = File Handle
- mov ax,ASPI_Get_Entry
- lea dx,ASPI_Entry ;Store entry point here
- mov cx,4 ;Four bytes to transfer
- int 21h ;Get ASPI entry point
-
- mov ax,ASPI_Close
- pop bx ;BX = ASPI File Handle
- ;BX = ASPI File Handle
- int 21h ;Close ASPI Manager
- clc ;Return with carry clear
- ret
-
- NoASPIManager: lea dx,Str_NoASPI ;Display error message, no
- call outtext ; ASPI manager found
- stc ;Return with carry set
- ret
- GetASPIEntry endp
-
- ;****************************************************************************
- ; Subroutine Name: Poll_Status
- ;
- ; Description: This subroutine polls the ASPI Status Byte and waits for
- ; non-zero status. When status goes non-zero we return.
- ; Although this sample code will hange if status never goes
- ; non-zero, an actual program should time out.
- ;
- ; Entry: Assumes that si is pointing to an SRB that has just been issued
- ;
- ;****************************************************************************
- Poll_Status proc near
- poll_loop: mov al,[si]._SRStat ;get the status byte of SRB
- cmp al,0 ;compare to zero
- jz poll_loop ;jump if still zero
- ret
- Poll_Status endp
-
- ;****************************************************************************
- ; Subroutine Name: HAInquiry
- ;
- ; Description: This subroutine sends the Host Adapter Inquiry Command to the
- ; ASPI Manager. First the SRB is totally cleared. Then the
- ; opcode and other fields of the SRB are set for HOST ADAPTER
- ; INQUIRY command.
- ;
- ; Entry: si points to the SRB
- ;
- ; Exit: SRB is full of returned data
- ;****************************************************************************
- HAInquiry proc near
- call ClearSRB ;Zero out our SRB
- mov [si]._SRCmd,HA_INQ ;ASPI opcode = HA inquiry
- mov [si]._SRHAid,0 ;Host Adapter 0
- mov [si]._SRFlags,0 ;0=no length checking
- mov [si]._SRTarget,0 ;Target 0
- mov [si]._SRLun,0 ;Lun 0
-
- ;CALLING ASPI !!
- push ds ;push segment of SRB
- lea bx,SRB
- push bx ;push offset of SRB
- call [ASPI_Entry] ;Call ASPI
- add sp,4 ;Restore stack
- ret
- HAInquiry endp
-
- ;****************************************************************************
- ; Subroutine Name: GetDevType
- ;
- ; Description: This subroutine sends the Get Device Type Command to the
- ; ASPI Manager. First the SRB is totally cleared then the SRB
- ; is loaded with opcode and other parameters for the GET DEVICE
- ; TYPE command.
- ;
- ; Entry: si points to the SRB
- ;
- ; Exit: SRB is full of returned data
- ;****************************************************************************
- GetDevType proc near
- call ClearSRB ;Zero out our SRB
- mov [si]._SRCmd,GET_TYPE ;ASPI opcode = Get Device Type
- mov [si]._SRHAid,0 ;Host Adapter 0
- mov [si]._SRFlags,0 ;0=no length checking
- mov [si]._SRTarget,0 ;Target 0
- mov [si]._SRLun,0 ;Lun 0
-
- ;CALLING ASPI !!
- push ds ;push segment of SRB
- lea bx,SRB
- push bx ;push offset of SRB
- call [ASPI_Entry] ;Call ASPI
- add sp,4 ;Restore stack
- ret
- GetDevType endp
-
- ;****************************************************************************
- ; Subroutine Name: XSCSI_IO
- ;
- ; Description: This subroutine sends the Execute SCSI I/O Command to the
- ; ASPI Manager. It is assumed that the SCSI command has already
- ; been loaded into the SRB. Here the EXEC_SIO is loaded into
- ; opcode of the SRB along with setting the other fields for a
- ; 24 byte read of SCSI INQUIRY data.
- ;
- ; Entry: The SCSI Command Block is setup upon entry, si points to SRB
- ;
- ; Exit: SRB is full of returned data
- ;****************************************************************************
- XSCSI_IO proc near
- mov [si]._SRCmd,EXEC_SIO ;ASPI opcode = execute SCSI IO
- mov [si]._SRHaId,0 ;Host Adapter 0
- mov [si]._SRFlags,SRB_DIR_IN ;Set flags to direction in
- mov [si]._SRTarget,0 ;Target 0
- mov [si]._SRLun,0 ;Lun 0
- mov [si]._SRBuflenLo,24 ;Buffer xfer length LSB
- mov [si]._SRBuflenHi,0 ;Buffer xfer length MSB
- mov [si]._SRSnsLen,20 ;Sense Buffer length 20
- lea ax,Data_Buffer
- mov [si]._SRBufPtrLo,ax ;load Data buffer offset
- mov [si]._SRBufPtrHi,ds ;load Data buffer segment
- mov [si]._SRCDBLen,6 ;SCSI CDB Length
-
- ;CALLING ASPI !!
- push ds ;push segment of SRB
- lea bx,SRB
- push bx ;push offset of SRB
- call [ASPI_Entry] ;Call ASPI
- add sp,4 ;Restore stack
- ret
- XSCSI_IO endp
-
- ;****************************************************************************
- ; Subroutine Name: RST_SDevice
- ;
- ; Description: This subroutine sends the RESET SCSI DEVICE Command to the
- ; ASPI Manager. It attempts to reset SCSI ID 2 instead of
- ; ID 0 in case ID 0 is the boot device of your computer.
- ; Posting is used by this routine.
- ;
- ; Entry: si points to the SRB
- ;
- ;****************************************************************************
- RST_SDevice proc near
- call ClearSRB ;Zero out our SRB
- mov [si]._SRCmd,RESET_DEV ;ASPI opcode = Reset Device
- mov [si]._SRHaId,0 ;Host Adapter 0
- mov [si]._SRFlags,SRB_POST ;set post bit
- mov [si]._SRTarget,0 ;Target 0
- mov [si]._SRLun,2 ;Lun 0
- mov [si]._SRBuflenLo,0 ;Buffer xfer length LSB
- mov [si]._SRBuflenHi,0 ;Buffer xfer length MSB
- mov [si]._SRSnsLen,20 ;Sense Buffer length 20
- mov ax,OFFSET ASPI_Post
- mov [si]._SRPostOff,ax ;load post routine offset
- mov [si]._SRPostCS,cs ;load post routine segment
-
- ;CALLING ASPI !!
- push ds ;push segment of SRB
- lea bx,SRB
- push bx ;push offset of SRB
- call [ASPI_Entry] ;Call ASPI
- add sp,4 ;Restore stack
- ret
- RST_SDevice endp
-
- ;****************************************************************************
- ; Subroutine Name: Abort_SIO
- ;
- ; Description: This subroutine sends the Abort SCSI I/O Request command to the
- ; ASPI Manager. First SRB2 is totally cleared then the SRB2
- ; is loaded with opcode and other parameters for the ABORT SCSI
- ; I/O COMMAND.
- ;
- ; Entry: si points to the SRB to be annihilated
- ;
- ;****************************************************************************
- Abort_SIO proc near
- push si ;save pointer to SRB 2b killed
- lea si,SRB2 ;point to another SRB
- call ClearSRB ;Zero out SRB2
- pop si ;restore pointer to SRB
- mov SRB2._SRCmd,ABORT_SRB ;ASPI opcode = Abort SRB
- mov SRB2._SRHAid,0 ;Host Adapter 0
- mov SRB2._SRFlags,0 ;0=no length checking
- mov SRB2._AbortPtrLo,si ;load offset of SRB 2b killed
- mov SRB2._AbortPtrHi,ds ;load segment of SRB 2b killed
-
- ;CALLING ASPI !!
- push ds ;push segment of SRB2
- lea bx,SRB2
- push bx ;push offset of SRB2
- call [ASPI_Entry] ;Call ASPI
- add sp,4 ;Restore stack
- ret
- Abort_SIO endp
-
- ;****************************************************************************
- ; Subroutine Name: Load_Inquiry
- ;
- ; Description: This routine loads the SCSI inquiry command into the
- ; SRB.
- ;
- ; Entry: si points to the SRB
- ;
- ; Exit: All registers preserved
- ;****************************************************************************
- Load_Inquiry proc near
- call ClearSRB ;Zero out our SRB
- mov [si]._OpCode,SCSI_Inquiry ;load opcode
- mov [si]._LUNumber,0 ;set LUN = 0
- mov [si]._LBAMiddl,0 ;set byte 2 = 0
- mov [si]._LBALeast,0 ;set byte 3 = 0
- mov [si]._Length,24 ;set length = 24
- mov [si]._Control,0 ;set control = 0
- ret
- Load_Inquiry endp
-
- ;****************************************************************************
- ; Subroutine Name: ClearSRB
- ;
- ; Description: This routine zeros out the given ASPI SRB.
- ;
- ; Entry: SI - ASPI SRB
- ;
- ; Exit: All registers preserved
- ;****************************************************************************
- ClearSRB proc near
- push es ;Save registers
- push ax
- push cx
- push di
-
- mov cx,(64+10)/2 ;Zero out 74 bytes
- mov ax,ds
- mov es,ax ;ES=DS
- mov di,si ;ES:DI points to SRB
- xor ax,ax ;Store zeros
- cld
- rep stosw ;Zero out the SRB
-
- pop di
- pop cx
- pop ax
- pop es ;Restore registers and
- ret ;return to caller
- ClearSRB endp
-
- ;****************************************************************************
- ; Subroutine Name: ASPI_Post
- ;
- ; Description: This routine is executed when the Reset Device command
- ; completes. It simply flips a flag so that execution in
- ; the RST_SDEV routine can continue. This flag method is
- ; used strictly for example purposes.
- ;
- ;
- ; Exit: All registers preserved
- ;****************************************************************************
- ASPI_Post proc far
- push bp
- mov bp,sp
-
- pusha
- push ds
- push es ;Save registers
- push dx
-
- ; mov bx,[bp+6] ;BX = SRB's offset
- ; mov ds,[bp+8] ;ES = SRB's segment
-
- ; CODE TO DETERMINE WHICH SRB JUST COMPLETED
-
- mov ds,[bp+8] ;set ds to our data segment
- mov Flag,1 ;set the flag
-
- pop dx
- pop es ;Restore registers and
- pop ds
- popa
- pop bp
- retf ;return to caller
- ASPI_Post endp
- ;***************************************************************************
- ;
- ; %%% DISPLAY ROUTINES %%%
- ;
- ;***************************************************************************
- ; Subroutine Name: outtext
- ;
- ; Description: Displays a message on the screen.
- ;
- ; Entry: DS:DX - Pointer to '$' terminated character string
- ;
- ; Exit: Nothing
- ;***************************************************************************
- outtext proc near
- push ax ; save ax
- mov ah,09h ; Do DOS Function Print String
- int 21h ; call interrupt routine
- pop ax ; restore ax
- ret
- outtext endp
-
- ;****************************************************************************
- ; Subroutine Name: itoa
- ;
- ; Description: Converts the digits of the given value to a '$'-terminated
- ; character string. Appends a carriage return and linefeed
- ; to the end of the string as well if requested.
- ;
- ; Entry: AX - Number to be converted
- ; DS:DX - Pointer to string result
- ; CX - Base of value (ie. 16 for hex, 10 for dec.)
- ;
- ; Exit: All registers preserved
- ;****************************************************************************
- itoa proc near
- pusha
- mov bx,dx
- or ax,ax ;Is input value zero?
- jne NotZero ;Branch if it's not
- mov BYTE PTR [bx],'0' ; else fill string with
- inc bx ; a single '0' and exit
- jmp SHORT itoa_exit
-
- NotZero: xor di,di
- NextDigit: or ax,ax ;Finished pushing remainders
- je itoa_pop ; onto the stack?
- xor dx,dx
- div cx ;Let's get the remainder
- push dx ;Push the remainder
- inc di ;Increment digit count
- jmp NextDigit
-
- itoa_pop: or di,di ;Finished popping digits?
- je itoa_exit ;Branch and exit if we are
- pop dx ;Pop a digit
- cmp dl,10 ;Is it a 0-9 digit?
- jb DecDigit ;If it is convert to ASCII
- add dl,'A'-10 ; else convert to HEX
- jmp SHORT PlaceChar ; alphabet
- DecDigit: add dl,'0'
- PlaceChar: mov [bx],dl ;Store character in string
- inc bx ;Move to next place in string
- dec di ;Decrement pop count
- jmp itoa_pop ;Pop next value
-
- itoa_exit:
- mov BYTE PTR [bx],CR ;Place Carriage Return &
- mov BYTE PTR [bx+1],LF ; and Line Feed and '$'
- mov BYTE PTR [bx+2],'$' ; char at end of string
- jmp SHORT itoa_exit1
-
- mov BYTE PTR [bx],'$'
- itoa_exit1: popa ;Restore all registers
- ret
- itoa endp
-
- ;****************************************************************************
- ; Subroutine Name: DispSRBInq
- ;
- ; Description: This subroutine displays the information returned in the SRB
- ; for the Host Adapter Inquiry Command.
- ;
- ; Entry: Expects The SRB to be full of Host Adapter Inquiry Data
- ;
- ; Exit:
- ;****************************************************************************
- DispSRBInq proc near
- lea dx,Str_HA_Inquiry ;load the string for outtext
- call outtext ;output the text
-
- mov cx,16 ;set base= hex for iota
- lea dx,Str_ASPI_STAT+36 ;point to loc in string
- mov al,SRB._SRStat ;load value to convert
- mov ah,0 ;zero out ah
- call itoa ;convert to ASCII in string loc
- lea dx,Str_ASPI_STAT ;load the string for outtext
- call outtext ;output the text
-
- lea bx,Str_Num_HA ;Get Number of HA string loc
- mov al,SRB._HACount ;Get # of ASPI host adapters
- add al,'0' ;AL = ASCII Host Adapter #
- mov BYTE PTR [bx+36],al ;Place HA # in string
- mov dx,bx ;load the string for outtext
- call outtext ;output the text
-
- lea bx,Str_TID_HA ;Get Target ID of HA string loc
- mov al,SRB._HAIdNum ;Get ID
- add al,'0' ;AL = ASCII ID
- mov BYTE PTR [bx+36],al ;Place HA # in string
- mov dx,bx ;load the string for outtext
- call outtext ;output the text
-
- mov cx,16 ;ID has 16 bytes (for movsb)
- lea si,SRB._SCSIMgrId ;load source of string mov
- lea di,Str_Mgr_ID+36 ;load destination of string mov
- rep movsb ;move string
- lea dx,Str_Mgr_ID ;Get Manager ID string loc
- call outtext ;output the text
-
- mov cx,16 ;ID has 16 bytes (for movsb)
- lea si,OFFSET SRB._HAIdString ;load source of string mov
- lea di,Str_HA_ID+36 ;load destination of string mov
- rep movsb ;move string
- lea dx,Str_HA_ID ;Get Manager ID string loc
- call outtext ;output the text
- ret
- DispSRBInq endp
-
- ;****************************************************************************
- ; Subroutine Name: DispDevType
- ;
- ; Description: This subroutine displays the information returned in the SRB
- ; for the Get Device Type Command.
- ;
- ; Entry: Expects The SRB to be full of Host Adapter Inquiry Data
- ;
- ; Exit:
- ;****************************************************************************
- DispDevTyp proc near
- lea dx,Str_Get_DevTyp ;point to Get Dev Type string
- call outtext ;output the text
-
- lea bx,Str_ASPI_STAT ;point to ASPI Status string
- mov al,SRB._SRStat ;Get ASPI status
- add al,'0' ;convert to ASCII
- mov BYTE PTR [bx+36],al ;place Status in string
- mov dx,bx ;load the string for outtext
- call outtext ;output the text
-
- lea bx,Str_Dev_Typ ;Get SCSI Dev Type string loc
- mov al,SRB._ScsiDevType ;Get # of ASPI host adapters
- add al,'0' ;AL = ASCII Host Adapter #
- mov BYTE PTR [bx+36],al ;Place HA # in string
- mov dx,bx ;load the string for outtext
- call outtext ;output the text
-
- ret
- DispDevTyp endp
-
- ;****************************************************************************
- ; Subroutine Name: DispInquiry
- ;
- ; Description: This subroutine displays the information returned in the SRB
- ; for the Get Device Type Command.
- ;
- ; Entry: Expects The SRB to be full of Host Adapter Inquiry Data
- ;
- ; Exit:
- ;****************************************************************************
- DispInquiry proc near
- lea dx,Str_SCSI_IO ;load the string for outtext
- call outtext ;output the text
-
- mov cx,16 ;set for HEX base (iota call)
- lea dx,Str_ASPI_STAT+36 ;point to string location
- mov al,SRB._SRStat ;load value to convert
- mov ah,0 ;zero out ah
- call itoa ;convert to ASCII in string
- lea dx,Str_ASPI_STAT ;load the string for outtext
- call outtext ;output the text
-
- lea dx,Str_PQualTyp+36 ;point to string location
- mov al,Data_Buffer.PerQualTyp ;load value to convert
- mov ah,0 ;zero out ah
- call itoa ;convert to ASCII in string
- lea dx,Str_PQualTyp ;Get Peripheral Qual Dev string
- call outtext ;output the text
-
- lea dx,Str_Versions+36 ;Get Peripheral Qual Dev string
- mov al,Data_Buffer.Versions ;Get Byte from Data Buffer
- mov ah,0 ;zero out ah
- call itoa ;convert to ASCII in string
- lea dx,Str_Versions ;load the string for outtext
- call outtext ;output the text
-
- push si ;save pointer to SRB
- mov cx,28 ;load number of bytes to mov
- lea si,OFFSET Data_Buffer.VendorID ;load source address
- lea di,Str_Inq_Dat+36 ;load destination address
- rep movsb ;move the string
- lea dx,Str_Inq_Dat ;load the string for outtext
- call outtext ;output the text
- pop si ;restore pointer to SRB
- ret
- DispInquiry endp
-
- ;****************************************************************************
- ; Subroutine Name: DispStat
- ;
- ; Description: This subroutine displays the ASPI status byte
- ;
- ;
- ;****************************************************************************
- DispStat proc near
- lea dx,Str_CRLF
- call outtext ;output the text
-
- lea bx,Str_ASPI_STAT ;point to ASPI Status string
- mov al,SRB._SRStat ;Get ASPI status
- add al,'0' ;convert to ASCII
- mov BYTE PTR [bx+36],al ;place Status in string
- mov dx,bx ;load the string for outtext
- call outtext ;output the text
-
- ret
- DispStat endp
- ;****************************************************************************
- END START