COMPILE FUNCTION Comm_WM_Out(Instruction, Parm1,Parm2) #pragma precomp SRP_PreCompiler /* Commuter module for WM_Out (Work Order Material - Inbound) window 05/22/2005 - John C. Henry, J.C. Henry & Co., Inc. 11/12/2018 - DJS - Updated VerifyFullBoxReject subroutine to set the SAP Batch No. as a rejected cassette. Previously this was being done prematurely in OBJ_WO_MAT('SignNCR'). 01/23/2019 - DJS - Added * Verify RDS Metrology has been completed * section to ensure all RDS records associated with the current WM_OUT record have metrology run data. 08/26/2019 - DJS - Updated the RDS Metrology verification section to use RDS_Services('VerifyEPPMetrology'), which contains code adapted from the RDS_POST_EPI FQA sign button event. 02/27/2025 - DJM - Added prompt to remove hold when creating NCR in 'RejMat' */ DECLARE SUBROUTINE Set_Property, Set_Status, ErrMsg, Set_Property, obj_AppWindow, Set_List_Box_Data, obj_Post_Log DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, Forward_Event, End_Window, Start_Window, obj_WO_Mat_Log DECLARE SUBROUTINE Send_Message, Print_Cass_Out, obj_WM_Out, obj_Notes, obj_WO_Mat, obj_Tables, Set_Property, obj_WO_Wfr DECLARE SUBROUTINE Start_Window, Obj_RDS, Database_Services, Rds_Services, Signature_Services, Wm_Out_Services, Sleepery DECLARE SUBROUTINE Logging_Services, Wo_Mat_Qa_Services, Error_Services, Post_Event, Wafer_Counter_Services, Hold_Services Declare subroutine Labeling_Services DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box, RowExists, obj_Tables DECLARE FUNCTION Dialog_Box, obj_WO_Log, MemberOf, obj_NCR, Send_Message, MemberOf, obj_WM_Out, NextKey, obj_MUWafers DECLARE FUNCTION Start_Window, Database_Services, Error_Services, Obj_WO_Mat, Obj_RDS, obj_Clean_Insp,SRP_Array DECLARE FUNCTION Signature_Services, Environment_Services, Logging_Services, obj_Clean_Insp, Wm_Out_Services DECLARE FUNCTION Wafer_Counter_Services, Datetime, Hold_Services $INSERT POPUP_EQUATES $INSERT LOGICAL $INSERT MSG_EQUATES $INSERT APPCOLORS $INSERT WM_OUT_EQUATES $INSERT WO_STEP_EQU $INSERT WO_MAT_EQUATES $INSERT ORDER_EQU $INSERT PROD_SPEC_EQUATES $INSERT PRS_STAGE_EQUATES $INSERT RDS_EQUATES $INSERT LSL_USERS_EQU $INSERT SECURITY_RIGHTS_EQU $INSERT QUOTE_SIGS_EQU $INSERT NOTIFICATION_EQU $INSERT RTI_STYLE_EQUATES $INSERT TOOL_EQUATES $INSERT TOOL_CLASS_EQUATES $INSERT EPI_PART_EQUATES $INSERT WO_LOG_EQUATES $INSERT COMPANY_EQUATES $INSERT CLEAN_INSP_EQUATES $INSERT REACT_RUN_EQUATES $INSERT WAFER_COUNTER_EQUATES EQU FONT_FACE_NAME$ TO 1 EQU FONT_HEIGHT$ TO 2 EQU FONT_WEIGHT$ TO 3 EQU FONT_ITALIC$ TO 4 EQU FONT_UNDERLINE$ TO 5 EQU FONT_WIDTH$ TO 6 EQU FONT_CHAR_SET$ TO 7 EQU FONT_PITCH_AND_FAMILY$ TO 8 EQU FONT_STRIKE_OUT$ TO 9 EQU FONT_OUT_PRECISION$ TO 10 EQU FONT_CLIP_PRECISION$ TO 11 EQU FONT_QUALITY$ TO 12 EQU COL$SLOT TO 1 EQU COL$RDS_NO TO 2 EQU COL$REACT_NO TO 3 EQU COL$RDS_STATUS TO 4 EQU COL$POCKET TO 5 EQU COL$ZONE TO 6 EQU COL$IN_CASS TO 7 EQU COL$IN_SLOT TO 8 EQU COL$SLOT_NCR TO 9 EQU COL$MU_WO_NO TO 10 EQU COL$MU_WO_STEP TO 11 EQU COL$MU_CASS_NO TO 12 EQU COL$MU_SLOT_NO TO 13 EQU COL$UMW_CASS_ID TO 14 EQU COL$UMW_SLOT_NO TO 15 EQU COL$MU_BY TO 16 EQU COL$MU_ADD_DATE TO 17 EQU COL$MU_REM_DATE TO 18 EQU COL$LS_ID TO 1 EQU COL$THICK_MIN_ALL TO 2 EQU COL$THICK_TARGET_ALL TO 3 EQU COL$THICK_MAX_ALL TO 4 EQU COL$THICK_UNITS_ALL TO 5 EQU COL$ON_HOLD_DTM TO 1 EQU COL$ON_HOLD_USER TO 2 EQU COL$ON_REASON TO 3 EQU COL$OFF_HOLD_DTM TO 4 EQU COL$OFF_HOLD_USER TO 5 EQU COL$OFF_REASON TO 6 EQU COL$INV_TAG TO 8 ;* Inventory history control on 2nd page EQU COL$MET_TEST TO 1 EQU COL$MET_TEST_DESC TO 2 EQU COL$MET_SLOT TO 3 EQU COL$MET_SLOT_DESC TO 4 EQU COL$MET_WFR_QTY TO 5 EQU COL$MET_MIN TO 6 EQU COL$MET_MAX TO 7 EQU COL$MET_RESULT TO 8 EQU COL$MET_STD_MAX TO 9 EQU COL$MET_STD_RESULT TO 10 EQU COL$MET_SIG TO 11 EQU COL$MET_SIG_DTM TO 12 EQU COL$LOG_FILE TO 1 EQU COL$LOG_DTM TO 2 EQU COL$ACTION TO 3 EQU COL$WH_CD TO 4 EQU COL$LOC_CD TO 5 EQU COL$WO_NOS TO 6 EQU COL$CASS_NOS TO 7 EQU COL$USER_ID TO 8 EQU COL$TAGS TO 9 EQU COL$TOOL_ID TO 10 EQU CRLF$ TO \0D0A\ EQU Comma$ TO ',' LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WM_OUT' LogDate = Oconv(Date(), 'D4/') LogTime = Oconv(Time(), 'MTS') LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' Makeup Flag Log.csv' Headers = 'Logging DTM' : @FM : 'WM_OUT Key' : @FM : 'Makeup Flag' : @FM : 'User' objLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, Comma$, Headers, '', False$, False$) LoggingDTM = LogDate : ' ' : LogTime ; // Logging DTM ErrTitle = 'Error in Comm_WM_Out' ErrorMsg = '' Result = '' If Get_Property('NDW_MAIN', 'VISIBLE') then AppMain = 'NDW_MAIN' end else AppMain = 'LSL_MAIN2' end BEGIN CASE CASE Instruction = 'Create' ; GOSUB Create CASE Instruction = 'Refresh' ; GOSUB Refresh CASE Instruction = 'Read' ; GOSUB Read CASE Instruction = 'Page' ; GOSUB Page CASE Instruction = 'Write' ; GOSUB Write CASE Instruction = 'Clear' ; GOSUB Clear CASE Instruction = 'Delete' ; GOSUB Delete CASE Instruction = 'Close' ; GOSUB Close CASE Instruction = 'WONoLF' ; GOSUB WONoLF CASE Instruction = 'FirstSurfscan' ; GOSUB FirstSurfscan CASE Instruction = 'PostCleanSurfscan' ; GOSUB PostCleanSurfscan CASE Instruction = 'SignSupVer' ; GOSUB SignSupVer CASE Instruction = 'SignSAP' ; GOSUB SignSAP CASE Instruction = 'RejMat' ; GOSUB RejMat CASE Instruction = 'NCRKeysDC' ; GOSUB NCRKeysDC CASE Instruction = 'HoldClick' ; GOSUB HoldClick CASE Instruction = 'HoldDC' ; GOSUB HoldDC CASE Instruction = 'PrintCass' ; GOSUB PrintCass CASE Instruction = 'AddMakeup' ; GOSUB AddMakeup CASE Instruction = 'RemMakeup' ; GOSUB RemMakeup CASE Instruction = 'RemSlots' ; GOSUB RemSlots CASE Instruction = 'MakeupClick' ; GOSUB MakeupClick CASE Instruction = 'SendMessage' ; GOSUB SendMessage CASE Instruction = 'ViewPSN' ; GOSUB ViewPSN CASE Instruction = 'RebuildLoad' ; GOSUB RebuildLoad CASE Instruction = 'ClearLoad' ; GOSUB ClearLoad CASE Instruction = 'MetTestDC' ; GOSUB MetTestDC CASE Instruction = 'LUPostCode' ; GOSUB LUPostCode CASE Instruction = 'CIClick' ; GOSUB CIClick CASE Instruction = 'AddComment' ; GOSUB AddComment CASE Instruction = 'ViewComments' ; GOSUB ViewComments CASE Instruction = 'ReprintHold' ; GOSUB ReprintHold CASE 1 ErrorMsg = 'Unknown Instruction ':QUOTE(Instruction):' passed to routine' END CASE IF ErrorMsg NE '' THEN ErrMsg(ErrTitle:@SVM:ErrorMsg) END RETURN Result * * * * * * * Create: * * * * * * * obj_Appwindow('Create',@WINDOW) * Provides compatibility with the existing messaging attachment system IF Parm1 NE '' THEN PassedKeys = Parm1 obj_Appwindow('ViewRelated',@WINDOW:@RM:PassedKeys) END Ctrls = @WINDOW:'.POST_BOAT_ID':@RM ; Props = 'LIST':@RM ; Vals = @VM:XLATE('LISTBOX_CONFIG','POSTCLEANCASSID',1,'X'):@RM Ctrls := @WINDOW:'.POST_CODE':@RM ; Props := 'LIST':@RM ; Vals := XLATE('LISTBOX_CONFIG','POSTCLEANCODE',1,'X'):@RM Ctrls := @WINDOW:'.POST_SRD_NO':@RM ; Props := 'LIST':@RM ; Vals := XLATE('LISTBOX_CONFIG','POSTCLEANSRD',1,'X'):@RM Ctrls := @WINDOW:'.SHIFT' ; Props := 'LIST' ; Vals := XLATE('LISTBOX_CONFIG','SHIFT',1,'X') CONVERT @VM TO @FM IN Vals Set_Property(Ctrls,Props,Vals) IF MemberOf(@USER4,'OI_ADMIN') THEN Set_Property(@WINDOW:'.VOID','VISIBLE',1) END ELSE Set_Property(@WINDOW:'.VOID','VISIBLE',0) END GOSUB Refresh RETURN * * * * * * * Read: * * * * * * * WMOKey = Get_Property(@WINDOW,'ID') IF RowExists('WM_OUT',WMOKey) THEN *IF NOT(Security_Check('Work Order',READ$)) THEN * Send_Event(@WINDOW,'CLEAR') * Security_Err_Msg('Work Order',READ$) * RETURN *END END ELSE ErrMsg('WM_OUT entries may only be created from the Work Order Release process.') Send_Event(@WINDOW,'CLEAR') RETURN END WONo = WMOKey[1,'*'] IF WONo NE '' THEN PriDisp = XLATE('WO_LOG',WONo,'PRI_DISPLAY','X') Set_Property(@WINDOW:'.PRI_DISPLAY_TEXT','TEXT',PriDisp) CurrFontProp = Get_Property(@WINDOW:'.PRI_DISPLAY_TEXT','FONT') NewFontProp = FIELD(CurrFontProp,@SVM,1,12) IF PriDisp[1,2] = 'P1' THEN Set_Property(@WINDOW:'.PRI_DISPLAY_TEXT','DEFPROP','P1 - High') NewFontProp<1,1,FONT_WEIGHT$> = 700 NewFontProp<1,1,FONT_ITALIC$> = 255 NewFontProp<1,1,FONT_WIDTH$> = 7 ForeColor = BRED$ END IF PriDisp[1,2] = 'P2' THEN Set_Property(@WINDOW:'.PRI_DISPLAY_TEXT','DEFPROP','P2 - Medium') NewFontProp<1,1,FONT_WEIGHT$> = 400 NewFontProp<1,1,FONT_ITALIC$> = 255 NewFontProp<1,1,FONT_WIDTH$> = 6 ForeColor = BYELLOW$ END IF PriDisp[1,2] = 'P3' THEN Set_Property(@WINDOW:'.PRI_DISPLAY_TEXT','DEFPROP','P3 - Low') NewFontProp<1,1,FONT_WEIGHT$> = 400 NewFontProp<1,1,FONT_ITALIC$> = 0 NewFontProp<1,1,FONT_WIDTH$> = 6 ForeColor = FONTGREEN$ END Set_Property(@WINDOW:'.PRI_DISPLAY_TEXT','FONT', NewFontProp) Set_Property(@WINDOW:'.PRI_DISPLAY_TEXT','FORECOLOR',ForeColor) END ;* End of check for window GOSUB Refresh RETURN * * * * * * * Write: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') WOStep = Get_Property(@WINDOW:'.PROC_STEP_NO','DEFPROP') CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP') WMOKey = WONo:'*':WOStep:'*':CassNo If WMOKey NE '**' then OrigFqaWCQty = Get_Property(@Window, '@ORIG_WFR_CTR_QTY') CurrFqaWCQty = Get_Property(@Window:'.EDL_WAFER_COUNTER_QTY', 'TEXT') If OrigFqaWCQty NE CurrFqaWCQty then Wafer_Counter_Services('AddScan', WMOKey, CurrFqaWCQty, Datetime(), '', @User4, 'QA', '') end end Forward_Event() Set_Status(0) errCode = '' IF Get_Status(errCode) THEN ErrMsg(errCode) END Result = 0 RETURN * * * * * * * Clear: * * * * * * * GOTO Refresh RETURN * * * * * * * Delete: * * * * * * * ErrMsg('Records may not be modified or deleted.') Result = 0 ;* No Deletes RETURN * * * * * * * Close: * * * * * * * Set_Property('SYSTEM','MODAL',0:@FM:@WINDOW) obj_Appwindow('DetailReturn') RETURN * * * * * * * * AddComment: * * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','TEXT') WONo = WONo : '*' : Get_Property(@WINDOW:'.PROC_STEP_NO','TEXT') WONo = WONo : '*' : Get_Property(@WINDOW:'.OUT_CASS_NO','TEXT') If WONo NE '' then Response = Dialog_Box('NDW_ADD_RDS_COMMENT', @Window) If Response NE '' then WM_OUT_Services('AddComment', WONo, Response) end return * * * * * * * * ViewComments: * * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','TEXT') WONo = WONo : '*' : Get_Property(@WINDOW:'.PROC_STEP_NO','TEXT') WONo = WONo : '*' : Get_Property(@WINDOW:'.OUT_CASS_NO','TEXT') If WONo NE '' then Response = Dialog_Box('NDW_WM_OUT_COMMENT_VIEWER', @Window, WONo) return * * * * * * * WONoLF: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') IF INDEX(WONo,'.',1) > 0 THEN CONVERT '.' TO '*' IN WONo Set_Property(@WINDOW:'.WO_NO','DEFPROP','') obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WONo) END RETURN * * * * * * * ReprintHold: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP') WOStep = Get_Property(@WINDOW:'.PROC_STEP_NO','DEFPROP') WMOKey = WONo:'*':WOStep:'*':CassNo Labeling_Services('ReprintHoldLabel', 'WM_OUT', WMOKey) RETURN ******** Refresh: ******** IF MemberOf(@USER4,'OI_ADMIN') THEN Set_Property(@WINDOW:'.WO_MAT_WMO_CURR_STATUS','VISIBLE',1) END ELSE Set_Property(@WINDOW:'.WO_MAT_WMO_CURR_STATUS','VISIBLE',0) END IF Get_Property(@WINDOW:'.HOLD_CHECKBOX','CHECK') THEN Set_Property(@WINDOW:'.HOLD_BUTTON','TEXT','Remove Hold') Set_Property(@Window:'.MENU.PRINT.REPRINT_HOLD_LABEL', 'ENABLED', True$) END ELSE Set_Property(@WINDOW:'.HOLD_BUTTON','TEXT','Place on Hold') Set_Property(@Window:'.MENU.PRINT.REPRINT_HOLD_LABEL', 'ENABLED', False$) END QuoteSigs = XLATE('CONFIG','QUOTE_SIGS','','X') MakeupBox = Get_Property(@WINDOW:'.MAKEUP_BOX','CHECK') IF NOT(MakeupBox) THEN IF MemberOf(@USER4,'EPI_BACKFILL') OR MemberOf(@USER4,'OI_ADMIN') THEN Set_Property(@WINDOW:'.BACKFILL_BUTTON','VISIBLE',1) Set_Property(@WINDOW:'.REM_BACKFILL_BUTTON','VISIBLE',1) END ELSE Set_Property(@WINDOW:'.BACKFILL_BUTTON','VISIBLE',0) Set_Property(@WINDOW:'.REM_BACKFILL_BUTTON','VISIBLE',0) END END ELSE Set_Property(@WINDOW:'.BACKFILL_BUTTON','VISIBLE',0) Set_Property(@WINDOW:'.REM_BACKFILL_BUTTON','VISIBLE',0) END QuoteSigInfo = XLATE('CONFIG','QUOTE_SIGS','','X') Supervisors = QuoteSigInfo:@FM Supervisors := QuoteSigInfo:@FM Supervisors := QuoteSigInfo:@FM Supervisors := QuoteSigInfo LOCATE @USER4 IN Supervisors USING @FM SETTING SPos THEN ShiftSuper = 1 END ELSE ShiftSuper = 0 END IF ShiftSuper OR MemberOf(@USER4,'OI_ADMIN') THEN Set_Property(@WINDOW:'.REM_MU_WFR_BUTTON','VISIBLE',1) END ELSE Set_Property(@WINDOW:'.REM_MU_WFR_BUTTON','VISIBLE',0) END IF MemberOf(@USER4,'OI_ADMIN') THEN Set_Property(@WINDOW:'.REM_SLOT_BUTTON','VISIBLE',1) Set_Property(@WINDOW:'.REBUILD_LOAD','VISIBLE',1) Set_Property(@WINDOW:'.CLEAR_LOAD','VISIBLE',1) END ELSE Set_Property(@WINDOW:'.REM_SLOT_BUTTON','VISIBLE',0) Set_Property(@WINDOW:'.REBUILD_LOAD','VISIBLE',0) Set_Property(@WINDOW:'.CLEAR_LOAD','VISIBLE',0) END WONo = Get_Property(@Window:'.WO_NO', 'TEXT') IF ( (MemberOf(@USER4,'MASTER_SCHED')) OR (MemberOf(@USER4,'SUPERVISOR')) OR (MemberOf(@USER4,'ENGINEERING')) OR (MemberOf(@USER4,'LEAD')) OR (MemberOf(@USER4,'OI_ADMIN')) ) THEN Set_Property(@WINDOW:'.MAKEUP_BOX','ENABLED',1) END ELSE Set_Property(@WINDOW:'.MAKEUP_BOX','ENABLED',0) END RemSlots = Get_Property(@WINDOW:'.REM_SLOTS','DEFPROP') IF RemSlots > 0 THEN Set_Property(@WINDOW:'.MAKEUP_WAFER_BUTTON','ENABLED',1) END ELSE Set_Property(@WINDOW:'.MAKEUP_WAFER_BUTTON','ENABLED',0) END IF Get_Property(@WINDOW:'.MAKEUP_BOX','CHECK') = 1 THEN MakeupBox = 1 Set_Property(@WINDOW:'.BOX_TYPE','VISIBLE',1) END ELSE MakeupBox = 0 Set_Property(@WINDOW:'.BOX_TYPE','VISIBLE',0) END IF Get_Property(@WINDOW:'.PS_TYPE','DEFPROP')[1,4] = 'Qual' THEN QualRun = 1 END ELSE QualRun = 0 END Ctrls = @WINDOW:'.POST_CODE':@RM ; Props = 'ENABLED':@RM Ctrls := @WINDOW:'.POST_BOAT_ID':@RM ; Props := 'ENABLED':@RM Ctrls := @WINDOW:'.POST_SRD_NO' ; PRops := 'ENABLED' PostEpiSig = Get_Property(@WINDOW:'.POST_EPI_SIG','DEFPROP') IF PostEpiSig NE '' THEN Vals = '0':@RM:'0':@RM:'0' END ELSE Vals = '1':@RM:'1':@RM:'1' END Set_Property(Ctrls,Props,Vals) * Out of spec RDS CtrlName = @WINDOW:'.SLOT' CassArray = Get_Property(CtrlName,'INVALUE') RdsStatuses = CassArray IF INDEX(RdsStatuses,'SPEC',1) THEN OutOfSpec = 1 ELSE OutOfSpec = 0 IF INDEX(RdsStatuses,'ULMET',1) THEN MissingMet = 1 ELSE MissingMet = 0 * 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) CtrlName = @WINDOW:'.NCR_KEYS' NCRList = Get_Property(CtrlName,'LIST') ShipShort = Get_Property(@WINDOW:'.SHIP_SHORT','CHECK') OpenNCR = 0 ColCount = COUNT(NCRList<1>,@VM) + (NCRList<1> NE '') FOR Line = 1 TO COUNT(NCRList,@FM) + (NCRList NE '') Status = NCRList BEGIN CASE CASE Status = '' ; Color = WHITE$ CASE Status = 'Closed' ; Color = GREEN$ CASE Status = 'Open' ; Color = RED$ CASE Status = 'Verified' ; Color = YELLOW$ CASE 1 ; Color = WHITE$ END CASE IF Color = RED$ THEN OpenNCR = 1 FOR Col = 1 TO ColCount stat = Send_Message(CtrlName,'COLOR_BY_POS',Col,Line,Color) NEXT Col NEXT Line OpenSlots = Get_Property(@WINDOW:'.REM_SLOTS','DEFPROP') IF MakeupBox THEN OpenSlots = 0 ;*Added to ignore MU box slots dkk 11/3/15 IF OpenNCR = 0 AND OutOfSpec = 0 AND MissingMet = 0 And OpenSlots = 0 THEN OKtoSign = 1 END ELSE OKtoSign = 0 END WONo = Get_Property(@Window : '.WO_NO', 'TEXT') StepNo = Get_Property(@Window : '.PROC_STEP_NO', 'TEXT') OutCassNo = Get_Property(@Window : '.OUT_CASS_NO', 'TEXT') WOMatKey = WONO : '*' : OutCassNo WMOKey = WONo : '*' : StepNo : '*' : OutCassNo WMORec = Database_Services('ReadDataRow', 'WM_OUT', WMOKey) MUAddDTMS = WMORec MURemDTMS = WMORec List = Get_Property(@Window : '.SLOT', 'LIST') NumRows = DCount(List, @FM) For fPos = 1 to NumRows Row = List Row<1, COL$MU_REM_DATE> = OConv(MURemDTMS<1, fPos, 1>, 'DT2/^H') ; // Grab only the most recent datetime to display Row<1, COL$MU_ADD_DATE> = OConv(MUAddDTMS<1, fPos, 1>, 'DT2/^H') List = Row Next fPos Set_Property(@Window : '.SLOT', 'LIST', List) * All SLOT detail background colors OutOfSpecBox = 0 CtrlName = @WINDOW:'.SLOT' CassArray = Get_Property(CtrlName,'INVALUE') RdsStatuses = CassArray MU_WONos = CassArray ;* CHANGED 5/18/2007 JCH ******************* SlotNos = CassArray FOR I = 1 TO COUNT(SlotNos,@VM) + (SlotNos NE '') RdsStatus = RdsStatuses<1,I> MU_WONo = MU_WONos<1,I> IF NOT(ShipShort) THEN IF OKtoSign AND SlotNos<1,I> NE '' THEN ;* Added check for null slot JCH 04/11/2007 SlotFull = CassArray NE '' AND CassArray NE '' IF NOT(SlotFull) AND NOT(MakeupBox) AND NOT(QualRun) THEN OKtoSign = 0 IF RdsStatus[1,3] = 'Out' THEN OutOfSpecBox = 1 END END BEGIN CASE CASE MU_WONo NE '' ; LineColor = MU_GREEN$ CASE RdsStatus = 'RLOAD' ; LineColor = INP_BLUE$ ;* xxx Load CASE RdsStatus = 'LOAD' ; LineColor = GREEN$ ;* Loaded CASE RdsStatus = 'ULOAD' ; LineColor = LTGREY$ ;* EpiPRO Unloaded & Met complete CASE RdsStatus = 'ULMET' ; LineColor = YELLOW$ ;* EpiPro Unloaded Needs Metrology CASE RdsStatus = 'TLOAD' ; LineColor = ORANGE$ ;* EpiPRO Test CASE RdsStatus = 'ULOAD' ; LineColor = LTORANGE$ ;* EpiPRO Test CASE RdsStatus = 'SPEC' ; LineColor = RED$ ;* Out of Spec CASE 1 ; LineColor = WHITE$ END CASE stat = Send_Message(CtrlName,'COLOR_BY_POS',0,I,LineColor) NEXT I IF MemberOf(@USER4,'OI_ADMIN') THEN Set_Property(@WINDOW:'.SIGN_SAP','VISIBLE',1) END ELSE Set_Property(@WINDOW:'.SIGN_SAP','VISIBLE',0) END GoSub RefreshWaferCounterData IF OutOfSpec THEN Set_Property(@WINDOW:'.SIGN_SUP_VER','ENABLED',0) Set_Property(@WINDOW:'.SIGN_POST','ENABLED',0) END ELSE Set_Property(@WINDOW:'.SIGN_POST','ENABLED',1) IF OKtoSign OR MemberOf(@USER4, 'OI_SUPERUSER') THEN Set_Property(@WINDOW:'.SIGN_SUP_VER','ENABLED',1) END ELSE Set_Property(@WINDOW:'.SIGN_SUP_VER','ENABLED',0) END END CtrlName = @WINDOW:'.INV_WH' InvArray = Get_Property(CtrlName,'INVALUE') TagIDs = InvArray TagCnt = COUNT(TagIDs,@VM) + (TagIDs NE '') FOR I = 1 TO TagCnt InvTag = InvArray BEGIN CASE CASE InvTag[1,1] = 'I' ; LineColor = PRE_BLUE$ CASE InvTag[1,1] = 'O' ; LineColor = YELLOW$ CASE 1 ; LineColor = GREEN$ END CASE stat = Send_Message(CtrlName,'COLOR_BY_POS',0,I,LineColor) NEXT I ThickSpecs = Get_Property(@WINDOW:'.THICK_MIN_ALL','LIST') ADERead = Get_Property(@WINDOW:'.ADE_READ','DEFPROP') IF ADERead NE '' THEN RowCnt = COUNT(ThickSpecs,@FM) + (ThickSpecs NE '') FOR I = RowCnt TO 1 STEP -1 RowData = ThickSpecs UNTIL RowData NE @VM:@VM:@VM:@VM NEXT I IF ADERead < RowData<1,COL$THICK_MIN_ALL> OR ADERead > RowData<1,COL$THICK_MAX_ALL> THEN Set_Property(@WINDOW:'.ADE_READ','BACKCOLOR',RED$) END ELSE Set_Property(@WINDOW:'.ADE_READ','BACKCOLOR',WHITE$) END END ELSE Set_Property(@WINDOW:'.ADE_READ','BACKCOLOR',WHITE$) END // Color QA Metrology test rows CtrlName = @WINDOW:'.MET_TEST' MetList = Get_Property(CtrlName,'LIST') MLCnt = COUNT(MetList,@FM) + (MetList NE '') FOR Line = 1 TO MLCnt IF MetList NE '' THEN BEGIN CASE CASE (MetList = '') Color = YELLOW$ CASE ((MetList < MetList) OR (MetList > MetList)) Color = RED$ CASE ((MetList NE '') AND (MetList = '')) Color = YELLOW$ CASE Otherwise$ Color = GREEN$ END CASE END else Color = '' end stat = Send_Message(CtrlName,'COLOR_BY_POS',0,Line,Color) NEXT Line * 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:'.NCR_KEYS' AND ETCtrl NE @WINDOW:'.SLOT' AND ETCtrl NE @WINDOW:'.INV_WH' AND ETCtrl NE @WINDOW:'.MET_TEST' 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 * * * * * * * CIClick: * * * * * * * Ctrls = @WINDOW:'.WO_NO':@RM ; Props = 'DEFPROP':@RM Ctrls := @WINDOW:'.PROC_STEP_NO':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.OUT_CASS_NO':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.EPO_CI_NO':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.PS_NO' ; Props := 'DEFPROP' Vals = Get_Property(Ctrls,Props) WONo = Vals[1,@RM] StepNo = Vals[COL2()+1,@RM] CassNo = Vals[COL2()+1,@RM] CINo = Vals[COL2()+1,@RM] PSNo = Vals[COL2()+1,@RM] IF WONo = '' OR CassNo = '' THEN RETURN IF CINo = '' THEN MsgHead = 'Create Clean_Insp Record' MsgText = 'Are you sure you wish to create a Clean_Insp record for this stage?' OK = Msg(@WINDOW,'','YESNO','',MsgHead:@FM:MsgText) IF NOT(OK) THEN RETURN oCIParms = WONo:@RM oCIParms := StepNo:@RM oCIParms := CassNo:@RM oCIParms := 'POST':@RM oCIParms := '':@RM ;* RDSNo passed as null oCIParms := PSNo:@RM oCIParms := '' ;* PSRec passed as null CINo = obj_Clean_Insp('Create',oCIParms) IF Get_Status(errCode) THEN ErrMsg(errCode) RETURN END obj_Post_Log('Create','WO_MAT':@RM:WONo:'*':CassNo:@RM:WO_MAT_EPO_CI_NO$:@RM:CINo) END ;* End of check for null CINo IF CINo NE '' THEN Send_Event(@WINDOW,'WRITE') Send_Event(@WINDOW,'CLEAR') ; // 12/22/2017 - DMB - Although WRITE normally clears the form, QBF mode will prevent the clear so do this explicitly so the lock is removed from the RDS record. DetWindow = 'CLEAN_INSP' DetKeys = CINo DefaultRec = '' RetKey = WONo:'*':StepNo:'*':CassNo RetWin = @WINDOW RetPage = 1 RetCtrl = @WINDOW:'.CLEAN_INSP_BUTTON' RetPos = '' obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos) END RETURN * * * * * * * LUPostCode: * * * * * * * ToolKeys = XLATE('TOOL_CLASS','AKRION',TOOL_CLASS_TOOL$,'X') ToolKeys<1,-1> = XLATE('TOOL_CLASS','WET BENCH',TOOL_CLASS_TOOL$,'X') TypeOver = '' TypeOver = 'K' TypeOver = ToolKeys ToolID = Popup(@WINDOW,TypeOver,'TOOLS') IF ToolID = '' THEN RETURN obj_Appwindow('LUValReturn',ToolID:@RM:@WINDOW:'.POST_CODE') RETURN * * * * * * * FirstSurfscan: * * * * * * * Ctrls = @WINDOW:'.WO_NO':@RM ; Props = 'DEFPROP':@RM Ctrls := @WINDOW:'.PROC_STEP_NO':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.OUT_CASS_NO' ; Props := 'DEFPROP' Vals = Get_Property(Ctrls,Props) WONo = Vals[1,@RM] ProcStepNo = Vals[COL2()+1,@RM] OutCassNo = Vals[COL2()+1,@RM] IF WONo NE '' AND ProcStepNo NE '' AND OutCassNo NE '' THEN Stage = 'FW' ;* First Wafer SurfScanKey = WONO:'*':ProcStepNo:'*':OutCassNo:'*':Stage obj_AppWindow('ViewRelated','SURFACE_SCAN':@RM:SurfScanKey) END RETURN * * * * * * * PostCleanSurfscan: * * * * * * * Ctrls = @WINDOW:'.WO_NO':@RM ; Props = 'DEFPROP':@RM Ctrls := @WINDOW:'.PROC_STEP_NO':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.OUT_CASS_NO' ; Props := 'DEFPROP' Vals = Get_Property(Ctrls,Props) WONo = Vals[1,@RM] ProcStepNo = Vals[COL2()+1,@RM] OutCassNo = Vals[COL2()+1,@RM] IF WONo NE '' AND ProcStepNo NE '' AND OutCassNo NE '' THEN Stage = 'PC' ;* PostCleans SurfScanKey = WONO:'*':ProcStepNo:'*':OutCassNo:'*':Stage obj_AppWindow('ViewRelated','SURFACE_SCAN':@RM:SurfScanKey) END RETURN * * * * * * * RdsDC: * * * * * * * WOStepKey = Get_Property(@WINDOW,'ID') IF WOStepKey = '' THEN RETURN CtrlEntID = @WINDOW:'.CASSETTES' CurrPos = Get_Property(CtrlEntID,'NOTIFYPOS') ;* Undocumented property that gives cell location when multi select is enabled. CurrCol = CurrPos<1> CurrRow = CurrPos<2> RDSNo = Get_Property(CtrlEntID,'CELLPOS',2:@FM:CurrRow) IF RDSNo NE '' THEN Set_Property(@WINDOW,'@RETURN_FROM_RDS',WOStepKey) ;* Bullshit lashup to work with multiple RDS windows thisFormName = 'RDS' thisFormWindowUp = Get_Property(thisFormName,'VISIBLE') ;* Returns 0 = hidden, 1 = visible, 2 = minimized, 3 = maximized IF thisFormWindowUp = '' THEN Start_Window(thisFormName,AppMain,RDSNo:'*CENTER', '', '') ;* Put up the card window RETURN END IF thisFormWindowUp = 2 THEN Set_Property(thisFormName,'VISIBLE',9) ;* Restore the window if minimized IF Get_Property(thisFormName,'SAVEWARN') THEN Send_Event(thisFormName,'CLEAR') ;* Clear anything existing (prompts for save first) END END RETURN * * * * * * * SignSupVer: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP') WOStep = Get_Property(@WINDOW:'.PROC_STEP_NO','DEFPROP') SupVerSig = Get_Property(@WINDOW:'.SUP_VER_SIG','TEXT') WMOutKey = WONo:'*':WOStep:'*':CassNo ********************************************* * Moved from Post-Epi signature event code * ********************************************* AllRDSNos = Xlate('WM_OUT', WMOutKey, 'RDS', 'X') MetNotCompList = '' For each RDSNo in AllRDSNos using @VM // EpiPro RDS records must have either zone 1 or zone 2 (or both) thickness data ThickAvgZ1 = Xlate('RDS', RDSNo, 'TTHICK_AVG_ALL_Z1', 'X') ThickAvgZ2 = Xlate('RDS', RDSNo, 'TTHICK_AVG_ALL_Z2', 'X') ResAvgZ1 = Xlate('RDS', RDSNo, 'TRES_AVG_ALL_Z1', 'X') ResAvgZ2 = Xlate('RDS', RDSNo, 'TRES_AVG_ALL_Z2', 'X') If ( (ThickAvgZ1 EQ '') and (ThickAvgZ2 EQ '') ) or ( (ResAvgZ1 EQ '') and (ResAvgZ2 EQ '') ) then Locate RDSNo in MetNotCompList using @FM setting fPos else MetNotCompList<-1> = RDSNo end end Next RDSNo If MetNotCompList NE '' then // One or more RDS metrology records are not complete ErrorMessage = 'Process Error':@SVM:'RDS metrology data is not complete for RDS(s):':MetNotCompList ErrMsg(ErrorMessage) return 0 end ********************************************* * Verify if the FQA has already been signed * ********************************************* IF (SupVerSig = '') THEN WOMatRec = XLATE('WO_MAT',WONo:'*':CassNo,'','X') LOCATE WOStep:'MO_QA' IN WOMatRec USING @VM SETTING Pos THEN CurrSig = WOMatRec IF (CurrSig NE '') THEN * Already signed off without saving the RDS signatures CurrSigDTM = OCONV(WOMatRec,'DT4/^HS') CurrSigName = OCONV(CurrSig,'[XLATE_CONV,LSL_USERS*FIRST_LAST]') Set_Property(@WINDOW:'.SUP_VER_SIG','TEXT',CurrSig) Set_Property(@WINDOW:'.SUP_VER_SIG_NAME','TEXT',CurrSigName) Set_Property(@WINDOW:'.SUP_VER_SIG_DTM','TEXT',CurrSigDTM) /* Sync up the WM_OUT record with WO_MAT */ IOOptions = Get_Property(@Window, 'IOOPTIONS') IOOptions<6> = True$ Set_Property(@Window, 'IOOPTIONS', IOOptions) Send_Event(@Window, 'WRITE') IOOptions<6> = False$ Set_Property(@Window, 'IOOPTIONS', IOOptions) RETURN 0 END END END ********************************************** * Verify all ROTR have passed * ********************************************** WMOutList = Get_Property(@Window : '.SLOT', 'ARRAY') RDSNos = WMOutList ROTRAllowed = True$ ; // Assume all have passed for now. For Each RDSNo in RDSNos using @VM ReactRunRow = Database_Services('ReadDataRow', 'REACT_RUN', RDSNo) If Error_Services('NoError') then CIKeyStages = ReactRunRow CIKeyIDs = ReactRunRow Locate 'LWI' in CIKeyStages using @VM setting vPos then CIKeyID = CIKeyIDs<0, vPos> If (CIKeyID NE '') then CleanInspRow = Database_Services('ReadDataRow', 'CLEAN_INSP', CIKeyID) If Error_Services('NoError') then ROTRAction = CleanInspRow ROTRSignature = CleanInspRow ROTRAllowed = Not(ROTRAction EQ 'F') OR (ROTRSignature NE '') ; // If ROTR action failed then ROTRAllowed is set to False$ end end end end Until ROTRAllowed EQ False$ Next RDSNo If ROTRAllowed NE True$ then MsgInfo = '' MsgInfo = '!' MsgInfo = 'ROTR for RDS No ' : RDSNo : ' does not meet all requirements.' Void = Msg('', MsgInfo ) return end ********************************************** * Verify if Final QA has already been signed * ********************************************** WOMatKey = WONo:'*':CassNo Signature_Services('CheckSigOrder', WOMatKey, 'MO_QA') If Error_Services('HasError') then ErrMsg(Error_Services('GetMessage')) Return end ********************************************** * Verify Signatures Profile has been fulfill * ********************************************** Signature_Services('FQAReady', WOMatKey) If Error_Services('HasError') then ErrMsg(Error_Services('GetMessage')) Return 0 end ******************************************************* * Verify that the current user is allowed to sign FQA * ******************************************************* IF MemberOf( @USER4, 'ENGINEERING' ) OR MemberOf( @USER4, 'SUPERVISOR' ) OR MemberOf( @USER4, 'LEAD' ) OR MemberOf( @USER4, 'FINAL_QA' ) ELSE MsgInfo = '' MsgInfo = '!' MsgInfo = 'You must be authorized to sign for final verification.' Void = Msg( '', MsgInfo ) RETURN END ********************************************* * Verify if the FQA has already been signed * ********************************************* PostEpiSig = Get_Property(@WINDOW:'.POST_EPI_SIG','TEXT') SupVerSig = Get_Property(@WINDOW:'.SUP_VER_SIG','TEXT') IF (SupVerSig NE '') THEN ErrMsg('Supervisor Verification for this material has already been signed.') IF MemberOf(@USER4,'OI_ADMIN') ELSE RETURN END END ******************************************* * Verify RDS Metrology has been completed * ******************************************* AllRDSNos = Xlate('WM_OUT', WMOutKey, 'RDS', 'X') AllRDSNos = SRP_Array('Clean', AllRDSNos, 'TrimAndMakeUnique', @VM) For each RDSNo in AllRDSNos using @VM If RDSNo NE '' then Rds_Services('VerifyEPPMetrology', RDSNo) If Error_Services('HasError') then ErrMsg(Error_Services('GetMessage')) return 0 end end Next RDSNo ****************************************** * Verify QA Metrology has been completed * ****************************************** CtrlName = @WINDOW:'.MET_TEST' MetList = Get_Property(CtrlName,'LIST') MLCnt = COUNT(MetList,@FM) + (MetList NE '') FOR Line = 1 TO MLCnt Buffer = MetList IF MetList NE '' THEN BEGIN CASE Case ( ( MetList NE '') and (MetList NE @User4) ) ErrMsg('Process Error':@SVM:'QA Metrology results were signed by another technician. QA Metrology results must be signed by FQA technician.') WO_Mat_QA_Services('ClearResultsByStage', WONo:'*':CassNo, 'MO_QA') Post_Event(@Window, 'READ') RETURN CASE ((MetList = '') AND (MetList = '')) NULL CASE (MetList = '') ErrMsg('Required QA Metrology results have not been entered.') RETURN CASE ((MetList < MetList) OR (MetList > MetList)) ErrMsg('One or more QA Metrology results is out of specification.') RETURN CASE ((MetList NE '') AND (MetList = '')) ErrMsg('One or more QA Metrology results are not signed off.') RETURN END CASE END ;* End of check for a test requirement on the line NEXT Line ************************************************************************ * Prompt user to validate the Process Specification Stage Instructions * ************************************************************************ WMOKey = Get_Property(@WINDOW,'ID') PSNo = Get_Property(@WINDOW:'.PS_NO)','TEXT') VerInst = XLATE('PRS_STAGE',PSNo:'*MO_QA',PRS_STAGE_INST$,'X') IF (VerInst NE '') THEN Yes = Dialog_Box( 'RDS_VER', @WINDOW, VerInst ) IF NOT(Yes) THEN RETURN END END WCCheckEnabled = Xlate('APP_INFO', 'WAFER_COUNTER_CHECK', '', 'X') If WCCheckEnabled then **************************************** * Verify the Wafer Counter information * **************************************** WafersOut = Get_Property(@WINDOW:'.WAFER_CNT','TEXT') WaferCounterQty = Get_Property(@WINDOW:'.EDL_WAFER_COUNTER_QTY','DEFPROP') ************************************ * Wafer Counter - Quantity Section * ************************************ If (WaferCounterQty NE '') then If (WaferCounterQty NE WafersOut) then ErrMsg('Unable to sign FQA because Wafer Counter and Wafers Filled quantities do not match.') RETURN 0 end end else ErrMsg('Unable to sign FQA because the Wafer Counter quantity is missing.') RETURN 0 end end ************************** * Verify user's password * ************************** Valid = Dialog_Box('NDW_VERIFY_USER', @Window, @User4) IF NOT(Valid) THEN RETURN ;* User is not worthy or can't type END ELSE ScanUser = @USER4 WMOKey = WONo:'*':WOStep:'*':CassNo Signature_Services('SignPostEpiStage', '', ScanUser, WMOKey) If Error_Services('NoError') then ScanDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTHS') ScanDTM1 = OCONV(Date(),'D4/'):' ':OCONV(Time()+1,'MTHS') ScanDTM2 = OCONV(Date(),'D4/'):' ':OCONV(Time()+2,'MTHS') * Following 2 lines moved ahead of the QA signature add OrgMUPart = XLATE('WM_OUT',WMOKey,'MU_PART_NO','X') ;* Added 10/13/2010 CurrToolID = 'R':Get_Property(@WINDOW:'.EPI_REACT_NO','DEFPROP') ;* Added 08/13/2013 JCH StatusStage = 'MO_QA' LogFile = 'WO_MAT' ; WOMLParms = LogFile:@RM LogDTM = ScanDTM1 ; WOMLParms := LogDTM:@RM Action = WOStep:StatusStage ; WOMLParms := Action:@RM WhCd = 'CR' ; WOMLParms := WhCd:@RM LocCd = 'QA' ; WOMLParms := LocCd:@RM WONos = WONo ; WOMLParms := WONos:@RM CassNos = CassNo ; WOMLParms := CassNos:@RM UserID = @USER4 ; WOMLParms := UserID:@RM Tags = '' ; WOMLParms := Tags:@RM ToolID = CurrToolID ; WOMLParms := ToolID obj_WO_Mat_Log('Create',WOMLParms) ;* Log MO_QA in INV_ACTIONS IF Get_Status(errCode) THEN ErrMsg(errCode) RETURN END ELSE owmParms = WONo:@RM:CassNo:@RM:WOStep:@RM:StatusStage:@RM:ScanUser:@RM:ScanDTM:@RM:ToolID:@RM:WHCd:@RM:LocCD:@RM:Tags ;* 4/30/2013 JCH added parms for merging of two methods IF Get_Status(errCode) THEN RETURN END Set_Property(@WINDOW:'.SUP_VER_SIG','TEXT',ScanUser) Set_Property(@WINDOW:'.SUP_VER_SIG_DTM','TEXT',ScanDTM) Set_Property(@WINDOW:'.SUP_VER_SIG_NAME','TEXT',OCONV( @USER4, '[XLATE_CONV,LSL_USERS*FIRST_LAST]' )) Send_Event(@WINDOW,'WRITE') NewMUPart = XLATE('WM_OUT',WMOKey,'MU_PART_NO','X') IndexTransactionRow = 'MU_PART_NO':@FM:WMOKey:@FM:OrgMUPart:@FM:NewMUPart:@FM OPEN "!WM_OUT" TO BangTable THEN LOCK BangTable, 0 THEN READ PendingTrans FROM BangTable, 0 ELSE PendingTrans = '0':@FM PendingTrans := IndexTransactionRow WRITE PendingTrans ON BangTable, 0 ELSE ErrMsg('Unable to write index transaction to !WM_OUT. ':WMOutKey) END UNLOCK BangTable, 0 ELSE ErrMsg('Unable to Open !WM_OUT to add index transaction. ':WMOutKey) END ELSE ErrMsg('Unable to Lock !WM_OUT to add index transaction. ':WMOutKey) END END ELSE ErrMsg('Unable to Open !WM_OUT to add index transaction. ':WMOutKey) END obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WMOKey) END end else Error_Services('DisplayError') end end RETURN * * * * * * * SignSAP: * * * * * * * WMOKey = Get_Property(@WINDOW,'ID') WONo = WMOKey[1,'*'] WOStep = WMOKey[COL2()+1,'*'] CassNo = WMOKey[COL2()+1,'*'] ScanUser = @USER4 ScanDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTHS') WMOKey = WONo:'*':WOStep:'*':CassNo OrgMUPart = XLATE('WM_OUT',WMOKey,'MU_PART_NO','X') ;* Added 10/13/2010 StatusStage = 'MO_QA' WhCd = 'CR' LocCd = 'QA' Tags = '' ToolID = '' owmParms = WONo:@RM:CassNo:@RM:WOStep:@RM:StatusStage:@RM:ScanUser:@RM:ScanDTM:@RM:ToolID:@RM:WHCd:@RM:LocCD:@RM:Tags ;* 4/30/2013 JCH added parms for merging of two methods IF Get_Status(errCode) THEN ErrMsg(errCode) RETURN END ELSE Set_Property(@WINDOW:'.SUP_VER_SIG','TEXT',ScanUser) Set_Property(@WINDOW:'.SUP_VER_SIG_DTM','TEXT',ScanDTM) Set_Property(@WINDOW:'.SUP_VER_SIG_NAME','TEXT',OCONV( @USER4, '[XLATE_CONV,LSL_USERS*FIRST_LAST]' )) Send_Event(@WINDOW,'WRITE') * Added 10/14/2010 JCH * NewMUPart = XLATE('WM_OUT',WMOKey,'MU_PART_NO','X') IndexTransactionRow = 'MU_PART_NO':@FM:WMOKey:@FM:OrgMUPart:@FM:NewMUPart:@FM OPEN "!WM_OUT" TO BangTable THEN LOCK BangTable, 0 THEN READ PendingTrans FROM BangTable, 0 ELSE PendingTrans = '0':@FM PendingTrans := IndexTransactionRow WRITE PendingTrans ON BangTable, 0 ELSE ErrMsg('Unable to write index transaction to !WM_OUT. ':WMOutKey) END UNLOCK BangTable, 0 ELSE ErrMsg('Unable to Open !WM_OUT to add index transaction. ':WMOutKey) END ELSE ErrMsg('Unable to Lock !WM_OUT to add index transaction. ':WMOutKey) END END ELSE ErrMsg('Unable to Open !WM_OUT to add index transaction. ':WMOutKey) END * End of 10/14/2010 update obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WMOKey) END RETURN * * * * * * * RejMat: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') WOStep = Get_Property(@WINDOW:'.PROC_STEP_NO','DEFPROP') OutCassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP') WOMatKey = WONo:'*':OutCassNo WMOKey = WONo:'*':WOStep:'*':OutCassNo WMOStatus = Xlate('WM_OUT', WMOKey, 'CURR_STATUS', 'X') OnHold = (WMOStatus EQ 'HOLD') Result = '' SlotSelection = Get_Property(@WINDOW:'.SLOT','SELPOS') SelectedRows = SlotSelection<2> CONVERT @VM TO @FM in SelectedRows SelCnt = COUNT(SelectedRows,@FM) + (SelectedRows NE '') IF SelCnt = 0 THEN ErrMsg('You must select at least one row in order to create an NCR.') RETURN END GoSub FQAVerify If Not(Authorized) then Return 0 If OnHold EQ True$ then Result = Dialog_Box('NDW_HOLD_REMOVAL_PROMPT',@WINDOW,'WM_OUT':@VM:WMOKey:@VM:WOMatKey) If Result NE True$ then Return end else Send_Event(@Window, 'READ') end end If (OnHold NE True$) OR (Result = True$) then OffHoldDTMs = Xlate('WO_MAT', WOMatKey, 'HOLD_STOP_DTM', 'X') SAPBatchNo = Xlate('WO_MAT', WOMatKey, WO_MAT_SAP_BATCH_NO$, 'X') If OffHoldDTMs NE '' then // Ensure at least a minute has elapsed since the cassette was last taken off hold. LastDTM = OffHoldDTMs[-1, 'B':@VM] TimeElapsed = Datetime() - LastDTM // .000694 is the equivalent to 60 seconds in datetime format If (TimeElapsed LT '.000694') AND (SAPBatchNo NE '') then Def = "" Def = "Please wait for SAP to process off hold transaction..." Def = "U" MsgUp = Msg(@window, Def) ;* display the processing message WaitTime = '.000694' - TimeElapsed WaitSeconds = WaitTime * 86400 ;* 86400 = 60 seconds * 60 minutes * 24 hours WaitMilliSec = WaitSeconds * 1000 Sleepery(WaitMilliSec) Msg(@window, MsgUp) ;* take down the processing message end end WMOutList = Get_Property(@WINDOW:'.SLOT','LIST') InCassNos = '' InSlotNos = '' RDSNos = '' PocketNos = '' Zones = '' OutSlotNos = '' OutCassNos = '' SlotNCRs = '' MUWONos = '' MUWOSteps = '' MUCassIDs = '' MUSlotNos = '' ErrFlag = 0 GoodLines = 0 FOR I = 1 TO SelCnt IF WMOutList,COL$UMW_CASS_ID> = '' THEN IF WMOutList,COL$RDS_NO> NE '' THEN IF WMOutList,COL$SLOT_NCR> = '' OR WMOutList,COL$MU_WO_NO> NE '' THEN GoodLines += 1 RDSNos<1,GoodLines> = WMOutList,COL$RDS_NO> InCassNos<1,GoodLines> = WMOutList,COL$IN_CASS> InSlotNos<1,GoodLines> = WMOutList,COL$IN_SLOT> PocketNos<1,GoodLines> = WMOutList,COL$POCKET> Zones<1,GoodLines> = WMOutList,COL$ZONE> OutSlotNos<1,GoodLines> = WMOutList,COL$SLOT> OutCassNos<1,GoodLines> = OutCassNo SlotNCRs = WMOutList,COL$SLOT_NCR> MUWONos = WMOutList,COL$MU_WO_NO> MUWOSteps = WMOutList,COL$MU_WO_STEP> MUCassIDs = WMOutList,COL$MU_CASS_NO> MUSlotNos = WMOutList,COL$MU_SLOT_NO> END ELSE ErrMsg('Slot ':SelectedRows:' is empty.') ErrFlag = 1 END ;* End of check for no Slot NCR (original wafer being rejected) or MU wafer data (makeup wafer being rejected) END ELSE ErrMsg('Slot ':SelectedRows:' is not used.') ErrFlag = 1 END ;* End of check for RDS (wafer) present and not used for makeup END ELSE ErrMsg('Slot ':SelectedRows:' has been used for makeup.') ErrFlag = 1 END ;* End of check for slot Used for Makeup Wafer NEXT I IF ErrFlag OR NOT(GoodLines) THEN RETURN ncrParms = WONo:@RM ncrParms := WOStep:@RM ncrParms := OutCassNo:@RM ;* Place holder for WO_MAT_CASS_NO **** Changed 9/26/2011 JCH ncrParms := '':@RM ;* Single RDS field ncrParms := '':@RM ;* Reactor No ncrParms := 'POST':@RM ncrParms := InCassNos:@RM ncrParms := InSlotNos:@RM ncrParms := PocketNos:@RM ncrParms := Zones:@RM ncrParms := OutCassNos:@RM ncrParms := OutSlotNos:@RM ncrParms := RDSNos:@RM ncrParms := '':@RM ;* Placeholder for RejWaferIDS ncrParms := SlotNCRs:@RM ncrParms := MUWONos:@RM ncrParms := MUWOSteps:@RM ncrParms := MUCassIDs:@RM ncrParms := MUSlotNos BarcodeVerified = Dialog_Box('NDW_VERIFY_BARCODE', @Window, WMOKey, @User4) If BarcodeVerified EQ TRUE$ then Set_Status(0) NCRNo = obj_NCR('Create',ncrParms) ;* Create new NCR for this wafer/group of wafers IF Get_Status(errCode) THEN ErrMsg(errCode) END ELSE RejDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS') RejWfrIDs = '' CurrSlotIDs = '' FOR N = 1 TO COUNT(OutSlotNos,@VM) + (OutSlotNos NE '') * * * * Added 4/23/2016 JCH - wafer history * * * * CurrSlotID = WONo:'*':OutCassNos<1,N>:'*':OutSlotNos<1,N> CurrSlotIDs<1,-1> = CurrSlotID IF MUWONos<1,N> = '' THEN RejWfrID = WONo:'*':InCassNos<1,N>:'*':InSlotNos<1,N> END ELSE RejWfrID = MUWONos<1,N>:'*':MUCassIDs<1,N>:'*':MUSlotNos<1,N> END RejWfrIDs<1,-1> = RejWfrID Parms = RejWfrID:@RM ;* WfrID Parms := RejDTM:@RM ;* EventDtm Parms := @USER4:@RM ;* EventBy Parms := 'NCR':@RM ;* Event Parms := '':@RM ;* NewSlotID Parms := '':@RM ;* RunLoc Parms := NCRNo:@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) LineNo = OutSlotNos<1,N> Set_Property(@WINDOW:'.SLOT','CELLPOS','',COL$RDS_NO:@FM:LineNo) Set_Property(@WINDOW:'.SLOT','CELLPOS','',COL$RDS_STATUS:@FM:LineNo) Set_Property(@WINDOW:'.SLOT','CELLPOS','',COL$POCKET:@FM:LineNo) Set_Property(@WINDOW:'.SLOT','CELLPOS','',COL$ZONE:@FM:LineNo) Set_Property(@WINDOW:'.SLOT','CELLPOS','',COL$IN_CASS:@FM:LineNo) Set_Property(@WINDOW:'.SLOT','CELLPOS','',COL$IN_SLOT:@FM:LineNo) Set_Property(@WINDOW:'.SLOT','CELLPOS',NCRNo,COL$SLOT_NCR:@FM:LineNo) Set_Property(@WINDOW:'.SLOT','CELLPOS','',COL$MU_WO_NO:@FM:LineNo) Set_Property(@WINDOW:'.SLOT','CELLPOS','',COL$MU_WO_STEP:@FM:LineNo) Set_Property(@WINDOW:'.SLOT','CELLPOS','',COL$MU_CASS_NO:@FM:LineNo) Set_Property(@WINDOW:'.SLOT','CELLPOS','',COL$MU_SLOT_NO:@FM:LineNo) NEXT N END Set_Property(@WINDOW:'.SLOT','SELPOS',SlotSelection) ;* Toggle WM_IN select off Send_Event(@WINDOW,'WRITE') DetWindow = 'NCR' DetKeys = NCRNo DefaultRec = '' RetKey = WMOKey RetWin = @WINDOW RetPage = 1 RetCtrl = @WINDOW:'.SLOT' RetPos = 1:@FM:1 obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos) End end RETURN * * * * * * * NCRKeysDC: * * * * * * * WMId = Get_Property(@WINDOW,'ID') CtrlEntID = @WINDOW:'.NCR_KEYS' CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> NCRKey = Get_Property(CtrlEntID,'CELLPOS',1:@FM:CurrRow) Send_Event(@WINDOW,'WRITE') DetWindow = 'NCR' DetKeys = NCRKey DefaultRec = '' RetKey = WMId RetWin = @WINDOW RetPage = 1 RetCtrl = CtrlEntID RetPos = CurrPos obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos) RETURN * * * * * * * HoldClick: * * * * * * * WMOutKey = Get_Property(@WINDOW,'ID') CtrlEnt = Get_Property(@WINDOW,'FOCUS') WONo = WMOutKey[1,'*'] CassNo = FIELD(WMOutKey,'*',3) WOMatKey = WONo:'*':CassNo HoldEntity = 'WM_OUT' HoldEntityID = WMOutKey Stage = Xlate('WO_MAT', WOMatKey, WO_MAT_HOLD_STAGE$, 'X') Interrupted = Xlate('WO_MAT', WOMatKey, WO_MAT_HOLD_INTERRUPTED$, 'X') Reactor = 'EPP' PSN = Get_Property(@Window:'.PS_NO', 'TEXT') Send_Event(@WINDOW,'WRITE') //obj_WO_Mat('ToggleHold',WOMatKey:@RM:HoldEntity:@RM:HoldEntityID:@RM:CtrlEnt) ;* 8/31/2010 JCH Added CtrlEnt * IF Get_Status(errCode) THEN ErrMsg(errCode) Transition = Hold_Services('CheckForHold', WOMatKey, CtrlEnt) HoldType = 'HOLD' HoldData = '' HoldData = Dialog_Box('DIALOG_HOLD',@WINDOW,Transition:@FM:@FM:HoldType:@FM:Stage:@FM:Interrupted) If HoldData NE 'Cancel' then Hold_Services('ToggleHold', WOMatKey, HoldEntity, HoldEntityID, CtrlEnt, '', HoldData) IF Error_Services("HasError") THEN ErrCode = Error_Services("GetMessage") ErrMsg(errCode) end else If Transition EQ False$ then MsgInfo = '' MsgInfo = 'BNY' MsgInfo = 'Hold Successful. Would you like to print label(s)?' MsgInfo = '!' PrintLabel = Msg(@WINDOW,MsgInfo,'') HoldBy = HoldData<1> Reason = HoldData<2> Stage = HoldData<4> Interrupted = HoldData<5> DTM = Datetime() If PrintLabel EQ True$ then Labeling_Services('PrintHoldLabel', HoldEntity, HoldEntityID, Stage, Reason, HoldBy, DTM, PSN, Reactor, Interrupted) end end end end obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WMOutKey) RETURN * * * * * * * HoldDC: * * * * * * * CtrlEntID = @WINDOW:'.HOLD_HISTORY' RecordID = Get_Property(@WINDOW,'ID') WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP') IF WONo = '' OR CassNo = '' THEN RETURN WOMatKey = WONo:'*':CassNo HoldHistory = Get_Property(CtrlEntID,'LIST') CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> HistoryCols = Get_Property(CtrlEntID, "COLUMN") ColName = HistoryCols<1,1,CurrCol> WOMatRec = Database_Services("ReadDataRow", "WO_MAT", WOMatKey, "", "", FALSE$) IF INDEX(ColName,'START',1) THEN HoldStartReason = WOMatRec UpdatedText = Dialog_Box('DIALOG_TEXT',@WINDOW,'Hold Start Reason':@FM:HoldStartReason) END ELSE IF INDEX(ColName,'STOP',1) THEN HoldStopReason = WOMatRec UpdatedText = Dialog_Box('DIALOG_TEXT',@WINDOW,'Hold Stop Reason':@FM:HoldStopReason) END END If UpdatedText NE 'Cancel' then Hold_Services("EditHoldReason",WOMatKey, ColName, CurrRow, UpdatedText) End IF Error_Services("NoError") NE TRUE$ THEN ErrMsg(Error_Services("GetMessage")) end Send_Event(CtrlEntID,'CALCULATE',CurrCol) RETURN * * * * * * * PrintCass: * * * * * * * WMOutKey = Get_Property(@WINDOW,'ID') IF WMOutKey NE '' THEN Print_Cass_Out( WMOutKey, 0) RETURN * * * * * * * AddMakeup: * * * * * * * WMOutKey = Get_Property(@WINDOW,'ID') WOStepKey = FIELD(WMOutKey,'*',1,2) WOStepRec = XLATE('WO_STEP',WOStepKey,'','X') PSNo = WOStepRec WMOutKeys = WOStepRec WONo = WMOutKeys[1,'*'] ProcStepNo = WMOutKey[COL2()+1,'*'] CassNo = WMOutKey[COL2()+1,'*'] WOMatKey = WONo:'*':CassNo WMOStatus = Xlate('WM_OUT', WMOutKey, 'CURR_STATUS', 'X') OnHold = (WMOStatus EQ 'HOLD') IF OnHold NE True$ then GoSub FQAVerify If Not(Authorized) then Return 0 * Build popup of available makeup wafers based on following priority: * Non-Empty Makeup Boxes in the current Work Order * Non-Empty WM_OUT makeup boxes with the same PSNo - Sorted with lowest WO No (oldest) first IF Parm1 = 'BACKFILL' THEN Backfill = 1 END ELSE Backfill = 0 END WMOutList = Get_Property(@WINDOW:'.SLOT','LIST') SlotSelection = Get_Property(@WINDOW:'.SLOT','SELPOS') SelectedRows = SlotSelection<2> CONVERT @VM TO @FM in SelectedRows SelCnt = COUNT(SelectedRows,@FM) + (SelectedRows NE '') EmptySlots = SelectedRows CONVERT @FM TO @VM IN EmptySlots IF EmptySlots = '' THEN ErrMsg('No empty slots selected for makeup!') RETURN END FOR I = 1 TO COUNT(EmptySlots,@VM) + (EmptySlots NE '') EmptySlot = EmptySlots<1,I> IF WMOutList NE '' THEN ErrMsg('Slot No ':EmptySlot:' is not empty.') RETURN END IF WMOutList = '' AND NOT(BackFill) THEN ErrMsg('Slot No ':EmptySlot:' does not have an NCR.') RETURN END IF WMOutList NE '' AND BackFill THEN ErrMsg('Slot No ':EmptySlot:' has an NCR.') RETURN END NEXT I Continue = True$ ShowSpecInst = Xlate('PROD_SPEC', PSNo, PROD_SPEC_SHOW_SPEC_INST_ON_MU_ADD$, 'X') If ShowSpecInst then SpecInst = Xlate('PROD_SPEC', PSNo, PROD_SPEC_SPEC_INST$, 'X') If SpecInst NE '' then Continue = Dialog_Box('NDW_ACKNOWLEDGE_MESSAGE', @Window, SpecInst) If Not(Continue) then Msg(@Window, '', 'OK', '', 'Process Error':@FM:'This PSN requires you to acknowledge special instructions to add makeup wafers.') end end end If Continue then Response = Dialog_Box('NDW_MAKEUP_WAFERS', @Window, WOMatKey) Begin Case Case Response EQ True$ // User requested to convert the current cassette into a makeup box. WOMatRec = Database_Services('ReadDataRow', 'WO_MAT', WOMatKey) If Error_Services('NoError') then SAPBatchNo = WOMatRec SAPTXDtm = WOMatRec AwaitingBatchNo = ( (SAPTXDtm NE '') and (SAPBatchNo EQ '') ) HasBatchNo = (SAPBatchNo NE '') FullBoxReject = (SAPBatchNo[-1, 1] = 'R') Begin Case Case AwaitingBatchNo InvalidRequest = True$ ErrMsg('WARNING: Cassette ineligible to be converted as it is awaiting a batch number from SAP.') Return Case FullBoxReject InvalidRequest = True$ ErrMsg('WARNING: Cassette is ineligible to be converted as it is a full box reject.') Return Case HasBatchNo // Operation limited to LEAD and SUPERVISOR groups OverrideMsg = "Cassette has a batch number. SUPERVISOR or LEAD must override." Response = Msg(@Window, '', 'OVERRIDE', '', OverrideMsg) Begin Case Case Response EQ 1 Response = True$ ; // User Clicked Override Case Response EQ 2 Response = False$ ; // User Clicked Cancel Case Response EQ char(27) Response = False$ ; // User Pressed Escape Key End Case If Response EQ True$ then Response = Dialog_Box('NDW_VERIFY_USER', @WINDOW, @USER4:@FM:'LEAD':@VM:'SUPERVISOR') Authorized = Response<1> end else Authorized = False$ end If Not(Authorized) then Return Case Otherwise$ Null End Case AvailMU_WMOKeys = '' UserResp = Response MakeupBox = '' // User requested to convert the current cassette into a makeup box. // Verify the quantity before proceeding. If WMOutKey NE '' then Parms = '' Parms<1> = WMOutKey ; // Cassette to verify wafer count of. Parms<2> = 0 ; // Wafer count adjustment - 0 because converting box. Parms<3> = 'MU' ; // Wafer counter tool location Proceed = Dialog_Box('NDW_WAFER_COUNTER', @Window, Parms) If Proceed NE True$ then Return end else ErrMsg('Error starting wafer counter check. WM_OUT key is missing.') end CheckValue = 1 FieldNo = WO_MAT_EPO_MAKEUP_BOX$ obj_WO_Mat('ChangeFlag',WOMatKey:@RM:FieldNo:@RM:CheckValue) ;* Set WMO_MAKEUP flag on WM_OUT IF Get_Status(errCode) THEN ErrMsg(errCode) Set_Property(@WINDOW:'.MAKEUP_BOX','DEFPROP',CheckValue) ;* Make this the makeup box Send_Event(@WINDOW,'WRITE') ;* Write the record WMOKey = WONo:'*':ProcStepNo:'*':CassNo obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WMOKey) ;* Reread the updated record Return end else ErrMsg('WARNING: Error reading WO_MAT record.') Return end Case Response EQ '' // User has cancelled this process. Return Case Otherwise$ // User has selected a makeup box to use and backfill. AvailMU_WMOKeys = Response MakeupBox = Response MuWfrsNeeded = SelCnt If AvailMU_WMOKeys NE '' then // Wafer counter check - Account for the possibility of selecting more than one makeup box. For each MuWmoKey in AvailMU_WMOKeys using @FM MuWoMatKey = Field(MuWmoKey, '*', 1):'*':Field(MuWmoKey, '*', 3) QtyAdj = MuWfrsNeeded CurrMuWfrCnt = obj_WO_Mat('CurrWaferCnt', MuWoMatKey) If MuWfrsNeeded GT CurrMuWfrCnt then QtyAdj = CurrMuWfrCnt MuWfrsNeeded -= CurrMuWfrCnt end Parms = '' Parms<1> = MuWmoKey ; // Cassette to verify wafer count of. Parms<2> = QtyAdj ; // Wafer count adjustment - 0 because converting box. Parms<3> = 'MU' ; // Wafer counter tool location Proceed = Dialog_Box('NDW_WAFER_COUNTER', @Window, Parms) If Proceed NE True$ then Return Next MuWmoKey end * Signature block added 10/6/2010 JCH * Valid = Dialog_Box('NDW_VERIFY_USER', @Window, @User4) IF NOT(Valid) THEN RETURN ;* User is not worthy or can't type Send_Event(@WINDOW,'WRITE') obj_WM_Out('AddMakeupWafers',WMOutKey:@RM:EmptySlots:@RM:MakeupBox) //Remove the signatures for the WO_MAT_QA record because they are changing its results. WOMatQaKey = Field(WMOutKey, '*', 1) : '*' : Field(WMOutKey, '*', 3) Wo_Mat_Qa_Services('ClearSignatureByStage', WOMatQaKey, 'MO_QA') obj_Appwindow('LoadFormKeys',@WINDOW:@RM:WMOutKey) RETURN End Case end end else // Cassette is on hold so makeup wafers cannot be added. ErrorMessage = 'Add MU Wafer Denied!. The cassette must be taken off hold before adding makeup wafers.' Msg(@Window, '', 'OK', '', 'Error':@FM:ErrorMessage) RETURN end Return * * * * * * * RemMakeup: * * * * * * * GoSub FQAVerify If Not(Authorized) then Return 0 IF NOT(MemberOf(@USER4,'OI_ADMIN')) THEN RETURN IF Parm1 = 'BACKFILL' THEN Backfill = 1 END ELSE Backfill = 0 END WMOutList = Get_Property(@WINDOW:'.SLOT','LIST') SlotSelection = Get_Property(@WINDOW:'.SLOT','SELPOS') SelectedRows = SlotSelection<2> SelCnt = COUNT(SelectedRows,@VM) + (SelectedRows NE '') MadeupSlots = SelectedRows IF MadeupSlots = '' THEN ErrMsg('No madeup slots selected for removing makeup wafers!') RETURN END FOR I = 1 TO COUNT(MadeupSlots,@VM) + (MadeupSlots NE '') MadeupSlot = MadeupSlots<1,I> IF WMOutList = '' THEN ErrMsg('Slot No ':MadeupSlot:' does not contain a makeup wafer') RETURN END NEXT I WMOutKey = Get_Property(@WINDOW,'ID') Send_Event(@WINDOW,'WRITE') MUWaferData = obj_WM_Out('SubMakeupWafers',WMOutKey:@RM:MadeupSlots) IF Get_Status(errCode) THEN ErrMsg(errCode) END IF MUWaferData NE '' THEN obj_WM_Out('RepMakeupWafers',WMOutKey:@RM:MUWaferData) IF Get_Status(errCode) THEN ErrMsg(errCode) END END obj_Appwindow('LoadFormKeys',@WINDOW:@RM:WMOutKey) RETURN * * * * * * * RemSlots: * * * * * * * IF NOT(MemberOf(@USER4,'OI_ADMIN')) THEN ErrMsg('Contact your system administrator for this function.') RETURN END SlotList = Get_Property(@WINDOW:'.SLOT','LIST') SlotArray = Get_Property(@WINDOW:'.SLOT','ARRAY') SlotCnt = COUNT(SlotList,@FM) + (SlotList NE '') OpenSlots = '' FOR N = SlotCnt TO 1 STEP -1 SlotLine = SlotList CONVERT @VM TO '' IN SlotLine IF SlotLine = N THEN OpenSlots<1,-1> = SlotLine END UNTIL SlotLine NE '' AND SlotLine NE N NEXT N TypeOver = '' TypeOver = OpenSlots RemSlots = Popup(@WINDOW,TypeOver,'EMPTY_SLOTS') WMOutKey = Get_Property(@WINDOW,'ID') Send_Event(@WINDOW,'WRITE') obj_WM_Out('RemSlots',WMOutKey:@RM:RemSlots) IF Get_Status(errCode) THEN ErrMsg(errCode) END obj_Appwindow('LoadFormKeys',@WINDOW:@RM:WMOutKey) RETURN ************ MakeupClick: ************ WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP') ProcStepNo = Get_Property(@WINDOW:'.PROC_STEP_NO','DEFPROP') CtrlEnt = @WINDOW:'.MAKEUP_BOX' CheckValue = Get_Property(CtrlEnt,'DEFPROP') InvalidRequest = False$ IF ( (WONo NE '') AND (CassNo NE '') AND (ProcStepNo NE '') ) THEN WMOKey = WONo:'*':ProcStepNo:'*':CassNo WOMatKey = WONo:'*':CassNo OnHold = Xlate('WO_MAT', WOMatKey, 'HOLD', 'X') IF OnHold NE True$ then IF (MemberOf(@USER4,'MASTER_SCHED')) | OR (MemberOf(@USER4,'SUPERVISOR')) | OR (MemberOf(@USER4,'ENGINEERING')) | OR (MemberOf(@USER4,'LEAD')) | OR (MemberOf(@USER4,'OI_ADMIN')) THEN If WMOKey NE '' then WOMatKey = Xlate('WM_OUT', WMOKey, 'WO_MAT_KEY', 'X') If WOMatKey NE '' then WOMatRec = Database_Services('ReadDataRow', 'WO_MAT', WOMatKey) If Error_Services('NoError') then SAPBatchNo = WOMatRec SAPTXDtm = WOMatRec FullBoxReject = (SAPBatchNo[-1, 1] = 'R') AwaitingBatchNo = ( (SAPTXDtm NE '') and (SAPBatchNo EQ '') ) Begin Case Case AwaitingBatchNo ErrMsg('WARNING: Cassette ineligible to be converted as it is awaiting a batch number from SAP.') InvalidRequest = True$ Case FullBoxReject ErrMsg('WARNING: Cassette ineligible to be converted as it is a full box reject.') InvalidRequest = True$ Case Otherwise$ Null End Case If Not(InvalidRequest) then Parms = '' Parms<1> = WMOKey ; // Cassette to verify wafer count of. Parms<2> = 0 ; // Wafer count adjustment - 0 because converting box. Parms<3> = 'MU' ; // Wafer counter tool location Proceed = Dialog_Box('NDW_WAFER_COUNTER', @Window, Parms) If Proceed EQ True$ then Send_Event(CtrlEnt,'GOTFOCUS') OrgMUPart = XLATE('WM_OUT',WMOKey,'MU_PART_NO','X') // Log the makeup flag change LogData = '' LogData<1> = LoggingDTM LogData<2> = WONo:'*':ProcStepNo:'*':CassNo LogData<3> = CheckValue LogData<4> = @User4 Logging_Services('AppendLog', objLog, LogData, @RM, @FM) Send_Event(@WINDOW,'WRITE') ;************* 6/30/2010 FieldNo = WO_MAT_EPO_MAKEUP_BOX$ obj_WO_Mat('ChangeFlag',WOMatKey:@RM:FieldNo:@RM:CheckValue) IF Get_Status(errCode) THEN ErrMsg(errCode) * Added 10/11/2010 JCH NewMUPart = XLATE('WM_OUT',WMOKey,'MU_PART_NO','X') IndexTransactionRow = 'MU_PART_NO':@FM:WMOKey:@FM:OrgMUPart:@FM:NewMUPart:@FM OPEN "!WM_OUT" TO BangTable THEN LOCK BangTable, 0 THEN READ PendingTrans FROM BangTable, 0 ELSE PendingTrans = '0':@FM PendingTrans := IndexTransactionRow WRITE PendingTrans ON BangTable, 0 ELSE ErrMsg('Unable to write index transaction to !WM_OUT. ':WMOutKey) END UNLOCK BangTable, 0 ELSE ErrMsg('Unable to Unlock !WM_OUT while adding index transaction. ':WMOutKey) END ELSE ErrMsg('Unable to Lock !WM_OUT to add index transaction. ':WMOutKey) END END ELSE ErrMsg('Unable to Open !WM_OUT to add index transaction. ':WMOutKey) END * End of 10/11/2010 update end else InvalidRequest = True$ end end end else InvalidRequest = True$ ErrMsg('WARNING: Error reading WO_MAT record.') end end else InvalidRequest = True$ ErrMsg('WARNING: Error reading WO_MAT key.') end end else InvalidRequest = True$ ErrMsg('WARNING: Error starting wafer counter check. WM_OUT key is missing.') end END ELSE InvalidRequest = True$ ErrMsg('INFO: This function is limited to members of MASTER_SCHED, SUPERVISOR, ENGINEERING, or LEAD security groups.') END END else InvalidRequest = True$ ErrMsg('INFO: The lot is currently on hold and may not be modified.') end END ELSE InvalidRequest = True$ ErrMsg('WARNING: Work Order/Cassette/Step information is missing.') END If (InvalidRequest EQ True$) then /* Toggle back the checkbox flag */ If (CheckValue EQ False$) then Set_Property(CtrlEnt, 'DEFPROP', True$) end else Set_Property(CtrlEnt, 'DEFPROP', False$) end end obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WMOKey) RETURN ************ SendMessage: ************ WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') StepNo = Get_Property(@WINDOW:'.PROC_STEP_NO','DEFPROP') CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP') IF WONo NE '' AND StepNo NE '' AND CassNo NE '' THEN WMOKey = WONo:'*':StepNo:'*':CassNo Send_Event(@WINDOW,'WRITE') NoteID = NextKey('NOTES') obj_AppWindow('ViewRelated','NOTE_MESSAGE':@RM:NoteID:@RM:'WM_OUT':@FM:WMOKey) END RETURN * * * * * * * ViewPSN: * * * * * * * PSNo = Get_Property(@WINDOW:'.PS_NO','DEFPROP') IF PSNo NE '' THEN Start_Window('PROD_SPEC',@WINDOW, PSNo:'*CENTER', '', '' ) ;* Old style call to old style window END RETURN * * * * * * * RebuildLoad: * * * * * * * IF NOT(MemberOf(@USER4,'OI_ADMIN')) THEN RETURN WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') StepNo = Get_Property(@WINDOW:'.PROC_STEP_NO','DEFPROP') CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP') IF WONo = '' OR StepNo = '' OR CassNo = '' THEN RETURN SlotArray = Get_Property(@WINDOW:'.SLOT','ARRAY') NCRs = SlotArray MUWOs = SlotArray UMWCassIDs = SlotArray CONVERT @VM TO '' IN NCRs CONVERT @VM TO '' IN MUWOs CONVERT @VM TO '' IN UMWCassIDs IF MUWOs NE '' THEN ErrMsg('Makeup Wafer(s) have been added to Cassette') RETURN END IF UMWCassIDs NE '' THEN ErrMsg('Wafer(s) have been used for Makeup Wafers') RETURN END WMOKey = WONo:'*':StepNo:'*':CassNo Send_Event(@WINDOW,'WRITE') obj_WM_Out('RebuildLoad',WMOKey) ;* Rebuilds wafer unload data from ReactRun Reacords IF Get_Status(errCode) THEN ErrMsg(errCode) END obj_Appwindow('LoadFormKeys',@WINDOW:@RM:WMOKey) RETURN * * * * * * * ClearLoad: * * * * * * * IF NOT(MemberOf(@USER4,'OI_ADMIN')) THEN RETURN WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') StepNo = Get_Property(@WINDOW:'.PROC_STEP_NO','DEFPROP') CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP') IF WONo = '' OR StepNo = '' OR CassNo = '' THEN RETURN WMOKey = WONo:'*':StepNo:'*':CassNo Send_Event(@WINDOW,'WRITE') obj_WM_Out('ClearLoad',WMOKey) ;* Clear Load Data for manual cleanup IF Get_Status(errCode) THEN ErrMsg(errCode) END obj_Appwindow('LoadFormKeys',@WINDOW:@RM:WMOKey) RETURN * * * * * * * MetTestDC: * * * * * * * WMId = Get_Property(@WINDOW,'ID') CtrlEntID = @WINDOW:'.MET_TEST' CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> TestLine = Get_Property(CtrlEntID,'LIST') RDSNo = '' RunStep = 'MO_QA' WMId := '*':RDSNo:'*':RunStep void = Start_Window( 'QA_MET_RESULT', @WINDOW, WMId:@FM:TestLine) RETURN * * * * * * FQAVerify: * * * * * * // Check if FQA'd. If so, prompt for override. Authorized = False$ WMOutKey = Get_Property(@Window : '.WMO_NO', 'TEXT') Convert '.' to '*' in WMOutKey WoMatKey = Xlate('WM_OUT', WMOutKey, 'WO_MAT_KEY', 'X') WoMatRec = Database_Services('ReadDataRow', 'WO_MAT', WoMatKey) FQASig = '' FQADate = '' WONo = Field(WoMatKey, '*', 1) ReactorType = XLATE('WO_LOG', WONo, 'REACT_TYPE', 'X') SigArray = Signature_Services('GetSigProfile', WOMatKey) SigProfile = SigArray<1> Signatures = SigArray<2> SigDTMS = SigArray<3> StatusStage = 'MO_QA' LOCATE StatusStage IN SigProfile USING @VM SETTING Pos THEN FQASig = Signatures<1, Pos> FQADate = SigDTMS<1, Pos> end If (FQASig NE '') or (FQADate NE '') then // Cassette FQA'd OverrideMsg = "Cassette already FQA'd. Supervisor, Lead or Eng.Tech must override." Response = Msg(@Window, '', 'OVERRIDE', '', OverrideMsg) Begin Case Case Response EQ 1 Response = True$ ; // User Clicked Override Case Response EQ 2 Response = False$ ; // User Clicked Cancel Case Response EQ char(27) Response = False$ ; // User Pressed Escape Key End Case If Response EQ True$ then Response = Dialog_Box('NDW_VERIFY_USER', @WINDOW, @USER4 : @FM : 'LEAD' : @VM : 'SUPERVISOR':@VM:'ENG_TECH') Authorized = Response<1> end else Authorized = False$ end end else Authorized = True$ end 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) return RefreshWaferCounterData: WCCheckEnabled = Xlate('APP_INFO', 'WAFER_COUNTER_CHECK', '', 'X') If WCCheckEnabled then Set_Property(@Window:'.LBL_WAFER_COUNTER_QTY', 'VISIBLE', True$) Set_Property(@Window:'.EDL_WAFER_COUNTER_QTY', 'VISIBLE', True$) QtyBackColor = GREEN$ WONo = Get_Property(@Window : '.WO_NO', 'TEXT') Cassette = Get_Property(@Window : '.OUT_CASS_NO', 'TEXT') WMOKey = WONo:'*1*':Cassette If WMOKey NE '*1*' then FqaWcRec = Wafer_Counter_Services('GetLastScan', WMOKey, 'QA') WaferCounterQty = FqaWcRec Set_Property(@Window, '@ORIG_WFR_CTR_QTY', WaferCounterQty) WafersFilled = Get_Property(@WINDOW:'.WAFER_CNT','TEXT') Set_Property(@WINDOW:'.EDL_WAFER_COUNTER_QTY','DEFPROP', WaferCounterQty) ************************************ * Wafer Counter - Quantity Section * ************************************ If (WaferCounterQty NE '') then If (WaferCounterQty NE WafersFilled) then QtyBackColor = RED$ end else QtyBackColor = ORANGE$ end WaferSize = Xlate('WM_OUT', WMOKey, 'WAFER_SIZE', 'X') WaferSize = Field(WaferSize, ' ', 3, 1) If ( (WaferSize EQ 6) or (WaferSize EQ 8) ) then WCToolId = Wafer_Counter_Services('GetWaferCounterToolID', WaferSize:'INCH', 'QA') If Error_Services('NoError') then WCCurrMode = '' If RowExists('TOOL', WCToolID) then WCCurrModeKey = Xlate('TOOL', WCToolID, 'CURR_MODE_KEY', 'X') WCCurrMode = Xlate('TOOL_LOG', WCCurrModeKey, 'TOOL_MODE', 'X') Set_Property(@WINDOW:'.EDL_WAFER_COUNTER_QTY', 'ENABLED', (WCCurrMode NE 'PROD')) end else ErrMsg('Verify wafer count error. Invalid wafer counter tool ID "':WCToolID:'".') end end else ErrMsg(Error_Services('GetMessage')) end end else ErrMsg('Verify wafer count error. Invalid wafer size "':WaferSize:'" returned for WMO "':WMOKey:'".') end end Set_Property(@WINDOW:'.EDL_WAFER_COUNTER_QTY','BACKCOLOR', QtyBackColor) end else Set_Property(@Window:'.LBL_WAFER_COUNTER_QTY', 'VISIBLE', False$) Set_Property(@Window:'.EDL_WAFER_COUNTER_QTY', 'VISIBLE', False$) end return