COMPILE Subroutine FIX_RDS(Dummy) * ROWDEF(CHARSTR) #pragma precomp SRP_PreCompiler DECLARE SUBROUTINE obj_Schedule,Send_Dyn,Send_Info, Send_Dyn, obj_WO_Step, Set_Status, Btree.Extract, obj_RDS, RList, ErrMsg, Sleepery DECLARE SUBROUTINE Make.List, obj_RDS_Test, obj_RDS_Layer, REACT_RUN_RDS, obj_Tables, Msg, Yield, SRP_Stopwatch, Schedule_Services, Error_Services, Database_Services, Epi_Part_Services, Activate_Save_Select DECLARE FUNCTION Get_Status, Set_Printer, obj_RDS, ErrMsg, obj_Prod_Spec, obj_React_Item_Hist,ICONV, Schedule_Services, Error_Services, Database_Services, Epi_Part_Services, SRP_Math Declare function SRP_COM, Memory_Services, SRP_Array, Date_Services, SRP_Math, MemberOf, Environment_Services, Get_Property, RTI_Task_Submit, obj_Tables, RTI_Task_Status Declare subroutine SRP_COM, Memory_Services $INSERT LOGICAL $INSERT RDS_EQUATES $INSERT WO_LOG_EQUATES $INSERT WO_MAT_EQUATES $INSERT WO_STEP_EQUATES $INSERT RDS_LAYER_EQUATES $INSERT PROD_SPEC_EQU $INSERT SURFACE_SCAN_EQUATES $INSERT PRS_LAYER_EQU $INSERT REACT_ITEM_EQUATES $INSERT WO_WFR_EQUATES $insert FILE.SYSTEM.EQUATES $Insert SCHED_DET_EQUATES $insert REVDOTNETEQUATES Equ MIDNIGHT_PM$ to 86400 ; // Midnight represented as the end of the day. // <1> Transaction type out // <2> Number of transactions per type // <3> Number of transactions out // <2,1> Transaction type in // <2,2> Number of transactions in per type // <2,3> Number of transactions in // CASS_COMP, // SAP_COMM_LOG Fields // Log DTM // Trans Type (Rx, Tx) // DOS Path // Filename // DOS Filename // SAP Trans Type Equ Tab$ to \09\ Equ LF$ to \0A\ Equ Comma$ to ',' Equ CRLF$ to \0D0A\ //COC Fix when default printer isn't set, run this for each missed SAP Shipment ShipNo = 152037 cocParms = 'COC':@RM:ShipNo ShipRec = obj_Tables('ReadRec',cocParms) TaskID = RTI_Task_Submit('', 'PRINT_SHIPMENT_DEV', ShipNo, ShipRec, 1, True$) If TaskID NE 0 then Done = False$ Loop Status = RTI_Task_Status(TaskID, TaskResponse) If (Status EQ 'COMPLETED') OR (Status EQ 'ERROR') then Done = True$ Until Done Repeat end Return Debug SapStartDTM = 18630.27152777778 SapStopDTM = 18631.0708333333333333 OutStatsArray = '' InStatsArray = '' LotHoldInfo = '' OutFilename = 'SAPStatsOut.txt' InFilename = 'SAPStatsIn.txt' HoldFilename = 'SAPHoldInfo.txt' OutDir = 'C:\Users\ecStieberD\Desktop\' Open 'SAP_COMM_LOG' to SAPCommHandle then StartKey = 194900 CurrKey = StartKey Done = False$ Loop Read SAPCommRec from SAPCommHandle, CurrKey then LogDTM = SAPCommRec<1> If LogDTM LT SAPStopDTM then If LogDTM GT SAPStartDTM then TransType = SAPCommRec<2> DOSPath = SAPCommRec<3> SAPTransType = SAPCommRec<6> If TransType EQ 'TX' then ArrayTransTypes = OutStatsArray<1> Locate SAPTransType in ArrayTransTypes using @VM setting vPos then OutTransTypeCount = OutStatsArray<2,vPos> OutStatsArray<2,vPos> = OutTransTypeCount + 1 OutTransCount = OutStatsArray<3> OutStatsArray<3> = OutTransCount + 1 end else OutStatsArray<1,-1> = SAPTransType OutStatsArray<2,-1> = 1 OutTransCount = OutStatsArray<3> OutStatsArray<3> = OutTransCount + 1 end If SAPTransType EQ 'WO_MAT_HOLD' then DOSFilename = SAPCommRec<5> LotHoldInfo<-1> = DOSFilename end end else ArrayTransTypes = InStatsArray<1> Locate SAPTransType in ArrayTransTypes using @VM setting vPos then InTransTypeCount = InStatsArray<2,vPos> InStatsArray<2,vPos> = InTransTypeCount + 1 InTransCount = InStatsArray<3> InStatsArray<3> = InTransCount + 1 end else InStatsArray<1,-1> = SAPTransType InStatsArray<2,-1> = 1 InTransCount = InStatsArray<3> InStatsArray<3> = InTransCount + 1 end end end end else Done = True$ end end CurrKey += 1 Until Done EQ True$ Repeat end Convert @VM to ',' in OutStatsArray Convert @FM to LF$ in OutStatsArray Convert @VM to ',' in InStatsArray Convert @FM to LF$ in InStatsArray Convert @FM to ',' in LotHoldInfo * OSWrite OutStatsArray to OutDir:OutFilename * OSWrite InStatsArray to OutDir:InFilename OSWrite LotHoldInfo to OutDir:HoldFilename Return Debug HazeAvg = 'NA' HazeAvg = Iconv(HazeAvg, 'MD3') Return ShipNo = 1234 DosTable1 = 'C:\OIReports\W':ShipNo:'.TSV' DosTable2 = Environment_Services('GetReportsRootPath') : '\W':ShipNo:'.TSV' DosTable = Environment_Services('GetReportsRootPath') : '\T':ShipNo:'.csv' DataOut = 'Hello World' OSOPEN DosTable TO DOSFile THEN OSWrite DataOut ON DosTable ;* Clear file it was already there END ELSE OSWrite DataOut ON DosTable ;* Create the file if it wasn't OSOPEN DosTable TO DOSFile ELSE ErrorMsg = "Unable to open ":QUOTE(DosTable):" in Export_TSV routine." RETURN END END Return Debug hTable = Database_Services('GetTableHandle', 'SCHED_DET') Activate_Save_Select('SRP') EOF = False$ IDList = '' IDCount = 0 * Select hTable Loop Readnext ID else EOF = True$ Until EOF Delete hTable, ID then IDCount += 1 Send_Info('Deleted ' : IDCount) end else Debug end * Row = Database_Services('ReadDataRow', 'SCHED_DET', ID) * Database_Services('DeleteDataRow', 'SCHED_DET', ID, True$) * If Error_Services('HasError') then * Message = Error_Services('GetMessage') * end Repeat Debug Return Open 'DICT.WO_MAT' to @Dict else Null WO = 164826 Cassette = 38 @ID = WO : '*' : Cassette @RECORD = Database_Services('ReadDataRow', 'WO_MAT', @ID) Debug WOLogRow = Database_Services('ReadDataRow', 'WO_LOG', {WO_NO}) ReactType = WOLogRow If ReactType _EQC 'EPP' OR ReactType _EQC 'EpiPro' then WOStepKeyID = WOLogRow WOStepRow = Database_Services('ReadDataRow', 'WO_STEP', WOStepKeyID) RDSNo = WOStepRow ActionFlow = Xlate('REACT_RUN', RDSNo, 'LOAD_WFR_CNT', 'X') end else ActionFlow = '' end Return Debug TOTAL_WAFERS_EXPECTED = 79.83 Round = SRP_Math('ROUND', (TOTAL_WAFERS_EXPECTED / 25), '', 0) ActionFlow = Round * 25 Return Debug Activate_Save_Select('SRP') * RList('SELECT REACTOR_PERFORMANCE WITH SCHEDULE_DATE FROM "11/01/2017" TO "11/02/2017"', 5, '', '', '') EOF = False$ Loop Readnext PerfKeyID else EOF = True$ Until EOF PerfRow = Database_Services('ReadDataRow', 'REACTOR_PERFORMANCE', PerfKeyID, True$, 0) PerfRow<2> = 0 Database_Services('WriteDataRow', 'REACTOR_PERFORMANCE', PerfKeyID, PerfRow, True$, False$, True$) Repeat Return EQU TARGET_ACTIVELIST$ TO 5 Debug Open 'REACT_MODE' to hReactMode then Activate_Save_Select('SRP') EOF = False$ PrevReactNo = '' Loop Readnext KeyID else EOF = True$ Until EOF Read Row from hReactMode, KeyID then * Write Row to hReactModeBack, KeyID else Debug ReactNo = KeyID[1, '*'] StartDTM = KeyID[Col2() + 1, '*'] If (PrevReactNo NE ReactNo) then // This is the first REACT_MODE row for the current reactor. Do not update anything but read its data for // the following REACT_MODE row. end else // Take the "start" data fields from the previous (i.e., newer) row and put it in the "stop" data fields // in the current row. PrevReactNo = PrevKeyID[1, '*'] PrevStartDTM = PrevKeyID[Col2() + 1, '*'] Row<6> = PrevStartDTM ; // Stop DTM Row<7> = PrevRow<1> ; // Stop User Row<8> = PrevRow<2> ; // Stop Note Row<9> = PrevRow<3> ; // Stop REACT_UTIL Key ID Row<10> = PrevRow<4> ; // Stop REACTOR_LOG Key ID Write Row to hReactMode, KeyID else Debug end end PrevReactNo = ReactNo PrevKeyID = KeyID PrevRow = Row Repeat end Return Debug OtherEvents = 1 : @VM : 'A' : @FM : 2 : @VM : 'A' : @FM : 3 : @VM : 'A' : @FM : 4 : @VM : 'A' : @FM WorkOrderEvents = 1 : @VM : 'A' : @FM : 2 : @VM : 'A' : @FM : 3 : @VM : 'A' OtherEvents = SRP_Array('Join', OtherEvents, WorkOrderEvents, 'NOT', @FM) Return Debug Open 'SCHED_DET' to hSchedDet then Select hSchedDet EOF = 0 Loop Readnext ID else EOF = 1 Until EOF Read Row from hSchedDet, ID then DayLengthCode = Row If DayLengthCode = '' then DayLengthCode = 4 Row = 0 Row = 86400 * (DayLengthCode * .25) Write Row to hSchedDet, ID else Debug end Repeat end Return WafersRemainings = '0,2,4,6,8,10,12,14,15,17,19,20,24,28,31,38,42,55,100' WafersPerDay = 10 For Each WafersRemaining in WafersRemainings using ',' DaysNeeded1 = SRP_Math('ROUND', (WafersRemaining / WafersPerDay) * 4, '', 0) / 4 DaysNeeded2 = SRP_Math('NONE', (WafersRemaining / WafersPerDay) * 4, '', 0) / 4 Next NumberOfDays Debug Return Open 'SCHED_DET' to hSchedDet then Open 'APP_INFO' to hAppInfo then RLIST('SELECT APP_INFO WITH @ID STARTING 59', 5, '', '', '') eof = 0 Loop Readnext ID else eof = 1 Until EOF If Field(ID, '*', 2) LT 18094 then Read Rec from hAppInfo, ID then Write Rec to hSchedDet, ID else Debug end end Repeat end end Debug Complete = '17.70833333333' Complete = Oconv(Iconv(Complete, 'MD2'), 'MD2') Return KeyID = '31*18172*1' Row = '164299' Row<8> = 'OrangeRed' * Debug Open 'SCHED_DET' to hSchedDet then * hSchedDet = Delete(hSchedDet, 1, 1, 1) SRP_Stopwatch('Reset') For Loop = 1 to 50 SRP_Stopwatch('Start', 'Write') Write Row to hSchedDet, KeyID else Debug SRP_Stopwatch('Stop', 'Write') * SRP_Stopwatch('Start', 'Read') Read Row from hSchedDet, KeyID else Null * SRP_Stopwatch('Stop', 'Read') SRP_Stopwatch('Start', 'Delete') Delete hSchedDet, KeyID else Null SRP_Stopwatch('Stop', 'Delete') Next Loop SRP_Stopwatch('ShowAll') end Return Debug NumberOfEvents = SRP_Math('NONE', 0.00 + .49, '', 0) NumberOfEvents = SRP_Math('NONE', 0.25 + .49, '', 0) NumberOfEvents = SRP_Math('NONE', 0.50 + .49, '', 0) NumberOfEvents = SRP_Math('NONE', 0.75 + .49, '', 0) NumberOfEvents = SRP_Math('NONE', 1.00 + .49, '', 0) NumberOfEvents = SRP_Math('NONE', 1.25 + .49, '', 0) NumberOfEvents = SRP_Math('NONE', 1.50 + .49, '', 0) NumberOfEvents = SRP_Math('NONE', 1.75 + .49, '', 0) Return * Debug SchedKeys = Schedule_Services('GetScheduleDetailKeys', 18108, '', '52', '', True$) Schedule_Services('DeleteScheduleDetail', SchedKeys) Return Debug call Activate_Save_Select('FIX_RDS') Open 'SCHED_DET' to hSchedDet then EOF = 0 Loop Readnext ID else EOF = 1 Until EOF Read Rec from hSchedDet, ID then Delete hSchedDet, ID else Null end Repeat end Return '' call Detach_Table('SCHED_DET') call Alias_Table('APPDATA', 'LSL2', 'SCHED_DET_TEST', 'SCHED_DET') call Memory_Services('ReleaseHashTable') Return '' Debug * OSRead MPWArray from 'E:\apps\Temp\OpenInsight (Parts) v12.txt' then * * Convert \09\ to @VM in MPWArray * Swap \0D0A\ with @FM in MPWArray * ReactorTypes = 'ASM,ASM+,HTR,EPIPRO' * * Open 'EPI_PART' to hEpiPart then * For Each MPWRow in MPWArray using @FM * EpiPartNo = MPWRow<0, 1> * For TypeCnt = 1 to 4 * MPWVal = MPWRow<0, TypeCnt + 1> * If MPWVal NE '' then * ReactorType = Field(ReactorTypes, ',', TypeCnt) * Epi_Part_Services('SetMinutesPerWaferScheduler', EpiPartNo, ReactorType, MPWVal) * end * Next TypeCnt * Next MPWRow * end * * end * * Return * Debug * ReactorTypes = 'ASM,ASM+,HTR,EPIPRO' * Call Activate_Save_Select('EPI_PARTS') * MPWArray = '' * Open 'EPI_PART' to hEpiPart then * EOF = False$ * Loop * Readnext EpiPartNo else EOF = True$ * If EpiPartNo EQ '567930' then Debug * Until EOF * MPWArray := EpiPartNo : \09\ * For Each ReactorType in ReactorTypes using ',' * MPW = Epi_Part_Services('GetMinutesPerWaferScheduler', EpiPartNo, ReactorType) * MPWArray := MPW : \09\ * Next Each * MPWArray[-1, 1] = \0D0A\ * Repeat * MPWArray[-2, 2] = '' * end * * OSWrite MPWArray to 'E:\apps\Temp\OpenInsight (Parts) 3.txt' * * Return call Epi_Part_Services('SetReactorUtilization', 'ASM', 53) call Epi_Part_Services('SetReactorUtilization', 'ASM+', 58) call Epi_Part_Services('SetReactorUtilization', 'HTR', 58) call Epi_Part_Services('SetReactorUtilization', 'EpiPro', 52) Return Call Activate_Save_Select('TEST2') Open 'RDS_TEST' to hRDSTest then EOF = False$ Loop Readnext ID else EOF = True$ Until EOF Read Record from hRDSTest, ID then * If Record<132> NE '' then Debug Record<130> = Record<130>[-1, 'B' : @VM] Record<131> = Record<131>[-1, 'B' : @VM] Record<132> = Record<132>[-1, 'B' : @VM] Record<134> = Record<134>[-1, 'B' : @VM] Write Record to hRDSTest, ID else Debug end Repeat end Return ****************************************** * Update the new WO_LOG Sched Det Fields ****************************************** OPEN 'SCHED_DET' TO SchedDetTable THEN Done = 0 * RLIST('SELECT WO_MAT WITH WO_NO > 138176',TARGET_ACTIVELIST$,'','','') RLIST('SELECT SCHED_DET BY @ID',TARGET_ACTIVELIST$,'','','') NumRowsUpdated = 0 LOOP Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield() Sleepery(500) READNEXT SchedDetKeyID ELSE Done = 1 UNTIL Done READ SchedDetRec FROM SchedDetTable,SchedDetKeyID THEN WOLogKeyID = SchedDetRec if (WOLogKeyID) then If Database_Services('GetKeyIDLock', 'WO_LOG', WOLogKeyID, True$) then WOLogRow = Database_Services('ReadDataRow', 'WO_LOG', WOLogKeyID) If Error_Services('NoError') then Locate SchedDetKeyID in WOLogRow using @VM setting vPos else WOLogRow = Insert(WOLogRow, WO_LOG_SCHED_DET_KEYIDS$, vPos, 0, SchedDetKeyID) Database_Services('WriteDataRow', 'WO_LOG', WOLogKeyID, WOLogRow, True$, True$) end end Database_Services('ReleaseKeyIDLock', 'WO_LOG', WOLogKeyID) end end END NumRowsUpdated+= 1 REPEAT END return * SchedDetKeys = '59*18055*2' : @FM * SchedDetKeys := '59*18056*1' : @FM * SchedDetKeys := '60*18057*2' : @FM * SchedDetKeys := '60*18058*2' : @FM * SchedDetKeys := '60*18059*2' : @FM * SchedDetKeys := '60*18060*2' : @FM * SchedDetKeys := '60*18061*2' : @FM * SchedDetKeys := '60*18062*2' : @FM * SchedDetKeys := '60*18063*2' : @FM * SchedDetKeys := '60*18064*2' * SchedDetKeys = '100*18055*2' : @FM SchedDetKeys := '100*18056*1' : @FM SchedDetKeys := '101*18057*2' : @FM SchedDetKeys := '101*18058*2' : @FM SchedDetKeys := '101*18059*2' : @FM SchedDetKeys := '101*18060*2' : @FM SchedDetKeys := '101*18061*2' : @FM SchedDetKeys := '101*18062*2' : @FM SchedDetKeys := '101*18063*2' : @FM SchedDetKeys := '101*18064*2' Debug For Each SchedDetKey in SchedDetKeys using @FM SchedDetRow = Schedule_Services('GetScheduleDetail', SchedDetKey) If Error_Services('NoError') then ReactorNo = SchedDetKey[1, '*'] StartDate = SchedDetKey[Col2() + 1, '*'] SeqNo = SchedDetKey[Col2() + 1, '*'] If ReactorNo EQ 59 then NewReactorNo = 100 If ReactorNo EQ 100 then NewReactorNo = 59 If ReactorNo EQ 60 then NewReactorNo = 101 If ReactorNo EQ 101 then NewReactorNo = 60 NewSchedDetKey = NewReactorNo : '*' : StartDate : '*' : SeqNo Schedule_Services('SetScheduleDetail', NewSchedDetKey, SchedDetRow) If Error_Services('NoError') then Schedule_Services('DeleteScheduleDetail', SchedDetKey) If Error_Services('HasError') then Error_Services('DisplayError') end end else Error_Services('DisplayError') end end else Error_Services('DisplayError') end Next SchedDetKey Return SRP_Stopwatch('Reset') SRP_Stopwatch('Start', 'Write') StartDate = Date() Open 'SCHED_DET' to hSchedDet then SchedDetRow = '999999' : @FM : @FM : @FM For RowCnt = 1 to 5 SchedDetKey = 100 : '*' : StartDate + RowCnt : '*' : 1 call Database_Services('WriteDataRow', 'SCHED_DET', SchedDetKey, SchedDetRow, True$) * call Database_Services('DeleteDataRow', 'SCHED_DET', SchedDetKey, True$) Next RowCnt SchedDetRow = '888888' : @FM : @FM : @FM For RowCnt = 1 to 5 SchedDetKey = 101 : '*' : StartDate + RowCnt : '*' : 1 call Database_Services('WriteDataRow', 'SCHED_DET', SchedDetKey, SchedDetRow, True$) * call Database_Services('DeleteDataRow', 'SCHED_DET', SchedDetKey, True$) Next RowCnt end SRP_Stopwatch('Stop', 'Write') SRP_Stopwatch('ShowAll') Return ***************************************** * Find old Metrology Records not in use * ***************************************** SmallestMetKey = 1000000 Counter = 0 OPEN 'WO_MAT' TO WOMatTable THEN Done = 0 RLIST('SELECT WO_MAT WITH WO_NO > 138176',TARGET_ACTIVELIST$,'','','') LOOP Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield() READNEXT WOMatKey ELSE Done = 1 UNTIL Done Counter = Counter + 1 MetKeys = XLATE('WO_MAT', WOMatKey, 'CASS_RDS_MET_KEYS', 'X') If (MetKeys NE '') then MetKeysCnt = DCount(MetKeys, @VM) FOR MetKeysIndex = 1 TO MetKeysCnt MetKey = TRIM(MetKeys<1, MetKeysIndex>) if (MetKey NE '') AND (MetKey < SmallestMetKey) then SmallestMetKey = MetKey end NEXT MetKeysIndex end * If Counter > 5000 then * Errmsg("WO_MAT = ": WOMatKey : " - " : SmallestMetKey) * Counter = 0 * Debug * end REPEAT Errmsg("WO_MAT = ": WOMatKey : " - " : SmallestMetKey) END return ****************************************** * Update the new WO_LOG Hot Lot data field ****************************************** OPEN 'WO_MAT' TO WOMatTable THEN Done = 0 * RLIST('SELECT WO_MAT WITH WO_NO > 138176',TARGET_ACTIVELIST$,'','','') RLIST('SELECT WO_MAT WITH WO_NO > 162069',TARGET_ACTIVELIST$,'','','') LOOP Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield(); Yield() READNEXT WOMatKey ELSE Done = 1 UNTIL Done READ WOMatRec FROM WOMatTable,WOMatKey THEN HotLot = WOMatRec if (HotLot) then WOMatRec = 0 obj_Tables('WriteRec','WO_MAT':@RM:WOMatKey:@RM:@RM:WOMatRec) WOMatRec = 1 obj_Tables('WriteRec','WO_MAT':@RM:WOMatKey:@RM:@RM:WOMatRec) end END REPEAT END return * NextFS = 'RTP57' * NewFSList = 'RTP57' * Open 'RDS_TEST' to Handle then * Handle = Handle<1, 2, 1>[-1, 'B' : \0D\] * Handle = \0D\ : Handle[1, 27] * Name = '1000141' * OrigRecord = '' * ActionStatus = 1 * Call @NextFS(READO.RECORD, NewFSList, Handle, Name, FMC, OrigRecord, ActionStatus) * end Open 'EPI_PART' to hHandle then Name = '892593' hHandle = hHandle<1, 2, 1>[-1, 'B' : \0D\] hHandle = \0D\ : hHandle[1, 27] * Status Call RTP57(1, 'RTP57', hHandle, Name, FMC, Record, Status) end Debug Return Goto FixRDSRecords OPEN 'DICT.RDS' TO DictVar ELSE debug GOTO Bail END OPEN 'RDS' TO RDSTable ELSE debug GOTO Bail END OPEN 'WO_WFR' TO WfrTable ELSE debug GOTO Bail END ************** FixRDSRecords: ************** ******************** * Input Parameters * ******************** WONo = '163710' RONos = '1' NewPONo = 'NA' NewCustNo = '6874' NewPSNNo = '3524' NewPartNo = 'WEP860778IRE' NewEpiPartNo = 'WEP860778IRE' NewShipDate = '04/18/2017' CONVERT ',' TO @VM IN RONos ********************** * Fix WO_MAT Records * ********************** OPEN 'WO_MAT' TO WOMatTable THEN CassettesCount = COUNT(RONos,@VM) + (RONos NE '') FOR CassettesLoopIndex = 1 TO CassettesCount WOMatKey = WONo:'*':RONos<1,CassettesLoopIndex> READ WOMatRec FROM WOMatTable,WOMatKey THEN Msg(WOMatKey : ' Replace ' : WOMatRec : ' with ' : NewPartNo) WOMatRec = NewPartNo /* Line #003 */ obj_Tables('WriteRec','WO_MAT':@RM:WOMatKey:@RM:@RM:WOMatRec) END NEXT CassettesLoopIndex END *********************** * Fix WO_STEP Records * *********************** OPEN 'WO_STEP' TO WOStepTable THEN WOStepKey = WONo:'*1' READ WOStepRec FROM WOStepTable,WOStepKey THEN Msg(WOStepKey : ' Replace ' : WOStepRec : ' with ' : NewPSNNo) WOStepRec = NewPSNNo /* Line #001 */ obj_Tables('WriteRec','WO_STEP':@RM:WOStepKey:@RM:@RM:WOStepRec) END END ******************* * Fix RDS Records * ******************* OPEN 'RDS' TO RDSTable THEN Done = 0 RLIST('SELECT REACT_RUN WITH WO_NO = ':QUOTE(WONo):' ',TARGET_ACTIVELIST$,'','','') LOOP READNEXT RDSNo ELSE Done = 1 UNTIL Done READ RDSRec FROM RDSTable,RDSNo THEN PONo = RDSRec RONo = XLATE('RDS',RDSNo,'RUN_ORDER_NUM','X') LOCATE RONo IN RONos USING @VM SETTING Pos THEN Msg('WONo: ' : WONo : ' / RDSNo: ' : RDSNo : ' / RONo: ' : RONo : ' Replace ' : RDSRec : ' with ' : NewPSNNo) RDSRec = NewPONo /* Line #008 */ RDSRec = NewCustNo /* Line #009 */ RDSRec = NewPSNNo /* Line #010 */ RDSRec = NewPartNo /* Line #114 */ obj_Tables('WriteRec','RDS':@RM:RDSNo:@RM:@RM:RDSRec) END END REPEAT END ********************** * Fix WO_LOG Records * ********************** OPEN 'WO_LOG' TO WOLogTable THEN WOLogKey = WONo READ WOLogRec FROM WOLogTable,WOLogKey THEN Msg('WOLogKey: ':WOLogKey:' Replace ' : WOLogRec : ' with ' : NewCustNo) WOLogRec = NewCustNo /* Line #003 */ WOLogRec = ICONV(NewShipDate,'D4/') /* Line #014 */ WOLogRec = NewEpiPartNo /* Line #048 */ WOLogRec = NewPONo /* Line #051 */ WOLogRec = NewPartNo /* Line #054 */ obj_Tables('WriteRec','WO_LOG':@RM:WOLogKey:@RM:@RM:WOLogRec) END END Debug GoTo Bail ********************************* DEBUG SELECT RDSTable Done = 0 RecCnt = 0 LOOP READNEXT RDSNo ELSE Done = 1 UNTIL Done RecCnt += 1 ReactType = XLATE('RDS',RDSNo,'REACTOR_TYPE','X') IF ReactType = 'EPP' THEN READ RDSRec FROM RDSTable,RDSNo THEN WONo = RDSRec pktCnt = COUNT(RDSRec,@VM) + (RDSRec NE '') FOR I = 1 TO pktCnt InCassNo = RDSRec InSlotNo = RDSRec WfrKey = WONo:'*':InCassNo:'*':InSlotNo READ WfrRec FROM WfrTable,WfrKey ELSE WfrRec = '' WfrRec = RDSRec WfrRec = RDSRec WfrRec = RDSRec WfrRec = RDSRec WfrRec = RDSRec *WRITE WfrRec ON WfrTable,WfrKey THEN Send_Info(RecCnt) *END NEXT I END ;* End of RDS Record read END REPEAT GOTO Bail OPEN 'WO_MAT' TO WOMatTable ELSE debug GOTO Bail END RLIST('SELECT WO_MAT WITH WO_NO = "161511" ',5,'','','') Done = 0 RecCnt = 0 LOOP READNEXT WOMatKey ELSE Done = 1 UNTIL Done RecCnt += 1 READ WOMatRec FROM WOMatTable,WOMatKey THEN WOMatRec = CustPartNo WRITE WOMatRec ON WOMatTable,WOMatKey THEN Send_Dyn('WO_Mat Key: ':WOMatKey:' updated.') END END REPEAT GOTO Bail RLIST('SELECT REACT_RUN WITH WO_NO = "161511" ',5,'','','') Done = 0 RecCnt = 0 LOOP READNEXT RDSNo ELSE Done = 1 UNTIL Done RecCnt += 1 Send_Info(RecCnt) WONo = XLATE('REACT_RUN',RDSNo,'WO_NO','X') *React_Run_RDS(RDSNo) ;* Recreates basic RDS records from REACT_RUN records ****************************************************** PS_No = '3223' 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') Send_Info('Retrieving PSN Layer Properties...') 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 DEBUG 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 Send_Info('Creating RDS Layer ':LayerSet:'...') obj_RDS_Layer('Create',RDSNo:@RM:LayerSet:@RM:PS_No:@RM:NoCombinedLayerFlag) *RDSRec = RDSNo:'*':LayerSet ;* Added 4/17/2006 JCH Send_Info('Creating Metrology for Layer Set ':LayerSet:'...') obj_RDS_Test('Create',RDSNo:@RM:LayerSet:@RM:PS_No) NEXT I *Send_Info('Saving RDS record...') *obj_Tables('WriteRec','RDS':@RM:RDSNo:@RM:@RM:RDSRec) REPEAT GOTO Bail * * * * * * * * * * * * * * Result = '' RLIST('SELECT RDS WITH DATE_OUT >= "20 FEB 2014" BY SEQ ',5,'','','') Done = 0 RecCnt = 0 LOOP READNEXT RDSNo ELSE Done = 1 UNTIL Done RecCnt += 1 Send_Info(RecCnt) READ RDSRec FROM FileIn,RDSNo THEN DateOut = RDSRec ReactNo = RDSRec TubeID = RDSRec TubeGrade = RDSRec SuscID = RDSRec /* HistoryKeys = obj_React_Item_Hist('GetHistory',ReactNo:@RM:@RM:'T') LOOP HistKey = HistoryKeys<1,1> RINo = FIELD(HistKey,'*',2) InstDt = FIELD(HistKey,'*',3)[1,'.'] UNTIL DateOut >= InstDt OR HistoryKeys = '' HistoryKeys = DELETE(HistoryKeys,1,1,0) REPEAT RITubeGrade = XLATE('REACT_ITEM',RINo,REACT_ITEM_TUBE_GRADE$,'X') *Send_Dyn(ReactNo:' ':OCONV(DateOut,'D4/'):' ':OCONV(InstDt,'D4/'):' Tube No: ':RINo:' Grade: ':TubeGrade:'/':RITubeGrade) RDSRec = RINo RDSRec = RITubeGrade */ HistoryKeys = obj_React_Item_Hist('GetHistory',ReactNo:@RM:@RM:'S') LOOP HistKey = HistoryKeys<1,1> RINo = FIELD(HistKey,'*',2) InstDt = FIELD(HistKey,'*',3)[1,'.'] UNTIL DateOut >= InstDt OR HistoryKeys = '' HistoryKeys = DELETE(HistoryKeys,1,1,0) REPEAT RDSRec = RINo *Send_Dyn(ReactNo:' ':OCONV(DateOut,'D4/'):' ':OCONV(InstDt,'D4/'):' Susc No: ':RINo:' Susc ID: ':SuscID) *Send_Dyn(' ') WRITE RDSRec ON FileIn,RDSNo THEN NULL END END REPEAT GOTO Bail ********************************** *RLIST('SELECT RDS WITH WO = "" ',5,'','','') RLIST('SELECT RDS WITH WO <= "128597" ',5,'','','') Done = 0 RecCnt = 0 LOOP READNEXT RDSNo ELSE Done = 1 UNTIL Done RecCnt += 1 Send_Info(RecCnt) READ RDSRec FROM FileIn,RDSNo THEN LSKeys = RDSRec NCRKeys = RDSRec SurfScanKeys = RDSRec MetKeys = XLATE('RDS_LAYER',LSKeys,RDS_LAYER_RDS_TEST_KEYS$,'X') IF NCRKeys NE '' THEN OPEN 'NCR' TO NCRFile THEN NCRCnt = COUNT(NCRKeys,@VM) FOR NCR = 1 TO NCRCnt DELETE NCRFile,NCRKeys<1,NCR> THEN Send_Dyn(' NCR ':NCRKeys<1,NCR>:' deleted') END NEXT NCR END END ;* End of NCR section IF SurfScanKeys NE '' THEN OPEN 'SURFACE_SCAN' TO SurfScanTable THEN ScanCnt = COUNT(SurfScanKeys,@VM) + (SurfScanKeys NE '') FOR Scan = 1 TO ScanCnt DELETE SurfScanTable,SurfScanKeys<1,Scan> THEN Send_Dyn(' SURFACE_SCAN ':SurfScanKeys<1,Scan>:' deleted') END NEXT Scan END ;* End of SURFACE_SCAN open END ;* End of SurfScan sectioin IF MetKeys NE '' THEN CONVERT @VM TO ',' IN MetKeys Send_Dyn(' Met Keys ':MetKeys:' deleted') obj_RDS_Test('Delete',MetKeys) END ;* End of check for MetKeys IF LSKeys NE '' THEN CONVERT @VM TO ',' IN LSKeys Send_Dyn(' Layer Set Keys ':LSKeys:' deleted') obj_RDS_Layer('Delete',LSKeys) END ;* End of check for LSKeys DELETE FileIn,RDSNo THEN Send_Dyn('RDS ':RDSNo:' deleted') END END REPEAT GOTO Bail DEBUG Set_Status(0) SELECT FileIn RecCnt = 0 Done = 0 LOOP READNEXT RDSKey ELSE Done = 1 UNTIL Done OR RecCnt > 5000 READ RDSRec FROM FileIn,RDSKey THEN RecCnt += 1 Send_Info(RecCnt) SCTool = RDSRec IF SCTool[1,2] _EQC 'NO' THEN SCTool = '' PreEpiSigs = RDSRec IF RDSKey = 466635 THEN DEBUG IF INDEX(PreEpiSigs,@VM, 1) THEN PreCodes = RDSRec PreEpiSigDates = RDSRec PreEpiSigTimes = RDSRec SigCnt = COUNT(PreEpiSigs,@VM) + (PreEpiSigs NE '') PreSig = '' PreSigDTM = '' VerSig = '' VerSigDTM = '' FOR I = 1 TO SigCnt IF I = 1 THEN VerSig = RDSRec VerSigDTM = ICONV(OCONV(RDSRec,'D4/'):' ':OCONV(RDSRec,'MTS'),'DT') END ELSE PreSig = RDSRec PreSigDTM = ICONV(OCONV(RDSRec,'D4/'):' ':OCONV(RDSRec,'MTS'),'DT') END NEXT I IF PreSig = '' THEN PreSig = VerSig IF PreSigDTM = '' THEN PreSigDTM = VerSigDTM Send_Dyn(RDSKey:'VerSig: ':VerSig:' ':VerSigDTM:' PreSig: ':PreSig:' ':PreSigDTM) END ELSE VerSig = RDSRec VerSigDTM = ICONV(OCONV(RDSRec,'D4/'):' ':OCONV(RDSRec,'MTS'),'DT') END END REPEAT GOTO Bail ***********************8 RDSCnt = COUNT(RDSNos,@VM) + (RDSNos NE '') FOR I = 1 TO RDSCnt RDSNo = RDSNos<1,I> READ RDSRec FROM FileIn,RDSNo THEN RDSRec = 'I' RDSRec = '' RDSRec = '' RDSRec = '' RDSRec = '' RDSRec = '' RDSRec = '' WRITE RDSRec ON FileIn,RDSNo THEN Send_Dyn(RDSNo:' -> Fixed') END END NEXT I GOTO Bail RLIST('SELECT RDS WITH WO "146221"',5,'','','') Done = 0 RecCnt = 0 LOOP READNEXT RDSNo ELSE Done = 1 UNTIL Done RecCnt += 1 Send_Info(RecCnt) READ RDSRec FROM FileIn,RDSNo THEN LotNo = RDSRec NewLotNo = LotNo CONVERT "'" TO "" IN NewLotNo WRITE RDSRec ON FileIn,RDSNo THEN Send_Dyn(RDSNo:' -> ':LotNo:' -> ':NewLotNo) END END REPEAT GOTO Bail RDSNos = '380294':@VM RDSNos := '380297':@VM RDSNos := '380300':@VM RDSNos := '380303':@VM RDSNos := '380304':@VM RDSNos := '380308':@VM RDSNos := '380309':@VM RDSNos := '380311':@VM RDSNos := '380317':@VM RDSNos := '380331' RDSCnt = COUNT(RDSNos,@VM) + 1 FOR I = 1 TO RDSCnt RDSNo = RDSNos<1,I> READ RDSRec FROM FileIn,RDSNo THEN IF RDSRec = '3029' THEN IF RDSRec = '6035' THEN IF RDSRec = '6593' THEN RDSRec = '3062' RDSRec = '6068' RDSRec = '7034' debug DELETE FileIn,I THEN WRITE RDSRec ON FileIn,RDSNo THEN Send_Dyn(RDSNo) END END END END END END NEXT I GOTO Bail ***** Bail: ***** END