5607 lines
173 KiB
Plaintext
5607 lines
173 KiB
Plaintext
COMPILE FUNCTION obj_WO_Mat(Method,Parms)
|
|
/*
|
|
Methods for the Work Order Material (WO_MAT) table
|
|
|
|
10/17/2006 JCH - Initial Coding
|
|
11/12/2018 DJS - Updated SignNCR routine to not prematurely auto-FQA when all wafers currently in the cassette
|
|
have been NCR'd. (e.g. 7 of 7 wafers NCR'd, but cassette not yet complete (full).)
|
|
01/14/2019 DJS - Updated the SetSignature routine to write regardless if the record is locked. This is to help
|
|
keep the signatures in WO_MAT and RDS records in sync.
|
|
10/29/2019 DJS - Updated material log entry method to be more reliable. Material log entries in quick succession
|
|
were failing to be recorded.
|
|
11/06/2019 DJS - Updated test wafer quantity calculation within GetGRProps for GaN to use the IN_WFR_ID column
|
|
instead of the CHAR_WFR_ID column, which is no longer used by the GaN system.
|
|
|
|
Properties:
|
|
|
|
Methods:
|
|
|
|
Create(WONo,CassNo,......) ;* Create new WO Material entry
|
|
Delete(WONo,CassNo) ;* Delete only if certain conditions are met
|
|
CurrStatus(WONo,CassNo) ;* Curr status of this cassette
|
|
AddInvTrans(LogTable,WONo,CassNo,InvLocation,InvAction,Tag) ;* Adds Inventory transactions at current DTM and with Current User (@USER4)
|
|
CassInvHistory(WONo,CassNo,InvField) ;* Returns Inventory history for this box
|
|
|
|
*/
|
|
#pragma precomp SRP_PreCompiler
|
|
|
|
|
|
DECLARE FUNCTION Get_Status, Msg, Utility, obj_Tables, Dialog_Box,NextKey, Popup, Get_Property, obj_RDS, RetStack
|
|
DECLARE FUNCTION Database_Services, GaN_Services, Logging_Services, Environment_Services, Signature_Services
|
|
DECLARE FUNCTION obj_WO_Mat, obj_WM_In, obj_WM_Out, obj_Prod_Spec, obj_Clean_Insp, obj_Calendar, obj_Popup
|
|
DECLARE FUNCTION Error_Services, Memberof, Datetime
|
|
DECLARE SUBROUTINE Set_Status, Msg, obj_Tables, Send_Dyn, Btree.Extract, ErrMsg, Send_Dyn, RList, obj_WO_Log, Send_Event, obj_RDS, Extract_SI_Keys
|
|
DECLARE SUBROUTINE obj_notes, obj_Clean_Insp, obj_Post_Log, Send_Info, obj_WO_Mat_Log, obj_SAP, obj_WO_Mat, obj_Pend_Ship_Labels, obj_WO_Mat_QA
|
|
DECLARE SUBROUTINE obj_WO_Wfr, Logging_Services, Set_Property, Delete, Database_Services, SRP_Stopwatch
|
|
DECLARE SUBROUTINE Material_Services, Work_Order_Services
|
|
|
|
$INSERT MSG_EQUATES
|
|
$INSERT WO_MAT_EQUATES
|
|
$INSERT WM_OUT_EQUATES
|
|
$INSERT WM_IN_EQUATES
|
|
$INSERT WO_STEP_EQU
|
|
$INSERT WO_LOG_EQUATES
|
|
$INSERT NOTIFICATION_EQU
|
|
$INSERT RDS_MAKEUP_EQU
|
|
$INSERT DICT_EQUATES
|
|
$INSERT REACT_RUN_EQUATES
|
|
$INSERT ORDER_EQU
|
|
$INSERT ORDER_DET_EQU
|
|
$INSERT RDS_EQU
|
|
$INSERT PROD_SPEC_EQUATES
|
|
$INSERT PRS_STAGE_EQUATES
|
|
$INSERT QUOTE_SPEC_EQU
|
|
$INSERT SAP_LOG_EQUATES
|
|
$INSERT CUST_EPI_PART_EQUATES
|
|
$INSERT EPI_PART_EQUATES
|
|
$INSERT PROD_VER_EQUATES
|
|
$INSERT COMPANY_EQUATES
|
|
$INSERT SEMI_VEND_CODE_EQUATES
|
|
$INSERT WO_MAT_QA_EQUATES
|
|
$INSERT QA_MET_EQUATES ;* Used for GetQAMet return data structure
|
|
$INSERT LOGICAL
|
|
$INSERT WO_MAT_WFR_EQUATES
|
|
$INSERT RUN_STAGE_EQUATES
|
|
|
|
EQU TARGET_ACTIVELIST$ TO 5
|
|
|
|
EQU CRLF$ TO \0D0A\
|
|
EQU TAB$ TO \09\
|
|
EQU Comma$ TO ','
|
|
|
|
errCode = ''
|
|
|
|
ErrTitle = 'Error in Stored Procedure "obj_WO_Mat"'
|
|
ErrorMsg = ''
|
|
LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WO_Mat'
|
|
LogDate = Oconv(Date(), 'D4/')
|
|
LogTime = Oconv(Time(), 'MTS')
|
|
LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' Dual Status Log.csv'
|
|
Headers = 'Logging DTM' : @FM : 'Source' : @FM : 'ProdOrdNo' : @FM : 'WO#' : @FM : 'InCassNo' : @FM : 'GRWfrQty' : @FM : 'ScrapQty' : @FM : 'ProdTWQty' : @FM : 'CassID' : @FM : 'LotNo' : @FM : 'SubSuppCd' : @FM : 'CustPartRev' : @FM : 'MakeupFlag' : @FM : 'MUBatchNo' : @FM : 'MUCassQty'
|
|
objLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, Comma$, Headers, '', False$, False$)
|
|
LoggingDTM = LogDate : ' ' : LogTime ; // Logging DTM
|
|
|
|
WOMatLogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WO_Mat'
|
|
WOMatLogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' NCR_FQA.csv'
|
|
WOMatHeaders = 'Logging DTM' : @FM : 'WONo' : @FM : 'CassNo' : @FM : 'NCRNo' : @FM : 'CurrWfrCnt'
|
|
WOMatObjLog = Logging_Services('NewLog', WOMatLogPath, WOMatLogFileName, CRLF$, Comma$, WOMatHeaders, '', False$, False$)
|
|
|
|
WOMatLogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WO_Mat'
|
|
WOMatLogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' WO_MAT_LOG.csv'
|
|
WOMatHeaders = 'Logging DTM' : @FM : 'WONo' : @FM : 'CassNo' : @FM : 'User' : @FM : 'Log Pos' : @FM : 'Tag' : @FM : 'Warehouse' : @FM : 'Loc' : @FM : 'InvAction' : @FM : 'ToolID'
|
|
WOMatObjLog2 = Logging_Services('NewLog', WOMatLogPath, WOMatLogFileName, CRLF$, Comma$, WOMatHeaders, '', False$, False$)
|
|
|
|
WOMatLogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WO_Mat'
|
|
WOMatLogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' WO_MAT_LOG - Log Attempts.csv'
|
|
WOMatHeaders = 'Logging DTM' : @FM : 'WONo' : @FM : 'CassNo' : @FM : 'User' : @FM : 'Log Pos' : @FM : 'Tag' : @FM : 'Warehouse' : @FM : 'Loc' : @FM : 'InvAction' : @FM : 'ToolID'
|
|
WOMatObjLog3 = Logging_Services('NewLog', WOMatLogPath, WOMatLogFileName, CRLF$, Comma$, WOMatHeaders, '', False$, False$)
|
|
|
|
WOMatLogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WO_Mat'
|
|
WOMatLogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' WO_MAT_LOG - PTI.csv'
|
|
WOMatHeaders = 'Logging DTM' : @FM : 'WONo' : @FM : 'CassNo' : @FM : 'User' : @FM : 'Log Pos' : @FM : 'Tag' : @FM : 'Warehouse' : @FM : 'Loc' : @FM : 'InvAction' : @FM : 'ToolID'
|
|
WOMatObjLog4 = Logging_Services('NewLog', WOMatLogPath, WOMatLogFileName, CRLF$, Comma$, WOMatHeaders, '', False$, False$)
|
|
|
|
SignNCRLogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\NCR'
|
|
SignNCRLogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' SIGN_NCR.csv'
|
|
SignNCRHeaders = 'Logging DTM':@FM:'WONo':@FM:'CassNo':@FM:'NCRNo':@FM:'SignBy':@FM:'SignByDTM':@FM:'Notes'
|
|
SignNCRObjLog = Logging_Services('NewLog', SignNCRLogPath, SignNCRLogFileName, CRLF$, Comma$, SignNCRHeaders, '', False$, False$)
|
|
|
|
RemNCRLogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\NCR'
|
|
RemNCRLogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' REM_NCR.csv'
|
|
RemNCRHeaders = 'Logging DTM':@FM:'WONo':@FM:'CassNo':@FM:'NCRNo':@FM:'SlotNos':@FM:'RejWaferIDs':@FM:'PrevNCRNos':@FM:'Notes':@FM:'User'
|
|
RemNCRObjLog = Logging_Services('NewLog', RemNCRLogPath, RemNCRLogFileName, CRLF$, Comma$, RemNCRHeaders, '', False$, False$)
|
|
|
|
WOMatLogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WO_Mat'
|
|
WOMatLogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' CurrStatus Log.csv'
|
|
WOMatHeaders = 'Logging DTM' : @FM : 'User' : @FM : 'WOMatKey' : @FM : 'Calculated Value' : @FM : 'Physical Value'
|
|
objCurrStatusLog = Logging_Services('NewLog', WOMatLogPath, WOMatLogFileName, CRLF$, Comma$, WOMatHeaders, '', False$, False$)
|
|
|
|
SAPLogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\SAP'
|
|
SAPFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' SetSAPBatch Log.csv'
|
|
SAPHeaders = 'Logging DTM' : @FM : 'WOMatKey' : @FM : 'SAPBatchNo'
|
|
objSAPLog = Logging_Services('NewLog', SAPLogPath, SAPFileName, CRLF$, Comma$, SAPHeaders, '', 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
|
|
|
|
/*
|
|
TraceOn = XLATE('PROGRAM_TRACE',@STATION:'*FLAG','','X')
|
|
IF TraceOn THEN
|
|
OPEN 'PROGRAM_TRACE' TO PTFile THEN
|
|
READ TraceLog FROM PTFile,@STATION:'*LOG' ELSE TraceLog = ''
|
|
LogParms = Parms
|
|
CONVERT @RM TO '/' IN LogParms
|
|
TraceLog := @FM:"obj_WO_Mat('":Method:"',":LogParms
|
|
WRITE TraceLog ON PTFile,@STATION:'*LOG' THEN NULL
|
|
END
|
|
END
|
|
*/
|
|
|
|
Result = ''
|
|
|
|
BEGIN CASE
|
|
CASE Method = 'Create' ; GOSUB Create
|
|
CASE Method = 'CreateWMO' ; GOSUB CreateWMO
|
|
CASE Method = 'Delete' ; GOSUB Delete
|
|
CASE Method = 'LockSet' ; GOSUB LockSet
|
|
CASE Method = 'UnlockSet' ; GOSUB UnlockSet
|
|
CASE Method = 'CurrStatus' ; GOSUB CurrStatus
|
|
Case Method = 'OutofPTO' ; Gosub OutofPTO
|
|
CASE Method = 'CRComp' ; GOSUB CRComp ;* Cleanroom Complete flag
|
|
CASE Method = 'PartNo' ; GOSUB PartNo ;* Added 9/22/2010 jch
|
|
CASE Method = 'AddInvTrans' ; GOSUB AddInvTrans
|
|
CASE Method = 'InvDelta' ; GOSUB InvDelta
|
|
CASE Method = 'TimeInFab' ; GOSUB TimeInFab
|
|
CASE Method = 'ProcessTime' ; GOSUB ProcessTime
|
|
CASE Method = 'EpiCassInvHistory' ; GOSUB EpiCassInvHistory
|
|
CASE Method = 'ToggleHold' ; GOSUB ToggleHold
|
|
CASE Method = 'EditHoldReason' ; GOSUB EditHoldReason
|
|
CASE Method = 'ChangeFlag' ; GOSUB ChangeFlag
|
|
CASE Method = 'AddNCR' ; GOSUB AddNCR
|
|
CASE Method = 'RemNCR' ; GOSUB RemNCR
|
|
CASE Method = 'SignNCR' ; GOSUB SignNCR
|
|
CASE Method = 'AddMakeupWafers' ; GOSUB AddMakeupWafers
|
|
CASE Method = 'RemMakeupWafers' ; GOSUB RemMakeupWafers
|
|
CASE Method = 'SubMakeupWafers' ; GOSUB SubMakeupWafers
|
|
CASE Method = 'RepMakeupWafers' ; GOSUB RepMakeupWafers
|
|
CASE Method = 'BackfillNCR' ; GOSUB BackfillNCR
|
|
CASE Method = 'ChangeCassProps' ; GOSUB ChangeCassProps
|
|
CASE Method = 'SlotWaferIDs' ; GOSUB SlotWaferIDs
|
|
CASE Method = 'CurrWaferCnt' ; GOSUB CurrWaferCnt
|
|
CASE Method = 'GetGRProps' ; GOSUB GetGRProps
|
|
CASE Method = 'ConvertMakeup' ; GOSUB ConvertMakeup
|
|
CASE Method = 'RemProdTW' ; GOSUB RemProdTW
|
|
CASE Method = 'RepProdTW' ; GOSUB RepProdTW
|
|
CASE Method = 'SetWMStatus' ; GOSUB SetWMStatus
|
|
CASE Method = 'ReportStatus' ; GOSUB ReportStatus
|
|
CASE Method = 'CassRDSNos' ; GOSUB CassRDSNos
|
|
CASE Method = 'CassRDSWfrCnts' ; GOSUB CassRDSWfrCnts
|
|
CASE Method = 'CassSigProfile' ; GOSUB CassSigProfile
|
|
CASE Method = 'CassMetProfile' ; GOSUB CassMetProfile
|
|
CASE Method = 'SetSignature' ; GOSUB SetSignature
|
|
CASE Method = 'ClearSignature' ; GOSUB ClearSignature
|
|
CASE Method = 'TestStatus' ; GOSUB TestStatus
|
|
CASE Method = 'SigDt' ; GOSUB SigDt
|
|
CASE Method = 'AddShip' ; GOSUB AddShip
|
|
CASE Method = 'RemShip' ; GOSUB RemShip
|
|
CASE Method = 'AddReship' ; GOSUB AddReship
|
|
CASE Method = 'SetPartNo' ; GOSUB SetPartNo
|
|
CASE Method = 'RefreshSigProfile' ; GOSUB RefreshSigProfile
|
|
CASE Method = 'SetWfrQty' ; GOSUB SetWfrQty
|
|
CASE Method = 'UpdateSpec' ; GOSUB UpdateSpec
|
|
CASE Method = 'FinalSigComp' ; GOSUB FinalSigComp
|
|
CASE Method = 'SetSAPBatch' ; GOSUB SetSAPBatch
|
|
CASE Method = 'GetCycleTime' ; GOSUB GetCycleTime
|
|
CASE Method = 'GetQAMet' ; GOSUB GetQAMet
|
|
CASE Method = 'GetMUCassIDs' ; GOSUB GetMUCassIDs
|
|
CASE Method = 'GetEventLog' ; GOSUB GetEventLog
|
|
CASE Method = 'GetADERead' ; GOSUB GetADERead
|
|
CASE Method = 'CheckSigOrder' ; GOSUB CheckSigOrder
|
|
CASE Method = 'MQAComp' ; GOSUB MQAComp
|
|
CASE Method = 'EpiReactNo' ; GOSUB EpiReactNo
|
|
CASE Method = 'GetSigProfile' ; GOSUB GetSigProfile
|
|
CASE Method = 'GetQAMetKeys' ; GOSUB GetQAMetKeys
|
|
CASE Method = 'AddQAMet' ; GOSUB AddQAMet
|
|
CASE Method = 'RemQAMet' ; GOSUB RemQAMet
|
|
Case Method = 'GetWfrKeys' ; Gosub GetWfrKeys
|
|
CASE Method = 'GetBinLocID' ; GOSUB GetBinLocID
|
|
CASE Method = 'GetMUAddedDTMS' ; GOSUB GetMUAddedDTMS
|
|
CASE Method = 'GetMURemovedDTMS' ; GOSUB GetMURemovedDTMS
|
|
CASE Method = 'ExpCOA' ; GOSUB ExpCOA
|
|
|
|
CASE 1
|
|
ErrorMsg = 'Unknown Method ':QUOTE(Method):' passed to routine.'
|
|
|
|
END CASE
|
|
|
|
IF ErrorMsg NE '' THEN
|
|
Set_Status(-1,ErrTitle:@SVM:ErrorMsg)
|
|
RETURN ''
|
|
END
|
|
|
|
RETURN Result
|
|
|
|
* * * * * * *
|
|
GetWfrKeys:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
If WOMatKey = '' Then Return
|
|
|
|
If WOMatRec = '' Then
|
|
WOMatRec = Xlate('WO_MAT',WOMatKey,'','X')
|
|
End
|
|
|
|
WOWfrIDs = ''
|
|
Extract_SI_Keys('WO_WFR', 'CURR_CASS_ID', WOMatKey, WOWfrIDs)
|
|
|
|
CurrLocs = Xlate('WO_WFR',WOWfrIDs,'CURR_LOC','X')
|
|
|
|
Result = CurrLocs
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
Create:
|
|
* * * * * * *
|
|
|
|
WONo = Parms[1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
ProdVerNo = Parms[COL2()+1,@RM]
|
|
LotNo = Parms[COL2()+1,@RM]
|
|
WaferQty = Parms[COL2()+1,@RM]
|
|
CustPartNo = Parms[COL2()+1,@RM]
|
|
OrderItem = Parms[COL2()+1,@RM]
|
|
ReactType = Parms[COL2()+1,@RM]
|
|
SubPartNo = Parms[COL2()+1,@RM]
|
|
RxWH = Parms[COL2()+1,@RM]
|
|
RxLocation = Parms[COL2()+1,@RM]
|
|
RxDTM = Parms[COL2()+1,@RM]
|
|
RxBy = Parms[COL2()+1,@RM]
|
|
SubSupplyBy = Parms[COL2()+1,@RM]
|
|
MUWaferFlag = Parms[COL2()+1,@RM]
|
|
RetRejects = Parms[COL2()+1,@RM]
|
|
Reprocessed = Parms[COL2()+1,@RM]
|
|
CassShipQty = Parms[COL2()+1,@RM]
|
|
ShipShort = Parms[COL2()+1,@RM]
|
|
SubVendCd = Parms[COL2()+1,@RM]
|
|
MinCassShipQty = Parms[Col2() + 1, @RM]
|
|
|
|
IF WONo = '' THEN ErrorMsg = 'Null parameter "WONo" passed to routine. (':Method:')'
|
|
IF CassNo = '' THEN ErrorMsg = 'Null parameter "CassNo" passed to routine. (':Method:')'
|
|
IF LotNo = '' THEN ErrorMsg = 'Null parameter "LotNo" passed to routine. (':Method:')'
|
|
IF WaferQty = '' THEN ErrorMsg = 'Null parameter "Wafer Qty" passed to routine. (':Method:')'
|
|
IF CustPartNo = '' THEN ErrorMsg = 'Null parameter "Cust PartNo" passed to routine. (':Method:')'
|
|
IF OrderItem = '' THEN ErrorMsg = 'Null parameter "OrderItem" passed to routine. (':Method:')'
|
|
IF ReactType = '' THEN ErrorMsg = 'Null parameter "ReactType" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
IF RxWH = '' THEN RxWH = 'SR' ;* Shipping/Receiving area
|
|
IF RxLocation = '' THEN RxLocation = 'RB' ;* Receiving Bench
|
|
IF RxBy = '' THEN RxBy = @USER4 ;* Current LSL user
|
|
IF RxDTM = '' THEN
|
|
CurrDate = OCONV(Date(),'D4/')
|
|
CurrTime = OCONV(Time(),'MTS')
|
|
thisRxDTM = ICONV(CurrDate:' ':CurrTime,'DT') ;* Use Current Date-Time for default
|
|
END ELSE
|
|
thisRxDTM = ICONV(RxDTM,'DT')
|
|
END
|
|
|
|
IF ReactType = 'P' THEN ReactType = 'EPP' ;* Reactor Type code cleanups
|
|
|
|
WOMatKey = WONo:'*':CassNo
|
|
|
|
WOMatRec = ''
|
|
|
|
WOMatRec<WO_MAT_LOT_NO$> = LotNo
|
|
WOMatRec<WO_MAT_WAFER_QTY$> = WaferQty
|
|
WOMatRec<WO_MAT_CUST_PART_NO$> = CustPartNo
|
|
WOMatRec<WO_MAT_SUB_PART_NO$> = SubPartNo
|
|
WOMatRec<WO_MAT_ORDER_ITEM$> = OrderItem
|
|
WOMatRec<WO_MAT_PROD_VER_NO$> = ProdVerNo
|
|
WOMatRec<WO_MAT_INV_WH$> = RxWH
|
|
WOMatRec<WO_MAT_INV_LOCATION$> = RxLocation
|
|
WOMatRec<WO_MAT_INV_ACTION$> = 'RCVD'
|
|
WOMatRec<WO_MAT_INV_DTM$> = thisRxDTM
|
|
WOMatRec<WO_MAT_INV_TAG$> = '' ;* No tag actually scanned -> so no tag value
|
|
WOMatRec<WO_MAT_INV_USER$> = RxBy
|
|
WOMatRec<WO_MAT_RX_DTM$> = thisRxDTM
|
|
WOMatRec<WO_MAT_RX_BY$> = RxBy
|
|
WOMatRec<WO_MAT_SUB_SUPPL_BY$> = SubSupplyby
|
|
WOMatRec<WO_MAT_MU_WAFER_FLAG$> = MUWaferFlag
|
|
WOMatRec<WO_MAT_RET_REJECTS$> = RetRejects
|
|
WOMatRec<WO_MAT_REPROCESSED_MAT$> = Reprocessed
|
|
WOMatRec<WO_MAT_CASS_SHIP_QTY$> = CassShipQty
|
|
WOMatRec<WO_MAT_SHIP_SHORT$> = ShipShort
|
|
WOMatRec<WO_MAT_SUB_VEND_CD$> = SubVendCd
|
|
WOMatRec<WO_MAT_INV_SCAN_ENTRY$> = False$
|
|
|
|
WaferCnt = WOMatRec<WO_MAT_WAFER_QTY$> ;* Changed to add slots for both EpiPRO and standard reactor types 8/13/2010 JCH
|
|
ShipCnt = WOMatRec<WO_MAT_CASS_SHIP_QTY$>
|
|
|
|
BEGIN CASE
|
|
CASE ShipCnt = '' ; SlotCnt = WaferCnt
|
|
CASE WaferCnt > ShipCnt ; SlotCnt = WaferCnt
|
|
CASE WaferCnt < ShipCnt ; SlotCnt = ShipCnt
|
|
CASE WaferCnt = ShipCnt ; SlotCnt = ShipCnt
|
|
END CASE
|
|
|
|
|
|
FOR I = 1 TO SlotCnt
|
|
WOMatRec<WO_MAT_SLOT_NO$,I> = I
|
|
IF (ShipCnt NE '') AND (WaferCnt < ShipCnt) AND (I > WaferCnt) THEN
|
|
WOMatRec<WO_MAT_SLOT_MET_NO$,I> = 'x' ;* Box is received less than ShipQty -> add slot but place 'x' in Met column to 'indicate' empty slot
|
|
END
|
|
NEXT I
|
|
|
|
* * * * * * * * Build QA_MET profile * * * * * * * *
|
|
|
|
obj_WO_Mat_QA('Create',WONo:@RM:CassNo) ;* Added 5/28/2015 JCH
|
|
|
|
|
|
IF ReactType = 'P' OR ReactType = 'EPP' THEN
|
|
|
|
*Inbound EpiPRO material
|
|
|
|
WOStepKeys = XLATE('WO_LOG',WONo,WO_LOG_WO_STEP_KEY$,'X')
|
|
EpiProPSNo = XLATE('WO_STEP',WOStepKeys<1,1>,WO_STEP_PROD_SPEC_ID$,'X')
|
|
EpiProPSRec = XLATE('PROD_SPEC',EpiProPSNo,'','X')
|
|
|
|
|
|
WOMatRec<WO_MAT_EPI_PRO$> = 1 ;* Added 7/29/2010 JCH
|
|
|
|
IF RowExists('PRS_STAGE',EpiProPSNo:'*PRE') THEN
|
|
|
|
ociParms = WONo:@RM ;* WONo
|
|
ociParms := 1:@RM ;* WOStep
|
|
ociParms := CassNo:@RM ;* CassNo
|
|
ociParms := 'PRE':@RM ;* Stage ;* Pre Epi Cleaning on inbound material
|
|
ociParms := '':@RM ;* RDSNo ;* No specific RDS on Epi Pro inbound material
|
|
ociParms := EpiProPSNo:@RM ;* PSNo
|
|
ociParms := EpiProPSRec ;* PSRec
|
|
|
|
WOMatRec<WO_MAT_EPI_CI_NO$> = obj_Clean_Insp('Create',ociParms) ;* Added 8/13/2010
|
|
|
|
IF Get_Status(errCode) THEN ErrMsg(errCode)
|
|
|
|
END ;* End of check for PRS_Stage record
|
|
|
|
|
|
* Outbound EpiPRO empty cassette creation - This section setup 11/14/2011 JCH
|
|
|
|
IF RowExists('PRS_STAGE',EpiProPSNo:'*POST') THEN
|
|
|
|
|
|
ociParms = WONo:@RM ;* WONo
|
|
ociParms := 1:@RM ;* WOStep
|
|
ociParms := CassNo:@RM ;* CassNo
|
|
ociParms := 'POST':@RM ;* Stage
|
|
ociParms := '':@RM ;* RDSNo
|
|
ociParms := EpiProPSNo:@RM ;* PSNo
|
|
ociParms := EpiProPSRec ;* PSRec
|
|
|
|
PostCINo = obj_Clean_Insp('Create',ociParms)
|
|
WOMatRec<WO_MAT_EPO_CI_NO$> = PostCINo
|
|
END
|
|
END
|
|
|
|
|
|
IF Reprocessed THEN
|
|
Result = '1PSTC':@VM:'1PSTS':@VM:'1PSTI':@VM:'1QA'
|
|
END ELSE
|
|
GOSUB CassSigProfile ;* 8/22/2009 JCH Added signature profile
|
|
END
|
|
|
|
WOMatRec<WO_MAT_SIG_PROFILE$> = Result ;* 8/22/2009 JCH
|
|
Result = ''
|
|
|
|
|
|
OtParms = 'WO_MAT':@RM:WOMatKey:@RM:@RM:WOMatRec
|
|
obj_Tables('WriteRec',OtParms)
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
CreateWMO:
|
|
* * * * * * *
|
|
|
|
* Creates basic WO_MAT record for EpiPRO Outbound cassette w/o corresponding WM_IN cassette
|
|
|
|
WONo = Parms[1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
|
|
|
|
|
|
|
|
IF WONo = '' THEN ErrorMsg = 'Null parameter "WONo" passed to routine. (':Method:')'
|
|
IF CassNo = '' THEN ErrorMsg = 'Null parameter "CassNo" passed to routine. (':Method:')'
|
|
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
WORec = XLATE('WO_LOG',WONo,'','X')
|
|
|
|
CustPartNo = WOrec<WO_LOG_CUST_PART_NO$>
|
|
SubPartNo = WORec<WO_LOG_ORD_SUB_PART_NO$>
|
|
|
|
EpiProFlag = 1
|
|
|
|
WOStepKeys = XLATE('WO_LOG',WONo,WO_LOG_WO_STEP_KEY$,'X')
|
|
LastWOStepKey = WOStepKeys[-1,'B':@VM]
|
|
|
|
EPIPartNo = WORec<WO_LOG_EPI_PART_NO$>
|
|
EPIPartRec = XLATE('EPI_PART',EpiPartNo,'','X')
|
|
|
|
SubSuppBy = EPIPartRec<EPI_PART_SUB_SUPP_BY$> ;* L - EpiSvcs supplied, C - Customer Supplied
|
|
|
|
ProdVerNo = WORec<WO_LOG_PROD_VER_NO$>
|
|
CustNo = WORec<WO_LOG_CUST_NO$>
|
|
|
|
CustEpiPartRec = XLATE('CUST_EPI_PART',CustNo:'*':EpiPartNo,'','X') ;* Added 7/31/2012 JCH
|
|
MUWaferFlag = CustEpiPartRec<CUST_EPI_PART_MAKEUP_WAFERS$> ;* Added 7/31/2012 JCH
|
|
RetRejects = CustEpiPartRec<CUST_EPI_PART_RET_REJECTS$> ;* Added 7/31/2012 JCH
|
|
CassShipQty = CustEpiPartRec<CUST_EPI_PART_CASS_SHIP_QTY$> ;* Added 7/31/2012 JCH
|
|
ShipShort = CustEpiPartRec<CUST_EPI_PART_EPI_PRO_SHIP_SHORT$> ;* Added 7/31/2012 JCH
|
|
Reprocessed = '' ;* Added 12/16/2009 JCH to match parms passed to obj_WO_Mat('Create
|
|
MinCassShipQty = CustEpiPartRec<CUST_EPI_PART_MIN_CASS_SHIP_QTY$> ; // Added 02/01/2018 dmb
|
|
|
|
|
|
WOMatKey = WONo:'*':CassNo
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X') ;* Added 8/21/2013 JCH - WO_MAT record may exist only because a WM_OUT is in place.
|
|
|
|
WOMatRec<WO_MAT_LOT_NO$> = ''
|
|
WOMatRec<WO_MAT_WAFER_QTY$> = ''
|
|
WOMatRec<WO_MAT_CUST_PART_NO$> = CustPartNo
|
|
WOMatRec<WO_MAT_SUB_PART_NO$> = SubPartNo
|
|
WOMatRec<WO_MAT_ORDER_ITEM$> = '' ;* OrderItem
|
|
WOMatRec<WO_MAT_INV_WH$> = ''
|
|
WOMatRec<WO_MAT_INV_LOCATION$> = ''
|
|
WOMatRec<WO_MAT_INV_ACTION$> = ''
|
|
WOMatRec<WO_MAT_INV_DTM$> = ''
|
|
WOMatRec<WO_MAT_INV_TAG$> = '' ;* No tag actually scanned -> so no tag value
|
|
WOMatRec<WO_MAT_INV_USER$> = ''
|
|
WOMatRec<WO_MAT_RX_DTM$> = ''
|
|
WOMatRec<WO_MAT_RX_BY$> = ''
|
|
WOMatRec<WO_MAT_SUB_SUPPL_BY$> = SubSuppBy
|
|
WOMatRec<WO_MAT_MU_WAFER_FLAG$> = MUWaferFlag
|
|
WOMatRec<WO_MAT_RET_REJECTS$> = ''
|
|
WOMatRec<WO_MAT_REPROCESSED_MAT$> = ''
|
|
WOMatRec<WO_MAT_CASS_SHIP_QTY$> = CassShipQty ;* Added 6/14/2016 JCH *********
|
|
WOMatRec<WO_MAT_SHIP_SHORT$> = ShipShort
|
|
WOMatRec<WO_MAT_EPI_PRO$> = EpiProFlag ;* Added EpiProFlag variable 6/14/2016 JCH
|
|
WOMatRec<WO_MAT_MIN_CASS_SHIP_QTY$> = MinCassShipQty ; // Added 02/01/2018 dmb
|
|
|
|
GOSUB CassSigProfile ;* 8/22/2009 JCH Added signature profile
|
|
|
|
WOMatRec<WO_MAT_SIG_PROFILE$> = Result ;* 8/22/2009 JCH
|
|
Result = ''
|
|
|
|
OtParms = 'WO_MAT':@RM:WOMatKey:@RM:@RM:WOMatRec
|
|
obj_Tables('WriteRec',OtParms)
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
Delete:
|
|
* * * * * * *
|
|
|
|
WONo = Parms[1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
|
|
WOMatKey = WONo:'*':CassNo
|
|
|
|
ReactType = XLATE('WO_LOG',WONo,'PS_REACTOR_TYPE','X')<1,1>
|
|
|
|
IF ReactType = 'P' THEN ReactType = 'EPP' ;* React Type code cleanup JCH 9/2/2014
|
|
|
|
TableVar = ''
|
|
OtParms = 'WO_MAT':@RM:WOMatKey:@RM:TableVar
|
|
WOMatRec = obj_Tables('ReadRec',OtParms) ;* Locks and reads record for update
|
|
|
|
EmptyWOMatRec = WOMatRec
|
|
ProdVerNo = WOMatRec<WO_MAT_PROD_VER_NO$>
|
|
CIKeys = WOMatRec<WO_MAT_CLEAN_INSP_KEY$>
|
|
|
|
CONVERT @FM TO '' IN EmptyWOMatRec
|
|
|
|
DeleteFlag = 0
|
|
|
|
IF (WOMatRec<WO_MAT_SIG_PROFILE$,1> NE '' AND WOMatRec<WO_MAT_SIGNATURE$,1> = '') THEN DeleteFlag = 1
|
|
IF EmptyWOMatRec = '' THEN DeleteFlag = 1
|
|
IF EmptyWOMatRec = ProdVerNo THEN DeleteFlag = 1
|
|
IF EmptyWOMatRec = ProdVerNo:CIKeys THEN DeleteFlag = 1
|
|
IF WOMatRec<WO_MAT_SIG_PROFILE$> = '' THEN DeleteFlag = 1
|
|
|
|
IF DeleteFlag = 1 THEN
|
|
|
|
IF WOMatRec<WO_MAT_RDS_NO$> NE '' THEN
|
|
|
|
RDSCnt = COUNT(WOMatRec<WO_MAT_RDS_NO$>,@VM) + (WOMatRec<WO_MAT_RDS_NO$> NE '')
|
|
|
|
FOR I = 1 TO RDSCnt
|
|
Set_Status(0)
|
|
obj_RDS('Delete',WOMatRec<WO_MAT_RDS_NO$,1>)
|
|
NEXT I
|
|
END
|
|
|
|
END ELSE
|
|
ErrorMsg = "Unable to delete WO_Mat Record ":QUOTE(WOMatKey):' has started processing'
|
|
END
|
|
|
|
IF WOMatRec<WO_MAT_RDS_NO$> NE '' THEN
|
|
|
|
Set_Status(0)
|
|
BadRDSNo = obj_RDS('Delete',WOMatRec<WO_MAT_RDS_NO$,1>)
|
|
IF Get_Status(errCode) THEN
|
|
ErrorMsg = "Unable to delete WO_Mat ID ":QUOTE(WOMatKey):' - RDS ':QUOTE(BadRDSNo):' has started processing'
|
|
END
|
|
|
|
END
|
|
|
|
WOStepKeys = XLATE('WO_LOG',WONo,'WO_STEP_KEYS','X')
|
|
|
|
IF ReactType = 'P' OR ReactType = 'EPP' THEN
|
|
|
|
Tmp = ''
|
|
StepCnt = COUNT(WOStepKeys,@VM) + (WOStepKeys NE '')
|
|
FOR I = 1 TO StepCnt
|
|
WMKey = WOStepKeys<1,I>:'*':CassNo
|
|
WMInRec = XLATE('WM_IN',WMKey,'','X')
|
|
WMOutRec = XLATE('WM_OUT',WMKey,'','X')
|
|
|
|
IF WMInRec NE '' THEN
|
|
ErrorMsg = 'Work Order Material record currently has WM_IN records attached and may not be deleted.'
|
|
END
|
|
IF WMOutRec NE '' THEN
|
|
ErrorMsg = 'Work Order Material record currently has WM_OUT records attached and may not be deleted.'
|
|
END
|
|
NEXT I
|
|
|
|
END
|
|
|
|
IF WOMatRec<WO_MAT_CLEAN_INSP_KEY$> NE '' THEN
|
|
obj_Clean_Insp('Delete',WOMatRec<WO_MAT_CLEAN_INSP_KEY$>)
|
|
END
|
|
|
|
InWfrIDs = XLATE('WO_MAT_WFR' , @ID , 'IN_WFR_ID' , 'X' )
|
|
|
|
|
|
IF ErrorMsg = '' THEN
|
|
obj_Tables('DeleteRec',OtParms)
|
|
END ELSE
|
|
obj_Tables('UnlockRec',OtParms)
|
|
END
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
LockSet:
|
|
* * * * * * *
|
|
|
|
WOMKeys = Parms[1,@RM]
|
|
|
|
IF WOMKeys = '' THEN RETURN
|
|
|
|
Set_Status(0)
|
|
WOMParms = 'WO_MAT'
|
|
LockedWOMKeys = ''
|
|
|
|
WOMKeyCnt = COUNT(WOMKeys,@VM) + (WOMKeys NE '')
|
|
|
|
FOR I = 1 TO WOMKeyCnt
|
|
WOMKey = WOMKeys<1,I>
|
|
WOMParms = FieldStore(WOMParms, @RM, 2, 1, WOMKey)
|
|
obj_Tables('LockRec',WOMParms)
|
|
IF Get_Status(errCode) THEN
|
|
LockedWOMKeyCnt = COUNT(LockedWOMKeys,@VM) + (LockedWOMKeys NE '')
|
|
FOR N = 1 TO LockedWOMKeyCnt
|
|
WOMParms = FieldStore(WOMParms, @RM, 2, 1, LockedWOMKeys<1,N>)
|
|
obj_Tables('UnlockRec',WOMParms) ;* Unlock everything locked up to here
|
|
NEXT N
|
|
ErrorMsg = 'Unable to lock WO_MAT ':QUOTE(WOMKey):'.'
|
|
RETURN
|
|
END ELSE
|
|
LockedWOMKeys<1,I> = WOMKey
|
|
END
|
|
NEXT I
|
|
|
|
TableVar = FIELD(WOMParms,@RM,3,1)
|
|
|
|
Result = TableVar
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
UnlockSet:
|
|
* * * * * * *
|
|
|
|
WOMKeys = Parms[1,@RM]
|
|
TableVar = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMKeys = '' THEN RETURN
|
|
IF TableVar = '' THEN RETURN
|
|
|
|
Set_Status(0)
|
|
WOMParms = 'WO_MAT':@RM:@RM:TableVar
|
|
LockedWOMKeys = ''
|
|
|
|
WOMKeyCnt = COUNT(WOMKeys,@VM) + (WOMKeys NE '')
|
|
FOR I = 1 TO WOMKeyCnt
|
|
WOMKey = WOMKeys<1,I>
|
|
WOMParms = FieldStore(WOMParms, @RM, 2, 1, WOMKey)
|
|
obj_Tables('UnlockRec',WOMParms)
|
|
NEXT I
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
CurrStatus:
|
|
* * * * * * *
|
|
* If @User4 EQ 'DANIEL_ST' then SRP_Stopwatch('Reset')
|
|
* If @User4 EQ 'DANIEL_ST' then SRP_Stopwatch('Start', 'Begin CurrStatus')
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN WOMatKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(WOMatRec)) THEN WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
IF WOMatRec<WO_MAT_VOID$> THEN
|
|
Result = 'VOID'
|
|
RETURN
|
|
END
|
|
|
|
IF WOMatRec<WO_MAT_SHIP_NO$> NE '' THEN
|
|
Result = 'SHIP'
|
|
RETURN
|
|
END
|
|
|
|
WMIKey = WOMatRec<WO_MAT_WMI_KEY$>
|
|
WMOKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
|
|
LocCnt = COUNT(WOMatRec<WO_MAT_INV_LOCATION$>,@VM) + (WOMatRec<WO_MAT_INV_LOCATION$> NE '')
|
|
|
|
LastIn = ''
|
|
LastOut = ''
|
|
|
|
FOR I = LocCnt TO 1 STEP -1
|
|
IF WOMatRec<WO_MAT_INV_LOCATION$,I> = 'PTI' AND LastIn = '' THEN
|
|
LastIn = WOMatRec<WO_MAT_INV_DTM$,I>
|
|
END
|
|
|
|
IF WOMatRec<WO_MAT_INV_LOCATION$,I> = 'PTO' AND LastOut = '' THEN
|
|
LastOut = WOMatRec<WO_MAT_INV_DTM$,I>
|
|
END
|
|
UNTIL LastIn NE '' AND LastOut NE ''
|
|
NEXT I
|
|
|
|
LastWH = WOMatRec<WO_MAT_INV_WH$>[-1,'B':@VM]
|
|
LastLoc = WOMatRec<WO_MAT_INV_LOCATION$>[-1,'B':@VM]
|
|
|
|
CurrLoc = ''
|
|
IF LastWH NE '' AND LastLoc NE '' THEN
|
|
CurrLoc = LastWH:'*':LastLoc
|
|
IF CurrLoc = 'SR*SB' THEN CurrLoc = ''
|
|
END
|
|
|
|
BEGIN CASE
|
|
CASE LastIn = '' AND LastOut = '' ; InCleanRoom = 0
|
|
CASE LastIn = '' ; InCleanRoom = 0
|
|
CASE LastOut = '' ; InCleanRoom = 1
|
|
CASE LastOut > LastIn ; InCleanRoom = 0
|
|
CASE LastIn > LastOut ; InCleanRoom = 1
|
|
END CASE
|
|
|
|
IF WMIKey NE '' THEN
|
|
WMIStatus = WOMatRec<WO_MAT_WMI_CURR_STATUS$>
|
|
END ELSE
|
|
WMIStatus = ''
|
|
END
|
|
|
|
|
|
IF WMOKey NE '' THEN
|
|
WMOStatus = WOMatRec<WO_MAT_WMO_CURR_STATUS$>
|
|
IF WMOStatus = 'COMP' AND NOT(InCleanRoom) THEN
|
|
WMOStatus = 'RTS'
|
|
END
|
|
|
|
WMOMakeup = XLATE('WM_OUT',WMOKey,'MAKEUP_BOX','X')
|
|
END ELSE
|
|
WMOStatus = ''
|
|
END
|
|
|
|
IF WMIKey NE '' OR WMOKey NE '' THEN
|
|
InboundStat = ''
|
|
OutboundStat = ''
|
|
|
|
IF WOMatRec<WO_MAT_HOLD$> = 1 THEN
|
|
IF WOMatRec<WO_MAT_HOLD_ENTITY$,1> = 'WM_IN' THEN
|
|
InboundStat = 'HOLD'
|
|
END
|
|
|
|
IF WOMatRec<WO_MAT_HOLD_ENTITY$,1> = 'WM_OUT' THEN
|
|
OutBoundStat = 'HOLD'
|
|
END
|
|
|
|
BEGIN CASE
|
|
CASE InboundStat EQ 'HOLD' AND OutboundStat EQ 'HOLD'
|
|
Result = 'HOLD'
|
|
|
|
CASE InboundStat = '' AND OutboundStat = ''
|
|
Result = ''
|
|
|
|
CASE InboundStat = '' AND OutboundStat NE ''
|
|
Result = WMOStatus
|
|
|
|
CASE InboundStat NE '' AND OutboundStat = ''
|
|
Result = InboundStat
|
|
|
|
CASE InboundStat NE '' AND OutboundStat NE ''
|
|
Result = InboundStat:@VM:WMOStatus
|
|
Result = Result:WMOStatus
|
|
|
|
END CASE
|
|
|
|
RETURN
|
|
END
|
|
|
|
IF WMIKey NE '' THEN
|
|
IF WMIStatus = 'MT' OR WMIStatus = 'VOID' THEN
|
|
NULL
|
|
END ELSE
|
|
InboundStat = WMIStatus
|
|
END
|
|
END
|
|
|
|
IF WMOKey NE '' THEN
|
|
IF WMOStatus = 'RTB' OR WMOStatus = 'VOID' THEN
|
|
NULL
|
|
END ELSE
|
|
OutboundStat = WMOStatus
|
|
END
|
|
END
|
|
|
|
UnhandledCase = False$
|
|
|
|
BEGIN CASE
|
|
|
|
Case WMIStatus EQ 'RFW' and WMOStatus EQ 'QA'
|
|
Result = 'QA'
|
|
|
|
Case WMIStatus EQ 'NCR' and WMOStatus EQ 'SHIP'
|
|
Result = 'SHIP'
|
|
|
|
Case WMIStatus EQ 'NCR' and WMOStatus EQ 'MT'
|
|
Result = 'MT'
|
|
|
|
Case WMIStatus EQ 'NCR' and WMOStatus EQ 'RTS'
|
|
Result = 'RTS'
|
|
|
|
Case WMIStatus EQ 'NCR' and WMOStatus EQ 'RTU'
|
|
Result = 'RTU'
|
|
|
|
CASE WMIStatus EQ 'RFW' and WMOStatus EQ 'BLD'
|
|
Result = 'RFW'
|
|
|
|
CASE WMIStatus EQ 'MT' and WMOStatus EQ 'RTB'
|
|
Result = 'RTB'
|
|
Case WMIStatus EQ 'HOLD' and WMOStatus NE ''
|
|
Result = WMOStatus
|
|
CASE InboundStat = '' AND OutboundStat = ''
|
|
Result = ''
|
|
|
|
CASE InboundStat = '' AND OutboundStat NE ''
|
|
Result = WMOStatus
|
|
|
|
CASE InboundStat NE '' AND OutboundStat = ''
|
|
Result = InboundStat
|
|
|
|
CASE InboundStat NE '' AND OutboundStat NE ''
|
|
Result = InboundStat:@VM
|
|
Result = Result:WMOStatus
|
|
UnhandledCase = True$
|
|
|
|
END CASE
|
|
|
|
If UnhandledCase then
|
|
// Log it in case we need to address an unhandled inbound / outbound status combination.
|
|
LogData = ''
|
|
LogData<1> = LoggingDTM
|
|
LogData<2> = WOMatKey
|
|
LogData<3> = 'Inbound Status: ':InboundStat
|
|
LogData<4> = 'Outbound Status: ':OutboundStat
|
|
Logging_Services('AppendLog', objLog, LogData, @RM, @FM, False$, '', '')
|
|
end
|
|
|
|
RETURN
|
|
END
|
|
|
|
SigArray = Signature_Services('GetSigProfile', WOMatKey)
|
|
|
|
SigProfs = SigArray<1>
|
|
Signatures = SigArray<2>
|
|
|
|
LastSigPos = DCount(SigProfs, @VM) + 1
|
|
LastStepSig = Signatures<0, LastSigPos>
|
|
Canceled = WOMatRec<WO_MAT_CANCELLED$>
|
|
SubSupplyBy = WOMatRec<WO_MAT_SUB_SUPPL_BY$>
|
|
RetRejects = WOMatRec<WO_MAT_RET_REJECTS$>
|
|
MakeupBox = WOMatRec<WO_MAT_MAKEUP_BOX$>
|
|
CurrWfrCnt = XLATE('WO_MAT',WOMatKey,'CURR_WFR_CNT','X')
|
|
NCRNos = WOMatRec<WO_MAT_NCR_KEYS$>
|
|
NCRFinalSigs = WOMatRec<WO_MAT_NCR_FINAL_SIG$>
|
|
|
|
NCRNoCnt = COUNT(NCRNos,@VM) + (NCRNos NE '')
|
|
NCRSigCnt = COUNT(NCRFinalSigs,@VM) + (NCRFinalSigs NE '')
|
|
|
|
IF RetRejects = '' AND SubSupplyBy = 'C' THEN RetRejects = 1 ;* Fix up for RetRejects flag left null
|
|
|
|
ProcessStart = 0
|
|
ProcessComp = 0
|
|
|
|
LOOP
|
|
Signature = Signatures<1,1>
|
|
SigProf = SigProfs<1,1>
|
|
UNTIL Signature = ''
|
|
ProcessStart = 1
|
|
Signatures = DELETE(Signatures,1,1,0)
|
|
SigProfs = DELETE(SigProfs,1,1,0)
|
|
REPEAT
|
|
|
|
IF SigProf[1,4] = 'PSTI' AND SigProfs<1,2>[1,4] = 'PSTS' THEN
|
|
SigProf = SigProfs<1,2> ;* Added 1/5/2011 JCH
|
|
END
|
|
|
|
IF Signature = '' AND SigProf = '' AND ProcessStart = 1 THEN ProcessComp = 1
|
|
|
|
IF NUM(SigProf[1,1]) THEN SigProf[1,1] = ''
|
|
|
|
BEGIN CASE
|
|
CASE WOMatRec<WO_MAT_HOLD$> = 1 ; Result = 'HOLD'
|
|
CASE WOMatRec<WO_MAT_SHIP_NO$> NE '' ; Result = 'SHIP'
|
|
|
|
CASE Canceled = 1 AND SubSupplyBy NE 'C' ; Result = 'CANC'
|
|
CASE Canceled = 1 AND SubSupplyBy = 'C' AND InCleanRoom ; Result = 'COMP'
|
|
CASE Canceled = 1 AND SubSupplyBy = 'C' AND NOT(InCleanRoom) ; Result = 'RTS'
|
|
|
|
|
|
CASE NCRNoCnt > 0 AND NCRNoCnt NE NCRSigCnt ; Result = 'NCR'
|
|
|
|
CASE MakeupBox AND ProcessComp AND CurrWfrCnt > 0 ; Result = 'RTU'
|
|
CASE MakeupBox AND ProcessComp AND CurrWfrCnt = 0 ; Result = 'MT'
|
|
|
|
CASE NCRNoCnt > 0 AND CurrWfrCnt = 0 AND NOT(RetRejects) ; Result = 'REJ'
|
|
CASE NCRNoCnt > 0 AND CurrWfrCnt = 0 AND RetRejects ; Result = 'RTS'
|
|
|
|
CASE CurrWfrCnt = 0 ; Result = 'MT' ;* Added 8/14/2008 JCH - Used for Prod Test Wafers
|
|
|
|
CASE ProcessComp AND NOT(InCleanRoom) ; Result = 'RTS'
|
|
CASE ProcessComp AND CurrLoc = 'CR*PKO' ; Result = 'PKO'
|
|
CASE ProcessComp AND CurrLoc = 'CR*PACK' ; Result = 'PACK'
|
|
CASE ProcessComp AND InCleanroom ; Result = 'COMP'
|
|
|
|
CASE WOMatRec<WO_MAT_REL_DTM$> NE '' AND InCleanRoom ; Result = SigProf
|
|
CASE ProcessStart AND NOT(InCleanRoom) ; Result = SigProf
|
|
CASE WOMatRec<WO_MAT_REL_DTM$> NE '' AND NOT(InCleanRoom) ; Result = 'REL'
|
|
CASE WOMatRec<WO_MAT_RX_DTM$> NE '' ; Result = 'RX'
|
|
CASE SubSupplyBy = 'L' ; Result = 'RTP'
|
|
|
|
CASE 1 ; Result = 'AWM'
|
|
|
|
END CASE
|
|
|
|
IF Result = 'RTS' AND WOMatRec<WO_MAT_SHIP_HOLD$> = 1 THEN Result = 'SHOLD'
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
OutofPTO:
|
|
* * * * * * *
|
|
|
|
* Checks for INV movement through the PTO. If found it returns data for a user message.
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN WOMatKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(WOMatRec)) THEN WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
InvLocations = WOMatRec<WO_MAT_INV_LOCATION$>
|
|
|
|
ICnt = COUNT(InvLocations,@VM) + (InvLocations NE '')
|
|
|
|
FOR I = ICnt TO 1 STEP -1
|
|
|
|
IF InvLocations<1,I> = 'PTO' THEN
|
|
IF WOMatRec<WO_MAT_INV_WH$,I> = '1K' AND WOMatRec<WO_MAT_INV_ACTION$,I> = 'PLACE' THEN
|
|
|
|
InvDtm = WOMatRec<WO_MAT_INV_DTM$,I>
|
|
InvUser = WOMatRec<WO_MAT_INV_USER$,I>
|
|
|
|
Result = XLATE( 'LSL_USERS', InvUser , 'FIRST_LAST', 'X' ):@FM:OCONV(InvDtm,'DT4/^S')
|
|
|
|
RETURN
|
|
|
|
END
|
|
END ;* End of check for PTO locaton
|
|
NEXT I
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
CRComp:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN WOMatKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(WOMatRec)) THEN WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
IF WONo < 128680 THEN RETURN ;* This is the first WO No on 7/29/2005 - The day we cut over to the new system.
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
IF WOMatRec<WO_MAT_VOID$> THEN
|
|
Result = 'VOID'
|
|
END
|
|
|
|
Canceled = WOMatRec<WO_MAT_CANCELLED$>
|
|
CurrWfrCnt = XLATE('WO_MAT',WOMatKey,'CURR_WFR_CNT','X')
|
|
NCRNos = WOMatRec<WO_MAT_NCR_KEYS$>
|
|
NCRFinalSigs = WOMatRec<WO_MAT_NCR_FINAL_SIG$>
|
|
WMOKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
|
|
IF WMOKey NE '' THEN
|
|
Result = obj_WM_Out('CRComp',WMOKey:@RM:@RM:WOMatRec)
|
|
RETURN
|
|
END
|
|
|
|
NCRNoCnt = COUNT(NCRNos,@VM) + (NCRNos NE '')
|
|
NCRSigCnt = COUNT(NCRFinalSigs,@VM) + (NCRFinalSigs NE '')
|
|
|
|
SigArray = Signature_Services('GetSigProfile', WOMatKey)
|
|
SigProfs = SigArray<1>
|
|
Signatures = SigArray<2>
|
|
|
|
ProcessStart = 0
|
|
ProcessComp = 0
|
|
|
|
LOOP
|
|
Signature = Signatures<1,1>
|
|
SigProf = SigProfs<1,1>
|
|
UNTIL Signature = ''
|
|
ProcessStart = 1
|
|
Signatures = DELETE(Signatures,1,1,0)
|
|
SigProfs = DELETE(SigProfs,1,1,0)
|
|
REPEAT
|
|
|
|
IF Signature = '' AND SigProf = '' THEN ProcessComp = 1
|
|
|
|
IF NUM(SigProf[1,1]) THEN SigProf[1,1] = ''
|
|
|
|
CRComplete = 1
|
|
|
|
IF CurrWfrCnt > 0 THEN
|
|
IF NCRNoCnt > 0 AND NCRNoCnt NE NCRSigCnt THEN CRComplete = 0
|
|
IF NOT(ProcessStart) THEN CRComplete = 0
|
|
IF ProcessStart AND NOT(ProcessComp) THEN CRComplete = 0
|
|
END
|
|
|
|
Result = CRComplete
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
AddInvTrans:
|
|
* * * * * * *
|
|
|
|
LogFile = Parms[1,@RM] ;* This is always set to 'WO_MAT' now. Was changeable during development JCH
|
|
WONo = Parms[COL2()+1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
InvLocation = Parms[COL2()+1,@RM]
|
|
InvAction = Parms[COL2()+1,@RM]
|
|
InvDTM = Parms[COL2()+1,@RM]
|
|
ScanUserID = Parms[COL2()+1,@RM]
|
|
Tag = Parms[COL2()+1,@RM]
|
|
ToolID = Parms[COL2()+1,@RM]
|
|
ScanEntry = Parms[COL2()+1,@RM]
|
|
|
|
IF LogFile = '' THEN ErrorMsg = 'Null parameter "LogFile" passed to routine. (':Method:')'
|
|
IF WONo = '' THEN ErrorMsg = 'Null parameter "WONo" passed to routine. (':Method:')'
|
|
IF CassNo = '' THEN ErrorMsg = 'Null parameter "CassNo" passed to routine. (':Method:')'
|
|
IF InvLocation = '' THEN ErrorMsg = 'Null parameter "InvLocation" passed to routine. (':Method:')'
|
|
IF InvAction = '' THEN ErrorMsg = 'Null parameter "InvAction" passed to routine. (':Method:')'
|
|
IF InvDTM = '' THEN ErrorMsg = 'Null parameter "InvDTM" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN
|
|
ErrorMsg := CRLF$:Parms
|
|
SWAP @RM WITH CRLF$ IN ErrorMsg
|
|
RETURN
|
|
END
|
|
|
|
IF ScanUserID = '' THEN ScanUserID = @USER4
|
|
|
|
thisInvDTM = ICONV(InvDTM,'DT')
|
|
|
|
IF thisInvDTM = '' THEN
|
|
ErrorMsg = 'Invalid InvDTM ':InvDTM:' passed to routine.'
|
|
RETURN
|
|
END
|
|
|
|
BEGIN CASE
|
|
CASE LogFile = 'WO_MAT'
|
|
|
|
WOMatKey = WONo:'*':CassNo
|
|
WHCd = InvLocation[1,'*']
|
|
LocCd = InvLocation[COL2()+1,'*']
|
|
|
|
TableVar = ''
|
|
OtParms = 'WO_MAT':@RM:WOMatKey:@RM:TableVar
|
|
WOMatRec = obj_Tables('ReadRec',OtParms) ;* Locks and reads record for update
|
|
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',OtParms)
|
|
RETURN
|
|
END
|
|
|
|
IF WHCd = '1K' AND WOMatRec<WO_MAT_WMO_KEY$> NE '' THEN
|
|
|
|
WMOKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
|
|
IF LocCd = 'PTO' OR LocCd = 'PKO' THEN
|
|
WTableVar = ''
|
|
WOtParms = 'WM_OUT':@RM:WMOKey:@RM:WTableVar
|
|
WMOutRec = obj_Tables('ReadRec',WOtParms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',WOtParms)
|
|
obj_Tables('UnlockRec',OtParms)
|
|
RETURN
|
|
END
|
|
|
|
IF LocCd = 'PTO' THEN
|
|
WMOutRec<WM_OUT_IN_CLEANROOM$> = 0 ;* Clear the InCleanRoom flag
|
|
WMOutRec<WM_OUT_IN_PTO$> = 0 ;* Clear In Passtrough flag
|
|
END ELSE
|
|
WMOutRec<WM_OUT_IN_PTO$> = 1 ;* Set the In PTO flag
|
|
END
|
|
|
|
WOtParms = FieldStore(WOtParms,@RM,4,0,WMOutRec) ;* Put record in 4th field of OtParms
|
|
|
|
obj_Tables('WriteRec',WOtParms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
NULL
|
|
END
|
|
|
|
END ;* End of check for PTO or PKO location
|
|
|
|
IF LocCd = 'PTI' THEN
|
|
WTableVar = ''
|
|
WOtParms = 'WM_OUT':@RM:WMOKey:@RM:WTableVar
|
|
WMOutRec = obj_Tables('ReadRec',WOtParms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',WOtParms)
|
|
obj_Tables('UnlockRec',OtParms)
|
|
RETURN
|
|
END
|
|
|
|
WMOutRec<WM_OUT_IN_CLEANROOM$> = 1 ;* Set the InCleanRoom flag
|
|
WOtParms = FieldStore(WOtParms,@RM,4,0,WMOutRec) ;* Put record in 4th field of OtParms
|
|
|
|
obj_Tables('WriteRec',WOtParms)
|
|
|
|
END ;* End of check for PTI location
|
|
|
|
END ;* End of check for Class 1000 location and EpiPRO box
|
|
|
|
* Following check added 8/23/2013 by JCH - problems trying to get a 'DELETE' inventory transaction on the WO_MAT record -> passes on to FabTime to close out bogus transactions.
|
|
|
|
IF @WINDOW NE 'WO_MAT_INV' THEN
|
|
IF WOMatRec<WO_MAT_LOT_NO$> = '' OR WOMatRec<WO_MAT_CUST_PART_NO$> = '' THEN
|
|
obj_Tables('UnlockRec',OtParms)
|
|
RETURN
|
|
END
|
|
END
|
|
|
|
InvDTMs = WOMatRec<WO_MAT_INV_DTM$>
|
|
|
|
LOCATE thisInvDTM IN InvDTMS BY 'AL' USING @VM SETTING Pos ELSE
|
|
Pos = -1
|
|
END
|
|
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_WH$,Pos,0,WHCd)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_LOCATION$,Pos,0,LocCd)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_ACTION$,Pos,0,InvAction)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_DTM$,Pos,0,thisInvDTM)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_USER$,Pos,0,ScanUserID)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_TAG$,Pos,0,Tag)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_TOOL_ID$,Pos,0,ToolID)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_SCAN_ENTRY$,Pos,0,ScanEntry)
|
|
|
|
IF InvAction[-3,3] = 'VER' THEN
|
|
IF WOMatRec<WO_MAT_WIP_START_DTM$> = '' THEN
|
|
WOMatRec<WO_MAT_WIP_START_DTM$> = thisInvDTM
|
|
END
|
|
END
|
|
|
|
IF LocCd = 'PTO' THEN
|
|
IF WOMatRec<WO_MAT_WIP_STOP_DTM$> = '' THEN
|
|
WOMatRec<WO_MAT_WIP_STOP_DTM$> = thisInvDTM
|
|
END
|
|
END
|
|
|
|
OtParms = FieldStore(OtParms,@RM,4,0,WOMatRec) ;* Put record in 4th field of OtParms
|
|
|
|
Done = False$
|
|
NumAttempts = 0
|
|
Loop
|
|
NumAttempts += 1
|
|
Database_Services('WriteDataRow', 'WO_MAT', WOMatKey, WOMatRec, True$, False$, True$)
|
|
WOMatRecVerify = Database_Services('ReadDataRow', 'WO_MAT', WOMatKey)
|
|
LastEntryIndex = DCount(WOMatRecVerify<WO_MAT_INV_WH$>, @VM)
|
|
LastEntryAction = WOMatRecVerify<WO_MAT_INV_ACTION$, LastEntryIndex>
|
|
LastEntryLocCd = WOMatRecVerify<WO_MAT_INV_LOCATION$, LastEntryIndex>
|
|
If LastEntryAction EQ InvAction AND LastEntryLocCd = LocCd then
|
|
Done = True$
|
|
end
|
|
|
|
* Begin Case
|
|
* Case InvAction EQ '1QA'
|
|
*
|
|
* WOMatRecVerify = Database_Services('ReadDataRow', 'WO_MAT', WOMatKey)
|
|
* LastEntryIndex = DCount(WOMatRecVerify<WO_MAT_INV_WH$>, @VM)
|
|
* LastEntryAction = WOMatRecVerify<WO_MAT_INV_ACTION$, LastEntryIndex>
|
|
* If LastEntryAction EQ '1QA' then Done = True$
|
|
* LogData = ''
|
|
* LogData<1> = WOMatRecVerify<WO_MAT_INV_DTM$, LastEntryIndex>
|
|
* LogData<2> = WONo
|
|
* LogData<3> = CassNo
|
|
* LogData<4> = WOMatRecVerify<WO_MAT_INV_USER$, LastEntryIndex>
|
|
* LogData<5> = LastEntryIndex
|
|
* LogData<6> = WOMatRecVerify<WO_MAT_INV_TAG$, LastEntryIndex>
|
|
* LogData<7> = WOMatRecVerify<WO_MAT_INV_WH$, LastEntryIndex>
|
|
* LogData<8> = WOMatRecVerify<WO_MAT_INV_LOCATION$, LastEntryIndex>
|
|
* LogData<9> = LastEntryAction
|
|
* LogData<10> = WOMatRecVerify<WO_MAT_INV_TOOL_ID$, LastEntryIndex>
|
|
* LogData<11> = WOMatRecVerify<WO_MAT_INV_SCAN_ENTRY$, LastEntryIndex>
|
|
* LogData<12> = NumAttempts
|
|
* Logging_Services('AppendLog', WOMatObjLog3, LogData, @RM, @FM)
|
|
*
|
|
* Case InvAction EQ 'PLACE' and LocCd EQ 'PTI'
|
|
*
|
|
* WOMatRecVerify = Database_Services('ReadDataRow', 'WO_MAT', WOMatKey)
|
|
* LastEntryIndex = DCount(WOMatRecVerify<WO_MAT_INV_WH$>, @VM)
|
|
* LastEntryAction = WOMatRecVerify<WO_MAT_INV_ACTION$, LastEntryIndex>
|
|
* LastEntryLocCd = WOMatRecVerify<WO_MAT_INV_LOCATION$, LastEntryIndex>
|
|
* If ( (LastEntryAction EQ 'PLACE') and (LastEntryLocCd EQ 'PTI') ) then Done = True$
|
|
* LogData = ''
|
|
* LogData<1> = WOMatRecVerify<WO_MAT_INV_DTM$, LastEntryIndex>
|
|
* LogData<2> = WONo
|
|
* LogData<3> = CassNo
|
|
* LogData<4> = WOMatRecVerify<WO_MAT_INV_USER$, LastEntryIndex>
|
|
* LogData<5> = LastEntryIndex
|
|
* LogData<6> = WOMatRecVerify<WO_MAT_INV_TAG$, LastEntryIndex>
|
|
* LogData<7> = WOMatRecVerify<WO_MAT_INV_WH$, LastEntryIndex>
|
|
* LogData<8> = WOMatRecVerify<WO_MAT_INV_LOCATION$, LastEntryIndex>
|
|
* LogData<9> = LastEntryAction
|
|
* LogData<10> = WOMatRecVerify<WO_MAT_INV_TOOL_ID$, LastEntryIndex>
|
|
* LogData<11> = WOMatRecVerify<WO_MAT_INV_SCAN_ENTRY$, LastEntryIndex>
|
|
* LogData<12> = NumAttempts
|
|
* Logging_Services('AppendLog', WOMatObjLog4, LogData, @RM, @FM)
|
|
*
|
|
* Case Otherwise$
|
|
* Done = True$
|
|
*
|
|
* End Case
|
|
|
|
Until ( (Done EQ True$) or (NumAttempts EQ 10) )
|
|
Repeat
|
|
LogData = ''
|
|
LogData<1> = WOMatRecVerify<WO_MAT_INV_DTM$, LastEntryIndex>
|
|
LogData<2> = WONo
|
|
LogData<3> = CassNo
|
|
LogData<4> = WOMatRecVerify<WO_MAT_INV_USER$, LastEntryIndex>
|
|
LogData<5> = LastEntryIndex
|
|
LogData<6> = WOMatRecVerify<WO_MAT_INV_TAG$, LastEntryIndex>
|
|
LogData<7> = WOMatRecVerify<WO_MAT_INV_WH$, LastEntryIndex>
|
|
LogData<8> = WOMatRecVerify<WO_MAT_INV_LOCATION$, LastEntryIndex>
|
|
LogData<9> = LastEntryAction
|
|
LogData<10> = WOMatRecVerify<WO_MAT_INV_TOOL_ID$, LastEntryIndex>
|
|
LogData<11> = WOMatRecVerify<WO_MAT_INV_SCAN_ENTRY$, LastEntryIndex>
|
|
LogData<12> = NumAttempts
|
|
Logging_Services('AppendLog', WOMatObjLog3, LogData, @RM, @FM)
|
|
|
|
LogData = ''
|
|
LogData<1> = thisInvDTM
|
|
LogData<2> = WONo
|
|
LogData<3> = CassNo
|
|
LogData<4> = ScanUserID
|
|
LogData<5> = Pos
|
|
LogData<6> = Tag
|
|
LogData<7> = WHCd
|
|
LogData<8> = LocCd
|
|
LogData<9> = InvAction
|
|
LogData<10> = ToolID
|
|
LogData<11> = ScanEntry
|
|
|
|
Logging_Services('AppendLog', WOMatObjLog2, LogData, @RM, @FM)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
errCode = errCode:'User = ':ScanUserID
|
|
Gosub SendErrorNotification
|
|
END ELSE
|
|
|
|
|
|
END ;* End of check for Write error
|
|
|
|
obj_Tables('UnlockRec',OtParms)
|
|
|
|
CASE 1
|
|
ErrorMsg = 'Unknown Log File ':QUOTE(LogFile):' passed to routine. (':Method:')'
|
|
|
|
END CASE
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
InvDelta:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN WOMatKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(WOMatRec)) THEN WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
DTMs = WOMatRec<WO_MAT_INV_DTM$>
|
|
|
|
IF INDEX(DTMs,@VM,1) THEN
|
|
|
|
TransCnt = COUNT(DTMs,@VM) + (DTMs NE '')
|
|
|
|
Result = ''
|
|
|
|
FOR I = 1 TO TransCnt - 1
|
|
Result<1,I> = ICONV((DTMs<1,I+1> - DTMs<1,I>) * 24,'MD1')
|
|
NEXT I
|
|
|
|
END ;* End of check for more than a single date-time
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
TimeInFab:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN WOMatKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(WOMatRec)) THEN WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
LOCATE 'PTI' IN WOMatRec<WO_MAT_INV_LOCATION$> USING @VM SETTING IPos THEN
|
|
StartDTM = WOMatRec<WO_MAT_INV_DTM$,IPos>
|
|
LOCATE 'PTO' IN WOMatRec<WO_MAT_INV_LOCATION$> USING @VM SETTING OPos THEN
|
|
Result = ICONV((WOMatRec<WO_MAT_INV_DTM$,OPos> - WOMatRec<WO_MAT_INV_DTM$,IPos>) * 24,'MD1')
|
|
END ELSE
|
|
CurrDTM = ICONV(OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTHS'),'DT')
|
|
Result = ICONV((CurrDTM - WOMatRec<WO_MAT_INV_DTM$,IPos>) * 24,'MD1')
|
|
END
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ProcessTime:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN WOMatKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(WOMatRec)) THEN WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
FirstRDS = WOMatRec<WO_MAT_RDS_NO$,1> ;* Start with first or only run
|
|
|
|
VerSigDTM = XLATE('REACT_RUN',FirstRDS,REACT_RUN_VER_SIG_DTM$,'X')
|
|
|
|
IF VerSigDTM = '' THEN
|
|
RDSRec = XLATE('RDS',FirstRDS,'','X')
|
|
PreEpiDt = RDSRec<RDS_PRE_EPI_SIG_DATE$>
|
|
PreEpiTm = RDSRec<RDS_PRE_EPI_SIG_TIME$>
|
|
|
|
IF PreEpiDt NE '' AND PreEpiTm NE '' THEN
|
|
VerSigDTM = ICONV(OCONV(PreEpiDt,'D4/'):' ':OCONV(PreEpiTm,'MTS'),'DT')
|
|
END
|
|
END
|
|
|
|
IF VerSigDTM = '' THEN
|
|
Result = ''
|
|
RETURN
|
|
END
|
|
|
|
LOCATE 'PTO' IN WOMatRec<WO_MAT_INV_LOCATION$> USING @VM SETTING OPos THEN
|
|
Result = ICONV((WOMatRec<WO_MAT_INV_DTM$,OPos> - VerSigDTM) * 24,'MD1')
|
|
END ELSE
|
|
CurrDTM = ICONV(OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTHS'),'DT')
|
|
Result = ICONV((CurrDTM - VerSigDTM) * 24,'MD1')
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
EpiCassInvHistory:
|
|
* * * * * * *
|
|
|
|
WONo = Parms[1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
InvField = Parms[COL2()+1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WONo = '' OR CassNo = '' THEN RETURN ;* Called from dictionary items so no errors returned
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WONo:'*':CassNo,'','X')
|
|
|
|
IF WOMatRec<WO_MAT_INV_WH$> NE '' THEN Result<1> = WOMatRec<WO_MAT_INV_WH$>
|
|
IF WOMatRec<WO_MAT_INV_LOCATION$> NE '' THEN Result<2> = WOMatRec<WO_MAT_INV_LOCATION$>
|
|
IF WOMatRec<WO_MAT_INV_ACTION$> NE '' THEN Result<3> = WOMatRec<WO_MAT_INV_ACTION$>
|
|
IF WOMatRec<WO_MAT_INV_DTM$> NE '' THEN Result<4> = WOMatRec<WO_MAT_INV_DTM$>
|
|
IF WOMatRec<WO_MAT_INV_USER$> NE '' THEN Result<5> = WOMatRec<WO_MAT_INV_USER$>
|
|
|
|
WOSteps = XLATE('WO_LOG',WONo,WO_LOG_WO_STEP_KEY$,'X')
|
|
|
|
|
|
BEGIN CASE
|
|
CASE InvField = 'INV_WH' ; Result = Result<1>
|
|
CASE InvField = 'INV_LOCATION' ; Result = Result<2>
|
|
CASE InvField = 'INV_ACTION' ; Result = Result<3>
|
|
CASE InvField = 'INV_DTM' ; Result = Result<4>
|
|
CASE InvField = 'INV_USER' ; Result = Result<5>
|
|
END CASE
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ToggleHold:
|
|
* * * * * * *
|
|
|
|
* This is called from Comm_WM_In, Comm_WM_Out, Comm_WO_Mat and Comm_RDS. IT toggles the hold on the WO_MAT record
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
HoldEntity = Parms[COL2()+1,@RM] ;* Table Name i.e. RDS, REACT_RUN, WM_IN, WM_OUT or WO_MAT
|
|
HoldEntityID = Parms[COL2()+1,@RM] ;* Key value for associated Table Name (null for WO_MAT records)
|
|
CtrlEntID = Parms[COL2()+1,@RM] ;* Control checked/unchecked
|
|
OriginFlag = Parms[COL2()+1,@RM] ;* OriginFlag, i.e., which form/process called this
|
|
OperatorID = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null parameter "WOMatKey" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms)
|
|
|
|
IF Get_Status(errCode) THEN RETURN ;* Probably locked -> return
|
|
|
|
BEGIN CASE
|
|
CASE INDEX(CtrlEntID,'SHIP_HOLD',1) ; HoldType = 'SHOLD' ; * Ship Hold
|
|
CASE 1 ; HoldType = 'HOLD' ; * Production or Engineering Hold
|
|
END CASE
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
IF HoldType = 'SHOLD' THEN
|
|
HoldCheck = WOMatRec<WO_MAT_SHIP_HOLD$>
|
|
END ELSE
|
|
HoldCheck = WOMatRec<WO_MAT_HOLD$>
|
|
END
|
|
|
|
CustInfo = XLATE('WO_MAT',WOMatKey,'CUST_NAME','X')
|
|
|
|
IF HoldCheck = 1 THEN Transition = 'OFF' ELSE Transition = 'ON'
|
|
|
|
//9/16/21 DPC - added permissions check
|
|
IF Transition EQ 'OFF' then
|
|
if MemberOf(@USER4, 'ENG_TECH') OR MemberOf(@USER4, 'LEAD') OR MemberOf(@USER4, 'SUPERVISOR') else
|
|
obj_Tables('UnlockRec',otParms)
|
|
Errmsg('Current user does not have permission to remove hold.')
|
|
return
|
|
end
|
|
end
|
|
|
|
HoldData = ''
|
|
Begin Case
|
|
Case OriginFlag EQ 'P' ;*Packaging form
|
|
HoldData<1> = OperatorID
|
|
HoldData<2> = 'Packaging scanned data mismatch.'
|
|
HoldData<3> = False$
|
|
Case OriginFlag EQ 'PTO' ;*PTO/PSVER form
|
|
HoldData<1> = OperatorID
|
|
HoldData<2> = 'PTO/PSVER scanned data mismatch.'
|
|
HoldData<3> = False$
|
|
Case OriginFlag EQ 'H' ;*Auto-hold service
|
|
HoldData<1> = OperatorID
|
|
HoldData<2> = 'Makeup box is older than three years.'
|
|
HoldData<3> = False$
|
|
Case Otherwise$
|
|
// Collect hold data from user
|
|
HoldData = Dialog_Box('DIALOG_HOLD',@WINDOW,Transition:@FM:@FM:HoldType)
|
|
End Case
|
|
|
|
IF HoldData = 'Cancel' THEN
|
|
obj_Tables('UnlockRec',otParms)
|
|
RETURN
|
|
END
|
|
|
|
UserID = HoldData<1>
|
|
Reason = HoldData<2>
|
|
Extended = HoldData<3>
|
|
|
|
CurrDate = OCONV(Date(),'D4/')
|
|
CurrTime = OCONV(Time(),'MTS')
|
|
CurrDTM = ICONV(CurrDate:' ':CurrTime,'DT')
|
|
|
|
IF Transition = 'ON' THEN
|
|
IF HoldType = 'HOLD' THEN
|
|
|
|
WOMatRec<WO_MAT_HOLD$> = 1
|
|
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_HOLD_START_DTM$,1,0,CurrDTM)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_HOLD_START_USER$,1,0,UserID)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_HOLD_START_REASON$,1,0,Reason)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_HOLD_EXTENDED$,1,0,Extended)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_HOLD_STOP_DTM$,1,0,'')
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_HOLD_STOP_USER$,1,0,'')
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_HOLD_STOP_REASON$,1,0,'')
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_HOLD_ENTITY$,1,0,HoldEntity)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_HOLD_ENTITY_ID$,1,0,HoldEntityID)
|
|
|
|
***********************************************************
|
|
|
|
// - djs - 10/29/2019
|
|
// Updated material log entry method to be more reliable.
|
|
// Material log entries in quick succession were failing to be recorded.
|
|
NumTimestamps = Dcount(WOMatRec<WO_MAT_INV_WH$>, @VM)
|
|
NewEntryPos = NumTimestamps + 1
|
|
CurrWH = WOMatRec<WO_MAT_INV_WH$, NewEntryPos - 1> ;* WH before hold
|
|
CurrLoc = WOMatRec<WO_MAT_INV_LOCATION$, NewEntryPos - 1> ;* LOC before hold
|
|
CurrTool = WOMatRec<WO_MAT_INV_TOOL_ID$, NewEntryPos - 1> ;* ToolID before hold
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_INV_WH$, NewEntryPos, 0, CurrWH)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_INV_LOCATION$, NewEntryPos, 0, CurrLoc)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_INV_ACTION$, NewEntryPos, 0, 'HOLD_ON')
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_INV_DTM$, NewEntryPos, 0, CurrDTM)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_INV_USER$, NewEntryPos, 0, UserID)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_INV_TAG$, NewEntryPos, 0, '')
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_INV_TOOL_ID$, NewEntryPos, 0, CurrTool)
|
|
|
|
END ELSE
|
|
|
|
WOMatRec<WO_MAT_SHIP_HOLD$> = 1
|
|
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_SHIP_HOLD_START_DTM$,1,0,CurrDTM)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_SHIP_HOLD_START_USER$,1,0,UserID)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_SHIP_HOLD_START_REASON$,1,0,Reason)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_SHIP_HOLD_EXTENDED$,1,0,Extended)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_SHIP_HOLD_STOP_DTM$,1,0,'')
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_SHIP_HOLD_STOP_USER$,1,0,'')
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_SHIP_HOLD_STOP_REASON$,1,0,'')
|
|
END
|
|
|
|
IF HoldEntity = 'WM_OUT' THEN
|
|
WOMatRec<WO_MAT_WMO_CURR_STATUS$> = 'HOLD' ;* JCH 7/14/2009
|
|
END
|
|
|
|
IF HoldEntity = 'WM_IN' THEN
|
|
WOMatRec<WO_MAT_WMI_CURR_STATUS$> = 'HOLD' ;* JCH 7/14/2009
|
|
END
|
|
END
|
|
|
|
IF Transition = 'OFF' THEN
|
|
IF HoldType = 'HOLD' THEN
|
|
|
|
WOMatRec<WO_MAT_HOLD$> = 0
|
|
|
|
WOMatRec<WO_MAT_HOLD_STOP_DTM$,1> = CurrDTM
|
|
WOMatRec<WO_MAT_HOLD_STOP_USER$,1> = UserID
|
|
WOMatRec<WO_MAT_HOLD_STOP_REASON$,1> = Reason
|
|
WOMatRec<WO_MAT_HOLD_EXTENDED$,1> = 0
|
|
|
|
***********************************************************
|
|
|
|
LOCATE CurrDTM IN WOMatRec<WO_MAT_INV_DTM$> BY 'AR' USING @VM SETTING Pos ELSE
|
|
|
|
IF Pos > 1 THEN
|
|
CurrWH = WOMatRec<WO_MAT_INV_WH$,Pos-1> ;* WH before hold
|
|
CurrLoc = WOMatRec<WO_MAT_INV_LOCATION$,Pos-1> ;* LOC before hold
|
|
CurrTool = WOMatRec<WO_MAT_INV_TOOL_ID$,Pos-1> ;* ToolID before hold
|
|
|
|
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_WH$,Pos,0,CurrWH)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_LOCATION$,Pos,0,CurrLoc)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_ACTION$,Pos,0,'HOLD_OFF')
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_DTM$,Pos,0,CurrDTM)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_USER$,Pos,0,UserID)
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_TAG$,Pos,0,'')
|
|
WOMatRec = INSERT(WOMatRec,WO_MAT_INV_TOOL_ID$,Pos,0,CurrTool)
|
|
|
|
END ;* End of check for Pos > 1 Rcvd is always the first transaction
|
|
|
|
END ;* End of DTM locate
|
|
|
|
**************************************************************
|
|
|
|
END ELSE
|
|
WOMatRec<WO_MAT_SHIP_HOLD$> = 0
|
|
|
|
WOMatRec<WO_MAT_SHIP_HOLD_STOP_DTM$,1> = CurrDTM
|
|
WOMatRec<WO_MAT_SHIP_HOLD_STOP_USER$,1> = UserID
|
|
WOMatRec<WO_MAT_SHIP_HOLD_STOP_REASON$,1> = Reason
|
|
WOMatRec<WO_MAT_SHIP_HOLD_EXTENDED$,1> = 0
|
|
END
|
|
|
|
IF HoldEntity = 'WM_OUT' THEN
|
|
WOMatRec<WO_MAT_WMO_CURR_STATUS$> = obj_WM_Out('CurrStatus',HoldEntityID:@RM:@RM:WOMatRec)
|
|
END
|
|
|
|
IF HoldEntity = 'WM_IN' THEN
|
|
WOMatRec<WO_MAT_WMI_CURR_STATUS$> = obj_WM_In('CurrStatus',HoldEntityID:@RM:@RM:WOMatRec)
|
|
END
|
|
|
|
END
|
|
|
|
BEGIN CASE
|
|
|
|
CASE HoldEntity = 'RDS'
|
|
IF Transition = 'ON' THEN
|
|
Subject = 'Material Placed on Hold ':HoldEntityID
|
|
Message = 'Material Placed on Hold'
|
|
END ELSE
|
|
Subject = 'Material Taken off Hold ':HoldEntityID
|
|
Message = 'Material Taken off Hold'
|
|
END
|
|
|
|
AttachWindow = 'RDS_PRE_EPI'
|
|
AttachKey = HoldEntityID
|
|
|
|
CASE HoldEntity = 'WO_MAT'
|
|
IF Transition = 'ON' THEN
|
|
IF HoldType = 'HOLD' THEN
|
|
Subject = 'Material Placed on Hold ':HoldEntityID
|
|
Message = 'Material Placed on Hold'
|
|
END ELSE
|
|
Subject = 'Material Placed on Ship Hold ':HoldEntityID
|
|
Message = 'Material Placed on Ship Hold'
|
|
END
|
|
END ELSE
|
|
IF HoldType = 'HOLD' THEN
|
|
Subject = 'Material Taken off Hold ':HoldEntityID
|
|
Message = 'Material Taken off Hold'
|
|
END ELSE
|
|
Subject = 'Material Taken off Ship Hold ':HoldEntityID
|
|
Message = 'Material Taken off Ship Hold'
|
|
END
|
|
END
|
|
|
|
AttachWindow = HoldEntity
|
|
AttachKey = HoldEntityID
|
|
|
|
|
|
CASE HoldEntity = 'REACT_RUN'
|
|
IF Transition = 'ON' THEN
|
|
Subject = 'Material Placed on Hold ':HoldEntityID
|
|
Message = 'Material Placed on Hold'
|
|
END ELSE
|
|
Subject = 'Material Taken off Hold ':HoldEntityID
|
|
Message = 'Material Taken off Hold'
|
|
END
|
|
|
|
AttachWindow = 'REACT_RUN'
|
|
AttachKey = HoldEntityID
|
|
|
|
|
|
CASE HoldEntity = 'WM_IN'
|
|
|
|
IF Transition = 'ON' THEN
|
|
Subject = 'Material Placed on Hold ':HoldEntityID
|
|
Message = 'Material Placed on Hold'
|
|
END ELSE
|
|
Subject = 'Material Taken off Hold ':HoldEntityID
|
|
Message = 'Material Taken off Hold'
|
|
END
|
|
|
|
AttachWindow = HoldEntity
|
|
AttachKey = HoldEntityID
|
|
|
|
CASE HoldEntity = 'WM_OUT'
|
|
WMOKey = HoldEntity[2,99]
|
|
IF Transition = 'ON' THEN
|
|
IF HoldType = 'HOLD' THEN
|
|
Subject = 'Material Placed on Hold ':HoldEntityID
|
|
Message = 'Material Placed on Hold'
|
|
END ELSE
|
|
Subject = 'Material Placed on Ship Hold ':HoldEntityID
|
|
Message = 'Material Placed on Ship Hold'
|
|
END
|
|
END ELSE
|
|
IF HoldType = 'HOLD' THEN
|
|
Subject = 'Material Taken off Hold ':HoldEntityID
|
|
Message = 'Material Taken off Hold'
|
|
END ELSE
|
|
Subject = 'Material Taken off Ship Hold ':HoldEntityID
|
|
Message = 'Material Taken off Ship Hold'
|
|
END
|
|
END
|
|
|
|
AttachWindow = HoldEntity
|
|
AttachKey = HoldEntityID
|
|
|
|
END CASE
|
|
|
|
Message := ' - ':Reason
|
|
|
|
IF HoldType = 'SHOLD' THEN
|
|
|
|
Recipients = XLATE('NOTIFICATION','SHIP_HOLD',NOTIFICATION_USER_ID$,'X')
|
|
SentFrom = @USER4
|
|
|
|
SendToGroup = ''
|
|
|
|
Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup
|
|
obj_Notes('Create',Parms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
|
|
END
|
|
|
|
Recipients = XLATE('NOTIFICATION','RDS_HOLD',NOTIFICATION_USER_ID$,'X')
|
|
SentFrom = @USER4
|
|
|
|
SendToGroup = ''
|
|
|
|
Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup
|
|
obj_Notes('Create',Parms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
|
|
otParms = FieldStore(OtParms,@RM,4,0,WOMatRec) ;* Put record in 4th field of OtParms
|
|
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * * *
|
|
EditHoldReason:
|
|
* * * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
ColName = Parms[COL2()+1,@RM]
|
|
ColValNo = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null parameter "WOMatKey" passed to routine. (':Method:')'
|
|
IF ColName = '' THEN ErrorMsg = 'Null parameter "ColName" passed to routine. (':Method:')'
|
|
IF ColValNo = '' THEN ErrorMsg = 'Null parameter "ColValNo" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms)
|
|
|
|
IF Get_Status(errCode) THEN RETURN
|
|
|
|
IF INDEX(ColName,'START',1) THEN
|
|
|
|
HoldStartReason = WOMatRec<WO_MAT_HOLD_START_REASON$,ColValNo>
|
|
UpdatedText = Dialog_Box('DIALOG_TEXT',@WINDOW,'Hold Start Reason':@FM:HoldStartReason)
|
|
|
|
IF UpdatedText NE 'Cancel' THEN
|
|
WOMatRec<WO_MAT_HOLD_START_REASON$,ColValNo> = UpdatedText
|
|
END
|
|
|
|
END
|
|
|
|
IF INDEX(ColName,'STOP',1) THEN
|
|
|
|
HoldStopReason = WOMatRec<WO_MAT_HOLD_STOP_REASON$,ColValNo>
|
|
UpdatedText = Dialog_Box('DIALOG_TEXT',@WINDOW,'Hold Stop Reason':@FM:HoldStopReason)
|
|
|
|
IF UpdatedText NE 'Cancel' THEN
|
|
WOMatRec<WO_MAT_HOLD_STOP_REASON$,ColValNo> = UpdatedText
|
|
END
|
|
|
|
END
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ChangeFlag:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
FieldNo = Parms[COL2()+1,@RM]
|
|
Value = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null parameter "WOMatKey" passed to routine. (':Method:')'
|
|
IF FieldNo = '' THEN ErrorMsg = 'Null parameter "Property" passed to routine. (':Method:')'
|
|
|
|
IF Value = '' OR Value = '0' OR Value = '1' THEN
|
|
* Good values passed
|
|
END ELSE
|
|
ErrorMsg = 'Invalid Flag ':QUOTE(Value):' passed to routine. (':Method:')'
|
|
END
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
InvTransFlag = ''
|
|
|
|
WMTableParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',WMTableParms)
|
|
|
|
BEGIN CASE
|
|
CASE FieldNo = 23 ; FieldName = "WO_MAT_MAKEUP_BOX$"
|
|
CASE FieldNo = 52 ; FieldName = "WO_MAT_EPO_MAKEUP_BOX$"
|
|
CASE 1 ; FieldName = 'Field No: ':QUOTE(FieldNo)
|
|
END CASE
|
|
|
|
IF Get_Status(errCode) THEN
|
|
|
|
RETURN ;* Probably locked -> return
|
|
END
|
|
|
|
IF FieldNo = WO_MAT_CANCELLED$ THEN
|
|
RDSNos = WOMatRec<WO_MAT_RDS_NO$>
|
|
|
|
IF RDSNos NE '' THEN
|
|
|
|
ReactRunTableVar = obj_Tables('LockSet','REACT_RUN':@RM:RDSNos)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',WMTableParms) ;* Unlock WO_LOG record
|
|
RETURN
|
|
END
|
|
|
|
RunCnt = COUNT(RDSNos,@VM) + (RDSNos NE '')
|
|
FOR I = 1 TO RunCnt
|
|
RDSNo = RDSNos<1,I>
|
|
|
|
ReactRunRec = XLATE('REACT_RUN',RDSNo,'','X')
|
|
|
|
ReactRunRec<REACT_RUN_CANCELLED$> = Value
|
|
|
|
RRParms = 'REACT_RUN':@RM:RDSNo:@RM:ReactRunTableVar:@RM:ReactRunRec
|
|
obj_Tables('WriteRec',RRParms) ;* Writes and unlocks React Run Record
|
|
|
|
NEXT I
|
|
END
|
|
|
|
IF Value = 1 AND WOMatRec<WO_MAT_WIP_STOP_DTM$> = '' THEN
|
|
WOMatRec<WO_MAT_WIP_STOP_DTM$> = ICONV(OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS') ,'DT') ;* Added 11/8/2012 JCH *
|
|
END
|
|
|
|
END
|
|
|
|
IF FieldNo = WO_MAT_VOID$ THEN
|
|
RDSNos = WOMatRec<WO_MAT_RDS_NO$>
|
|
IF RDSNos NE '' THEN
|
|
|
|
ReactRunTableVar = obj_Tables('LockSet','REACT_RUN':@RM:RDSNos)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',WMTableParms) ;* Unlock WO_LOG record
|
|
RETURN
|
|
END
|
|
|
|
RunCnt = COUNT(RDSNos,@VM) + (RDSNos NE '')
|
|
FOR I = 1 TO RunCnt
|
|
RDSNo = RDSNos<1,I>
|
|
|
|
ReactRunRec = XLATE('REACT_RUN',RDSNo,'','X')
|
|
|
|
ReactRunRec<REACT_RUN_VOID$> = Value
|
|
|
|
RRParms = 'REACT_RUN':@RM:RDSNo:@RM:ReactRunTableVar:@RM:ReactRunRec
|
|
obj_Tables('WriteRec',RRParms) ;* Writes and unlocks React Run Record
|
|
|
|
NEXT I
|
|
|
|
IF Value = 1 AND WOMatRec<WO_MAT_WIP_STOP_DTM$> = '' THEN
|
|
WOMatRec<WO_MAT_WIP_STOP_DTM$> = ICONV(OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS') ,'DT') ;* Added 11/8/2012 JCH *
|
|
END
|
|
|
|
InvTransFlag = Value ;* Added 1/14/2015 DKK & JCH
|
|
|
|
END
|
|
END
|
|
|
|
IF FieldNo = WO_MAT_EPO_MAKEUP_BOX$ THEN
|
|
|
|
* Superfluous when called from COMM_WM_OUT
|
|
|
|
IF @WINDOW = 'WO_MAT' THEN
|
|
WMOutKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
|
|
IF WMOutKey NE '' THEN
|
|
|
|
WMOParms = 'WM_OUT':@RM:WMOutKey
|
|
WMORec = Database_Services('ReadDataRow', 'WM_OUT', WMOutKey)
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',WMOParms) ;* Unlock WM_Out record
|
|
RETURN
|
|
END
|
|
|
|
WMORec<WM_OUT_MAKEUP_BOX$> = Value
|
|
Database_Services('WriteDataRow', 'WM_OUT', WMOutKey, WMORec, True$, False$, True$)
|
|
|
|
END
|
|
END
|
|
END
|
|
|
|
|
|
WOMatRec<FieldNo> = Value ;* Set Flag field here
|
|
|
|
WMTableParms = FieldStore(WMTableParms,@RM,4,0,WOMatRec) ;* Put record in 4th field of OtParms
|
|
|
|
obj_Tables('WriteRec',WMTableParms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
|
|
* Logging
|
|
|
|
LogRec = 'obj_WO_Mat':TAB$:'Change Flag: Error':TAB$:WOMatKey:TAB$:FieldName:TAB$:Value:TAB$:'Unable to WRITE WO_MAT record. ':errCode
|
|
LogRec := TAB$:@STATION:TAB$:@USER4:TAB$:OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
|
|
|
|
SWAP @RM WITH TAB$ IN LogRec
|
|
|
|
OPEN 'JCH_LOG' TO JCHLogFile THEN
|
|
LogKey = NextKey('JCH_LOG')
|
|
WRITE LogRec ON JCHLogFile,LogKey ELSE NULL
|
|
END
|
|
|
|
END ELSE
|
|
|
|
* Logging
|
|
|
|
LogRec = 'obj_WO_Mat':TAB$:'Change Flag':TAB$:WOMatKey:TAB$:FieldName:TAB$:Value:TAB$:'WO_MAT updated OK'
|
|
LogRec := TAB$:@STATION:TAB$:@USER4:TAB$:OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
|
|
|
|
SWAP @RM WITH TAB$ IN LogRec
|
|
|
|
OPEN 'JCH_LOG' TO JCHLogFile THEN
|
|
LogKey = NextKey('JCH_LOG')
|
|
WRITE LogRec ON JCHLogFile,LogKey ELSE NULL
|
|
END
|
|
END
|
|
|
|
|
|
* * * * Added 1/14/2015 * * * *
|
|
|
|
IF InvTransFlag = 1 THEN
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
CassNo = WOMatKey[COL2()+1,'*']
|
|
WhCd = 'CR'
|
|
LocCd = 'QA'
|
|
Action = 'DELETE'
|
|
InvDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
|
|
Tag = ''
|
|
ScanToolID = ''
|
|
UserID = @USER4
|
|
|
|
Set_Status(0)
|
|
aiParms = 'WO_MAT':@RM:WONo:@RM:CassNo:@RM:WhCd:'*':LocCd:@RM:Action:@RM:InvDTM:@RM:UserID:@RM:Tag:@RM:ScanToolID
|
|
obj_WO_Mat('AddInvTrans',aiParms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
|
|
END
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
AddNCR:
|
|
* * * * * * *
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
RemNCR:
|
|
* * * * * * *
|
|
|
|
* Called by COMM_NCR('Delete') as a pre-event to clear NCR information from WO_MAT Record
|
|
|
|
WONo = Parms[1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
NCRNo = Parms[COL2()+1,@RM]
|
|
SlotNos = Parms[COL2()+1,@RM]
|
|
RejWaferIDs = Parms[COL2()+1,@RM]
|
|
PrevNCRNos = Parms[COL2()+1,@RM]
|
|
|
|
RemNCRHeaders = 'Logging DTM':@FM:'WONo':@FM:'CassNo':@FM:'NCRNo':@FM:'SlotNos':@FM:'RejWaferIDs':@FM:'PrevNCRNos':@FM:'Notes'
|
|
|
|
LogData = ''
|
|
LogData<1> = LoggingDTM
|
|
LogData<2> = WONo
|
|
LogData<3> = CassNo
|
|
LogData<4> = NCRNo
|
|
LogData<5> = SlotNos
|
|
LogData<6> = RejWaferIDs
|
|
LogData<7> = PrevNCRNos
|
|
LogData<8> = 'Begin obj_WO_MAT("RemNCR")'
|
|
LogData<9> = @User4
|
|
Logging_Services('AppendLog', RemNCRObjLog, LogData, @RM, @FM)
|
|
|
|
IF WONo = '' THEN ErrorMsg = 'Null parameter "WONo" passed to routine. (':Method:')'
|
|
IF CassNo = '' THEN ErrorMsg = 'Null parameter "CassNo" passed to routine. (':Method:')'
|
|
IF NCRNo = '' THEN ErrorMsg = 'Null parameter "NCRNo" passed to routine. (':Method:')'
|
|
IF SlotNos = '' THEN ErrorMsg = 'Null parameter "SlotNos" passed to routine. (':Method:')'
|
|
IF RejWaferIDs = '' THEN ErrorMsg = 'Null parameter "RejWaferNos" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
|
|
WOMatKey = WONo:'*':CassNo
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
* WOMatRec = obj_Tables('ReadRec',otParms)
|
|
|
|
WOMatRec = Database_Services('ReadDataRow', 'WO_MAT', WOMatKey)
|
|
|
|
IF Get_Status(errCode) THEN RETURN
|
|
|
|
SlotCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
|
|
|
|
EventDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
|
|
|
|
FOR I = 1 TO SlotCnt
|
|
|
|
SlotNo = SlotNos<1,I>
|
|
DefWaferID = WONo:'.':CassNo:'.':SlotNo
|
|
RejWfrID = RejWaferIDs<1,I>
|
|
|
|
WOMatRec<WO_MAT_SLOT_NCR$,SlotNo> = PrevNCRNos<1,I>
|
|
|
|
IF RejWfrID NE DefWaferID THEN
|
|
WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,SlotNo> = RejWfrID
|
|
EventWfrID = RejWfrID
|
|
End Else
|
|
EventWfrID = DefWaferID
|
|
END
|
|
|
|
* * * * Added 3/24/2016 JCH - wafer history * * * *
|
|
|
|
Convert '.' To '*' In EventWfrID
|
|
|
|
Parms = EventWfrID:@RM ;* WfrID
|
|
Parms := 'NCR':@RM ;* Event
|
|
Parms := NCRNo ;* EventID
|
|
|
|
obj_WO_Wfr('RemEvent',Parms)
|
|
|
|
NEXT I
|
|
|
|
otParms = FieldStore(OtParms,@RM,4,0,WOMatRec) ;* Put record in 4th field of OtParms
|
|
|
|
Database_Services('WriteDataRow', 'WO_MAT', WOMatKey, WOMatRec, True$, False$, True$)
|
|
|
|
LogData<8> = 'End obj_WO_MAT("RemNCR"'
|
|
Logging_Services('AppendLog', RemNCRObjLog, LogData, @RM, @FM)
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
SignNCR:
|
|
* * * * * * *
|
|
|
|
* Used to Sign NCR line item as complete.
|
|
WONo = Parms[1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
NCRNo = Parms[COL2()+1,@RM]
|
|
SignBy = Parms[COL2()+1,@RM]
|
|
SignByDTM = Parms[COL2()+1,@RM]
|
|
|
|
IF WONo = '' THEN ErrorMsg = 'Null parameter "WONo" passed to routine. (':Method:')'
|
|
IF CassNo = '' THEN ErrorMsg = 'Null parameter "CassNo" passed to routine. (':Method:')'
|
|
IF NCRNo = '' THEN ErrorMsg = 'Null parameter "NCRNo" passed to routine. (':Method:')'
|
|
IF SignBy = '' THEN ErrorMsg = 'Null parameter "SignBy" passed to routine. (':Method:')'
|
|
IF SignByDTM = '' THEN ErrorMsg = 'Null parameter "SignByDTM" passed to routine. (':Method:')'
|
|
|
|
LogData = ''
|
|
LogData<1> = WONo
|
|
LogData<2> = CassNo
|
|
LogData<3> = NCRNo
|
|
LogData<4> = SignBy
|
|
LogData<5> = SignByDTM
|
|
LogData<6> = 'Beginning SignNCR subroutine.'
|
|
Logging_Services('AppendLog', SignNCRObjLog, LogData, @RM, @FM)
|
|
|
|
IF ErrorMsg EQ '' then
|
|
WOMatKey = WONo:'*':CassNo
|
|
WOMatRec = Database_Services('ReadDataRow', 'WO_MAT', WOMatKey)
|
|
If Error_Services('NoError') then
|
|
LOCATE NCRNo IN WOMatRec<WO_MAT_NCR_KEYS$> USING @VM SETTING Pos THEN
|
|
CurrSig = Trim(WOMatRec<WO_MAT_NCR_FINAL_SIG$,Pos>)
|
|
IF CurrSig = '' THEN
|
|
WOMatRec<WO_MAT_NCR_FINAL_SIG$,Pos> = SignBy
|
|
WOMatRec<WO_MAT_NCR_FINAL_SIG_DTM$,Pos> = SignByDTM
|
|
LogData<6> = 'NCRNo located and signature set within WOMatRec.'
|
|
Logging_Services('AppendLog', SignNCRObjLog, LogData, @RM, @FM)
|
|
END ELSE
|
|
// NCR_KEYS relational index may not have added the NCR key yet.
|
|
// Just append the signature and signature DTM to the end of the list.
|
|
WOMatRec<WO_MAT_NCR_FINAL_SIG$,-1> = SignBy
|
|
WOMatRec<WO_MAT_NCR_FINAL_SIG_DTM$,-1> = SignByDTM
|
|
LogData<6> = 'NCR final signature already in place. Current final signature value = "':CurrSig:'"'
|
|
Logging_Services('AppendLog', SignNCRObjLog, LogData, @RM, @FM)
|
|
END
|
|
END ELSE
|
|
LogData<6> = 'SignNCR routine failed. Failed to locate NCRNo in WOMatRec.'
|
|
Logging_Services('AppendLog', SignNCRObjLog, LogData, @RM, @FM)
|
|
END
|
|
Database_Services('WriteDataRow', 'WO_MAT', WOMatKey, WOMatRec, True$, False$, True$)
|
|
If Error_Services('NoError') then
|
|
LogData<6> = 'WO_MAT record successfully written.'
|
|
Logging_Services('AppendLog', SignNCRObjLog, LogData, @RM, @FM)
|
|
end else
|
|
LogData<6> = 'WO_MAT record failed to write.'
|
|
Logging_Services('AppendLog', SignNCRObjLog, LogData, @RM, @FM)
|
|
end
|
|
end else
|
|
LogData<6> = 'SignNCR routine failed. Error message: ':Error_Services('GetMessage')
|
|
Logging_Services('AppendLog', SignNCRObjLog, LogData, @RM, @FM)
|
|
end
|
|
end else
|
|
LogData<6> = 'SignNCR routine failed. Error message: ':ErrorMsg
|
|
Logging_Services('AppendLog', SignNCRObjLog, LogData, @RM, @FM)
|
|
end
|
|
LogData<6> = 'Ending SignNCR subroutine.'
|
|
Logging_Services('AppendLog', SignNCRObjLog, LogData, @RM, @FM)
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
AddMakeupWafers:
|
|
* * * * * * *
|
|
* Places makeup wafers into a production cassette
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
EmptySlots = Parms[COL2()+1,@RM]
|
|
MakeupBox = Parms[COL2()+1,@RM]
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN ErrorMsg = 'Unassigned Parm "WOMatKey" 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 WOMatKey = '' THEN ErrorMsg = 'Null Parm "WOMatKey" 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 = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
|
|
|
|
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
|
|
|
|
MakeupWaferData = obj_WO_Mat('RemMakeupWafers',MakeUpBox:@RM:EmptySlots:@RM:WOMatKey) ;* Extracts and returns slot data from Makeup Box
|
|
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',otParms)
|
|
RETURN
|
|
END
|
|
|
|
IF MakeupWaferData = '' THEN
|
|
obj_Tables('UnlockRec',otParms)
|
|
RETURN
|
|
END
|
|
|
|
MakeupWONo = MakeupBox[1,'*']
|
|
MakeupCassNo = MakeupBox[COL2()+1,'*']
|
|
|
|
ReplacedBy = @USER4
|
|
|
|
MWDCnt = COUNT(MakeupWaferData,@FM) + (MakeupWaferData NE '')
|
|
FOR I = 1 TO MWDCnt
|
|
SlotNo = MakeupWaferData<I,1>
|
|
WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,SlotNo> = MakeupWaferData<I,2>
|
|
WOMatRec<WO_MAT_SLOT_MOVED_FROM$,SlotNo> = MakeupWaferData<I,3> ;* Added 8/12/2014 JCH Added Moved from slot ID
|
|
WOMatRec<WO_MAT_SLOT_REP_BY$,SlotNo> = ReplacedBy ;* Added 10/6/2010 JCH *
|
|
// Timestamp MU Wafer KLUSA project
|
|
WOMatRec<WO_MAT_MU_WAFER_ADDED_DTM$, SlotNo> = MakeupWaferData<I,4>
|
|
|
|
NEXT I
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
SubMakeupWafers:
|
|
* * * * * * *
|
|
|
|
* Subtracts makeup wafers from a production box for return to the makeup box
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
MadeupSlots = Parms[COL2()+1,@RM]
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN ErrorMsg = 'Unassigned Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF NOT(ASSIGNED(MadeupSlots)) THEN ErrorMsg = 'Unassigned Parm "MadeupSlots" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF MadeupSlots = '' THEN ErrorMsg = 'Null Parm "MadeupSlots" passed to routine. (':Method:')'
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
|
|
|
|
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
|
|
|
|
SlotID = WOMatKey
|
|
CONVERT '*' TO '.' IN SlotID
|
|
|
|
CurrDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
|
|
|
|
WfrIDs = '' ;* JCH 9/7/23016
|
|
NewSlotIDs = '' ;* JCH 9/7/23016
|
|
CurrSlotIDs = '' ;* JCH 9/7/23016
|
|
|
|
RepWaferIDs = ''
|
|
MadeupCnt = COUNT(MadeupSlots,@VM) + (MadeupSlots NE '')
|
|
|
|
FOR I = 1 TO MadeupCnt
|
|
MadeupSlot = MadeupSlots<1,I>
|
|
RepWaferIDs<I,1> = SlotID:'.':MadeupSlot
|
|
RepWaferIDs<I,2> = WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,MadeupSlot>
|
|
// Timestamp MU Wafer Project
|
|
// Makeup wafer is being 'put back' into makeup cassette.
|
|
// Remove most recent 'added' DTM from WOMatRec.
|
|
AddedDTMS = WOMatRec<WO_MAT_MU_WAFER_ADDED_DTM$, MadeupSlot>
|
|
AddedDTMS = Delete(AddedDTMS, 1, 1, 1)
|
|
WOMatRec<WO_MAT_MU_WAFER_ADDED_DTM$, MadeupSlot> = AddedDTMS
|
|
|
|
* * * * Added 5/12/2016 JCH - wafer history * * * *
|
|
|
|
WfrID = WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,MadeupSlot>
|
|
NewSlotID = WOMatRec<WO_MAT_SLOT_MOVED_FROM$,MadeupSlot>
|
|
|
|
IF NewSlotID = '' THEN
|
|
NewSlotID = WfrID
|
|
END
|
|
|
|
CurrSlotID = WOMatKey:'*':MadeupSlot
|
|
|
|
CONVERT '.' TO '*' IN WfrID
|
|
CONVERT '.' TO '*' IN NewSlotID
|
|
|
|
WfrIDs<1,-1> = WfrID ;* JCH 9/7/23016
|
|
NewSlotIDs<1,-1> = NewSlotID ;* JCH 9/7/23016
|
|
CurrSlotIDs<1,-1> = CurrSlotID ;* JCH 9/7/23016
|
|
|
|
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 * * * *
|
|
|
|
WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,MadeupSlot> = ''
|
|
WOMatRec<WO_MAT_SLOT_MOVED_FROM$,MadeupSlot> = '' ;* Added 08/12/2014 JCH Moved From Slot IDs
|
|
WOMatRec<WO_MAT_SLOT_REP_BY$,MadeupSlot> = '' ;* Added 10/06/2010 JCH *
|
|
WOMatRec<WO_MAT_MU_WAFER_THK_RESULT$,MadeupSlot> = '' ;* Added 03/14/2017 FDR *
|
|
|
|
|
|
NEXT I
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
Result = RepWaferIDs
|
|
|
|
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 = 'WO_MAT':@RM:MUBoxKey
|
|
MU_WOMatRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
|
|
|
|
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
|
|
|
|
CONVERT '*' TO '.' IN TargetBoxKey
|
|
|
|
SlotWaferIDs = obj_WO_Mat('SlotWaferIDs',MUBoxKey:@RM:MU_WOMatRec) ;* MV'd list of available wafers in MU Box (All slots)
|
|
|
|
AvailWafers = ''
|
|
AvailWaferCnt = 0
|
|
SWIDCnt = COUNT(SlotWaferIDs,@VM) + (SlotWaferIDs NE '')
|
|
FOR I = 1 TO SWIDCnt
|
|
IF SlotWaferIDs<1,I> NE '' THEN
|
|
AvailWaferCnt += 1
|
|
AvailWafers = INSERT(AvailWafers,AvailWaferCnt,1,0,I)
|
|
AvailWafers = INSERT(AvailWafers,AvailWaferCnt,2,0,SlotWaferIDs<1,I>)
|
|
|
|
MovedFromCode = MUBoxKey:'.':I ;* 8/12/2014 JCH Add Source slot ID to Return data
|
|
CONVERT '*' TO '.' IN MovedFromCode ;* 8/12/2014 JCH
|
|
|
|
AvailWafers = INSERT(AvailWafers,AvailWaferCnt,3,0,MovedFromCode) ;* 8/12/2014 JCH
|
|
END
|
|
NEXT I
|
|
|
|
EmptySlotCnt = COUNT(EmptySlots,@VM) + (EmptySlots NE '')
|
|
|
|
IF EmptySlotCnt > AvailWaferCnt THEN
|
|
FillCnt = AvailWaferCnt
|
|
END ELSE
|
|
FillCnt = EmptySlotCnt
|
|
END
|
|
|
|
IF FillCnt > 0 AND MU_WOMatRec<WO_MAT_MAKEUP_BOX$> NE 1 THEN
|
|
MU_WOMatRec<WO_MAT_MAKEUP_BOX$> = 1 ;* Flag Box as a makeup box
|
|
End
|
|
|
|
CurrDate = OCONV(Date(),'D4/')
|
|
CurrTime = OCONV(Time(),'MTHS')
|
|
CurrDTM = CurrDate:' ':CurrTime
|
|
|
|
WfrIDs = '' ;* JCH 9/7/2016
|
|
NewSlotIDs = '' ;* JCH 9/7/2016
|
|
CurrSlotIDs = '' ;* JCH 9/7/2016
|
|
|
|
FOR I = 1 TO FillCnt
|
|
AvailSlotNo = AvailWafers<I,1>
|
|
MU_WOMatRec<WO_MAT_SLOT_MOVED_TO$,AvailSlotNo> = TargetBoxKey:'.':EmptySlots<1,I>
|
|
Result<I,1> = EmptySlots<1,I>:@VM:AvailWafers<I,2>:@VM:AvailWafers<I,3> ;* 8/12/2014 JCH
|
|
|
|
// Timestamp MU Wafer Project
|
|
// Get Makeup wafer added DTM history. Insert current DTM into first @SVM of the result record.
|
|
// Only the first (newest) DTM is displayed on the WO_MAT_WFR form.
|
|
DateTime = Datetime() ; // Date() : '.' : Time()
|
|
AddedDTMS = MU_WOMatRec<WO_MAT_MU_WAFER_ADDED_DTM$, AvailSlotNo>
|
|
Result<I,4> = Insert(AddedDTMS, 0, 0, 1, DateTime)
|
|
// Get Makeup wafer removed DTM history. Insert current DTM into first @SVM of the makeup wafer record.
|
|
// Only the first (newest) DTM is displayed on the WO_MAT_WFR form.
|
|
RemovedDTMS = MU_WOMatRec<WO_MAT_MU_WAFER_REMOVED_DTM$, AvailSlotNo>
|
|
MU_WOMatRec<WO_MAT_MU_WAFER_REMOVED_DTM$, AvailSlotNo> = Insert(RemovedDTMS, 0, 0, 1, DateTime)
|
|
|
|
* * * * Added 3/28/2016 JCH - wafer history * * * *
|
|
|
|
WfrID = AvailWafers<I,2>
|
|
NewSlotID = TargetBoxKey:'.':EmptySlots<1,I>
|
|
CurrSlotID = AvailWafers<I,3>
|
|
|
|
Convert '.' To '*' In WfrID
|
|
Convert '.' To '*' In NewSlotID
|
|
Convert '.' To '*' In CurrSlotID
|
|
|
|
WfrIDs<1,-1> = WfrID ;* JCH 9/7/2016
|
|
NewSlotIDs<1,-1> = NewSlotID ;* JCH 9/7/2016
|
|
CurrSlotIDs<1,-1> = CurrSlotID ;* JCH 9/7/2016
|
|
|
|
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 * * * *
|
|
|
|
NEXT I
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,MU_WOMatRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
* Send 'RTU' WO_Mat_Log Entry to update qty in FabTime
|
|
|
|
SigAction = 'RTU'
|
|
WHCd = 'CR'
|
|
LocCd = 'MU'
|
|
WONo = MUBoxKey[1,'*']
|
|
CassNo = MUBoxKey[COL2()+1,'*']
|
|
UserID = @USER4
|
|
|
|
Tag = ''
|
|
ToolID = ''
|
|
|
|
WOMLParms = 'WO_MAT':@RM
|
|
WOMLParms := CurrDTM:@RM
|
|
WOMLParms := SigAction:@RM
|
|
WOMLParms := WhCd:@RM
|
|
WOMLParms := LocCd:@RM
|
|
WOMLParms := WONo:@RM
|
|
WOMLParms := CassNo:@RM
|
|
WOMLParms := UserID:@RM
|
|
WOMLParms := Tag:@RM
|
|
WOMLParms := ToolID
|
|
|
|
obj_WO_Mat_Log('Create',WOMLParms) ;* Stage PSTC log entry
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
RepMakeupWafers:
|
|
* * * * * * *
|
|
|
|
* Replaces makeup wafers into a makeup box. Used when returning makeups from a production box.
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
RepWaferIDs = Parms[COL2()+1,@RM] ;* Data structure for wafers subtracted from production box
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN ErrorMsg = 'Unassigned Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF NOT(ASSIGNED(RepWaferIDs)) THEN ErrorMsg = 'Unassigned Parm "RepWaferIDs" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF RepWaferIDs = '' THEN ErrorMsg = 'Null Parm "RepWaferIDs" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
WONo = WOMatKey[1,'*'] ;* Added 12/20/2010 JCH * SAP project
|
|
WipProdOrdNo = XLATE('WO_LOG',WONo,WO_LOG_PROD_ORD_NO$,'X') ;* Added 12/20/2010 JCH * SAP project
|
|
IF WIPProdOrdNo = '' THEN WIPProdOrdNo = 'M':FMT(WONo, "R(0)#6"):'.1' ;* Added 12/20/2010 JCH * SAP project
|
|
|
|
|
|
RepWfrCnt = COUNT(RepWaferIDs,@FM) + (RepWaferIDs NE '')
|
|
|
|
FOR I = 1 TO RepWfrCnt
|
|
MovedToSlot = RepWaferIDs<I,1>
|
|
WaferID = RepWaferIDs<I,2>
|
|
MU_BoxKey = FIELD(WaferID,'.',1,2)
|
|
CONVERT '.' TO '*' IN MU_BoxKey
|
|
|
|
MUWONo = MU_BoxKey[1,'*'] ;* Added 12/20/2010 JCH * SAP project
|
|
MUProdOrdNo = XLATE('WO_LOG',MUWONo,WO_LOG_PROD_ORD_NO$,'X') ;* Added 12/20/2010 JCH * SAP project
|
|
IF MUProdOrdNo = '' THEN MUProdOrdNo = 'M':FMT(MUWONo, "R(0)#6"):'.1' ;* Added 12/20/2010 JCH * SAP project
|
|
|
|
otParms = 'WO_MAT':@RM:MU_BoxKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
|
|
|
|
IF Get_Status(errCode) ELSE
|
|
LOCATE MovedToSlot IN WOMatRec<WO_MAT_SLOT_MOVED_TO$> USING @VM SETTING Pos THEN
|
|
|
|
WOMatRec<WO_MAT_SLOT_MOVED_TO$,Pos> = ''
|
|
// Timestamp MU Wafer Project
|
|
// Remove the most recent 'removed' DTM from WOMatRec.
|
|
RemovedDTMS = WOMatRec<WO_MAT_MU_WAFER_REMOVED_DTM$, Pos>
|
|
RemovedDTMS = Delete(RemovedDTMS, 1, 1, 1)
|
|
WOMatRec<WO_MAT_MU_WAFER_REMOVED_DTM$, Pos> = RemovedDTMS
|
|
|
|
TranQty = '-1' ;* Material being moved from WIP back to makeup
|
|
*obj_SAP('AddTransaction','MU_WFR':@RM:WIPProdOrdNo:@RM:MUProdOrdNo:@RM:TranQty) ;* End of SAP project new code
|
|
|
|
END
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
END
|
|
NEXT I
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ChangeCassProps:
|
|
* * * * * * *
|
|
|
|
WOMatKeys = Parms[1,@RM]
|
|
HotLots = Parms[COL2()+1,@RM]
|
|
MUBoxes = Parms[COL2()+1,@RM]
|
|
|
|
IF NOT(ASSIGNED(WOMatKeys)) THEN ErrorMsg = 'Unassigned Parm "WOMatKEys" passed to routine. (':Method:')'
|
|
IF NOT(ASSIGNED(HotLots)) THEN HotLots = ''
|
|
IF NOT(ASSIGNED(MUBoxes)) THEN MUBoxes = ''
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
IF WOMatKeys = '' THEN RETURN
|
|
|
|
Set_Status(0)
|
|
WMParms = 'WO_MAT'
|
|
LockedWOMatKeys = ''
|
|
|
|
WOMatKeyCnt = COUNT(WOMatKeys,@VM) + (WOMatKeys NE '')
|
|
|
|
FOR I = 1 TO WOMatKeyCnt
|
|
|
|
WOMatKey = WOMatKeys<1,I>
|
|
WMParms = FieldStore(WMParms, @RM, 2, 1, WOMatKey)
|
|
|
|
obj_Tables('LockRec',WMParms)
|
|
IF Get_Status(errCode) THEN
|
|
LockedWOMatKeyCnt = COUNT(LockedWOMatKeys,@VM) + (LockedWOMatKeys NE '')
|
|
FOR N = 1 TO LockedWOMatKeyCnt
|
|
WMParms = FieldStore(WMParms, @RM, 2, 1, LockedWOMatKeys<1,N>)
|
|
obj_Tables('UnlockRec',WMParms) ;* Unlock everything locked up to here
|
|
NEXT N
|
|
ErrorMsg = 'Unable to lock WO_MAT ':QUOTE(WOMatKey):' for update.'
|
|
RETURN
|
|
END ELSE
|
|
LockedWOMatKeys<1,I> = WOMatKey
|
|
END
|
|
NEXT I
|
|
|
|
HotLots = ICONV(HotLots,'B')
|
|
MUBoxes = ICONV(MUBoxes,'B')
|
|
|
|
WOMatTableVar = FIELD(WMParms,@RM,3)
|
|
|
|
LockedWOMatKeyCnt = COUNT(LockedWOMatKeys,@VM) + (LockedWOMatKeys NE '')
|
|
|
|
FOR I = 1 TO LockedWOMatKeyCnt
|
|
LockedWOMatKey = LockedWOMatKeys<1,I>
|
|
READ WOMatRec FROM WOMatTableVar,LockedWOMatKey THEN
|
|
HotLot = HotLots<1,I>
|
|
MUBox = MUBoxes<1,I>
|
|
|
|
IF HotLot NE WOMatRec<WO_MAT_HOT_LOT$> THEN WOMatRec<WO_MAT_HOT_LOT$> = HotLot
|
|
IF MUBox NE WOMatRec<WO_MAT_MAKEUP_BOX$> THEN WOMatRec<WO_MAT_MAKEUP_BOX$> = MUBox
|
|
|
|
WMParms = FieldStore(WMParms, @RM, 2, 1, LockedWOMatKey)
|
|
WMParms = FieldStore(WMParms, @RM, 4, 1, WOMatRec)
|
|
obj_Tables('WriteRec',WMParms) ;* Write and unlock WOMat records
|
|
END
|
|
NEXT I
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
SlotWaferIDs:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
IF WOMatRec = '' THEN
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
END
|
|
|
|
SlotNos = WOMatRec<WO_MAT_SLOT_NO$>
|
|
SlotNCRs = WOMatRec<WO_MAT_SLOT_NCR$>
|
|
SlotMetNos = WOMatRec<WO_MAT_SLOT_MET_NO$>
|
|
SlotMovedTos = WOMatRec<WO_MAT_SLOT_MOVED_TO$>
|
|
SlotRepWaferIDs = WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$>
|
|
|
|
IF SlotNos[-1,1] = @VM THEN SlotNos[-1,1] = ''
|
|
|
|
SlotNoCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
|
|
|
|
FOR I = 1 TO SlotNoCnt
|
|
DefWaferID = WOMatKey:'*':SlotNos<1,I>
|
|
CONVERT '*' TO '.' IN DefWaferID
|
|
|
|
WafersPulled = (SlotNCRs<1,I> NE '' OR SlotMetNos<1,I> NE '')
|
|
|
|
BEGIN CASE
|
|
CASE SlotNos<1,I> EQ ''
|
|
Result<1,I> = ''
|
|
|
|
CASE WafersPulled AND SlotMovedTos<1,I> NE '' AND SlotRepWaferIDs<1,I> NE ''
|
|
Result<1,I> = ''
|
|
|
|
CASE WafersPulled AND SlotMovedTos<1,I> NE '' AND SlotRepWaferIDs<1,I> = ''
|
|
Result<1,I> = ''
|
|
|
|
CASE WafersPulled AND SlotMovedTos<1,I> = '' AND SlotRepWaferIDs<1,I> NE ''
|
|
Result<1,I> = SlotRepWaferIDs<1,I>
|
|
|
|
CASE WafersPulled AND SlotMovedTos<1,I> = '' AND SlotRepWaferIDs<1,I> = ''
|
|
Result<1,I> = ''
|
|
|
|
CASE NOT(WafersPulled) AND SlotMovedTos<1,I> NE '' AND SlotRepWaferIDs<1,I> NE ''
|
|
Result<1,I> = SlotRepWaferIDs<1,I>
|
|
|
|
CASE NOT(WafersPulled) AND SlotMovedTos<1,I> NE '' AND SlotRepWaferIDs<1,I> = ''
|
|
Result<1,I> = ''
|
|
|
|
CASE NOT(WafersPulled) AND SlotMovedTos<1,I> = '' AND SlotRepWaferIDs<1,I> NE ''
|
|
Result<1,I> = '** Error **'
|
|
|
|
CASE NOT(WafersPulled) AND SlotMovedTos<1,I> = '' AND SlotRepWaferIDs<1,I> = ''
|
|
Result<1,I> = DefWaferID
|
|
|
|
END CASE
|
|
NEXT I
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
TestSlotWaferIDs:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
IF WOMatRec = '' THEN
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
END
|
|
|
|
SlotNos = WOMatRec<WO_MAT_SLOT_NO$>
|
|
SlotNCRs = WOMatRec<WO_MAT_SLOT_NCR$>
|
|
SlotMetNos = WOMatRec<WO_MAT_SLOT_MET_NO$>
|
|
SlotMovedTos = WOMatRec<WO_MAT_SLOT_MOVED_TO$>
|
|
SlotRepWaferIDs = WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$>
|
|
|
|
IF SlotNos[-1,1] = @VM THEN SlotNos[-1,1] = ''
|
|
|
|
SlotNoCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
|
|
|
|
FOR I = 1 TO SlotNoCnt
|
|
DefWaferID = WOMatKey:'*':SlotNos<1,I>
|
|
CONVERT '*' TO '.' IN DefWaferID
|
|
|
|
WafersPulled = (SlotNCRs<1,I> NE '' OR SlotMetNos<1,I> NE '' OR SlotMovedTos<1,I> NE '')
|
|
|
|
BEGIN CASE
|
|
CASE WafersPulled AND SlotRepWaferIDs<1,I> = ''
|
|
Result<1,I> = ''
|
|
|
|
CASE NOT(WafersPulled) AND SlotRepWaferIDs<1,I> NE ''
|
|
Result<1,I> = SlotRepWaferIDs<1,I>
|
|
|
|
|
|
CASE NOT(WafersPulled) AND SlotRepWaferIDS<1,I> = ''
|
|
Result<1,I> = DefWaferID
|
|
|
|
END CASE
|
|
NEXT I
|
|
|
|
|
|
* * * * * * *
|
|
BackfillNCR:
|
|
* * * * * * *
|
|
|
|
* This is temporary until we start using the WO_MAT_WFR window for everything
|
|
|
|
RETURN ;* Dead 9/8/2008 JCH
|
|
|
|
WONo = Parms[1,@RM]
|
|
WOCassNo = Parms[COL2()+1,@RM]
|
|
NCRId = Parms[COL2()+1,@RM]
|
|
SlotNos = 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(NCRId)) THEN ErrorMsg = 'Unassigned Parm "NCRId" passed to routine. (':Method:')'
|
|
IF NOT(ASSIGNED(SlotNos)) THEN ErrorMsg = 'Unassigned Parm "SlotNos" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
otParms = 'WO_MAT':@RM:WONo:'*':WOCassNo
|
|
WOMatRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
|
|
|
|
IF Get_Status(errCode) ELSE
|
|
|
|
AllSlotCnt = COUNT(WOMatRec<WO_MAT_SLOT_NCR$>,@VM) + (WOMatRec<WO_MAT_SLOT_NCR$> NE '')
|
|
FOR I = 1 TO AllSlotCnt
|
|
IF WOMatRec<WO_MAT_SLOT_NCR$,I> = NCRId THEN
|
|
WOMatRec<WO_MAT_SLOT_NCR$,I> = '' ;* Added 8/12/2008 to clear before setting -> junk left from conversion cleanup
|
|
END
|
|
NEXT I
|
|
|
|
SlotCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
|
|
|
|
FOR I = 1 TO SlotCnt
|
|
SlotNo = SlotNos<1,I>
|
|
WOMatRec<WO_MAT_SLOT_NCR$,SlotNo> = NCRId
|
|
NEXT I
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
*************
|
|
CurrWaferCnt:
|
|
*************
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
OutOnly = Parms[COL2()+1,@RM] ;* Added 1/25/2010 JCH
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
IF WOMatRec = '' THEN
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
END
|
|
|
|
WMIKey = WOMatRec<WO_MAT_WMI_KEY$>
|
|
WMOKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
ReactorType = Xlate('WO_MAT', WOMatKey, 'REACTOR_TYPE', 'X')
|
|
If ReactorType EQ 'GAN' then
|
|
Result = XLATE('WO_MAT_WFR', WOMatKey, 'OUT_WFR_QTY', 'X')
|
|
end else
|
|
IF WMOKey NE '' THEN
|
|
Result = XLATE('WM_OUT',WMOKey,'WAFER_CNT','X')
|
|
IF NOT(OutOnly) THEN
|
|
IF WMIKey NE '' THEN
|
|
Result += XLATE('WM_IN',WMIKey,'REM_WFRS','X') ;* Combination of WM_IN + WM_OUT
|
|
END
|
|
END
|
|
END ELSE
|
|
|
|
GOSUB SlotWaferIDs
|
|
|
|
SlotWaferIDs = Result
|
|
Result = ''
|
|
Tmp = 0
|
|
WaferIDCnt = COUNT(SlotWaferIDs,@VM) + (SlotWaferIDs NE '')
|
|
FOR I = 1 TO WaferIDCnt
|
|
IF SlotWaferIDs<1,I> NE '' THEN Tmp += 1
|
|
NEXT I
|
|
Result = Tmp
|
|
END
|
|
end
|
|
|
|
|
|
IF Result NE '' THEN
|
|
IF WOMatRec<WO_MAT_WIP_STOP_DTM$> = '' AND Result = 0 THEN
|
|
oPLParms = 'WO_MAT':@RM
|
|
oPLParms := WOMatKey:@RM
|
|
oPLParms := WO_MAT_WIP_STOP_DTM$:@RM
|
|
oPLParms := ICONV(OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS') ,'DT'):@RM
|
|
|
|
obj_Post_Log('Create',oPLParms)
|
|
END
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
***********
|
|
GetGRProps:
|
|
***********
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
|
|
If WOMatRec = '' Then
|
|
WOMatRec = XLATE('WO_MAT', WOMatKey, '', 'X')
|
|
End
|
|
|
|
WOMatWfrRec = XLATE('WO_MAT_WFR', WOMatKey, '', 'X')
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
ReactorType = XLATE('WO_LOG', WONo, 'REACT_TYPE', 'X')
|
|
|
|
WOStepKey = WONo : '*1'
|
|
WOStepRec = XLATE('WO_STEP', WOStepKey, '', 'X')
|
|
|
|
WMOKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
WMIKey = WOMatRec<WO_MAT_WMI_KEY$>
|
|
|
|
IF WMIKey NE '' AND WMOKey = '' THEN
|
|
NULL ;* Skip the final sig check on the WMIn box if no corresponding WMOut box
|
|
END ELSE
|
|
// Check for full box reject. If so, then skip signature check.
|
|
RejectedWafers = 0
|
|
RejectedMUWafers = 0
|
|
ProdTestWafers = 0
|
|
|
|
Set_Status(0)
|
|
ReactorType = XLATE('WO_LOG', WONo, 'REACT_TYPE', 'X')
|
|
CassetteQty = XLATE('WO_MAT', WOMatKey, 'WAFER_QTY', 'X')
|
|
RejectedWafers = XLATE('WO_MAT', WOMatKey, 'TOT_REJ_WFRS', 'X')
|
|
RejectedMUWafers = XLATE('WO_MAT', WOMatKey, 'TOT_REJ_MU_WFRS', 'X')
|
|
ProdTestWafers = XLATE('WO_MAT', WOMatKey, 'TW_PROD','X')
|
|
|
|
IF (RejectedWafers = '') then
|
|
RejectedWafers = 0
|
|
END
|
|
IF (RejectedMUWafers = '') then
|
|
RejectedMUWafers = 0
|
|
END
|
|
IF (ProdTestWafers = '') then
|
|
ProdTestWafers = 0
|
|
END
|
|
|
|
IF ((ReactorType = 'EPP') OR (ReactorType = 'EpiPro')) THEN
|
|
RejectedQty = RejectedWafers + RejectedMUWafers
|
|
END ELSE
|
|
RejectedQty = RejectedWafers + RejectedMUWafers + ProdTestWafers
|
|
END
|
|
|
|
end
|
|
|
|
GRWfrQty = 0
|
|
ScrapQty = 0
|
|
ProdTWQty = 0
|
|
AvailMUWfrQty = 0
|
|
MUCassIDs = ''
|
|
MUCassQtys = ''
|
|
|
|
IF WMOKey NE '' OR WMIKey NE '' THEN
|
|
|
|
IF WMIKey NE '' THEN
|
|
ProdTWQty = XLATE('WM_IN',WMIKey,'TW_PROD','X') ;* Changes on 4/21/2014 JCH - operators are forgetting to do some of the metrology and TW use records.
|
|
ScrapQty = Sum(XLATE('WM_IN',WMIKey,'NCR_REJ_CNT','X')) ;* 6/4/2014 JCH
|
|
END ;* End of check for WMIKey
|
|
|
|
IF WMOKey NE '' THEN
|
|
|
|
WMORec = XLATE('WM_OUT',WMOKey,'','X')
|
|
|
|
SlotNos = WMORec<WM_OUT_SLOT_NO$>
|
|
SlotCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
|
|
|
|
FOR I = 1 TO SlotCnt
|
|
IF WMORec<WM_OUT_MAKEUP_BOX$> = 1 THEN
|
|
|
|
IF WMORec<WM_OUT_SLOT_NCR$,I> NE '' THEN ScrapQty += 1
|
|
IF WMORec<WM_OUT_MU_WO_NO$,I> = '' AND WMORec<WM_OUT_RDS$,I> NE '' THEN AvailMUWfrQty += 1
|
|
IF WMORec<WM_OUT_MU_WO_NO$,I> = '' AND WMORec<WM_OUT_UMW_CASS_ID$,I> NE '' THEN AvailMUWfrQty += 1
|
|
|
|
|
|
END ELSE
|
|
IF WMORec<WM_OUT_SLOT_NCR$,I> NE '' THEN ScrapQty += 1
|
|
IF WMORec<WM_OUT_MU_WO_NO$,I> = '' AND WMORec<WM_OUT_RDS$,I> NE '' THEN GRWfrQty += 1
|
|
IF WMORec<WM_OUT_MU_WO_NO$,I> = '' AND WMORec<WM_OUT_UMW_CASS_ID$,I> NE '' THEN GRWfrQty += 1
|
|
|
|
END
|
|
|
|
IF WMORec<WM_OUT_MU_WO_NO$,I> NE '' THEN
|
|
|
|
MUCassID = WMORec<WM_OUT_MU_WO_NO$,I>:'*':WMORec<WM_OUT_MU_CASS_NO$,I>
|
|
|
|
LOCATE MUCassID IN MUCassIDs USING @VM SETTING Pos THEN
|
|
MUCassQtys<1,Pos> = MUCassQtys<1,Pos> + 1
|
|
END ELSE
|
|
MUCassIDs = INSERT(MUCassIDs,1,Pos,0,MUCassID) ;* @MV'd list of CassIDs used for makeup
|
|
MUCassQtys = INSERT(MUCassQtys,1,Pos,0,1) ;* @MV'd list of Wfr Qtys for each CassID
|
|
END
|
|
END
|
|
|
|
NEXT I
|
|
END;* End of check for WMOKey
|
|
|
|
END ELSE
|
|
SlotIDs = WOMatRec<WO_MAT_SLOT_NO$>
|
|
SlotCnt = COUNT(SlotIDs,@VM) + (SlotIDs NE '')
|
|
SlotWfrIDs = Xlate('WO_MAT', WOMatKey, 'SLOT_WAFER_ID', 'X')
|
|
FOR I = 1 TO SlotCnt
|
|
IF WOMatRec<WO_MAT_MAKEUP_BOX$> = 1 THEN
|
|
SlotWfrID = SlotWfrIDs<0, I>
|
|
BEGIN CASE
|
|
CASE WOMatRec<WO_MAT_SLOT_NCR$,I> EQ '' AND WOMatRec<WO_MAT_SLOT_MET_NO$,I> EQ ''
|
|
AvailMUWfrQty += 1
|
|
CASE WOMatRec<WO_MAT_SLOT_NCR$,I> EQ '' AND WOMatRec<WO_MAT_SLOT_MET_NO$,I> NE '' AND WOMatRec<WO_MAT_SLOT_MET_NO$,I> _NEC 'x'
|
|
ProdTWQty += 1
|
|
CASE WOMatRec<WO_MAT_SLOT_NCR$,I> NE '' AND WOMatRec<WO_MAT_SLOT_MET_NO$,I> EQ ''
|
|
ScrapQty += 1
|
|
END CASE
|
|
END ELSE
|
|
BEGIN CASE
|
|
CASE WOMatRec<WO_MAT_SLOT_NCR$,I> EQ '' AND WOMatRec<WO_MAT_SLOT_MET_NO$,I> EQ '' AND WOMatRec<WO_MAT_SLOT_NO$, I> EQ ''
|
|
Null
|
|
CASE WOMatRec<WO_MAT_SLOT_NCR$,I> EQ '' AND WOMatRec<WO_MAT_SLOT_MET_NO$,I> EQ ''
|
|
GRWfrQty += 1
|
|
CASE WOMatRec<WO_MAT_SLOT_NCR$,I> EQ '' AND WOMatRec<WO_MAT_SLOT_MET_NO$,I> NE '' AND WOMatRec<WO_MAT_SLOT_MET_NO$,I> _NEC 'x'
|
|
ProdTWQty += 1
|
|
CASE WOMatRec<WO_MAT_SLOT_NCR$,I> NE '' AND WOMatRec<WO_MAT_SLOT_MET_NO$,I> EQ ''
|
|
ScrapQty += 1
|
|
END CASE
|
|
END
|
|
|
|
IF WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,I> NE '' THEN
|
|
|
|
|
|
RepMUCassID = FIELD(WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,I>,'.',1,2) ;* Replacement Wafer CassID
|
|
FromMUCassID = FIELD(WOMatRec<WO_MAT_SLOT_MOVED_FROM$,I>,'.',1,2) ;* MU Cassette ID
|
|
ToMUCassID = FIELD(WOMatRec<WO_MAT_SLOT_MOVED_TO$,I>,'.',1,2)
|
|
|
|
IF ( (FromMUCassID NE '') and (ToMUCassID EQ '') ) THEN
|
|
MUCassID = FromMUCassID
|
|
END ELSE
|
|
MUCassID = RepMUCassID
|
|
END
|
|
|
|
CONVERT '.' TO '*' IN MUCassID
|
|
LOCATE MUCassID IN MUCassIDs USING @VM SETTING Pos THEN
|
|
MUCassQtys<1,Pos> = MUCassQtys<1,Pos> + 1
|
|
END ELSE
|
|
MUCassIDs = INSERT(MUCassIDs,1,Pos,0,MUCassID) ;* @MV'd list of CassIDs used for makeup
|
|
MUCassQtys = INSERT(MUCassQtys,1,Pos,0,1) ;* @MV'd list of Wfr Qtys for each CassID
|
|
END
|
|
END
|
|
|
|
NEXT I
|
|
END
|
|
|
|
MUCassCnt = COUNT(MUCassIDs,@VM) + (MUCassIDs NE '')
|
|
|
|
IF MUCassCnt > 0 THEN
|
|
|
|
SortMUCassIDs = ''
|
|
SortMUCassQtys = ''
|
|
|
|
FOR I = 1 TO MUCassCnt
|
|
MUCassQty = MUCassQtys<1,I>
|
|
LOCATE MUCassQty IN SortMUCassQtys BY 'DR' USING @VM SETTING Pos THEN
|
|
SortMUCassQtys = INSERT(SortMUCassQtys,1,Pos,0,MUCassQty)
|
|
SortMUCassIDs = INSERT(SortMUCassIDs,1,Pos,0,MUCassIds<1,I>)
|
|
END ELSE
|
|
SortMUCassQtys = INSERT(SortMUCassQtys,1,Pos,0,MUCassQty)
|
|
SortMUCassIDs = INSERT(SortMUCassIDs,1,Pos,0,MUCassIds<1,I>)
|
|
END
|
|
NEXT I
|
|
|
|
MUCassIDs = SortMUCassIDs
|
|
MUCassQtys = SortMUCassQtys
|
|
|
|
END
|
|
|
|
Result = GRWfrQty:@FM:ScrapQty:@FM:ProdTWQty:@FM:AvailMUWfrQty:@FM:MUCassIDs:@FM:MUCassQtys
|
|
// GAN uses GaN_Serices('GetGaNGRProps')
|
|
If ReactorType EQ 'GAN' then Result = ''
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
ConvertMakeup:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
IF WOMatRec<WO_MAT_MU_WAFER_FLAG$> AND NOT(WOMatRec<WO_MAT_MAKEUP_BOX$>) THEN
|
|
|
|
SlotNCRs = WOMatRec<WO_MAT_SLOT_NCR$>
|
|
SlotRepBys = WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$>
|
|
|
|
EmptySlots = ''
|
|
MakeupCassIDs = ''
|
|
MakeupCassWfrQtys = ''
|
|
|
|
SlotCnt = COUNT(SlotNCRs,@VM) + (SlotNCRs NE '')
|
|
|
|
FOR I= 1 TO SlotCnt
|
|
SlotRepBy = SlotRepBys<1,I>
|
|
IF SlotNCRs<1,I> NE '' AND SlotRepBy = '' THEN
|
|
EmptySlots<1,-1> = I
|
|
END
|
|
IF SlotRepBy NE '' THEN
|
|
MakeupCassID = FIELD(SlotRepBy,'.',1,2)
|
|
LOCATE MakeupCassID IN MakeupCassIDs USING @VM SETTING Pos THEN
|
|
MakeupCassWfrQtys<1,Pos> = MakeupCassWfrQtys<1,Pos> + 1
|
|
END ELSE
|
|
MakeupCassIDs = INSERT(MakeupCassIDs,1,Pos,0,MakeupCassID)
|
|
MakeupCassWfrQtys = INSERT(MakeupCassWfrQtys,1,Pos,0,1)
|
|
END
|
|
END ;* End of check for SlotRepBy data
|
|
|
|
NEXT I
|
|
|
|
CONVERT '.' TO '*' IN MakeupCassIDs
|
|
|
|
RDSNo = WOMatRec<WO_MAT_RDS_NO$>
|
|
|
|
IF NOT(INDEX(RDSNo,@VM,1)) THEN
|
|
RDSMakeupBox = XLATE('RDS_MAKEUP',RDSNo,'','X')
|
|
MUSrcRDSs = RDSMakeupBox<RDS_MAKEUP_SRC_RDS$>
|
|
MUSrcSlots = RDSMakeupBox<RDS_MAKEUP_SRC_SLOT$>
|
|
|
|
SourceCassettes = ''
|
|
SourceCassCnts = ''
|
|
|
|
MUCnt = COUNT(MUSrcRDSs,@VM) + (MUSrcRDSs NE '')
|
|
FOR I = 1 TO MUCnt
|
|
MuRDSNo = MUSrcRDSs<1,I>
|
|
MUSlotNo = MUSrcSlots<1,I>
|
|
IF MuRDSNo NE '' AND MUSlotNo NE '' THEN
|
|
MURdsRec = XLATE('RDS',MuRDSNo,'','X')
|
|
MUWoNo = MURdsRec<RDS_WO$>
|
|
MUCassNo = MURdsRec<RDS_CASS_NO$>
|
|
SourceCassette = MUWoNo:'*':MUCassNo
|
|
|
|
LOCATE SourceCassette IN MakeupCassIDs USING @VM SETTING Pos1 THEN
|
|
MakeupCassWfrQtys<1,Pos1> = MakeupCassWfrQtys<1,Pos1> - 1
|
|
IF MakeupCassWfrQtys<1,Pos1> = 0 THEN
|
|
MakeupCassIDs = DELETE(MakeupCassIDs,1,Pos1,0)
|
|
MakeupCassWfrQtys= DELETE(MakeupCassWfrQtys,1,Pos1,0)
|
|
END
|
|
|
|
END ELSE
|
|
LOCATE SourceCassette IN SourceCassettes USING @VM SETTING Pos THEN
|
|
SourceCassCnts<1,Pos> = SourceCassCnts<1,Pos> + 1
|
|
END ELSE
|
|
SourceCassettes = INSERT(SourceCassettes,1,Pos,0,SourceCassette)
|
|
SourceCassCnts = INSERT(SourceCassCnts,1,Pos,0,1)
|
|
END
|
|
END
|
|
END
|
|
NEXT I
|
|
|
|
SCCnt = COUNT(SourceCassettes,@VM) + (SourceCassettes NE '')
|
|
|
|
FOR N = 1 TO SCCnt
|
|
SourceCassette = SourceCassettes<1,N>
|
|
SourceCassCnt = SourceCassCnts<1,N>
|
|
|
|
CassEmptySlots = FIELD(EmptySlots,@VM,1,SourceCassCnt)
|
|
EmptySlots[1,COL2()] = ''
|
|
|
|
CALL obj_WO_Mat('AddMakeupWafers',WOMatKey:@RM:CassEmptySlots:@RM:SourceCassette) ;* This fills first batch of empty slots
|
|
IF Get_Status(errCode) THEN ErrMsg(errCode)
|
|
|
|
NEXT N
|
|
|
|
END ;* End of check single RDSNo for cassette
|
|
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
RemProdTW:
|
|
* * * * * * *
|
|
|
|
WONo = Parms[1,@RM]
|
|
WOCassNo = Parms[COL2()+1,@RM]
|
|
MetNo = Parms[COL2()+1,@RM]
|
|
SlotNos = Parms[COL2()+1,@RM]
|
|
PTW_Flag = 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
|
|
|
|
otParms = 'WO_MAT':@RM:WONo:'*':WOCassNo
|
|
WOMatRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
|
|
|
|
IF Get_Status(errCode) THEN
|
|
NULL
|
|
END ELSE
|
|
SlotCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
|
|
PulledWaferIDs = ''
|
|
FOR I = 1 TO SlotCnt
|
|
SlotNo = SlotNos<1,I>
|
|
IF PTW_Flag = 1 THEN
|
|
PulledWaferIDs<1,-1> = WONo:'.':WOCassNo:'.':SlotNo
|
|
END ELSE
|
|
PulledWaferIDs := WONo:'.':WOCassNo:'.':SlotNo:','
|
|
END
|
|
WOMatRec<WO_MAT_SLOT_MET_NO$,SlotNo> = MetNo
|
|
NEXT I
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
END
|
|
|
|
IF PulledWaferIDs[-1,1] = ',' THEN PulledWaferIDs[-1,1] = ''
|
|
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
|
|
|
|
otParms = 'WO_MAT':@RM:WONo:'*':WOCassNo
|
|
|
|
WOMatRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
|
|
|
|
IF WaferIDs = '' THEN
|
|
MetNos = WOMatRec<WO_MAT_SLOT_MET_NO$>
|
|
WaferIDCnt = COUNT(MetNos,@VM) + (MetNos NE '')
|
|
|
|
FOR I = 1 TO WaferIDCnt
|
|
IF WOMatRec<WO_MAT_SLOT_MET_NO$,I> = MetNo THEN
|
|
WOMatRec<WO_MAT_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.']
|
|
WOMatRec<WO_MAT_SLOT_MET_NO$,SlotNo> = ''
|
|
NEXT I
|
|
END
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
SetWMStatus:
|
|
* * * * * * *
|
|
|
|
RETURN
|
|
|
|
|
|
* Replaced with WM_MFS
|
|
|
|
WONo = Parms[1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
FieldNo = Parms[COL2()+1,@RM]
|
|
NewStatus = Parms[COL2()+1,@RM]
|
|
|
|
IF WONo = '' THEN ErrorMsg = 'Null parameter "WONo" passed to routine. (':Method:')'
|
|
IF CassNo = '' THEN ErrorMsg = 'Null parameter "CassNo" passed to routine. (':Method:')'
|
|
IF FieldNo = '' THEN ErrorMsg = 'Null parameter "FieldNo" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
WOMatKey = WONo:'*':CassNo
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms)
|
|
|
|
IF Get_Status(errCode) THEN RETURN
|
|
|
|
IF FieldNo = WO_MAT_WMI_CURR_STATUS$ THEN
|
|
WOMatRec<WO_MAT_WMI_CURR_STATUS$> = NewStatus
|
|
END
|
|
|
|
IF FieldNo = WO_MAT_WMO_CURR_STATUS$ THEN
|
|
WOMatRec<WO_MAT_WMO_CURR_STATUS$> = NewStatus
|
|
END
|
|
|
|
otParms = FieldStore(OtParms,@RM,4,0,WOMatRec) ;* Put record in 4th field of OtParms
|
|
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ReportStatus:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null parameter "WOMatKey" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
IF WONo < 128680 THEN RETURN ;* This is the first WO No on 7/29/2005 - The day we cut over to the new system.
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
IF WOMatRec<WO_MAT_VOID$> THEN
|
|
Result = 'VOID'
|
|
RETURN
|
|
END
|
|
|
|
ReactType = XLATE('WO_MAT',WOMatKey,'PS_REACTOR_TYPE','X')
|
|
|
|
RDSNo = WOMatRec<WO_MAT_RDS_NO$>[-1,'B':@VM]
|
|
WMIKey = WOMatRec<WO_MAT_WMI_KEY$>
|
|
WMOKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
|
|
WMIStatus = WOMatRec<WO_MAT_WMI_CURR_STATUS$>
|
|
WMOStatus = WOMatRec<WO_MAT_WMO_CURR_STATUS$>
|
|
|
|
IF WMOStatus = 'COMP' THEN
|
|
WMOStatus = obj_WO_Mat('CurrStatus',WOMatKey:@RM:WOMatRec)
|
|
END
|
|
|
|
IF WOMatRec<WO_MAT_SHIP_NO$> NE '' THEN
|
|
IF WMOKey NE '' THEN
|
|
Result = 'WMO - Shipped'
|
|
END ELSE
|
|
Result = 'ASM - Shipped'
|
|
END
|
|
RETURN
|
|
END
|
|
|
|
|
|
IF WMOKey NE '' THEN
|
|
WMOMakeup = XLATE('WM_OUT',WMOKey,'MAKEUP_BOX','X')
|
|
END ELSE
|
|
WMOMakeup = ''
|
|
END
|
|
|
|
TypeDesc = ''
|
|
|
|
|
|
IF WMIKey = '' AND WMOKey = '' AND ( ReactType = 'P' OR ReactType = 'EPP' ) THEN
|
|
TypeDesc<1,-1> = 'WMI'
|
|
TypeDesc := ' * Error * '
|
|
Result = TypeDesc
|
|
RETURN
|
|
END
|
|
|
|
IF WMIKey NE '' OR WMOKey NE '' THEN
|
|
InboundStat = ''
|
|
OutboundStat = ''
|
|
|
|
IF WOMatRec<WO_MAT_HOLD$> = 1 THEN
|
|
IF WOMatRec<WO_MAT_HOLD_ENTITY$,1> = 'WM_IN' THEN
|
|
InboundStat = 'HOLD'
|
|
END
|
|
|
|
IF WOMatRec<WO_MAT_HOLD_ENTITY$,1> = 'WM_OUT' THEN
|
|
OutBoundStat = 'HOLD'
|
|
END
|
|
|
|
BEGIN CASE
|
|
CASE InboundStat = '' AND OutboundStat = ''
|
|
Result = ''
|
|
|
|
CASE InboundStat = '' AND OutboundStat NE ''
|
|
Result = 'WMO':' - ':OCONV(OutboundStat,'[WM_OUT_CURR_STATUS_CONV]')
|
|
|
|
CASE InboundStat NE '' AND OutboundStat = ''
|
|
Result = 'WMI':' - ':OCONV(InboundStat,'[WM_IN_CURR_STATUS_CONV]')
|
|
|
|
CASE InboundStat NE '' AND OutboundStat NE ''
|
|
Result = 'WMI':' - ':OCONV(InboundStat,'[WM_IN_CURR_STATUS_CONV]'):@VM
|
|
Result := 'WMO':' - ':OCONV(OutboundStat,'[WM_OUT_CURR_STATUS_CONV]')
|
|
END CASE
|
|
|
|
RETURN
|
|
END
|
|
|
|
IF WMIKey NE '' THEN
|
|
IF WMIStatus = 'MT' OR WMIStatus = 'VOID' THEN
|
|
NULL
|
|
END ELSE
|
|
InboundStat = WMIStatus
|
|
END
|
|
END
|
|
|
|
IF WMOKey NE '' THEN
|
|
|
|
* Removed "( WMOMakeup = 1 AND WMOStatus = 'MT' ) from the OR conditions * 5/1/2014 JCH
|
|
|
|
IF WMOStatus = 'RTB' OR WMOStatus = 'VOID' THEN
|
|
NULL
|
|
END ELSE
|
|
OutboundStat = WMOStatus
|
|
END
|
|
END
|
|
|
|
BEGIN CASE
|
|
CASE InboundStat = '' AND OutboundStat = ''
|
|
Result = ''
|
|
|
|
CASE InboundStat = '' AND OutboundStat NE ''
|
|
IF WMOMakeup = 1 THEN
|
|
OutboundStat = 'WMO':' - M/U - ':OCONV(WMOStatus,'[WM_OUT_CURR_STATUS_CONV]')
|
|
END ELSE
|
|
OutboundStat = 'WMO':' - ':OCONV(WMOStatus,'[WM_OUT_CURR_STATUS_CONV]')
|
|
END
|
|
Result = OutboundStat
|
|
|
|
|
|
CASE InboundStat NE '' AND OutboundStat = ''
|
|
Result = 'WMI':' - ':OCONV(WMIStatus,'[WM_IN_CURR_STATUS_CONV]')
|
|
|
|
|
|
CASE InboundStat NE '' AND OutboundStat NE ''
|
|
Result = 'WMI':' - ':OCONV(WMIStatus,'[WM_IN_CURR_STATUS_CONV]'):@VM
|
|
|
|
IF WMOMakeup = 1 THEN
|
|
OutboundStat = 'WMO':' - M/U - ':OCONV(WMOStatus,'[WM_OUT_CURR_STATUS_CONV]')
|
|
END ELSE
|
|
OutboundStat = 'WMO':' - ':OCONV(WMOStatus,'[WM_OUT_CURR_STATUS_CONV]')
|
|
END
|
|
Result = Result:OutboundStat
|
|
|
|
END CASE
|
|
|
|
RETURN
|
|
|
|
END ELSE
|
|
|
|
WOMatCurrStatus = obj_WO_Mat('CurrStatus',WOMatKey:@RM:WOMatRec)
|
|
IF WOMatRec<WO_MAT_MAKEUP_BOX$> = 1 THEN
|
|
TypeDesc<1,-1> = 'ASM - M/U':' - ':OCONV(WOMatCurrStatus,'[WO_MAT_CURR_STATUS_CONV]')
|
|
END ELSE
|
|
TypeDesc<1,-1> = 'ASM'
|
|
|
|
TypeDesc := ' - ':OCONV(WOMatCurrStatus,'[WO_MAT_CURR_STATUS_CONV]') ;* Last
|
|
|
|
End
|
|
|
|
END
|
|
|
|
Result = TypeDesc
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
CassRDSNos:
|
|
* * * * * * *
|
|
|
|
WOMatKeys = Parms[1,@RM]
|
|
|
|
IF WOMatKeys = '' THEN RETURN
|
|
|
|
ReactType = XLATE('WO_MAT',WOMatKeys<1,1>,'PS_REACTOR_TYPE','X')
|
|
|
|
IF ReactType = 'P' OR ReactType = 'EPP' THEN RETURN ;* This isn't valid for EpiPro reactors
|
|
|
|
GOSUB SlotWaferIDs
|
|
SlotWaferIDs = Result
|
|
Result = ''
|
|
CassWOMatKeys = ''
|
|
|
|
CONVERT '.' TO '*' IN SlotWaferIDs
|
|
SlotCnt = COUNT(SlotWaferIDs,@VM) + (SlotWaferIDs NE '')
|
|
FOR I = 1 TO SlotCnt
|
|
SlotWOMatKey = FIELD(SlotWaferIDs<1,I>,'*',1,2)
|
|
LOCATE SlotWOMatKey IN CassWOMatKeys BY 'AR' USING @VM SETTING Pos ELSE
|
|
CassWOMatKeys = INSERT(CassWOMatKeys,1,Pos,0,SlotWOMatKey)
|
|
END
|
|
NEXT I
|
|
|
|
RDSNos = XLATE('WO_MAT',CassWOMatKeys,'SHIP_RDS','X')
|
|
|
|
Result = ''
|
|
RDSNoCnt = COUNT(RDSNos,@VM) + (RDSNos NE '')
|
|
FOR I = 1 TO RDSNoCnt
|
|
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:
|
|
* * * * * * *
|
|
|
|
WOMatKeys = Parms[1,@RM]
|
|
|
|
IF WOMatKeys = '' THEN RETURN
|
|
|
|
ReactType = XLATE('WO_MAT',WOMatKeys<1,1>,'PS_REACTOR_TYPE','X')
|
|
|
|
IF ReactType = 'P' OR ReactType = 'EPP' THEN RETURN ;* This isn't valid for EpiPro reactors
|
|
|
|
GOSUB SlotWaferIDs
|
|
SlotWaferIDs = Result
|
|
Result = ''
|
|
|
|
CassWOMatKeys = ''
|
|
|
|
CONVERT '.' TO '*' IN SlotWaferIDs
|
|
|
|
SlotCnt = COUNT(SlotWaferIDs,@VM) + (SlotWaferIDs NE '')
|
|
|
|
CassWOMatCnts = ''
|
|
|
|
FOR I = 1 TO SlotCnt
|
|
SlotWOMatKey = FIELD(SlotWaferIDs<1,I>,'*',1,2)
|
|
IF SlotWOMatKey NE '' THEN
|
|
LOCATE SlotWOMatKey IN CassWOMatKeys BY 'AR' USING @VM SETTING Pos THEN
|
|
CassWOMatCnts<1,Pos> = CassWOMatCnts<1,Pos> + 1
|
|
END ELSE
|
|
CassWOMatKeys = INSERT(CassWOMatKeys,1,Pos,0,SlotWOMatKey)
|
|
CassWOMatCnts = INSERT(CassWOMatCnts,1,Pos,0,1)
|
|
END
|
|
END
|
|
NEXT I
|
|
|
|
Result = CassWOMatCnts
|
|
|
|
RETURN
|
|
|
|
*********
|
|
GetFQADtm:
|
|
*********
|
|
WOMatKey = Parms[1,@RM]
|
|
rec = Signature_Services('GetSigInfo', WOMatKey, 'QA')
|
|
|
|
Result = rec<2>
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
GetSigProfile:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOStep = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
IF WOMatRec = '' THEN RETURN
|
|
|
|
IF WOStep NE '' THEN
|
|
|
|
SigProfile = ''
|
|
Signatures = ''
|
|
SigDTMs = ''
|
|
SigVers = ''
|
|
|
|
ProfCnt = COUNT(WOMatRec<WO_MAT_SIG_PROFILE$>,@VM) + (WOMatRec<WO_MAT_SIG_PROFILE$> NE '')
|
|
LineNo = 0
|
|
FOR I = 1 TO ProfCnt
|
|
IF WOMatRec<WO_MAT_SIG_PROFILE$,I>[1,1] = WOStep THEN
|
|
LineNo += 1
|
|
SigProfile<1,LineNo> = WOMatRec<WO_MAT_SIG_PROFILE$,I>
|
|
Signatures<1,LineNo> = WOMatRec<WO_MAT_SIGNATURE$,I>
|
|
SigDTMs<1,LineNo> = WOMatRec<WO_MAT_SIG_DTM$,I>
|
|
SigVers<1,LineNo> = WOMatRec<WO_MAT_SIG_VER$,I>
|
|
END
|
|
NEXT I
|
|
END ELSE
|
|
SigProfile = WOMatRec<WO_MAT_SIG_PROFILE$>
|
|
Signatures = WOMatRec<WO_MAT_SIGNATURE$>
|
|
SigDTMs = WOMatRec<WO_MAT_SIG_DTM$>
|
|
SigVers = WOMatRec<WO_MAT_SIG_VER$>
|
|
END
|
|
|
|
SigDTMs = OCONV(SigDTMs,'DT4/^S')
|
|
|
|
Result = SigProfile:@FM:Signatures:@FM:SigDTMs:@FM:SigVers
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
CassSigProfile:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN
|
|
WOMatKey = Parms[1,@RM]
|
|
END
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null parameter "WOMatKey" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
IF WONo < 128680 THEN RETURN ;* This is the first WO No on 7/29/2005 - The day we cut over to the new system.
|
|
|
|
WOStepKeys = XLATE('WO_LOG',WONo,'WO_STEP_KEY','X') ;***********************************************
|
|
|
|
SigProfile = ''
|
|
|
|
StepCnt = COUNT(WOStepKeys,@VM) + (WOStepKeys NE '')
|
|
|
|
FOR I = 1 TO StepCnt
|
|
PSNo = XLATE('WO_STEP',WOStepKeys<1,I>,WO_STEP_PROD_SPEC_ID$,'X')
|
|
StepProfile = obj_Prod_Spec('GetSigProfile',PSNo)
|
|
SigCnt = COUNT(StepProfile,@VM) + (StepProfile NE '')
|
|
FOR N = 1 TO SigCnt
|
|
StepSig = StepProfile<1,N>
|
|
IF StepSig[1,2] NE 'RN' THEN
|
|
SigProfile := I:StepProfile<1,N>:@VM
|
|
END
|
|
NEXT N
|
|
NEXT I
|
|
IF SigProfile[-1,1] = @VM THEN SigProfile[-1,1] = ''
|
|
|
|
Result = SigProfile
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
CassMetProfile:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN
|
|
WOMatKey = Parms[1,@RM]
|
|
END
|
|
|
|
* * * * * * * These doesn't appear to be used anywhere * * * * * * * * JCH 3/9/2015
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null parameter "WOMatKey" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
IF NOT(ASSIGNED(WOMatRec)) THEN
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
END
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
IF WONo < 128680 THEN RETURN ;* This is the first WO No on 7/29/2005 - The day we cut over to the new system.
|
|
|
|
WOStepKeys = XLATE('WO_LOG',WONo,WO_LOG_WO_STEP_KEY$,'X')
|
|
|
|
MetProfile = ''
|
|
|
|
StepCnt = COUNT(WOStepKeys,@VM) + (WOStepKeys NE '')
|
|
|
|
MetLine = 1
|
|
|
|
FOR I = 1 TO StepCnt
|
|
PSNo = XLATE('WO_STEP',WOStepKeys<1,I>,WO_STEP_PROD_SPEC_ID$,'X')
|
|
PSRec = XLATE('PROD_SPEC',PSNo,'','X')
|
|
|
|
MetCnt = COUNT(PSRec<PROD_SPEC_MET_TEST$>,@VM) + (PSRec<PROD_SPEC_MET_TEST$> NE '')
|
|
|
|
FOR N = 1 TO MetCnt
|
|
|
|
Interval = PSRec<PROD_SPEC_MET_INTERVAL$,N>
|
|
Start = PSRec<PROD_SPEC_MET_START$,N>
|
|
|
|
TestFlag = 0
|
|
|
|
IF Interval NE '' AND Start NE '' THEN
|
|
IF Interval = Start THEN
|
|
IF REM(I,Interval) = 0 THEN TestFlag = 1
|
|
END ELSE
|
|
IF ABS((Start + INT(I/Interval)*Interval) - I) = 0 THEN TestFlag = 1
|
|
END
|
|
IF TestFlag THEN
|
|
WOMatRec<WO_MAT_MET_PROFILE$,MetLine> = I:PSRec<PROD_SPEC_MET_TEST$,N>
|
|
WOMatRec<WO_MAT_MET_RUN_STEP$,MetLine> = PSRec<PROD_SPEC_MET_RUN_STEP$,N>
|
|
WOMatRec<WO_MAT_MET_MIN$,MetLine> = PSRec<PROD_SPEC_MET_MIN$
|
|
WOMatRec<WO_MAT_MET_MAX$,MetLine> = PSRec<PROD_SPEC_MET_MAX$
|
|
WOMatRec<WO_MAT_MET_SLOT$,MetLine> = PSRec<PROD_SPEC_MET_SLOT$,N>
|
|
WOMatRec<WO_MAT_MET_SIG$,MetLine> = ''
|
|
WOMatRec<WO_MAT_MET_SIG_DTM$,MetLine> = ''
|
|
MetLine += 1
|
|
END
|
|
END
|
|
|
|
NEXT N
|
|
|
|
NEXT I
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
SetSignature:
|
|
* * * * * * *
|
|
|
|
WONo = Parms[1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
WOStepNo = Parms[COL2()+1,@RM]
|
|
SigProfKeys = Parms[COL2()+1,@RM]
|
|
Signatures = Parms[COL2()+1,@RM]
|
|
SigDTMs = Parms[COL2()+1,@RM]
|
|
MetResults = Parms[COL2()+1,@RM]
|
|
RunSteps = Parms[COL2()+1,@RM]
|
|
StdMaxs = Parms[COL2()+1,@RM]
|
|
StdResults = Parms[COL2()+1,@RM] ;* Added 8/5/2013 JCH
|
|
IgnoreLock = Parms[COL2()+1,@RM] ;* Self-Lock only
|
|
|
|
|
|
IF WONo = '' THEN ErrorMsg = 'Null parameter "WONo" passed to routine. (':Method:')'
|
|
IF CassNo = '' THEN ErrorMsg = 'Null parameter "CassNo" passed to routine. (':Method:')'
|
|
IF WOStepNo = '' THEN Errormsg = 'Null parameter "WOStepNo" passed to routine. (':Method:')'
|
|
IF SigProfKeys = '' THEN ErrorMsg = 'Null parameter "SigProfKeys" passed to routine. (':Method:')'
|
|
IF Signatures = '' THEN ErrorMsg = 'Null parameter "Signatures" passed to routine. (':Method:')'
|
|
IF SigDTMs = '' THEN ErrorMsg = 'Null parameter "SigDTMs" passed to routine. (':Method:')'
|
|
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
SigCnt = COUNT(SigProfKeys,@VM) + (SigProfKeys NE '')
|
|
|
|
FOR I = 1 TO SigCnt
|
|
|
|
IF SigProfKeys<1,I> = '' THEN ErrorMsg = 'Null parameter "SigProfKey" passed to routine. (':Method:')'
|
|
|
|
thisSigDTM = ICONV(SigDTMs<1,I>,'DT')
|
|
IF thisSigDTM = '' THEN
|
|
NULL
|
|
END
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
NEXT I
|
|
|
|
otParms = 'WO_MAT':@RM:WONo:'*':CassNo
|
|
WOMatRec = obj_Tables('ReadOnlyRec',otParms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
RETURN
|
|
END
|
|
|
|
ProfileCnt = COUNT(WOMatRec<WO_MAT_SIG_PROFILE$>,@VM) + (WOMatRec<WO_MAT_SIG_PROFILE$> NE '')
|
|
LastProfSig = WOMatRec<WO_MAT_SIG_PROFILE$,ProfileCnt>
|
|
|
|
LastBoxSigned = 0
|
|
WriteFlag = 0
|
|
|
|
FOR I = 1 TO SigCnt
|
|
SigProfKey = SigProfKeys<1,I>
|
|
RunStep = RunSteps<1,I>
|
|
|
|
IF NUM(SigProfKey[1,1]) ELSE
|
|
SigProfKey = WOStepNo:SigProfKey
|
|
END
|
|
|
|
LOCATE SigProfKey IN WOMatRec<WO_MAT_SIG_PROFILE$> USING @VM SETTING Pos THEN
|
|
WOMatRec<WO_MAT_SIGNATURE$,Pos> = Signatures<1,I>
|
|
WOMatRec<WO_MAT_SIG_DTM$,Pos> = ICONV(SigDTMs<1,I>,'DT')
|
|
|
|
WriteFlag = 1
|
|
|
|
IF WOMatRec<WO_MAT_WMO_KEY$> = '' THEN
|
|
IF SigProfKey = LastProfSig THEN
|
|
|
|
WOLogRec = XLATE('WO_LOG',WONo,'','X')
|
|
LastWOMatKey = WOLogRec<WO_LOG_WO_MAT_KEY$>[-1,@VM]
|
|
|
|
WOMatKey = WONo:'*':CassNo
|
|
|
|
IF WOMatKey = LastWOMatKey THEN
|
|
|
|
* Last box in the Work Order *** 4/1/2014 JCH this doesn't appear to be working.
|
|
* See method 'SetSAPBatch' which should be working. jch
|
|
|
|
CurrDTM = ICONV(OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTH') ,'DT')
|
|
obj_Post_Log('Create','WO_LOG':@RM:WONo:@RM:WO_LOG_WO_STOP_DTM$:@RM:CurrDTM)
|
|
|
|
END ;* End of check for Last Box on the Work Order
|
|
END ;* End of check for Last Signature on this cassette
|
|
END ;* End of check for Non EpiPRO material
|
|
|
|
END
|
|
|
|
NEXT I
|
|
|
|
IF WriteFlag = 1 THEN
|
|
otParms = FieldStore(OtParms,@RM,4,0,WOMatRec) ;* Put record in 4th field of OtParms
|
|
obj_Tables('WriteOnlyRec',otParms)
|
|
|
|
END
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
ClearSignature:
|
|
* * * * * * *
|
|
|
|
WONo = Parms[1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
WOStepNo = Parms[COL2()+1,@RM]
|
|
SigProfKey = Parms[COL2()+1,@RM]
|
|
|
|
IF WONo = '' THEN ErrorMsg = 'Null parameter "WONo" passed to routine. (':Method:')'
|
|
IF CassNo = '' THEN ErrorMsg = 'Null parameter "CassNo" passed to routine. (':Method:')'
|
|
IF WOStepNo = '' THEN Errormsg = 'Null parameter "WOStepNo" passed to routine. (':Method:')'
|
|
IF SigProfKey = '' THEN ErrorMsg = 'Null parameter "SigProfKey" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
otParms = 'WO_MAT':@RM:WONo:'*':CassNo
|
|
WOMatRec = obj_Tables('ReadRec',otParms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
RETURN
|
|
END
|
|
|
|
SigProfKey = WOStepNo:SigProfKey
|
|
|
|
LOCATE SigProfKey IN WOMatRec<WO_MAT_SIG_PROFILE$> USING @VM SETTING Pos THEN
|
|
WOMatRec<WO_MAT_SIGNATURE$,Pos> = ''
|
|
WOMatRec<WO_MAT_SIG_DTM$,Pos> = ''
|
|
|
|
otParms = FieldStore(OtParms,@RM,4,0,WOMatRec) ;* Put record in 4th field of OtParms
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
END ELSE
|
|
|
|
LOCATE SigProfKey IN WOMatRec<WO_MAT_MET_PROFILE$> USING @VM SETTING Pos THEN
|
|
WOMatRec<WO_MAT_MET_RESULT$,Pos> = ''
|
|
WOMatRec<WO_MAT_MET_SIG$,Pos> = ''
|
|
WOMatRec<WO_MAT_MET_SIG_DTM$,Pos> = ''
|
|
|
|
otParms = FieldStore(OtParms,@RM,4,0,WOMatRec) ;* Put record in 4th field of OtParms
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
END ELSE
|
|
obj_Tables('UnlockRec',otParms)
|
|
|
|
END
|
|
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
SigDt:
|
|
* * * * * * *
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
SigProfID = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null parameter "WOMatKey" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
IF WONo < 128680 THEN RETURN ;* This is the first WO No on 7/29/2005 - The day we cut over to the new system.
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
SigProfile = WOMatRec<WO_MAT_SIG_PROFILE$>
|
|
LastSig = SigProfile[-1,'B':@VM]
|
|
|
|
StepCnt = LastSig[1,1] ;* Sig Profiles all start with the step no.
|
|
|
|
|
|
FOR I = 1 TO StepCnt
|
|
LOCATE I:SigProfID IN WOMatRec<WO_MAT_SIG_PROFILE$> USING @VM SETTING Pos THEN
|
|
SigDTM = WOMatRec<WO_MAT_SIG_DTM$,Pos>
|
|
Result<1,-1> = SigDTM[1,'.']
|
|
END
|
|
|
|
NEXT I
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
TestStatus:
|
|
* * * * * * *
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN WOMatKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(WOMatRec)) THEN WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
IF WOMatRec<WO_MAT_VOID$> THEN
|
|
Result = 'VOID'
|
|
RETURN
|
|
END
|
|
|
|
WMIKey = WOMatRec<WO_MAT_WMI_KEY$>
|
|
WMOKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
|
|
IF WOMatRec<WO_MAT_SHIP_NO$> NE '' THEN
|
|
Result = 'SHIP'
|
|
RETURN
|
|
END
|
|
|
|
LocCnt = COUNT(WOMatRec<WO_MAT_INV_LOCATION$>,@VM) + (WOMatRec<WO_MAT_INV_LOCATION$> NE '')
|
|
|
|
LastIn = ''
|
|
LastOut = ''
|
|
|
|
FOR I = LocCnt TO 1 STEP -1
|
|
IF WOMatRec<WO_MAT_INV_LOCATION$,I> = 'PTI' AND LastIn = '' THEN
|
|
LastIn = WOMatRec<WO_MAT_INV_DTM$,I>
|
|
END
|
|
|
|
IF WOMatRec<WO_MAT_INV_LOCATION$,I> = 'PTO' AND LastOut = '' THEN
|
|
LastOut = WOMatRec<WO_MAT_INV_DTM$,I>
|
|
END
|
|
UNTIL LastIn NE '' AND LastOut NE ''
|
|
NEXT I
|
|
|
|
|
|
LastWH = WOMatRec<WO_MAT_INV_WH$>[-1,'B':@VM]
|
|
LastLoc = WOMatRec<WO_MAT_INV_LOCATION$>[-1,'B':@VM]
|
|
|
|
CurrLoc = ''
|
|
IF LastWH NE '' AND LastLoc NE '' THEN
|
|
CurrLoc = LastWH:'*':LastLoc
|
|
IF CurrLoc = 'SR*SB' THEN CurrLoc = ''
|
|
END
|
|
|
|
BEGIN CASE
|
|
CASE LastIn = '' AND LastOut = '' ; InCleanRoom = 0
|
|
CASE LastIn = '' ; InCleanRoom = 0
|
|
CASE LastOut = '' ; InCleanRoom = 1
|
|
CASE LastOut > LastIn ; InCleanRoom = 0
|
|
CASE LastIn > LastOut ; InCleanRoom = 1
|
|
END CASE
|
|
|
|
IF WMIKey NE '' THEN
|
|
WMIStatus = WOMatRec<WO_MAT_WMI_CURR_STATUS$>
|
|
END ELSE
|
|
WMIStatus = ''
|
|
END
|
|
|
|
|
|
IF WMOKey NE '' THEN
|
|
WMOStatus = WOMatRec<WO_MAT_WMO_CURR_STATUS$>
|
|
IF WMOStatus = 'COMP' AND NOT(InCleanRoom) THEN
|
|
WMOStatus = 'RTS'
|
|
END
|
|
|
|
IF CurrLoc = 'CR*PKO' THEN
|
|
WMOStatus = 'PKO'
|
|
END
|
|
|
|
|
|
WMOMakeup = XLATE('WM_OUT',WMOKey,'MAKEUP_BOX','X')
|
|
END ELSE
|
|
WMOStatus = ''
|
|
END
|
|
|
|
IF WMIKey NE '' OR WMOKey NE '' THEN
|
|
InboundStat = ''
|
|
OutboundStat = ''
|
|
|
|
IF WOMatRec<WO_MAT_HOLD$> = 1 THEN
|
|
IF WOMatRec<WO_MAT_HOLD_ENTITY$,1> = 'WM_IN' THEN
|
|
InboundStat = 'HOLD'
|
|
END
|
|
|
|
IF WOMatRec<WO_MAT_HOLD_ENTITY$,1> = 'WM_OUT' THEN
|
|
OutBoundStat = 'HOLD'
|
|
END
|
|
|
|
BEGIN CASE
|
|
CASE InboundStat = '' AND OutboundStat = ''
|
|
Result = ''
|
|
|
|
CASE InboundStat = '' AND OutboundStat NE ''
|
|
Result = WMOStatus
|
|
|
|
CASE InboundStat NE '' AND OutboundStat = ''
|
|
Result = InboundStat
|
|
|
|
CASE InboundStat NE '' AND OutboundStat NE ''
|
|
Result = InboundStat:@VM:WMOStatus
|
|
Result = Result:WMOStatus
|
|
END CASE
|
|
|
|
RETURN
|
|
END
|
|
|
|
IF WMIKey NE '' THEN
|
|
IF WMIStatus = 'MT' OR WMIStatus = 'VOID' THEN
|
|
NULL
|
|
END ELSE
|
|
InboundStat = WMIStatus
|
|
END
|
|
END
|
|
|
|
IF WMOKey NE '' THEN
|
|
IF WMOStatus = 'RTB' OR ( WMOMakeup = 1 AND WMOStatus = 'MT' ) OR WMOStatus = 'VOID' THEN
|
|
NULL
|
|
END ELSE
|
|
OutboundStat = WMOStatus
|
|
END
|
|
END
|
|
|
|
BEGIN CASE
|
|
CASE InboundStat = '' AND OutboundStat = ''
|
|
Result = ''
|
|
|
|
CASE InboundStat = '' AND OutboundStat NE ''
|
|
Result = WMOStatus
|
|
|
|
CASE InboundStat NE '' AND OutboundStat = ''
|
|
Result = InboundStat
|
|
|
|
CASE InboundStat NE '' AND OutboundStat NE ''
|
|
Result = InboundStat:@VM
|
|
Result = Result:WMOStatus
|
|
|
|
END CASE
|
|
|
|
RETURN
|
|
END
|
|
|
|
LastStepSig = WOMatRec<WO_MAT_SIGNATURE$>[-1,'B':@VM]
|
|
Canceled = WOMatRec<WO_MAT_CANCELLED$>
|
|
SubSupplyBy = WOMatRec<WO_MAT_SUB_SUPPL_BY$>
|
|
RetRejects = WOMatRec<WO_MAT_RET_REJECTS$>
|
|
MakeupBox = WOMatRec<WO_MAT_MAKEUP_BOX$>
|
|
CurrWfrCnt = XLATE('WO_MAT',WOMatKey,'CURR_WFR_CNT','X')
|
|
NCRNos = WOMatRec<WO_MAT_NCR_KEYS$>
|
|
NCRFinalSigs = WOMatRec<WO_MAT_NCR_FINAL_SIG$>
|
|
|
|
NCRNoCnt = COUNT(NCRNos,@VM) + (NCRNos NE '')
|
|
NCRSigCnt = COUNT(NCRFinalSigs,@VM) + (NCRFinalSigs NE '')
|
|
|
|
SigProfs = WOMatRec<WO_MAT_SIG_PROFILE$>
|
|
Signatures = WOMatRec<WO_MAT_SIGNATURE$>
|
|
|
|
ProcessStart = 0
|
|
ProcessComp = 0
|
|
|
|
LOOP
|
|
Signature = Signatures<1,1>
|
|
SigProf = SigProfs<1,1>
|
|
UNTIL Signature = ''
|
|
ProcessStart = 1
|
|
Signatures = DELETE(Signatures,1,1,0)
|
|
SigProfs = DELETE(SigProfs,1,1,0)
|
|
REPEAT
|
|
|
|
IF Signature = '' AND SigProf = '' THEN ProcessComp = 1
|
|
|
|
IF NUM(SigProf[1,1]) THEN SigProf[1,1] = ''
|
|
|
|
|
|
BEGIN CASE
|
|
|
|
CASE WOMatRec<WO_MAT_SHIP_NO$> NE '' ; Result = 'SHIP'
|
|
|
|
CASE Canceled = 1 AND SubSupplyBy NE 'C' ; Result = 'CANC'
|
|
CASE Canceled = 1 AND SubSupplyBy = 'C' AND InCleanRoom ; Result = 'COMP'
|
|
CASE Canceled = 1 AND SubSupplyBy = 'C' AND NOT(InCleanRoom) ; Result = 'RTS'
|
|
|
|
CASE WOMatRec<WO_MAT_HOLD$> = 1 ; Result = 'HOLD'
|
|
CASE NCRNoCnt > 0 AND NCRNoCnt NE NCRSigCnt ; Result = 'NCR'
|
|
|
|
CASE MakeupBox AND ProcessComp AND CurrWfrCnt > 0 ; Result = 'RTU'
|
|
CASE MakeupBox AND ProcessComp AND CurrWfrCnt = 0 ; Result = 'MT'
|
|
|
|
CASE NCRNoCnt > 0 AND CurrWfrCnt = 0 AND NOT(RetRejects) ; Result = 'REJ'
|
|
CASE NCRNoCnt > 0 AND CurrWfrCnt = 0 AND RetRejects ; Result = 'RTS'
|
|
|
|
CASE CurrWfrCnt = 0 ; Result = 'MT' ;* Added 8/14/2008 JCH - Used for Prod Test Wafers
|
|
|
|
CASE ProcessComp AND NOT(InCleanRoom) ; Result = 'RTS'
|
|
CASE ProcessComp AND CurrLoc = 'CR*PKO' ; Result = 'PKO'
|
|
CASE ProcessComp AND InCleanroom ; Result = 'COMP'
|
|
|
|
CASE WOMatRec<WO_MAT_REL_DTM$> NE '' AND SigProf NE '' ; Result = SigProf
|
|
CASE WOMatRec<WO_MAT_REL_DTM$> NE '' AND NOT(InCleanRoom) ; Result = 'REL'
|
|
CASE WOMatRec<WO_MAT_RX_DTM$> NE '' ; Result = 'RX'
|
|
CASE SubSupplyBy = 'L' ; Result = 'RTP'
|
|
|
|
CASE 1 ; Result = 'AWM'
|
|
|
|
END CASE
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
AddShip:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
ShipNo = Parms[COL2()+1,@RM]
|
|
Reship = Parms[COL2()+1,@RM]
|
|
|
|
If Reship EQ '' then
|
|
Reship = False$
|
|
end
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN ErrorMsg = 'Unassigned Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF NOT(ASSIGNED(ShipNo)) THEN ErrorMsg = 'Unassigned Parm "ShipNo" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF ShipNo = '' THEN ErrorMsg = 'Null Parm "ShipNo" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
|
|
|
|
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
|
|
|
|
IF WOMatRec<WO_MAT_SHIP_NO$> = '' or Reship EQ True$ THEN
|
|
WOMatRec<WO_MAT_SHIP_NO$> = ShipNo
|
|
END ELSE
|
|
END
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
// Update work order SHIP_QTY_STATIC
|
|
WONo = Field(WOMatKey, '*', 1)
|
|
Work_Order_Services('UpdateShippedQty', WONo)
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
RemShip:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
ShipNo = Parms[COL2()+1,@RM]
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN ErrorMsg = 'Unassigned Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF NOT(ASSIGNED(ShipNo)) THEN ErrorMsg = 'Unassigned Parm "ShipNo" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF ShipNo = '' THEN ErrorMsg = 'Null Parm "ShipNo" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
|
|
|
|
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
|
|
|
|
IF WOMatRec<WO_MAT_SHIP_NO$> = ShipNo OR WOMatRec<WO_MAT_SHIP_NO$> = '' THEN
|
|
WOMatRec<WO_MAT_SHIP_NO$> = ''
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
END ELSE
|
|
obj_Tables('UnlockRec',otParms)
|
|
ErrorMsg = "Passed Ship No " :QUOTE(ShipNo): " doesn't match Ship No on WO_MAT record " :QUOTE(WOMatKey): ". (" :Method: ")"
|
|
END
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
AddReship:
|
|
* * * * * * *
|
|
|
|
* Adds data entered in the WO_MAT_RESHIP window to WO_MAT record. Data entered allows new shipping labels to be printed prior to
|
|
* setting up a new delivery in SAP. The RESHIP_NO is added in the AddShip method when the delivery data is received from SAP.
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
ReshipDt = Parms[COL2()+1,@RM]
|
|
ReshipReason = Parms[COL2()+1,@RM]
|
|
ReshipCustNo = Parms[COL2()+1,@RM]
|
|
ReshipCustPartNo = Parms[COL2()+1,@RM]
|
|
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF ReshipDt = '' THEN ErrorMsg = 'Null Parm "ReshipDt" passed to routine. (':Method:')'
|
|
IF ReshipReason = '' THEN ErrorMsg = 'Null Parm "ReshipReason" passed to routine. (':Method:')'
|
|
IF ReshipCustNo = '' THEN ErrorMsg = 'Null Parm "ReshipCustNo" passed to routine. (':Method:')'
|
|
IF ReshipCustPartNo = '' THEN ErrorMsg = 'Null Parm "ReshipCustPartNo" passed to routine. (':Method:')'
|
|
|
|
|
|
IF ErrorMsg = '' THEN RETURN
|
|
|
|
thisReshipDt = ICONV(ReshipDt,'D')
|
|
|
|
IF thisReshipDt = '' THEN
|
|
ErrorMsg = 'Invalid Data ':QUOTE(ReshipDt):' for Parm "ReshipDt" passed to routine. (':Method:')'
|
|
RETURN
|
|
END
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
|
|
|
|
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
|
|
|
|
WOMatRec<WO_MAT_RESHIP_DT$> = thisReshipDt
|
|
WOMatRec<WO_MAT_RESHIP_REASON$> = ReshipReason
|
|
WOMatRec<WO_MAT_RESHIP_CUST_NO$> = ReshipCustNo
|
|
WOMatRec<WO_MAT_RESHIP_CUST_PART_NO$> = ReshipCustPartNo
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
RETURN
|
|
|
|
* * * * * *
|
|
SetPartNo:
|
|
* * * * * *
|
|
|
|
WOMatKeys = Parms[1,@RM]
|
|
NewPartNo = Parms[COL2()+1,@RM]
|
|
|
|
IF NOT(ASSIGNED(WOMatKeys)) THEN ErrorMsg = 'Unassigned Parm "WOMatKeys" passed to routine. (':Method:')'
|
|
IF NOT(ASSIGNED(NewPartNo)) THEN ErrorMsg = 'Unassigned Parm "NewPartNo" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
IF WOMatKeys = '' THEN ErrorMsg = 'Null Parm "WOMatKeys" passed to routine. (':Method:')'
|
|
IF NewPartNo = '' THEN ErrorMsg = 'Null Parm "NewPartNo" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKeys
|
|
WOMatTableVar = obj_Tables('LockSet',otParms) ;* Locks all WO_Mat records to be updated
|
|
|
|
IF Get_Status(errCode) THEN RETURN ;* Problems getting the locks
|
|
|
|
WOMatCnt = COUNT(WOMatKeys,@VM) + (WOMatKeys NE '')
|
|
|
|
AllRDSNos = ''
|
|
|
|
FOR I = 1 TO WOMatCnt
|
|
WOMatKey = WOMatKeys<1,I>
|
|
READV RDSNos FROM WOMatTableVar,WOMatKey,WO_MAT_RDS_NO$ THEN
|
|
|
|
AllRDSNos := RDSNos:@VM
|
|
END
|
|
NEXT I
|
|
|
|
AllCnt = COUNT(AllRDSNos,@VM) + (AllRDSNos NE '')
|
|
|
|
ActiveRDSNos = ''
|
|
FOR I = 1 TO AllCnt
|
|
IF AllRDSNos<1,I> NE '' THEN
|
|
ActiveRDSNos<1,-1> = AllRDSNos <1,I>
|
|
END
|
|
NEXT I
|
|
|
|
IF ActiveRDSNos NE '' THEN
|
|
rtParms = 'RDS':@RM:ActiveRdsNos
|
|
|
|
RDSTableVar = obj_Tables('LockSet',rtParms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
obj_Tables('UnlockSet','WO_MAT':@RM:WOMatKeys:@RM:WOMatTableVar) ;* Unlock WO_MAT records
|
|
RETURN
|
|
END
|
|
|
|
obj_RDS('SetPartNo',AllRDSNos:@RM:NewPartNo:@RM:RDSTableVar) ;* Updates & unlocks RDS records
|
|
|
|
END ;* End of check for RDSNos
|
|
|
|
FOR I = 1 TO WOMatCnt
|
|
WOMatKey = WOMatKeys<1,I>
|
|
READ WOMatRec FROM WOMatTableVar,WOMatKey THEN
|
|
WOMatRec<WO_MAT_CUST_PART_NO$> = NewPartNo
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKey:@RM:WOMatTableVar:@RM:WOMatRec
|
|
obj_Tables('WriteRec',otParms) ;* Writes and unlocks WOMat record
|
|
|
|
Send_Info('WO_MAT record: ':WOMatKey:' updated. ':I:'/':WOMatCnt)
|
|
END
|
|
NEXT I
|
|
|
|
Send_Info(' ')
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
RefreshSigProfile:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN ErrorMsg = 'Unassigned Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null Parm "WOMatKey" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadOnlyRec',otParms) ;* Reads and sets lock
|
|
|
|
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
|
|
|
|
GOSUB CassSigProfile ;* Local method returns CassSigProfile from Spec
|
|
|
|
SpecSigProfile = Result
|
|
SpecSignatures = ''
|
|
SpecDTMs = ''
|
|
SpecVers = ''
|
|
|
|
Result = '' ;* Clear result variable
|
|
|
|
NewSignatures = ''
|
|
NewSigDTMs = ''
|
|
|
|
SigProfile = WOMatRec<WO_MAT_SIG_PROFILE$>
|
|
Signatures = WOMatRec<WO_MAT_SIGNATURE$>
|
|
SigDTMS = WOMatRec<WO_MAT_SIG_DTM$>
|
|
SigVers = WOMatRec<WO_MAT_SIG_VER$>
|
|
|
|
IF SigProfile = SpecSigProfile THEN
|
|
obj_Tables('UnlockRec',otParms)
|
|
RETURN ;* Nothing to do here
|
|
END
|
|
|
|
SpecCnt = COUNT(SpecSigProfile,@VM) + (SpecSigProfile NE '')
|
|
|
|
FOR I = 1 TO SpecCnt
|
|
SpecProfItem = SpecSigProfile<1,I>
|
|
|
|
* Look for new PItem in Existing Profile
|
|
|
|
LOCATE SpecProfItem IN SigProfile USING @VM SETTING Pos THEN
|
|
SpecSignatures<1,I> = Signatures<1,Pos>
|
|
SpecDTMs<1,I> = SigDTMs<1,Pos>
|
|
SpecVers<1,I> = SigVers<1,Pos>
|
|
|
|
SigProfile = DELETE(SigProfile,1,Pos,0) ;* Pulls lines from existing -> deleted sigs left
|
|
Signatures = DELETE(Signatures,1,Pos,0) ;* at end of loop - SAVE for possible reporting JCH 1/31/2013
|
|
SigDTMs = DELETE(SigDTMs,1,Pos,0) ;*
|
|
SigVers = DELETE(SigVers,1,Pos,0) ;*
|
|
|
|
END ELSE
|
|
* Check for FWI or LWI newer profile being stored as old 'WFR'
|
|
IF SpecProfItem[2,3] = 'FWI' OR SpecProfItem[2,3] = 'LWI' THEN
|
|
|
|
WfrString = SpecProfItem[2,3] ;* LWI or FWI
|
|
SWAP WfrString WITH 'WFR' IN SpecProfItem ;* Update WfrString
|
|
|
|
LOCATE SpecProfItem IN SigProfile USING @VM SETTING Pos THEN
|
|
SpecSignatures<1,I> = Signatures<1,Pos>
|
|
SpecDTMs<1,I> = SigDTMs<1,Pos>
|
|
SpecVers<1,I> = SigVers<1,Pos>
|
|
END
|
|
END ELSE
|
|
* New item in Spec Sig -> won't be signed
|
|
END
|
|
END
|
|
NEXT I
|
|
|
|
WOMatRec<WO_MAT_SIG_PROFILE$> = SpecSigProfile
|
|
WOMatRec<WO_MAT_SIGNATURE$> = SpecSignatures
|
|
WOMatRec<WO_MAT_SIG_DTM$> = SpecDTMs
|
|
WOMatRec<WO_MAT_SIG_VER$> = SpecVers
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteOnlyRec',otParms)
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
SetWfrQty:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WfrQty = Parms[COL2()+1,@RM]
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN ErrorMsg = 'Unassigned Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF NOT(ASSIGNED(WfrQty)) THEN ErrorMsg = 'Unassigned Parm "WfrQty" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF WfrQty = '' THEN ErrorMsg = 'Null Parm "WfrQty" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms) ;* Reads and sets lock
|
|
|
|
IF Get_Status(errCode) THEN RETURN ;* Problems getting the lock
|
|
|
|
CurrWfrQty = WOMatRec<WO_MAT_WAFER_QTY$>
|
|
CurrSlots = WOMatRec<WO_MAT_SLOT_NO$>
|
|
|
|
ReactorType = Xlate('WO_MAT', WOMatKey, 'REACTOR_TYPE', 'X')
|
|
EpiPro = ( (ReactorType EQ 'EPP') or (ReactorType EQ 'EpiPro') )
|
|
|
|
BEGIN CASE
|
|
|
|
CASE WfrQty > CurrWfrQty
|
|
// Adding wafers
|
|
WOMatRec<WO_MAT_WAFER_QTY$> = WfrQty ;* Update Wafer Qty
|
|
FOR I = 1 TO WfrQty
|
|
WOMatRec<WO_MAT_SLOT_NO$,I> = I ;* Add new slots
|
|
NEXT I
|
|
|
|
CASE WfrQty = CurrWfrQty
|
|
// No quantity change
|
|
FOR I = 1 TO WfrQty
|
|
WOMatRec<WO_MAT_SLOT_NO$,I> = I ;* Refresh slot numbers in slot values
|
|
NEXT I
|
|
|
|
CASE WfrQty < CurrWfrQty
|
|
|
|
// Removing wafers
|
|
EligibleWfrList = ''
|
|
|
|
FOR I = 1 TO CurrWfrQty
|
|
NCRNo = WOMatRec<WO_MAT_SLOT_NCR$,I>
|
|
MetNo = WOMatRec<WO_MAT_SLOT_MET_NO$,I>
|
|
MovedTo = WOMatRec<WO_MAT_SLOT_MOVED_TO$,I>
|
|
ReplacedBy = WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,I>
|
|
|
|
IF NCRNo = '' AND MetNo = '' AND MovedTo = '' AND ReplacedBy = '' then EligibleWfrList<-1> = I
|
|
NEXT I
|
|
|
|
NumEligibleWfrs = DCount(EligibleWfrList, @FM)
|
|
|
|
DiffQty = CurrWfrQty - WfrQty
|
|
|
|
If NumEligibleWfrs GE DiffQty then
|
|
// We have enough wafers, so remove enough to make cassette quantity equal the desired quantity
|
|
|
|
Loop
|
|
Until CurrWfrQty EQ WfrQty
|
|
BottomIndex = EligibleWfrList<NumEligibleWfrs>
|
|
WfrToRemove = BottomIndex
|
|
WOMatRec<WO_MAT_SLOT_NO$, WfrToRemove> = ''
|
|
CurrWfrQty -= 1
|
|
NumEligibleWfrs -= 1
|
|
Repeat
|
|
WOMatRec<WO_MAT_WAFER_QTY$> = WfrQty ;* Update Wafer Qty
|
|
end else
|
|
ErrorMsg = 'This cassette cannot be reduced to ':WfrQty:' wafers because only ':NumEligibleWfrs:' are eligible to be removed. '
|
|
end
|
|
|
|
END CASE
|
|
|
|
If ErrorMsg EQ '' then
|
|
If EpiPro then
|
|
WMIKey = WOMatRec<WO_MAT_WMI_KEY$>
|
|
If WMIKey NE '' then
|
|
WMIRec = Database_Services('ReadDataRow', 'WM_IN', WMIKey)
|
|
If Error_Services('NoError') then
|
|
WMIRec<WM_IN_SLOT_NO$> = WOMatRec<WO_MAT_SLOT_NO$>
|
|
Database_Services('WriteDataRow', 'WM_IN', WMIKey, WMIRec, True$, False$, True$)
|
|
end
|
|
end
|
|
end
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteRec',otParms) ; // This will release the lock
|
|
Result = CurrWfrQty
|
|
end else
|
|
RecordLocked = Database_Services('IsKeyIDLocked', 'WO_MAT', WOMatKey, False$)
|
|
If RecordLocked then Database_Services('ReleaseKeyIDLock', 'WO_MAT', WOMatKey)
|
|
end
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
UpdateSpec:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN WOMatKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(WOMatRec)) THEN WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
IF WONo < 128680 THEN RETURN ;* This is the first WO No on 7/29/2005 - The day we cut over to the new system.
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
GOSUB CurrStatus
|
|
|
|
CurrStatus = Result[-1,'B':@VM]
|
|
|
|
Result = ''
|
|
|
|
IF CurrStatus = 'PKO' THEN RETURN
|
|
IF CurrStatus = 'BLD' THEN RETURN
|
|
IF CurrStatus = '' THEN RETURN
|
|
IF CurrStatus = 'MT' THEN RETURN
|
|
IF CurrStatus = 'RTU' THEN RETURN
|
|
IF CurrStatus = 'REJ' THEN RETURN
|
|
IF WOMatRec<WO_MAT_VOID$> NE '' THEN RETURN
|
|
IF WOMatRec<WO_MAT_SHIP_NO$> NE '' THEN RETURN
|
|
IF WOMatRec<WO_MAT_CANCELLED$> NE '' THEN RETURN
|
|
IF WOMatRec<WO_MAT_SIG_PROFILE$> = '' THEN RETURN
|
|
|
|
LastSigPos = COUNT(WOMatRec<WO_MAT_SIG_PROFILE$>,@VM) + (WOMatRec<WO_MAT_SIG_PROFILE$> NE '')
|
|
|
|
|
|
IF WOMatRec<WO_MAT_SIGNATURE$,LastSigPos> = '' THEN
|
|
Result = 1
|
|
END ELSE
|
|
Result = ''
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
PartNo:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN WOMatKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(WOMatRec)) THEN WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
OrdNo = XLATE('WO_LOG',WONo,WO_LOG_ORDER_NO$,'X')
|
|
OrdDetKey = OrdNo:'*':WOMatRec<WO_MAT_ORDER_ITEM$>
|
|
|
|
OrdDetRec = XLATE('ORDER_DET',OrdDetKey,'','X')
|
|
|
|
CustPN = OrdDetRec<ORDER_DET_CUST_PN$>
|
|
SubPN = OrdDetRec<ORDER_DET_SUB_PART_NO$>
|
|
|
|
Supplier = SubPN[-1,'B-']
|
|
IF Supplier[1,1] = 'I' AND LEN(Supplier) = 2 ELSE Supplier = ''
|
|
|
|
ProcStepPSNs = XLATE('ORDER_DET',OrdDetKey,'QUOTE_PROC_STEP_PSN','X')
|
|
|
|
PsnID = ProcStepPSNs
|
|
CONVERT @VM TO '.' IN PsnID
|
|
|
|
PartWorkKey = CustPN:'*':SubPN:'*':PsnID:'*':Supplier ;* Determines a unique part number
|
|
|
|
IF PartWorkKey NE '****' THEN
|
|
Result = XLATE('PART_WORK',PartWorkKey,1,'X') ;* Finally, get the new part number
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
FinalSigComp:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(WOMatKey)) THEN WOMatKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(WOMatRec)) THEN WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
SigProfCnt = COUNT(WOMatRec<WO_MAT_SIG_PROFILE$>,@VM) + (WOMatRec<WO_MAT_SIG_PROFILE$> NE '')
|
|
|
|
IF WOMatRec<WO_MAT_SIGNATURE$,SigProfCnt> = '' THEN
|
|
Result = 0
|
|
END ELSE
|
|
Result = 1
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
SetSAPBatch:
|
|
* * * * * * *
|
|
|
|
FileIn = Parms[1,@RM]
|
|
|
|
CassID = FileIn<1,1>
|
|
SAPBatchNo = FileIn<1,2>
|
|
ErrFields = ''
|
|
ErrValues = ''
|
|
ErrDescs = ''
|
|
ErrCnt = 0
|
|
|
|
IF CassID = '' THEN
|
|
ErrCnt += 1
|
|
ErrFields<1,ErrCnt> = 'CASS_ID'
|
|
ErrDescs<1,ErrCnt> = 'Null Value'
|
|
ErrValues<1,ErrCnt> = '<null>'
|
|
END
|
|
|
|
IF SAPBatchNo = '' THEN
|
|
ErrCnt += 1
|
|
ErrFields<1,ErrCnt> = 'SAP_BATCH_NO'
|
|
ErrDescs<1,ErrCnt> = 'Null Value'
|
|
ErrValues<1,ErrCnt> = '<null>'
|
|
END
|
|
|
|
CONVERT '.' TO '*' IN CassID
|
|
|
|
IF NUM(CassID) THEN
|
|
|
|
* RDS
|
|
|
|
IF RowExists('REACT_RUN',CassID) THEN
|
|
|
|
ReactRunRec = XLATE('REACT_RUN',CassID,'','X')
|
|
|
|
WONo = ReactRunRec<REACT_RUN_WO_NO$>
|
|
CassNo = ReactRunRec<REACT_RUN_CASS_NO$>
|
|
END ELSE
|
|
ErrCnt += 1
|
|
ErrFields<1,ErrCnt> = 'RDS No'
|
|
ErrDescs<1,ErrCnt> = 'React Run record not on file.'
|
|
ErrValues<1,ErrCnt> = CassID
|
|
|
|
WONo = ''
|
|
CassNo = ''
|
|
|
|
END
|
|
|
|
END ELSE
|
|
|
|
* WM_OUT
|
|
|
|
WONo = CassID[1,'*']
|
|
CassNo = CassID[-1,'B*']
|
|
END
|
|
|
|
|
|
OPEN 'DICT.WO_MAT' TO SAPDictVar ELSE
|
|
RETURN
|
|
END
|
|
|
|
SearchString = 'SAP_BATCH_NO':@VM:SAPBatchNo:@FM
|
|
ExistingWOMatKey = ''
|
|
Option = ''
|
|
Flag = ''
|
|
|
|
Btree.Extract(SearchString,'WO_MAT',SAPDictVar,ExistingWOMatKey,Option,Flag)
|
|
|
|
IF Get_Status(errCode) THEN RETURN
|
|
|
|
IF ExistingWOMatKey NE '' THEN
|
|
ErrCnt += 1
|
|
ErrFields<1,ErrCnt> = 'SAP_BATCH_NO'
|
|
ErrDescs<1,ErrCnt> = QUOTE(SAPBatchNo):' already exists in WOMat record ':QUOTE(ExistingWOMatKey)
|
|
ErrValues<1,ErrCnt> = SAPBatchNo
|
|
|
|
END
|
|
|
|
IF WONo = '' THEN
|
|
ErrCnt += 1
|
|
ErrFields<1,ErrCnt> = 'WO_MAT'
|
|
ErrDescs<1,ErrCnt> = 'Null WONo'
|
|
ErrValues<1,ErrCnt> = ''
|
|
END
|
|
|
|
IF CassNo = '' THEN
|
|
ErrCnt += 1
|
|
ErrFields<1,ErrCnt> = 'WO_MAT'
|
|
ErrDescs<1,ErrCnt> = 'Null CassNo'
|
|
ErrValues<1,ErrCnt> = ''
|
|
END
|
|
|
|
IF WONo NE '' AND CassNo NE '' THEN
|
|
|
|
IF RowExists('WO_LOG',WONo) THEN
|
|
IF RowExists('WO_MAT',WONo:'*':CassNo) Then
|
|
CurrBatchNo = Xlate('WO_MAT',WONo:'*':CassNo,WO_MAT_SAP_BATCH_NO$,'X')
|
|
If CurrBatchNo NE '' And CurrBatchNo NE SAPBatchNo Then
|
|
If CurrBatchNo NE 0 then
|
|
ErrCnt += 1
|
|
ErrFields<1,ErrCnt> = 'SAP_BATCH_NO'
|
|
ErrDescs<1,ErrCnt> = QUOTE(WONo:'*':CassNo):' already has SAP Batch No ':QUOTE(CurrBatchNo)
|
|
ErrValues<1,ErrCnt> = SAPBatchNo
|
|
END
|
|
end
|
|
End ELSE
|
|
ErrCnt += 1
|
|
ErrFields<1,ErrCnt> = 'WO_MAT_KEY'
|
|
ErrDescs<1,ErrCnt> = 'WOMat record not on file.'
|
|
ErrValues<1,ErrCnt> = WONo:'*':CassNo
|
|
END
|
|
END ELSE
|
|
ErrCnt += 1
|
|
ErrFields<1,ErrCnt> = 'WO_NO'
|
|
ErrDescs<1,ErrCnt> = 'WO Log record not on file.'
|
|
ErrValues<1,ErrCnt> = WONo
|
|
END
|
|
END
|
|
|
|
IF ErrFields NE '' THEN
|
|
LogNo = NextKey('SAP_LOG')
|
|
LogRec = ''
|
|
LogRec<SAP_LOG_TIMESTAMP$> = ICONV(OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS'),'DT')
|
|
LogRec<SAP_LOG_LOG_DESC$> = 'Batch ID error from SAP'
|
|
LogRec<SAP_LOG_PROD_ORD_NO$> = WONo:'*':CassNo
|
|
LogRec<SAP_LOG_FIELD_NAME$> = ErrFields
|
|
LogRec<SAP_LOG_ERR_DESC$> = ErrDescs
|
|
LogRec<SAP_LOG_SAP_VALUE$> = ErrValues
|
|
|
|
logParms = 'SAP_LOG':@RM:LogNo:@RM:@RM:LogRec
|
|
obj_Tables('WriteRec',logParms)
|
|
|
|
|
|
Message = 'Batch ID error from SAP':CRLF$:CRLF$
|
|
fCnt = Count(ErrFields,@VM) + (ErrFields NE '')
|
|
For N = 1 To fCnt
|
|
Message := FMT(ErrFields<1,N>, "L#20")' ':FMT(ErrValues<1,N>, "L#20"):' ':ErrDescs<1,N>:CRLF$
|
|
Next I
|
|
|
|
Recipients = Xlate('SEC_GROUPS', 'SAP_ADMIN', 'USER', 'X')
|
|
SentFrom = "SAP Posting Process"
|
|
Subject = 'SAP Error Logged ':LogNo
|
|
AttachWindow = 'SAP_LOG'
|
|
AttachKey = LogNo
|
|
SendToGroup = ''
|
|
|
|
Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup
|
|
obj_Notes('Create',Parms)
|
|
|
|
Result = 1
|
|
|
|
RETURN
|
|
|
|
END ELSE
|
|
|
|
oblParms = 'WO_MAT':@RM
|
|
oblParms := WONo:'*':CassNo:@RM
|
|
oblParms := WO_MAT_SAP_BATCH_NO$:@RM
|
|
oblParms := SAPBatchNo
|
|
|
|
// Log this event
|
|
LogData = ''
|
|
LogData<1> = LoggingDTM
|
|
LogData<2> = WONo:'*':CassNo
|
|
LogData<3> = SAPBatchNo
|
|
Logging_Services('AppendLog', objSAPLog, LogData, @RM, @FM)
|
|
|
|
obj_Post_Log('Create',oblParms)
|
|
|
|
UnReleasedQty = Xlate('WO_LOG',WONo,'UNREL_QTY','X') ;* 10/8/2014 DKK & JCH
|
|
|
|
IF UnReleasedQty = 0 THEN
|
|
|
|
AllCassIDs = XLATE('WO_LOG',WONo,WO_LOG_WO_MAT_KEY$,'X')
|
|
AllCassBatchNos = XLATE('WO_MAT',AllCassIDs,WO_MAT_SAP_BATCH_NO$,'X')
|
|
|
|
AllCassCnt = COUNT(AllCassIDs,@VM) + (AllCassIDs NE '')
|
|
OpenCassIDs = ''
|
|
|
|
FOR N = 1 TO AllCassCnt
|
|
IF AllCassBatchNos<1,N> = '' THEN
|
|
OpenCassIDs<-1> = AllCassIDs<1,N>
|
|
END
|
|
UNTIL INDEX(OpenCassIDs,@FM,1)
|
|
NEXT N
|
|
|
|
IF INDEX(OpenCassIDs,@FM,1) THEN
|
|
* More than 1 box still open
|
|
NULL
|
|
END ELSE
|
|
IF OpenCassIDs = WONo:'*':CassNo OR OpenCassIDs<1,1> = WONo:'*':(CassNo + 1) OR OpenCassIds = '' THEN
|
|
|
|
* All Done with work order
|
|
|
|
CurrDTM = ICONV(obj_Calendar('CurrDTM'),'DT')
|
|
CurrDt = Date()
|
|
|
|
WOLogFields = WO_LOG_WO_STOP_DTM$:@VM:WO_LOG_CLOSE_DATE$ ;* Stop data added
|
|
WOLogVals = CurrDTM:@VM:CurrDt
|
|
|
|
WOQty = XLATE('WO_LOG',WONo,'WO_QTY','X')
|
|
SAPConfirmScrapQty = XLATE('WO_LOG',WONo,'SAP_CONFIRM_SCRAP_QTY','X')
|
|
SAPYieldQty = XLATE('WO_LOG',WONo,'SAP_YIELD_QTY','X')
|
|
|
|
IF (SAPConfirmScrapQty + SAPYieldQty) = WOQty THEN
|
|
|
|
WOLogFields = WO_LOG_WO_STOP_DTM$:@VM:WO_LOG_CLOSE_DATE$ ;* Stop data added
|
|
WOLogVals = CurrDTM:@VM:CurrDt
|
|
|
|
|
|
obj_Post_Log('Create','WO_LOG':@RM:WONo:@RM:WOLogFields:@RM:WOLogVals) ;* Add values to WO_LOG record
|
|
|
|
* * * * * * Added check for EpiPRO Last inbound box w/o and outbound box and then check for PROD_TEST_WAFERS **** * * * * * * * * * * * * * * * * * * *
|
|
|
|
WORec = XLATE('WO_LOG',WONo,'','X')
|
|
|
|
WOMatKeys = WORec<WO_LOG_WO_MAT_KEY$>
|
|
|
|
WMIKeys = XLATE('WO_MAT',WOMatKeys,WO_MAT_WMI_KEY$,'X')
|
|
WMOKeys = XLATE('WO_MAT',WOMatKeys,WO_MAT_WMO_KEY$,'X')
|
|
|
|
LOOP
|
|
WMOKey = WMOKeys[-1,'B':@VM]
|
|
UNTIL WMOKey NE '' OR WMOKeys = ''
|
|
WMOKeys[COL1(),99] = ''
|
|
REPEAT
|
|
|
|
InCnt = COUNT(WMIKeys,@VM) + (WMIKeys NE '')
|
|
OutCnt = COUNT(WMOKeys,@VM) + (WMOKeys NE '')
|
|
|
|
IF InCnt > OutCnt THEN
|
|
InOnlyKeys = FIELD(WMIKeys,@VM,OutCnt+1,4)
|
|
InProdTest = SUM(XLATE('WM_IN',InOnlyKeys,'TW_PROD','X'))
|
|
|
|
IF InProdTest > 0 THEN
|
|
InWMIKey = InOnlyKeys<1,1>
|
|
InCassNo = FIELD(InWMIKey,'*',3,1) ;* Cassette is the last part of the key
|
|
|
|
WOMatRec = XLATE('WO_MAT',WONo:'*':InCassNo,'','X')
|
|
SupplierLotNo = WOMatRec<WO_MAT_LOT_NO$>
|
|
ProdOrdNo = WORec<WO_LOG_PROD_ORD_NO$>
|
|
|
|
ProdVerRec = XLATE('PROD_VER',WOMatRec<WO_MAT_PROD_VER_NO$>,'','X')
|
|
CustNo = ProdVerRec<PROD_VER_CUST_NO$>
|
|
VendCd = XLATE('COMPANY',CustNo,COMPANY_VEND_CD$,'X')
|
|
SubPartNo = ProdVerRec<PROD_VER_SUB_PART_NO$>
|
|
CustPartRev = ProdVerRec<PROD_VER_CUST_PART_REV$>
|
|
CassID = WONo:'.':InCassNo
|
|
|
|
|
|
IF VendCd NE '' THEN
|
|
SubSuppCd = VendCd
|
|
END ELSE
|
|
IF SubPartNo MATCHES "6N'-'1A'-'2A" THEN
|
|
SubSuppCd = FIELD(SubPartNo,'-',3)
|
|
END ELSE
|
|
SubSuppCd = WOMatRec<WO_MAT_SUB_VEND_CD$>
|
|
SubSuppCd = XLATE('SEMI_VEND_CODE',SubSuppCd,SEMI_VEND_CODE_EPI_VEND_CD$,'X')
|
|
END
|
|
END
|
|
|
|
If ReactorType NE 'GAN' then
|
|
GRProps = obj_WO_Mat('GetGRProps',WONo:'*':InCassNo:@RM)
|
|
end else
|
|
GRProps = GaN_Services('GetGaNGRProps', WONo:'*':InCassNo)
|
|
end
|
|
|
|
GRWfrQty = GRProps[1,@FM]
|
|
ScrapQty = GRProps[COL2()+1,@FM]
|
|
ProdTWQty = GRProps[COL2()+1,@FM]
|
|
AvailMUWfrQty = GRProps[COL2()+1,@FM]
|
|
MUCassIDs = GRProps[COL2()+1,@FM]
|
|
MUCassQtys = GRProps[COL2()+1,@FM]
|
|
|
|
MakeupFlag = 0
|
|
MUCassID = FIELD(MUCassIDs,@VM,1)
|
|
MUCassQty = FIELD(MUCassQtys,@VM,1)
|
|
MUBatchNo = XLATE('WO_MAT',MUCassID,WO_MAT_SAP_BATCH_NO$,'X')
|
|
|
|
* Have all of the parameters need to send this to SAP to balance the Work Order
|
|
|
|
atParms = 'CASS_COMP':@RM
|
|
atParms := WORec<WO_LOG_PROD_ORD_NO$>:@RM
|
|
atParms := WONo:@RM
|
|
atParms := InCassNo:@RM
|
|
atParms := GRWfrQty:@RM
|
|
atParms := ScrapQty:@RM
|
|
atParms := ProdTWQty:@RM
|
|
atParms := CassID:@RM
|
|
atParms := WOMatRec<WO_MAT_LOT_NO$>:@RM
|
|
atParms := SubSuppCd:@RM
|
|
atParms := CustPartRev:@RM
|
|
atParms := MakeupFlag:@RM
|
|
atParms := MUBatchNo:@RM
|
|
atParms := MUCassQty
|
|
|
|
LogData = ''
|
|
LogData<1> = LoggingDTM
|
|
LogData<2> = RetStack()<1>
|
|
LogData<3> = WORec<WO_LOG_PROD_ORD_NO$>
|
|
LogData<4> = WONo
|
|
LogData<5> = InCassNo
|
|
LogData<6> = GRWfrQty
|
|
LogData<7> = ScrapQty
|
|
LogData<8> = ProdTWQty
|
|
LogData<9> = CassID
|
|
LogData<10> = WOMatRec<WO_MAT_LOT_NO$>
|
|
LogData<11> = SubSuppCd
|
|
LogData<12> = CustPartRev
|
|
LogData<13> = MakeupFlag
|
|
LogData<14> = MUBatchNo
|
|
LogData<15> = MUCassQty
|
|
Logging_Services('AppendLog', objLog, LogData, @RM, @FM)
|
|
|
|
obj_SAP('AddTransaction',atParms)
|
|
|
|
END ;* End of check for Inbound Product Test wafers
|
|
END ;* End of check for more WM_In records than WM_Out records
|
|
|
|
END ELSE
|
|
|
|
Recipients = Xlate('SEC_GROUPS', 'SAP_ADMIN', 'USER', 'X')
|
|
SentFrom = "obj_WO_Mat -> SetSAPBatch"
|
|
Subject = 'Unable to auto Close Work Order ':WONo:' ':CassNo:' ':SAPBatchNo
|
|
Message = 'Stopped at ':TimeDate()
|
|
NewForm = Xlate('APP_INFO', 'NEW_WO_FORM', '', 'X')
|
|
If NewForm then
|
|
AttachWindow = 'NDW_WO_LOG'
|
|
end else
|
|
AttachWindow = 'WO_LOG2'
|
|
end
|
|
AttachKey = WONo
|
|
SendToGroup = ''
|
|
|
|
Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup
|
|
obj_Notes('Create',Parms)
|
|
|
|
END ;* End of check for WO quantities balanced
|
|
|
|
END ;* End of check for this being the only box
|
|
END ;* End of check for Multiple Open Cass ID's
|
|
|
|
END ;* End of check for fully released Work Order ;* 10/8/2014 DKK & JCH
|
|
|
|
Result = 1
|
|
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
GetCycleTime:
|
|
* * * * * * *
|
|
|
|
CassID = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
StartEvent = Parms[COL2()+1,@RM]
|
|
StopEvent = Parms[COL2()+1,@RM]
|
|
|
|
IF CassID = '' THEN RETURN
|
|
IF WOMatRec = '' THEN
|
|
WOMatRec = XLATE('WO_MAT',CassID,'','X')
|
|
IF WOMatRec = '' THEN RETURN
|
|
END
|
|
|
|
IF StartEvent = '' THEN RETURN
|
|
IF StopEvent = '' THEN RETURN
|
|
|
|
StartDTM = ''
|
|
StopDTM = ''
|
|
|
|
|
|
WONo = CassID[1,'*']
|
|
ReactType = XLATE('WO_LOG',WONo,'REACTOR_TYPE','X') ;* Variable not used in method JCH 8/28/2014
|
|
|
|
BEGIN CASE
|
|
CASE StartEvent = 'PTI'
|
|
LOCATE 'PTI' IN WOMatRec<WO_MAT_INV_LOCATION$> USING @VM SETTING StartPos THEN
|
|
StartDTM = WOMatRec<WO_MAT_INV_DTM$,StartPos>
|
|
END
|
|
|
|
CASE StartEvent = 'VER'
|
|
LastRDSNo = WOMatRec<WO_MAT_RDS_NO$>[-1,'B':@VM]
|
|
StartDTM = XLATE('REACT_RUN',LastRDSNo,REACT_RUN_VER_SIG_DTM$,'X')
|
|
|
|
CASE StartEvent = 'REL'
|
|
StartDTM = WOMatRec<WO_MAT_REL_DTM$>
|
|
|
|
CASE StartEvent = 'QA'
|
|
SigCnt = COUNT(WOMatRec<WO_MAT_SIGNATURE$>,@VM) + (WOMatRec<WO_MAT_SIGNATURE$> NE '')
|
|
StartDTM = WOMatRec<WO_MAT_SIG_DTM$,SigCnt>
|
|
|
|
CASE StartEvent = 'RB'
|
|
LOCATE 'RB' IN WOMatRec<WO_MAT_INV_LOCATION$> USING @VM SETTING StartPos THEN
|
|
StartDTM = WOMatRec<WO_MAT_INV_DTM$,StartPos>
|
|
END
|
|
|
|
END CASE
|
|
|
|
|
|
BEGIN CASE
|
|
|
|
CASE StopEvent = 'QA'
|
|
SigCnt = COUNT(WOMatRec<WO_MAT_SIGNATURE$>,@VM) + (WOMatRec<WO_MAT_SIGNATURE$> NE '')
|
|
StopDTM = WOMatRec<WO_MAT_SIG_DTM$,SigCnt>
|
|
|
|
CASE StopEvent = 'PTO'
|
|
InvLocations = WOMatRec<WO_MAT_INV_LOCATION$>
|
|
|
|
LOOP
|
|
Loc = InvLocations[-1,'B':@VM]
|
|
UNTIL Loc = 'PTO' OR InvLocations = ''
|
|
InvLocations[COL1(),99] = ''
|
|
REPEAT
|
|
|
|
Pointer = COUNT(InvLocations,@VM) + (InvLocations NE '')
|
|
|
|
IF Pointer > 0 THEN
|
|
StopDTM = WOMatRec<WO_MAT_INV_DTM$,Pointer>
|
|
END
|
|
|
|
|
|
CASE StopEvent = 'SB'
|
|
LOCATE 'SB' IN WOMatRec<WO_MAT_INV_LOCATION$> USING @VM SETTING StopPos THEN
|
|
StopDTM = WOMatRec<WO_MAT_INV_DTM$,StopPos>
|
|
END
|
|
|
|
CASE StopEvent = 'VER'
|
|
LastRDSNo = WOMatRec<WO_MAT_RDS_NO$>[-1,'B':@VM]
|
|
StopDTM = XLATE('REACT_RUN',LastRDSNo,REACT_RUN_VER_SIG_DTM$,'X')
|
|
|
|
END CASE
|
|
|
|
|
|
IF StartDTM NE '' AND StopDTM NE '' AND StopDTM NE '0' THEN
|
|
Result = ICONV((StopDTM - StartDTM)*24,'MD1')
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
GetQAMet:
|
|
* * * * * * *
|
|
|
|
CassID = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
WOStep = Parms[COL2()+1,@RM]
|
|
RunStep = Parms[COL2()+1,@RM]
|
|
MetFields = Parms[COL2()+1,@RM]
|
|
|
|
IF CassID = '' THEN RETURN
|
|
IF WOStep = '' THEN RETURN
|
|
IF RunStep = '' THEN RETURN
|
|
|
|
|
|
IF MetFields = '' THEN
|
|
MetFields = WO_MAT_MET_PROFILE$:@VM
|
|
MetFields := WO_MAT_MET_RUN_STEP$:@VM
|
|
MetFields := WO_MAT_MET_MIN$:@VM
|
|
MetFields := WO_MAT_MET_MAX$:@VM
|
|
MetFields := WO_MAT_MET_RESULT$:@VM
|
|
MetFields := WO_MAT_MET_SLOT$:@VM
|
|
MetFields := WO_MAT_MET_SIG$:@VM
|
|
MetFields := WO_MAT_MET_SIG_DTM$:@VM
|
|
MetFields := WO_MAT_MET_SLOT_TEST$:@VM
|
|
MetFields := WO_MAT_MET_STD_MAX$:@VM
|
|
MetFields := WO_MAT_MET_STD_RESULT$:@VM
|
|
MetFields := WO_MAT_MET_RECIPE$:@VM
|
|
MetFields := WO_MAT_MET_RECIPE_PATTERN$:@VM
|
|
MetFields := WO_MAT_MET_PROP$:@VM
|
|
MetFields := WO_MAT_MET_TOOL_CLASS$:@VM
|
|
MetFields := WO_MAT_MET_WFR_QTY$:@VM
|
|
MetFields := WO_MAT_MET_WFR_TYPE$
|
|
END
|
|
|
|
IF WOMatRec = '' THEN
|
|
WOMatRec = XLATE('WO_MAT',CassID,'','X')
|
|
IF WOMatRec = '' THEN RETURN
|
|
END
|
|
|
|
MetTests = WOMatRec<WO_MAT_MET_PROFILE$>
|
|
MetRunSteps = WOMatRec<WO_MAT_MET_RUN_STEP$>
|
|
|
|
FieldCnt = COUNT(MetFields,@VM) + (MetFields NE '')
|
|
MetCnt = COUNT(MetTests,@VM) + (MetTests NE '')
|
|
|
|
LineCnt = 1
|
|
Ans = ''
|
|
FOR I = 1 TO MetCnt
|
|
MetWOStep = MetTests<1,I>[1,1]
|
|
|
|
IF MetWOStep = WOStep AND WOMatRec<WO_MAT_MET_RUN_STEP$,I> = RunStep THEN
|
|
FOR N = 1 TO FieldCnt
|
|
MetField = MetFields<1,N>
|
|
IF MetField = WO_MAT_MET_PROFILE$ THEN
|
|
Ans<N,LineCnt> = WOMatRec<MetField,I>[2,99] ;* Profile (test) field has stage embedded in the 1st character
|
|
END ELSE
|
|
Ans<N,LineCnt> = WOMatRec<MetField,I>
|
|
END
|
|
NEXT N
|
|
LineCnt += 1
|
|
END
|
|
NEXT I
|
|
|
|
Result = Ans
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
GetMUCassIDs:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
IF WOMatRec = '' THEN
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
END
|
|
|
|
WMOKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
|
|
MUCassIDs = ''
|
|
MUCassQtys = ''
|
|
|
|
IF WMOKey NE '' THEN
|
|
|
|
WMORec = XLATE('WM_OUT',WMOKey,'','X')
|
|
|
|
SlotNos = WMORec<WM_OUT_SLOT_NO$>
|
|
SlotCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
|
|
|
|
FOR I = 1 TO SlotCnt
|
|
|
|
IF WMORec<WM_OUT_MU_WO_NO$,I> NE '' THEN
|
|
MUCassID = WMORec<WM_OUT_MU_WO_NO$,I>:'*':WMORec<WM_OUT_MU_CASS_NO$,I>
|
|
LOCATE MUCassID IN MUCassIDs USING @VM SETTING Pos ELSE
|
|
MUCassIDs = INSERT(MUCassIDs,1,Pos,0,MUCassID) ;* @MV'd list of CassIDs used for makeup
|
|
END
|
|
END
|
|
|
|
NEXT I
|
|
|
|
END ELSE
|
|
SlotIDs = WOMatRec<WO_MAT_SLOT_NO$>
|
|
SlotCnt = COUNT(SlotIDs,@VM) + (SlotIDs NE '')
|
|
|
|
FOR I = 1 TO SlotCnt
|
|
|
|
IF WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,I> NE '' THEN
|
|
|
|
MUCassID = FIELD(WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,I>,'.',1,2)
|
|
CONVERT '.' TO '*' IN MUCassID
|
|
LOCATE MUCassID IN MUCassIDs USING @VM SETTING Pos ELSE
|
|
MUCassIDs = INSERT(MUCassIDs,1,Pos,0,MUCassID) ;* @MV'd list of CassIDs used for makeup
|
|
END
|
|
END
|
|
|
|
NEXT I
|
|
END
|
|
|
|
Result = MUCassIDs
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * * *
|
|
GetMUAddedDTMS:
|
|
* * * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
IF WOMatRec = '' THEN
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
END
|
|
|
|
WMOKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
|
|
MUCassIDs = ''
|
|
MUCassQtys = ''
|
|
|
|
IF WMOKey NE '' THEN
|
|
|
|
WMORec = XLATE('WM_OUT',WMOKey,'','X')
|
|
|
|
SlotNos = WMORec<WM_OUT_SLOT_NO$>
|
|
SlotCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
|
|
AddedDTMS = WMORec<WM_OUT_MU_WAFER_ADDED_DTM$>
|
|
MUAddedDTMS = ''
|
|
FOR I = 1 TO SlotCnt
|
|
|
|
IF WMORec<WM_OUT_MU_WO_NO$,I> NE '' THEN
|
|
MUCassID = WMORec<WM_OUT_MU_WO_NO$,I>:'*':WMORec<WM_OUT_MU_CASS_NO$,I>
|
|
LOCATE MUCassID IN MUCassIDs USING @VM SETTING Pos ELSE
|
|
ThisDTM = AddedDTMS<1, Pos>
|
|
MostRecentDTM = ThisDTM[1, @SVM]
|
|
MUAddedDTMS = Insert(MUAddedDTMS, 1, Pos, 0, MostRecentDTM)
|
|
END
|
|
END
|
|
|
|
NEXT I
|
|
|
|
END ELSE
|
|
SlotIDs = WOMatRec<WO_MAT_SLOT_NO$>
|
|
SlotCnt = COUNT(SlotIDs,@VM) + (SlotIDs NE '')
|
|
AddedDTMS = WOMatRec<WO_MAT_MU_WAFER_ADDED_DTM$>
|
|
MUAddedDTMS = ''
|
|
FOR I = 1 TO SlotCnt
|
|
|
|
IF WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,I> NE '' THEN
|
|
|
|
MUCassID = FIELD(WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,I>,'.',1,2)
|
|
CONVERT '.' TO '*' IN MUCassID
|
|
LOCATE MUCassID IN MUCassIDs USING @VM SETTING Pos ELSE
|
|
ThisDTM = AddedDTMS<1, Pos>
|
|
MostRecentDTM = ThisDTM[1, @SVM]
|
|
MUAddedDTMS = Insert(MUAddedDTMS, 1, Pos, 0, MostRecentDTM)
|
|
END
|
|
END
|
|
|
|
NEXT I
|
|
END
|
|
|
|
Result = MUAddedDTMS
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * * * *
|
|
GetMURemovedDTMS:
|
|
* * * * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
IF WOMatRec = '' THEN
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
END
|
|
|
|
WMOKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
|
|
MUCassIDs = ''
|
|
MUCassQtys = ''
|
|
|
|
IF WMOKey NE '' THEN
|
|
|
|
WMORec = XLATE('WM_OUT',WMOKey,'','X')
|
|
|
|
SlotNos = WMORec<WM_OUT_SLOT_NO$>
|
|
SlotCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
|
|
RemovedDTMS = WMORec<WM_OUT_MU_WAFER_REMOVED_DTM$>
|
|
MURemovedDTMS = ''
|
|
FOR I = 1 TO SlotCnt
|
|
|
|
IF WMORec<WM_OUT_MU_WO_NO$,I> NE '' THEN
|
|
MUCassID = WMORec<WM_OUT_MU_WO_NO$,I>:'*':WMORec<WM_OUT_MU_CASS_NO$,I>
|
|
LOCATE MUCassID IN MUCassIDs USING @VM SETTING Pos ELSE
|
|
ThisDTM = RemovedDTMS<1, Pos>
|
|
MostRecentDTM = ThisDTM[1, @SVM]
|
|
MURemovedDTMS = Insert(MURemovedDTMS, 1, Pos, 0, MostRecentDTM)
|
|
END
|
|
END
|
|
|
|
NEXT I
|
|
|
|
END ELSE
|
|
SlotIDs = WOMatRec<WO_MAT_SLOT_NO$>
|
|
SlotCnt = COUNT(SlotIDs,@VM) + (SlotIDs NE '')
|
|
RemovedDTMS = WOMatRec<WO_MAT_MU_WAFER_REMOVED_DTM$>
|
|
MURemovedDTMS = ''
|
|
FOR I = 1 TO SlotCnt
|
|
|
|
IF WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,I> NE '' THEN
|
|
|
|
MUCassID = FIELD(WOMatRec<WO_MAT_SLOT_REP_WAFER_ID$,I>,'.',1,2)
|
|
CONVERT '.' TO '*' IN MUCassID
|
|
LOCATE MUCassID IN MUCassIDs USING @VM SETTING Pos ELSE
|
|
ThisDTM = RemovedDTMS<1, Pos>
|
|
MostRecentDTM = ThisDTM[1, @SVM]
|
|
MURemovedDTMS = Insert(MURemovedDTMS, 1, Pos, 0, MostRecentDTM)
|
|
END
|
|
END
|
|
|
|
NEXT I
|
|
END
|
|
|
|
Result = MURemovedDTMS
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
GetEventLog:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
*Result<1,-1> = 'SAP Transmit':@SVM:OCONV(WOMatRec<WO_MAT_SAP_TX_DTM$>,'DT4/^S'):@SVM
|
|
Result<1,-1> = 'Received':@SVM:OCONV(WOMatRec<WO_MAT_RX_DTM$>,'DT4/^S'):@SVM:WOMatRec<WO_MAT_RX_BY$>
|
|
Result<1,-1> = 'Released':@SVM:OCONV(WOMatRec<WO_MAT_REL_DTM$>,'DT4/^S'):@SVM:WOMatRec<WO_MAT_REL_BY$>
|
|
|
|
RETURN
|
|
|
|
* * * * * * *
|
|
GetADERead:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKEy,'','X')
|
|
|
|
StepCnt = COUNT(WOMatRec<WO_MAT_RDS_NO$>,@VM) + (WOMatRec<WO_MAT_RDS_NO$> NE '')
|
|
|
|
ADEProfile = StepCnt:'ADE'
|
|
|
|
LOCATE ADEProfile IN WOMatRec<WO_MAT_MET_PROFILE$> USING @VM SETTING Pos THEN
|
|
Result = WOMatRec<WO_MAT_MET_RESULT$,Pos>
|
|
END ELSE
|
|
Result = ''
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
CheckSigOrder:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
SigProfItem = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF SigProfItem = '' THEN ErrorMsg = 'Null Parm "SigProfItem" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
LOCATE SigProfItem IN WOMatRec<WO_MAT_SIG_PROFILE$> USING @VM SETTING Pos THEN
|
|
|
|
BEGIN CASE
|
|
Case SigProfItem EQ '1LOAD'
|
|
// Barcode Integration Project
|
|
// PRE stage (1VER) and LOAD stage can be signed simultaneously, so do not throw and error.
|
|
Null
|
|
|
|
CASE Pos > 1 AND WOMatRec<WO_MAT_SIGNATURE$,Pos - 1> = ''
|
|
ErrTitle = 'Process Error'
|
|
ErrorMsg = 'Previous step ':QUOTE(WOMatRec<WO_MAT_SIG_PROFILE$,Pos - 1>):' is not signed. ':WOMatKey:' (':Method:')'
|
|
|
|
CASE WOMatRec<WO_MAT_SIGNATURE$,Pos> NE ''
|
|
ErrTitle = 'Process Error'
|
|
ErrorMsg = 'This step is already signed. ':WOMatKey:'(':Method:')'
|
|
|
|
CASE 1
|
|
NULL
|
|
|
|
END CASE
|
|
|
|
END ELSE
|
|
ErrorMsg = 'SigProfItem ':QUOTE(SigProfItem):' not found in Signature Profile. ':WOMatKey:' (':Method:')'
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
MQAComp:
|
|
* * * * * * *
|
|
|
|
* Checks for completion of Met QA step
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOStep = Parms[COL2()+1,@RM]
|
|
RunStep = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null Parm "WOMatKey" passed to routine. (':Method:')'
|
|
IF WOStep = '' THEN ErrorMsg = 'Null Parm "WOStep" passed to routine. (':Method:')'
|
|
IF RunStep = '' THEN ErrorMsg = 'Null Parm "RunStep" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
WOMatQARec = XLATE('WO_MAT_QA',WOMatKey,'','X')
|
|
|
|
If WOMatQARec NE '' Then
|
|
|
|
AllSteps = obj_Popup('AllCodes','RUN_STEPS') ;* All Run Steps in sequence
|
|
|
|
Locate RunStep In AllSteps USING @VM SETTING StepPos THEN
|
|
|
|
MPCnt = COUNT(WOMatQARec<WO_MAT_QA_PROFILE$>,@VM) + (WOMatQARec<WO_MAT_QA_PROFILE$> NE '')
|
|
|
|
FOR I = 1 TO MPCnt
|
|
LineStep = WOMatQARec<WO_MAT_QA_STAGE$,I>
|
|
LineResult = WOMatQARec<WO_MAT_QA_RESULT$,I>
|
|
|
|
Locate LineStep In AllSteps USING @VM SETTING LinePos THEN
|
|
IF LinePos <= StepPos And LineResult = '' THEN
|
|
ErrTitle = 'Process Error'
|
|
ErrorMsg = 'Met QA is incomplete in ':obj_Popup('CodeDesc','RUN_STEPS':@RM:WOMatQARec<WO_MAT_QA_STAGE$,I> ):' step'
|
|
End
|
|
End ;* End of LinePos locate
|
|
Until ErrorMsg NE ''
|
|
NEXT I
|
|
End;* End of StepPos Locate
|
|
End ;* End of check for null WOMatQA record
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
EpiReactNo:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
IF WOMatRec = '' THEN RETURN
|
|
|
|
Result = ''
|
|
|
|
WMOutRec = XLATE('WM_OUT',WOMatRec<WO_MAT_WMO_KEY$>,'','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
|
|
|
|
|
|
* * * * * * *
|
|
GetQAMetKeys:
|
|
* * * * * * *
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
IF WOMetRec = '' THEN
|
|
WOMetRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
IF WOMetRec = '' THEN RETURN
|
|
END
|
|
|
|
ProdVerNo = WOMetRec<WO_MAT_PROD_VER_NO$>
|
|
|
|
StepPSNos = XLATE('PROD_VER',ProdVerNo,PROD_VER_PROC_STEP_PSN$,'X')
|
|
|
|
psCnt = COUNT(StepPSNos,@VM) + (StepPSNos NE '')
|
|
|
|
LineCnt = 1
|
|
|
|
FOR I = 1 TO psCNT
|
|
StepPSNo = StepPSNos<1,I>
|
|
|
|
QAMetStruct = obj_Prod_Spec('GetQAMet',StepPSNo:@RM:'')
|
|
|
|
msCnt = COUNT(QAMetStruct<COL$QA_MET_STAGE>,@VM) + (QAMetStruct<COL$QA_MET_STAGE> NE '')
|
|
|
|
FOR N = 1 TO msCnt
|
|
Result<1,LineCnt> = I:'*':QAMetStruct<COL$QA_MET_STAGE,N>:'*':QAMetStruct<COL$QA_MET_PROP,N>
|
|
Result<2,LineCnt> = LineCnt
|
|
LineCnt += 1
|
|
NEXT N
|
|
|
|
NEXT I
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
AddQAMet:
|
|
* * * * * * *
|
|
|
|
* Dead 6/5/2015 JCH Remove after a few days (the entire method has moved
|
|
|
|
WONo = Parms[1,@RM]
|
|
WOStep = Parms[COL2()+1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
Stage = Parms[COL2()+1,@RM]
|
|
MetTest = Parms[COL2()+1,@RM]
|
|
MetProp = Parms[COL2()+1,@RM]
|
|
MetToolClass = Parms[COL2()+1,@RM]
|
|
MetMin = Parms[COL2()+1,@RM]
|
|
MetMax = Parms[COL2()+1,@RM]
|
|
MetSlot = Parms[COL2()+1,@RM]
|
|
MetRecipe = Parms[COL2()+1,@RM]
|
|
MetRecipePattern = 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 Stage = '' THEN ErrorMsg = 'Null Parm "Stage" passed to routine. (':Method:')'
|
|
IF MetProp = '' THEN ErrorMsg = 'Null Parm "MetProp" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN
|
|
SWAP @RM WITH '","' IN Parms
|
|
ErrorMsg = ErrorMsg:' Parms = ':QUOTE(Parms)
|
|
RETURN
|
|
END
|
|
|
|
NewMetKey = WOStep:'*':Stage:'*':MetProp
|
|
|
|
WOMatKey = WONo:'*':CassNo
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms)
|
|
|
|
IF WOMatRec = '' THEN RETURN
|
|
|
|
AllQAMetKeysStruct = obj_WO_Mat('GetQAMetKeys',WOMatKey:@RM:WOMatRec) ;* All QAMetSort Keys Specified for this Work Order Returns Keys in <1> and Sequence numbers = <2>
|
|
|
|
AllMetKeys = AllQAMetKeysStruct<1> ;* Correctly sorted list of all possible QA Met keys built from the PRS_SPEC records for all WO Steps
|
|
AllLines = AllQAMetKeysStruct<2> ;* List of position numbers for each of the met keys
|
|
|
|
CurrMetKeys = ''
|
|
CurrLines = ''
|
|
cmqCnt = COUNT(WOMatRec<WO_MAT_MET_PROFILE$>,@VM) + (WOMatRec<WO_MAT_MET_PROFILE$> NE '')
|
|
|
|
FOR M = 1 to cmqCnt
|
|
CurrMetKey = WOMatRec<WO_MAT_MET_PROFILE$,M>[1,1]:'*':WOMatRec<WO_MAT_MET_RUN_STEP$,M>:'*':WOMatRec<WO_MAT_MET_PROP$,M>
|
|
CurrMetKeys<1,M> = CurrMetKey
|
|
|
|
LOCATE CurrMetKey IN AllMetKeys USING @VM SETTING AllPos THEN
|
|
CurrLines<1,M> = AllPos ;* Builds a list of CurrLines for the Met Keys on the existing WO_MAT records
|
|
END
|
|
NEXT M
|
|
|
|
LOCATE NewMetKey IN AllMetKeys USING @VM SETTING SpecLine THEN
|
|
|
|
LOCATE SpecLine IN CurrLines BY 'AR' USING @VM SETTING InsertPos THEN
|
|
|
|
obj_Tables('UnlockRec',otParms)
|
|
|
|
END ELSE
|
|
|
|
CurrLines = INSERT(CurrLines,1,InsertPos,0,SpecLine)
|
|
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_MET_PROFILE$, InsertPos, 0, WOStep:MetTest)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_MET_PROP$,InsertPos,0,MetProp)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_MET_TOOL_CLASS$, InsertPos, 0, MetToolClass)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_MET_RUN_STEP$, InsertPos, 0, Stage)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_MET_MIN$, InsertPos, 0, MetMin)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_MET_MAX$, InsertPos, 0, MetMax)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_MET_SLOT$, InsertPos, 0, MetSlot)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_MET_RECIPE$, InsertPos, 0, MetRecipe)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_MET_RECIPE_PATTERN$, InsertPos, 0, MetRecipePattern)
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_MET_SIG$, InsertPos, 0, '')
|
|
WOMatRec = INSERT(WOMatRec, WO_MAT_MET_SIG_DTM$, InsertPos, 0, '')
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
END ;* End of SpecLine LOCATE
|
|
|
|
END ELSE
|
|
|
|
obj_Tables('UnlockRec',otParms)
|
|
|
|
END ;* End of NewMetKey LOCATE
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
RemQAMet:
|
|
* * * * * * *
|
|
|
|
* Dead 6/5/2015 JCH Remove after a few days (the entire method has moved
|
|
|
|
WONo = Parms[1,@RM]
|
|
WOStep = Parms[COL2()+1,@RM]
|
|
CassNo = Parms[COL2()+1,@RM]
|
|
Stage = Parms[COL2()+1,@RM]
|
|
PropCd = 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 Stage = '' THEN ErrorMsg = 'Null Parm "Stage" passed to routine. (':Method:')'
|
|
IF PropCd = '' THEN ErrorMsg = 'Null Parm "PropCd" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
WOMatKey = WONo:'*':CassNo
|
|
otParms = 'WO_MAT':@RM:WOMatKey
|
|
WOMatRec = obj_Tables('ReadRec',otParms)
|
|
|
|
CurrMetKeys = ''
|
|
|
|
cmqCnt = COUNT(WOMatRec<WO_MAT_MET_PROFILE$>,@VM) + (WOMatRec<WO_MAT_MET_PROFILE$> NE '')
|
|
|
|
FOR M = 1 to cmqCnt
|
|
CurrMetKey = WOMatRec<WO_MAT_MET_PROFILE$,M>[1,1]:'*':WOMatRec<WO_MAT_MET_RUN_STEP$,M>:'*':WOMatRec<WO_MAT_MET_PROP$,M>
|
|
CurrMetKeys<1,M> = CurrMetKey
|
|
NEXT M
|
|
|
|
DelMetKey = WOStep:'*':Stage:'*':PropCd
|
|
|
|
LOCATE DelMetKey IN CurrMetKeys USING @VM SETTING DelPos THEN
|
|
|
|
IF WOMatRec<WO_MAT_MET_SIG$,DelPos> = '' THEN
|
|
|
|
WOMatRec = DELETE(WOMatRec, WO_MAT_MET_PROFILE$, DelPos, 0)
|
|
WOMatRec = DELETE(WOMatRec, WO_MAT_MET_PROP$,DelPos,0)
|
|
WOMatRec = DELETE(WOMatRec, WO_MAT_MET_TOOL_CLASS$, DelPos, 0)
|
|
WOMatRec = DELETE(WOMatRec, WO_MAT_MET_RUN_STEP$, DelPos, 0)
|
|
WOMatRec = DELETE(WOMatRec, WO_MAT_MET_MIN$, DelPos, 0)
|
|
WOMatRec = DELETE(WOMatRec, WO_MAT_MET_MAX$, DelPos, 0)
|
|
WOMatRec = DELETE(WOMatRec, WO_MAT_MET_SLOT$, DelPos, 0)
|
|
WOMatRec = DELETE(WOMatRec, WO_MAT_MET_RECIPE$, DelPos, 0)
|
|
WOMatRec = DELETE(WOMatRec, WO_MAT_MET_RECIPE_PATTERN$, DelPos, 0)
|
|
WOMatRec = DELETE(WOMatRec, WO_MAT_MET_SIG$, DelPos, 0)
|
|
WOMatRec = DELETE(WOMatRec, WO_MAT_MET_SIG_DTM$, DelPos, 0)
|
|
|
|
otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
END ELSE
|
|
obj_Tables('UnlockRec',otParms)
|
|
END
|
|
|
|
END ELSE
|
|
obj_Tables('UnlockRec',otParms)
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
GetBinLocID:
|
|
* * * * * * *
|
|
|
|
* Method finds Bin No in FGS warehouse (Finished Goods Storage)
|
|
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN ErrorMsg = 'Null Parm "WONo" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
IF WOMatRec = '' THEN
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
IF WOMatRec = '' THEN
|
|
ErrorMsg = 'No WOMatRec FOR WOMatKey: ':WOMatKey:'.'
|
|
RETURN
|
|
END
|
|
END
|
|
|
|
WONo = WOMatKey[1,'*']
|
|
|
|
CustNo = XLATE('WO_LOG' , WONo , WO_LOG_CUST_NO$ , 'X')
|
|
|
|
|
|
OPEN 'DICT.LOCATION' TO DictVar THEN
|
|
|
|
SearchString = 'CUST_NO':@VM:CustNo:@FM
|
|
Option = 'E' ;* Suppress error message (method called from MFS)
|
|
Flag = ''
|
|
LocIDs = ''
|
|
Btree.Extract(SearchString,'LOCATION',DictVar,LocIDs,Option,Flag)
|
|
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * * * * * *
|
|
SendErrorNotification:
|
|
* * * * * * * * * * *
|
|
|
|
swap @SVM with CRLF$ in errCode
|
|
ErrorMsg = 'Error code: ':errCode
|
|
|
|
Recipients = XLATE('SEC_GROUPS', 'OI_ADMIN', 'USER', 'X')
|
|
SentFrom = "OBJ_WO_MAT"
|
|
Subject = 'Error Writing to WO_MAT'
|
|
Message = 'Error occured while attempting to write WO_MAT':CRLF$:ErrorMsg
|
|
AttachKey = WoMatKey
|
|
AttachWindow = ''
|
|
SendToGroup = ''
|
|
|
|
Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup
|
|
obj_Notes('Create',Parms)
|
|
|
|
return
|
|
|
|
|
|
* * * * * * *
|
|
ExpCOA:
|
|
* * * * * * *
|
|
|
|
Result = ''
|
|
WOMatKey = Parms[1,@RM]
|
|
WOMatRec = Parms[COL2()+1,@RM]
|
|
|
|
IF WOMatKey = '' THEN RETURN
|
|
|
|
IF WOMatRec = '' THEN WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
NoConversion = 1
|
|
|
|
Result = WOMatRec
|
|
|
|
RETURN
|
|
|
|
|
|
|