COMPILE FUNCTION Comm_WO_Prod(Instruction, Parm1,Parm2) /* Commuter module for WO_Prod, Read Only WO Step window for production use (Work Order Step) Work Order step table 11/11/2004 - John C. Henry, J.C. Henry & Co., Inc. */ DECLARE SUBROUTINE Set_Property, Set_Status, ErrMsg, Set_Property, obj_AppWindow, obj_Notes, obj_WO_Log DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, Forward_Event, End_Window, Start_Window, obj_WM_IN, obj_WM_Out DECLARE SUBROUTINE Print_Control_Plan DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box, RowExists DECLARE FUNCTION Dialog_Box, obj_WO_Log, obj_WM_In, obj_RDS, obj_React_Run, MemberOf $INSERT POPUP_EQUATES $INSERT LOGICAL $INSERT MSG_EQUATES $INSERT APPCOLORS $INSERT REACT_RUN_EQUATES $INSERT WO_LOG_EQU $INSERT WO_STEP_EQU $INSERT WM_IN_EQUATES $INSERT WM_OUT_EQUATES $INSERT WO_MAT_EQUATES $INSERT NOTIFICATION_EQU $INSERT ORDER_EQU $INSERT LSL_USERS_EQU $INSERT SECURITY_RIGHTS_EQU $INSERT QUOTE_SIGS_EQU EQU CRLF$ TO \0D0A\ EQU COL$ADD_DESC TO 1 EQU COL$ADD_AMT TO 2 EQU COL$CASS_NO TO 1 EQU COL$RDS_NO TO 2 EQU COL$REACTOR TO 3 EQU COL$HOT_LOT TO 4 EQU COL$STEP_COMMIT_DT TO 5 EQU COL$HOLD TO 6 EQU COL$MAKEUP_BOX TO 7 EQU COL$RDS_STATUS TO 14 ErrTitle = 'Error in Comm_WO_Log' ErrorMsg = '' Result = '' BEGIN CASE CASE Instruction = 'Create' ; GOSUB Create CASE Instruction = 'Refresh' ; GOSUB Refresh CASE Instruction = 'Page' ; GOSUB Page CASE Instruction = 'Read' ; GOSUB Read CASE Instruction = '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 = 'StepGF' ; GOSUB StepGF CASE Instruction = 'OpenWOS' ; GOSUB OpenWOS CASE Instruction = 'ViewProdSpec' ; GOSUB ViewProdSpec CASE Instruction = 'CassPC' ; GOSUB CassPC CASE Instruction = 'CassDC' ; GOSUB CassDC CASE Instruction = 'LUWONo' ; GOSUB LUWONo CASE Instruction = 'BrowseRDS' ; GOSUB BrowseRDS CASE Instruction = 'RemCassettes' ; GOSUB RemCassettes CASE Instruction = 'ControlPlanClick' ; GOSUB ControlPlanClick CASE 1 ErrorMsg = 'Unknown Instruction passed to routine' END CASE RETURN Result * * * * * * * Create: * * * * * * * obj_Appwindow('Create',@WINDOW) QuoteSigs = XLATE( 'CONFIG', 'QUOTE_SIGS','', 'X' ) IF @USER4 = QuoteSigs OR MemberOf(@USER4, 'OI_SUPERUSER') THEN Set_Property(@WINDOW:'.REM_CASSETTES','VISIBLE',1) END ELSE Set_Property(@WINDOW:'.REM_CASSETTES','VISIBLE',0) END GOSUB Refresh RETURN * * * * * * * Read: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','TEXT') IF RowExists('WO_LOG',WONo) ELSE ErrMsg('Incorrect Work Order Number entered.') Send_Event(@WINDOW,'CLEAR') RETURN END GOSUB Refresh RETURN * * * * * * * Write: * * * * * * * RETURN * * * * * * * Clear: * * * * * * * Send_Event(@WINDOW,'PAGE',1) GOTO Refresh RETURN * * * * * * * Delete: * * * * * * * RETURN * * * * * * * Page: * * * * * * * obj_Appwindow('Page') GOSUB Refresh RETURN * * * * * * * Close: * * * * * * * obj_Appwindow('DetailReturn') RETURN * * * * * * * WONoLF: * * * * * * * DataValue = Get_Property(@WINDOW:'.WO_NO','TEXT') If DataValue = '' Then Return IF INDEX(DataValue,'.',1) THEN * Try a BTREE lookup on PROD_ORD_NO OPEN 'DICT.WO_LOG' TO DictVar ELSE ErrMsg('Unable to open "DICT.WO_LOG" for index lookup in COMM_SHIPMENT routine.') RETURN END SearchString = 'PROD_ORD_NO':@VM:DataValue:@FM WONos = '' Flag = '' Btree.Extract(SearchString, 'WO_LOG', DictVar, WONos, '', Flag) IF Get_Status(errCode) THEN ErrMsg(errCode) RETURN END IF WONos = '' THEN ErrMsg('Value Entered "':DataValue:'" is not found.') Result = 0 RETURN END IF INDEX(WONos,@VM,1) THEN * This is an error ErrMsg('Multiple Work Orders ':QUOTE(DataValue):' for Prod Order entered.') Result = 0 RETURN END ELSE Set_Property(@WINDOW:'.WO_NO','DEFPROP',WONos) END Result = 1 END ELSE IF RowExists('WO_LOG', DataValue) THEN Result = 1 END ELSE Message = QUOTE(DataValue):' is not a valid WO No' ErrMsg(Message) Set_Property(@WINDOW:'.WO_NO','DEFPROP','') Result = 0 END END RETURN * * * * * * * Refresh: * * * * * * * PSStatus = Get_Property(@WINDOW:'.PS_STATUS','TEXT') IF PSStatus = 'Active' THEN Set_Property(@WINDOW:'.PS_STATUS','BACKCOLOR',GREEN$) END ELSE Set_Property(@WINDOW:'.PS_STATUS','BACKCOLOR',RED$) END * All cassette detail background colors CtrlName = @WINDOW:'.CASSETTES' CassArray = Get_Property(CtrlName,'INVALUE') RdsStatuses = CassArray FOR I = 1 TO COUNT(RdsStatuses,@VM) + (RdsStatuses NE '') RdsStatus = RdsStatuses<1,I> RdsHold = CassArray RdsHotLot = CassArray IF RdsHold OR RdsHotLot THEN IF RdsHold THEN LineColor = YELLOW$ IF RdsHotLot THEN LineColor = RED$ END ELSE BEGIN CASE CASE RdsStatus = 'Out of Spec' ; LineColor = RED$ CASE RdsStatus = 'QA Complete' ; LineColor = LTGREY$ CASE RdsStatus = 'Ready to Start' ; LineColor = RCV_BLUE$ CASE RdsStatus = 'Ready to Pre Clean' ; LineColor = PRE_BLUE$ CASE RdsStatus = 'Ready to Pre Surface Inspect' ; LineColor = PRE_BLUE$ CASE RdsStatus = 'Ready to Pre Surf Scan' ; LineColor = PRE_BLUE$ CASE RdsStatus = 'Ready to Load' ; LineColor = INP_BLUE$ CASE RdsStatus = 'Loaded' ; LineColor = GREEN$ CASE RdsStatus = 'Unloaded' ; LineColor = POS_BLUE$ CASE RdsStatus = 'Ready to Wafer Clean' ; LineColor = POS_BLUE$ CASE RdsStatus = 'Ready to Wafer Inspect' ; LineColor = GREEN$ CASE RdsStatus = 'Ready to Wafer Surf Scan' ; LineColor = GREEN$ CASE RdsStatus = 'Ready to Post Clean' ; LineColor = POS_BLUE$ CASE RdsStatus = 'Ready to Post Inspect' ; LineColor = POS_BLUE$ CASE RdsStatus = 'Ready to Post Surf Scan' ; LineColor = POS_BLUE$ CASE RdsStatus = 'EpiPRO Test Loaded' ; LineColor = ORANGE$ CASE RdsStatus = 'EpiPRO Test Unloaded' ; LineColor = LTORANGE$ CASE RdsStatus = 'Ready for QA' ; LineColor = YELLOW$ CASE RdsStatus = 'Cancelled' ; LineColor = LTGREY$ CASE RdsStatus = 'Voided' ; LineColor = LTGREY$ CASE RdsStatus = 'Unknown' ; LineColor = RED$ CASE 1 ; LineColor = WHITE$ END CASE END stat = Send_Message(CtrlName,'COLOR_BY_POS',0,I,LineColor) NEXT I * 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:'.CASSETTES' 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 * * * * * * * LUWONo: * * * * * * * Set_Status(0) WOKeys = obj_WO_Log('Find') IF Get_Status(errCode) THEN ErrMsg(ErrCode) IF WOKeys NE '' THEN TypeOver = '' TypeOver = WOKeys TypeOver = 'K' TypeOver = 1 WOKey = Popup(@WINDOW,TypeOver,'WO_LOG_QUERY') IF Get_Status(errCode) THEN ErrMsg(errCode) END IF WOKey NE '' THEN obj_Appwindow('LUValReturn',WOKey:@RM:@WINDOW:'.WO_NO':@RM:'') ;* Loads form key or QBFList as required END RETURN * * * * * * * StepGF: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','TEXT') WOStep = Get_Property(@WINDOW:'.PROC_STEP_NO','TEXT') IF WONo NE '' AND WOStep = '' THEN WOStepKeys = XLATE('WO_LOG',WONo,WO_LOG_WO_STEP_KEY$,'X') IF INDEX(WOStepKeys,@VM,1) THEN LastStep = WOStepKeys[-1,'B':@VM] WOStep = FIELD(LastStep,'*',2) END ELSE WOStep = FIELD(WOStepKeys,'*',2) END CurrControl = @WINDOW:'.PROC_STEP_NO' CurrPos = '' obj_Appwindow('LUValReturn',WOStep:@RM:CurrControl:@RM:CurrPos) END RETURN * * * * * * * ViewProdSpec: * * * * * * * PSNo = Get_Property(@WINDOW:'.PS_NO','TEXT') IF PSNo = '' THEN RETURN obj_AppWindow('ViewRelated','PROD_SPEC':@RM:PSNo) Send_Event(@WINDOW:'.PS_NO','LOSTFOCUS') ;* Kicks the symbolics RETURN * * * * * * * OpenWOS: * * * * * * * IF Get_Property(@WINDOW:'.WO_NO','TEXT') NE '' THEN Send_Event(@WINDOW,'CLEAR') END OpenWONo = obj_WO_Log('OpenWONos','') IF OpenWONo NE '' THEN obj_AppWindow('LoadFormKeys',@WINDOW:@RM:OpenWONo) END RETURN * * * * * * * CassPC: * * * * * * * CtrlEntID = @WINDOW:'.CASSETTES' SlotSelection = Get_Property(CtrlEntID,'SELPOS') SelectedRows = SlotSelection<2> CONVERT @VM TO @FM in SelectedRows SelCnt = COUNT(SelectedRows,@FM) + (SelectedRows NE '') *IF SelCnt = 0 THEN RETURN SelPos = Get_Property(CtrlEntID,'SELPOS') SelCol = SelPos<1> SelRow = SelPos<2> CurrPos = Get_Property(CtrlEntID,'NOTIFYPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> RETURN * * * * * * * CassDC: * * * * * * * CtrlEntID = @WINDOW:'.CASSETTES' CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> NotifyPos = Get_Property(CtrlEntID,'NOTIFYPOS') NotifyCol = NotifyPos<1> NotifyRow = NotifyPos<2> IF NotifyCol >= COL$RDS_NO THEN RDSNo = Get_Property(CtrlEntID,'CELLPOS',COL$RDS_NO:@FM:NotifyRow) WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') StepNo = Get_Property(@WINDOW:'.PROC_STEP_NO','DEFPROP') WOStepKey = WONo:'*':StepNo 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 If Get_Property('NDW_MAIN', 'VISIBLE') then AppMain = 'NDW_MAIN' end else AppMain = 'LSL_MAIN2' end 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 END IF NotifyCol = COL$CASS_NO THEN WONo = Get_Property(@WINDOW:'.WO_NO','TEXT') CassNo = Get_Property(CtrlEntID,'CELLPOS',COL$CASS_NO:@FM:NotifyRow) IF WONo NE '' AND CassNo NE '' THEN obj_AppWindow('ViewRelated','WO_MAT':@RM:WONo:'*':CassNo) IF Get_Status(errCode) THEN ErrMsg(errCode) END END END RETURN * * * * * * * BrowseRDS: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','TEXT') StepNo = Get_Property(@WINDOW:'.PROC_STEP_NO','TEXT') IF WONo NE '' AND StepNo NE '' THEN WOStepKey = WONo:'*':StepNo END ELSE RETURN END CtrlEntID = @WINDOW:'.CASSETTES' CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> RDSNos = Get_Property(CtrlEntID,'ARRAY')<2> ;* Multivalue list of RDS Nos LOOP TestChar = RDSNos[-1,1] UNTIL TestChar NE @VM OR RDSNos = '' RDSNos[-1,1] = '' REPEAT IF RDSNos = '' THEN RETURN WONo = Get_Property(@Window:'.WO_NO', 'TEXT') RDSKeys = Dialog_Box('NDW_RDS_QUERY', @Window, WONo) IF RDSKeys = '' THEN RETURN 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 If Get_Property('NDW_MAIN', 'VISIBLE') then AppMain = 'NDW_MAIN' end else AppMain = 'LSL_MAIN2' end Start_Window(thisFormName,AppMain,RDSKeys:'*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 RETURN * * * * * * * RemCassettes: * * * * * * * * This routine is not used RETURN WONo = Get_Property(@WINDOW:'.WO_NO','TEXT') IF WONo = '' THEN RETURN *Send_Event(@WINDOW,'WRITE') WORec = XLATE('WO_LOG',WONo,'','X') WOMatKeys = WORec WMInKeys = XLATE('WO_MAT',WOMatKeys,WO_MAT_WMI_KEY$,'X') WOMatRDSNos = XLATE('WO_MAT',WOMatKeys,WO_MAT_RDS_NO$,'X') RDSVerSigs = XLATE('REACT_RUN',WOMatRDSNos,REACT_RUN_VER_SIG$,'X') RDSTestString = RdsVerSigs CONVERT @VM TO '' IN RDSTestString RDSLoadSigs = XLATE('WO_MAT',WOMatKeys,REACT_RUN_LOAD_SIG$,'X') WMInKeys = XLATE('WO_MAT',WOMatKeys,WO_MAT_WMI_KEY$,'X') WMInCnt = COUNT(WMInKeys,@VM) + (WMinKeys NE '') RDSNos = '' CassNos = '' WMIData = '' RDSData = '' Display = '' DispLine = 1 IF WMInCnt > 0 THEN FOR I = WMInCnt TO 1 STEP -1 WMIRec = XLATE('WM_IN',WMInKeys<1,I>,'','X') WMIRdsNos = WMIRec WMINCRNos = WMIRec CONVERT @VM TO '' IN WMIRdsNos CONVERT @VM TO '' IN WMINCRNos UNTIL WMIRdsNos NE '' OR WMINCRNos NE '' Display<1,DispLine,1> = FIELD(WOMatKeys<1,I>,'*',2) Display<1,DispLine,2> = XLATE('WO_MAT',WOMatKeys<1,I>,WO_MAT_LOT_NO$,'X') Display<1,DispLine,3> = XLATE('WO_MAT',WOMatKeys<1,I>,WO_MAT_WAFER_QTY$,'X') Display<1,DispLine,4> = WMInKeys<1,I> DispLine += 1 NEXT I IF Display NE '' THEN TypeOver = '' TypeOver = Display WMIData = Popup(@WINDOW,TypeOver,'UNUSED_WM_IN') IF WMIData = '' OR WMIData = CHAR(27) THEN RETURN ;* Cancelled out END ELSE ErrMsg('All cassettes on this Work Order have started processing.') obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WONo) RETURN END DelWMInKeys = '' FOR I = 1 TO COUNT(WMIData,@FM) + (WMIData NE '') CassNos<1,I> = WMIData DelWMInKeys<1,I> = WMIData NEXT I TestWMInKeys = DelWMInKeys CONVERT @VM TO '' IN TestWMInKeys IF TestWMInKeys NE '' THEN Set_Status(0) obj_WM_In('Delete',DelWMInKeys) IF Get_Status(errCode) THEN ErrMsg(errCode) END END Set_Status(0) obj_WO_Log('RemoveCassettes',WONo:@RM:CassNos) IF Get_Status(errCode) THEN ErrMsg(errCode) END END ELSE CassCnt = COUNT(WOMatKeys,@VM) + (WOMatKeys NE '') FOR I = CassCnt TO 1 STEP -1 UNTIL WOMatRDSNos<1,I> NE '' Display<1,DispLine,1> = WOMatKeys<1,I>[-1,'B*'] Display<1,DispLine,2> = XLATE('WO_MAT',WOMatKeys<1,I>,WO_MAT_LOT_NO$,'X') Display<1,DispLine,3> = XLATE('WO_MAT',WOMatKeys<1,I>,WO_MAT_WAFER_QTY$,'X') Display<1,DispLine,4> = WOMatRDSNos<1,I> DispLine += 1 NEXT I IF Display NE '' THEN TypeOver = '' TypeOver = Display RDSData = Popup(@WINDOW,TypeOver,'UNUSED_RDS') END ELSE ErrMsg('All cassettes on this Work Order have started processing.') obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WONo) RETURN END FOR I = 1 TO COUNT(RDSData,@FM) + (RDSData NE '') CassNos<1,I> = RDSData RDSNos<1,I> = RDSData NEXT I TestRDSNos = RDSNos CONVERT @VM TO '' IN TestRDSNos IF TestRDSNos NE '' THEN Set_Status(0) InProcessRDSNos = obj_RDS('Delete',RDSNos) ;* Removes RDS records from system dummy = obj_React_Run('Delete',RDSNos) ;* Hook to new table change when RDS cutover is accomplished IF Get_Status(errCode) THEN ErrMsg(errCode) END END Set_Status(0) obj_WO_Log('RemoveCassettes',WONo:@RM:CassNos) IF Get_Status(errCode) THEN ErrMsg(errCode) END END IF Display = '' THEN ErrMsg('All cassettes on this Work Order have started processing.') RETURN END Recipients = XLATE('NOTIFICATION','WO_ENTRY',NOTIFICATION_USER_ID$,'X') SentFrom = @USER4 Subject = 'Unprocessed Cassettes removed from WO ':WONo Message = 'Cassettes removed from WO.' NewForm = Xlate('APP_INFO', 'NEW_WO_FORM', '', 'X') If NewForm then AttachWindow = 'NDW_WO_LOG' end else AttachWindow = 'WO_LOG2' end AttachKey = WONo SendToGroup = '' Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup obj_Notes('Create',Parms) IF Get_Status(errCode) THEN ErrMsg(errCode) END *obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WONo) Send_Event(@WINDOW,'READ') RETURN * * * * * * * ControlPlanClick: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP') IF PSNo NE '' AND WONo NE '' THEN Print_Control_Plan(PSNo,WONo) END RETURN