home *** CD-ROM | disk | FTP | other *** search
- /*DDK*************************************************************************/
- /* */
- /* COPYRIGHT Copyright (C) 1995 IBM Corporation */
- /* */
- /* The following IBM OS/2 WARP source code is provided to you solely for */
- /* the purpose of assisting you in your development of OS/2 WARP device */
- /* drivers. You may use this code in accordance with the IBM License */
- /* Agreement provided in the IBM Device Driver Source Kit for OS/2. This */
- /* Copyright statement may not be removed. */
- /* */
- /*****************************************************************************/
- /*static char *SCCSID = "src/dev/dasd/os2scsi/scsubrs.c, scsy, ddk_subset, b_bdd.032 93/08/25";*/
- /**************************************************************************
- *
- * SOURCE FILE NAME = SCSUBRS.C
- *
- * DESCRIPTIVE NAME = OS2SCSI.DMD - OS/2 SCSI.SYS Emulation
- *
- *
- *
- * VERSION = V2.0
- *
- * DATE
- *
- * DESCRIPTION : IORB Management and miscellaneous functions.
- *
- *
- *
- */
-
- #define INCL_NOBASEAPI
- #define INCL_NOPMAPI
- #include "os2.h"
- #include "error.h"
- #include "strat2.h"
- #include "reqpkt.h"
- #include "dhcalls.h"
- #include "SCB.h"
- #include "iorb.h"
- #include "scsi.h"
- #include "scscsi.h"
- #include "scgen.h"
- #include "abios.h"
- #include "scproto.h"
-
-
- extern UNITCB UnitCB[1]; /* First UnitCB allocated here */
- extern USHORT NumUnitCBs; /* number of unit control blocks */
- extern NPSELARRAY npSelArray; /* near ptr to GDT selector array */
- extern ULONG plDataSeg; /* near ptr to GDT selector array */
- extern USHORT GDTSelStack[];
- extern USHORT GDTSelStackPtr;
-
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: SetAdditionalData *
- * *
- * DESCRIPTIVE NAME: Set Additional Data segment area *
- * *
- * FUNCTION: This routine allocates request queues for each unit, and*
- * allocates GDT selector array. *
- * *
- * ENTRY POINT: SetAdditionalData *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: None *
- * *
- * EXIT-NORMAL: The final size of DATA segment *
- * *
- * EXIT-ERROR: 0 => Devhelp function failed *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- USHORT near SetAdditionalData()
- {
- USHORT i;
- NPBYTE npEndData;
-
- npEndData = (NPBYTE)UnitCB;
- npEndData += (sizeof(UNITCB) * (BYTE)NumUnitCBs);
-
- npSelArray = (NPSELARRAY)npEndData;
-
- npEndData += (sizeof(SEL) * (BYTE)NumUnitCBs);
-
- DevHelp_AllocGDTSelector((PSEL)npSelArray, NumUnitCBs);
-
- DevHelp_AllocGDTSelector((PSEL) &GDTSelStack[1], MAX_GDT_SEL_STACK);
-
- return((USHORT)npEndData);
-
- }
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: WaitIORB *
- * *
- * DESCRIPTIVE NAME: Wait for IORB until available *
- * *
- * FUNCTION: This routine check wether IORB is in use or not, *
- * and wait for IORB until available. *
- * *
- * ENTRY POINT: WaitIORB *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: pGenctl Pointer to Generic I/O Control request packet *
- * *
- * EXIT-NORMAL: TRUE *
- * *
- * *
- * EXIT-ERROR: FALSE Devhelp error *
- * REQ_FLUSHED Request is flushed *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- BOOL near WaitIORB(pGenctl, EntryType)
- USHORT EntryType;
- PRP_GENIOCTL pGenctl;
- {
- USHORT bottom;
- USHORT rc;
- USHORT status = 0;
- USHORT allocated = FALSE;
- NPUCB npUCB;
- PSCSI_IN pParm;
-
- pParm = (PSCSI_IN)(pGenctl->ParmPacket);
-
- npUCB = &UnitCB[pParm->hDev];
-
- /*--------------------------------------------------*/
- /* Requesting threads are blocked here waiting for */
- /* the device. A thread may wakeup from the block */
- /* under the following conditions: */
- /* */
- /* 1.) The underlying process was aborted. */
- /* 2.) The driver is flushing the queues for this */
- /* device. */
- /* 3.) The request has timed out. */
- /* 4.) A spurious wakeup occurred. */
- /*--------------------------------------------------*/
-
- npUCB->WaitReqCnt++;
-
- while ( npUCB->IntUnitFlags & IUF_IORB_BUSY )
- {
- rc = DevHelp_ProcBlock((ULONG) (PUSHORT) &npUCB->WaitReqCnt,
- (ULONG) MAX_REQ_WAIT,
- (USHORT) WAIT_IS_INTERRUPTABLE );
-
- /*------------------------------------------------*/
- /* If the request has timed out, then put it on a */
- /* FIFO queue of timed out requests. This queue */
- /* will be serviced before the general queue */
- /*------------------------------------------------*/
-
- if ( rc == WAIT_TIMED_OUT )
- {
- rc = HoldInTimeOutQ( npUCB, pGenctl );
- }
-
-
- if (npUCB->IntUnitFlags & IUF_REQ_FLUSH)
- {
- if (!(npUCB->WaitReqCnt--))
- npUCB->IntUnitFlags &= ~IUF_REQ_FLUSH;
-
- status = REQ_FLUSHED;
- break;
- }
-
- /*------------------------------------------------*/
- /* If the request was aborted. Then just return */
- /* it to the caller. */
- /*------------------------------------------------*/
-
- if ( rc == WAIT_INTERRUPTED )
- {
- npUCB->WaitReqCnt--;
-
- /*--------------------------------------------------*/
- /* The current drivers IBM drivers do not handle */
- /* INTERRUPTED requests. Return request as FLUSHED */
- /* instead. */
- /*--------------------------------------------------*/
-
- status = REQ_FLUSHED /* REQ_INTERRUPTED */;
- break;
- }
-
- }
-
- /*-----------------------------------------------*/
- /* If this is a normal wakeup and the queues are */
- /* not being flushed. Then start-up this request */
- /*-----------------------------------------------*/
-
- if ( !status )
- {
- npUCB->IntUnitFlags |= IUF_IORB_BUSY;
-
- if (ValidateUserPacket(pGenctl, npUCB, EntryType))
- status = TRUE;
- else
- {
- ReleaseIORB(pGenctl);
- status = FALSE;
- }
- }
-
- return ( status );
- }
-
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: ReleaseIORB *
- * *
- * DESCRIPTIVE NAME: Release request from the queue. *
- * *
- * FUNCTION: This routine removes the request already done from the *
- * queue. *
- * *
- * ENTRY POINT: ReleaseQueue *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: pGenctl Pointer to Generic I/O Control request packet *
- * *
- * EXIT-NORMAL: *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- void near ReleaseIORB(pGenctl)
- PRP_GENIOCTL pGenctl;
- {
- NPUCB npUCB;
- ULONG BlockId;
- USHORT AwakeCount;
- PSCSI_IN pParm;
-
- pParm = (PSCSI_IN)(pGenctl->ParmPacket);
- npUCB = &UnitCB[pParm->hDev];
-
- npUCB->WaitReqCnt--;
-
- UnlockUserPacket(npUCB);
-
- npUCB->IntUnitFlags &= ~IUF_IORB_BUSY;
-
- /*----------------------------------------*/
- /* If there are requests waiting, then */
- /* run the request at the head of the */
- /* TimeOut Q first. Then run the normal */
- /* requests. */
- /*----------------------------------------*/
-
- if ( npUCB->WaitReqCnt )
- {
- BlockId = ( npUCB->TimeOutQHead ) ? (ULONG) npUCB->TimeOutQHead
- : (ULONG) (PULONG) &npUCB->WaitReqCnt;
-
- DevHelp_ProcRun((ULONG) BlockId, &AwakeCount);
- }
-
-
- return;
-
- }
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: WaitOtherIORB *
- * *
- * DESCRIPTIVE NAME: Wait for IORB until available *
- * *
- * FUNCTION: This routine check whether the Other IORB is in use *
- * or not and waits for the IORB to become available. *
- * *
- * ENTRY POINT: WaitOtherIORB *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: *
- * *
- * EXIT-NORMAL: *
- * *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- void near WaitOtherIORB( npUCB )
-
- NPUCB npUCB;
- {
-
- npUCB->OtherReqCnt++;
-
- while ( npUCB->IntUnitFlags & IUF_OTHERIORB_BUSY )
- {
- DevHelp_ProcBlock((ULONG)(PUSHORT) &npUCB->OtherReqCnt,
- (ULONG) -1,
- (USHORT) WAIT_IS_NOT_INTERRUPTABLE );
- }
- ENABLE
-
- npUCB->IntUnitFlags |= IUF_OTHERIORB_BUSY;
-
- return;
- }
-
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: ReleaseOtherIORB *
- * *
- * DESCRIPTIVE NAME: Release the Other IORB. *
- * *
- * FUNCTION: This routine indicates the OtherIORB is available *
- * *
- * ENTRY POINT: ReleaseOtherIORB *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: *
- * *
- * EXIT-NORMAL: *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- void near ReleaseOtherIORB( npUCB )
-
- NPUCB npUCB;
- {
- USHORT AwakeCount;
-
-
- npUCB->OtherReqCnt--;
-
- if ( npUCB->OtherReqCnt )
- {
- DevHelp_ProcRun((ULONG) (PUSHORT) &npUCB->OtherReqCnt, &AwakeCount);
- }
-
- npUCB->IntUnitFlags &= ~IUF_OTHERIORB_BUSY;
-
- return;
-
- }
-
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: FlushQueue *
- * *
- * DESCRIPTIVE NAME: Flush the requests from the queue *
- * *
- * FUNCTION: This routine flush the request from the queue *
- * *
- * ENTRY POINT: FlushQueue *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: npUCB Unit Control Block *
- * *
- * EXIT_NORMAL: always *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- void near FlushReqPkt(npUCB)
-
- NPUCB npUCB;
- {
- USHORT AwakeCount;
- NPQELE npQEle;
-
-
- if (npUCB->WaitReqCnt > 1)
- {
- npUCB->IntUnitFlags |= IUF_REQ_FLUSH;
-
- /*---------------------------------*/
- /* Flush requests on the TimeOut Q */
- /*---------------------------------*/
-
- for (npQEle=npUCB->TimeOutQHead; npQEle; npQEle=npQEle->Next ) /*@V73138*/
- {
- DevHelp_ProcRun((ULONG)(PVOID) npQEle, &AwakeCount);
- }
- DevHelp_ProcRun((ULONG)((PIORB) &npUCB->XferSCB_IORB), &AwakeCount);
- }
- return;
- }
-
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: HoldInTimeOutQueue *
- * *
- * DESCRIPTIVE NAME: *
- * *
- * FUNCTION: *
- * *
- * *
- * ENTRY POINT: *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: pGenctl Pointer to Generic I/O Control request packet *
- * *
- * EXIT-NORMAL: *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- USHORT near HoldInTimeOutQ(npUCB, pGenctl)
-
- NPUCB npUCB;
- PRP_GENIOCTL pGenctl;
- {
- USHORT rc;
- NPQELE npQEle;
-
- if ( !(npUCB->IntUnitFlags & IUF_IORB_BUSY) )
- {
- return ( 0 );
- }
-
- if ( !( npQEle=AddToTimeOutQ( npUCB, pGenctl ) ) )
- {
- return( 1 );
- }
-
- do
- {
- rc = DevHelp_ProcBlock((ULONG) (PVOID) npQEle,
- (ULONG) -1,
- (USHORT) WAIT_IS_INTERRUPTABLE );
- }
-
- while ( !rc
- && !(npUCB->IntUnitFlags & IUF_REQ_FLUSH)
- && (npUCB->IntUnitFlags & IUF_IORB_BUSY ) );
-
- if ( RemoveFromTimeOutQ( npUCB, npQEle ) )
- {
- _asm { int 3 }
- }
-
- return ( rc );
- }
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: AddToTimeOutQ *
- * *
- * DESCRIPTIVE NAME: *
- * *
- * FUNCTION: *
- * *
- * *
- * ENTRY POINT: *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: pGenctl Pointer to Generic I/O Control request packet *
- * *
- * EXIT-NORMAL: *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- NPQELE AddToTimeOutQ(npUCB, pGenctl)
-
- NPUCB npUCB;
- PRP_GENIOCTL pGenctl;
- {
- NPQELE npQEle;
-
-
- /*---------------------------------------*/
- /* Add element to TimeOut Q if available */
- /*---------------------------------------*/
-
- if ( npQEle = npUCB->TimeOutQFree )
- {
- npUCB->TimeOutQFree = npQEle->Next;
- npQEle->Next = 0;
-
- npQEle->pRP = (ULONG) pGenctl;
-
- if ( !npUCB->TimeOutQFoot )
- {
- npUCB->TimeOutQHead = npQEle;
- }
- else
- {
- (npUCB->TimeOutQFoot)->Next = npQEle;
- }
-
- npUCB->TimeOutQFoot = npQEle;
- }
-
- return ( npQEle );
- }
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: RemoveFromTimeOutQ *
- * *
- * DESCRIPTIVE NAME: *
- * *
- * FUNCTION: *
- * *
- * *
- * ENTRY POINT: *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: pGenctl Pointer to Generic I/O Control request packet *
- * *
- * EXIT-NORMAL: *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- USHORT near RemoveFromTimeOutQ(npUCB, npQEleRemove)
-
- NPUCB npUCB;
- NPQELE npQEleRemove;
- {
- USHORT rc = 0;
- NPQELE npQEle;
- NPQELE npQElePrev;
-
- npQElePrev = 0;
- npQEle = npUCB->TimeOutQHead;
-
- /*-----------------------------------*/
- /* Search TimeOut Q for match on pRP */
- /*-----------------------------------*/
-
- while ( npQEle && npQEle != npQEleRemove )
- {
- npQElePrev = npQEle;
- npQEle = npQEle->Next;
- }
-
- /*----------------------------------------*/
- /* Delete element from TimeOut Q if found */
- /*----------------------------------------*/
-
- if ( npQEle )
- {
- if ( npQElePrev )
- {
- npQElePrev->Next = npQEle->Next;
- }
- else
- {
- if ( !(npUCB->TimeOutQHead = npQEle->Next) )
- {
- npUCB->TimeOutQFoot = 0;
- }
- }
-
- npQEle->Next = npUCB->TimeOutQFree;
- npUCB->TimeOutQFree = npQEle;
- }
- else
- {
- rc = 1;
- }
-
- return( rc );
- }
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: ValidateUserPacket *
- * *
- * DESCRIPTIVE NAME: Lock and Validate Device Class Driver Packets *
- * *
- * FUNCTION: Normally requests packets received from device class *
- * drivers are locked and are addressed by GDT selectors *
- * which are not context sensitive. *
- * *
- * For SenseData buffers on the R0 stack or passed from *
- * an application we lock the area and alias it to a *
- * GDT Selector. *
- * *
- * For SCB chains, we allow the device class driver to *
- * use its stack only during its initialization phase. *
- * Any other context-sensitive references to SCB chains *
- * are rejected. *
- * *
- * *
- * ENTRY POINT: ValidateUserPacket *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: npUCB Unit Control Block *
- * *
- * EXIT_NORMAL: TRUE *
- * *
- * EXIT-ERROR: FALSE Devhelp function error *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- BOOL near ValidateUserPacket (pGenctl, npUCB, EntryType)
-
- PRP_GENIOCTL pGenctl;
- NPUCB npUCB;
- USHORT EntryType;
- {
- PSCSI_IN pParm;
- PSCSI_OUT pData;
- USHORT rc;
- USHORT Sel;
- USHORT Function;
- ULONG plPkt; /* Linear address of Parm or Data Packet */
- ULONG plLockHandle;
- ULONG plPhysAddr;
- ULONG PageListCount;
- ULONG VMLockFlags;
- ULONG Length;
-
- pParm = (PSCSI_IN)(pGenctl->ParmPacket);
- pData = (PSCSI_OUT)(pGenctl->DataPacket);
-
- npUCB->ppDataPkt = 0;
- npUCB->SenseSel = 0;
-
- Function = pGenctl->Function - SCSI_PLUS_VALUE;
-
- /*--------------------------------------------------------*/
- /* Validate XFER SCB Requests */
- /* -------------------------- */
- /* If an SCB chain is pointed to by a Context-Sensitive */
- /* selector, we reject the request. The only exception */
- /* is a device class driver in its initialization */
- /* phase. */
- /*--------------------------------------------------------*/
-
- if (Function == ABFC_SCSIP_TRANSFER_SCB)
- {
- Sel = SELECTOROF( ((PSCSI_IN_XFERSCB) pParm)->lpSCBH );
-
- /*--------------------------------------------------------------*/
- /* We determine whether the device class driver is initializing */
- /* by its use of the Strat 1 entry point rather than the IDC */
- /* entry point. */
- /*--------------------------------------------------------------*/
-
- if ((Sel == R0_STACK_SEL) ||
- ((Sel & LDT_SEL) && (EntryType != STRAT1_ENTRY)) )
- {
- return(FALSE);
- }
- }
-
- /*--------------------------------------------------------*/
- /* Validate Sense Data Requests */
- /* ---------------------------- */
- /* These requests can potentially return SCSI Sense Data. */
- /* The request is examined further to determine whether */
- /* the buffer needs to be locked. */
- /*--------------------------------------------------------*/
-
- if ( Function == ABFC_RESET_DEVICE ||
- Function == ABFC_SCSIP_ABORT ||
- Function == ABFC_SCSIP_TRANSFER_SCB )
- {
- if (pParm && (Length = ((PSCSI_IN_XFERSCB)pParm)->lnSenseData))
- {
- npUCB->pSenseData = (PSCSI_REQSENSE_DATA) pData;
-
- Sel = SELECTOROF( pData );
-
- if ((Sel == R0_STACK_SEL) || (Sel & LDT_SEL) )
- {
- rc = DevHelp_VirtToLin(SELECTOROF(pData), (ULONG) OFFSETOF(pData),
- (PVOID) &plPkt);
- if (!rc)
- {
- plLockHandle = plDataSeg + (ULONG) ((USHORT) &(npUCB->hLockDataP));
- plPhysAddr = plDataSeg + (ULONG) ((USHORT) &(npUCB->ppDataPkt));
- VMLockFlags = (VMDHL_LONG | VMDHL_WRITE | VMDHL_CONTIGUOUS | VMDHL_16M);
-
- if (DevHelp_VMLock(VMLockFlags, plPkt, Length, plPhysAddr,
- plLockHandle, (PULONG) &PageListCount) != 0)
-
- return(FALSE);
-
- if ( (Sel = npUCB->SenseSel = AllocateGDTSel()) )
- {
- if ( !DevHelp_PhysToGDTSelector( (ULONG) npUCB->ppDataPkt,
- (USHORT) Length,
- (SEL) Sel ) )
- { /*@V53750*/
- npUCB->pSenseData = (PSCSI_REQSENSE_DATA) MAKEP(Sel, 0);
- }
- else
- {
- return(FALSE);
- }
- }
- else
- return(FALSE);
- }
- else
- return(FALSE);
- }
- }
- }
-
- return(TRUE);
- }
-
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: UnlockUserPacket *
- * *
- * DESCRIPTIVE NAME: Unlock Parameter and Data Pakets *
- * *
- * FUNCTION: Unlock parameter and data packets from General control *
- * request. *
- * *
- * ENTRY POINT: UnlockUserPacket *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: npUCB Unit Control Block *
- * *
- * EXIT_NORMAL: TRUE *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- void near UnlockUserPacket (npUCB)
-
- NPUCB npUCB;
-
- {
- if ( npUCB->ppDataPkt )
- {
- DevHelp_VMUnLock((LIN)(plDataSeg+(ULONG) ((USHORT) &(npUCB->hLockDataP))));
- npUCB->ppDataPkt = 0;
- }
-
- if ( npUCB->SenseSel )
- {
- DeallocateGDTSel( npUCB->SenseSel );
- npUCB->SenseSel = 0;
- }
- }
-
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: f_CheckIORBError *
- * *
- * DESCRIPTIVE NAME: Far Check IORB Error Code *
- * *
- * FUNCTION: This routine just calls CheckIORBError *
- * *
- * ENTRY POINT: f_CheckIORBError *
- * *
- * LINKAGE: Call Far *
- * *
- * INPUT: *
- * *
- * EXIT-NORMAL: *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK/INTERRUPT TIME * *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- USHORT far f_CheckIORBError(npUCB, npIORB)
-
- NPUCB npUCB;
- NPIORBH npIORB;
- {
- return(CheckIORBError(npUCB, npIORB));
- }
-
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: CheckIORBError *
- * *
- * DESCRIPTIVE NAME: Check IORB Error Code *
- * *
- * FUNCTION: This routine convert SCSI error code from IORB and *
- * sense key. If sense key is UNIT ATTENTION, the rest *
- * of the requests will be flushed. *
- * *
- * ENTRY POINT: CheckIORBError *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: *
- * *
- * EXIT-NORMAL: *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK/INTERRUPT TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
-
- USHORT near CheckIORBError(npUCB, npIORB)
-
- NPUCB npUCB;
- NPIORBH npIORB;
- {
- NPSCSI_STATUS_BLOCK npStatusBlk;
- PSCSI_REQSENSE_DATA pSense;
-
- USHORT status = STDON | STERR;
- USHORT ErrorCode;
-
-
- if ( !(npIORB->Status & IORB_ERROR) )
- {
- return( STDON );
- }
-
- ErrorCode = npIORB->ErrorCode;
-
- if (npIORB->Status & IORB_STATUSBLOCK_AVAIL)
- {
- npStatusBlk = (NPSCSI_STATUS_BLOCK) npIORB->pStatusBlock;
-
- if (npStatusBlk->Flags & STATUS_SENSEDATA_VALID)
- {
- pSense = npStatusBlk->SenseData;
-
- if ((pSense->SenseKey & SCSI_SENSEKEY_MASK) == SCSI_SK_UNITATTN)
- {
- FlushReqPkt(npUCB);
- }
- return(status | SCSI_ERR_DEVICE);
- }
- else
- {
- if (npStatusBlk->AdapterErrorCode)
- {
- ErrorCode = npStatusBlk->AdapterErrorCode;
- }
- }
- }
-
- /*--------------------------------------------------------*/
- /* Normally an ADD will return SCSI Sense Data. However, */
- /* in cases where an error occurred on the adapter itself */
- /* or in the ADD, sense data might not be available. In */
- /* these cases, the AdapterError code or IORBError code */
- /* is examined and the error is reported either as a */
- /* failed request sense or an I24_* device driver */
- /* error code as appropriate. */
- /*--------------------------------------------------------*/
-
- switch (ErrorCode & IORB_ERR_MASK)
- {
- case (IOERR_CMD):
- status |= ERROR_I24_BAD_COMMAND;
- break;
-
-
- case (IOERR_ADAPTER):
-
- switch (ErrorCode)
- {
- case (IOERR_ADAPTER_TIMEOUT):
- case (IOERR_ADAPTER_DEVICE_TIMEOUT):
- status |= SCSI_ERR_TIMEOUT;
- break;
-
- case (IOERR_ADAPTER_REQ_NOT_SUPPORTED):
- status |= ERROR_I24_BAD_COMMAND;
- break;
-
- default:
- status |= SCSI_ERR_REQ_SENSE_FAILED;
- break;
- }
- break;
-
- case (IOERR_DEVICE):
-
- switch (ErrorCode)
- {
- case (IOERR_DEVICE_REQ_NOT_SUPPORTED):
- status |= ERROR_I24_BAD_COMMAND;
- break;
-
- case (IOERR_DEVICE_BUSY):
- status |= SCSI_ERR_DEV_BUSY;
- break;
-
- default:
- status |= SCSI_ERR_REQ_SENSE_FAILED;
- }
- break;
-
- default:
- status |= ERROR_I24_GEN_FAILURE;
-
- }
- return (status);
-
- }
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: AllocateGDTSel *
- * *
- * DESCRIPTIVE NAME: Allocate GDT Selector *
- * *
- * FUNCTION: This routine manages a stack of GDT selectors which *
- * are used to alias Sense Data buffers pointed to by *
- * LDT or Ring 0 Stack selectors. *
- * *
- * ENTRY POINT: AllocateGDTSel *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: *
- * *
- * EXIT-NORMAL: *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- USHORT near AllocateGDTSel(VOID)
- {
- USHORT Sel = 0;
- if ( GDTSelStackPtr )
- {
- Sel = GDTSelStack[GDTSelStackPtr];
- GDTSelStack[GDTSelStackPtr--] = 0;
- }
- return( Sel );
- }
-
- /********************** START OF SPECIFICATIONS *****************************
- * *
- * SUBROUTINE NAME: DeallocateGDTSel *
- * *
- * DESCRIPTIVE NAME: Deallocate GDT Selector *
- * *
- * FUNCTION: This routine manages a stack of GDT selectors which *
- * are used to alias Sense Data buffers pointed to by *
- * LDT or Ring 0 Stack selectors. *
- * *
- * ENTRY POINT: DeallocateGDTSel *
- * *
- * LINKAGE: Call Near *
- * *
- * INPUT: *
- * *
- * EXIT-NORMAL: *
- * *
- * EXIT-ERROR: *
- * *
- * Notes: Called at TASK TIME *
- * *
- *********************** END OF SPECIFICATIONS *******************************/
-
- VOID near DeallocateGDTSel(Sel)
-
- USHORT Sel;
- {
- GDTSelStack[++GDTSelStackPtr] = Sel;
- }
-