COMPILE FUNCTION Comm_WO_Rec(Instruction, Parm1,Parm2) /* Commuter module for WO_Rec (Work Order Receipt) window 05/18/2004 - John C. Henry, J.C. Henry & Co., Inc. */ DECLARE SUBROUTINE Set_Property, Set_Status, ErrMsg, Set_Property, obj_AppWindow, obj_Notes, Print_RX_Voucher, obj_Tables DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, Forward_Event, End_Window, obj_WO_Log, obj_WO_Mat DECLARE SUBROUTINE Logging_Services, Post_Event, Work_Order_Services DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box, RowExists, obj_Prod_Spec DECLARE FUNCTION obj_Schedule, Dialog_Box, obj_WO_Log, obj_Order_Det, FindWindow,ShowWindow, obj_Tables, obj_WO_Mat, MemberOf DECLARE FUNCTION Logging_Services, Environment_Services $INSERT POPUP_EQUATES $INSERT LOGICAL $INSERT MSG_EQUATES $INSERT APPCOLORS $INSERT WO_LOG_EQUATES $INSERT WO_MAT_EQUATES $INSERT QUOTE_EQU $INSERT QUOTE_DET_EQU $INSERT ORDER_EQU $INSERT ORDER_DET_EQU $INSERT COMPANY_EQU $INSERT PROD_SPEC_EQUATES $INSERT QUOTE_SPEC_EQU $INSERT LSL_USERS_EQU $INSERT SECURITY_RIGHTS_EQU $INSERT NOTIFICATION_EQU $INSERT PROD_VER_EQUATES $INSERT EPI_PART_EQUATES $INSERT CUST_EPI_PART_EQUATES EQU CRLF$ TO \0D0A\ EQU COL$CASS_NO TO 1 ;* Equates for CASS_NO edit table control (cassettes received) EQU COL$CASS_LOT_NO TO 2 EQU COL$CASS_QTY TO 3 EQU COL$CASS_CUST_PART_NO TO 4 EQU COL$CASS_SUB_PART_NO TO 5 EQU COL$CASS_SUB_VEND_CD TO 6 EQU COL$CASS_TIME_STAMP TO 7 EQU COL$CASS_SCAN_BY TO 8 EQU COL$CASS_ORDER_ITEM TO 9 EQU COL$OD_ITEM_NO TO 1 ;* Equates for ORDER_DETAIL control (material ordered) EQU COL$OD_CUST_PART_NO TO 2 EQU COL$OD_CUST_PN_DESC TO 3 EQU COL$OD_CUST_PN_INBOUND TO 4 EQU COL$OD_SUB_PART_NO TO 5 EQU COL$OD_PROMISE_DT TO 6 EQU COL$OD_ITEM_QTY TO 7 EQU COL$OD_WAFER_QTY TO 8 EQU CA$ITEM_NO TO 1 ;* Equates for Checking Array passed to Scan routine EQU CA$LOT_NO TO 2 EQU CA$LOT_QTY TO 3 EQU CA$CUST_PART_NO TO 4 EQU CA$SUB_PART_NO TO 5 EQU CA$SCANNED_LOT_QTY TO 6 EQU CA$VERIFY_PART_NO TO 7 EQU CA$SUB_SUPP_BY TO 8 LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WO_LOG' LogDate = Oconv(Date(), 'D4/') LogTime = Oconv(Time(), 'MTS') LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' WO_MAT Receive Performance Log.csv' Headers = 'Logging DTM':@FM:'WO':@FM:'User':@FM:'Cassettes (Qty)':@FM:'WO_MAT Create (Secs)':@FM:'Form Refresh (Secs)':@FM:'Total Duration (Secs)':@FM:'Seconds/Cassette' objReceiveLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, COMMA$, Headers, '', False$, False$) LoggingDTM = LogDate : ' ' : LogTime ; // Logging DTM ErrTitle = 'Error in Comm_WO_Rec' ErrorMsg = '' ErrCode = '' Result = '' BEGIN CASE CASE Instruction = 'Create' ; GOSUB Create CASE Instruction = 'Refresh' ; GOSUB Refresh CASE Instruction = 'Page' ; GOSUB Page CASE Instruction = 'Read' ; GOSUB Read CASE Instruction = 'Clear' ; GOSUB Clear CASE Instruction = 'Delete' ; GOSUB Delete CASE Instruction = 'Close' ; GOSUB Close CASE Instruction = 'LUWONo' ; GOSUB LUWONo CASE Instruction = 'DueInWONos' ; GOSUB DueInWONos CASE Instruction = 'PrintVoucher' ; GOSUB PrintVoucher CASE Instruction = 'Scan' ; GOSUB Scan CASE Instruction = 'AddLeftover' ; GOSUB AddLeftover CASE 1 ErrorMsg = 'Unknown Instruction passed to routine' END CASE IF ErrorMsg NE '' THEN ErrMsg(ErrTitle:@SVM:ErrorMsg) END RETURN Result * * * * * * * Create: * * * * * * * IF NOT(Security_Check('WO Log',READ$)) THEN Security_Err_Msg('WO Log',READ$) End_Window(@WINDOW) RETURN END obj_Appwindow('Create',@WINDOW) GOSUB Refresh Parent = Get_Property(@Window, 'PARENT') If Parent EQ 'NDW_RELEASE_CASSETTES' then WONo = Get_Property(Parent:'.EDL_WO_NO', 'TEXT') Set_Property(@Window:'.WO_NO', 'TEXT', WONo) Post_Event(@Window, 'READ') end RETURN * * * * * * * Read: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','TEXT') IF RowExists('WO_LOG',WONo) THEN IF NOT(Security_Check('Work Order',READ$)) THEN Send_Event(@WINDOW,'CLEAR') Security_Err_Msg('Work Order',READ$) RETURN END END ELSE ErrMsg('Work Order Log entries may only be created from the ORDER window.') Send_Event(@WINDOW,'CLEAR') RETURN END ProdVerNo = Get_Property(@WINDOW:'.PROD_VER','DEFPROP') IF ProdVerNo = '' THEN ErrMsg('Work Order has not been routed.') Send_Event(@WINDOW,'CLEAR') RETURN END RxBy = Get_Property(@WINDOW:'.RX_BY','TEXT') IF RxBy = '' THEN CurrDate = OCONV(Date(),'D4/') CurrTime = OCONV(Time(),'MTS') CurrDTM = CurrDate:' ':CurrTime Set_Property(@WINDOW:'.RX_BY','TEXT',OCONV(@USER4,'[XLATE_CONV,LSL_USERS*FIRST_LAST]')) Set_Property(@WINDOW:'.RX_DTM','TEXT',CurrDTM) END GOSUB Refresh RETURN * * * * * * * Clear: * * * * * * * Send_Event(@WINDOW,'PAGE',1) GOTO Refresh RETURN * * * * * * * Delete: * * * * * * * Result = 0 ;* No deletes from here RETURN * * * * * * * Page: * * * * * * * Page = Parm1 IF Page = '' THEN Page = Get_Property(@WINDOW:'.TAB_MAIN','VALUE') END ELSE Set_Property(@WINDOW:'.TAB_MAIN','VALUE',Page) END Set_Property(@WINDOW,'VPOSITION', Page) GOSUB Refresh RETURN * * * * * * * Close: * * * * * * * Send_Event(@WINDOW,'CLEAR') ;* If this isn't here, the WO_LOG record has a lock on it obj_Appwindow('DetailReturn') RETURN * * * * * * * Refresh: * * * * * * * Ctrls = @WINDOW:'.RX_BY':@RM ; Props = 'DEFPROP':@RM Ctrls := @WINDOW:'.RX_DTM' ; Props := 'DEFPROP' Vals = Get_Property(Ctrls,Props) RxBy = Vals[1,@RM] RxDTM = Vals[COL2()+1,@RM] IF RxBy = '' THEN Vals = 1:@RM ELSE Vals = 0:@RM IF RxDTM = '' THEN Vals := 1 ELSE Vals := 0 Props = 'ENABLED':@RM:'ENABLED' Set_Property(Ctrls,Props,Vals) Ctrls = @WINDOW:'.WO_QTY':@RM ; Props = 'DEFPROP':@RM Ctrls := @WINDOW:'.RX_QTY' ; Props := 'DEFPROP' Vals = Get_Property(Ctrls,Props) WOQty = ICONV(Vals[1,@RM],'MD0') RxQty = ICONV(Vals[COL2()+1,@RM],'MD0') IF RxQty >= WOQty THEN Set_Property(@WINDOW:'.SCAN_BUTTON','ENABLED',-1) ;* Already RX'd complete END ELSE Set_Property(@WINDOW:'.SCAN_BUTTON','ENABLED',1) ;* Not yet received complete END * QBF buttons Ctrls = @WINDOW:'.QBF_FIRST_FIX':@RM ; Props = 'ENABLED':@RM Ctrls := @WINDOW:'.QBF_PREV_FIX':@RM ; Props := 'ENABLED':@RM Ctrls := @WINDOW:'.QBF_ABS_FIX':@RM ; Props := 'ENABLED':@RM Ctrls := @WINDOW:'.QBF_NEXT_FIX':@RM ; Props := 'ENABLED':@RM Ctrls := @WINDOW:'.QBF_LAST_FIX':@RM ; Props := 'ENABLED':@RM Ctrls := @WINDOW:'.QBF_STOP_FIX' ; Props := 'ENABLED' IF Get_Property(@WINDOW,'QBFLIST') = '' THEN Vals = 0:@RM:0:@RM:0:@RM:0:@RM:0:@RM:0 END ELSE Vals = 1:@RM:1:@RM:1:@RM:1:@RM:1:@RM:1 END Set_Property(Ctrls,Props,Vals) * Turn edit table symbolic column backgrounds to green ETSymbolics = Get_Property(@WINDOW,'@ET_SYMBOLICS') ;* Loaded during 'Create' in obj_Appwindow ETCtrls = ETSymbolics<1> ETCols = ETSymbolics<2> FOR I = 1 TO COUNT(ETCtrls,@VM) + (ETCtrls NE '') ETCtrl = ETCtrls<1,I> IF ETCtrl NE @WINDOW:'.ALL_RDS_KEYS' THEN ETList = Get_Property(ETCtrl,'LIST') FOR Line = 1 TO COUNT(ETList,@FM) + (ETList NE '') IF ETList NE '' THEN FOR N = 1 TO COUNT(ETCols<1,I>,@SVM) + (ETCols<1,I> NE '') stat = Send_Message(ETCtrl,'COLOR_BY_POS',ETCols<1,I,N>,Line,GREEN$) NEXT N END NEXT Line END NEXT I RETURN * * * * * * * DueInWONos: * * * * * * * OPEN 'DICT.WO_LOG' TO DictWOLogTable ELSE RETURN END MsgUp = Msg(@WINDOW,'','SELECT_OPEN_WO') WOKeys = '' SelectStatement = 'CURR_STATUS':@VM:'ASN':@VM:'AWM':@VM:'RTP':@FM Btree.Extract(SelectStatement,'WO_LOG',DictWOLogTable,WOKeys,'','') IF Get_Status(errCode) THEN ErrMsg(errCode) Msg(@WINDOW,MsgUp) RETURN END Msg(@WINDOW,MsgUp) TypeOver = '' TypeOver = WOKeys DueInWONo = Popup(@WINDOW,TypeOver,'DUE_IN_WORK_ORDERS') IF DueInWONo NE '' THEN obj_AppWindow('LoadFormKeys',@WINDOW:@RM:DueInWONo) END RETURN * * * * * * * LUWONo: * * * * * * * Set_Status(0) WONo = Dialog_Box( 'DIALOG_WO_DUE_IN', @WINDOW, '' ) IF Get_Status(errCode) THEN ErrMsg(ErrCode) IF WONo NE '' THEN obj_Appwindow('LoadFormKeys',@WINDOW:@RM:WONo) END RETURN * * * * * * * OpenWOS: * * * * * * * OpenWONo = obj_WO_Log('OpenWONos','') IF OpenWONo NE '' THEN obj_AppWindow('LoadFormKeys',@WINDOW:@RM:OpenWONo) END RETURN * * * * * * * PrintVoucher: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','TEXT') IF WONo = '' THEN RETURN Send_Event(@WINDOW,'WRITE') Print_RX_Voucher(WONo) obj_Appwindow('LoadFormKeys',@WINDOW:@RM:WONo) Set_Property('SYSTEM','FOCUS','VSPRINTER') RETURN * * * * * * * Scan: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','TEXT') CtrlEntID = @WINDOW:'.CASS_NO' CassList = Get_Property(CtrlEntID,'LIST') CassArray = Get_Property(CtrlEntID,'DEFPROP') CassListCnt = COUNT(CassList,@FM) CassPointer = 1 LOOP IF CassList NE '' THEN CassPointer += 1 END ELSE CassList = DELETE(CassList,CassPointer,0,0) END UNTIL CassList = '' REPEAT ExistCassCnt = COUNT(CassList,@FM) + (CassList NE '') WORec = XLATE('WO_LOG',WONo,'','X') WOMatKeys = WORec ;* List of WO_MAT Keys associated with this WO_LOG Record * * * * * * * OpenQty = ICONV(Get_Property(@WINDOW:'.OPEN_QTY','DEFPROP'),'MD0') ;* Scan button is disabled if there isn't anything to receive EPIPartNo = WORec EPIPartRec = XLATE('EPI_PART',EpiPartNo,'','X') SubSuppBy = EPIPartRec ;* L - EpiSvcs supplied, C - Customer Supplied SAPMaterial = EPIPartRec ;* 0 = OrderNo = Get_Property(@WINDOW:'.ORDER_NO','TEXT') IF OrderNo = '' THEN ProdVerNo = WORec ProdVerRec = XLATE('PROD_VER',ProdVerNo,'','X') SubPartNo = ProdVerRec ProdVerStepPSNs = ProdVerRec ;* Added 6/24/2016 JCH - GaN receipt Vendor = WORec ;* Added 4/14/2014 IF LEN(Vendor) NE 2 THEN Vendor = '' IF SubSuppBy = 'L' THEN VendorDef = Vendor END ELSE VendorDef = '' END CheckArray = '' CheckArray = 1 CheckArray = WORec CheckArray = OpenQty ;* Qty of wafers left to receive CustPartNo = WORec IF CustPartNo = '' THEN CheckArray = WORec ;******** This bites us farther in ****** JCH 10/13/2011 check with DK and then dump END ELSE CheckArray = CustPartNo END CheckArray = WORec ;* This is the Substrate Part No received from SAP CheckArray = '' CheckArray = SubSuppBy CheckArray = VendorDef:@FM:CheckArray END ELSE OrderDetailList = Get_Property(@WINDOW:'.ORDER_ITEMS','LIST') ;* Get Order Items from the control on the 2nd page ORDCnt = COUNT(OrderDetailList,@FM) + (OrderDetailList NE '') FOR I = OrdCnt TO 1 STEP -1 WHILE OrderDetailList = '' OrderDetailList = DELETE(OrderDetailList,I,0,0) ;* Strip blank lines from control data NEXT I CheckArray = '' CALine = 1 FOR I = 1 TO COUNT(OrderDetailList,@FM) + (OrderDetailList NE '') OrdItem = OrderDetailList IF OrderDetailList NE '' THEN VerifyPartNo = OrderDetailList END ELSE VerifyPartNo = OrderDetailList END ItemLotNos = WORec ItemLotQtys = WORec IF ItemLotNos = '' THEN ItemLotNos = XLATE('ORDER_DET',OrderNo:'*':OrdItem,ORDER_DET_CUST_LOT_NO$,'X') ;* Get the list of expected lot numbers on that item ItemLotQtys = XLATE('ORDER_DET',OrderNo:'*':OrdItem,ORDER_DET_CUST_LOT_QTY$,'X') ;* Get the list of expected lot qtys for associated item END IF ItemLotNos = '' THEN IF OrderDetailList NE '' THEN CheckArray = OrderDetailList CheckArray = '' CheckArray = ICONV(OrderDetailList,'MD0') CheckArray = OrderDetailList CheckArray = OrderDetailList CheckArray = VerifyPartNo CheckArray = SubSuppBy END END ELSE FOR N = 1 TO COUNT(ItemLotNos,@VM) + (ItemLotNos NE '') LOCATE ItemLotNos<1,N> IN CheckArray USING @VM SETTING Pos THEN CheckArray = CheckArray + ItemLotQtys<1,N> END ELSE CheckArray = INSERT(CheckArray,CA$ITEM_NO,Pos,0,OrderDetailList) CheckArray = INSERT(CheckArray,CA$LOT_NO,Pos,0,ItemLotNos<1,N>) CheckArray = INSERT(CheckArray,CA$LOT_QTY,Pos,0,ItemLotQtys<1,N>) CheckArray = INSERT(CheckArray,CA$CUST_PART_NO,Pos,0,OrderDetailList) CheckArray = INSERT(CheckArray,CA$SUB_PART_NO,Pos,0,OrderDetailList) CheckArray = INSERT(CheckArray,CA$VERIFY_PART_NO,Pos,0,VerifyPartNo) CheckArray = INSERT(CheckArray,CA$SUB_SUPP_BY,Pos,0,SubSuppBy) END NEXT N END NEXT I FOR I = 1 TO COUNT(CassList,@FM) + (CassList NE '') CassLotNo = CassList CassQty = CassList LOCATE CassLotNo IN CheckArray USING @VM SETTING Pos THEN CheckArray = CheckArray - CassQty ;* Back out lot qtys already scanned END NEXT I CheckArray = '':@FM:CheckArray END ;* End of check for Order Number present *********************************** ScanResults = Dialog_Box('DIALOG_WO_SCAN', @WINDOW, CheckArray) ;* Returns a line for each cassette scanned, checked, filled in or override data IF ScanResults = 'Cancel' THEN RETURN WOMatCreateStartTime = Time() * * * * * * New 3/9/2011 * * * * * * ProdOrderNo = WORec ProdVerNo = WORec CustNo = WORec ProdVerRec = XLATE('PROD_VER',ProdVerNo,'','X') ProcStepPSNs = ProdVerRec ReactType = ProdVerRec ;* This is in 3 letter code version SpecType = XLATE('PROD_SPEC',ProcStepPSNs[-1,'B':@VM],'SPEC_TYPE','X') ;* Shipping PSN Spec Type CustEpiPartRec = XLATE('CUST_EPI_PART',CustNo:'*':EpiPartNo,'','X') ;* Added 7/31/2012 JCH MUWaferFlag = CustEpiPartRec ;* Added 7/31/2012 JCH RetRejects = CustEpiPartRec ;* Added 7/31/2012 JCH IF SpecType = 'Q' THEN CassShipQty = '' ;* If Spec is in Qual Mode then no Quantity is used END ELSE CassShipQty = CustEpiPartRec END MinCassShipQty = CustEpiPartRec ShipShort = CustEpiPartRec ;* Added 7/31/2012 JCH Reprocessed = '' ;* Added 12/16/2009 JCH to match parms passed to obj_WO_Mat('Create RelStamps = Get_Property(@WINDOW:'.REL_STAMP','ARRAY') Released = '' IF RelStamps[-1,'B*'] = '' THEN Released = 0 ELSE Released = 1 IF ReactType = 'GAN' THEN GOTO RecGaN ;* * * * * * * * * * * IF ExistCassCnt >= 1 THEN IF Released THEN Resp = 1 ;* 12/13/20007 - JCH added to limit replace function to unreleased WO's END ELSE TypeOver = '' TypeOver = 'Add or Replace Work Order Cassette Information' TypeOver = 'Do you wish to Add To or Replace the existing cassette information?' TypeOver = 'B&Add,&Replace,&Cancel' Resp = Msg(@WINDOW,TypeOver) END IF Resp = 3 THEN RETURN ;* Canceled IF Resp = 1 THEN * Add to Existing NewCassetteCnt = COUNT(ScanResults,@VM) + (ScanResults NE '') Def = '' Def = 'Receiving Cassettes...' Def = 'G' Def = NewCassetteCnt Def = 600 MsgUp = Msg(@WINDOW,Def) FOR I = 1 TO NewCassetteCnt Msg(@WINDOW, MsgUp, I, MSGINSTUPDATE$) ScanLotNo = ScanResults ScanQty = ScanResults ScanPartNo = ScanResults ScanOrdItem = ScanResults ScanVendor = ScanResults ;* Added 7/14/2011 for SAP project JCH IF ScanLotNo NE '' AND ScanQty NE '' AND ScanPartNo NE '' AND ScanOrdItem NE '' THEN CassNo = ExistCassCnt + 1 Parms = WONo:@RM Parms := CassNo:@RM Parms := ProdVerNo:@RM Parms := ScanResults:@RM Parms := ScanResults:@RM Parms := ScanResults:@RM ;* This is the CUSTOMER part No Parms := ScanResults:@RM Parms := ReactType:@RM ;* 3 character Reactor Type Code Parms := ScanResults:@RM Parms := 'SR':@RM ;* Warehouse = 'SR' - Shipping/Receiving Area Parms := 'RB':@RM ;* Location = 'RB' - Receiving Bench Parms := ScanResults:@RM Parms := ScanResults:@RM Parms := SubSuppBy:@RM Parms := MUWaferFlag:@RM Parms := RetRejects :@RM ;* Added 8/18/2009 JCH Parms := Reprocessed:@RM ;* Added 12/16/2009 JCH Parms := CassShipQty:@RM ;* Added 11/4/2009 JCH Parms := ShipShort:@RM ;* Added 05/14/2010 JCH Parms := ScanVendor:@RM ;* Added 07/14/2011 for SAP Project JCH Parms := MinCassShipQty ; // Added 02/01/2018 dmb obj_WO_Mat('Create',Parms) ;* Added 10/18/2006 JCH - New Work Order material subsystem. ExistCassCnt += 1 WOMatKey = WONo:'*':CassNo LOCATE WOMatKey IN WOMatKeys BY 'AR' USING @VM SETTING NewPos ELSE WOMatKeys = INSERT(WOMatKeys,1,NewPos,0,WOMatKey) END END NEXT I Msg(@WINDOW,MsgUp) ScanResults = CassArray Scheduled = XLATE('WO_LOG',WONo,'SCHEDULED','X') IF Scheduled THEN * Message to production about change in Work Order Size Recipients = XLATE('NOTIFICATION','MAST_SCHED_BEG',NOTIFICATION_USER_ID$,'X') ;* Added 10/03/2005 JCH - J.C. Henry & Co., Inc OtherRecipients = XLATE('NOTIFICATION','MAST_SCHED_END',NOTIFICATION_USER_ID$,'X') ;* Added 10/03/2005 JCH - J.C. Henry & Co., Inc FOR N = 1 TO COUNT(OtherRecipients,@VM) + (OtherRecipients NE '') OtherRecip = OtherRecipients<1,N> LOCATE OtherRecip IN Recipients USING @VM SETTING Pos ELSE Recipients = INSERT(Recipients,1,Pos,0,OtherRecip) END NEXT N SentFrom = @USER4 Subject = 'Cassettes Added to Work Order' Message = NewCassetteCnt:" Cassettes have been added to Scheduled Work Order ":WONo AttachWindow = 'WO_PROD' AttachKey = WONo SendToGroup = '' Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup *obj_Notes('Create',Parms) END END END ELSE * Loop through ScanResults and call obj_WO_Mat('Create') NewCassetteCnt = COUNT(ScanResults,@VM) + (ScanResults NE '') Def = '' Def = 'Receiving Cassettes...' Def = 'G' Def = NewCassetteCnt Def = 600 MsgUp = Msg(@WINDOW,Def) FOR I = 1 TO NewCassetteCnt Msg(@WINDOW, MsgUp, I, MSGINSTUPDATE$) CassNo = I Parms = WONo:@RM Parms := CassNo:@RM Parms := ProdVerNo:@RM Parms := ScanResults:@RM Parms := ScanResults:@RM Parms := ScanResults:@RM Parms := ScanResults:@RM Parms := ReactType:@RM Parms := ScanResults:@RM Parms := 'SR':@RM ;* Warehouse = 'SR' - Shipping/Receiving Area Parms := 'RB':@RM ;* Location = 'RB' - Receiving Bench Parms := ScanResults:@RM Parms := ScanResults:@RM Parms := SubSuppBy:@RM Parms := MUWaferFlag:@RM Parms := RetRejects:@RM ;* Added 8/18/2009 JCH Parms := Reprocessed:@RM ;* Added 12/16/2009 JCH Parms := CassShipQty:@RM ;* Added 11/4/2009 JCH Parms := ShipShort:@RM ;* Added 05/14/2010 JCH Parms := ScanResults:@RM ;* Added 07/14/2011 for SAP project JCH Parms := MinCassShipQty ; // Added 02/01/2018 dmb obj_WO_Mat('Create',Parms) ;* Added 10/18/2006 JCH - New Work Order material subsystem. ExistCassCnt += 1 WOMatKey = WONo:'*':CassNo LOCATE WOMatKey IN WOMatKeys BY 'AR' USING @VM SETTING NewPos ELSE WOMatKeys = INSERT(WOMatKeys,1,NewPos,0,WOMatKey) END NEXT I Msg(@WINDOW,MsgUp) END Set_Property(CtrlEntID,'DEFPROP',ScanResults) IF ScanResults NE '' THEN Recipients = XLATE('NOTIFICATION','MATERIAL_RECEIPT',NOTIFICATION_USER_ID$,'X') ;* Added 10/04/2005 JCH - J.C. Henry & Co., Inc SentFrom = @USER4 Subject = 'Cassettes Received for Work Order' Message = "Cassettes have been received for Work Order ":WONo 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 Set_Property(@WINDOW:'.RX_BY','DEFPROP',OCONV(@USER4,'[XLATE_CONV,LSL_USERS*FIRST_LAST]')) ;* Current user Set_Property(@WINDOW:'.RX_DTM','DEFPROP',OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS') ) ;* Current timestamp Set_Property(@WINDOW:'.WO_MAT_KEY','DEFPROP',WOMatKeys) Send_Event(@WINDOW,'WRITE') WOMatCreateStopTime = Time() FormRefreshStartTime = Time() // Update RX_QTY_STATIC Work_Order_Services('UpdateReceivedQty', WONo) obj_AppWindow('LoadFormKeys','WO_REC':@RM:WONo) FormRefreshStopTime = Time() WOMatCreateDuration = WOMatCreateStopTime - WOMatCreateStartTime FormRefreshDuration = FormRefreshStopTime - FormRefreshStartTime TotalDuration = WOMatCreateDuration + FormRefreshDuration If Unassigned(NewCassetteCnt) then NewCassetteCnt = NewCassetteCnt = COUNT(ScanResults,@VM) + (ScanResults NE '') end NumCass = NewCassetteCnt LogData = '' LogData<1> = Oconv(Date(), 'D4/') : ' ' : Oconv(Time(), 'MTS') LogData<2> = WONo LogData<3> = @User4 LogData<4> = NumCass LogData<5> = WOMatCreateDuration LogData<6> = FormRefreshDuration LogData<7> = TotalDuration If NumCass GT 0 then LogData<8> = TotalDuration / NumCass end else LogData<8> = 'N/A' end Logging_Services('AppendLog', objReceiveLog, LogData, @RM, @FM) RETURN *********************************************************************************************************************************************************** * * * * * * * RecGaN: * * * * * * * WfrsRxd = SUM(ScanResults<3>) ;* Total Wafers received CassettesRxd = COUNT(ScanResults<1>,@VM) + (ScanResults<1> NE '') ;* Total Cassettes received * IF CassShipQty <= 0 THEN CassShipQty = 25 CassShipQty = 25 ;! We are hardcoding this to 25 WOMatReq = INT(WfrsRxd/CassShipQty) ;* Qty of WO_MAT records required IF MOD(WfrsRxd,CassShipQty) THEN WOMatReq += 1 ;* Add another WO_MAT for a short qty box at the end END PSNo = ProdVerStepPSNs<1,1> ;* This is GaN => single WO Step WfrSigProfile = obj_Prod_Spec('GetWfrSigProfile',PSNo) ;* Final QA signature on the shipping cassette. (like EpiPro) LastInCassNo = '' LastOutCassNo = '' * * * * Loop through existing WOMatKeys and set pointers for newly received information * * * * IF WOMatKeys NE '' THEN womCnt = COUNT(WOMatKeys,@VM) + (WOMatKeys NE '') FOR I = 1 TO womCnt WOMatKey = WOMatKeys<1,I> RxDTM = XLATE('WO_MAT',WOMatKey,WO_MAT_RX_DTM$,'X') IF RxDTM NE '' THEN LastInCassNo = I ;* This assumes cassettes received are in numerical order and none have been deleted out of sequence END LastOutCassNo = I NEXT I END Def = '' Def = 'Receiving Cassettes...' Def = 'G' Def = CassettesRxD Def = 600 MsgUp = Msg(@WINDOW,Def) NextInCassNo = LastInCassNo + 1 NextOutCassNo = LastOutCassNo + 1 FOR I = 1 TO WOMatReq Msg(@WINDOW, MsgUp, I, MSGINSTUPDATE$) WOMatExists = '' CassNo = NextInCassNo WOMatKey = WONo:'*':CassNo LOCATE WOMatKey IN WOMatKeys BY 'AR' USING @VM SETTING NewPos ELSE WOMatKeys = INSERT(WOMatKeys,1,NewPos,0,WOMatKey) END IF ScanResults<1,I> NE '' THEN otParms = 'WO_MAT':@RM:WOMatKey WOMatRec = obj_Tables('ReadRec',otParms) ;* WOMat record may be an outbound on IF Get_Status(errCode) THEN DEBUG END IF WOMatRec NE '' THEN WOMatExists = 1 RxDTM = ScanResults RxDTM = ICONV( ScanResults , 'DT' ) RxBy = ScanResults IF WOMatExists THEN * * Add Receiving information to existing * * WO_MAT record WOMatRec = ScanResults WOMatRec = ScanResults WOMatRec = ScanResults WOMatRec = ScanResults WOMatRec = ScanResults WOMatRec = ScanResults WOMatRec = RxDTM WOMatRec = RxBy WOMatRec = 'SR' ;* Shipping/Receiving WOMatRec = 'RB' ;* Receiving bench WOMatRec = 'RCVD' WOMatRec = RxDTM WOMatRec = '' ;* No tag actually scanned -> so no tag value WOMatRec = RxBy WOMatRec = RxDTM WOMatRec = RxBy WaferCnt = WOMatRec ;* Changed to add slots for both EpiPRO and standard reactor types 8/13/2010 JCH ShipCnt = WOMatRec BEGIN CASE CASE ShipCnt = '' ; SlotCnt = WaferCnt CASE WaferCnt > ShipCnt ; SlotCnt = WaferCnt CASE WaferCnt < ShipCnt ; SlotCnt = ShipCnt CASE WaferCnt = ShipCnt ; SlotCnt = ShipCnt END CASE FOR S = 1 TO SlotCnt WOMatRec = S NEXT S otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec) obj_Tables('WriteRec',otParms) IF Get_Status(errCode) THEN DEBUG END END ELSE * * Create new WO_MAT record with Receiving Data * * WOMatRec = '' WOMatRec = ScanResults WOMatRec = ScanResults WOMatRec = ScanResults WOMatRec = ScanResults WOMatRec = ScanResults WOMatRec = ScanResults WOMatRec = RxDTM WOMatRec = RxBy WOMatRec = 'SR' ;* Shipping/Receiving WOMatRec = 'RB' ;* Receiving bench WOMatRec = 'RCVD' WOMatRec = RxDTM WOMatRec = '' ;* No tag actually scanned -> so no tag value WOMatRec = RxBy WOMatRec = RxDTM WOMatRec = RxBy WOMatRec = ProdVerNo WOMatRec = SubSuppBy WOMatRec = MUWaferFlag WOMatRec = RetRejects WOMatRec = CassShipQty WOMatRec = MinCassShipQty WOMatRec = ShipShort WOMatRec = obj_WO_Mat('CassSigProfile',WOMatKey) ;******************* WaferCnt = WOMatRec ;* Changed to add slots for both EpiPRO and standard reactor types 8/13/2010 JCH ShipCnt = WOMatRec BEGIN CASE CASE ShipCnt = '' ; SlotCnt = WaferCnt CASE WaferCnt > ShipCnt ; SlotCnt = WaferCnt CASE WaferCnt < ShipCnt ; SlotCnt = ShipCnt CASE WaferCnt = ShipCnt ; SlotCnt = ShipCnt END CASE FOR S = 1 TO SlotCnt WOMatRec = S NEXT S otParms = FIELDSTORE(otParms,@RM,4,0,WOMatRec) obj_Tables('WriteRec',otParms) IF Get_Status(errCode) THEN DEBUG END END ;* End of check for existing WO_MAT record NextInCassNo += 1 IF NextInCassNo >= NextOutCassNo THEN NextOutCassNo += 1 END END ELSE * * Create new WO_MAT record without Receiving Data * * WOMatRec = '' WOMatRec = ProdVerNo WOMatRec = SubSuppBy WOMatRec = MUWaferFlag WOMatRec = RetRejects WOMatRec = CassShipQty WOMatRec = MinCassShipQty WOMatRec = ShipShort WOMatRec = obj_WO_Mat('CassSigProfile',WOMatKey) SlotCnt = WOMatRec FOR S = 1 TO SlotCnt WOMatRec = S NEXT S otParms = 'WO_MAT':@RM:WOMatKey:@RM:@RM:WOMatRec obj_Tables('WriteRec',otParms) IF Get_Status(errCode) THEN DEBUG END NextOutCassNo += 1 END ;* End of check to see if a new Out Only WO_MAT is needed NEXT I Msg(@WINDOW,MsgUp) ;* Take down processing message IF LastInCassNo > 0 THEN ScanResults = CassArray Scheduled = XLATE('WO_LOG',WONo,'SCHEDULED','X') IF Scheduled THEN * Message to production about change in Work Order Size Recipients = XLATE('NOTIFICATION','MAST_SCHED_BEG',NOTIFICATION_USER_ID$,'X') ;* Added 10/03/2005 JCH - J.C. Henry & Co., Inc OtherRecipients = XLATE('NOTIFICATION','MAST_SCHED_END',NOTIFICATION_USER_ID$,'X') ;* Added 10/03/2005 JCH - J.C. Henry & Co., Inc FOR N = 1 TO COUNT(OtherRecipients,@VM) + (OtherRecipients NE '') OtherRecip = OtherRecipients<1,N> LOCATE OtherRecip IN Recipients USING @VM SETTING Pos ELSE Recipients = INSERT(Recipients,1,Pos,0,OtherRecip) END NEXT N SentFrom = @USER4 Subject = 'Cassettes Added to Work Order' Message = CassettesRxd:" Cassettes have been added to Scheduled Work Order ":WONo AttachWindow = 'WO_PROD' AttachKey = WONo SendToGroup = '' Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup *obj_Notes('Create',Parms) END END ;* End of check for previously received material Set_Property(CtrlEntID,'DEFPROP',ScanResults) IF ScanResults NE '' THEN Recipients = XLATE('NOTIFICATION','MATERIAL_RECEIPT',NOTIFICATION_USER_ID$,'X') ;* Added 10/04/2005 JCH - J.C. Henry & Co., Inc SentFrom = @USER4 Subject = 'Cassettes Received for Work Order' Message = "Cassettes have been received for Work Order ":WONo 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 Set_Property(@WINDOW:'.RX_BY','DEFPROP',OCONV(@USER4,'[XLATE_CONV,LSL_USERS*FIRST_LAST]')) ;* Current user Set_Property(@WINDOW:'.RX_DTM','DEFPROP',OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS') ) ;* Current timestamp Set_Property(@WINDOW:'.WO_MAT_KEY','DEFPROP',WOMatKeys) Send_Event(@WINDOW,'WRITE') obj_AppWindow('LoadFormKeys','WO_REC':@RM:WONo) RETURN * * * * * * * AddLeftover: * * * * * * * RETURN