COMPILE FUNCTION Comm_React_Run(Instruction,Parm1,Parm2) #pragma precomp SRP_PreCompiler /* Template Commuter module for REACT_RUN (Reactor Run) window 02/21/2008 - John C. Henry, J.C. Henry & Co., Inc. */ DECLARE SUBROUTINE Set_Property, End_Dialog, Send_Event, Set_Status, Center_Window, Post_Event DECLARE SUBROUTINE ErrMsg, Send_Message, Set_Property, Send_Event, Btree.Extract, obj_AppWindow, DECLARE SUBROUTINE obj_Notes, Security_Err_Msg, End_Window, Forward_Event, Start_Window, Create_Note DECLARE SUBROUTINE obj_RDS_Test, Print_Control_Plan, Print_RDS_Instruction, Send_Info, Post_Event DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, Utility, Center_Window, Popup, Collect.Ixvals DECLARE FUNCTION Send_Message, Msg, Security_Check, RowExists, NextKey, obj_React_Esc, obj_React_Run DECLARE FUNCTION obj_RDS_Test, MemberOf, Create_Dialog, obj_Popup, obj_WO_Wfr $INSERT MSG_EQUATES $INSERT APPCOLORS $INSERT LSL_USERS_EQU $INSERT SECURITY_RIGHTS_EQU $INSERT REACT_EVENT_EQUATES $INSERT REACT_RUN_EQUATES $INSERT WO_STEP_EQU $INSERT WO_MAT_EQUATES $INSERT WO_WFR_WIP_EQUATES $INSERT EPI_SUSCEPTOR_EQUATES $INSERT REACTOR_EQUATES $INSERT RTI_STYLE_EQUATES $INSERT POPUP_EQUATES $INSERT LOGICAL EQU CRLF$ TO \0D0A\ EQU COL$LSID TO 1 EQU COL$RECIPE TO 2 EQU COL$RECIPE_NAME TO 3 EQU COL$PARAMS TO 4 EQU COL$PARMS_OUT TO 5 EQU COL$BLANK_COL TO 6 EQU COL$MET_NO TO 7 EQU COL$THICK_AVG TO 8 EQU COL$RRHO_AVG TO 9 EQU COL$MET_NO_Z1 TO 10 EQU COL$THICK_AVG_Z1 TO 11 EQU COL$RRHO_AVG_Z1 TO 12 EQU COL$MET_NO_Z2 TO 13 EQU COL$THICK_AVG_Z2 TO 14 EQU COL$RRHO_AVG_Z2 TO 15 EQU COL$MET_OUT TO 16 EQU COL$MET_OUT_Z1 TO 17 EQU COL$MET_OUT_Z2 TO 18 EQU COL$MET_TWSIG TO 19 EQU COL$MET_TWSIG_Z1 TO 20 EQU COL$MET_TWSIG_Z2 TO 21 EQU COL$CHAR_WFR_ID TO 1 EQU COL$SCRIBE TO 2 EQU COL$SPLIT_BY TO 3 EQU COL$SPLIT_DTM TO 4 EQU COL$CURR_STAGE TO 5 EQU COL$CHAR_DEST TO 6 EQU COL$CHAR_TW_NO TO 7 EQU COL$CHAR_WFR_STATUS TO 8 EQU COL$CARR_SLOG_NO TO 1 EQU COL$CARR_WFR_ID TO 2 EQU COL$CARR_SCRIBE TO 3 EQU COL$CARR_CHAR_FLAG TO 4 EQU COL$CARR_NCR TO 5 EQU COL$CARR_GRADE TO 6 EQU COL$SIG_PROF TO 1 EQU COL$SIGNATURE TO 2 EQU COL$SIG_DTM TO 3 EQU COL$STAGE_COMMENT TO 4 EQU COL$STAGE_STATUS TO 5 EQU COL$SUSC_LOAD_WFR_ID TO 6 ;* SUSC_LOAD control EQU COL$SUSC_LOAD_WFR_SCRIBE TO 7 EQU EDITABLE$ TO 4 EQU PROTECTED$ TO 8 ;* Protected - Edittable COLSTYLE constants EQU MULTILINE_STYLE$ TO 512 ;* MultiLine Select EQU LOCKED$ TO 8192 EQU DROPDOWN_STYLE$ TO 131072 ErrCode = '' ErrorMsg = '' ErrTitle = 'Error in Comm_React_Run' Result = '' BEGIN CASE CASE Instruction = 'Create' ; GOSUB Create CASE Instruction = 'Refresh' ; GOSUB Refresh CASE Instruction = 'Page' ; GOSUB Page CASE Instruction = 'VScroll' ; GOSUB VScroll CASE Instruction = 'Read' ; GOSUB Read CASE Instruction = 'Write' ; GOSUB Write CASE Instruction = 'Clear' ; GOSUB Clear CASE Instruction = 'Delete' ; GOSUB Delete CASE Instruction = 'Close' ; GOSUB Close CASE Instruction = 'RDSNoLF' ; GOSUB RDSNoLF CASE Instruction = 'CIClick' ; GOSUB CIClick CASE Instruction = 'LURDSNo' ; GOSUB LURDSNo CASE Instruction = 'LUReactNo' ; GOSUB LUReactNo CASE Instruction = 'LUReactEsc' ; GOSUB LUReactEsc CASE Instruction = 'CopyMetrology' ; GOSUB CopyMetrology CASE Instruction = 'LSIdDC' ; GOSUB LSIdDC CASE Instruction = 'AddZoneMet' ; GOSUB AddZoneMet CASE Instruction = 'MoveMetToZone' ; GOSUB MoveMetToZone CASE Instruction = 'ViewWOMat' ; GOSUB ViewWOMat CASE Instruction = 'SendMsg' ; GOSUB SendMsg CASE Instruction = 'CtrlPlanClick' ; GOSUB CtrlPlanClick CASE Instruction = 'ViewPSN' ; GOSUB ViewPSN CASE Instruction = 'PrintInstruction' ; GOSUB PrintInstruction CASE Instruction = 'SignSuppl' ; GOSUB SignSuppl CASE Instruction = 'SignFinalQA' ; GOSUB SignFinalQA CASE Instruction = 'SigProfileClick' ; GOSUB SigProfileClick CASE Instruction = 'ViewWO' ; GOSUB ViewWO CASE Instruction = 'CharWfrDC' ; GOSUB CharWfrDC CASE Instruction = 'CarrWfrDC' ; GOSUB CarrWfrDC CASE Instruction = 'CharWfrOptions' ; GOSUB CharWfrOptions CASE Instruction = 'SplitClick' ; GOSUB SplitClick CASE Instruction = 'DispoClick' ; GOSUB DispoClick CASE Instruction = 'LURunPri' ; GOSUB LURunPri CASE Instruction = 'EditScribe' ; GOSUB SUSC_LOAD.OPTIONS * CASE EntID = @WINDOW:'.SUSC_LOAD' AND Event = 'OPTIONS' ; GOSUB SUSC_LOAD.OPTIONS CASE 1 ErrorMsg = 'Unknown Instruction ':QUOTE(Instruction):' passed to routine.' ErrMsg(ErrorMsg) END CASE IF ErrorMsg NE '' THEN ErrMsg(ErrTitle:@SVM:ErrorMsg) END RETURN Result * * * * * * * Create: * * * * * * * /* IF NOT(Security_Check('Reactor Event Log',READ$)) THEN Security_Err_Msg('Reactor Event Log',READ$) End_Window(@WINDOW) RETURN END */ obj_Appwindow('Create',@WINDOW) * Provides compatibility with the existing messaging attachment system IF Parm1 NE '' THEN PassedKeys = FIELD(Parm1,'*',1) obj_Appwindow('ViewRelated',@WINDOW:@RM:PassedKeys) END * /* ReactorStyles = Send_Message(@WINDOW:'.REACTOR_LOAD','COLSTYLE',0,'') ReactorStyles = BitOr(ReactorStyles,DROPDOWN_STYLE$) Send_Message(@WINDOW:'.REACTOR_LOAD','COLSTYLE',0,ReactorStyles) Send_Message(@WINDOW:'.REACTOR_LOAD','COLFORMAT',COL$USAGE,@VM:'TEST':@VM:'PROD':@VM:'DUMMY') */ CharStyles = Send_Message(@WINDOW:'.CHAR_WFR_ID','COLSTYLE',0,'') ;* Get All Styes CharStyles = BitOr(CharStyles,DTCS_OPTIONSBUTTON$) ;* Set column to Dropdown Send_Message(@WINDOW:'.CHAR_WFR_ID','COLSTYLE',0,CharStyles) ;* Set Col Styles SuscLoadStyles = Send_Message(@WINDOW:'.SUSC_LOAD','COLSTYLE',0,'') SuscLoadStyles = BitOr(SuscLoadStyles,DTCS_OPTIONSBUTTON$) void = Send_Message(@WINDOW:'.SUSC_LOAD','COLSTYLE',0,SuscLoadStyles) CarrStyles = Send_Message(@WINDOW:'.CARR_WFR_ID','COLSTYLE',0,'') CarrStyles = BitOr(CarrStyles,DTCS_CHECKBOX$) CarrStyles = BitOr(CarrStyles,DTCS_CHECKBOXCENTER$) void = Send_Message(@WINDOW:'.CARR_WFR_ID','COLSTYLE',0,CarrStyles) Set_Property(@WINDOW:'.CANCELLED','ENABLE',0) GOSUB Refresh RETURN * * * * * * * Clear: * * * * * * * IF Get_Property(@WINDOW,'@READONLY') THEN obj_AppWindow('ReadOnly',@RM:1) ;* Reenables data bound controls Set_Property(@WINDOW,'@READONLY',0) ;* Clear flag on window END * * * * * * * Refresh: * * * * * * * RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP') CharWfrData = Get_Property(@WINDOW:'.CHAR_WFR_ID','DEFPROP') CharWfrIDs = CharWfrData WfrSigKeys = obj_React_Run('GetNextWfrStage',RDSNo:@RM:CharWfrIDs) IF Get_Status(errCode) THEN ErrMsg(errCode) DEBUG END RunPri = Get_Property(@WINDOW:'.RUN_PRI','DEFPROP') BEGIN CASE CASE RunPri = 'P1' ; PriBackColor = PR1_RED$ CASE RunPri = 'P2' ; PriBackColor = PR2_RED$ CASE RunPri = 'P3' ; PriBackColor = PR3_RED$ CASE 1 ; PriBackColor = GREEN$ END CASE Set_Property(@WINDOW:'.RUN_PRI_DESC','BACKCOLOR',PriBackColor) * * * * * * * * * * * * * * * * Original code below here needs a serious review JCH * * * * * *& * * * * * * * * SuppInst = Get_Property(@WINDOW:'.SUPP_INST','TEXT') SuppSig = Get_Property(@WINDOW:'.SUPP_SIG','TEXT') Ctrls = @WINDOW:'.SUPP_SIG':@RM ; Props = 'BACKCOLOR':@RM Ctrls := @WINDOW:'.SUPP_SIG_DTM':@RM ; Props := 'BACKCOLOR':@RM Ctrls := @WINDOW:'.SUPP_SIG_BUTTON':@RM ; Props := 'ENABLED':@RM Ctrls := @WINDOW:'..NEEDS_ATTENTION':@RM ; Props := 'TEXT':@RM Ctrls := @WINDOW:'..NEEDS_ATTENTION' ; Props := 'VISIBLE' IF SuppSig = '' THEN Vals = WHITE$:@RM Vals := WHITE$:@RM END ELSE Vals = GREEN$:@RM Vals := GREEN$:@RM END NeedsAttention = '' IF SuppInst NE '' THEN SuppSig = Get_Property(@WINDOW:'.SUPP_SIG','TEXT') IF SuppSig = '' THEN NeedsAttention = 'Supplemental Instruction is not signed!' END END IF NeedsAttention = '' THEN Vals := 0:@RM ELSE Vals := 1:@RM ;* Turns the signbutton on Vals := NeedsAttention:@RM ;* Sets red text for operator IF NeedsAttention = '' THEN Vals := 0 ELSE Vals := 1 ;* Makes the text visible Set_Property(Ctrls,Props,Vals) ;* Sets NEEDS_ATTENTION and associated stuff * NeedsAttention NE '' Ctrls = @WINDOW:'.ADE_READ':@RM ; Props = 'DEFPROP':@RM Ctrls := @WINDOW:'.LAST_WAFER_RHO':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.FIN_WFR_QTY':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.SHIFT':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.FQA_LPD':@RM ; Props := 'DEFPROP':@RM ;* Added FQA_LPD property check dkk 12/29/14 Ctrls := @WINDOW:'.WFR_SIG':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.UNLOAD_SIG':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.POST_SIG':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.FIN_SIG' ; Props := 'DEFPROP' Vals = Get_Property(Ctrls,Props) ADERead = Vals[1,@RM] LastWaferRHO = Vals[COL2()+1,@RM] FinWfrQty = Vals[COL2()+1,@RM] Shift = Vals[COL2()+1,@RM] FqaLpd = Vals[COL2()+1,@RM] ;* Added FqaLpd check dkk 12/29/14 WfrSig = Vals[COL2()+1,@RM] UnloadSig = Vals[COL2()+1,@RM] PostSig = Vals[COL2()+1,@RM] FinSig = Vals[COL2()+1,@RM] IF NeedsAttention = '' AND ADERead NE '' AND LastWaferRHO NE '' AND FinWfrQty NE '' AND Shift NE '' AND FqaLpd NE '' Then;* Added FqaLpd check to ensure completed dkk 12/29/14 BEGIN CASE CASE PostCIDesc NE '' AND PostSig NE '' AND UnloadSig NE '' AND FinSig = '' Set_Property(@WINDOW:'.FINAL_SIG_BUTTON','ENABLED',1) CASE PostCIDesc = '' AND WfrSig NE '' AND UnloadSig NE '' AND FinSig = '' Set_Property(@WINDOW:'.FINAL_SIG_BUTTON','ENABLED',1) CASE 1 Set_Property(@WINDOW:'.FINAL_SIG_BUTTON','ENABLED',0) END CASE END ELSE Set_Property(@WINDOW:'.FINAL_SIG_BUTTON','ENABLED',0) END IF Get_Property(@WINDOW:'.HOT_LOT','CHECK') THEN *Set_Property(@WINDOW:'.HOT_LOT_LABEL','VISIBLE',1) END ELSE *Set_Property(@WINDOW:'.HOT_LOT_LABEL','VISIBLE',0) END LoadLockVal = Get_Property(@WINDOW:'.LOAD_LOCK_SIDE_HIDDEN','TEXT') ;* This little bit of code clears the default radio button (with much difficulty!) IF LoadLockVal = '' THEN CurrSaveWarn = Get_Property(@WINDOW,'SAVEWARN') Set_Property(@WINDOW:'.LOAD_LOCK_SIDE','DEFPROP','') IF NOT(CurrSaveWarn) THEN Set_Property(@WINDOW,'SAVEWARN',0) END END ReactType = Get_Property(@WINDOW:'.REACTOR_TYPE','INVALUE') Ctrls = @WINDOW:'.LOAD_LOCK_SIDE':@RM ; Props = 'ENABLED':@RM Ctrls := @WINDOW:'.ASM_LOAD_LOCK_LBL':@RM ; Props := 'ENABLED':@RM Ctrls := @WINDOW:'.ASM_LOAD_LOCK' ; Props := 'ENABLED' IF ReactType = 'ASM+' THEN Vals = STR('1':@RM,9) Vals[-1,1] = '' END ELSE Vals = STR('0':@RM,9) Vals[-1,1] = '' END Set_Property(Ctrls,Props,Vals) Ctrls = @WINDOW:'.WFR_REJECT_LABEL':@RM ; Props = 'VISIBLE':@RM Ctrls := @WINDOW:'.WFR_REJECT':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.MU_WFRS_ADDED_LABEL':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.MU_WFRS_ADDED':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.MU_WFRS_REMOVED_LABEL':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.MU_WFRS_REMOVED':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.CURR_WFR_CNT_LABEL':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.CURR_WFR_CNT':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.CASS_SHIP_QTY_LABEL':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.CASS_SHIP_QTY':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.SIG_PROFILE':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.LOAD_REQ_GROUP':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.FINAL_QA_GROUP':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.LOAD_SIG_BUTTON':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.LOAD_SIG_LABEL':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.LOAD_SIG':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.LOAD_SIG_DTM':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.UNLOAD_SIG_BUTTON':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.UNLOAD_SIG_LABEL':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.UNLOAD_SIG':@RM ; Props := 'VISIBLE':@RM Ctrls := @WINDOW:'.UNLOAD_SIG_DTM' ; Props := 'VISIBLE' IF ReactType = 'EPP' OR ReactType[1,6] = 'EpiPro' THEN END Else Vals = STR('1':@RM,13):STR('0':@RM,8) ; Vals[-1,1] = '' Set_Property(Ctrls,Props,Vals) SigProfileList = Get_Property(@WINDOW:'.SIG_PROFILE','LIST') SigProfCnt = COUNT(SigProfileList,@FM) + (SigProfileList NE '') NextStepSigProf = '' FOR I =1 TO SigProfCnt SigProf = SigProfileList Signature = SigProfileList StageStatus = SigProfileList BEGIN CASE CASE SigProf NE '' AND StageStatus EQ 'RUN' ;LineColor = LS3_GREEN$ CASE SigProf NE '' AND StageStatus EQ 'SIG' ;LineColor = ORANGE$ CASE SigProf NE '' AND Signature EQ '' ;LineColor = YELLOW$ CASE SigProf NE '' AND Signature NE '' ;LineColor = GREEN$ CASE SigProf EQ '' AND Signature EQ '' ;LineColor = WHITE$ CASE 1 ; LineColor = WHITE$ END CASE stat = Send_Message(@WINDOW:'.SIG_PROFILE','COLOR_BY_POS',0,I,LineColor) IF LineColor = YELLOW$ AND NextStepSigProf = '' THEN BasicSigProf = ICONV(SigProf,'[SIG_PROFILE_CONV]') BEGIN CASE CASE BasicSigProf = 'VER' ; NextStepSigProf = 'VER' CASE BasicSigProf = 'LOAD' ; NextStepSigProf = 'LOAD' CASE BasicSigProf = 'UNLOAD' ; NextStepSigProf = 'UNLOAD' CASE BasicSigProf = 'QA' ; NextStepSigProf = 'QA' END CASE END ;* End of check for unsigned line and null NextStepSigProf NEXT I WfrSigProfileList = Get_Property(@WINDOW:'.WFR_SIG_PROFILE','LIST') WfrSigProfCnt = COUNT(WfrSigProfileList,@FM) + (WfrSigProfileList NE '') NextStepSigProf = '' FOR I =1 TO WfrSigProfCnt SigProf = WfrSigProfileList Signature = WfrSigProfileList StageStatus = WfrSigProfileList BEGIN CASE CASE SigProf NE '' AND StageStatus EQ 'RUN' ;LineColor = LS3_GREEN$ CASE SigProf NE '' AND StageStatus EQ 'SIG' ;LineColor = ORANGE$ CASE SigProf NE '' AND Signature EQ '' ;LineColor = YELLOW$ CASE SigProf NE '' AND Signature NE '' ;LineColor = GREEN$ CASE SigProf EQ '' AND Signature EQ '' ;LineColor = WHITE$ CASE 1 ; LineColor = WHITE$ END CASE stat = Send_Message(@WINDOW:'.WFR_SIG_PROFILE','COLOR_BY_POS',0,I,LineColor) NEXT I VerReqCtrl = @WINDOW:'.VER_WFR_CNT' LoadReqCtrls = @WINDOW:'.LOAD_WFR_CNT':@RM LoadReqCtrls := @WINDOW:'.LOAD_LOCK_SIDE' UnloadReqCtrl = @WINDOW:'.WFR_UNLOAD_QTY' QAReqCtrls = @WINDOW:'.ADE_READ':@RM QAReqCtrls := @WINDOW:'.LAST_WAFER_RHO':@RM QAReqCtrls := @WINDOW:'.SHIFT':@RM QAReqCtrls := @WINDOW:'.FIN_WFR_CNT' QAReqCtrls := @WINDOW:'.FQA_LPD' ;* Added LPD's here -dkk 12/3/14 ClearCtrls = '' IF NextStepSigProf = 'VER' THEN Val = Get_Property(VerReqCtrl,'DEFPROP') IF Val = '' THEN BackColor = RED$ ELSE BackColor = WHITE$ Set_Property(VerReqCtrl,'BACKCOLOR',BackColor) END ELSE ClearCtrls := VerReqCtrl:@RM END IF NextStepSigProf = 'LOAD' THEN CtrlCnt = 2 Vals = Get_Property(LoadReqCtrls,'DEFPROP') BackColors = '' FOR I = 1 TO CtrlCnt IF FIELD(Vals,@RM,I) = '' THEN BackColors = FieldStore(BackColors,@RM,I,1,RED$) END ELSE BackColors = FieldStore(BackColors,@RM,I,1,WHITE$) END NEXT I Set_Property(LoadReqCtrls,'BACKCOLOR',BackColors) END ELSE ClearCtrls := LoadReqCtrls:@RM END IF NextStepSigProf = 'UNLOAD' THEN Val = Get_Property(UnloadReqCtrl,'DEFPROP') IF Val = '' THEN BackColor = RED$ ELSE BackColor = WHITE$ Set_Property(UnloadReqCtrl,'BACKCOLOR',BackColor) END ELSE ClearCtrls := UnloadReqCtrl:@RM END IF NextStepSigProf = 'QA' THEN CtrlCnt = 4 Vals = Get_Property(QAReqCtrls,'DEFPROP') BackColors = '' FOR I = 1 TO CtrlCnt IF FIELD(Vals,@RM,I) = '' THEN BackColors = FieldStore(BackColors,@RM,I,1,YELLOW$) END ELSE BackColors = FieldStore(BackColors,@RM,I,1,WHITE$) END NEXT I Set_Property(QAReqCtrls,'BACKCOLOR',BackColors) END ELSE ClearCtrls := QAReqCtrls:@RM END ClearCtrls[-1,1] = '' Set_Property(ClearCtrls,'BACKCOLOR',WHITE$) END ;* End of check for EpiPro reactor ************* * 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:'.SIG_PROFILE' AND ETCtrl NE @WINDOW:'.CHAR_WFR_ID' 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 ;* End of check for .SIG_PROFILE control NEXT I CtrlID = @WINDOW:'.RDS_LS_ID' LayerList = Get_Property(CtrlID,'LIST') FOR I = 1 TO COUNT(LayerList,@FM) + (LayerList NE '') IF ICONV(LayerList,'B') = 1 THEN ParmColor = RED$ END ELSE IF ICONV(LayerList,'B') = 0 THEN ParmColor = YELLOW$ EnableSignButton = 0 END ELSE ParmColor = GREEN$ END END FOR Col = COL$LSID TO COL$PARMS_OUT stat = Send_Message(CtrlID,'COLOR_BY_POS',Col,I,ParmColor) NEXT Col IF ICONV(LayerList,'B') = 0 THEN MetColor = ORANGE$ EnableLoadButton = 0 END ELSE IF ICONV(LayerList,'B') = 1 THEN MetColor = RED$ EnableSignButton = 0 END ELSE IF LayerList = '' AND LayerList = '' AND LayerList NE '' THEN MetColor = YELLOW$ EnableSignButton = 0 END ELSE MetColor = GREEN$ END END END FOR Col = COL$MET_NO TO COL$RRHO_AVG stat = Send_Message(CtrlID,'COLOR_BY_POS',Col,I,MetColor) NEXT Col IF ICONV(LayerList,'B') = 0 THEN MetColorZ1 = ORANGE$ EnableLoadButton = 0 END ELSE IF ICONV(LayerList,'B') = 1 THEN MetColorZ1 = RED$ EnableSignButton = 0 END ELSE IF LayerList = '' AND LayerList = '' AND LayerList NE '' THEN MetColorZ1 = YELLOW$ EnableSignButton = 0 END ELSE MetColorZ1 = PRE_BLUE$ END END END FOR Col = COL$MET_NO_Z1 TO COL$RRHO_AVG_Z1 stat = Send_Message(CtrlID,'COLOR_BY_POS',Col,I,MetColorZ1) NEXT Col IF ICONV(LayerList,'B') = 0 THEN MetColorZ2 = ORANGE$ EnableLoadButton = 0 END ELSE IF ICONV(LayerList,'B') = 1 THEN MetColorZ2 = RED$ EnableSignButton = 0 END ELSE IF LayerList = '' AND LayerList = '' AND LayerList NE '' THEN MetColorZ2 = YELLOW$ EnableSignButton = 0 END ELSE MetColorZ2 = INP_BLUE$ END END END FOR Col = COL$MET_NO_Z2 TO COL$RRHO_AVG_Z2 stat = Send_Message(CtrlID,'COLOR_BY_POS',Col,I,MetColorZ2) NEXT Col NEXT I CtrlID = @WINDOW:'.CHAR_WFR_ID' CharWfrList = Get_Property(CtrlID,'LIST') FOR I = 1 TO COUNT(CharWfrList,@FM) + (CharWfrList NE '') CurrStage = CharWfrList CharDest = CharWfrList StageStatus = CharWfrList BEGIN CASE CASE SigProf NE '' AND StageStatus EQ 'RUN' ;LineColor = LS3_GREEN$ CASE SigProf NE '' AND StageStatus EQ 'SIG' ;LineColor = ORANGE$ CASE SigProf NE '' AND StageStatus EQ 'PART' ;LineColor = GREY$ CASE SigProf NE '' AND Signature EQ '' ;LineColor = YELLOW$ CASE SigProf NE '' AND Signature NE '' ;LineColor = GREEN$ CASE SigProf EQ '' AND Signature EQ '' ;LineColor = WHITE$ CASE 1 ; LineColor = WHITE$ END CASE * * * * * * * Change to display 'DEST' column to red if destroyed, rest of line to LineColor ********** **************************** BEGIN CASE CASE CurrStage = '-' ; ParmColor = GREEN$ CASE CurrStage NE '' ; ParmColor = LineColor CASE 1 ; ParmColor = WHITE$ END CASE stat = Send_Message(CtrlID,'COLOR_BY_POS',0,I,ParmColor) IF CharDest = 'Yes' THEN stat = Send_Message(CtrlID,'COLOR_BY_POS',COL$CHAR_DEST,I,RED$) END NEXT I RETURN * * * * * * * Read: * * * * * * * ReactNo = Get_Property(@WINDOW:'.REACTOR','DEFPROP') ReactType = XLATE('REACTOR',ReactNo,REACTOR_REACT_TYPE$,'X') IF ReactType = 'EPP' THEN PSNo = Get_Property(@WINDOW:'.PS_NO','DEFPROP') ReactorLoad = Get_Property(@WINDOW:'.REACTOR_LOAD','LIST') CurrPockets = ReactorLoad CONVERT @VM TO '' IN CurrPockets IF CurrPockets = '' THEN PSNWaferSize = XLATE('PROD_SPEC',PSNo,'SUB_WAFER_SIZE','X') BEGIN CASE CASE PSNWaferSize = '150 mm 6 in' EpiSusceptor = XLATE('EPI_SUSCEPTOR','6','','X') CASE PSNWaferSize = '125 mm 5 in' EpiSusceptor = XLATE('EPI_SUSCEPTOR','5','','X') CASE 1 ErrorMsg = 'PSN: ':QUOTE(PSNo):' has a wafer size of ':PSNWaferSize:'.':CRLF$:CRLF$ ErrorMsg := 'The EpiPRO reactors cannot process wafers of this size.' ErrMsg(ErrorMsg) GOSUB Refresh RETURN END CASE Pockets = EpiSusceptor Zones = EpiSusceptor PTypes = EpiSusceptor FOR I = 1 TO COUNT(Pockets,@VM) + (Pockets NE '') Set_Property(@WINDOW:'.REACTOR_LOAD','CELLPOS',Pockets<1,I>,COL$POCKET:@FM:I) Set_Property(@WINDOW:'.REACTOR_LOAD','CELLPOS',PTypes<1,I>,COL$USAGE:@FM:I) Set_Property(@WINDOW:'.REACTOR_LOAD','CELLPOS',Zones<1,I>,COL$ZONE:@FM:I) NEXT I END ;* End of check for Pocket column data END ;* End of check for EpiPro reactor type GOSUB Refresh RETURN * * * * * * * Page: * * * * * * * Page = Get_Property(@WINDOW:'.TABCONTROL', 'VALUE') Set_Property(@WINDOW,'VPOSITION', Page) RETURN * * * * * * * VScroll: * * * * * * * Page = Parm1 Set_Property(@WINDOW:'.TABCONTROL','VALUE', Page) RETURN * * * * * * * Write: * * * * * * * prevControl = Get_Property("SYSTEM" , "PREVFOCUS") Result = 1 RETURN * * * * * * * Delete: * * * * * * * /* IF Security_Check('Order',Delete$) THEN Result = 1 ;* Proceed with delete END ELSE Security_Err_Msg('Order',Delete$) Result = 0 ;* Stop event chain END */ RETURN * * * * * * * RDSNoLF: * * * * * * * PromptDataIn = Get_Property(@WINDOW:'.RDS_NO','DEFPROP') CONVERT '.' TO '*' IN PromptDataIN IF INDEX(PromptDataIn,'*',1) THEN WOMatRec = XLATE('WO_MAT',PromptDataIn,'','X') IF WOMatRec NE '' THEN RDSNos = WOMatRec IF RDSNos NE '' THEN IF INDEX(RDSNos,@VM,1) THEN TypeOver = '' TypeOver = RDSNos RDSNo = Popup(@WINDOW,TypeOver,'REACT_RUN') IF RDSNo = CHAR(27) OR RDSNo = '' THEN RETURN Set_Property(@WINDOW:'.RDS_NO','DEFPROP','') obj_AppWindow('LoadFormKeys',@WINDOW:@RM:RDSNo) END ELSE Set_Property(@WINDOW:'.RDS_NO','DEFPROP','') obj_AppWindow('LoadFormKeys',@WINDOW:@RM:RDSNos) END END ELSE * Must be EpiPro WMIRdsNos = XLATE('WO_MAT',PromptDataIn,'WMI_RDS_NO','X') WMISlotNCRs = XLATE('WO_MAT',PromptDataIn,'WMI_SLOT_NCR','X') WMORdsNos = XLATE('WO_MAT',PromptDataIn,'WMO_RDS_NO','X') WMOSlotNCRs = XLATE('WO_MAT',PromptDataIn,'WMO_SLOT_NCR','X') WMICnt = COUNT(WMIRdsNos,@VM) + (WMIRdsNos NE '') WMOCnt = COUNT(WMORdsNos,@VM) + (WMORdsNos NE '') InboundRDSs = '' OutBoundRDSs = '' FOR I = 1 TO WMICnt RDSNo = WMIRdsNos<1,I> IF WMISlotNCRs<1,I> = '' THEN LOCATE RDSNo IN InboundRDSs USING @VM SETTING Pos ELSE InboundRDSs = INSERT(InboundRDSs,1,Pos,0,RDSNo) END END NEXT I FOR I = 1 TO WMOCnt RDSNo = WMORdsNos<1,I> IF WMOSlotNCRs<1,I> = '' THEN LOCATE RDSNo IN OutboundRDSs USING @VM SETTING Pos ELSE OutboundRDSs = INSERT(OutboundRDSs,1,Pos,0,RDSNo) END END NEXT I IRCnt = COUNT(InboundRDSs,@VM) + (InboundRDSs NE '') ORCnt = COUNT(OutboundRDSs,@VM) + (OutboundRDSs NE '') Display = '' FOR I = 1 TO IRCnt Display<1,-1> = 'Inbound':@SVM:InboundRDSs<1,I> NEXT I FOR I = 1 TO ORCnt Display<1,-1> = 'Outbound':@SVM:OutboundRDSs<1,I> NEXT I TypeOver = '' TypeOver = Display RDSNo = Popup(@WINDOW,TypeOver,'EPI_PRO_WO_MAT_RDS') IF RDSNo = CHAR(27) OR RDSNo = '' THEN RETURN Set_Property(@WINDOW:'.RDS_NO','DEFPROP','') obj_AppWindow('LoadFormKeys',@WINDOW:@RM:RDSNo) END END END RETURN * * * * * * * CIClick: * * * * * * * CINO = 0 CurrCtrl = Parm1 /*BEGIN CASE CASE CurrCtrl = @WINDOW:'.PRE_EPI_CI_BUTTON' ; CIKey = Get_Property(@WINDOW:'.PRE_EPI_CI_BUTTON','TEXT') CASE CurrCtrl = @WINDOW:'.UNLOAD_CI_BUTTON' ; CIKey = Get_Property(@WINDOW:'.UNLOAD_CI_BUTTON','TEXT') CASE CurrCtrl = @WINDOW:'.POST_CI_BUTTON' ; CIKey = Get_Property(@WINDOW:'.POST_CI_BUTTON','TEXT') CASE 1 ; RETURN END Case*/ BEGIN Case ;* Substituted for remarked out code above. Copied from COMM_RDS. -dkk 10/22/14 CASE @WINDOW = 'REACT_RUN' ;* CASE @WINDOW = 'RDS_PRE_EPI' Stage = 'PRE' CICtrl = @WINDOW:'.PRE_EPI_CI_BUTTON' CASE @WINDOW = 'REACT_RUN' ;* CASE @WINDOW = 'RDS' Stage = 'FWI' CICtrl = @WINDOW:'.LOAD_CI_BUTTON' CASE @WINDOW = 'REACT_RUN' ;* CASE @WINDOW = 'RDS_UNLOAD' Stage = 'LWI' CICtrl = @WINDOW:'.UNLOAD_CI_BUTTON' CASE @WINDOW = 'REACT_RUN' ;* CASE @WINDOW = 'RDS_POST_EPI' Stage = 'POST' CICtrl = @WINDOW:'.POST_CI_BUTTON' CASE 1 ; RETURN END CASE DetWindow = 'CLEAN_INSP' DetKeys = CINO DefaultRec = '' obj_AppWindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:'') RETURN * * * * * * * LURunPri: * * * * * * * RunPri = Popup(@WINDOW,'','GAN_WFR_PRIORITY') IF RunPri = CHAR(27) THEN RETURN ;* Canceled obj_Appwindow('LUValReturn',RunPri:@RM:@WINDOW:'.RUN_PRI') GOSUB Refresh RETURN * * * * * * * LURDSNo: * * * * * * * RETURN * * * * * * * LUReactNo: * * * * * * * ReactorNo = Get_Property(@WINDOW:'.REACTOR','DEFPROP') Set_Status(0) ReactorNo = Popup(@WINDOW,'','REACTORS') IF ReactorNo = '' THEN RETURN obj_Appwindow('LUValReturn',ReactorNo:@RM:@WINDOW:'.REACTOR') RETURN RETURN * * * * * * * LUReactEsc: * * * * * * * IF NOT(ASSIGNED(Parm1)) THEN FocusControl = '' ELSE FocusControl = Parm1 IF NOT(ASSIGNED(Parm2)) THEN FocusPos = '' ELSE FocusPos = Parm2 Set_Status(0) EventKeys = obj_React_Esc('Find') IF Get_Status(errCode) THEN ErrMsg(ErrCode) IF INDEX(EventKeys,@VM,1) THEN TypeOver = '' TypeOver = 'K' TypeOver = EventKeys EventKeys = Popup(@WINDOW,TypeOver,'REACT_ESC_QUERY') END CONVERT @VM TO @FM IN EventKeys IF INDEX(EventKeys,@FM,1) THEN Send_Event(@WINDOW,'QBFINIT') Set_Property(@WINDOW,'QBFLIST',EventKeys) GOSUB Refresh Send_Event(@WINDOW,'QBFIRST') END ELSE obj_Appwindow('LoadFormKeys',@WINDOW:@RM:EventKeys) END RETURN * * * * * * * Close: * * * * * * * obj_Notes('Inbox',@USER4) ;* Checks for any new messages Parent = Get_Property(@WINDOW,'PARENT') IF Parent[1,7] = 'WO_PROD' THEN Post_Event(Parent, 'READ') END RETURN * * * * * * * CopyMetrology: * * * * * * * RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP') WONo = Get_Property(@Window:'.WO_NO', 'TEXT') DestRDSNos = Dialog_Box('NDW_RDS_QUERY', @Window, WONo : @FM : 'quick') SourceMetKeys = obj_React_Run('GetMetKeys',RDSNo) RDSCnt = COUNT(DestRDSNos,@VM) + (DestRDSNos NE '') FOR I = 1 TO RDSCnt Copy = 1 ;* Set flag DestRDSNo = DestRDSNos<1,I> MetEntered = XLATE('RDS',DestRDSNo,'LS_MET_ENTERED','X') ;* @VM list of binary values by layer IF MetEntered[1,1] = 1 THEN MsgInfo = '' MsgInfo = 'RDS ':DestRDSNo:' already has Metrology Results. Do you wish to overwrite them?' MsgInfo = '?' MsgInfo = 'BNY' MsgInfo = '2' ;* This sets the default to the No button Copy = Msg(@WINDOW,MsgInfo) END IF Copy THEN DestMetKeys = obj_React_Run('GetMetKeys',DestRDSNo) IF SourceMetKeys<1> = DestMetKeys<1> THEN Set_Status(0) obj_RDS_Test('CopyStats',SourceMetKeys<2>:@RM:DestMetKeys<2>) IF Get_Status(errCode) THEN ErrMsg(errCode) END END ELSE ErrMsg('SourceMetKeys not equal DestMetKeys: Contact FI') END END ;* End of check for Copy flag NEXT I RETURN * * * * * * * LSIdDC: * * * * * * * CtrlEntID = @WINDOW:'.RDS_LS_ID' RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP') IF Get_Property(@WINDOW,'SAVEWARN') THEN Set_Property(@WINDOW,'@SKIP_SAVEWARN',0) END ELSE Set_Property(@WINDOW,'@SKIP_SAVEWARN',1) END CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> IF CurrCol LT COL$MET_NO THEN LSId = Get_Property(CtrlEntID,'CELLPOS',COL$LSID:@FM:CurrRow) IF RDSNo NE '' AND LSId NE '' THEN Send_Event('REACT_RUN','WRITE') RdsLSID = RDSNo:'*':LSId DetWindow = 'RDS_LAYER' DetKeys = RdsLSID DefaultRec = '' RetKey = RDSNo RetWin = @WINDOW RetPage = 1 RetCtrl = CtrlEntID RetPos = CurrPos obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos) END END IF CurrCol = COL$MET_NO OR CurrCol = COL$MET_NO_Z1 OR CurrCol = COL$MET_NO_Z2 THEN MetNo = Get_Property(CtrlEntID,'CELLPOS',CurrCol:@FM:CurrRow) IF MetNo NE '' THEN Send_Event('REACT_RUN','WRITE') DetWindow = 'RDS_TEST' DetKeys = MetNo DefaultRec = '' RetKey = RDSNo RetWin = 'RDS' RetPage = 1 RetCtrl = CtrlEntID RetPos = CurrPos obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos) END END RETURN * * * * * * * AddZoneMet: * * * * * * * CtrlEntID = @WINDOW:'.RDS_LS_ID_FIX' RDSNo = Get_Property(@WINDOW:'.RDS_NO_FIX','DEFPROP') PSNo = Get_Property(@WINDOW:'.PS_NO_FIX','DEFPROP') LSArray = Get_Property(CtrlEntID,'DEFPROP') LSIDs = LSArray MetNos = LSArray MetNosZ1 = LSArray MetNosZ2 = LSArray MetTest = MetNos Z1Test = MetNosZ1 Z2Test = MetNosZ2 CONVERT @VM TO '' IN MetTest CONVERT @VM TO '' IN Z1Test CONVERT @VM TO '' IN Z2Test IF MetTest = '' THEN BEGIN CASE CASE Z1Test = '' AND Z2Test = '' * Ask for z1 or z2 TypeOver = '' TypeOver = 'B&1,&2,&Cancel' TypeOver = 'Add Reactor Zone Metrology' TypeOver = '?' TypeOver = '3' TypeOver = 'Add Metrology for Zone:' NewZone = Msg(@WINDOW,TypeOver,'') IF NewZone = 3 THEN RETURN CASE Z1Test = '' AND Z2Test NE '' NewZone = 1 CASE Z1Test NE '' AND Z2Test = '' NewZone = 2 CASE 1 ErrMsg('No open Zone to move to.') RETURN END CASE Send_Event(@WINDOW,'WRITE') FOR I = 1 TO COUNT(LSIDs,@VM) + (LSIDs NE '') IF LSIDs<1,I> NE '' THEN LSID = LSIDs<1,I> oRTParms = RDSNo:@RM oRTParms := LSID:@RM oRTParms := PSNo:@RM oRTParms := NewZone obj_RDS_Test('Create',oRTPARms) END NEXT I Set_Property(@WINDOW:'.RDS_NO','DEFPROP',RDSNo) Send_Event(@WINDOW,'READ') END RETURN * * * * * * * MoveMetToZone: * * * * * * * CtrlEntID = @WINDOW:'.RDS_LS_ID_FIX' RDSNo = Get_Property(@WINDOW:'.RDS_NO_FIX','DEFPROP') LSArray = Get_Property(CtrlEntID,'DEFPROP') MetNos = LSArray MetNosZ1 = LSArray MetNosZ2 = LSArray MetTest = MetNos Z1Test = MetNosZ1 Z2Test = MetNosZ2 CONVERT @VM TO '' IN MetTest CONVERT @VM TO '' IN Z1Test CONVERT @VM TO '' IN Z2Test IF MetTest NE '' THEN BEGIN CASE CASE Z1Test = '' AND Z2Test = '' * Ask for z1 or z2 TypeOver = '' TypeOver = 'B&1,&2,&Cancel' TypeOver = 'Move Metrology to Reactor Zone' TypeOver = '?' TypeOver = '3' TypeOver = 'Move Metrology to Zone:' DestZone = Msg(@WINDOW,TypeOver,'') IF DestZone = 3 THEN RETURN CASE Z1Test = '' AND Z2Test NE '' DestZone = 1 CASE Z1Test NE '' AND Z2Test = '' DestZone = 2 CASE 1 ErrMsg('No open Zone to move to.') RETURN END CASE Send_Event(@WINDOW,'WRITE') FOR I = 1 TO COUNT(MetNos,@VM) + (MetNos NE '') IF MetNos<1,I> NE '' THEN MetNo = MetNos<1,I> oRTParms = MetNo:@RM oRTParms := DestZone obj_RDS_Test('SetZone',oRTPARms) END NEXT I Set_Property(@WINDOW:'.RDS_NO','DEFPROP',RDSNo) Send_Event(@WINDOW,'READ') END RETURN * * * * * * * ViewWOMat: * * * * * * * Ctrls = @WINDOW:'.WO_NO':@RM ; Props = 'DEFPROP':@RM Ctrls := @WINDOW:'.CASS_NO':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.RDS_NO':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.REACTOR':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.WO_STEP' ; Props := 'DEFPROP' Vals = Get_Property(Ctrls,Props) WONo = Vals[1,@RM] CassNo = Vals[COL2()+1,@RM] RDSNo = Vals[COL2()+1,@RM] Reactor = Vals[COL2()+1,@RM] WOStep = Vals[COL2()+1,@RM] Send_Event(@WINDOW,'WRITE') thisFormWindowUp = Get_Property('WO_MAT_WFR','VISIBLE') ;* Returns 0 = hidden, 1 = visible, 2 = minimized, 3 = maximized IF thisFormWindowUp = '' THEN Start_Window('WO_MAT_WFR',@WINDOW,'') END ELSE IF thisFormWindowUp = 2 THEN Set_Property('WO_MAT_WFR','VISIBLE',9) ;* Restore the window if minimized IF Get_Property('WO_MAT_WFR','SAVEWARN') THEN Set_Property('WO_MAT_WFR','@SKIP_CARD_RETURN',1) ;* This stops the Return behavior Send_Event('WO_MAT_WFR','CLEAR') ;* Clear anything existing (prompts for save first) END END * Load Key Controls with Key Parts Ctrls = 'WO_MAT_WFR':@RM ; Props = '@RETURN_KEY':@RM ; Vals = RDSNo:@RM Ctrls := 'WO_MAT_WFR':@RM ; Props := '@RETURN_PAGE':@RM ; Vals := '':@RM Ctrls := 'WO_MAT_WFR':@RM ; Props := '@RETURN_CONTROL':@RM ; Vals := '':@RM Ctrls := 'WO_MAT_WFR':@RM ; Props := '@RETURN_POS':@RM ; Vals := '':@RM Ctrls := 'WO_MAT_WFR':@RM ; Props := '@RDS_NO':@RM ; Vals := RDSNo:@RM Ctrls := 'WO_MAT_WFR':@RM ; Props := '@REACTOR':@RM ; Vals := Reactor:@RM Ctrls := 'WO_MAT_WFR':@RM ; Props := '@WO_STEP_NO':@RM ; Vals := WOStep:@RM Ctrls := 'WO_MAT_WFR.WO_NO':@RM ; Props := 'DEFPROP':@RM ; Vals := WONo:@RM Ctrls := 'WO_MAT_WFR.CASS_NO' ; Props := 'DEFPROP' ; Vals := CassNo Set_Property(Ctrls,Props,Vals) Send_Event('WO_MAT_WFR.CASS_NO','LOSTFOCUS') RETURN * * * * * * * SendMsg: * * * * * * * CurrWindow = @WINDOW CurrKey = Get_Property(CurrWindow,'ID') IF CurrKey = '' THEN MsgInfo = '' MsgInfo = 'You must have a record present...' MsgInfo = 'H' Msg( '', MsgInfo ) RETURN END IF RowExists('REACT_RUN',CurrKey) THEN NoteID = NextKey('NOTES') obj_AppWindow('ViewRelated','NOTE_MESSAGE':@RM:NoteID:@RM:@WINDOW:@FM:CurrKey) END ELSE MsgInfo = '' MsgInfo = 'You must save this run data sheet first...' MsgInfo = 'H' Msg( '', MsgInfo ) END RETURN * * * * * * * CtrlPlanClick: * * * * * * * PSNo = Get_Property(@WINDOW:'.PS_NO','DEFPROP') IF PSNo NE '' THEN Print_Control_Plan(PSNo) 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 * * * * * * * ViewWO: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') IF WONo NE '' THEN NewForm = Xlate('APP_INFO', 'NEW_WO_FORM', '', 'X') If NewForm then Start_Window('NDW_WO_LOG', @Window, WONo) end else Start_Window('WO_LOG2',@WINDOW, WONo:'*CENTER', '', '' ) ;* Added (copied from ViewPSN) -dkk 10/23/14 end END RETURN * * * * * * * PrintInstruction: * * * * * * * RDSNo = Get_Property(@WINDOW:'.RDS_NO','TEXT') IF RDSNo NE '' THEN Print_RDS_Instruction(RDSNo) END RETURN * * * * * * * SignSuppl: * * * * * * * IF MemberOf( @USER4, 'DATA_ENTRY' ) OR MemberOf( @USER4, 'SUPERVISOR' ) THEN Valid = Dialog_Box( 'QUOTE_SIG_PWD_ENTRY', @WINDOW, @USER4:@VM:XLATE( 'LSL_USERS', @USER4, LSL_USERS_PASSWORD$, 'X' ) ) IF Valid THEN Set_Property(@WINDOW:'.SUPP_SIG','INVALUE',@USER4) *Set_Property(@WINDOW:'.SUPP_SIG','TEXT',XLATE('LSL_USERS',@USER4,'FIRST_LAST','X' ) Set_Property(@WINDOW:'.SUPP_SIG_DTM','INVALUE',ICONV(OCONV(Date(), 'D4/'):' ':OCONV(Time(), 'MTHS'),'DT')) END END ELSE MsgInfo = '' MsgInfo = '!' MsgInfo = 'Only cleanroom personnel are permitted to sign the work order verification.' Msg( '', MsgInfo ) END RETURN * * * * * * * SignFinalQA: * * * * * * * Ctrls = @WINDOW:'RDS_NO':@RM ; Props = 'DEFPROP':@RM Ctrls := @WINDOW:'.WO_NO':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.CASS_NO':@RM ; Props := 'DEFPROP':@RM Ctrls := @WINDOW:'.STEP_NO' ; Props := 'DEFPROP' Vals = Get_Property(Ctrls,Props) RDSNo = Vals[1,@RM] WONo = Vals[COL2()+1,@RM] CassNo = Vals[COL2()+1,@RM] StepNo = Vals[COL2()+1,@RM] RETURN /* * This section adjusts the SchedQty on the Next RDS to run on this box WOMatRec = XLATE('WO_MAT',WONo:'*':CassNo,'','X') WOMRDSKeys = WOMatRec LOCATE RDSNo IN WOMRDSKeys USING @VM SETTING Pos THEN IF WOMRDSKeys<1,Pos+1> NE '' THEN NextRDSNo = WOMRDSKeys<1,Pos+1> CurrWfrQty = obj_WO_Mat('CurrWaferCnt',WONo:'*':CassNo:@RM:WOMatRec) obj_React_Run('SetSchedWfrCnt', END ;* End of check for next WO_Step run END */ RETURN * * * * * * * SigProfileClick: * * * * * * * CtrlEntID = @WINDOW:'.SIG_PROFILE' SigList = Get_Property(CtrlEntID,'LIST') CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrRow = CurrPos<2> CurrSigProf = ICONV(SigList,'[SIG_PROFILE_CONV]') RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP') CurrStage = CurrSigProf IF RDSNo NE '' AND CurrStage NE '' THEN RunStageKey = RDSNo:'*':CurrStage Send_Event('REACT_RUN','WRITE') DetWindow = 'RUN_STAGE' DetKeys = RunStageKey DefaultRec = '' RetKey = RDSNo RetWin = @WINDOW RetPage = 1 RetCtrl = @WINDOW:'.RDS_NO' RetPos = CurrPos obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos) IF Get_Status(errCode) THEN ErrMsg(errCode) END END RETURN * * * * * * * CharWfrDC: * * * * * * * CtrlEntID = @WINDOW:'.CHAR_WFR_ID' RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP') IF RDSNo = '' THEN RETURN CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> WfrList = Get_Property(CtrlEntID,'LIST') CharWfrID = WfrList BEGIN CASE CASE CurrCol = COL$CHAR_WFR_ID WfrSigProfile = obj_React_Run('GetWfrSigKeys',RDSNo:@RM:CharWfrID) TypeOver = '' TypeOver = WfrSigProfile RunStageWfrKey = Popup(@WINDOW,TypeOver,'CHAR_WFR_STAGES') IF Get_Status(errCode) THEN ErrMsg(errCode) IF RunStageWfrKey = CHAR(27) OR RunStageWfrKey = '' THEN RETURN Send_Event('REACT_RUN','WRITE') DetWindow = 'RUN_STAGE_WFR' DetKeys = RunStageWfrKey DefaultRec = '' RetKey = RDSNo RetWin = @WINDOW RetPage = 1 RetCtrl = @WINDOW:'.RDS_NO' RetPos = CurrPos obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos) IF Get_Status(errCode) THEN ErrMsg(errCode) END CASE CurrCol = COL$CURR_STAGE CurrStage = WfrList CurrStatus = WfrList IF CurrStatus = 'PART' THEN Msg(@WINDOW,'','PART_CHAR') RETURN END IF CurrStage = '-' THEN RunStageWfrKey = '' END ELSE WfrKID = CharWfrID CONVERT '*' TO '.' IN WfrKID RunStageWfrKey = RDSNo:'*':CurrStage:'*':WfrKID Send_Event('REACT_RUN','WRITE') DetWindow = 'RUN_STAGE_WFR' DetKeys = RunStageWfrKey DefaultRec = '' RetKey = RDSNo RetWin = @WINDOW RetPage = 1 RetCtrl = @WINDOW:'.RDS_NO' RetPos = CurrPos obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos) IF Get_Status(errCode) THEN ErrMsg(errCode) END END CASE CurrCol = COL$CHAR_TW_NO TWNo = WfrList IF TWNo NE '' THEN DetWindow = 'TEST_WAFER' DetKeys = TWNo DefaultRec = '' RetKey = RDSNo RetPage = 1 RetCtrl = CtrlEntID RetPos = CurrPos oAParms = DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos obj_AppWindow('ViewNewDetail',oAParms) IF Get_Status(errCode) THEN ErrMsg(errCode) END END CASE 1 NULL END CASE RETURN * * * * * * * CharWfrOptions: * * * * * * * CtrlEntID = @WINDOW:'.CHAR_WFR_ID' CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> WfrList = Get_Property(CtrlEntID,'LIST') CharWfrID = WfrList IF CharWfrID NE '' THEN TraceData = obj_WO_Wfr('TraceData',CharWfrID:@RM:'') END TypeOver = '' TypeOver = TraceData void = Popup(@WINDOW,TypeOver,'WAFER_TRACE') IF Get_Status(errCode) THEN ErrMsg(errCode) RETURN END RETURN * * * * * * * CarrWfrDC: * * * * * * * RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP') IF RDSNo = '' THEN RETURN CtrlEntID = @WINDOW:'.CARR_WFR_ID' CurrList = Get_Property(CtrlEnTID,'LIST') CurrPos = Get_Property(CtrlEntID,'NOTIFYPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> BEGIN CASE CASE CurrCol = COL$CARR_NCR NCRNo = CurrList IF NCRNo NE '' THEN Send_Event('REACT_RUN','WRITE') DetWindow = 'NCR' DetKeys = NCRNo DefaultRec = '' RetKey = RDSNo RetPage = 1 RetCtrl = CtrlEntID RetPos = CurrPos obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos) END END CASE RETURN * * * * * * * SplitClick: * * * * * * * RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP') CarrWfrIDs = Get_Property(@WINDOW:'.CARR_WFR_ID','DEFPROP')<1> Stage = '' ToolID = '' TestCarrWfrIDs = CarrWfrIDs CONVERT @VM TO '' IN TestCarrWfrIDS IF TestCarrWfrIDs = '' THEN ErrMsg('Wafers have not been unloaded from the reactor.') RETURN END Send_Event(@WINDOW,'WRITE') * The process of splitting the wafer writes the REACT_RUN record after pulling stuff off the window * WfrID = Dialog_Box('DIALOG_SPLIT_WAFER', 'REACT_RUN', RDSNo:@FM:Stage:@FM:ToolID:@FM:CarrWfrIDs) IF Get_Status(errCode) THEN ErrMsg(errCode) RETURN END obj_Appwindow('LoadFormKeys','REACT_RUN':@RM:RDSNo) ;* Reloads the updated REACT_RUN record RETURN * * * * * * * DispoClick: * * * * * * * RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP') Send_Event(@WINDOW,'WRITE') DetWindow = 'REACT_RUN_DISP' DetKeys = RDSNo DefaultRec = '' RetKey = RDSNo RetPage = 1 RetCtrl = '' RetPos = '' obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos) IF Get_Status(errCode) THEN ErrMsg(errCode) RETURN END RETURN SUSC_LOAD.OPTIONS: CtrlEntID = @WINDOW:'.SUSC_LOAD' SelPos = Get_Property(CtrlEntID, 'SELPOS') Array = Get_Property(CtrlEntID, 'ARRAY') ColPos = SelPos<1> RowPos = SelPos<2> WOWfrID = Array rv = Dialog_Box('DIALOG_WO_WFR_SCRIBE', @Window, WOWfrID) Send_Event(CtrlEntID, 'CALCULATE', COL$SUSC_LOAD_WFR_SCRIBE) return