COMPILE FUNCTION obj_RDS(Method,Parms) #pragma precomp SRP_PreCompiler /* Methods for RDS table 08/21/2004 JCH - Initial Coding Properties: Methods: Create(DataStruct) ;* Create new record */ DECLARE FUNCTION Get_Status, Msg, Utility, obj_Tables, NextKey, obj_WO_Verify, obj_Prod_Spec, Send_Dyn, obj_RDS_Makeup DECLARE FUNCTION obj_RDS2, obj_RDS_Test, obj_WO_Mat, obj_Clean_Insp, obj_PRS_Prop, Database_Services, RDS_Services DECLARE FUNCTION Return_To_Fab_Services DECLARE FUNCTION Logging_Services, Environment_Services, Error_Services, Signature_Services, Lot_Services, Supplement_Services DECLARE SUBROUTINE Set_Status, Msg, obj_Tables, Send_Dyn, obj_WO_Step, obj_RDS_Layer, obj_RDS_Test, obj_WM_In DECLARE SUBROUTINE Btree.Extract, RDS_React_Run, Environment_Services, Logging_Services, Error_Services, Send_Info DECLARE SUBROUTINE SRP_Stopwatch, Database_Services, Lot_Services, Supplement_Services $INSERT MSG_EQUATES $INSERT WO_VERIFY_EQU $INSERT WO_LOG_EQUATES $INSERT RDS_EQUATES $INSERT RDS_MAKEUP_EQU $INSERT RDS_LAYER_INFO_EQU $INSERT QUOTE_SPEC_EQU $INSERT PROD_SPEC_EQUATES $INSERT SCHEDULE_EQU $INSERT WO_STEP_EQU $INSERT NCR_EQU $INSERT WO_MAT_EQUATES $INSERT REACT_RUN_EQUATES $INSERT CLEAN_INSP_EQUATES $INSERT EPI_PART_EQUATES $INSERT WO_REACT_EQUATES $INSERT PRS_LAYER_EQU ;* Used to return obj_Prod_Spec values $INSERT LOGICAL ErrTitle = 'Error in Stored Procedure "obj_RDS"' ErrorMsg = '' LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\RDS' LogDate = Oconv(Date(), 'D4/') LogTime = Oconv(Time(), 'MTS') LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' RDS Log.csv' Headers = 'Logging DTM' : @FM : 'User' : @FM : 'RDS Key ID' : @FM : 'Notes' objLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, Comma$, Headers, '', False$, False$) LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\RemoveMetrology' LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : '.log' Headers = 'Logging DTM' : @FM : 'Results' ColumnWidths = 20 : @FM : 50 objLog2 = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, ' ', Headers, ColumnWidths, False$, False$) LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WO_LOG' LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' Release Log.csv' Headers = 'Logging DTM' : @FM : 'User' : @FM : 'Work Order No' : @FM : 'Notes' objReleaseLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, COMMA$, Headers, '', False$, False$) LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\RDS' LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' WAFERS_IN.csv' Headers = 'Logging DTM' : @FM : 'RDS Key ID' : @FM : 'WAFERS_IN' objWafersLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, ',', Headers, '', False$, False$) LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\RDS' LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' RDS_TEST_DELETE.csv' Headers = 'Logging DTM' : @FM : 'RDS Test Key ID' : @FM : 'Message' objRDSTestDeleteLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, ',', 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 = 'CurrStatus' ; GOSUB CurrStatus CASE Method = 'Create' ; GOSUB Create CASE Method = 'VerifySpecInfo' ; GOSUB VerifySpecInfo * CASE Method = 'Update' ; GOSUB Update CASE Method = 'SchedWfrQty' ; GOSUB SchedWfrQty CASE Method = 'TestRejWfrQty' ; GOSUB TestRejWfrQty CASE Method = 'MUSrcWfrQty' ; GOSUB MUSrcWfrQty CASE Method = 'MUDestWfrQty' ; GOSUB MUDestWfrQty CASE Method = 'RemMUWafers' ; GOSUB RemMUWafers CASE Method = 'WafersOut' ; GOSUB WafersOut CASE Method = 'YieldOutThruput' ; GOSUB YieldOutThruput CASE Method = 'WafersPerHour' ; GOSUB WafersPerHour CASE Method = 'AddShip' ; GOSUB AddShip CASE Method = 'RemShip' ; GOSUB RemShip CASE Method = 'RefreshRDSSpec' ; GOSUB RefreshRDSSpec CASE Method = 'WMInKeys' ; GOSUB WMInKeys CASE Method = 'WMOutKeys' ; GOSUB WMOutKeys CASE Method = 'SetSchedWfrQty' ; GOSUB SetSchedWfrQty CASE Method = 'MU_ADE_Reads' ; GOSUB MU_ADE_Reads CASE Method = 'MetPropFlag' ; GOSUB MetPropFlag CASE 1 Result = obj_RDS2(Method,Parms) END CASE IF ErrorMsg NE '' THEN Set_Status(-1,ErrTitle:@SVM:ErrorMsg) END RETURN Result * * * * * * * CurrStatus: * * * * * * * IF NOT(ASSIGNED(RDSNos)) THEN RDSNos = Parms[1,@RM] RDSRec = Parms[COL2()+1,@RM] END IF RDSNos = '' THEN RETURN ;* 9/9/2014 JCH *** This routine has multiple Keys in with only a single record **** AWS__T! needs to be fixed ReturnVals = '' RDSCnt = COUNT(RDSNos,@VM) + (RDSNos NE '') FOR R = 1 TO RDSCnt OpenRTF = Return_To_Fab_Services('GetOpenReturnToFabRecordIdByCassId', RDSNos) IF OpenRTF NE '' THEN ReturnVals<1,R> = 'RTF' ;* Open RTF on RDS * GOTO StatusHere END NCRStatuses = XLATE('NCR',RDSRec,7,'X') IF INDEX(NCRStatuses,'O',1) THEN ReturnVals<1,R> = 'NCR' ;* Open NCR on RDS * GOTO StatusHere END * ROTR inspection failure check -> Set status to PSTC (PostCleans) RotrAction = XLATE('RDS',RDSNos,'ROTR_ACTION','X') IF RotrAction = 'F' Then ;* Drive the CURR_STATUS to PostEpi Clean if the ROTR fails ReturnVals<1,R> = 'PSTC' GOTO StatusHere END * Check for out of spec OutOfSpec = 0 ; OutOfSpecThick = '' OutOfSpecRes = '' LSKeys = RDSRec MetOutOfSpec = SUM(XLATE('RDS_LAYER',LSKeys,'TEST_OUT_OF_SPEC','X')) ;* Updated for Metrology update 4/16/2006 JCH IF MetOutOfSpec > 0 THEN ;* Added check for F(ailed) ROTR_ACTION value. ReturnVals<1,R> = 'SPEC' ;* Run is out of spec * GOTO StatusHere END * Check for Metrology Complete MetComplete = SUM(XLATE('RDS_LAYER',LSKeys,'TEST_MET_COMPLETE','X')) ;* Added with DKK 11/3/2015 JCH IF NOT(MetComplete) THEN ;* Added check for F(ailed) ROTR_ACTION value. ReturnVals<1,R> = 'MET' ;* Run is missing metrology * GOTO StatusHere END WONo = RDSRec CassNo = RDSRec WOStepKey = RDSRec WOMatRec = XLATE('WO_MAT',WONo:'*':CassNo,'','X') WOStep = FIELD(WOStepKey,'*',2) RDSKeys = '' RSCnt = 0 RunSigProfs = '' RunSignatures = '' RunSigDTMs = '' WOMatKey = WONo:'*':CassNo SigArray = Signature_Services('GetSigProfile', WOMatKey) RunSigProfs = SigArray<1> RunSignatures = SigArray<2> ProcessStart = 0 ProcessComp = 0 LOOP RunSignature = RunSignatures<1,1> RunSigProf = RunSigProfs<1,1> UNTIL RunSignature = '' ProcessStart = 1 RunSignatures = DELETE(RunSignatures,1,1,0) RunSigProfs = DELETE(RunSigProfs,1,1,0) REPEAT IF RunSignature = '' AND RunSigProf = '' AND ProcessStart = 1 THEN ReturnVals<1,R> = 'COMP' GOTO StatusHere END ELSE ReturnVals<1,R> = RunSigProf[2,20] GOTO StatusHere END * EpiPRO specific (unload) TestPockets = RDSRec TestOutCassNos = RDSRec CONVERT @VM TO '' IN TestPockets CONVERT @VM TO '' IN TestOutCassNos IF TestPockets NE '' AND TestOutCassNos NE '' THEN ReturnVals<1,R> = 'COMP' ;* EpiPRO RDS is complete with wafer unload END StatusHere: NEXT R Result = ReturnVals RETURN * * * * * * * Create: * * * * * * * WONo = Parms[1,@RM] WOStep = Parms[COL2()+1,@RM] LastStep = Parms[COL2()+1,@RM] CassNo = Parms[COL2()+1,@RM] QuoteNo = Parms[COL2()+1,@RM] OrderNo = Parms[COL2()+1,@RM] OrderItem = Parms[COL2()+1,@RM] CustNo = Parms[COL2()+1,@RM] PONo = Parms[COL2()+1,@RM] PS_No = Parms[COL2()+1,@RM] SubSuppliedBy = Parms[COL2()+1,@RM] SubPreClean = Parms[COL2()+1,@RM] SubPostClean = Parms[COL2()+1,@RM] SchedDt = Parms[COL2()+1,@RM] LotNo = Parms[COL2()+1,@RM] CustPartNo = Parms[COL2()+1,@RM] WaferQty = Parms[COL2()+1,@RM] SubPartNo = Parms[COL2()+1,@RM] QXJFlag = Parms[COL2()+1,@RM] SubVendCd = Parms[COL2()+1,@RM] ErrorMsg = '' IF WONo = '' THEN ErrorMsg := 'Null Parameter "WONo" passed to routine. (':Method:')' IF WOStep = '' THEN ErrorMsg := 'Null Parameter "WOStep" passed to routine. (':Method:')' IF CassNo = '' THEN ErrorMsg := 'Null Parameter "CassNo" passed to routine. (':Method:')' IF CustNo = '' THEN ErrorMsg := 'Null Parameter "CustNo" passed to routine. (':Method:')' IF PS_No = '' THEN ErrorMsg := 'Null Parameter "PS_No" passed to routine. (':Method:')' IF SchedDt = '' THEN ErrorMsg := 'Null Parameter "SchedDt" passed to routine. (':Method:')' IF LotNo = '' THEN ErrorMsg := 'Null Parameter "LotNo" passed to routine. (':Method:')' IF WaferQty = '' THEN ErrorMsg := 'Null Parameter "WaferQty" passed to routine. (':Method:')' If ErrorMsg NE '' then Logging_Services('AppendLog', objLog, LoggingDTM : ',' : @USER4 : ',' : 'RDSKey Not Yet Assigned' : ',' : 'Error occured in OBJ_RDS(CREATE): ' : ErrorMsg) Return end RDSNo = NextKey('RDS') errCode = '' If RDSNo EQ '' or RDSNo EQ 0 or Error_Services('HasError') or Get_Status(errCode) then Logging_Services('AppendLog', objLog, LoggingDTM : ',' : @USER4 : ',' : RDSNo : ',' : 'NextKey(RDS) returned NULL or 0 for KeyID') Error_Services('Add', 'Error retrieving next RDS key from NextKey("RDS"). ' : Error_Services('GetMessage')) Result = RDSNo return end // Create new record RDSRec = '' RDSRec = @USER4 RDSRec = Date() RDSRec = Time() RDSRec = 'C' ;* Received RDSRec = WONo RDSRec = WONo:'*':WOStep RDSRec = CassNo RDSRec = QuoteNo RDSRec = OrderNo RDSRec = OrderItem RDSRec = CustNo RDSRec = PONo RDSRec = PS_No RDSRec = SchedDt RDSRec = LotNo RDSRec = CustPartNo RDSRec = WaferQty RDSRec = SubPartNo RDSRec = LastStep RDSRec = SubSuppliedBy RDSRec = SubPreClean RDSRec = SubPostClean IF CassNo EQ 1 THEN WOVStatus = 'O' ;* Open status (?) WOVNotes = '' WOVNo = obj_WO_Verify('Create',RDSNo:@RM:WOVStatus:@RM:WOVNotes) ;* Create a WO_Verify record on 1st run order RDSRec = WOVNo ;* Add pointer to RDS record IF Get_Status(errCode) THEN Logging_Services('AppendLog', objLog, LoggingDTM : ',' : @USER4 : ',' : RDSNo : ',' : 'Error calling OBJ_WO_VERIFY within OBJ_RDS(CREATE)') end End PSRec = XLATE('PROD_SPEC',PS_No,'','X') ReactorType = PSRec ;* This isn't used anwhere in the program 8/27/2014 JCH RDSRec = PSRec ;* 3/25/2013 jch RDSRec = XLATE('PROD_SPEC',PS_No,'SPEC_TYPE','X') LayerSpecs = obj_Prod_Spec('GetLayerProp',PS_No:@RM:@RM:1) ;* Returns specs for all layers in internal format * LayerSpecs is @RM between layers, @FM between fields, LayerSet ID is in the first Field and needs to peeled off * before the equates match up correctly * Prod_Spec table has layer specs all in one field * RDS has First layer stuff in individual fields and then has 2 and 3 shoved into Field 33 (Layer Info) LayerSpec = FIELD(LayerSpecs,@RM,1) ;* Take the first Layer LayerSet = FIELD(LayerSpec,@FM,1) ;* Not used here but shown for clarity LayerSpec = FIELD(LayerSpec,@FM,2,99) ;* LayerSpec without the LayerSet RecipeNo = LayerSpec RecipeRec = XLATE('RECIPE',RecipeNo,'','X') ;* This used in 2nd and 3rd layer stuff (in error it appears) RDSRec = LayerSpec ;* JCH 2/27/2006 IF QXJFlag THEN RDSRec = 0 ;* And here a couple of minor cluster operations END IF CustNo = '621' AND CassNo = 1 THEN RDSRec = 0 END NoCombinedLayerFlag = '' FOR I = 1 TO COUNT(LayerSpecs,@RM) + (LayerSpecs NE '') LayerSpec = FIELD(LayerSpecs,@RM,I) ;* Take the Ith Layer LayerSet = FIELD(LayerSpec,@FM,1) LayerSpec = FIELD(LayerSpec,@FM,2,99) ;* LayerSpec without the LayerSet IF LayerSet = I THEN NoCombinedLayerFlag = 1 ELSE NoCombinedLayerFlag = 0 obj_RDS_Layer('Create',RDSNo:@RM:LayerSet:@RM:PS_No:@RM:NoCombinedLayerFlag) RDSRec = RDSNo:'*':LayerSet ;* Added 4/17/2006 JCH obj_RDS_Test('Create',RDSNo:@RM:LayerSet:@RM:PS_No) NEXT I obj_Tables('WriteRec','RDS':@RM:RDSNo:@RM:@RM:RDSRec) IF Get_Status(errCode) THEN Logging_Services('AppendLog', objLog, LoggingDTM : ',' : @USER4 : ',' : RDSNo : ',' : 'Error writing new RDS record. Error code: ':errCode) Result = '' END ELSE NewLotId = Lot_Services('CreateNewLot', 'RDS', '', WaferQty, SubPartNo, LotNo, SubVendCd, @User4, '', RDSNo) If Rds_Services('IsEpiPro', RDSNo) then Lot_Services('AddLotOperationIntoSequence', NewLotId, 'RDS_CREATE', 1, False$) Lot_Services('AddLotOperationIntoSequence', NewLotId, 'PRE_EPI', 2, False$) Lot_Services('AddLotOperationIntoSequence', NewLotId, 'REACTOR_RUN', 3, False$) Lot_Services('AddLotOperationIntoSequence', NewLotId, 'POST_EPI', 4, False$) Lot_Services('AddLotOperationIntoSequence', NewLotId, 'RDS_CLOSE', 5, False$) Lot_Services('StartLot', NewLotId, @User4) ; // LOT_START event and move in to RDS_CREATE operation Lot_Services('MoveOutLot', NewLotId, @User4) ; // Move out of RDS_CREATE operation Lot_Services('MoveInLot', NewLotId, @User4) ; // Move in to PRE_EPI operation end Result = RDSNo // Automatically Apply Supplement // If first cassette in work order, then there is no supplement in place, therefore skip this step. If RDSRec GT 1 then WoStepKey = RDSRec WoStepRec = Database_Services('ReadDataRow', 'WO_STEP', WoStepKey) If Error_Services('NoError') then RDSKeyCount = Dcount(WoStepRec, @VM) LastRDSKey = WoStepRec LastRDSRec = Database_Services('ReadDataRow', 'RDS', LastRDSKey) If Error_Services('NoError') then HasSupplement = Supplement_Services('HasSupplements', 'RDS', LastRDSKey, '') If HasSupplement then Supplement_Services('CopySupplementsToNewLot', 'RDS', LastRDSKey, RDSNo) end end else Logging_Services('AppendLog', objLog, LoggingDTM : ',' : @USER4 : ',' : RDSNo : ',' : 'Error automatically applying supplement to new RDS.') end end else Logging_Services('AppendLog', objLog, LoggingDTM : ',' : @USER4 : ',' : RDSNo : ',' : 'Error automatically applying supplement to new RDS.') end end END RDS_React_Run(RDSNo) RETURN * * * * * * * VerifySpecInfo: * * * * * * * RDSNo = Parms[1,@RM] RDSRec = Parms[COL2()+1,@RM] IF NOT(ASSIGNED(RDSNo)) THEN ErrorMsg = 'Unassigned Parm "RDSNo" passed to routine. (':Method:')' IF NOT(ASSIGNED(RDSRec)) THEN RDSRec = '' IF ErrorMsg NE '' THEN RETURN IF RDSNo = '' THEN RETURN ;* used in dictionary - no error messages IF RDSRec = '' THEN RDSRec = XLATE('RDS',RDSNo,'','X') IF RDSRec = '' THEN RETURN PS_No = RDSRec PSRec = XLATE('PROD_SPEC',PS_No,'','X') LayerSpecs = obj_Prod_Spec('GetLayerProp',PS_No) ;* Returns specs for all layers IF RDSRec NE PSRec THEN Matches = 0 LayerSpec = FIELD(LayerSpecs,@RM,1) ;* Take the first Layer LayerSet = FIELD(LayerSpec,@FM,1) ;* Not used here but shown for clarity LayerSpec = FIELD(LayerSpec,@FM,2,99) ;* LayerSpec without the LayerSet RecipeNo = LayerSpec RecipeRec = XLATE('RECIPE',RecipeNo,'','X') ;* This used in 2nd and 3rd layer stuff (in error it appears) ErrNum = 1 * This section is here because the targets calculated in the existing SCHEDULE*WRITE event are not done correctly * There is a last decimal point difference in the calculation that causes a mismatch whenever a remainder of .5 * is generated during the division by 2. WRITE event code doesn't drop the remainder like it should * This section calculates the targets based on the min and max on the RDS. We can remove this after the WRITE * event is replaced and the data has had enough time to move through the system. * JCH 8/23/2004 RDSConMin = RDSRec ;* Record in internal format RDSConMax = RDSRec ;* Record in internal format GOSUB CalcConTarget ;* Returns RDSTarget in internal format RDSResMin = RDSRec RDSResMax = RDSRec GOSUB CalcResTarget RDSThickMin = RDSRec RDSThickMax = RDSRec GOSUB CalcThickTarget IF OCONV(RDSRec,'MS21') NE LayerSpec THEN ErrNum = -12 IF OCONV(RDSRec,'MS21') NE LayerSpec THEN ErrNum = -13 IF RDSRec NE LayerSpec THEN ErrNum = -14 IF OCONV(RDSConTarget,'MS21') NE LayerSpec THEN ErrNum = -15 IF OCONV(RDSRec,'MD3') NE LayerSpec THEN ErrNum = -16 IF OCONV(RDSRec,'MD3') NE LayerSpec THEN ErrNum = -17 IF RDSRec NE LayerSpec THEN ErrNum = -18 IF OCONV(RDSResTarget,'MD3') NE LayerSpec THEN ErrNum = -19 IF OCONV(RDSRec,'MD2') NE LayerSpec THEN ErrNum = -110 IF OCONV(RDSRec,'MD2') NE LayerSpec THEN ErrNum = -111 IF RDSRec NE LayerSpec THEN ErrNum = -112 IF OCONV(RDSThickTarget,'MD2') NE LayerSpec THEN ErrNum = -113 RDSLayerInfo = RDSRec ;* All Layers beyond the first FOR I = 2 TO COUNT(LayerSpecs,@RM) + (LayerSpecs NE '') LayerSpec = FIELD(LayerSpecs,@RM,I) ;* Take the Ith Layer LayerSet = LayerSpec<1> LayerSpec = FIELD(LayerSpec,@FM,2,99) ;* LayerSpec without the LayerSet thisLayerInfo = FIELD(RDSLayerInfo,CHAR(248),I-1,1) ;* L2 & 2 from the RDS * Calculate RDS target using the same algorithm used in obj_Prod_Spec RDSConMin = ICONV(thisLayerInfo<1,RLConMin$,1>,'MS') RDSConMax = ICONV(thisLayerInfo<1,RLConMax$,1>,'MS') GOSUB CalcConTarget IF RDSConMin AND RDSConMax THEN IF RDSConMin = RDSConMax THEN RDSConTarget = RDSConMin END ELSE Delta = INT((RdsConMax-RDSConMin)/2) RDSConTarget = OCONV(RDSConMin + Delta,'MS21') END END ELSE RDSConTarget = '' END IF thisLayerInfo<1,RLRecipeNo$> NE RecipeNo THEN ErrNum = '-':I:1 IF thisLayerInfo<1,RLConMin$,1> NE LayerSpec THEN ErrNum = '-':I:2 IF thisLayerInfo<1,RLConMax$,1> NE LayerSpec THEN ErrNum = '-':I:3 IF thisLayerInfo<1,RLConUnits$> NE LayerSpec THEN ErrNum = '-':I:4 IF RDSConTarget NE LayerSpec THEN ErrNum = '-':I:5 IF OCONV(thisLayerInfo<1,RLResMin$>,'MD3') NE LayerSpec THEN ErrNum = '-':I:6 IF OCONV(thisLayerInfo<1,RLResMax$>,'MD3') NE LayerSpec THEN ErrNum = '-':I:7 IF thisLayerInfo<1,RLResUnits$> NE LayerSpec THEN ErrNum = '-':I:8 IF OCONV(thisLayerInfo<1,RLResTarget$>,'MD3') NE LayerSpec THEN ErrNum = '-':I:9 IF OCONV(thisLayerInfo<1,RLThickMin$>,'MD2') NE LayerSpec THEN ErrNum = '-':I:10 IF OCONV(thisLayerInfo<1,RLThickMax$>,'MD2') NE LayerSpec THEN ErrNum = '-':I:11 IF thisLayerInfo<1,RLThickUnits$> NE LayerSpec THEN ErrNum = '-':I:12 IF OCONV(thisLayerInfo<1,RLThickTarget$>,'MD2') NE LayerSpec THEN ErrNum = '-':I:13 NEXT I SchedNo = RDSRec OrdNo = RDSRec Result = ErrNum:@FM:'Sched No: ':SchedNo:@FM:' Order No: ':OrdNo RETURN * * * * * * * SchedWfrQty: * * * * * * * IF NOT(ASSIGNED(thisRDSNo)) THEN thisRDSNo = Parms[1,@RM] END IF NOT(ASSIGNED(thisRDSRec)) THEN thisRDSRec = Parms[COL2()+1,@RM] END IF thisRDSNo = '' THEN RETURN IF thisRDSRec = '' THEN thisRDSRec = XLATE('RDS',thisRDSNo,'','X') IF thisRDSRec = '' THEN RETURN SchedNo = thisRDSRec SchedRec = XLATE('SCHEDULE',SchedNo,'','X') LOCATE thisRDSNo IN SchedRec USING @VM SETTING Pos THEN Result = SchedRec END RETURN * * * * * * * TestRejWfrQty: * * * * * * * IF NOT(ASSIGNED(thisRDSNo)) THEN thisRDSNo = Parms[1,@RM] END IF NOT(ASSIGNED(thisRDSRec)) THEN thisRDSRec = Parms[COL2()+1,@RM] END IF thisRDSNo = '' THEN RETURN IF thisRDSRec = '' THEN thisRDSRec = XLATE('RDS',thisRDSNo,'','X') IF thisRDSRec = '' THEN RETURN Tmp = 0 Tmp += XLATE('RDS',thisRDSNo,'TOT_REJ','X') TestKeys = XLATE('RDS_LAYER',thisRDSRec,3,'X') ProdTestWfrs = obj_RDS_Test('ProdTestCount',TestKeys) Tmp += ProdTestWfrs Tmp += thisRDSRec ;* <97> Tmp += thisRDSRec ;* <221> Result = Tmp RETURN * * * * * * * MUSrcWfrQty: * * * * * * * IF NOT(ASSIGNED(thisRDSNo)) THEN thisRDSNo = Parms[1,@RM] END IF NOT(ASSIGNED(thisRDSMakeupRec)) THEN thisRDSMakeupRec = Parms[COL2()+1,@RM] END IF thisRDSNo = '' THEN RETURN IF thisRDSMakeupRec = '' THEN thisRDSMakeupRec = XLATE('RDS_MAKEUP',thisRDSNo,'','X') IF thisRDSMakeupRec NE '' THEN Tmp = 0 FOR I = 1 TO COUNT(thisRDSMakeupRec,@VM) + (thisRDSMakeupRec NE '') IF thisRDSMakeupRec NE '' THEN Tmp += 1 NEXT I END RETURN * * * * * * * MUDestWfrQty: * * * * * * * IF NOT(ASSIGNED(thisRDSNo)) THEN thisRDSNo = Parms[1,@RM] END IF NOT(ASSIGNED(thisRDSMakeupRec)) THEN thisRDSMakeupRec = Parms[COL2()+1,@RM] END IF thisRDSNo = '' THEN RETURN IF thisRDSMakeupRec = '' THEN thisRDSMakeupRec = XLATE('RDS_MAKEUP',thisRDSNo,'','X') IF thisRDSMakeupRec NE '' THEN Tmp = 0 FOR I = 1 TO COUNT(thisRDSMakeupRec,@VM) + (thisRDSMakeupRec NE '') IF thisRDSMakeupRec NE '' THEN Tmp += 1 NEXT I Result = Tmp END RETURN * * * * * * * WafersOut: * * * * * * * IF NOT(ASSIGNED(RDSNo)) THEN RDSNo = Parms[1,@RM] IF NOT(ASSIGNED(RDSRec)) THEN RDSRec = Parms[COL2()+1,@RM] IF NOT(ASSIGNED(Filter)) THEN Filter = Parms[COL2()+1,@RM] IF NOT(ASSIGNED(NoMU)) THEN NoMU = Parms[COL2()+1,@RM] ;* NoMU = No Makeup Wafer counts IF RDSNo = '' THEN RETURN IF RDSRec = '' THEN RDSRec = XLATE('RDS',RDSNo,'','X') VerifyQty = RDSRec WafersIn = RDSRec CassWfrQty = RDSRec NCRKeys = RDSRec If Not(Num(WafersIn)) then // Log the WafersIn value LogData = '' LogData<1> = LoggingDTM LogData<2> = RDSNo LogData<3> = WafersIn Logging_Services('AppendLog', objWafersLog, LogData, @RM, @FM) WafersIn = WafersIn<1, 1, 1> end WONo = RDSRec CassNo = RDSRec MUWafersIn = XLATE('WO_MAT',WONo:'*':CassNo,'CURR_WFR_CNT_MU_ADDED','X') MUWafersRemoved = XLATE('WO_MAT',WONo:'*':CassNo,'CURR_WFR_CNT_USED_MU','X') CurrWfrCnt = XLATE('WO_MAT',WONo:'*':CassNo,'CURR_WFR_CNT','X') ;* Added 5/10/2011 JCH * * * * * * * * * * * * * * IF NCRKeys NE '' THEN * This happens when a box of wafers is bad upon opening in the cleanroom * An NCR rejecting the entire cassette is generated and the box is returned to shipping/receiving NCRStatuses = XLATE('NCR',NCRKeys,NCR_STATUS$,'X') ;* Added this section 09/17/2005 JCH - J.C. Henry & Co., Inc. IF INDEX(NCRStatuses,'O',1) ELSE * All NCR's are closed RejectQty = XLATE('NCR',NCRKeys,'REJ_CNT','X') * 11/17/22 - DJS/JRO - Updated the following line to check if CurrWfrCnt is equal to zero to prevent OI from * erroneously returning zero. Consider refactoring WafersOut subroutine. IF ( ( (SUM(RejectQty) = CassWfrQty) or (SUM(RejectQty) = WafersIn) ) and (CurrWfrCnt EQ 0) ) THEN Result = 0 RETURN end END END TotRejects = SUM(XLATE('NCR',NCRKeys,'REJ_CNT','X')) TestKeys = XLATE('RDS_LAYER',RDSRec,3,'X') TWProd = obj_RDS_Test('ProdTestCount',TestKeys) SRPBillable = RDSRec IF NoMU THEN Added = WafersIn Removed = TotRejects + TWProd + SRPBillable END ELSE Added = WafersIn + MUWafersIn Removed = TotRejects + TWProd + SRPBillable + MUWafersRemoved END IF Filter NE '' THEN BEGIN CASE CASE Filter = 'Q' SignedOff = RDSRec NE '' CASE Filter = 'P' SignedOff = RDSRec NE '' CASE 1 SignedOff = '' ;* This is an error END CASE END ELSE SignedOff = (RDSRec NE '') END IF (Removed <= Added) AND (Added NE 0) AND SignedOff THEN ;* Added SignedOff Flag for QA on 09/21/2005 JCH - J.C. Henry & Co., Inc. Result = Added - Removed IF Result NE CurrWfrCnt THEN Result = CurrWfrCnt END ELSE Result = '' END RETURN **************** YieldOutThruput: **************** RDSNo = Parms[1,@RM] RDSRec = Parms[COL2()+1,@RM] YieldOut = 0 If (RDSNo NE '') then If (RDSRec = '') then RDSRec = XLATE('RDS',RDSNo,'','X') end // Number of wafers out = Number of wafers in WafersOut = RDSRec // Calculate the total number of rejected wafers CustScrap = Xlate('RDS', RDSNo, 'CUST_TOT_REJ', 'X') IFXScrap = Xlate('RDS', RDSNo, 'LSL_TOT_REJ', 'X') TotalRejects = CustScrap + IFXScrap // Determine the number of production test wafers TestKeys = XLATE('RDS_LAYER',RDSRec, 3, 'X') TWProd = obj_RDS_Test('ProdTestCount', TestKeys) YieldOut = WafersOut - TotalRejects - TWProd end Result = YieldOut return * * * * * * * RemMUWafers: * * * * * * * RETURN * * * * * * * WafersPerHour: * * * * * * * RDSNos = Parms[1,@RM] IF NOT(ASSIGNED(RDSNos)) THEN RDSNos = '' IF RDSNos = '' THEN RETURN HoursTotal = 0 WafersInTotal = 0 TargetTotal = 0 RDSCount = COUNT(RDSNos,@VM) + (RDSNos NE '') FOR I = 1 TO RDSCount RDSRec = XLATE('RDS',RDSNos<1,I>,'','X') LoadDTM = ICONV(OCONV(RDSRec,'D4/'):' ':OCONV(RDSRec,'MTS'),'DT') UnLoadDTM = ICONV(OCONV(RDSRec,'D4/'):' ':OCONV(RDSRec,'MTS'),'DT') WafersIn = RDSRec If Not(Num(WafersIn)) then // Log the WafersIn value LogData = '' LogData<1> = LoggingDTM LogData<2> = RDSNo LogData<3> = WafersIn Logging_Services('AppendLog', objWafersLog, LogData, @RM, @FM) WafersIn = WafersIn<1, 1, 1> end IF UnloadDTM NE '' THEN HoursTotal += (UnloadDTM - LoadDTM)*24 WafersInTotal += WafersIn END MinutesPerWfr = XLATE('PROD_SPEC',RDSRec,96,'X') ;* MD3 format IF MinutesPerWfr = '' THEN MinutesPerWfr = ICONV('7.333','MD3') ;* Default per Todd to get us going with OEE WfrsPerHour = ICONV(ICONV(60,'MD3')/MinutesPerWfr,'MD2') ;* Should be in MD2 format TargetTotal += WfrsPerHour NEXT I IF HoursTotal = 0 THEN Actual = '' END ELSE Actual = OCONV(ICONV(WafersInTotal/HoursTotal,'MD2'),'MD2') ;* Average Actual Wafers per Hour END IF RDSCount = 0 THEN Target = '' END ELSE Target = OCONV(ICONV(TargetTotal/RDSCount,'MD0'),'MD2') ;* Average Target Wafers per Hour END Result = Actual:@RM:Target RETURN * * * * * * * AddShip: * * * * * * * ShipNo = Parms[1,@RM] RdsNo = Parms[COL2()+1,@RM] ShipDt = Parms[COL2()+1,@RM] ShipTm = Parms[COL2()+1,@RM] Reship = Parms[COL2()+1,@RM] If Reship EQ '' then Reship = False$ end IF NOT(ASSIGNED(RdsNo)) THEN ErrorMsg = 'Unassigned Parm "RdsNo" passed to routine. (':Method:')' IF NOT(ASSIGNED(ShipNo)) THEN ErrorMsg = 'Unassigned Parm "ShipNo" passed to routine. (':Method:')' IF NOT(ASSIGNED(ShipDt)) THEN ErrorMsg = 'Unassigned Parm "ShipDt" passed to routine. (':Method:')' IF NOT(ASSIGNED(ShipTm)) THEN ErrorMsg = 'Unassigned Parm "ShipTm" passed to routine. (':Method:')' IF ErrorMsg NE '' THEN RETURN IF RdsNo = '' THEN ErrorMsg = 'Null Parm "RdsNo" passed to routine. (':Method:')' IF ShipNo = '' THEN ErrorMsg = 'Null Parm "ShipNo" passed to routine. (':Method:')' IF ShipDt = '' THEN ErrorMsg = 'Null Parm "ShipDt" passed to routine. (':Method:')' IF ShipTm = '' THEN ErrorMsg = 'Null Parm "ShipTm" passed to routine. (':Method:')' IF ErrorMsg NE '' THEN RETURN thisShipDt = ICONV(ShipDt,'D') IF thisShipDt = '' THEN ErrorMsg = 'Invalid ShipDt ':QUOTE(ShipDt):' parameter passed to routine. (':Method:')' RETURN END thisShipTm = ICONV(ShipTm,'MT') IF thisShipTm = '' THEN ErrorMsg = 'Invalid ShipTm ':QUOTE(ShipTm):' parameter passed to routine. (':Method:')' RETURN END otParms = 'RDS':@RM:RdsNo RDSRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock IF RDSRec = '' OR RDSRec = ShipNo or Reship EQ True$ THEN RDSRec = ShipNo RDSRec = thisShipDt RDSRec = thisShipTm RDSRec = 'S' otParms = FIELDSTORE(otParms,@RM,4,0,RDSRec) obj_Tables('WriteRec',otParms) END ELSE obj_Tables('UnlockRec',otParms) ErrorMsg = "RDS was already shipped on shipment" :QUOTE(RDSRec): ". (" :Method: ")" END RETURN * * * * * * * RemShip: * * * * * * * ShipNo = Parms[1,@RM] RdsNo = Parms[COL2()+1,@RM] IF NOT(ASSIGNED(RdsNo)) THEN ErrorMsg = 'Unassigned Parm "RdsNo" passed to routine. (':Method:')' IF NOT(ASSIGNED(ShipNo)) THEN ErrorMsg = 'Unassigned Parm "ShipNo" passed to routine. (':Method:')' IF ErrorMsg NE '' THEN RETURN IF RdsNo = '' THEN ErrorMsg = 'Null Parm "RdsNo" passed to routine. (':Method:')' IF ShipNo = '' THEN ErrorMsg = 'Null Parm "ShipNo" passed to routine. (':Method:')' IF ErrorMsg NE '' THEN RETURN otParms = 'RDS':@RM:RdsNo RDSRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock IF RDSRec = ShipNo OR RDSRec = '' THEN RDSRec = '' RDSRec = '' RDSRec = '' RDSRec = 'R' otParms = FIELDSTORE(otParms,@RM,4,0,RDSRec) obj_Tables('WriteRec',otParms) END ELSE obj_Tables('UnlockRec',otParms) ErrorMsg = "Passed Ship No " :QUOTE(ShipNo): " doesn't match Ship No on RDS " :QUOTE(RdsNo): ". (" :Method: ")" END RETURN * * * * * * * RefreshRDSSpec: * * * * * * * RdsNos = Parms[1,@RM] IF RdsNos = '' THEN RETURN RTParms = 'RDS' LockedRDSNos = '' FOR I = 1 TO COUNT(RdsNos,@VM) + (RdsNos NE '') RdsNo = RdsNos<1,I> RTParms = FieldStore(RTParms, @RM, 2, 1, RdsNo) obj_Tables('LockRec',RTParms) IF Get_Status(errCode) THEN FOR N = 1 TO COUNT(LockedRDSNos,@VM) + (LockedRDSNos NE '') RTParms = FieldStore(RTParms, @RM, 2, 1, LockedRDSNos<1,N>) obj_Tables('UnlockRec',RTParms) ;* Unlock everything locked up to here NEXT N ErrorMsg = 'Unable to lock RDS ':QUOTE(RdsNo):' for update.' obj_Tables('UnlockRec',OTParms) RETURN END ELSE LockedRDSNos<1,-1> = RdsNo END NEXT I RDSTableVar = FIELD(RTParms,@RM,3) FOR N = 1 TO COUNT(LockedRDSNos,@VM) + (LockedRDSNos NE '') LockedRDSNo = LockedRDSNos<1,N> READ RDSRec FROM RDSTableVar,LockedRDSNo THEN PS_No = RDSRec PSRec = XLATE('PROD_SPEC',PS_No,'','X') RDSRec = PSRec RDSRec = XLATE('PROD_SPEC',PS_No,'SPEC_TYPE','X') LayerSpecs = obj_Prod_Spec('GetLayerProp',PS_No:@RM:@RM:1) ;* Returns specs for all layers * LayerSpecs is @RM between layers, @FM between fields, LayerSet ID is in the first Field and needs to peeled off * before the equates match up correctly * Prod_Spec table has layer specs all in one field * RDS has First layer stuff in individual fields and then has 2 and 3 shoved into Field 33 (Layer Info) LayerSpec = FIELD(LayerSpecs,@RM,1) ;* Take the first Layer LayerSet = FIELD(LayerSpec,@FM,1) ;* Not used here but shown for clarity LayerSpec = FIELD(LayerSpec,@FM,2,99) ;* LayerSpec without the LayerSet RecipeNo = LayerSpec RecipeRec = XLATE('RECIPE',RecipeNo,'','X') ;* This used in 2nd and 3rd layer stuff (in error it appears) * IF RecipeNo NE RDSRec THEN * RDSRec = RecipeNo * END RDSRec = LayerSpec RDSRec = LayerSpec RDSRec = LayerSpec RDSRec = LayerSpec RDSRec = LayerSpec RDSRec = LayerSpec RDSRec = LayerSpec RDSRec = LayerSpec RDSRec = LayerSpec RDSRec = LayerSpec RDSRec = LayerSpec RDSRec = LayerSpec LayerInfo = '' FOR I = 2 TO COUNT(LayerSpecs,@RM) + (LayerSpecs NE '') LayerSpec = FIELD(LayerSpecs,@RM,I) ;* Take the Ith Layer LayerSpec = FIELD(LayerSpec,@FM,2,99) ;* LayerSpec without the LayerSet thisLayerInfo = '' ;* Empty bucket to parse into thisLayerInfo<1,RLConMin$> = LayerSpec thisLayerInfo<1,RLConMax$> = LayerSpec thisLayerInfo<1,RLConUnits$> = LayerSpec thisLayerInfo<1,RLConTarget$> = LayerSpec thisLayerInfo<1,RLRecipeNo$> = RecipeNo ;* Copied from the original in the WRITE event of the Schedule window thisLayerInfo<1,RLThickRead$> = STR(@SVM,16) thisLayerInfo<1,RLSheetRhoRead$> = STR(@SVM,16) thisLayerInfo<1,RLResMin$> = LayerSpec thisLayerInfo<1,RLResMax$> = LayerSpec thisLayerInfo<1,RLResUnits$> = LayerSpec thisLayerInfo<1,RLResTarget$> = LayerSpec thisLayerInfo<1,RLThickMin$> = LayerSpec thisLayerInfo<1,RLThickMax$> = LayerSpec thisLayerInfo<1,RLThickUnits$> = LayerSpec thisLayerInfo<1,RLThickTarget$> = LayerSpec LayerInfo := thisLayerInfo:CHAR(248) NEXT I LayerInfo[-1,1] = '' ;* Strip trailing CHAR(248) RDSRec = LayerInfo ;* End of the great Layer cluster function RTParms = FieldStore(RTParms, @RM, 2, 1, LockedRDSNo) RTParms = FieldStore(RTParms, @RM, 4, 1, RDSRec) obj_Tables('WriteRec',RTParms) ;* Write and unlock RDS records END NEXT N RETURN * * * * * * * WMInKeys: * * * * * * * InFlag = 1 OutFlag = 0 GOTO WMKeys * * * * * * * WMOutKeys: * * * * * * * OutFlag = 1 InFlag = 0 * * * * * * * WMKeys: * * * * * * * RDSNo = Parms[1,@RM] RDSRec = Parms[COL2()+1,@RM] IF RDSNo = '' THEN RETURN IF RDSRec = '' THEN RDSRec = XLATE('RDS',RDSNo,'','X') IF InFlag THEN CassNos = RDSRec END ELSE CassNos = RDSRec END WOStepKey = RDSRec CassIDS = '' FOR I = 1 TO COUNT(CassNos,@VM) + (CassNos NE '') CassNo = CassNos<1,I> IF CassNo NE '' THEn LOCATE WOStepKey:'*':CassNo IN CassIDS BY 'AR' USING @VM SETTING Pos ELSE CassIDS = INSERT(CassIDS,1,Pos,0,WOStepKey:'*':CassNo) END END NEXT I Result = CassIDS RETURN * * * * * * * SetSchedWfrQty: * * * * * * * RdsNo = Parms[1,@RM] SchedWfrQty = Parms[COL2()+1,@RM] IF RdsNo = '' THEN ErrorMsg = 'Null Parm "RdsNo" passed to routine. (':Method:')' IF SchedWfrQty = '' THEN ErrorMsg = 'Null Parm "SchedWfrQty" passed to routine. (':Method:')' IF ErrorMsg NE '' THEN RETURN otParms = 'RDS':@RM:RdsNo RDSRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock RDSRec = SchedWfrQty otParms = FIELDSTORE(otParms,@RM,4,0,RDSRec) obj_Tables('WriteRec',otParms) RETURN * * * * * * * MU_ADE_Reads: * * * * * * * RDSNo = Parms[1,@RM] RDSRec = Parms[COL2()+1,@RM] IF RDSNo = '' THEN RETURN IF RDSRec = '' THEN RDSRec = XLATE('RDS',RDSNo,'','X') IF RDSRec = '' THEN RETURN WONo = RDSRec CassNo = RDSRec MUCassIDs = obj_WO_Mat('GetMUCassIDs',WONo:'*':CassNo) Result = XLATE('WO_MAT',MUCassIDs,'ADE_READ','X') RETURN * * * * * * * * MetPropFlag: * * * * * * * * RDSNo = Parms[1,@RM] RDSRec = Parms[COL2()+1,@RM] PropCd = Parms[COL2()+1,@RM] IF RDSNo = '' THEN RETURN IF PropCd = '' THEN RETURN IF RDSRec = '' THEN RDSRec = XLATE('RDS',RDSNo,'','X') IF RDSRec = '' THEN RETURN WONo = RDSRec WOStepKey = RDSRec ReactNo = RDSRec PSNo = RDSRec WOStepNo = FIELD(WOStepKey,'*',2) ReactRDSNos = XLATE('WO_REACT',WONo:'*':WOStepNo:'*':ReactNo,WO_REACT_RDS_NO$,'X') LOCATE RDSNo IN ReactRDSNos USING @VM SETTING Pos THEN Result = obj_PRS_Prop('GetIntervalFlag',PSNo:@RM:PropCd:@RM:Pos) END RETURN * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * P r i v a t e M e t h o d s * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * CalcConTarget: * * * * * * * IF RDSConMin AND RDSConMax THEN IF RDSConMin = RDSConMax THEN RDSConTarget = RDSConMin END ELSE Delta = INT((RdsConMax-RDSConMin)/2) RDSConTarget = RDSConMin + Delta END END ELSE RDSConTarget = '' END RETURN * * * * * * * CalcResTarget: * * * * * * * IF RDSResMin AND RDSResMax THEN IF RDSResMin = RDSResMax THEN RDSResTarget = RDSResMin END ELSE Delta = INT((RdsResMax-RDSResMin)/2) RDSResTarget = RDSResMin + Delta END END ELSE RDSResTarget = '' END RETURN * * * * * * * CalcThickTarget: * * * * * * * IF RDSThickMin AND RDSThickMax THEN IF RDSThickMin = RDSThickMax THEN RDSThickTarget = RDSThickMin END ELSE Delta = INT((RdsThickMax-RDSThickMin)/2) RDSThickTarget = RDSThickMin + Delta END END ELSE RDSThickTarget = '' END RETURN