open-insight/LSL2/STPROC/OBJ_WM_IN.txt

938 lines
25 KiB
Plaintext

COMPILE FUNCTION obj_WM_In(Method,Parms)
/*
Methods for WM_IN table
03/13/2005 JCH - Initial Coding
Properties:
Methods:
Create(WONo,ProcStep,CassNo,WfrQty) ;* Create new record
RemainingSlots(WONo,WOStep) ;* Returns list of CassNo:@VM:SlotNo, @FM'd for slot without an RDS or NCR number
RemoveWafer(WONo,WOStep,CassNo,SlotNo,RDSNo,PocketNo,Zone,NCRNo) ;* Adds usage information from COMM_DIALOG_LOAD_EPI_PRO routine
ReplaceWafer(WONo,WOStep,CassNo,SlotNo) ;* Removes usage information
*/
DECLARE FUNCTION Get_Status, Msg, Utility, obj_Tables, NextKey, obj_WO_Verify, obj_Prod_Spec, Send_Dyn, obj_RDS_Makeup
DECLARE FUNCTION Database_Services, obj_RDS2, Logging_Services, Environment_Services, Error_Services
DECLARE SUBROUTINE Set_Status, Msg, obj_Tables, Send_Dyn, obj_WO_Step, obj_RDS_Layer, obj_RDS_Test, Update_Index
DECLARE SUBROUTINE obj_Post_Log, obj_WO_Mat_Log,obj_WO_Wfr, Set_Property, Database_Services, Extract_SI_Keys
DECLARE SUBROUTINE Logging_Services
$INSERT MSG_EQUATES
$INSERT WO_LOG_EQU
$INSERT RDS_EQUATES
$INSERT WM_IN_EQUATES
$INSERT WO_MAT_EQUATES
$INSERT REACT_RUN_EQUATES
$INSERT APP_INSERTS
LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WM_IN'
LogDate = Oconv(Date(), 'D4/')
LogTime = Oconv(Time(), 'MTS')
LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' Release Error Log.csv'
Headers = 'Logging DTM':@FM:'Error':@FM:'NumAttempts':@FM:'WONo':@FM:'WOStep':@FM:'CassNo':@FM:'WaferQty'
objLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, Comma$, Headers, '', False$, False$)
LoggingDTM = LogDate : ' ' : LogTime ; // Logging DTM
ErrTitle = 'Error in Stored Procedure "obj_WM_In"'
ErrorMsg = ''
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 = 'RemainingSlots' ; GOSUB RemainingSlots
CASE Method = 'RemoveWafer' ; GOSUB RemoveWafer
CASE Method = 'ReplaceWafer' ; GOSUB ReplaceWafer
CASE Method = 'AddWafer' ; GOSUB AddWafer
CASE Method = 'NCRNos' ; GOSUB NCRNos
CASE Method = 'RebuildUnload' ; GOSUB RebuildUnload
CASE Method = 'RemProdTW' ; GOSUB RemProdTW
CASE Method = 'RepProdTW' ; GOSUB RepProdTW
CASE Method = 'RunProdTest' ; GOSUB RunProdTest
CASE 1
NULL
END CASE
IF ErrorMsg NE '' THEN
Set_Status(-1,ErrTitle:@SVM:ErrorMsg)
END
RETURN Result
* * * * * * *
Create:
* * * * * * *
WONo = Parms[1,@RM]
WOStep = Parms[COL2()+1,@RM]
CassNo = Parms[COL2()+1,@RM]
WaferQty = Parms[COL2()+1,@RM]
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 WaferQty = '' THEN ErrorMsg = 'Null Parameter "WaferQty" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
WMInKey = WONo:'*':WOStep:'*':CassNo
WMInRec = ''
FOR I = 1 TO WaferQty
WMInRec<WM_IN_SLOT_NO$,I> = I
NEXT I
Done = False$
NumAttempts = 0
Loop
NumAttempts += 1
Database_Services('WriteDataRow', 'WM_IN', WMInKey, WMInRec)
If Error_Services('HasError') then
// Log the error
LogData = ''
LogData<1> = LoggingDTM
LogData<2> = Error_Services('GetMessage')
LogData<3> = NumAttempts
LogData<4> = WONo
LogData<5> = WOStep
LogData<6> = CassNo
LogData<7> = WaferQty
Logging_Services('AppendLog', objLog, LogData, @RM, @FM)
end else
LogData = ''
LogData<1> = LoggingDTM
LogData<2> = 'Success'
LogData<3> = NumAttempts
LogData<4> = WONo
LogData<5> = WOStep
LogData<6> = CassNo
LogData<7> = WaferQty
Logging_Services('AppendLog', objLog, LogData, @RM, @FM)
Done = True$
end
Until ( (NumAttempts EQ 10) or (Done EQ True$) )
Repeat
WMInRec = Database_Services('ReadDataRow', 'WM_IN', WMInKey)
If WMInRec EQ '' then
// Record did not write to the database
LogData = ''
LogData<1> = LoggingDTM
LogData<2> = WMInKey
LogData<3> = WMInRec
LogData<4> = 'Record does not exist after obj_WM_IN("Create") call.'
Machine = Environment_Services('GetServer')
If Machine NE 'MESSA01EC' then
EmailAddr = 'dstieber@srpcs.com,6613649828@txt.att.net'
EmailMsg = 'WM_IN record ':WMInKey:' does not exist after obj_WM_IN("Create") call.'
Logging_Services('AppendLog', ObjLog, LogData, @RM, @FM, False$, EmailAddr, EmailMsg)
end else
Logging_Services('AppendLog', ObjLog, LogData, @RM, @FM, False$)
end
end
* obj_Tables('WriteRec','WM_IN':@RM:WMInKey:@RM:@RM:WMInRec)
RETURN
* * * * * * *
Delete:
* * * * * * *
WMInKeys = Parms[1,@RM]
IF WMInKeys = '' THEN RETURN
NCRs = XLATE('WM_IN',WMInKeys,'NCR_NOS','X')
CONVERT @FM TO @VM IN NCRs
TestString = NCRs
CONVERT @VM TO '' IN TestString
IF TestString NE '' THEN
FOR I = 1 TO COUNT(NCRs,@VM) + (NCRs NE '')
IF NCRs<1,I> NE '' THEN
Result<1,-1> = WMInKeys<1,I> ;* Return list of WMInKeys that have started processing and cannot be deleted
END
NEXT I
ErrorMsg = 'Material has been rejected'
RETURN
END
Set_Status(0)
WMiParms = 'WM_IN'
LockedWMInKeys = ''
FOR I = 1 TO COUNT(WMInKeys,@VM) + (WMInKeys NE '')
WMInKey = WMInKeys<1,I>
WMiParms = FieldStore(WMiParms, @RM, 2, 1, WMInKey)
obj_Tables('LockRec',WMiParms)
IF Get_Status(errCode) THEN
FOR N = 1 TO COUNT(LockedWMInKeys,@VM) + (LockedWMInKeys NE '')
WMiParms = FieldStore(WMiParms, @RM, 2, 1, LockedWMInKeys<1,N>)
obj_Tables('UnlockRec',WMiParms) ;* Unlock everything locked up to here
NEXT N
ErrorMsg = 'Unable to lock RDS ':QUOTE(WMInKey):' for delete.'
RETURN
END ELSE
LockedWMInKeys<1,I> = WMInKey
END
NEXT I
TableVar = FIELD(WMiParms,@RM,3,1)
FOR I = 1 TO COUNT(WMInKeys,@VM) + (WMInKeys NE '')
WMInKey = WMInKeys<1,I>
WMiParms = 'WM_IN':@RM:WMInKey:@RM:TableVar:@RM
obj_Tables('DeleteRec',WMiParms) ;* Deletes and removes the lock
NEXT I
RETURN
* * * * * * *
CurrStatus:
* * * * * * *
WMInKey = Parms[1,@RM]
WMInRec = Parms[COL2()+1,@RM]
WOMatRec = Parms[COL2()+1,@RM]
IF WMInKey = '' THEN RETURN
IF WMInRec = '' THEN WMInRec = XLATE('WM_IN',WMInKey,'','X')
*IF WMInRec = '' THEN RETURN
IF WMInRec<WM_IN_VOID$> = 1 THEN
Result = 'VOID'
RETURN
END
* Check for completion or abnormal condition
IF WOMatRec = '' THEN
WONo = WMInKey[1,'*']
CassNo = WMInKey[-1,'B*']
WOMatKey = WONo:'*':CassNo
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
END
IF WOMatRec<WO_MAT_HOLD$> = 1 AND WOMatRec<WO_MAT_HOLD_ENTITY$,1> = 'WM_IN' THEN
Result = 'HOLD'
RETURN
END
GOSUB NCRNos
NCRNos = Result
Result = ''
NCRStatuses = XLATE('NCR',NCRNos,7,'X')
IF INDEX(NCRStatuses,'O',1) THEN
Result = 'NCR' ;* Open NCR associated with box
RETURN
END
* Check for sequential status points
RemoveCount = 0
SlotCount = COUNT(WMInRec<WM_IN_SLOT_NO$>,@VM) + (WMInRec<WM_IN_SLOT_NO$> NE '')
FOR I = 1 TO SlotCount
IF (WMInRec<WM_IN_RDS_NO$,I> NE '' OR WMInRec<WM_IN_SLOT_NCR$,I> NE '') THEN RemoveCount += 1
NEXT I
IF RemoveCount = SlotCount THEN
Result = 'MT' ;* Empty
RETURN
END
/*
IF RemoveCount = 0 THEN
PreClean = XLATE('WM_IN',WMInKey,'PRE_CLEAN','X')
IF PreClean[1,2] = 'No' OR PreClean = '' THEN
NULL
END ELSE
Result = 'PREC' ;* Post Clean if Required
RETURN
END
END
*/
Result = 'RFW' ;* Changed 10/27/2011
RETURN
* * * * * * *
RemainingSlots:
* * * * * * *
WONo = Parms[1,@RM]
WOStep = Parms[COL2()+1,@RM]
CassNos = Parms[COL2()+1,@RM]
IF WONo = '' THEN ErrorMsg = 'Null Parameter "WONo" passed to routine. (':Method:')'
IF WOStep = '' THEN ErrorMsg = 'Null Parameter "WOStep" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
IF CassNos = '' THEN
CassNos = XLATE('WO_LOG',WONo,'WO_MAT_CASS_NO','X')
END
CassCnt = COUNT(CassNos,@VM) + (CassNos NE '')
* Start Counting at the last box and work backward
FOR I = CassCnt TO 1 STEP -1
CassNo = CassNos<1,I>
WMInRec = XLATE('WM_IN',WONo:'*':WOStep:'*':CassNo,'','X')
WOMatRec = XLATE('WO_MAT',WONo:'*':CassNo,'','X')
IF WOMatRec<WO_MAT_HOLD$> = 1 AND WOMatRec<WO_MAT_HOLD_ENTITY$,1> = 'WM_IN' THEN
NULL ;* Box is on hold - skip it
END ELSE
SlotCnt = COUNT(WMInRec<WM_IN_SLOT_NO$>,@VM) + (WMInRec<WM_IN_SLOT_NO$> NE '')
FOR N = SlotCnt TO 1 STEP -1
SlotNo = WMInRec<WM_IN_SLOT_NO$,N>
IF WMInRec<WM_IN_RDS_NO$,N> = '' AND WMInRec<WM_IN_SLOT_NCR$,N> = '' THEN
WMIWfrKey = WONo:'*':WOStep:'*':CassNo:'*':SlotNo
IF NOT(RowExists('WMI_WFRS', WMIWfrKey)) THEN
Result = INSERT(Result,1,0,0,I:@VM:N) ;* Plate-o-lator (LIFO) style
END
END
NEXT N
END
NEXT I
RETURN
* * * * * * *
RemoveWafer:
* * * * * * *
WONo = Parms[1,@RM]
WOStep = Parms[COL2()+1,@RM]
CassNo = Parms[COL2()+1,@RM]
SlotNos = Parms[COL2()+1,@RM]
RDSNos = Parms[COL2()+1,@RM]
PocketNos = Parms[COL2()+1,@RM]
Zones = Parms[COL2()+1,@RM]
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 SlotNos = '' THEN ErrorMsg = 'Null Parameter "SlotNos" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
SlotCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
FOR I = 1 TO SlotCnt
RDSNo = RDSNos<1,I>
PocketNo = PocketNos<1,I>
Zone = Zones<1,I>
IF RDSNo = '' THEN ErrorMsg = 'Null Parameter Value (':I:') in "RDSNos" passed to routine. (':Method:')'
IF PocketNo = '' THEN ErrorMsg = 'Null Parameter Value (':I:') in "PocketNos" passed to routine. (':Method:')'
IF Zone = '' THEN ErrorMsg = 'Null Parameter Value (':I:') in "Zones" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
NEXT I
otParms = 'WM_IN':@RM:WONo:'*':WOStep:'*':CassNo
WMInRec = obj_Tables('ReadRec',otParms)
IF Get_Status(errCode) THEN RETURN
FirstWafer = 0
FirstRDSNo = ''
LoadDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
WfrIDs = '' ;* Added 9/7/2016 JCH
RunLocs = '' ;* Added 9/7/2016 JCH
CurrSlotIDs = '' ;* Added 9/7/2016 JCH
FOR I = 1 TO SlotCnt
SlotNo = SlotNos<1,I>
IF SlotNo = 1 THEN
FirstWafer = 1
FirstRDSNo = RDSNos<1,I>
END
LOCATE SlotNo IN WMInRec<WM_IN_SLOT_NO$> USING @VM SETTING Pos THEN
ReactNo = XLATE('RDS',RDSNos<1,I>,RDS_REACTOR$,'X')
WMInRec<WM_IN_RDS_NO$,Pos> = RDSNos<1,I>
WMInRec<WM_IN_POCKET_NO$,Pos> = PocketNos<1,I>
WMInRec<WM_IN_ZONE$,Pos> = Zones<1,I>
WfrIDs<1,-1> = WONo:'*':CassNo:'*':SlotNo ;* Added 9/7/2016 JCH
RunLocs<1,-1> = RDSNos<1,I>:'*':PocketNos<1,I>:'*':Zones<1,I> ;* Added 9/7/2016 JCH
CurrSlotIDs<1,-1> = WONo:'*':CassNo:'*':SlotNo ;* Added 9/7/2016 JCH
* * * * Added 3/22/2016 JCH - wafer history * * * *
Parms = WONo:'*':CassNo:'*':SlotNo:@RM ;* WfrID
Parms := LoadDTM:@RM ;* EventDtm
Parms := @USER4:@RM ;* EventBy
Parms := 'LOAD':@RM ;* Event
Parms := '':@RM ;* NewSlotID
Parms := RDSNos<1,I>:'*':PocketNos<1,I>:'*':Zones<1,I>:@RM ;* RunLoc
Parms := '':@RM ;* NCRNo
Parms := '':@RM ;* TWUse
Parms := WONo:'*':CassNo:'*':SlotNo:@RM ;* CurrSlotID
Parms := 'R':ReactNo:@RM ;* NewToolID (Load Tool)
Parms := '':@RM ;* CurrToolID
Parms := '':@RM ;* NewInvLoc
Parms := '':@RM ;* CurrInvLoc
Parms := 'I' ;* Wfr Side
obj_WO_Wfr('AddEvent',Parms)
END
NEXT I
/*
* * * * * Added 9/7/2016 JCH * * * * * *
IF WfrIDs NE '' THEN
Parms = WfrIDs:@RM ;* WfrID - mv
Parms := LoadDTM:@RM ;* EventDtm
Parms := @USER4:@RM ;* EventBy
Parms := 'LOAD':@RM ;* Event
Parms := '':@RM ;* NewSlotID - mv
Parms := RunLocs:@RM ;* RunLoc - mv
Parms := '':@RM ;* NCRNo
Parms := '':@RM ;* TWUse
Parms := CurrSlotIDs:@RM ;* CurrSlotID - mv
Parms := 'R':ReactNo:@RM ;* NewToolID (Load Tool)
Parms := '':@RM ;* CurrToolID
Parms := '':@RM ;* NewInvLoc
Parms := '':@RM ;* CurrInvLoc
Parms := 'I' ;* Wfr Side
obj_WO_Wfr('AddEvent',Parms)
END
*/
otParms = FieldStore(otParms,@RM,4,0,WMInRec) ;* Put record in 4th field of OtParms
obj_Tables('WriteRec',otParms)
* Added 11/8/2012 JCH *
WIPStartDTM = XLATE('WO_MAT',WONo:'*':CassNo,WO_MAT_WIP_START_DTM$,'X')
DTMSecond = '0.0000115741' ;*********** Constant for 1 Second in DTM internal format
IF WIPStartDTM = '' THEN
CurrTime = Time()
CurrDTM = OCONV(Date(),'D4/'):' ':OCONV(CurrTime,'MTS')
CurrDTM1 = OCONV(Date(),'D4/'):' ':OCONV(CurrTime + 1,'MTS')
obj_Post_Log('Create','WO_MAT':@RM:WONo:'*':CassNo:@RM:WO_MAT_WIP_START_DTM$:@RM:ICONV(CurrDTM,'DT'))
END ELSE
CurrDTM = OCONV(WipStartDTM,'DT4/^S') ;* CurrDTM in OCONV format
CurrDTM1 = OCONV(WipStartDTM + DTMSecond,'DT4/^S')
END
* Added 2/4/2013 by JCH
IF FirstWafer THEN
Reactor = XLATE('REACT_RUN',FirstRDSNo,REACT_RUN_REACTOR$ ,'X')
IF Reactor = '' THEN
ReactWH = 'CR'
ReactLoc = 'EPR'
END ELSE
ReactWH = XLATE('REACTOR',Reactor,'TOOL_WH','X')
ReactLoc = XLATE('REACTOR',Reactor,'TOOL_LOC','X')
END
/*
BEGIN CASE
CASE Reactor = '40' OR Reactor = '42' ; ToolID = 'R4042'
CASE Reactor = '44' OR Reactor = '46' ; ToolID = 'R4446'
CASE Reactor = '48' OR Reactor = '50' ; ToolID = 'R4850'
CASE Reactor = '52' OR Reactor = '54' ; ToolID = 'R5254'
CASE 1 ; ToolID = ''
END CASE
*/
LogFile = 'WO_MAT' ; WOMLParms = LogFile:@RM
LogDTM = CurrDTM ; WOMLParms := LogDTM:@RM
Action = WOStep:'VER' ; WOMLParms := Action:@RM
WhCd = 'CR' ; WOMLParms := WhCd:@RM
LocCd = 'EPR' ; WOMLParms := LocCd:@RM
WONos = WONo ; WOMLParms := WONos:@RM
CassNos = CassNo ; WOMLParms := CassNos:@RM
UserID = @USER4 ; WOMLParms := UserID:@RM
Tags = '' ; WOMLParms := Tags:@RM
ToolID = '' ; WOMLParms := ToolID
obj_WO_Mat_Log('Create',WOMLParms) ;* Stage PSTC log entry
IF Get_Status(errCode) THEN
RETURN
END
Reactor = XLATE('REACT_RUN',FirstRDSNo,REACT_RUN_REACTOR$ ,'X')
IF Reactor = '' THEN
ReactWH = 'CR'
ReactLoc = 'EPR'
END ELSE
ReactWH = XLATE('REACTOR',Reactor,'TOOL_WH','X')
ReactLoc = XLATE('REACTOR',Reactor,'TOOL_LOC','X')
END
BEGIN CASE
CASE Reactor = '40' OR Reactor = '42' ; ToolID = 'R4042'
CASE Reactor = '44' OR Reactor = '46' ; ToolID = 'R4446'
CASE Reactor = '48' OR Reactor = '50' ; ToolID = 'R4850'
CASE Reactor = '52' OR Reactor = '54' ; ToolID = 'R5254'
END CASE
LogFile = 'WO_MAT' ; WOMLParms = LogFile:@RM
LogDTM = CurrDTM1 ; WOMLParms := LogDTM:@RM
Action = WOStep:'LOAD' ; WOMLParms := Action:@RM
WhCd = ReactWH ; WOMLParms := WhCd:@RM
LocCd = ReactLoc ; WOMLParms := LocCd:@RM
WONos = WONo ; WOMLParms := WONos:@RM
CassNos = CassNo ; WOMLParms := CassNos:@RM
UserID = @USER4 ; WOMLParms := UserID:@RM
Tags = '' ; WOMLParms := Tags:@RM
*ToolID = '' ; WOMLParms := ToolID
obj_WO_Mat_Log('Create',WOMLParms) ;* Stage PSTC log entry
IF Get_Status(errCode) THEN
RETURN
END
END
RETURN
* * * * * * *
ReplaceWafer:
* * * * * * *
WONo = Parms[1,@RM]
WOStep = Parms[COL2()+1,@RM]
CassNo = Parms[COL2()+1,@RM]
SlotNos = Parms[COL2()+1,@RM]
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 SlotNos = '' THEN ErrorMsg = 'Null Parameter "SlotNos" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
Set_Status(0)
otParms = 'WM_IN':@RM:WONo:'*':WOStep:'*':CassNo
WMInRec = obj_Tables('ReadRec',otParms)
IF Get_Status(errCode) THEN RETURN
ReplaceDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
WfrIDs = '' ;* Added 9/7/2016 JCH
NewSlotIDs = '' ;* Added 9/7/2016 JCH
FOR I = 1 TO COUNT(SlotNos,@VM) + (SlotNos NE '')
SlotNo = SlotNos<1,I>
LOCATE SlotNo IN WMInRec<WM_IN_SLOT_NO$> USING @VM SETTING Pos THEN
RdsNo = WMInRec<WM_IN_RDS_NO$,Pos>
ReactNo = XLATE('RDS',RdsNo,RDS_REACTOR$,'X')
WMInRec<WM_IN_RDS_NO$,Pos> = ''
WMInRec<WM_IN_POCKET_NO$,Pos> = ''
WMInRec<WM_IN_ZONE$,Pos> = ''
WfrIDs<1,-1> = WONo:'*':CassNo:'*':SlotNo
NewSlotIDs<1,-1> = WONo:'*':CassNo:'*':SlotNo
* * * * Added 3/22/2016 JCH - wafer history * * * *
Parms = WONo:'*':CassNo:'*':SlotNo:@RM ;* WfrID
Parms := ReplaceDTM:@RM ;* EventDtm
Parms := @USER4:@RM ;* EventBy
Parms := 'REPLACE':@RM ;* Event
Parms := WONo:'*':CassNo:'*':SlotNo:@RM ;* NewSlotID
Parms := '':@RM ;* RunLoc
Parms := '':@RM ;* NCRNo
Parms := '':@RM ;* TWUse
Parms := '':@RM ;* CurrSlotID
Parms := '':@RM ;* NewToolID (Load Tool)
Parms := 'R':ReactNo:@RM ;* CurrToolID (Unload Tool)
Parms := '':@RM ;* NewInvLoc
Parms := '':@RM ;* CurrInvLoc
Parms := 'I' ;* Wfr Side
obj_WO_Wfr('AddEvent',Parms)
END
NEXT I
/*
IF WfrIDs NE '' THEN
* * * * Added 9/7/2016 JCH - wafer history * * * *
Parms = WfrIDs:@RM ;* WfrID - mv
Parms := ReplaceDTM:@RM ;* EventDtm
Parms := @USER4:@RM ;* EventBy
Parms := 'REPLACE':@RM ;* Event
Parms := NewSlotIDs:@RM ;* NewSlotID - mv
Parms := '':@RM ;* RunLoc - mv
Parms := '':@RM ;* NCRNo
Parms := '':@RM ;* TWUse
Parms := '':@RM ;* CurrSlotID - mv
Parms := '':@RM ;* NewToolID (Load Tool)
Parms := 'R':ReactNo:@RM ;* CurrToolID (Unload Tool)
Parms := '':@RM ;* NewInvLoc
Parms := '':@RM ;* CurrInvLoc
Parms := 'I' ;* Wfr Side
obj_WO_Wfr('AddEvent',Parms)
END
*/
otParms = FieldStore(otParms,@RM,4,0,WMInRec) ;* Put record in 4th field of OtParms
obj_Tables('WriteRec',otParms)
RETURN
* * * * * * *
AddWafer:
* * * * * * *
WONo = Parms[1,@RM]
WOStep = Parms[COL2()+1,@RM]
CassNo = Parms[COL2()+1,@RM]
SlotNo = Parms[COL2()+1,@RM]
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 SlotNo = '' THEN ErrorMsg = 'Null Parameter "SlotNo" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
otParms = 'WM_IN':@RM:WONo:'*':WOStep:'*':CassNo
WMInRec = obj_Tables('ReadRec',otParms)
LOCATE SlotNo IN WMInRec<WM_IN_SLOT_NO$> USING @VM SETTING Pos THEN
WMInRec<WM_IN_SLOT_NCR$,Pos> = '' ;* Clears NCR numbers
END
*WMInRec<WM_IN_SLOT_NO$,SlotNo> = SlotNo ;* Slot numbers are the same as the position in the list.
otParms = FieldStore(otParms,@RM,4,0,WMInRec) ;* Put record in 4th field of OtParms
obj_Tables('WriteRec',otParms)
RETURN
* * * * * * *
NCRNos:
* * * * * * *
IF NOT(ASSIGNED(WMInKey)) THEN
* Called externally
WMInKey = Parms[1,@RM]
WMInRec = Parms[COL2()+1,@RM]
END
IF WMInKey = '' THEN RETURN
IF WMInRec = '' THEN WMInRec = XLATE('WM_IN',WMInKey,'','X')
SlotNCRs = WMInRec<WM_IN_SLOT_NCR$>
FOR I = 1 TO COUNT(SlotNCRs,@VM) + (SlotNCRs NE '')
SlotNCR = SlotNCRs<1,I>
IF SlotNCR NE '' THEN
LOCATE SlotNCR in Result BY 'AR' USING @VM SETTING Pos ELSE
Result = INSERT(Result,1,Pos,0,SlotNCR)
END
END
NEXT I
RETURN
* * * * * * *
RunProdTest:
* * * * * * *
WMIKey = Parms[1,@RM]
WMIRec = Parms[COL2()+1,@RM]
IF WMIKey = '' THEN RETURN
IF WMIRec = '' THEN
WMIRec = XLATE('WM_IN',WMIKey,'','X')
END
IF WMIRec = '' THEN RETURN
CassNo = FIELD(WMIKey,'*',3)
SlotNos = WMIRec<WM_IN_SLOT_NO$>
SlotCnt = COUNT(SlotNos,@VM) + ( SlotNos NE '')
Ans = ''
FOR I = 1 TO SlotCnt
RDSNo = WMIRec<WM_IN_RDS_NO$,I>
RDSRec = XLATE('RDS',RDSNo,'','X')
Pockets = RDSRec<RDS_POCKET$>
pktCnt = COUNT(Pockets,@VM) + (Pockets NE '')
FOR N = 1 TO pktCnt
InCassNo = RDSRec<RDS_IN_CASS_NO$,N>
InSlotNo = RDSRec<RDS_IN_SLOT_NO$,N>
PktChar = RDSRec<RDS_POCKET_CHAR$,N>
WfrChar = RDSRec<RDS_WAFER_CHAR$,N>
IF InCassNo = CassNo AND InSlotNo = I THEN
IF PktChar = 'TEST' AND WfrChar = 'PROD' THEN
Ans<1,I> = 1
END ELSE
Ans<1,I> = ''
END
END ;* End of check for matching Cassette and Slot number in the RDS
NEXT N
NEXT I
Result = Ans
RETURN
* * * * * * *
RebuildUnload:
* * * * * * *
WMInID = Parms[1,@RM]
IF WMInID = '' THEN RETURN
WONo = WMInID[1,'*']
ProcStep = WMInID[COL2()+1,'*']
CassNo = WMInID[COL2()+1,'*']
Update_Index ("RDS", "WO", "")
Extract_SI_Keys( 'RDS', 'WO', WONo, RDSNos ) ;* Original Code
WOBoxCnt = COUNT( RDSNos, @VM ) + ( RDSNos NE '' )
FOR I = 1 TO WOBoxCnt
RDSNo = RDSNos<1,I>
RDSRec = XLATE('RDS',RDSNo,'','X')
IF FIELD(WMInID,'*',1,2) = RDSRec<RDS_WO_STEP_KEY$> THEN
A = RDSRec<RDS_IN_CASS_NO$>
IF INDEX(RDSRec<RDS_IN_CASS_NO$>,CassNo,1) THEN
otParms = 'WM_IN':@RM:WMInID
WMInRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
FOR N = 1 TO COUNT(RDSRec<RDS_IN_CASS_NO$>,@VM) + (RDSRec<RDS_IN_CASS_NO$> NE '')
IF RDSRec<RDS_IN_CASS_NO$,N> = CassNo THEN
InSlotNo = RDSRec<RDS_IN_SLOT_NO$,N>
WMInRec<WM_IN_SLOT_NO$,InSlotNo> = InSlotNo
WMInRec<WM_IN_RDS_NO$,InSlotNo> = RDSNo
WMInRec<WM_IN_POCKET_NO$,InSlotNo> = RDSRec<RDS_POCKET$,N>
WMInRec<WM_IN_ZONE$,InSlotNo> = RDSRec<RDS_ZONE$,N>
END
NEXT N
otParms = FIELDSTORE(otParms,@RM,4,0,WMInRec)
obj_Tables('WriteRec',otParms)
END
END
NEXT I
RETURN
* * * * * * *
RemProdTW:
* * * * * * *
WONo = Parms[1,@RM]
WOCassNo = Parms[COL2()+1,@RM]
MetNo = Parms[COL2()+1,@RM]
SlotNos = Parms[COL2()+1,@RM]
IF WONo = '' THEN ErrorMsg = 'Null Parm "WONo" passed to routine. (':Method:')'
IF WOCassNo = '' THEN ErrorMsg = 'Null Parm "WOCassNo" passed to routine. (':Method:')'
IF MetNo = '' THEN ErrorMsg = 'Null Parm "MetNo" passed to routine. (':Method:')'
IF SlotNos = '' THEN ErrorMsg = 'Null Parm "SlotNos" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
StepNo = 1
otParms = 'WM_IN':@RM:WONo:'*':StepNo:'*':WOCassNo
WMInRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
PulledWaferIDs = ''
IF Get_Status(errCode) THEN
NULL
END ELSE
SlotCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
PulledWaferIDs = ''
FOR I = 1 TO SlotCnt
SlotNo = SlotNos<1,I>
PulledWaferIDs<1,-1> = WONo:'.':WOCassNo:'.':SlotNo
WMInRec<WM_IN_SLOT_MET_NO$,SlotNo> = MetNo
NEXT I
otParms = FIELDSTORE(otParms,@RM,4,0,WMInRec)
obj_Tables('WriteRec',otParms)
END
Result = PulledWaferIDs
RETURN
* * * * * * *
RepProdTW:
* * * * * * *
WONo = Parms[1,@RM]
WOCassNo = Parms[COL2()+1,@RM]
MetNo = Parms[COL2()+1,@RM]
WaferIDs = Parms[COL2()+1,@RM]
IF NOT(ASSIGNED(WONo)) THEN ErrorMsg = 'Unassigned Parm "WONo" passed to routine. (':Method:')'
IF NOT(ASSIGNED(WOCassNo)) THEN ErrorMsg = 'Unassigned Parm "WOCassNo" passed to routine. (':Method:')'
IF NOT(ASSIGNED(MetNo)) THEN ErrorMsg = 'Unassigned Parm "MetNo" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
StepNo = 1
otParms = 'WM_IN':@RM:WONo:'*':StepNo:'*':WOCassNo
WMInRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF WaferIDs = '' THEN
MetNos = WMInRec<WM_IN_SLOT_MET_NO$>
WaferIDCnt = COUNT(MetNos,@VM) + (MetNos NE '')
FOR I = 1 TO WaferIDCnt
IF WMInRec<WM_IN_SLOT_MET_NO$,I> = MetNo THEN
WMInRec<WM_IN_SLOT_MET_NO$,I> = ''
END
NEXT I
END ELSE
WaferIDCnt = COUNT(WaferIDs,',') + (WaferIDs NE '')
FOR I = 1 TO WaferIDCnt
WaferID = FIELD(WaferIDs,',',I)
SlotNo = WaferID[-1,'B.']
WMInRec<WM_IN_SLOT_MET_NO$,SlotNo> = ''
NEXT I
END
otParms = FIELDSTORE(otParms,@RM,4,0,WMInRec)
obj_Tables('WriteRec',otParms)
RETURN