COMPILE FUNCTION Comm_RDS2(Instruction, Parm1,Parm2) #pragma precomp SRP_PreCompiler /* Commuter module for RDS2 (Run Data Sheet) window 05/12/2005 - John C. Henry, J.C. Henry & Co., Inc. */ DECLARE SUBROUTINE Set_Property, Set_Status, ErrMsg, Set_Property, obj_AppWindow, obj_Notes, obj_RDS_Test, Labeling_Services DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, Forward_Event, End_Window, Start_Window, Database_Services DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box, RowExists DECLARE FUNCTION obj_Schedule, Dialog_Box, obj_WO_Log, obj_RDS2, obj_RDS_Audit, Create_Dialog, Database_Services $INSERT POPUP_EQUATES $INSERT LOGICAL $INSERT MSG_EQUATES $INSERT APPCOLORS $INSERT RDS_EQU $INSERT RDS_LAYER_EQUATES $INSERT RDS_TEST_EQUATES $INSERT WO_STEP_EQU $INSERT ORDER_EQU $INSERT LSL_USERS_EQU $INSERT SECURITY_RIGHTS_EQU $INSERT RDS_EPILOAD ;* Equates for data coming back from the EpiPRO Load/Unload dialog boxes 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$POCKET TO 1 EQU COL$USE TO 2 EQU COL$ZONE TO 3 EQU COL$IN_CASS TO 4 EQU COL$IN_SLOT TO 5 EQU COL$CHAR TO 6 EQU COL$OUT_CASS TO 7 EQU COL$OUT_SLOT TO 8 EQU COL$NCR TO 9 ;* Dead? EQU CRLF$ TO \0D0A\ ErrTitle = 'Error in Comm_RDS2' 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 = 'LURdsNo' ; GOSUB LURdsNo CASE Instruction = 'ViewProdSpec' ; GOSUB ViewProdSpec CASE Instruction = 'CopyMetrology' ; GOSUB CopyMetrology CASE Instruction = 'CopyRecipeParameters' ; GOSUB CopyRecipeParameters CASE Instruction = 'ViewAudit' ; GOSUB ViewAudit CASE Instruction = 'LSIdDC' ; GOSUB LSIdDC CASE Instruction = 'LoadEpiPro' ; GOSUB LoadEpiPro CASE Instruction = 'UnloadEpiPro' ; GOSUB UnloadEpiPro CASE Instruction = 'AddZoneMet' ; GOSUB AddZoneMet CASE Instruction = 'MoveMetToZone' ; GOSUB MoveMetToZone CASE Instruction = 'ViewWOMat' ; GOSUB ViewWOMat CASE Instruction = 'WMInKeyDC' ; GOSUB WMInKeyDC CASE Instruction = 'WMOutKeyDC' ; GOSUB WMOutKeyDC CASE Instruction = 'ReprintHold' ; GOSUB ReprintHold CASE 1 ErrorMsg = 'Unknown Instruction passed to routine' END CASE RETURN Result * * * * * * * Create: * * * * * * * IF NOT(Security_Check('RDS',READ$)) THEN Security_Err_Msg('RDS',READ$) End_Window(@WINDOW) RETURN END obj_Appwindow('Create',@WINDOW) GOSUB Refresh RETURN * * * * * * * Read: * * * * * * * RDSNo = Get_Property(@WINDOW:'.RDS_NO_FIX','TEXT') IF RowExists('RDS',RDSNo) THEN IF NOT(Security_Check('RDS',READ$)) THEN Send_Event(@WINDOW,'CLEAR') Security_Err_Msg('RDS',READ$) RETURN END END ELSE ErrMsg('RDS entries may only be created from the Work Order window.') Send_Event(@WINDOW,'CLEAR') RETURN END GOSUB Refresh RETURN * * * * * * * Write: * * * * * * * RETURN * * * * * * * Clear: * * * * * * * *Send_Event(@WINDOW,'PAGE',1) GOTO Refresh RETURN * * * * * * * Delete: * * * * * * * IF NOT(Security_Check('RDS',DELETE$)) THEN Security_Err_Msg('RDS',DELETE$) RETURN END Result = 0 ;* OK to proceed with the delete RETURN * * * * * * * Page: * * * * * * * obj_Appwindow('Page') GOSUB Refresh RETURN * * * * * * * Close: * * * * * * * RETURN * * * * * * * Refresh: * * * * * * * * 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 * * * * * * * ReprintHold: * * * * * * * RDSKey = Get_Property(@WINDOW:'.RDS_NO','DEFPROP') Labeling_Services('ReprintHoldLabel', 'RDS', RDSKey) RETURN * * * * * * * LURdsNo: * * * * * * * Set_Status(0) RDSKeys = obj_RDS2('Find') ErrCode = '' IF Get_Status(errCode) THEN ErrMsg(ErrCode) CONVERT @FM TO @VM IN RDSKeys IF RDSKeys NE '' THEN WONo = Get_Property(@Window:'.WO', 'TEXT') RDSKeys = Dialog_Box('NDW_RDS_QUERY', @Window, WONo) IF RDSKeys NE '' THEN obj_Appwindow('ViewRelated',@WINDOW:@RM:RDSKeys) ;* Loads form key or QBFList as required END RETURN * * * * * * * ViewQuote: * * * * * * * QuoteNo = Get_Property(@WINDOW:'.QUOTE_NO_FIX','TEXT') IF QuoteNo = '' THEN RETURN obj_AppWindow('ViewRelated','QUOTE':@RM:QuoteNo) RETURN * * * * * * * ViewProdSpec: * * * * * * * PSNo = Get_Property(@WINDOW:'.PS_NO_FIX','TEXT') IF PSNo = '' THEN RETURN obj_AppWindow('ViewRelated','PROD_SPEC':@RM:PSNo) Send_Event(@WINDOW:'.PS_NO_FIX','LOSTFOCUS') ;* Kicks the symbolics RETURN * * * * * * * CopyMetrology: * * * * * * * RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP') WONo = Get_Property(@Window:'.WO', 'TEXT') DestRDSNos = Dialog_Box('NDW_RDS_QUERY', @Window, WONo) SourceMetKeys = obj_RDS2('GetMetKeys',RDSNo) RDSCnt = COUNT(DestRDSNos,@VM) + (DestRDSNos NE '') FOR I = 1 TO RDSCnt Copy = 1 ;* Set flag DestRDSNo = DestRDSNos<1,I> DestQASig = XLATE('RDS',DestRDSNo,RDS_SUP_VER_SIG$,'X') IF DestQASig NE '' THEN ErrMsg("Destination RDS ":DestRDSNo:" has been final QA'd. Metrology NOT copied.") END ELSE 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_RDS2('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 Send_Event(@WINDOW:'.RDS_LS_ID','LOSTFOCUS') END ELSE ErrMsg('SourceMetKeys not equal DestMetKeys: Contact FI') END END ;* End of check for Copy flag END ;* End of check for Existing Final QA signature NEXT I RETURN CopyRecipeParameters: RDSRow = Get_Property(@Window, 'ATRECORD') RDSNo = Get_Property(@WINDOW:'.RDS_NO', 'DEFPROP') WONo = Get_Property(@Window:'.WO', 'TEXT') DestRDSNos = Dialog_Box('NDW_RDS_QUERY', @Window, WONo : @FM : 'quick') If DestRDSNos NE '' then RDSLayerKeyIDs = RDSRow If RDSLayerKeyIDs NE '' then For Each RDSLayerKeyID in RDSLayerKeyIDs using @VM RDSLayerRow = Database_Services('ReadDataRow', 'RDS_LAYER', RDSLayerKeyID) Layer = RDSLayerKeyID[-1, 'B*'] For Each DestRDSNo in DestRDSNos using @VM DestRDSLayerKeyID = DestRDSNo : '*' : Layer DestRDSLayerRow = Database_Services('ReadDataRow', 'RDS_LAYER', DestRDSLayerKeyID) DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow DestRDSLayerRow = RDSLayerRow Database_Services('WriteDataRow', 'RDS_LAYER', DestRDSLayerKeyID, DestRDSLayerRow, True$, False$, True$) Send_Event(@Window : '.RDS_LS_ID' , 'LOSTFOCUS') Next DestRDSNo Next RDSLayerKeyID end end return * * * * * * * ViewAudit: * * * * * * * RDSNo = Get_Property(@WINDOW:'.RDS_NO_FIX','DEFPROP') IF RDSNo = '' THEN RETURN AuditData = obj_RDS_Audit('Display',RDSNo:@RM:@WINDOW) ;* Returns all audit columns for this window DispText = AuditData[1,@RM] UserNames = AuditData[COL2()+1,@RM] LastDTMS = AuditData[COL2()+1,@RM] Windows = AuditData[COL2()+1,@RM] PopupDisplay = '' FOR I = 1 TO COUNT(DispText,@FM) + (DispText NE '') PopupDisplay<1,I> = DispText:@TM:OCONV(UserNames,'[XLATE_CONV,LSL_USERS*FIRST_LAST]' ):@TM:LastDTMs:@TM:Windows NEXT I OverRide = '' OverRide = PopupDisplay void = PopUp(@WINDOW, OverRide, 'RDS_MOD_HIST_VIEW' ) RETURN * * * * * * * LSIdDC: * * * * * * * CtrlEntID = @WINDOW:'.RDS_LS_ID_FIX' RDSNo = Get_Property(@WINDOW:'.RDS_NO_FIX','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('RDS','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('RDS','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 * * * * * * * LoadEpiPro: * * * * * * * RDSNo = Get_Property(@WINDOW:'.RDS_NO_FIX','DEFPROP') CurrentLoad = Get_Property(@WINDOW:'.POCKET','DEFPROP') IF RDSNo = '' THEN RETURN OutCassettes = CurrentLoad CONVERT @VM TO '' IN OutCassettes IF OutCassettes NE '' THEN ErrMsg('Wafers have already been unloaded from the reactor.') RETURN END Reactor = Get_Property(@WINDOW:'.REACTOR','TEXT') ReactorType = XLATE('REACTOR',Reactor,1,'X') IF ReactorType NE 'EPP' THEN ErrMsg('Reactor ':Reactor:' is not an EpiPro tool.') RETURN END Send_Event(@WINDOW,'WRITE') MatlLoadInfo = Create_Dialog('DIALOG_LOAD_EPI_PRO', @WINDOW, 0, RDSNo:@FM:CurrentLoad) RETURN * * * * * * * UnloadEpiPro: * * * * * * * RDSNo = Get_Property(@WINDOW:'.RDS_NO_FIX','DEFPROP') CurrentLoad = Get_Property(@WINDOW:'.POCKET','DEFPROP') IF RDSNo = '' THEN RETURN Reactor = Get_Property(@WINDOW:'.REACTOR','TEXT') ReactorType = XLATE('REACTOR',Reactor,1,'X') IF ReactorType NE 'EPP' THEN ErrMsg('Reactor ':Reactor:' is not an EpiPro tool.') RETURN END Send_Event(@WINDOW,'WRITE') MatlUnloadInfo = Create_Dialog('DIALOG_UNLOAD_EPI_PRO', @WINDOW, 0, RDSNo:@FM:CurrentLoad) 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: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO_FIX','DEFPROP') CassNo = Get_Property(@WINDOW:'.CASS_NO_FIX','DEFPROP') IF WONo NE '' AND CassNo NE '' THEN obj_AppWindow('ViewRelated','WO_MAT':@RM:WONo:'*':CassNo) END RETURN * * * * * * * WMInKeyDC: * * * * * * * CtrlEntID = @WINDOW:'.WM_IN_KEY_FIX' CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> WMInKey = Get_Property(CtrlEntID,'CELLPOS',1:@FM:CurrRow) IF WMInKey NE '' THEN obj_Appwindow('ViewRelated', 'WM_IN':@RM:WMInKey) END RETURN * * * * * * * WMOutKeyDC: * * * * * * * CtrlEntID = @WINDOW:'.WM_OUT_KEY_FIX' CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> WMOutKey = Get_Property(CtrlEntID,'CELLPOS',1:@FM:CurrRow) IF WMOutKey NE '' THEN obj_Appwindow('ViewRelated', 'WM_OUT':@RM:WMOutKey) END RETURN