open-insight/LSL2/STPROC/OBJ_WM_OUT.txt
2025-02-20 18:23:06 +01:00

2012 lines
61 KiB
Plaintext

COMPILE FUNCTION obj_WM_Out(Method,Parms)
/*
Methods for WM_OUT table
05/01/2005 JCH - Initial Coding
Properties:
Methods:
Create(WONo,ProcStep,CassNo,WfrQty) ;* Create new record
NextEmptySlot(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_UNLOAD_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 obj_RDS2, obj_WM_Out, Delete, Signature_Services, Environment_Services, Logging_Services
DECLARE FUNCTION Database_Services
DECLARE SUBROUTINE Set_Status, Msg, obj_Tables, Send_Dyn, obj_WO_Step, obj_RDS_Layer, obj_RDS_Test, Btree.Extract
DECLARE SUBROUTINE Extract_SI_Keys, obj_WM_Out, obj_WO_Mat, obj_Post_Log, obj_WO_Mat_Log, ErrMsg, obj_WO_Wfr
DECLARE SUBROUTINE Logging_Services, Material_Services, Database_Services, Update_Index, Work_Order_Services
$INSERT MSG_EQUATES
$INSERT APP_INSERTS
$INSERT WO_LOG_EQU
$INSERT WO_STEP_EQU
$INSERT WO_MAT_EQUATES
$INSERT EPI_SUSCEPTOR_EQUATES
$INSERT RDS_EQUATES
$INSERT WM_OUT_EQUATES
$INSERT PROD_SPEC_EQUATES
$INSERT QUOTE_SPEC_EQU
$INSERT SURFACE_SCAN_EQUATES
$INSERT CLEAN_INSP_EQUATES
$INSERT WMO_WFRS_EQUATES
$INSERT REACT_RUN_EQUATES
ErrTitle = 'Error in Stored Procedure "obj_WM_Out"'
ErrorMsg = ''
ErrCode = ''
LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WM_OUT'
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 : 'WMOutKey' : @FM : 'Calculated Value' : @FM : 'Physical Value'
objCurrStatusLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, Comma$, Headers, '', False$, False$)
LoggingDTM = LogDate : ' ' : LogTime ; // Logging DTM
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'
objReleaseLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, Comma$, Headers, '', False$, False$)
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 = 'CRComp' ; GOSUB CRComp ;* Cleanroom complete flag
CASE Method = 'NextOpenSlots' ; GOSUB NextOpenSlots
CASE Method = 'SlotStatus' ; GOSUB SlotStatus
CASE Method = 'AddWafer' ; GOSUB AddWafer
CASE Method = 'RemoveWafer' ; GOSUB RemoveWafer
CASE Method = 'AddShip' ; GOSUB AddShip
CASE Method = 'RemShip' ; GOSUB RemShip
CASE Method = 'ClearLoad' ; GOSUB ClearLoad
CASE Method = 'RDSSlots' ; GOSUB RDSSlots
CASE Method = 'InCassData' ; GOSUB InCassData
CASE Method = 'AddMakeupWafers' ; GOSUB AddMakeupWafers
CASE Method = 'SubMakeupWafers' ; GOSUB SubMakeupWafers
CASE Method = 'RemMakeupWafers' ; GOSUB RemMakeupWafers
CASE Method = 'RepMakeupWafers' ; GOSUB RepMakeupWafers
CASE Method = 'CassRDSNos' ; GOSUB CassRDSNos
CASE Method = 'CassRDSWfrCnts' ; GOSUB CassRDSWfrCnts
CASE Method = 'GetPartNoQtys' ; GOSUB GetPartNoQtys
CASE Method = 'GetLotNos' ; GOSUB GetLotNos
CASE Method = 'GetOrderItems' ; GOSUB GetOrderItems
CASE Method = 'NCRNos' ; GOSUB NCRNos
CASE Method = 'RebuildLoad' ; GOSUB RebuildLoad
CASE Method = 'RemSlots' ; GOSUB RemSlots
CASE Method = 'ConvertCleanInsp' ; GOSUB ConvertCleanInsp
CASE Method = 'WfrsOut' ; GOSUB WfrsOut
CASE Method = 'EpiReactNo' ; GOSUB EpiReactNo
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]
NewCassNos = Parms[COL2()+1,@RM]
CassLoadQty = 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 NewCassNos = '' THEN ErrorMsg = 'Null Parameter "NewCassNos" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
PSNo = XLATE('WO_STEP',WONo:'*':WOStep,1,'X')
SubstrateSpec = XLATE('PROD_SPEC',PSNo,PROD_SPEC_SPEC_SUBSTRATE$,'X') ;*********************************************************************************************
ReactorType = XLATE('PROD_SPEC',PSNo,PROD_SPEC_REACTOR_TYPE$,'X') ;* 9/2/2014 JCH Not used in this program
PromiseShipDt = XLATE('WO_LOG',WONo,WO_LOG_PROMISE_SHIP_DT$,'X')
SubPostClean = SubstrateSpec<1,QSSubPostClean$> ;***************************************************************************************
*PSType = SubstrateSpec<1,QSSubSpecType$> ;* Deprecated 8/22/2012 JCH
PSType = XLATE('PROD_SPEC',PSNo,'SPEC_TYPE','X') ;* Added 8/22/2012 JCH
IF CassLoadQty = '' THEN
IF PSType = 'Q' THEN
SusceptorPockets = ''
WaferSize = SubstrateSpec<1,QSSubWaferSize$> ;*Qual runs use the susceptor pocket count as the outbound wafer qty
IF WaferSize = '125 mm 5 in' THEN
SusceptorPockets = XLATE('EPI_SUSCEPTOR','5',EPI_SUSCEPTOR_POCKET_NO$,'X')
END
IF WaferSize = '150 mm 6 in' THEN
SusceptorPockets = XLATE('EPI_SUSCEPTOR','6',EPI_SUSCEPTOR_POCKET_NO$,'X')
END
IF WaferSize = '200 mm 8 in' THEN
SusceptorPockets = XLATE('EPI_SUSCEPTOR','8',EPI_SUSCEPTOR_POCKET_NO$,'X')
END
IF SusceptorPockets THEN CassLoadQty = SusceptorPockets[-1,'B':@VM]
END ELSE
CassLoadQty = 25
END
END
WORec = XLATE('WO_LOG',WONo,'','X')
InboundWaferQty = 0
FOR I = 1 TO COUNT(NewCassNos,@VM) + (NewCassNos NE '')
NewCassNo = NewCassNos<1,I>
CassWfrQty = XLATE('WO_MAT',WONo:'*':NewCassNo,WO_MAT_WAFER_QTY$,'X')
InboundWaferQty += CassWfrQty
NEXT I
WMOutKeys = XLATE('WO_STEP',WONo:'*':WOStep,WO_STEP_WM_OUT_KEYS$,'X')
IF WMOutKeys = '' THEN
WMOStartBox = 1
WMOStartSlot = 1
END ELSE
LastBoxOut = WMOutKeys[-1,'B':@VM]
LastWMORec = XLATE('WM_OUT',LastBoxOut,'','X')
LastBoxLastSlot = LastWMORec<WM_OUT_SLOT_NO$>[-1,'B':@VM]
IF LastBoxLastSlot < CassLoadQty THEN
WMOStartBox = FIELD(LastBoxOut,'*',3) ;* Start IN the last box
WMOStartSlot = LastBoxLastSlot + 1 ;* Start with first slot past current and less than Load Qty
END ELSE
WMOStartBox = FIELD(LastBoxOut,'*',3) + 1 ;* Start with next box
WMOStartSlot = 1 ;* Start with first slot
END
END
WMOCassNo = WMOStartBox
WMOSlotNo = WMOStartSlot
OutOnlyCassIDs = '' ;* List of Outbound only Cassette IDs added 8/12/1011 JCH
LOOP
UNTIL InboundWaferQty = 0
WMOutKey = WONo:'*':WOStep:'*':WMOCassNo
WMOutRec = XLATE('WM_OUT',WMOutKey,'','X') ;* In case there is a partial box
NewBoxFlag = ''
IF WMOutRec = '' THEN NewBoxFlag = 1 ELSE NewBoxFlag = 0
IF NewBoxFlag THEN
WMOutRec<WM_OUT_PROMISE_SHIP_DT$> = PromiseShipDt
WMOutRec<WM_OUT_POST_CLEAN$> = SubPostClean ;****************************************************
WMOutRec<WM_OUT_IN_CLEANROOM$> = 1 ;* Default InCleanRoom flag = 1
END
FOR S = WMOSlotNo TO CassLoadQty
IF WMOutRec<WM_OUT_SLOT_NO$,S> = '' THEN
WMOutRec<WM_OUT_SLOT_NO$,S> = S
InboundWaferQty -= 1
END
UNTIL InboundWaferQty = 0
NEXT S
LastSlotUsed = S
******** Added 4/23/2010 JCH ********
CheckWOMat = XLATE('WO_MAT',WONo:'*':WMOCassNo,'','X')
IF CheckWOMat = '' THEN
obj_WO_Mat('CreateWMO',WONo:@RM:WMOCassNo:@RM:LastSlotUsed) ;* Creates "shell" WO_MAT record with the signature profile in it.
OutOnlyCassIDs<1,-1> = WONo:'*':WMOCassNo ;* Added 8/12/2011 JCH
END
Done = False$
NumAttempts = 0
Loop
NumAttempts += 1
Database_Services('WriteDataRow', 'WM_OUT', WMOutKey, WMOutRec)
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> = WMOCassNo
Logging_Services('AppendLog', objReleaseLog, LogData, @RM, @FM)
end else
LogData = ''
LogData<1> = LoggingDTM
LogData<2> = 'Success'
LogData<3> = NumAttempts
LogData<4> = WONo
LogData<5> = WOStep
LogData<6> = WMOCassNo
Logging_Services('AppendLog', objReleaseLog, LogData, @RM, @FM)
Done = True$
end
Until ( (NumAttempts EQ 10) or (Done EQ True$) )
Repeat
WMOutRec = Database_Services('ReadDataRow', 'WM_OUT', WMOutKey)
If WMOutRec EQ '' then
// Record did not write to the database
LogData = ''
LogData<1> = LoggingDTM
LogData<2> = WMOutKey
LogData<3> = WMOutRec
LogData<4> = 'Record does not exist after obj_WM_OUT("Create") call.'
Machine = Environment_Services('GetServer')
If Machine NE 'MESSA01EC' then
EmailAddr = 'dstieber@srpcs.com,6613649828@txt.att.net'
EmailMsg = 'WM_OUT record ':WMOutKey:' does not exist after obj_WM_OUT("Create") call.'
Logging_Services('AppendLog', objReleaseLog, LogData, @RM, @FM, False$, EmailAddr, EmailMsg)
end else
Logging_Services('AppendLog', objReleaseLog, LogData, @RM, @FM, False$)
end
end
WMOCassNo += 1
WMOSlotNo = 1
REPEAT
Result = OutOnlyCassIDs
RETURN
* * * * * * *
Delete:
* * * * * * *
WMOutKeys = Parms[1,@RM]
IF WMOutKeys = '' THEN RETURN
Set_Status(0)
WMoParms = 'WM_OUT'
LockedWMOutKeys = ''
FOR I = 1 TO COUNT(WMOutKeys,@VM) + (WMOutKeys NE '')
WMOutKey = WMOutKeys<1,I>
WMoParms = FieldStore(WMoParms, @RM, 2, 1, WMOutKey)
obj_Tables('LockRec',WMoParms)
IF Get_Status(errCode) THEN
FOR N = 1 TO COUNT(LockedWMOutKeys,@VM) + (LockedWMOutKeys NE '')
WMiParms = FieldStore(WMoParms, @RM, 2, 1, LockedWMOutKeys<1,N>)
obj_Tables('UnlockRec',WMoParms) ;* Unlock everything locked up to here
NEXT N
ErrorMsg = 'Unable to lock WM_OUT ':QUOTE(WMOutKey):' for delete.'
RETURN
END ELSE
LockedWMOutKeys<1,I> = WMOutKey
END
NEXT I
TableVar = FIELD(WMoParms,@RM,3,1)
FOR I = 1 TO COUNT(WMOutKeys,@VM) + (WMOutKeys NE '')
WMOutKey = WMOutKeys<1,I>
WMoParms = 'WM_OUT':@RM:WMOutKey:@RM:TableVar:@RM
obj_Tables('DeleteRec',WMoParms) ;* Deletes and removes the lock
NEXT I
RETURN
* * * * * * *
CurrStatus:
* * * * * * *
WMOutKey = Parms[1,@RM]
WMOutRec = Parms[COL2()+1,@RM]
WOMatRec = Parms[COL2()+1,@RM]
//IF WMOutKey EQ '170964*1*18' then debug
IF WMOutKey = '' THEN RETURN
IF WMOutRec = '' THEN WMOutRec = XLATE('WM_OUT',WMOutKey,'','X')
* Check for completion or abnormal condition
IF WMOutRec<WM_OUT_VOID$> = 1 THEN
Result = 'VOID'
RETURN
END
CurrLocation = ''
IF WOMatRec = '' THEN
WONo = WMOutKey[1,'*']
CassNo = WMOutKey[-1,'B*']
WOMatKey = WONo:'*':CassNo
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
CurrLocation = XLATE('WO_MAT',WOMatKey,'CURR_LOCATION','X')
END
IF WOMatRec<WO_MAT_HOLD$> = 1 AND WOMatRec<WO_MAT_HOLD_ENTITY$,1> = 'WM_OUT' THEN
Result = 'HOLD' ;* Box is on Hold
RETURN
END
IF WMOutRec<WM_OUT_SHIP_NO$> NE '' THEN
Result = 'SHIP'
RETURN
END
NCRStatuses = XLATE('NCR',WMOutRec<WM_OUT_NCR_KEYS$>,7,'X')
IF INDEX(NCRStatuses,'O',1) THEN
Result = 'NCR' ;* Open NCR associated with box
RETURN
End
* Check for sequential status points
SlotCount = 0
FillCount = 0
NCRCount = 0
FOR I = 1 TO COUNT(WMOutRec<WM_OUT_SLOT_NO$>,@VM) + (WMOutRec<WM_OUT_SLOT_NO$> NE '')
SlotNo = WMOutRec<WM_OUT_SLOT_NO$,I>
RDSNo = WMOutRec<WM_OUT_RDS$,I>
SlotNCRNo = WMOutRec<WM_OUT_SLOT_NCR$,I>
IF SlotNo NE '' THEN SlotCount += 1
IF RDSNo NE '' AND SlotNo NE '' THEN FillCount += 1 ;* 5/6/2010 JCH
IF SlotNCRNo NE '' THEN NCRCount += 1
NEXT I
IF NCRCount = SlotCount AND FillCount = 0 AND WMOutRec<WM_OUT_MAKEUP_BOX$> NE 1 THEN
*Result = 'REJ'
*RETURN
RejectFlag = 1
END ELSE
RejectFlag = 0
END
StepID = ''
SigArray = Signature_Services('GetSigProfile', WOMatKey)
SigProfile = SigArray<1>
Signatures = SigArray<2>
SigDtms = SigArray<3>
* SigProfile = WOMatRec<WO_MAT_SIG_PROFILE$>
* Signatures = WOMatRec<WO_MAT_SIGNATURE$>
* SigDtms = WOMatRec<WO_MAT_SIG_DTM$>
ProfCnt = COUNT(SigProfile,@VM) + (SigProfile NE '')
* Section new on 12/8/2011 JCH
IF RejectFlag = 1 THEN
IF Signatures<1,ProfCnt> NE '' THEN
* This is the final QA signature - nothing else matters
Result = 'REJ'
END ELSE
Result = 'RQA'
END
RETURN
END
FOR I = 1 TO ProfCnt
Signature = Signatures<1,I>
StepID = SigProfile<1,I>
UNTIL Signature = ''
NEXT I
FinalQASig = ''
PostCleanSig = ''
PostInspSig = ''
PostScanSig = ''
BEGIN CASE
CASE StepID[-2,2] = 'QA' ; FinalQASig = Signature
CASE StepID[-4,4] = 'PSTC' ; PostCleanSig = Signature
CASE StepID[-4,4] = 'PSTI' ; PostInspSig = Signature
CASE StepID[-4,4] = 'PSTS' ; PostScanSig = Signature
END CASE
CutOffDtm = ICONV('11/17/2015 23:59:59','DT') ;* New status start at midnight on this day
IF FinalQASig NE '' THEN
IF WMOutRec<WM_OUT_MAKEUP_BOX$> = 1 THEN
IF FillCount > 0 THEN
Result = 'RTU'
END ELSE
Result = 'MT'
END
* This is a check to see if the box has been "Emptied" by the system admin so it can be disposed of.
* Used to move obsolete M/U boxes out of the system
* DKK & JCH 10/2/2014
IF Result = 'RTU' THEN
LocCnt = COUNT(WOMatRec<WO_MAT_INV_LOCATION$>,@VM) + (WOMatRec<WO_MAT_INV_LOCATION$> NE '')
FOR I = 1 TO LocCnt
ChkLoc = WOMatRec<WO_MAT_INV_LOCATION$,I>
ChkAction = WOMatRec<WO_MAT_INV_ACTION$,I>
IF ChkLoc = 'MU' AND ChkAction = 'EMPTY' THEN
Result = 'MT'
END
NEXT I
END
END ELSE
LastLoc = WOMatRec<WO_MAT_INV_LOCATION$>[-1,'B':@VM]
LastWH = WOMatRec<WO_MAT_INV_WH$>[-1,'B':@VM]
CurrLoc = ''
IF LastWH NE '' AND LastLoc NE '' THEN CurrLoc = LastWH:'*':LastLoc
IF WMOutRec<WM_OUT_IN_CLEANROOM$> = 1 THEN
Begin Case
Case CurrLoc EQ 'CR*PKO'
Result = 'PKO'
Case CurrLoc EQ 'CR*PACK'
Result = 'PACK'
Case Otherwise$
Result = 'COMP'
End Case
END ELSE
CurrDTM = ICONV(OCONV( Date(), 'D4/' ):' ':OCONV( Time(), 'MTS' ), 'DT' )
Result = 'RTS'
END
END
RETURN
END
IF FillCount = SlotCount THEN
Result = StepID[-1,'B':'_']
END
IF FillCount = 0 THEN
Result = 'RTB' ;* Ready to Build
RETURN
END
IF FillCount < SlotCount THEN
Result = 'BLD' ;* Building
RETURN
END
* StaticCurrStatus = WMOutRec<WM_OUT_CURR_STATUS_STATIC$>
*
* If Result NE StaticCurrStatus then
* // Log the discrepancy
* LogData = ''
* LogData<1> = LoggingDTM
* LogData<2> = @User4
* LogData<3> = WMOutKey
* LogData<4> = Result
* LogData<5> = StaticCurrStatus
* Logging_Services('AppendLog', objCurrStatusLog, LogData, @RM, @FM)
* Material_Services('PostWMOutUpdateRequest', WMOutKey)
* end
RETURN
* * * * * * *
CRComp:
* * * * * * *
WMOutKey = Parms[1,@RM]
WMOutRec = Parms[COL2()+1,@RM]
WOMatRec = Parms[COL2()+1,@RM]
IF WMOutKey = '' THEN RETURN
IF WMOutRec = '' THEN WMOutRec = XLATE('WM_OUT',WMOutKey,'','X')
* Check for completion or abnormal condition
IF WOMatRec = '' THEN
WONo = WMOutKey[1,'*']
CassNo = WMOutKey[-1,'B*']
WOMatKey = WONo:'*':CassNo
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
END
SlotCount = 0
FillCount = 0
NCRCount = 0
RecSlotCnt = COUNT(WMOutRec<WM_OUT_SLOT_NO$>,@VM) + (WMOutRec<WM_OUT_SLOT_NO$> NE '')
FOR I = 1 TO RecSlotCnt
IF WMOutRec<WM_OUT_SLOT_NO$,I> NE '' THEN SlotCount += 1
IF WMOutRec<WM_OUT_RDS$,I> NE '' THEN FillCount += 1
IF WMOutRec<WM_OUT_SLOT_NCR$,I> NE '' THEN NCRCount += 1
NEXT I
Result = 1
IF WMOutRec<WM_OUT_VOID$> NE 1 AND (NCRCount NE SlotCount) THEN
IF WOMatRec<WO_MAT_HOLD$> = 1 AND WOMatRec<WO_MAT_HOLD_ENTITY$,1> = 'WM_OUT' THEN Result = 0 ;* Box is on Hold
NCRStatuses = XLATE('NCR',WMOutRec<WM_OUT_NCR_KEYS$>,7,'X')
IF INDEX(NCRStatuses,'O',1) THEN Result = 0 ;* Open NCR associated with box
IF WMOutRec<WM_OUT_SUP_VER_SIG$> = '' THEN Result = 0
IF WMOutRec<WM_OUT_MAKEUP_BOX$> = 1 THEN Result = 0
END
RETURN
* * * * * * *
NextOpenSlots:
* * * * * * *
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
OPEN 'DICT.WM_OUT' TO DictVar ELSE
ErrorMsg = 'Unable to open "DICT.WM_OUT" in obj_WM_Out'
RETURN
END
SearchString = 'WO_NO':@VM:WONo:@FM
Flag = ''
Btree.Extract(SearchString, 'WM_OUT', DictVar, WMOKeys, '', Flag)
IF Get_Status(errCode) THEN
RETURN
END
FOR I = 1 TO COUNT(WMOKeys,@VM) + (WMOKeys NE '')
CassNo = WMOKeys<1,I>[-1,'B*']
LOCATE CassNo IN CassNos BY 'AR' USING @VM SETTING Pos ELSE
CassNos = INSERT(CassNos,1,Pos,0,CassNo)
END
NEXT I
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>
WMOutRec = XLATE('WM_Out',WONo:'*':WOStep:'*':CassNo,'','X')
SlotCnt = COUNT(WMOutRec<WM_OUT_SLOT_NO$>,@VM) + (WMOutRec<WM_OUT_SLOT_NO$> NE '')
IsMULot = WMOutRec EQ True$
IsFQASigned = WMOutRec<WM_OUT_SUP_VER_SIG$> NE ''
If Not(IsMULot) AND Not(IsFQASigned) then
FOR N = SlotCnt TO 1 STEP -1
IF WMOutRec<WM_OUT_SLOT_NO$,N> NE '' AND WMOutRec<WM_OUT_RDS$,N> = '' AND WMOutRec<WM_OUT_SLOT_NCR$,N> = '' AND WMOutRec<WM_OUT_UMW_CASS_ID$,N> = '' THEN
SlotNo = WMOutRec<WM_OUT_SLOT_NO$,N>
IF NOT(RowExists('WMO_WFRS',WONo:'*':WOStep:'*':CassNo:'*':SlotNo)) THEN ;* Check for 'LOCK' in WMO_WFRS table
Result = INSERT(Result,1,0,0,I:@VM:N) ;* Plate-o-lator (LIFO) style
END
END
NEXT N
end
NEXT I
RETURN
* * * * * * *
SlotStatus:
* * * * * * *
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
OPEN 'DICT.WM_OUT' TO DictVar ELSE
ErrorMsg = 'Unable to open "DICT.WM_OUT" in obj_WM_Out'
RETURN
END
SearchString = 'WO_NO':@VM:WONo:@FM
Flag = ''
Btree.Extract(SearchString, 'WM_OUT', DictVar, WMOKeys, '', Flag)
IF Get_Status(errCode) THEN
RETURN
END
FOR I = 1 TO COUNT(WMOKeys,@VM) + (WMOKeys NE '')
CassNo = WMOKeys<1,I>[-1,'B*']
LOCATE CassNo IN CassNos BY 'AR' USING @VM SETTING Pos ELSE
CassNos = INSERT(CassNos,1,Pos,0,CassNo)
END
NEXT I
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>
WMOutRec = XLATE('WM_Out',WONo:'*':WOStep:'*':CassNo,'','X')
SlotCnt = COUNT(WMOutRec<WM_OUT_SLOT_NO$>,@VM) + (WMOutRec<WM_OUT_SLOT_NO$> NE '')
FOR N = SlotCnt TO 1 STEP -1
IF WMOutRec<WM_OUT_SLOT_NO$,N> NE '' AND WMOutRec<WM_OUT_RDS$,N> = '' AND WMOutRec<WM_OUT_SLOT_NCR$,N> = '' AND WMOutRec<WM_OUT_UMW_CASS_ID$,N> = '' THEN
SlotNo = WMOutRec<WM_OUT_SLOT_NO$,N>
IF NOT(RowExists('WMO_WFRS',WONo:'*':WOStep:'*':CassNo:'*':SlotNo)) THEN ;* Check for 'LOCK' in WMO_WFRS table
Result = INSERT(Result,1,0,0,I:@VM:N:@VM:'Open') ;* Plate-o-lator (LIFO) style
END ELSE
LockRec = XLATE('WMO_WFRS',WONo:'*':WOStep:'*':CassNo:'*':SlotNo,'','X')
LockBy = LockRec<WMO_WFRS_USER_NAME$>
Workstation = LockRec<WMO_WFRS_WORKSTATION_ID$>
LockedAt = OCONV(LockRec<WMO_WFRS_LOCKED_AT$>,'DT/2^S')
Result = INSERT(Result,1,0,0,I:@VM:N:@VM:'Locked':@VM:LockBy:@VM:Workstation:@VM:LockedAt)
END
END ELSE
Result = INSERT(Result,1,0,0,I:@VM:N:@VM:'Filled')
END
NEXT N
NEXT I
RETURN
* * * * * * *
AddWafer:
* * * * * * *
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]
InCassNos = Parms[COL2()+1,@RM]
InSlotNos = Parms[COL2()+1,@RM]
PrevNCRs = Parms[COL2()+1,@RM]
MUWONos = Parms[COL2()+1,@RM]
MUSteps = Parms[COL2()+1,@RM]
MUCassIDs = Parms[COL2()+1,@RM]
MUSlots = 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 RDSNos = '' THEN ErrorMsg = 'Null Parameter "RDSNos" passed to routine. (':Method:')'
IF PocketNos = '' THEN ErrorMsg = 'Null Parameter "PocketNos" passed to routine. (':Method:')'
IF Zones = '' THEN ErrorMsg = 'Null Parameter "Zones" passed to routine. (':Method:')'
IF InCassNos = '' THEN ErrorMsg = 'Null Parameter "InCassNos" passed to routine. (':Method:')'
IF InSlotNos = '' THEN ErrorMsg = 'Null Parameter "InSlotNos" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
otParms = 'WM_OUT':@RM:WONo:'*':WOStep:'*':CassNo
* WMOutRec = obj_Tables('ReadRec',otParms)
WMOutRec = Database_Services('ReadDataRow', 'WM_OUT', WONo:'*':WOStep:'*':CassNo)
IF Get_Status(errCode) THEN RETURN
SlotCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
NewFlag = 1
FOR I = 1 TO SlotCnt
IF WMOutRec<WM_OUT_RDS$,I> NE '' THEN NewFlag = 0
IF WMOutRec<WM_OUT_SLOT_NCR$,I> THEN NewFlag = 0
IF WMOutRec<WM_OUT_UMW_CASS_ID$,I> THEN NewFlag = 0
UNTIL NOT(NewFlag)
NEXT I
CurrDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
IF NewFlag THEN
obj_Post_Log('Create','WO_MAT':@RM:WONo:'*':CassNo:@RM:WO_MAT_WMO_LOAD_DTM$:@RM:ICONV(CurrDTM,'DT'))
END
LastSlotNo = WMOutRec<WM_OUT_SLOT_NO$>[-1,'B':@VM]
LastSlot = 0
LastRDSNo = ''
LastReactNo = ''
WfrIDs = ''
NewSlotIDs = ''
FOR I = 1 TO SlotCnt
SlotNo = SlotNos<1,I>
IF SlotNo = LastSlotNo THEN
LastSlot = 1
LastRDSNo = RDSNos<1,I>
LastReactNo = XLATE('REACT_RUN',LastRDSNo,REACT_RUN_REACTOR$,'X')
END
LOCATE SlotNo IN WMOutRec<WM_OUT_SLOT_NO$> USING @VM SETTING Pos THEN
ReactNo = XLATE('RDS',RDSNos<1,I>,RDS_REACTOR$,'X')
WMOutRec<WM_OUT_RDS$,Pos> = RDSNos<1,I>
WMOutRec<WM_OUT_POCKET$,Pos> = PocketNos<1,I>
WMOutRec<WM_OUT_ZONE$,Pos> = Zones<1,I>
WMOutRec<WM_OUT_IN_CASS_NO$,Pos> = InCassNos<1,I>
WMOutRec<WM_OUT_IN_SLOT_NO$,Pos> = InSlotNos<1,I>
WMOutRec<WM_OUT_SLOT_NCR$,Pos> = PrevNCRs<1,I> ;* Clears NCR number when called from the NCR delete event
WMOutRec<WM_OUT_MU_WO_NO$,Pos> = MUWONos<1,I>
WMOutRec<WM_OUT_MU_WO_STEP$,Pos> = MUSteps<1,I>
WMOutRec<WM_OUT_MU_CASS_NO$,Pos> = MUCassIDs<1,I>
WMOutRec<WM_OUT_MU_SLOT_NO$,Pos> = MUSlots<1,I>
WfrIDs<1,-1> = WONo:'*':InCassNos<1,I>:'*':InSlotNos<1,I>
NewSlotIDs<1,-1> = WONo:'*':CassNo:'*':SlotNo
* * * * Added 3/22/2016 JCH - wafer history * * * *
Parms = WONo:'*':InCassNos<1,I>:'*':InSlotNos<1,I>:@RM ;* WfrID
Parms := CurrDTM:@RM ;* EventDtm
Parms := @USER4:@RM ;* EventBy
Parms := 'UNLOAD':@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 := 'O' ;* Wfr Side
obj_WO_Wfr('AddEvent',Parms)
END
NEXT I
/*
IF NewSlotIDs NE '' THEN
* * * * Added 9/7/2016 JCH - wafer history * * * *
Parms = WfrIDs:@RM ;* WfrID
Parms := CurrDTM:@RM ;* EventDtm
Parms := @USER4:@RM ;* EventBy
Parms := 'UNLOAD':@RM ;* Event
Parms := NewSlotIDs:@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 := 'O' ;* Wfr Side
obj_WO_Wfr('AddEvent',Parms)
END
*/
otParms = FieldStore(otParms,@RM,4,0,WMOutRec) ;* Put record in 4th field of OtParms
* obj_Tables('WriteRec',otParms)
Database_Services('WriteDataRow', 'WM_OUT', WONo:'*':WOStep:'*':CassNo, WMOutRec, True$, False$, True$)
If Error_Services('NoError') then
IF LastSlot = 1 THEN
CurrDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
EpiReactNo = obj_WM_Out('EpiReactNo',WONo:'*':WOStep:'*':CassNo:@RM:WMOutRec)
IF EpiReactNo NE '' THEN
ReactWH = XLATE('REACTOR',EpiReactNo,'TOOL_WH','X')
ReactLoc = XLATE('REACTOR',EpiReactNo,'TOOL_LOC','X')
END ELSE
ReactWH = ''
ReactLoc = ''
END
LogFile = 'WO_MAT' ; WOMLParms = LogFile:@RM
LogDTM = CurrDTM ; WOMLParms := LogDTM:@RM
Action = WOStep:'UNLOAD' ; 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 = 'R':EpiReactNo ; WOMLParms := ToolID
obj_WO_Mat_Log('Create',WOMLParms) ;* Stage PSTC log entry
IF Get_Status(errCode) THEN
RETURN
END
END ;* End of check for Box Full
end
RETURN
* * * * * * *
RemoveWafer:
* * * * * * *
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
WMOKey = WONo:'*':WOStep:'*':CassNo
* otParms = 'WM_OUT':@RM:WONo:'*':WOStep:'*':CassNo
* WMOutRec = obj_Tables('ReadRec',otParms)
WMOutRec = Database_Services('ReadDataRow', 'WM_OUT', WMOKey)
IF Get_Status(errCode) THEN RETURN ;* Added 2/24/2009 JCH
FOR I = 1 TO COUNT(SlotNos,@VM) + (SlotNos NE '')
SlotNo = SlotNos<1,I>
LOCATE SlotNo IN WMOutRec<WM_OUT_SLOT_NO$> USING @VM SETTING Pos THEN
WMOutRec<WM_OUT_RDS$,Pos> = ''
WMOutRec<WM_OUT_POCKET$,Pos> = ''
WMOutRec<WM_OUT_ZONE$,Pos> = ''
WMOutRec<WM_OUT_IN_CASS_NO$,Pos> = ''
WMOutRec<WM_OUT_IN_SLOT_NO$,Pos> = ''
END
NEXT I
* otParms = FieldStore(otParms,@RM,4,0,WMOutRec) ;* Put record in 4th field of OtParms
* obj_Tables('WriteRec',otParms)
Database_Services('WriteDataRow', 'WM_OUT', WMOkey, WMOutRec, True$, False$, True$)
RETURN
* * * * * * *
AddShip:
* * * * * * *
WMOutKey = Parms[1,@RM]
ShipNo = Parms[COL2()+1,@RM]
Reship = Parms[COL2()+1,@RM]
If Reship EQ '' then
Reship = False$
end
IF NOT(ASSIGNED(WMOutKey)) THEN ErrorMsg = 'Unassigned Parm "WMOutKey" passed to routine. (':Method:')'
IF NOT(ASSIGNED(ShipNo)) THEN ErrorMsg = 'Unassigned Parm "ShipNo" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
IF WMOutKey = '' THEN ErrorMsg = 'Null Parm "WMOutKey" passed to routine. (':Method:')'
IF ShipNo = '' THEN ErrorMsg = 'Null Parm "ShipNo" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
otParms = 'WM_OUT':@RM:WMOutKey
WMOutRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
IF WMOutRec<WM_OUT_SHIP_NO$> = '' OR WMOutRec<WM_OUT_SHIP_NO$> = ShipNo or Reship EQ True$ THEN
WMOutRec<WM_OUT_SHIP_NO$> = ShipNo
otParms = FIELDSTORE(otParms,@RM,4,0,WMOutRec)
obj_Tables('WriteRec',otParms)
END ELSE
obj_Tables('UnlockRec',otParms)
ErrorMsg = "WM_OUT Cassette was already shipped on shipment" :QUOTE(WMOutRec<WM_OUT_SHIP_NO$>): ". (" :Method: ")"
END
// Update work order SHIP_QTY_STATIC
WONo = Field(WMOutKey, '*', 1)
Work_Order_Services('UpdateShippedQty', WONo)
RETURN
* * * * * * *
RemShip:
* * * * * * *
WMOutKey = Parms[1,@RM]
ShipNo = Parms[COL2()+1,@RM]
IF NOT(ASSIGNED(WMOutKey)) THEN ErrorMsg = 'Unassigned Parm "WMOutKey" passed to routine. (':Method:')'
IF NOT(ASSIGNED(ShipNo)) THEN ErrorMsg = 'Unassigned Parm "ShipNo" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
IF WMOutKey = '' THEN ErrorMsg = 'Null Parm "WMOutKey" passed to routine. (':Method:')'
IF ShipNo = '' THEN ErrorMsg = 'Null Parm "ShipNo" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
otParms = 'WM_OUT':@RM:WMOutKey
WMOutRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
IF WMOutRec<WM_OUT_SHIP_NO$> = ShipNo OR WMOutRec<WM_OUT_SHIP_NO$> = '' THEN
WMOutRec<WM_OUT_SHIP_NO$> = ''
otParms = FIELDSTORE(otParms,@RM,4,0,WMOutRec)
obj_Tables('WriteRec',otParms)
END ELSE
obj_Tables('UnlockRec',otParms)
ErrorMsg = "Passed Ship No " :QUOTE(ShipNo): " doesn't match Ship No on WM_OUT record " :QUOTE(WMOutKey): ". (" :Method: ")"
END
RETURN
* * * * * * *
ClearLoad:
* * * * * * *
* The nuclear option for getting the RDS unload and WM_OUT load data back in sync.
WMOutKey = Parms[1,@RM]
IF NOT(ASSIGNED(WMOutKey)) THEN ErrorMsg = 'Unassigned Parm "WMOutKey" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
otParms = 'WM_OUT':@RM:WMOutKey
WMOutRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
Makeups = WMOutRec<WM_OUT_MU_WO_NO$>
NCRs = WMOutRec<WM_OUT_SLOT_NCR$>
UMWs = WMOutRec<WM_OUT_UMW_CASS_ID$>
CONVERT @VM TO '' IN Makeups
CONVERT @VM TO '' IN NCRs
CONVERT @VM TO '' IN UMWs
IF Makeups NE '' THEN ErrorMsg = 'Cassette has makeup wafers in it.'
IF NCRs NE '' THEN ErrorMsg = 'Cassette has NCR records attached.'
IF UMWs NE '' THEN ErrorMsg = 'Cassette has wafers used for makeups removed from it.'
IF ErrorMsg NE '' THEN
obj_Tables('UnlockRec',otParms)
RETURN
END
SlotCnt = COUNT(WMOutRec<WM_OUT_SLOT_NO$>,@VM) + (WMOutRec<WM_OUT_SLOT_NO$> NE '')
FOR Slot = 1 TO SlotCnt
WMOutRec<WM_OUT_RDS$,Slot> = ''
WMOutRec<WM_OUT_POCKET$,Slot> = ''
WMOutRec<WM_OUT_ZONE$,Slot> = ''
WMOutRec<WM_OUT_IN_CASS_NO$,Slot> = ''
WMOutRec<WM_OUT_IN_SLOT_NO$,Slot> = ''
NEXT Slot
otParms = FIELDSTORE(otParms,@RM,4,0,WMOutRec)
obj_Tables('WriteRec',otParms)
RETURN
* * * * * * *
RDSSlots:
* * * * * * *
WMOutKey = Parms[1,@RM]
WMOutRec = Parms[COL2()+1,@RM]
IF WMOutKey = '' THEN RETURN
IF WMOutRec = '' THEN WMOutRec = XLATE('WM_OUT',WMOutKey,'','X')
RDSNos = ''
SlotRanges = ''
FOR I = 1 TO COUNT(WMOutRec<WM_OUT_SLOT_NO$>,@VM) + (WMOutRec<WM_OUT_SLOT_NO$> NE '')
RDSNo = WMOutRec<WM_OUT_RDS$,I>
SlotNo = WMOutRec<WM_OUT_SLOT_NO$,I>
IF RDSNo NE '' THEN
LOCATE RDSNo IN RDSNos USING @VM SETTING Pos THEN
SlotRange = SlotRanges<1,Pos>
Start = SlotRange[1,'-']
SlotRanges<1,Pos> = Start:'-':SlotNo
END ELSE
RDSNos = INSERT(RDSNos,1,Pos,0,RDSNo)
SlotRanges = INSERT(SlotRanges,1,Pos,0,SlotNo)
END
END
NEXT I
Result = RDSNos:@FM:SlotRanges
RETURN
* * * * * * *
InCassData:
* * * * * * *
WMOutKey = Parms[1,@RM]
WMOutRec = Parms[COL2()+1,@RM]
IF WMOutKey = '' THEN RETURN
IF WMOutRec = '' THEN WMOutRec = XLATE('WM_OUT',WMOutKey,'','X')
WONo = WMOutKey[1,'*']
InWOCassettes = '' ;*Structure to hold WO*InCassNo pairs
InLotNos = ''
InPartNos = ''
InSubPartNos = ''
FOR I = 1 TO COUNT(WMOutRec<WM_OUT_SLOT_NO$>,@VM) + (WMOutRec<WM_OUT_SLOT_NO$> NE '')
InCassette = WMOutRec<WM_OUT_IN_CASS_NO$,I>
IF InCassette NE '' THEN
MUWONo = WMOutRec<WM_OUT_MU_WO_NO$,I>
IF MUWONo = '' THEN
ItemWONo = WONo
END ELSE
ItemWONo = MUWONo
END
WOMatRec = XLATE('WO_MAT',ItemWONo:'*':InCassette,'','X')
LotNo = WOMatRec<WO_MAT_LOT_NO$>
PartNo = WOMatRec<WO_MAT_CUST_PART_NO$>
SubPartNo = WOMatRec<WO_MAT_SUB_PART_NO$>
IF LotNo NE '' THEN
SortKey = ItemWONo:'*':InCassette
LOCATE SortKey IN InWOCassettes USING @VM SETTING Pos ELSE
InWOCassettes = INSERT(InWOCassettes,1,Pos,0,SortKey)
InLotNos = INSERT(InLotNos,1,Pos,0,LotNo)
InPartNos = INSERT(InPartNos,1,Pos,0,PartNo)
InSubPartNos = INSERT(InSubPartNos,1,Pos,0,SubPartNo)
END
END
END
NEXT I
Result = InWOCassettes:@FM:InLotNos:@FM:InPartNos:@FM:InSubPartNos
RETURN
* * * * * * *
AddMakeupWafers:
* * * * * * *
* Places makeup wafers into a production cassette
WMOutKey = Parms[1,@RM]
EmptySlots = Parms[COL2()+1,@RM]
MakeupBox = Parms[COL2()+1,@RM]
IF NOT(ASSIGNED(WMOutKey)) THEN ErrorMsg = 'Unassigned Parm "WMOutKey" passed to routine. (':Method:')'
IF NOT(ASSIGNED(EmptySlots)) THEN ErrorMsg = 'Unassigned Parm "EmptySlots" passed to routine. (':Method:')'
IF NOT(ASSIGNED(MakeupBox)) THEN ErrorMsg = 'Unassigned Parm "MakeupBox" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
IF WMOutKey = '' THEN ErrorMsg = 'Null Parm "WMOutKey" passed to routine. (':Method:')'
IF EmptySlots = '' THEN ErrorMsg = 'Null Parm "EmptySlots" passed to routine. (':Method:')'
IF MakeupBox = '' THEN ErrorMsg = 'Null Parm "MakeupBox" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
otParms = 'WM_OUT':@RM:WMOutKey
WMOutRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
MakeupWaferData = obj_WM_Out('RemMakeupWafers',MakeUpBox:@RM:EmptySlots:@RM:WMOutKey) ;* Extracts and returns slot data from Makeup Box
IF Get_Status(errCode) THEN RETURN
IF MakeupWaferData = '' THEN RETURN
MakeupWONo = MakeupBox[1,'*']
MakeupWOStep = MakeupBox[COL2()+1,'*']
MakeupCassNo = MakeupBox[COL2()+1,'*']
MakeupBy = @USER4
FOR I = 1 TO COUNT(EmptySlots,@VM) + (EmptySlots NE '')
UNTIL MakeupWaferData<I,WM_OUT_SLOT_NO$> = ''
SlotNo = EmptySlots<1,I>
WMOutRec<WM_OUT_SLOT_NO$,SlotNo> = SlotNo
WMOutRec<WM_OUT_MU_WO_NO$,SlotNo> = MakeupWONo
WMOutRec<WM_OUT_MU_WO_STEP$,SlotNo> = MakeupWOStep
WMOutRec<WM_OUT_MU_CASS_NO$,SlotNo> = MakeupCassNo
WMOutRec<WM_OUT_MU_BY$,SlotNo> = MakeupBy ;* Added 10/6/2010 JCH
WMOutRec<WM_OUT_MU_SLOT_NO$,SlotNo> = MakeupWaferData<I,WM_OUT_SLOT_NO$>
WMOutRec<WM_OUT_RDS$,SlotNo> = MakeupWaferData<I,WM_OUT_RDS$>
WMOutRec<WM_OUT_POCKET$,SlotNo> = MakeupWaferData<I,WM_OUT_POCKET$>
WMOutRec<WM_OUT_ZONE$,SlotNo> = MakeupWaferData<I,WM_OUT_ZONE$>
WMOutRec<WM_OUT_IN_CASS_NO$,SlotNo> = MakeupWaferData<I,WM_OUT_IN_CASS_NO$>
WMOutRec<WM_OUT_IN_SLOT_NO$,SlotNo> = MakeupWaferData<I,WM_OUT_IN_SLOT_NO$>
WMOutRec<WM_OUT_MU_WAFER_ADDED_DTM$, SlotNo> = MakeupWaferData<I,WM_OUT_MU_WAFER_ADDED_DTM$>
NEXT I
otParms = FIELDSTORE(otParms,@RM,4,0,WMOutRec)
obj_Tables('WriteRec',otParms)
RETURN
* * * * * * *
SubMakeupWafers:
* * * * * * *
* Subtracts makeup wafers from a production box for return to the makeup box
WMOutKey = Parms[1,@RM]
MadeupSlots = Parms[COL2()+1,@RM]
IF NOT(ASSIGNED(WMOutKey)) THEN ErrorMsg = 'Unassigned Parm "WMOutKey" passed to routine. (':Method:')'
IF NOT(ASSIGNED(MadeupSlots)) THEN ErrorMsg = 'Unassigned Parm "MadeupSlots" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
IF WMOutKey = '' THEN ErrorMsg = 'Null Parm "WMOutKey" passed to routine. (':Method:')'
IF MadeupSlots = '' THEN ErrorMsg = 'Null Parm "MadeupSlots" passed to routine. (':Method:')'
otParms = 'WM_OUT':@RM:WMOutKey
WMOutRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
CurrDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
WfrIDs = ''
NewSlotIDs = ''
CurrSlotIDs = ''
SMData = ''
FOR I = 1 TO COUNT(MadeupSlots,@VM) + (MadeupSlots NE '')
MadeupSlot = MadeupSlots<1,I>
SMData<I,1> = WMOutRec<WM_OUT_MU_WO_NO$,MadeupSlot>
SMData<I,2> = WMOutRec<WM_OUT_MU_WO_STEP$,MadeupSlot>
SMData<I,3> = WMOutRec<WM_OUT_MU_CASS_NO$,MadeupSlot>
SMData<I,4> = WMOutRec<WM_OUT_MU_SLOT_NO$,MadeupSlot>
SMData<I,5> = WMOutRec<WM_OUT_RDS$,MadeupSlot>
SMData<I,6> = WMOutRec<WM_OUT_POCKET$,MadeupSlot>
SMData<I,7> = WMOutRec<WM_OUT_ZONE$,MadeupSlot>
SMData<I,8> = WMOutRec<WM_OUT_IN_CASS_NO$,MadeupSlot>
SMData<I,9> = WMOutRec<WM_OUT_IN_SLOT_NO$,MadeupSlot>
// KLUSA Timestamp Makeup Wafer Project
// Delete most recent "added" DTM from WMOutRec
AddedDTMS = WMOutRec<WM_OUT_MU_WAFER_ADDED_DTM$, MadeupSlot>
AddedDTMS = Delete(AddedDTMS, 1, 1, 1)
WMOutRec<WM_OUT_MU_WAFER_ADDED_DTM$, MadeupSlot> = AddedDTMS
* * * * Added 5/11/2016 JCH - wafer history * * * *
WfrID = WMOutRec<WM_OUT_MU_WO_NO$,MadeupSlot>:'*':WMOutRec<WM_OUT_IN_CASS_NO$,MadeupSlot>:'*':WMOutRec<WM_OUT_IN_SLOT_NO$,MadeupSlot>
NewSlotID = WMOutRec<WM_OUT_MU_WO_NO$,MadeupSlot>:'*':WMOutRec<WM_OUT_MU_CASS_NO$,MadeupSlot>:'*':WMOutRec<WM_OUT_MU_SLOT_NO$,MadeupSlot>
CurrSlotID = FIELD(WMOutKey,'*',1,1):'*':FIELD(WMOutKey,'*',3,1):'*':MadeupSlot
WfrIDs<1,-1> = WfrID ;* Added 9/7/2016 JCH
NewSlotIDs<1,-1> = NewSlotId ;* Added 9/7/2016 JCH
CurrSlotIDs<1,-1> = CurrSlotId ;* Added 9/7/2016 JCH
Parms = WfrID:@RM ;* WfrID
Parms := CurrDTM:@RM ;* EventDtm
Parms := @USER4:@RM ;* EventBy
Parms := 'RMKUP':@RM ;* Event
Parms := NewSlotID:@RM ;* NewSlotID
Parms := '':@RM ;* RunLoc
Parms := '':@RM ;* NCRNo
Parms := '':@RM ;* TWUse
Parms := CurrSlotID:@RM ;* CurrSlotID
Parms := '':@RM ;* NewToolID
Parms := '':@RM ;* CurrToolID
Parms := '':@RM ;* NewInvLoc
Parms := '':@RM ;* CurrInvLoc
Parms := 'O' ;* Wfr Side
obj_WO_Wfr('AddEvent',Parms)
* * * * End of wafer history update * * * *
WMOutRec<WM_OUT_MU_WO_NO$,MadeupSlot> = ''
WMOutRec<WM_OUT_MU_WO_STEP$,MadeupSlot> = ''
WMOutRec<WM_OUT_MU_CASS_NO$,MadeupSlot> = ''
WMOutRec<WM_OUT_MU_SLOT_NO$,MadeupSlot> = ''
WMOutRec<WM_OUT_MU_BY$,MadeupSlot> = '' ;* Added 10/6/2010 JCH *
WMOutRec<WM_OUT_RDS$,MadeupSlot> = ''
WMOutRec<WM_OUT_POCKET$,MadeupSlot> = ''
WMOutRec<WM_OUT_ZONE$,MadeupSlot> = ''
WMOutRec<WM_OUT_IN_CASS_NO$,MadeupSlot> = ''
WMOutRec<WM_OUT_IN_SLOT_NO$,MadeupSlot> = ''
WMOutRec<WM_OUT_MU_WAFER_THK_RESULT$,MadeupSlot> = '' ;* Added 03/14/2017 FDR *
NEXT I
otParms = FIELDSTORE(otParms,@RM,4,0,WMOutRec)
obj_Tables('WriteRec',otParms)
Result = SMData
RETURN
* * * * * * *
RemMakeupWafers:
* * * * * * *
* Removes wafers from a makeup box for use as makeups in a production box
MUBoxKey = Parms[1,@RM]
EmptySlots = Parms[COL2()+1,@RM]
TargetBoxKey = Parms[COL2()+1,@RM]
IF NOT(ASSIGNED(MUBoxKey)) THEN ErrorMsg = 'Unassigned Parm "MUBoxKey" passed to routine. (':Method:')'
IF NOT(ASSIGNED(EmptySlots)) THEN ErrorMsg = 'Unassigned Parm "EmptySlots" passed to routine. (':Method:')'
IF NOT(ASSIGNED(TargetBoxKey)) THEN ErrorMsg = 'Unassigned Parm "TargetBoxKey" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
IF MUBoxKey = '' THEN ErrorMsg = 'Null Parm "MUBoxKey" passed to routine. (':Method:')'
IF EmptySlots = '' THEN ErrorMsg = 'Null Parm "EmptySlot" passed to routine. (':Method:')'
IF TargetBoxKey = '' THEN ErrorMsg = 'Null Parm "TargetBoxKey" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
otParms = 'WM_OUT':@RM:MUBoxKey
MU_WMOutRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
CONVERT '*' TO '.' IN TargetBoxKey
ReqWfrCnt = COUNT(EmptySlots,@VM) + (EmptySlots NE '')
ResCnt = 0
SlotCnt = COUNT(MU_WMOutRec<WM_OUT_SLOT_NO$>,@VM) + (MU_WMOutRec<WM_OUT_SLOT_NO$> NE '')
CurrDate = OCONV(Date(),'D4/')
CurrTime = OCONV(Time(),'MTHS')
CurrDTM = CurrDate:' ':CurrTime
WfrIDs = '' ;* Added 9/7/2016 JCH
NewSlotIDs = '' ;* Added 9/7/2016 JCH
CurrSlotIDs = '' ;* Added 9/7/2016 JCH
FOR I = 1 TO SlotCnt
IF MU_WMOutRec<WM_OUT_RDS$,I> NE '' THEN ;* This line changed from WM_OUT_SLOT_NO$ to WM_OUT_RDS
ResCnt += 1
* * * * Added 3/28/2016 JCH - wafer history * * * *
WfrID = FIELD(MUBoxKey,'*',1,1):'*':MU_WMOutRec<WM_OUT_IN_CASS_NO$,I>:'*':MU_WMOutRec<WM_OUT_IN_SLOT_NO$,I>
NewSlotID = FIELD(TargetBoxKey,'.',1,1):'*':FIELD(TargetBoxKey,'.',3,1):'*':EmptySlots<1,ResCnt>
CurrSlotID = FIELD(MUBoxKey,'*',1,1):'*':FIELD(MUBoxKey,'*',3,1):'*':MU_WMOutRec<WM_OUT_SLOT_NO$,I>
WfrIDs<1,-1> = WfrID ;* Added 9/7/2016 JCH
NewSlotIDs<1,-1> = NewSlotID ;* Added 9/7/2016 JCH
CurrSlotIDs<1,-1> = CurrSlotID ;* Added 9/7/2016 JCH
Parms = WfrID:@RM ;* WfrID
Parms := CurrDTM:@RM ;* EventDtm
Parms := @USER4:@RM ;* EventBy
Parms := 'MKUP':@RM ;* Event
Parms := NewSlotID:@RM ;* NewSlotID
Parms := '':@RM ;* RunLoc
Parms := '':@RM ;* NCRNo
Parms := '':@RM ;* TWUse
Parms := CurrSlotID:@RM ;* CurrSlotID
Parms := '':@RM ;* NewToolID
Parms := '':@RM ;* CurrToolID
Parms := '':@RM ;* NewInvLoc
Parms := '':@RM ;* CurrInvLoc
Parms := 'O' ;* Wfr Side
obj_WO_Wfr('AddEvent',Parms)
* * * * End of wafer history update * * * *
Result<ResCnt,WM_OUT_SLOT_NO$> = MU_WMOutRec<WM_OUT_SLOT_NO$,I> ; *MU_WMOutRec<WM_OUT_SLOT_NO$,I> = '' ;******* 4/16/2014 JCH ******* Leave Slot Nos in place
Result<ResCnt,WM_OUT_RDS$> = MU_WMOutRec<WM_OUT_RDS$,I> ; MU_WMOutRec<WM_OUT_RDS$,I> = ''
Result<ResCnt,WM_OUT_POCKET$> = MU_WMOutRec<WM_OUT_POCKET$,I> ; MU_WMOutRec<WM_OUT_POCKET$,I> = ''
Result<ResCnt,WM_OUT_ZONE$> = MU_WMOutRec<WM_OUT_ZONE$,I> ; MU_WMOutRec<WM_OUT_ZONE$,I> = ''
Result<ResCnt,WM_OUT_IN_CASS_NO$> = MU_WMOutRec<WM_OUT_IN_CASS_NO$,I> ; MU_WMOutRec<WM_OUT_IN_CASS_NO$,I> = ''
Result<ResCnt,WM_OUT_IN_SLOT_NO$> = MU_WMOutRec<WM_OUT_IN_SLOT_NO$,I> ; MU_WMOutRec<WM_OUT_IN_SLOT_NO$,I> = ''
MU_WMOutRec<WM_OUT_UMW_CASS_ID$,I> = TargetBoxKey
MU_WMOutRec<WM_OUT_UMW_SLOT_NO$,I> = EmptySlots<1,ResCnt>
// Timestamp MU Wafer Project
// Append makeup wafer removed datetime to the beginning of @VM for the available slot number. Dates will be
// @SVM delimited. Note only the most recent datetime will be displayed on the form.
DateTime = Date() : '.' : Time()
// Grab previous removed dates. (e.g. makeup wafer that became a makeup wafer)
AddedDTMS = MU_WMOutRec<WM_OUT_MU_WAFER_ADDED_DTM$, I>
// Insert this datetime to result record to use in AddMakeupWafers routine
Result<ResCnt,WM_OUT_MU_WAFER_ADDED_DTM$> = Insert(AddedDTMS, 0, 0, 1, DateTime)
// Append "removed" datetime to MU wafer record
RemovedDTMS = MU_WMOutRec<WM_OUT_MU_WAFER_REMOVED_DTM$, I>
RemovedDTMS = Insert(RemovedDTMS, 1, 1, 1, DateTime)
MU_WMOutRec<WM_OUT_MU_WAFER_REMOVED_DTM$, I> = RemovedDTMS
END
UNTIL ResCnt = ReqWfrCnt
NEXT I
otParms = FIELDSTORE(otParms,@RM,4,0,MU_WMOutRec)
obj_Tables('WriteRec',otParms)
WONo = FIELD(MUBoxKey,'*',1)
CassNo = FIELD(MUBoxKey,'*',3)
FillCnt = 0
FOR I = 1 TO SlotCnt
SlotNo = MU_WMOutRec<WM_OUT_SLOT_NO$,I>
RDSNo = MU_WMOutRec<WM_OUT_RDS$,I>
IF RDSNo NE '' AND SlotNo NE '' THEN FillCnt += 1
NEXT I
IF FillCnt = 0 THEN
WOMatInvActions = XLATE('WO_MAT',WONo:'*':CassNo,WO_MAT_INV_ACTION$,'X')
LOCATE 'EMPTY' IN WOMatInvActions USING @VM SETTING Dummy ELSE
CurrDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTHS')
LogFile = 'WO_MAT' ; WOMLParms = LogFile:@RM
LogDTM = CurrDTM ; WOMLParms := LogDTM:@RM
Action = 'EMPTY' ; WOMLParms := Action:@RM
WhCd = 'CR' ; WOMLParms := WhCd:@RM
LocCd = 'MU' ; 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
ErrMsg(errCode)
END
END
END
RETURN
* * * * * * *
RepMakeupWafers:
* * * * * * *
* Replaces makeup wafers into a makeup box. Used when returning makeups from a production box.
WMOutKey = Parms[1,@RM]
SMData = Parms[COL2()+1,@RM] ;* Data structure for wafers subtracted from production box
IF NOT(ASSIGNED(WMOutKey)) THEN ErrorMsg = 'Unassigned Parm "WMOutKey" passed to routine. (':Method:')'
IF NOT(ASSIGNED(SMData)) THEN ErrorMsg = 'Unassigned Parm "SMData" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
IF WMOutKey = '' THEN ErrorMsg = 'Null Parm "WMOutKey" passed to routine. (':Method:')'
IF SMData = '' THEN ErrorMsg = 'Null Parm "SMData" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
MadeupBoxKey = WMOutKey
CONVERT '*' TO '.' IN MadeupBoxKey
FOR I = 1 TO COUNT(SMData,@FM) + (SMData NE '')
MU_WONo = SMData<I,1>
MU_WOStep = SMData<I,2>
MU_WOCassNo = SMData<I,3>
MU_WOSlotNo = SMData<I,4>
MU_RDSNo = SMData<I,5>
MU_Pocket = SMData<I,6>
MU_Zone = SMData<I,7>
MU_InCassNo = SMData<I,8>
MU_InSlotNo = SMData<I,9>
MU_BoxKey = MU_WONo:'*':MU_WOStep:'*':MU_WOCassNo
otParms = 'WM_OUT':@RM:MU_BoxKey
WMOutRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF Get_Status(errCode) ELSE
IF WMOutRec<WM_OUT_UMW_CASS_ID$,MU_WOSlotNo> = MadeupBoxKey THEN
WMOutRec<WM_OUT_SLOT_NO$,MU_WOSlotNo> = MU_WOSlotNo
WMOutRec<WM_OUT_RDS$,MU_WOSlotNo> = MU_RDSNo
WMOutRec<WM_OUT_POCKET$,MU_WOSlotNo> = MU_Pocket
WMOutRec<WM_OUT_ZONE$,MU_WOSlotNo> = MU_Zone
WMOutRec<WM_OUT_IN_CASS_NO$,MU_WOSlotNo> = MU_InCassNo
WMOutRec<WM_OUT_IN_SLOT_NO$,MU_WOSlotNo> = MU_InSlotNo
WMOutRec<WM_OUT_UMW_SLOT_NO$,MU_WOSlotNo> = ''
WMOutRec<WM_OUT_UMW_CASS_ID$,MU_WOSlotNo> = ''
// Delete most recent "removed" DTM
RemovedDTMS = WMOutRec<WM_OUT_MU_WAFER_REMOVED_DTM$, MU_WOSlotNo>
RemovedDTMS = Delete(RemovedDTMS, 1, 1, 1)
WMOutRec<WM_OUT_MU_WAFER_REMOVED_DTM$, MU_WOSlotNo> = RemovedDTMS
END
otParms = FIELDSTORE(otParms,@RM,4,0,WMOutRec)
obj_Tables('WriteRec',otParms)
END
NEXT I
RETURN
* * * * * * *
CassRDSNos:
* * * * * * *
WMOutKeys = Parms[1,@RM]
IF WMOutKeys = '' THEN RETURN
RDSNos = XLATE('WM_OUT',WMOutKeys,WM_OUT_RDS$,'X')
Result = ''
FOR I = 1 TO COUNT(RDSNos,@VM) + (RDSNos NE '')
LOCATE RDSNos<1,I> IN Result BY 'AR' USING @VM SETTING Pos ELSE
Result = INSERT(Result,1,Pos,0,RDSNos<1,I>)
END
NEXT I
RETURN
* * * * * * *
CassRDSWfrCnts:
* * * * * * *
WMOutKeys = Parms[1,@RM]
IF WMOutKeys = '' THEN RETURN
OutRDSNos = XLATE('WM_OUT',WMOutKeys,WM_OUT_RDS$,'X')
RDSNos = ''
Result = ''
FOR I = 1 TO COUNT(OutRDSNos,@VM) + (OutRDSNos NE '')
LOCATE OutRDSNos<1,I> IN RDSNos BY 'AR' USING @VM SETTING Pos THEN
Result<1,Pos> = Result<1,Pos> + 1
END ELSE
RDSNos = INSERT(RDSNos,1,Pos,0,OutRDSNos<1,I>)
Result = INSERT(Result,1,Pos,0,1)
END
NEXT I
RETURN
* * * * * * *
GetPartNoQtys:
* * * * * * *
WMOutKeys = Parms[1,@RM]
IF WMOutKeys = '' THEN RETURN
AllPartNos = ''
AllPartQtys = ''
PrevWONo = ''
FOR I = 1 TO COUNT(WMOutKeys,@VM) + (WMOutKeys NE '')
WMOutKey = WMOutKeys<1,I>
WMOutRec = XLATE('WM_OUT',WMOutKey,'','X')
WONo = WMOutKey[1,'*']
InCassNos = WMOutRec<WM_OUT_IN_CASS_NO$ >
FOR L = 1 TO COUNT(InCassNos,@VM) + (InCassNos NE '')
InCassNo = InCassNos<1,L>
MUWONo = WMOutRec<WM_OUT_MU_WO_NO$,L>
MUCassNo = WMOutRec<WM_OUT_MU_CASS_NO$,L>
IF InCassNo NE '' THEN
IF MUWONo NE '' THEN
PartNo = XLATE('WO_MAT',MUWONo:'*':MUCassNo,WO_MAT_CUST_PART_NO$,'X')
END ELSE
PartNo = XLATE('WO_MAT',WONo:'*':InCassNo,WO_MAT_CUST_PART_NO$,'X')
END
LOCATE PartNo IN AllPartNos USING @VM SETTING PartPos THEN
AllPartQtys<1,PartPos> = AllPartQtys<1,PartPos> + 1
END ELSE
AllPartNos = INSERT(AllPartNos,1,PartPos,0,PartNo)
AllPartQtys = INSERT(AllPartQtys,1,PartPos,0,1)
END
END
NEXT L
NEXT I
Result = AllPartNos:@FM:AllPartQtys
RETURN
* * * * * * *
GetLotNos:
* * * * * * *
WMOutKeys = Parms[1,@RM]
IF WMOutKeys = '' THEN RETURN
AllLotNos = ''
FOR I = 1 TO COUNT(WMOutKeys,@VM) + (WMOutKeys NE '')
WMOutKey = WMOutKeys<1,I>
WMOutRec = XLATE('WM_OUT',WMOutKey,'','X')
WONo = WMOutKey[1,'*']
MUWONo = WMOutRec<WM_OUT_MU_WO_NO$,I>
IF MUWONo = '' THEN ItemWONo = WONo ELSE ItemWONo = MUWONo
InCassNos = WMOutRec<WM_OUT_IN_CASS_NO$ >
FOR L = 1 TO COUNT(InCassNos,@VM) + (InCassNos NE '')
InCassNo = InCassNos<1,L>
MUWONo = WMOutRec<WM_OUT_MU_WO_NO$,L>
IF MUWONo = '' THEN ItemWONo = WONo ELSE ItemWONo = MUWONo
IF InCassNo NE '' THEN
LotNo = XLATE('WO_MAT',ItemWONo:'*':InCassNo,WO_MAT_LOT_NO$,'X')
LOCATE LotNo IN AllLotNos USING @VM SETTING LotPos ELSE
AllLotNos = INSERT(AllLotNos,1,LotPos,0,LotNo)
END
END
NEXT L
NEXT I
Result = AllLotNos
RETURN
* * * * * * *
GetOrderItems:
* * * * * * *
WMOutKeys = Parms[1,@RM]
IF WMOutKeys = '' THEN RETURN
AllOrderItems = ''
FOR I = 1 TO COUNT(WMOutKeys,@VM) + (WMOutKeys NE '')
WMOutKey = WMOutKeys<1,I>
WMOutRec = XLATE('WM_OUT',WMOutKey,'','X')
WONo = WMOutKey[1,'*']
InCassNos = WMOutRec<WM_OUT_IN_CASS_NO$ >
FOR L = 1 TO COUNT(InCassNos,@VM) + (InCassNos NE '')
InCassNo = InCassNos<1,L>
MUWONo = WMOutRec<WM_OUT_MU_WO_NO$,L>
IF InCassNo NE '' AND MUWONo = '' THEN
OrderItem = XLATE('WO_MAT',WONo:'*':InCassNo,WO_MAT_ORDER_ITEM$,'X')
LOCATE OrderItem IN AllOrderItems USING @VM SETTING InsPos ELSE
AllOrderItems = INSERT(AllOrderItems,1,InsPos,0,OrderItem)
END
END
NEXT L
NEXT I
Result = AllOrderItems
RETURN
* * * * * * *
NCRNos:
* * * * * * *
WMOutKey = Parms[1,@RM]
WMOutRec = Parms[COL2()+1,@RM]
IF WMOutKey = '' THEN RETURN
IF WMOutRec = '' THEN WMOutRec = XLATE('WM_OUT',WMOutKey,'','X')
SlotNCRs = WMOutRec<WM_OUT_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
* * * * * * *
RebuildLoad:
* * * * * * *
WMOutID = Parms[1,@RM]
IF WMOutID = '' THEN RETURN
WONo = WMOutID[1,'*']
ProcStep = WMOutID[COL2()+1,'*']
OutCassNo = WMOutID[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(WMOutID,'*',1,2) = RDSRec<RDS_WO_STEP_KEY$> THEN
A = RDSRec<RDS_OUT_CASS_NO$>
IF INDEX(RDSRec<RDS_OUT_CASS_NO$>,OutCassNo,1) THEN
otParms = 'WM_OUT':@RM:WMOutID
WMOutRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
NCRKeys = WMOutRec<WM_OUT_SLOT_NCR$>
FOR N = 1 TO COUNT(RDSRec<RDS_OUT_CASS_NO$>,@VM) + (RDSRec<RDS_OUT_CASS_NO$> NE '')
IF RDSRec<RDS_OUT_CASS_NO$,N> = OutCassNo THEN
OutSlotNo = RDSRec<RDS_OUT_SLOT_NO$,N>
WMOutRec<WM_OUT_SLOT_NO$,OutSlotNo> = OutSlotNo
WMOutRec<WM_OUT_RDS$,OutSlotNo> = RDSNo
WMOutRec<WM_OUT_POCKET$,OutSlotNo> = RDSRec<RDS_POCKET$,N>
WMOutRec<WM_OUT_ZONE$,OutSlotNo> = RDSRec<RDS_ZONE$,N>
WMOutRec<WM_OUT_IN_CASS_NO$,OutSlotNo> = RDSRec<RDS_IN_CASS_NO$,N>
WMOutRec<WM_OUT_IN_SLOT_NO$,OutSlotNo> = RDSRec<RDS_IN_SLOT_NO$,N>
END
NEXT N
WMOutRec<WM_OUT_SLOT_NCR$> = NCRKeys
otParms = FIELDSTORE(otParms,@RM,4,0,WMOutRec)
obj_Tables('WriteRec',otParms)
END
END
NEXT I
RETURN
* * * * * * *
RemSlots:
* * * * * * *
WMOutKey = Parms[1,@RM]
RemSlots = Parms[COL2()+1,@RM]
IF WMOutKey = '' THEN ErrorMsg = 'Null Parm "WMOutKey" passed to routine. (':Method:')'
IF RemSlots = '' THEN ErrorMsg = 'Null Parm "RemSlots" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
otParms = 'WM_OUT':@RM:WMOutKey
WMOutRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF Get_Status(errCode) THEN
ErrorMsg = 'Unable to open WM_OUT Record for RemSlots'
RETURN
END
RemCnt = COUNT(RemSlots,@VM) + (RemSlots NE '')
FOR I = 1 TO RemCnt
RemSlot = RemSlots<1,I>
LOCATE RemSlot IN WMOutRec<WM_OUT_SLOT_NO$> USING @VM SETTING Pos THEN
WMOutRec = DELETE(WMOutRec,WM_OUT_SLOT_NO$,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_RDS$,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_POCKET$,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_ZONE$,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_IN_CASS_NO$ ,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_IN_SLOT_NO$,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_MU_WO_NO$,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_MU_WO_STEP$,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_MU_CASS_NO$,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_MU_SLOT_NO$,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_UMW_CASS_ID$ ,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_UMW_SLOT_NO$,Pos,0)
WMOutRec = DELETE(WMOutRec,WM_OUT_SLOT_NCR$,Pos,0)
END
NEXT I
otParms = FIELDSTORE(otParms,@RM,4,0,WMOutRec)
obj_Tables('WriteRec',otParms)
RETURN
* * * * * * *
WfrsOut:
* * * * * * *
WMOutKey = Parms[1,@RM]
WMOutRec = Parms[COL2()+1,@RM]
IF WMOutKey = '' THEN RETURN
IF WMOutRec = '' THEN WMOutRec = XLATE('WM_OUT',WMOutKey,'','X')
RDSNos = WMOutRec<WM_OUT_RDS$>
SlotNos = WMOutRec<WM_OUT_SLOT_NO$>
MakeupBox = WMOutRec<WM_OUT_MAKEUP_BOX$>
IF MakeupBox = 1 THEN
Result = 0
END ELSE
Result = ''
END
RDSCnt = COUNT(RDSNos,@VM) + (RDSNos NE '')
FOR I = 1 TO RDSCnt
IF RDSNos<1,I> NE '' AND SlotNos<1,I> NE '' THEN Result += 1
NEXT I
RETURN
* * * * * * *
EpiReactNo:
* * * * * * *
WMOutKey = Parms[1,@RM]
WMOutRec = Parms[COL2()+1,@RM]
IF WMOutKey = '' THEN RETURN
IF WMOutRec = '' THEN WMOutRec = XLATE('WM_OUT',WMOutKey,'','X')
SlotCnt = COUNT(WMOutRec<WM_OUT_SLOT_NO$>,@VM) + (WMOutRec<WM_OUT_SLOT_NO$> NE '')
AllRDSNos = ''
AllRDSCnts = ''
FOR I = 1 TO SlotCnt
SlotRDS = WMOutRec<WM_OUT_RDS$,I>
IF SlotRDS NE '' AND WMOutRec<WM_OUT_SLOT_NCR$,I> = '' THEN
LOCATE SlotRDS IN AllRDSNos USING @VM SETTING Pos THEN
AllRdsCnts<1,Pos> = AllRdsCnts<1,Pos> + 1
END ELSE
AllRdsNos = Insert(AllRdsNos,1,Pos,0,SlotRds)
AllRdsCnts = Insert(AllRdsCnts,1,Pos,0,1)
END
END
NEXT I
AllCnt = COUNT(AllRdsCnts,@VM) + (AllRdsCnts NE '')
BigRDS = ''
BigCnt = ''
FOR I = 1 TO AllCnt
IF AllRdsCnts<1,I> > BigCnt THEN
BigCnt = AllRdsCnts<1,I>
BigRDS = AllRdsNos<1,I>
END
NEXT I
Result = XLATE('REACT_RUN',BigRDS,REACT_RUN_REACTOR$,'X')
RETURN Result
* * * * * * *
ConvertCleanInsp:
* * * * * * *
WONo = Parms[1,@RM]
WOStep = Parms[COL2()+1,@RM]
CassNo = Parms[COL2()+1,@RM]
IF WONo = '' THEN ErrorMsg = 'Null Parm "WONo" passed to routine. (':Method:')'
IF WOStep = '' THEN ErrorMsg = 'Null Parm "WOStep" passed to routine. (':Method:')'
IF CassNo = '' THEN ErrorMsg = 'Null Parm "CassNo" passed to routine. (':Method:')'
IF ErrorMsg NE '' THEN RETURN
WMOutKey = WONo:'*':WOStep:'*':CassNo
otParms = 'WM_OUT':@RM:WMOutKey
WMOutRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
IF Get_Status(errCode) THEN
ErrorMsg = 'Unable to open WM_OUT Record for update.(':Method:')'
RETURN
END
CINo = XLATE('WO_MAT',WONo:'*':CassNo,WO_MAT_EPO_CI_NO$,'X')
WMOutRec<WM_OUT_CI_NO$> = CINo
otParms = FIELDSTORE(otParms,@RM,4,0,WMOutRec)
obj_Tables('WriteRec',otParms)
IF Get_Status(errCode) THEN
ErrorMsg = 'Unable to open WM_OUT Record for update.(':Method:')'
RETURN
END
obj_Tables('UnlockRec',otParms) ;* Unlock the WM_OUT record
cotParms = 'CLEAN_INSP':@RM:CINo
CIRec = obj_Tables('ReadRec',cotParms) ;* Reads and sets lock
IF Get_Status(errCode) THEN
ErrorMsg = 'Unable to open CLEAN_INSP Record for update.(':Method:')'
RETURN
END
CIRec<CLEAN_INSP_CLEAN_TOOL$> = WMOutRec<WM_OUT_POST_CODE$>
CIRec<CLEAN_INSP_CLEAN_BOAT_ID$> = WMOutRec<WM_OUT_POST_BOAT_ID$>
CIRec<CLEAN_INSP_CLEAN_SRD_NO$> = WMOutRec<WM_OUT_POST_SRD_NO$>
CIRec<CLEAN_INSP_CLEAN_SIG$> = WMOutRec<WM_OUT_POST_EPI_SIG$>
CIRec<CLEAN_INSP_CLEAN_SIG_DTM$> = WMOutRec<WM_OUT_POST_EPI_SIG_DTM$>
CIRec<CLEAN_INSP_INSP_PITS$> = WMOutRec<WM_OUT_POST_PITS$>
CIRec<CLEAN_INSP_INSP_MOUNDS$> = WMOutRec<WM_OUT_POST_MOUNDS$>
CIRec<CLEAN_INSP_INSP_LPD_IN$> = WMOutRec<WM_OUT_LPD_FIRSTWAFER$>
CIRec<CLEAN_INSP_INSP_LPD_OUT$> = WMOutRec<WM_OUT_LPD_POSTCLEAN$>
CIRec<CLEAN_INSP_INSP_SIG$> = WMOutRec<WM_OUT_SUP_VER_SIG$>
CIRec<CLEAN_INSP_INSP_SIG_DTM$> = WMOutRec<WM_OUT_SUP_VER_SIG_DTM$>
CIRec<CLEAN_INSP_INSP_BL_DEFECTS$> = WMOutRec<WM_OUT_POST_BL_DEFECTS$>
CIRec<CLEAN_INSP_INSP_STACK_FAULTS$> = WMOutRec<WM_OUT_POST_STACK_FAULTS$>
CIRec<CLEAN_INSP_INSP_SPIKES$> = WMOutRec<WM_OUT_POST_SPIKES$>
CIRec<CLEAN_INSP_INSP_SPOTS$> = WMOutRec<WM_OUT_POST_SPOTS$>
CIRec<CLEAN_INSP_INSP_FOV$> = WMOutRec<WM_OUT_POST_FOV$>
CIRec<CLEAN_INSP_INSP_SCRATCHES$> = WMOutRec<WM_OUT_POST_SCRATCHES$>
CIRec<CLEAN_INSP_INSP_SCRATCH_LEN$> = WMOutRec<WM_OUT_POST_SCRATCH_LEN$>
SurfScanKey = WONO:'*':WOStep:'*':CassNo:'*':'PC'
SurfScanRec = XLATE('SURFACE_SCAN',SurfScanKey,'','X')
IF SurfScanRec NE '' THEN
CIRec<CLEAN_INSP_SCAN_TOOL$> = SurfScanRec<SURFACE_SCAN_SCAN_TOOL$>
CIRec<CLEAN_INSP_SCAN_SIG_DTM$> = SurfScanRec<SURFACE_SCAN_SCAN_DTM$>
CIRec<CLEAN_INSP_SCAN_SUM_OF_DEF_MIN$> = SurfScanRec<SURFACE_SCAN_SUM_OF_DEF_MIN$>
CIRec<CLEAN_INSP_SCAN_SUM_OF_DEF_MAX$> = SurfScanRec<SURFACE_SCAN_SUM_OF_DEF_MAX$>
CIRec<CLEAN_INSP_SCAN_SUM_OF_DEF_AVG$> = SurfScanRec<SURFACE_SCAN_SUM_OF_DEF_AVG$>
CIRec<CLEAN_INSP_SCAN_HAZE_AVG_MIN$> = SurfScanRec<SURFACE_SCAN_HAZE_AVG_MIN$>
CIRec<CLEAN_INSP_SCAN_HAZE_AVG_MAX$> = SurfScanRec<SURFACE_SCAN_HAZE_AVG_MAX$>
CIRec<CLEAN_INSP_SCAN_HAZE_AVG_AVG$> = SurfScanRec<SURFACE_SCAN_HAZE_AVG_AVG$>
END
cotParms = FIELDSTORE(cotParms,@RM,4,0,CIRec)
obj_Tables('WriteRec',cotParms)
IF Get_Status(errCode) THEN
ErrorMsg = 'Unable to Write updated CLEAN_INSP record.(':Method:')'
RETURN
END
RETURN