COMPILE FUNCTION obj_WO_Step(Method,Parms) /* Methods for the Work Order Step (WO_STEP) table 12/15/2004 JCH - Initial Coding Properties: Methods: Create(WoNo,Step,PSNo,OrgWO) ;* Create new WO Step entry */ DECLARE FUNCTION Get_Status, Msg, Utility, obj_Tables, Dialog_Box,NextKey, Popup, Get_Property, obj_RDS, obj_React_Run DECLARE FUNCTION Logging_Services, Environment_Services, Database_Services DECLARE SUBROUTINE Set_Status, Msg, obj_Tables, Send_Dyn, Btree.Extract, ErrMsg, Send_Dyn, RList, obj_WO_Log DECLARE SUBROUTINE Send_Event, obj_RDS, Logging_Services, Work_Order_Services $INSERT MSG_EQUATES $INSERT WO_LOG_EQU $INSERT WO_STEP_EQUATES $INSERT RDS_EQU $INSERT SCHEDULE_EQU $INSERT PROD_SPEC_EQU $INSERT Popup_Equates $INSERT LOGICAL EQU TARGET_ACTIVELIST$ TO 5 EQU CRLF$ TO \0D0A\ ErrTitle = 'Error in Stored Procedure "obj_WO_Step"' ErrorMsg = '' LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WO_STEP' LogDate = Oconv(Date(), 'D4/') LogTime = Oconv(Time(), 'MTS') LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' CurrStatus Log.csv' Headers = 'Logging DTM' : @FM : 'User' : @FM : 'Work Order No' : @FM : 'Calculated Value' : @FM : 'Physical Value' objCurrStatusLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, COMMA$, Headers, '', False$, False$) LoggingDTM = LogDate : ' ' : LogTime ; // Logging DTM IF NOT(ASSIGNED(Method)) THEN ErrorMsg = 'Unassigned parameter "Method" passed to subroutine' IF NOT(ASSIGNED(Parms)) THEN Parms = '' IF ErrorMsg NE '' THEN Set_Status(-1,ErrTitle:@SVM:ErrorMsg) RETURN '' END Result = '' BEGIN CASE CASE Method = 'Create' ; GOSUB Create CASE Method = 'Delete' ; GOSUB Delete CASE Method = 'CurrStatus' ; GOSUB CurrStatus CASE Method = 'AdjStepRDSQtys' ; GOSUB AdjStepRDSQtys CASE 1 ErrorMsg = 'Unknown Method ':QUOTE(Method):' passed to routine.' END CASE IF ErrorMsg NE '' THEN Set_Status(-1,ErrTitle:@SVM:ErrorMsg) RETURN '' END RETURN Result * * * * * * * Create: * * * * * * * WONo = Parms[1,@RM] StepNo = Parms[COL2()+1,@RM] PSNo = Parms[COL2()+1,@RM] ProcDesc = Parms[COL2()+1,@RM] IF NOT(ASSIGNED(WONo)) THEN ErrorMsg = 'Unassigned parameter "WONo" passed to routine. (':Method:')' IF NOT(ASSIGNED(StepNo)) THEN ErrorMsg = 'Unassigned parameter "StepNo" passed to routine. (':Method:')' IF NOT(ASSIGNED(PSNo)) THEN ErrorMsg = 'Unassigned parameter "PSNo" passed to routine. (':Method:')' IF NOT(ASSIGNED(ProcDesc)) THEN ProcDesc = '' IF ErrorMsg NE '' OR WONo = '' OR StepNo = '' OR PSNo = '' THEN RETURN PSRec = XLATE('PROD_SPEC',PSNo,'','X') WOStepKey = WONo:'*':StepNo If RowExists('WO_STEP', WOStepKey) then WOStepRec = Database_Services('ReadDataRow', 'WO_STEP', WOStepKey) end else WOStepRec = '' end WOStepRec = PSNo WOStepRec = ProcDesc WOStepRec = PSRec WOStepRec = PSRec WOStepRec = PSRec WOStepRec = PSRec WOStepRec = PSRec OtParms = 'WO_STEP':@RM:WOStepKey:@RM:@RM:WOStepRec obj_Tables('WriteRec',OtParms) RETURN * * * * * * * Delete: * * * * * * * WONo = Parms[1,@RM] StepNo = Parms[COL2()+1,@RM] WOStepKey = WONo:'*':StepNo TableVar = '' OtParms = 'WO_STEP':@RM:WOStepKey:@RM:TableVar WOStepRec = obj_Tables('ReadRec',OtParms) ;* Locks and reads record for update IF WOStepRec NE '' THEN ErrorMsg = 'Work Order Step currently has RDS records attached and may not be deleted.' END IF WOStepRec NE '' THEN ErrorMsg = 'Work Order Step currently has WM_IN records attached and may not be deleted.' END IF WOStepRec NE '' THEN ErrorMsg = 'Work Order Step currently has WM_OUT records attached and may not be deleted.' END IF WOStepRec NE '' THEN ErrorMsg = 'Work Order Step currently has SCHED_DET records attached and may not be deleted.' ErrorMsg := CRLF$:'Remove Work Order from the New Scheduler and retry.' END IF ErrorMsg = '' THEN obj_Tables('DeleteRec',OtParms) END ELSE obj_Tables('UnlockRec',OtParms) END RETURN * * * * * * * CurrStatus: * * * * * * * IF NOT(ASSIGNED(WOStepKey)) THEN WOStepKey = Parms[1,@RM] IF NOT(ASSIGNED(WOStepRec)) THEN WOStepRec = Parms[COL2()+1,@RM] IF WOStepKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter IF WOStepRec = '' THEN WOStepRec = XLATE('WO_STEP',WOStepKey,'','X') WOCloseDt = XLATE('WO_LOG',WOStepKey[1,'*'],11,'X') IF WOCloseDt NE '' THEN Result = 'CL' RETURN END RDSNos = WOStepRec WMInKeys = WOStepRec WMOutKeys = WOStepRec IF RDSNos = '' AND WMInKeys = '' THEN Result = 'NEW' RETURN END IF WMInKeys NE '' THEN RawWMOStatusCodes = XLATE('WM_OUT',WMOutKeys,'CURR_STATUS','X') WMOMUBoxes = XLATE('WM_OUT',WMOutKeys,'MAKEUP_BOX','X') WMOStatusCodes = '' FOR I = 1 TO COUNT(RawWMOStatusCodes,@VM) + (RawWMOStatusCodes NE '') IF WMOMUBoxes<1,I> NE 1 THEN WMOStatusCodes<1,-1> = RawWMOStatusCodes<1,I> NEXT I IF INDEX(WMOStatusCodes,'RTS',1) THEN Result = 'RTS' ;* If any outbound box is RTS then WO_STEP status is also RTS RETURN END WMOTestString = WMOStatusCodes SWAP 'SHIP' WITH '' IN WMOTestString SWAP 'RTU' WITH '' IN WMOTestString SWAP 'MT' WITH '' IN WMOTestString SWAP 'REJ' WITH '' IN WMOTestString ;* Entire cassette rejected CONVERT @VM TO '' IN WMOTestString IF WMOTestString = '' THEN Result = 'COMP' ; ;* All items either Shipped, Complete, Cancelled or Rejected RETURN END WMOTestString = WMOStatusCodes SWAP 'RTB' WITH '' IN WMOTestString CONVERT @VM TO '' IN WMOTestString IF WMOTestString = '' THEN Result = 'RX' ;* All boxes are still at Ready To Build (No RDS's unloaded yet RETURN END Result = 'INPR' RETURN END IF RDSNos = '' THEN Result = 'NEW' RETURN END RDSStatusCodes = XLATE('RDS',RDSNos,'CURR_STATUS','X') Status = '' TestString = RDSStatusCodes CONVERT @VM TO '' IN TestString IF TestString = '' THEN * No RDS records on file WONo = WOStepKey[1,'*'] OrgWOStatus = XLATE('WO_LOG',WONo,WO_LOG_STATUS$,'X') IF OrgWOStatus = 'C' THEN Result = 'COMP' END ELSE WOStep = FIELD(WOStepKey,'*',2,1) IF WOStep = 1 THEN CassNos = XLATE('WO_LOG',WOStepKey[1,'*'],WO_LOG_CASS_NO$,'X') IF CassNos<1,1> = '' THEN PSNSuppliedBy = XLATE('PROD_SPEC',WOStepRec,'SUB_SUPPLIED_BY','X') IF PSNSuppliedBy = 'L' THEN Result = 'RTP' ;* Ready to Pick END ELSE Result = 'AWM' ;* Awaiting Material END END ELSE Result = 'RX' ;* Received END END ELSE Result = '' END END RETURN END IF INDEX(RDSStatusCodes,'RTS',1) THEN Result = 'RTS' ; Return ;* Any cassette is RTS END TestString = RDSStatusCodes SWAP 'RX' WITH '' IN TestString SWAP 'PREC' WITH '' IN TestString SWAP 'PREI' WITH '' IN TestString CONVERT @VM TO '' IN TestString IF TestString = '' THEN Result = 'RX' ; Return ;* Ready to Process TestString = RDSStatusCodes SWAP 'SHIP' WITH '' IN TestString CONVERT @VM TO '' IN TestString IF TestString = '' THEN Result = 'COMP' ; Return ;* Shipped Complete TestString = RDSStatusCodes SWAP 'STEP' WITH '' IN TestString CONVERT @VM TO '' IN TestString IF TestString = '' THEN Result = 'COMP' ; Return ;* Step Complete TestString = RDSStatusCodes SWAP 'SHIP' WITH '' IN TestString SWAP 'COMP' WITH '' IN TestString SWAP 'CANC' WITH '' IN TestString SWAP 'REJ' WITH '' IN TestString ;* Entire cassette rejected CONVERT @VM TO '' IN TestString IF TestString = '' THEN Result = 'COMP' ; Return ;* All items either Shipped, Complete, Cancelled or Rejected IF INDEX(RDSStatusCodes,'SHIP',1) THEN Result = 'SHIP' ; Return BEGIN CASE CASE INDEX(RDSStatusCodes,'PRE',1) ; Result = 'INPR' CASE INDEX(RDSStatusCodes,'PSTC',1) ; Result = 'INPR' CASE INDEX(RDSStatusCodes,'PSTI',1) ; Result = 'INPR' CASE INDEX(RDSStatusCodes,'POST',1) ; Result = 'INPR' CASE INDEX(RDSStatusCodes,'HOLD',1) ; Result = 'INPR' CASE INDEX(RDSStatusCodes,'SPEC',1) ; Result = 'INPR' CASE INDEX(RDSStatusCodes,'NCR',1) ; Result = 'INPR' CASE INDEX(RDSStatusCodes,'INPR',1) ; Result = 'INPR' CASE 1 ; Result = 'Unknown' END CASE * StaticCurrStatus = WOStepRec * * If Result NE StaticCurrStatus then * // Log the discrepancy * WONo = WOStepKey[1,'*'] * LogData = '' * LogData<1> = LoggingDTM * LogData<2> = @User4 * LogData<3> = WONo * LogData<4> = Result * LogData<5> = StaticCurrStatus * Logging_Services('AppendLog', objCurrStatusLog, LogData, @RM, @FM) * Work_Order_Services('PostWOStepUpdateRequest', WONo) * end RETURN * * * * * * * AdjStepRDSQtys: * * * * * * * WOStep = Parms[1,@RM] ;* This is an index into WOSteps which are keys to the WO_STEP table WOSteps = Parms[COL2()+1,@RM] IF WOStep = '' THEN RETURN IF WOSteps = '' THEN RETURN IF WOStep <= 1 THEN RETURN ;* This is only needed for Steps greater than 1 RDSNos = XLATE('WO_STEP',WOSteps<1,WOStep>,WO_STEP_RDS_KEY$,'X') ;* RDS Nos for selected WO Step PrevStepKey = WOSteps<1,WOStep - 1> PrevStepRDSNos = XLATE('WO_STEP',PrevStepKey,WO_STEP_RDS_KEY$,'X') ;* Get PREVIOUS step RDS keys PrevStepRDSStats = '' PSCnt = COUNT(PrevStepRDSNos,@VM) + (PrevStepRDSNos NE '') FOR I = 1 TO PSCnt PrevStepRDSStats<1,I> = obj_React_Run('RunStatus',PrevStepRDSNos<1,I>) ;* Get PREVIOUS Step Status codes NEXT I StepCompRdsNos = '' ;* List of previous step RDS's that are complete AdjRdsNos = '' ;* List of current step RDS's that need WAFERS_IN adjusted StepCompLine = 1 FOR I = 1 TO COUNT(PrevStepRDSNos,@VM) + (PrevStepRDSNos NE '') PrevStepRDSStat = PrevStepRDSStats<1,I> IF (PrevStepRDSStat = 'COMP') THEN StepCompRdsNos<1,StepCompLine> = PrevStepRDSNos<1,I> AdjRdsNos<1,StepCompLine> = RDSNos<1,I> StepCompLine += 1 END NEXT I IF AdjRdsNos = '' THEN Result = '' RETURN END *obj_RDS('AdjStepWafersIn',StepCompRdsNos:@RM:AdjRdsNos) ;* DEAD 11/5/2008 Resurrected on 11/17 JCH Result = AdjRdsNos ;* Return Current step RDSNos that are ready for labels RETURN