replaced with NDW_VERIFY_USER. Added barcode scan function to NDW_VERIFY_USER. fixed two instances of ohms square unit characters being garbled by git minor modification to NDW_VERIFY_USER_EVENTS lost focus events minor change to gotfocus event logic
1136 lines
44 KiB
Plaintext
1136 lines
44 KiB
Plaintext
COMPILE FUNCTION Comm_QA_Met_Result(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5)
|
|
#pragma precomp SRP_PreCompiler
|
|
|
|
/*
|
|
Commuter module for QA_MET_RESULT collector window
|
|
|
|
01/24/2012 - John C. Henry, J.C. Henry & Co., Inc.
|
|
*/
|
|
|
|
DECLARE SUBROUTINE Set_Property, End_Dialog, Send_Event, Set_Status, obj_WO_Mat, Btree.Extract, Signature_Services
|
|
DECLARE SUBROUTINE ErrMsg, Set_Property, obj_AppWindow, Send_Event, obj_WO_Mat_QA, obj_Tables
|
|
DECLARE SUBROUTINE Start_Window, End_Window, Post_Metrology_Manual_Data_Entry_Log, Database_Services
|
|
|
|
DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, obj_WM_Out, Datetime, Database_Services, Error_Services
|
|
DECLARE FUNCTION Msg, obj_WO_Mat, Send_Message, obj_Tables, Signature_Services, set_WinMsgVal, Start_Window, End_Window
|
|
Declare Function Wo_Mat_Qa_Services, SRP_Array, Math_Services
|
|
|
|
$INSERT APPCOLORS
|
|
$INSERT LSL_USERS_EQU
|
|
$INSERT WO_MAT_EQUATES
|
|
$INSERT WM_OUT_EQUATES
|
|
$INSERT WO_MAT_QA_EQUATES
|
|
$INSERT POPUP_EQUATES
|
|
$INSERT LOGICAL
|
|
$INSERT MSG_EQUATES
|
|
|
|
EQU WM_USER$ to 1024
|
|
EQU ETM_INSERTROW$ to (WM_USER$ + 2004)
|
|
EQU ETM_DELETEROW$ to (WM_USER$ + 2005)
|
|
|
|
EQU CRLF$ TO \0D0A\
|
|
EQU TAB$ TO \09\
|
|
|
|
EQU MULTILINE_STYLE$ TO 512 ;* MultiLine Select
|
|
EQU DTM_SELROW$ TO (1024+59) ;* Used to clear Single Line SELPOS property
|
|
|
|
EQU COL$MET_TEST TO 1 ;* @VM data structure passed in and returned
|
|
EQU COL$MET_TEST_DESC TO 2
|
|
EQU COL$MET_SPEC_SLOT TO 3
|
|
EQU COL$MET_SPEC_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$SLOT TO 1
|
|
EQU COL$SLOT_ID TO 2
|
|
EQU COL$WAFER_ID TO 3
|
|
EQU COL$SLOT_NCR TO 4
|
|
EQU COL$MET_NO$ TO 5
|
|
EQU COL$MOVED_TO_SLOT TO 6
|
|
EQU COL$MU_WAFER_ID TO 7
|
|
EQU COL$MU_CASS_ADE TO 8
|
|
EQU COL$MU_WAFER_THK_RESULT TO 9
|
|
|
|
EQU COL$EPI_SLOT TO 1
|
|
EQU COL$EPI_SLOT_ID TO 2
|
|
EQU COL$EPI_WAFER_ID TO 3
|
|
EQU COL$RUN_ID TO 4
|
|
EQU COL$EPI_SLOT_NCR TO 5
|
|
EQU COL$EPI_MOVED_TO TO 6
|
|
EQU COL$EPI_MU_WFR_ID TO 7
|
|
EQU COL$EPI_MU_CASS_ADE TO 8
|
|
EQU COL$EPI_MU_WAFER_THK_RESULT TO 9
|
|
|
|
ErrTitle = 'Error in Comm_QA_Met_Result'
|
|
ErrorMsg = ''
|
|
|
|
Result = ''
|
|
|
|
BEGIN CASE
|
|
CASE EntID = @WINDOW
|
|
BEGIN CASE
|
|
CASE Event = 'CREATE' ; GOSUB Create
|
|
CASE Event = 'CLOSE' ; GOSUB Exit
|
|
END CASE
|
|
|
|
CASE EntID = @WINDOW:'.MET_RESULT' AND Event = 'LOSTFOCUS' ; GOSUB ResultLF
|
|
CASE EntID = @WINDOW:'.MET_STD_RESULT' AND Event = 'LOSTFOCUS' ; GOSUB ResultLF
|
|
Case EntID = @WINDOW:'.TW_USE_BUTTON' AND Event = 'CLICK' ; Gosub TWUse
|
|
CASE EntID = @WINDOW:'.SIGN' AND Event = 'CLICK' ; GOSUB Sign
|
|
CASE EntID = @WINDOW:'.EXIT' AND Event = 'CLICK' ; GOSUB Exit
|
|
CASE EntID = @WINDOW:'.SLOT_FILL' AND Event = 'CLICK' ; GOSUB SlotClick
|
|
CASE EntID = @WINDOW:'.EPI_SLOT_FILL' AND Event = 'CLICK' ; GOSUB EpiSlotClick
|
|
CASE EntID = @WINDOW:'.SLOT_FILL' AND Event = 'POSCHANGED' ; GOSUB Refresh
|
|
CASE EntID = @WINDOW:'.EPI_SLOT_FILL' AND Event = 'POSCHANGED' ; GOSUB Refresh
|
|
CASE EntID = @WINDOW:'.SLOT_FILL' AND Event = 'LOSTFOCUS' ; GOSUB Refresh
|
|
CASE EntID = @WINDOW:'.EPI_SLOT_FILL' AND Event = 'LOSTFOCUS' ; GOSUB Refresh
|
|
CASE EntID = @WINDOW:'.SLOT_FILL' AND Event = 'WINMSG' ; GOSUB TrapKeys
|
|
CASE EntID = @WINDOW:'.EPI_SLOT_FILL' AND Event = 'WINMSG' ; GOSUB TrapKeys
|
|
CASE EntID = @WINDOW:'.SLOT_FILL' AND Event = 'DELETEROW' ; GOSUB DeleteRow
|
|
CASE EntID = @WINDOW:'.EPI_SLOT_FILL' AND Event = 'DELETEROW' ; GOSUB DeleteRow
|
|
CASE EntID = @WINDOW:'.SLOT_FILL' AND Event = 'INSERTROW' ; GOSUB InsertRow
|
|
CASE EntID = @WINDOW:'.EPI_SLOT_FILL' AND Event = 'INSERTROW' ; GOSUB InsertRow
|
|
CASE EntID = @WINDOW:'.PUB_SAVE' AND Event = 'CLICK' ; GOSUB PubSaveClick
|
|
|
|
CASE 1
|
|
|
|
ErrorMsg = 'Unknown Parameters ':EntID:' - ':Event:' passed to commuter'
|
|
|
|
END CASE
|
|
|
|
IF ErrorMsg NE '' THEN
|
|
ErrMsg(ErrTitle:@SVM:ErrorMsg)
|
|
END
|
|
|
|
RETURN Result
|
|
|
|
|
|
* * * * * * *
|
|
Create:
|
|
* * * * * * *
|
|
|
|
obj_Appwindow('Create',@WINDOW)
|
|
|
|
*******************************************************
|
|
* Trap INS/DEL key to prevent edit table row deletion *
|
|
*******************************************************
|
|
eventOp = TRUE$ ; * // Turn tracking on
|
|
eventOp<4> = TRUE$ ; * // Track Synchronously
|
|
call send_Message( @WINDOW:".SLOT_FILL", "QUALIFY_EVENT", ETM_INSERTROW$, eventOp )
|
|
call send_Message( @WINDOW:".SLOT_FILL", "QUALIFY_EVENT", ETM_DELETEROW$, eventOp )
|
|
call send_Message( @WINDOW:".EPI_SLOT_FILL", "QUALIFY_EVENT", ETM_INSERTROW$, eventOp )
|
|
call send_Message( @WINDOW:".EPI_SLOT_FILL", "QUALIFY_EVENT", ETM_DELETEROW$, eventOp )
|
|
|
|
*******************
|
|
* Read Parameters *
|
|
*******************
|
|
CassID = Parm1[1,@FM]
|
|
MetLineIn = Parm1[COL2()+1,@FM]
|
|
|
|
Set_Property(@WINDOW,'@MET_LINE_IN',MetLineIn)
|
|
|
|
WONo = FIELD(CassID,'*',1)
|
|
WOStepNo = FIELD(CassID,'*',2)
|
|
CassNo = FIELD(CassID,'*',3)
|
|
|
|
CONVERT '*' TO @RM IN CassID
|
|
|
|
Ctrls = @WINDOW:'.WO_NO':@RM
|
|
Ctrls := @WINDOW:'.PROC_STEP_NO':@RM
|
|
Ctrls := @WINDOW:'.OUT_CASS_NO':@RM
|
|
Ctrls := @WINDOW:'.RDS_NO':@RM
|
|
Ctrls := @WINDOW:'.RUN_STEP'
|
|
|
|
Props = 'DEFPROP':@RM:'DEFPROP':@RM:'DEFPROP':@RM:'DEFPROP':@RM:'DEFPROP'
|
|
Vals = CassID
|
|
|
|
Set_Property(Ctrls,Props,Vals)
|
|
|
|
MetTest = MetLineIn<1,COL$MET_TEST>
|
|
MetTestDesc = MetLineIn<1,COL$MET_TEST_DESC>
|
|
MetSpecSlot = MetLineIn<1,COL$MET_SPEC_SLOT>
|
|
MetSpecSlotDesc = MetLineIn<1,COL$MET_SPEC_SLOT_DESC>
|
|
MetMin = MetLineIn<1,COL$MET_MIN>
|
|
MetMax = MetLineIn<1,COL$MET_MAX>
|
|
MetResult = MetLineIn<1,COL$MET_RESULT>
|
|
MetStdMax = MetLineIn<1,COL$MET_STD_MAX>
|
|
MetStdResult = MetLineIn<1,COL$MET_STD_RESULT>
|
|
MetWfrQty = MetLineIn<1,COL$MET_WFR_QTY>
|
|
|
|
IF MetStdMax = '' THEN
|
|
IF MetTest = 'ADE' THEN
|
|
IF MetSpecSlot = 'A' OR MetWfrQty = 'A' OR MetWfrQty > 5 THEN
|
|
* Standard Deviation Required
|
|
MetStdMax = ((MetMin + MetMax) / 2) * (0.02)
|
|
MetStdMax = ICONV(MetStdMax,'MD3')
|
|
Set_Property(@WINDOW:'.MET_STD_MAX','DEFPROP',OCONV(MetStdMax,'MD3'))
|
|
END
|
|
END ;* End of check for ADE test
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.MET_STD_MAX','DEFPROP',MetStdMax)
|
|
END
|
|
|
|
Title = Get_Property(@WINDOW,'TEXT'):' - ':MetTest:' ':MetTestDesc
|
|
|
|
Set_Property(@WINDOW,'@MET_TEST',MetTest) ;* Added 8/6/2013 JCH
|
|
Set_Property(@WINDOW,'TEXT',Title)
|
|
Set_Property(@WINDOW:'.MET_TEST','DEFPROP',MetTest)
|
|
Set_Property(@WINDOW:'.MET_SPEC_SLOT','DEFPROP',MetSpecSlot)
|
|
Set_Property(@WINDOW:'.MET_SPEC_SLOT_DESC','DEFPROP',MetSpecSlotDesc)
|
|
Set_Property(@WINDOW:'.MET_SPEC_WFR_QTY','DEFPROP',MetWfrQty)
|
|
Set_Property(@WINDOW:'.MET_MIN','DEFPROP',MetMin)
|
|
Set_Property(@WINDOW:'.MET_MAX','DEFPROP',MetMax)
|
|
Set_Property(@WINDOW:'.MET_RESULT','DEFPROP',MetResult)
|
|
Set_Property(@WINDOW:'.MET_STD_RESULT','DEFPROP',MetStdResult)
|
|
|
|
Set_Property(@WINDOW:'.MET_STD_RESULT', 'ENABLED', False$)
|
|
IF MetStdMax = '' THEN
|
|
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',GREY$)
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',GREEN$)
|
|
END
|
|
|
|
IF ((MetResult < MetMin) OR (MetResult > MetMax)) then
|
|
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',RED$)
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',GREEN$)
|
|
END
|
|
|
|
Set_Property(@WINDOW:'.SIGN','ENABLED',1)
|
|
|
|
WOMatRec = XLATE('WO_MAT',WONo:'*':CassNo,'','X')
|
|
|
|
SlotArray = ''
|
|
|
|
IF WOMatRec<WO_MAT_WMO_KEY$> NE '' THEN
|
|
|
|
WMORec = XLATE('WM_OUT',WOMatRec<WO_MAT_WMO_KEY$>,'','X')
|
|
|
|
SlotCnt = COUNT(WMORec<WM_OUT_SLOT_NO$>,@VM) + (WMORec<WM_OUT_SLOT_NO$> NE '')
|
|
|
|
FOR N = 1 TO SlotCnt
|
|
SlotArray<COL$EPI_SLOT,N> = WMORec<WM_OUT_SLOT_NO$,N>
|
|
SlotArray<COL$EPI_SLOT_ID,N> = WONo:'.':CassNo:'.':WMORec<WM_OUT_SLOT_NO$,N>
|
|
SlotArray<COL$EPI_WAFER_ID,N> = WONo:'.':WMORec<WM_OUT_IN_CASS_NO$,N>:'.':WMORec<WM_OUT_IN_SLOT_NO$,N>
|
|
SlotArray<COL$RUN_ID,N> = WMORec<WM_OUT_RDS$,N>:'.':WMORec<WM_OUT_POCKET$,N>:'.':WMORec<WM_OUT_ZONE$,N>
|
|
SlotArray<COL$EPI_SLOT_NCR,N> = WMORec<WM_OUT_SLOT_NCR$,N>
|
|
|
|
IF WMORec<WM_OUT_UMW_CASS_ID$,N> = '' THEN
|
|
SlotArray<COL$EPI_MOVED_TO,N> = ''
|
|
END ELSE
|
|
SlotArray<COL$EPI_MOVED_TO,N> = WMORec<WM_OUT_UMW_CASS_ID$,N>:'.':WMORec<WM_OUT_UMW_SLOT_NO$,N>
|
|
END
|
|
|
|
IF WMORec<WM_OUT_MU_WO_NO$,N> = '' THEN
|
|
SlotArray<COL$EPI_MU_WFR_ID,N> = ''
|
|
END ELSE
|
|
SlotArray<COL$EPI_MU_WFR_ID,N> = WMORec<WM_OUT_MU_WO_NO$,N>:'.':WMORec<WM_OUT_MU_CASS_NO$,N>:'.':WMORec<WM_OUT_MU_SLOT_NO$,N>
|
|
END
|
|
|
|
SlotArray<COL$EPI_MU_CASS_ADE,N> = WMORec<WM_OUT_ADE_READ$,N>
|
|
|
|
SlotArray<COL$EPI_MU_WAFER_THK_RESULT,N> = WMORec<WM_OUT_MU_WAFER_THK_RESULT$,N>
|
|
NEXT N
|
|
|
|
SlotCtrl = @WINDOW:'.EPI_SLOT_FILL'
|
|
|
|
END ELSE
|
|
SlotNos = WOMatRec<WO_MAT_SLOT_NO$>
|
|
|
|
SlotCnt = COUNT(SlotNos,@VM) + (SlotNos NE '')
|
|
SlotIDs = ''
|
|
|
|
FOR I = 1 TO SlotCnt
|
|
SlotIDs<1,I> = WONo:'.':CassNo:'.':SlotNos<1,I>
|
|
NEXT I
|
|
|
|
SlotArray<COL$SLOT> = WOMatRec<WO_MAT_SLOT_NO$>
|
|
SlotArray<COL$SLOT_ID> = SlotIDs
|
|
SlotArray<COL$WAFER_ID> = obj_WO_Mat('SlotWaferIDs',WONo:'*':CassNo:@RM:WOMatRec)
|
|
SlotArray<COL$SLOT_NCR> = WOMatRec<WO_MAT_SLOT_NCR$>
|
|
SlotArray<COL$MET_NO$> = WOMatRec<WO_MAT_SLOT_MET_NO$>
|
|
SlotArray<COL$MOVED_TO_SLOT> = WOMatRec<WO_MAT_SLOT_MOVED_TO$>
|
|
SlotArray<COL$MU_WAFER_ID> = WOMatRec<WO_MAT_SLOT_MOVED_FROM$>
|
|
SlotArray<COL$MU_CASS_ADE> = ''
|
|
SlotArray<COL$MU_WAFER_THK_RESULT> = WOMatRec<WO_MAT_MU_WAFER_THK_RESULT$>
|
|
|
|
SlotCtrl = @WINDOW:'.SLOT_FILL'
|
|
END
|
|
|
|
TestSlot = ''
|
|
|
|
IF (MetSpecSlot = 'L') THEN
|
|
FOR N = SlotCnt TO 1 STEP -1
|
|
IF (SlotArray<COL$MU_WAFER_ID,N> = '') THEN
|
|
TestSlot = SlotArray<COL$SLOT,N>
|
|
END
|
|
UNTIL TestSlot NE ''
|
|
|
|
NEXT N
|
|
END
|
|
|
|
IF NUM(MetSpecSlot) THEN
|
|
FOR N = MetSpecSlot TO SlotCnt
|
|
IF SlotArray<COL$MU_WAFER_ID,N> = '' THEN
|
|
TestSlot = SlotArray<COL$SLOT,N>
|
|
END
|
|
UNTIL TestSlot NE ''
|
|
|
|
NEXT N
|
|
END
|
|
|
|
Ctrls = SlotCtrl ; Props = 'ARRAY' ; Vals = SlotArray
|
|
Ctrls := @RM:SlotCtrl ; Props := @RM:'VISIBLE' ; Vals := @RM:1
|
|
|
|
IF (TestSlot NE 'A') THEN
|
|
Set_Property(@WINDOW:'.TEST_SLOT','DEFPROP',TestSlot)
|
|
Ctrls := @RM:SlotCtrl ; Props := @RM:'SELPOS' ; Vals := @RM:0:@FM:TestSlot
|
|
END
|
|
|
|
Set_Property(Ctrls,Props,Vals)
|
|
|
|
GOSUB Refresh
|
|
|
|
RETURN
|
|
|
|
|
|
********
|
|
Refresh:
|
|
********
|
|
|
|
WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP')
|
|
CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP')
|
|
TestSlot = Get_Property(@WINDOW:'.TEST_SLOT','DEFPROP')
|
|
MetMin = Get_Property(@WINDOW:'.MET_MIN','DEFPROP',MetMin)
|
|
MetMax = Get_Property(@WINDOW:'.MET_MAX','DEFPROP',MetMax)
|
|
MetResult = Get_Property(@WINDOW:'.MET_MAX','DEFPROP',MetResult)
|
|
MetTest = Get_Property(@Window:'.MET_TEST', 'TEXT')
|
|
MetSpecSlot = Get_Property(@Window:'.MET_SPEC_SLOT', 'TEXT')
|
|
MetWfrQty = Get_Property(@Window:'.MET_SPEC_WFR_QTY', 'TEXT')
|
|
MetStdMax = Get_Property(@Window:'.MET_STD_MAX', 'TEXT')
|
|
|
|
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 1)
|
|
Set_Property(@WINDOW, '@ADE_STD_RESULT_REQ', 1)
|
|
Set_Property(@WINDOW, '@MU_WAFER_THK_RANGE_REQ', 1)
|
|
Set_Property(@WINDOW, '@MU_WAFER_THK_MISSING_REQ', 1)
|
|
Set_Property(@WINDOW, '@MULTI_MU_BOX_RESULT_REQ', 1)
|
|
Set_Property(@WINDOW, '@MU_BOXES_MISSING_RESULTS', '')
|
|
|
|
MUBoxes = ''
|
|
MUBoxResults = ''
|
|
|
|
IF Get_Property(@WINDOW:'.SLOT_FILL', 'VISIBLE') THEN
|
|
**********************************
|
|
* Non-EPIPRO MU Thickness Change *
|
|
**********************************
|
|
SlotCtrl = @WINDOW:'.SLOT_FILL'
|
|
SlotList = Get_Property(SlotCtrl,'LIST')
|
|
CtrlCols = Get_Property(SlotCtrl,'COLUMN')
|
|
|
|
If MetTest = 'ADE' then
|
|
If ( (MetSpecSlot EQ 'A') or (MetWfrQty EQ 'A') or (MetWfrQty GT 5) ) then
|
|
* Calculate Standard Deviation
|
|
StdDev = ''
|
|
SlotArray = Get_Property(SlotCtrl, 'ARRAY')
|
|
Vals = SlotArray<COL$MU_WAFER_THK_RESULT>
|
|
Vals = SRP_Array('Clean', Vals, 'Trim', @VM)
|
|
NumVals = DCount(Vals, @VM)
|
|
If NumVals EQ 25 then
|
|
StdDevType = 'POPULATION'
|
|
end else
|
|
StdDevType = 'SAMPLE'
|
|
end
|
|
If NumVals GT 0 then
|
|
StdDev = Math_Services('GetStdDev', Vals, StdDevType)
|
|
StdDev = OConv(IConv(StdDev, 'MD3'), 'MD3')
|
|
end
|
|
Set_Property(@WINDOW:'.MET_STD_RESULT', 'DEFPROP', StdDev)
|
|
If StdDev GT MetStdMax then
|
|
Backcolor = RED$
|
|
end else
|
|
Backcolor = GREEN$
|
|
end
|
|
Set_Property(@WINDOW:'.MET_STD_RESULT', 'BACKCOLOR', Backcolor)
|
|
end
|
|
end ;* End of check for ADE test
|
|
|
|
SlotCnt = COUNT(SlotList,@FM) + (SlotList NE '')
|
|
ColCnt = COUNT(CtrlCols,@SVM) + (CtrlCols NE '')
|
|
|
|
WOMatRec = XLATE('WO_MAT',WONo:'*':CassNo,'','X')
|
|
WMORec = XLATE('WM_OUT',WOMatRec<WO_MAT_WMO_KEY$>,'','X')
|
|
|
|
FOR Line = 1 TO SlotCnt
|
|
|
|
IF (SlotList<Line, 1> NE '') THEN
|
|
|
|
*******************
|
|
* Line = MU Wafer *
|
|
*******************
|
|
IF (SlotList<Line, COL$MU_WAFER_ID> NE '') THEN
|
|
|
|
FormMUWaferThkResult = TRIM(SlotList<Line, COL$MU_WAFER_THK_RESULT>)
|
|
DatabaseMUWaferThkResult = WOMatRec<WO_MAT_MU_WAFER_THK_RESULT$, Line>
|
|
|
|
*******************************************************
|
|
* MU Wafer Thickness Result value sets the line color *
|
|
*******************************************************
|
|
IF (FormMUWaferThkResult = '') THEN
|
|
Found = False$
|
|
BoxNumber = FIELD(SlotList<Line,COL$MU_WAFER_ID>,'.',1,2)
|
|
Locate BoxNumber in MUBoxes using @VM setting BoxIndex else
|
|
MUBoxes<0, -1> = BoxNumber
|
|
end
|
|
FOR LoopIndex = 1 TO SlotCnt
|
|
IF (SlotList<LoopIndex, 1> NE '') THEN
|
|
IF (SlotList<LoopIndex,COL$MU_WAFER_ID> NE '') THEN
|
|
LastMUBoxNumber = FIELD(SlotList<LoopIndex,COL$MU_WAFER_ID>,'.',1,2)
|
|
IF (BoxNumber = LastMUBoxNumber) THEN
|
|
IF (TRIM(SlotList<LoopIndex,COL$MU_WAFER_THK_RESULT>) NE '') THEN
|
|
IF ((SlotList<LoopIndex,COL$MU_WAFER_THK_RESULT> >= MetMin) AND (SlotList<LoopIndex,COL$MU_WAFER_THK_RESULT> <= MetMax)) THEN
|
|
Found = True$
|
|
END
|
|
END
|
|
END
|
|
END
|
|
END
|
|
NEXT LoopIndex
|
|
|
|
IF NOT(Found) THEN
|
|
MUBoxResults<0, BoxIndex> = False$
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, Line, LTGREY$)
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', COL$MU_WAFER_THK_RESULT, Line, WHITE$)
|
|
Set_Property(@WINDOW, '@MU_WAFER_THK_MISSING_REQ', 0)
|
|
END else
|
|
MUBoxResults<0, BoxIndex> = True$
|
|
end
|
|
END
|
|
|
|
IF (FormMUWaferThkResult NE '') THEN
|
|
IF ((FormMUWaferThkResult < MetMin) OR (FormMUWaferThkResult > MetMax)) THEN
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, Line, RED$)
|
|
Set_Property(@WINDOW, '@MU_WAFER_THK_RANGE_REQ', 0)
|
|
END
|
|
|
|
IF ((FormMUWaferThkResult >= MetMin) AND (FormMUWaferThkResult <= MetMax)) THEN
|
|
BoxNumber = FIELD(SlotList<Line,COL$MU_WAFER_ID>,'.',1,2)
|
|
FOR LoopIndex = 1 TO SlotCnt
|
|
IF (SlotList<LoopIndex, 1> NE '') THEN
|
|
IF (SlotList<LoopIndex,COL$MU_WAFER_ID> NE '') THEN
|
|
IF (BoxNumber = FIELD(SlotList<LoopIndex,COL$MU_WAFER_ID>,'.',1,2)) THEN
|
|
IF (LoopIndex = Line) OR (TRIM(SlotList<LoopIndex,COL$MU_WAFER_THK_RESULT>) = '') THEN
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, LoopIndex, MU_GREEN$)
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', COL$MU_WAFER_THK_RESULT, LoopIndex, WHITE$)
|
|
END
|
|
END
|
|
END
|
|
END
|
|
NEXT LoopIndex
|
|
END
|
|
END
|
|
|
|
END ELSE
|
|
************************
|
|
* Line = Regular Wafer *
|
|
************************
|
|
IF (Line = TestSlot) THEN
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, Line, YELLOW$)
|
|
END ELSE
|
|
//JRO
|
|
FormMUWaferThkResult = TRIM(SlotList<Line, COL$MU_WAFER_THK_RESULT>)
|
|
IF FormMUWaferThkResult NE '' AND ((FormMUWaferThkResult < MetMin) OR (FormMUWaferThkResult > MetMax)) then
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, Line, RED$)
|
|
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
|
|
end else
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, Line, WHITE$)
|
|
end
|
|
END
|
|
END
|
|
END
|
|
NEXT Line
|
|
|
|
END ELSE
|
|
******************************
|
|
* EPIPRO MU Thickness Change *
|
|
******************************
|
|
IF Get_Property(@WINDOW:'.EPI_SLOT_FILL', 'VISIBLE') THEN
|
|
SlotCtrl = @WINDOW:'.EPI_SLOT_FILL'
|
|
SlotList = Get_Property(SlotCtrl,'LIST')
|
|
CtrlCols = Get_Property(SlotCtrl,'COLUMN')
|
|
|
|
If MetTest = 'ADE' then
|
|
If ( (MetSpecSlot EQ 'A') or (MetWfrQty EQ 'A') or (MetWfrQty GT 5) ) then
|
|
* Calculate Standard Deviation
|
|
StdDev = ''
|
|
SlotArray = Get_Property(SlotCtrl, 'ARRAY')
|
|
Vals = SlotArray<COL$MU_WAFER_THK_RESULT>
|
|
Vals = SRP_Array('Clean', Vals, 'Trim', @VM)
|
|
NumVals = DCount(Vals, @VM)
|
|
If NumVals EQ 25 then
|
|
StdDevType = 'POPULATION'
|
|
end else
|
|
StdDevType = 'SAMPLE'
|
|
end
|
|
If NumVals GT 0 then
|
|
StdDev = Math_Services('GetStdDev', Vals, StdDevType)
|
|
StdDev = OConv(IConv(StdDev, 'MD3'), 'MD3')
|
|
end
|
|
Set_Property(@WINDOW:'.MET_STD_RESULT', 'DEFPROP', StdDev)
|
|
If StdDev GT MetStdMax then
|
|
Backcolor = RED$
|
|
end else
|
|
Backcolor = GREEN$
|
|
end
|
|
Set_Property(@WINDOW:'.MET_STD_RESULT', 'BACKCOLOR', Backcolor)
|
|
end
|
|
end ;* End of check for ADE test
|
|
|
|
SlotCnt = COUNT(SlotList,@FM) + (SlotList NE '')
|
|
ColCnt = COUNT(CtrlCols,@SVM) + (CtrlCols NE '')
|
|
|
|
WOMatRec = XLATE('WO_MAT',WONo:'*':CassNo,'','X')
|
|
WMORec = XLATE('WM_OUT',WOMatRec<WO_MAT_WMO_KEY$>,'','X')
|
|
|
|
FOR Line = 1 TO SlotCnt
|
|
|
|
IF (SlotList<Line, 1> NE '') THEN
|
|
|
|
*******************
|
|
* Line = MU Wafer *
|
|
*******************
|
|
IF (SlotList<Line, COL$EPI_MU_WFR_ID> NE '') THEN
|
|
FormMUWaferThkResult = TRIM(SlotList<Line, COL$EPI_MU_WAFER_THK_RESULT>)
|
|
DatabaseMUWaferThkResult = WMORec<WM_OUT_MU_WAFER_THK_RESULT$, Line>
|
|
|
|
*******************************************************
|
|
* MU Wafer Thickness Result value sets the line color *
|
|
*******************************************************
|
|
IF (FormMUWaferThkResult = '') THEN
|
|
Found = False$
|
|
BoxNumber = FIELD(SlotList<Line,COL$EPI_MU_WFR_ID>,'.',1,2)
|
|
Locate BoxNumber in MUBoxes using @VM setting BoxIndex else
|
|
MUBoxes<0, -1> = BoxNumber
|
|
end
|
|
FOR LoopIndex = 1 TO SlotCnt
|
|
IF (SlotList<LoopIndex, 1> NE '') THEN
|
|
IF (SlotList<LoopIndex,COL$EPI_MU_WFR_ID> NE '') THEN
|
|
LastMUBoxNumber = FIELD(SlotList<LoopIndex,COL$EPI_MU_WFR_ID>,'.',1,2)
|
|
IF (BoxNumber = LastMUBoxNumber) THEN
|
|
IF (TRIM(SlotList<LoopIndex,COL$EPI_MU_WAFER_THK_RESULT>) NE '') THEN
|
|
IF ((SlotList<LoopIndex,COL$EPI_MU_WAFER_THK_RESULT> >= MetMin) AND (SlotList<LoopIndex,COL$EPI_MU_WAFER_THK_RESULT> <= MetMax)) THEN
|
|
Found = True$
|
|
END
|
|
END
|
|
END
|
|
END
|
|
END
|
|
NEXT LoopIndex
|
|
|
|
IF NOT(Found) THEN
|
|
MUBoxResults<0, BoxIndex> = False$
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, Line, LTGREY$)
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', COL$EPI_MU_WAFER_THK_RESULT, Line, WHITE$)
|
|
Set_Property(@WINDOW, '@MU_WAFER_THK_MISSING_REQ', 0)
|
|
END else
|
|
MUBoxResults<0, BoxIndex> = True$
|
|
end
|
|
END
|
|
|
|
IF (FormMUWaferThkResult NE '') THEN
|
|
IF ((FormMUWaferThkResult < MetMin) OR (FormMUWaferThkResult > MetMax)) THEN
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, Line, RED$)
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', COL$EPI_MU_WAFER_THK_RESULT, Line, WHITE$)
|
|
Set_Property(@WINDOW, '@MU_WAFER_THK_RANGE_REQ', 0)
|
|
END
|
|
|
|
IF ((FormMUWaferThkResult >= MetMin) AND (FormMUWaferThkResult <= MetMax)) THEN
|
|
BoxNumber = FIELD(SlotList<Line,COL$EPI_MU_WFR_ID>,'.',1,2)
|
|
FOR LoopIndex = 1 TO SlotCnt
|
|
IF (SlotList<LoopIndex, 1> NE '') THEN
|
|
IF (SlotList<LoopIndex,COL$EPI_MU_WFR_ID> NE '') THEN
|
|
IF (BoxNumber = FIELD(SlotList<LoopIndex,COL$EPI_MU_WFR_ID>,'.',1,2)) THEN
|
|
IF ((LoopIndex = Line) OR (TRIM(SlotList<LoopIndex,COL$EPI_MU_WAFER_THK_RESULT>) = '')) THEN
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, LoopIndex, MU_GREEN$)
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', COL$EPI_MU_WAFER_THK_RESULT, LoopIndex, WHITE$)
|
|
END
|
|
END
|
|
END
|
|
END
|
|
NEXT LoopIndex
|
|
END
|
|
END
|
|
|
|
END ELSE
|
|
************************
|
|
* Line = Regular Wafer *
|
|
************************
|
|
IF (Line = TestSlot) THEN
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, Line, YELLOW$)
|
|
END ELSE
|
|
//JRO
|
|
FormMUWaferThkResult = TRIM(SlotList<Line, COL$MU_WAFER_THK_RESULT>)
|
|
IF FormMUWaferThkResult NE '' AND ((FormMUWaferThkResult < MetMin) OR (FormMUWaferThkResult > MetMax)) then
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, Line, RED$)
|
|
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
|
|
end else
|
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', 0, Line, WHITE$)
|
|
end
|
|
END
|
|
END
|
|
END
|
|
NEXT Line
|
|
|
|
END
|
|
END
|
|
|
|
If MUBoxes NE '' then
|
|
MUBoxesMissingResults = ''
|
|
For each MUBox in MUBoxes using @VM setting MUBoxIndex
|
|
If MUBoxResults<0, MUBoxIndex> NE True$ then
|
|
MUBoxesMissingResults<0, -1> = MUBox
|
|
end
|
|
Next MUBox
|
|
If MUBoxesMissingResults then
|
|
Set_Property(@WINDOW, '@MU_BOXES_MISSING_RESULTS', MUBoxesMissingResults)
|
|
If (DCount(MUBoxesMissingResults, @VM) GT 1) then
|
|
Set_Property(@WINDOW, '@MULTI_MU_BOX_RESULT_REQ', 0)
|
|
end
|
|
end
|
|
end
|
|
|
|
SlotSelection = Get_Property(SlotCtrl, 'SELPOS')
|
|
SelectedRow = SlotSelection<2>
|
|
Handle = Get_Property(SlotCtrl, 'HANDLE')
|
|
CALL sendMessage(Handle, DTM_SELROW$, 0, SelectedRow - 1)
|
|
|
|
RETURN
|
|
|
|
|
|
**************
|
|
SaveThickness:
|
|
**************
|
|
|
|
WONo = Get_Property(@WINDOW:'.WO_NO', 'DEFPROP')
|
|
CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO', 'DEFPROP')
|
|
WOStepNo = Get_Property(@WINDOW:'.PROC_STEP_NO', 'DEFPROP')
|
|
SigProfKey = Get_Property(@WINDOW:'.MET_TEST', 'DEFPROP')
|
|
MetResult = Get_Property(@WINDOW:'.MET_RESULT', 'DEFPROP')
|
|
Stage = Get_Property(@WINDOW:'.RUN_STEP', 'DEFPROP')
|
|
StdMax = Get_Property(@WINDOW:'.MET_STD_MAX', 'DEFPROP')
|
|
StdResult = Get_Property(@WINDOW:'.MET_STD_RESULT','DEFPROP')
|
|
Slot = Get_Property(@WINDOW:'.MET_SPEC_SLOT', 'DEFPROP')
|
|
|
|
***************************************
|
|
* Save MU Wafer Thickness Information *
|
|
***************************************
|
|
|
|
WOMatKey = WONo:'*':CassNo
|
|
WOMatRec = XLATE('WO_MAT', WOMatKey, '', 'X')
|
|
|
|
IF Get_Property(@WINDOW:'.SLOT_FILL', 'VISIBLE') THEN
|
|
********************************
|
|
* Save Non-EPIPRO MU Thickness *
|
|
********************************
|
|
SlotCtrl = @WINDOW:'.SLOT_FILL'
|
|
SlotList = Get_Property(SlotCtrl,'LIST')
|
|
SlotCnt = COUNT(SlotList,@FM) + (SlotList NE '')
|
|
|
|
FOR Row = 1 TO SlotCnt
|
|
WOMatRec<WO_MAT_MU_WAFER_THK_RESULT$, Row> = SlotList<Row, COL$MU_WAFER_THK_RESULT>
|
|
NEXT
|
|
|
|
Set_Status(0)
|
|
Parameters = 'WO_MAT':@RM:WOMatKey:@RM:'':@RM:WOMatRec
|
|
obj_Tables('WriteRec', Parameters)
|
|
errCode = ''
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
|
|
END ELSE
|
|
****************************
|
|
* Save EPIPRO MU Thickness *
|
|
****************************
|
|
SlotCtrl = @WINDOW:'.EPI_SLOT_FILL'
|
|
SlotList = Get_Property(SlotCtrl,'LIST')
|
|
SlotCnt = COUNT(SlotList,@FM) + (SlotList NE '')
|
|
|
|
WMOKey = WOMatRec<WO_MAT_WMO_KEY$>
|
|
WMORec = XLATE('WM_OUT', WMOKey, '', 'X')
|
|
|
|
FOR Row = 1 TO SlotCnt
|
|
WMORec<WM_OUT_MU_WAFER_THK_RESULT$, Row> = SlotList<Row, COL$EPI_MU_WAFER_THK_RESULT>
|
|
NEXT
|
|
|
|
Set_Status(0)
|
|
Parameters = 'WM_OUT':@RM:WMOKey:@RM:'':@RM:WMORec
|
|
obj_Tables('WriteRec', Parameters)
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
END
|
|
|
|
**********************************
|
|
* Save ADE Thickness Information *
|
|
**********************************
|
|
Set_Status(0)
|
|
WOMatQAKey = WONo:'*':CassNo
|
|
WOMatQARec = XLATE('WO_MAT_QA', WOMatQAKey, '', 'X')
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
|
|
Profiles = WOMatQARec<WO_MAT_QA_PROFILE$>
|
|
Stages = WOMatQARec<WO_MAT_QA_STAGE$>
|
|
Slots = WOMatQARec<WO_MAT_QA_SLOT$>
|
|
|
|
ProfSteps = ''
|
|
ProfileCnt = COUNT(WOMatQARec<WO_MAT_QA_PROFILE$>,@VM) + (WOMatQARec<WO_MAT_QA_PROFILE$> NE '')
|
|
FOR ProfileIndex = 1 TO ProfileCnt
|
|
ProfSteps<1,ProfileIndex> = Profiles<0, ProfileIndex>:'*':Stages<0, ProfileIndex>:'*':Slots<0, ProfileIndex>
|
|
NEXT ProfileIndex
|
|
|
|
IF NUM(SigProfKey[1,1]) ELSE
|
|
SigProfKey = WOStepNo:SigProfKey
|
|
END
|
|
ThisProfStep = SigProfKey:'*':Stage:'*':Slot
|
|
|
|
Found = False$
|
|
For each ProfStep in ProfSteps using @VM setting vPos
|
|
|
|
If ProfStep EQ ThisProfStep then
|
|
Found = True$
|
|
WOMatQARec<WO_MAT_QA_RESULT$,vPos> = MetResult
|
|
WOMatQARec<WO_MAT_QA_STD_MAX$,vPos> = ICONV(StdMax,'MD3')
|
|
WOMatQARec<WO_MAT_QA_STD_RESULT$,vPos> = StdResult ;* Added 8/5/2013 JCH
|
|
end
|
|
|
|
Until Found EQ True$
|
|
Next ProfStep
|
|
|
|
Database_Services('WriteDataRow', 'WO_MAT_QA', WOMatQAKey, WOMatQARec, True$, False$, False$)
|
|
If Error_Services('HasError') then
|
|
ErrMsg(Error_Services('GetMessage'))
|
|
end
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ResultLF:
|
|
* * * * * * *
|
|
|
|
MetLine = Get_Property(@WINDOW,'@MET_LINE_IN')
|
|
MetResult = Trim(Get_Property(@WINDOW:'.MET_RESULT','DEFPROP'))
|
|
MetStdResult = Get_Property(@WINDOW:'.MET_STD_RESULT','DEFPROP')
|
|
MetStdMax = Get_Property(@WINDOW:'.MET_STD_MAX','DEFPROP')
|
|
|
|
IF MetResult NE '' THEN
|
|
Set_Property(@WINDOW, '@MET_RESULT_REQ', 1)
|
|
END ELSE
|
|
Set_Property(@WINDOW, '@MET_RESULT_REQ', 0)
|
|
END
|
|
|
|
IF (MetResult NE '') THEN
|
|
If ( (MetResult < MetLine<1,COL$MET_MIN>) OR (MetResult > MetLine<1,COL$MET_MAX>) ) then
|
|
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
|
|
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',RED$)
|
|
end else
|
|
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 1)
|
|
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',GREEN$)
|
|
end
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',WHITE$)
|
|
Set_Property(@WINDOW, '@MET_RESULT_REQ', 0)
|
|
END
|
|
|
|
IF (MetStdResult NE '') THEN
|
|
If (MetStdResult > MetStdMax) then
|
|
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',RED$)
|
|
end else
|
|
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',GREEN$)
|
|
END
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
TWUse:
|
|
* * * * * * *
|
|
|
|
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:'.RDS_NO':@RM ; Props := 'DEFPROP':@RM
|
|
Ctrls := @WINDOW:'.RUN_STEP':@RM ; Props := 'DEFPROP':@RM
|
|
Ctrls := @WINDOW:'.TEST_SLOT' ; Props := 'DEFPROP'
|
|
|
|
Vals = Get_Property(Ctrls,Props)
|
|
|
|
WONo = Vals[1,@RM]
|
|
WOStep = Vals[COL2()+1,@RM]
|
|
CassNo = Vals[COL2()+1,@RM]
|
|
RDSNo = Vals[COL2()+1,@RM]
|
|
RunStep = Vals[COL2()+1,@RM]
|
|
TestSlot = Vals[COL2()+1,@RM]
|
|
|
|
If TestSlot = '' Then Return ;* Test Slot required
|
|
|
|
If RdsNo = '' Then
|
|
* EpiPRO WM Out
|
|
WMOutKey = WONo:'*':WOStep:'*':CassNo
|
|
RDSSlotNos = obj_WM_Out('RDSSlots',WMOutKey)
|
|
|
|
sCnt = Count(RDSSlotNos,@FM) + (RDSSlotNos NE '')
|
|
For I = 1 To sCnt
|
|
SlotRange = RDSSlotNos<2,I>
|
|
rLower = SlotRange[1,'-']
|
|
rUpper = SlotRange[COL2()+1,'-']
|
|
If TestSlot >= rLower And TestSlot <= rUpper Then
|
|
RDSNo = RDSSlotNos<1,I>
|
|
End
|
|
|
|
Until RDSNo NE ''
|
|
Next I
|
|
|
|
END
|
|
|
|
// RDS_TEST is Metrology Data
|
|
Open 'DICT.RDS_TEST' To DictRdsTest Else
|
|
ErrMsg('Unable to open DICT.RDS_TEST for index lookup')
|
|
Return
|
|
End
|
|
|
|
// Return Metrology key(s) associated with the RDSNo
|
|
Search = 'RDS_NO':@VM:RDSNo:@FM
|
|
RDSTestKeys = ''
|
|
Btree.Extract(Search,'RDS_TEST',DictRdsTest,RDSTestKeys,'','')
|
|
|
|
If Get_Status(errCode) Then
|
|
ErrMsg(errCode)
|
|
RETURN
|
|
End
|
|
|
|
// If there are multiple metrology records associated with the RDSNo, then
|
|
// provide a popup of the metrology records for the user to select from.
|
|
If Index(RDSTestKeys,@VM,1) Then
|
|
TypeOver = ''
|
|
TypeOver<PDISPLAY$> = RDSTestKeys
|
|
|
|
RDSTestKey = Popup(@WINDOW,TypeOver,'RDS_TEST')
|
|
End Else
|
|
RDSTestKey = RDSTestKeys
|
|
End
|
|
|
|
oaParms = 'RDS_TEST':@RM
|
|
oaParms := RDSTestKey:@RM
|
|
oaParms := ''
|
|
|
|
obj_AppWindow('ViewRelated',oaParms)
|
|
|
|
Gosub Refresh
|
|
|
|
RETURN
|
|
|
|
|
|
*****
|
|
Sign:
|
|
*****
|
|
|
|
******************************************
|
|
* Save the ADE & MU wafer thickness data *
|
|
******************************************
|
|
|
|
GOSUB SaveThickness
|
|
GoSub Refresh;//JRO
|
|
|
|
******************************************************************
|
|
* Verify that all requirements have been met to accept signature *
|
|
******************************************************************
|
|
|
|
SignatureReady = True$
|
|
|
|
// These checks should only apply to QA stage and ADE tests ///////////////
|
|
Test = Get_Property(@Window:'.RUN_STEP', 'TEXT')
|
|
Stage = Get_Property(@Window:'.MET_TEST', 'TEXT')
|
|
|
|
|
|
If (Test EQ 'QA' or Test EQ 'MO_QA') and (Stage EQ 'ADE') then
|
|
|
|
Slot = Get_Property(@Window:'.MET_SPEC_SLOT', 'TEXT')
|
|
SlotFillVisible = Get_Property(@WINDOW:'.SLOT_FILL', 'VISIBLE')
|
|
IF (Slot _EQC 'A') and SlotFillVisible THEN
|
|
WoNo = Get_Property(@Window:'.WO_NO', 'TEXT')
|
|
CassNo = Get_Property(@Window:'.OUT_CASS_NO', 'TEXT')
|
|
WoMatQaKey = WoNo:'*':CassNo
|
|
RunStep = Get_Property(@Window:'.RUN_STEP', 'TEXT')
|
|
AllWafersWereTested = Wo_Mat_Qa_Services('AllWafersWereTested', WoMatQaKey, RunStep)
|
|
If AllWafersWereTested EQ False$ then
|
|
SignatureReady = False$
|
|
ErrMsg("Error: Thickness value required on all wafers!")
|
|
end
|
|
end
|
|
|
|
ADEWaferThkRangeReq = Get_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ')
|
|
IF (ADEWaferThkRangeReq = 0) THEN
|
|
SignatureReady = False$
|
|
ErrMsg("Error: ADE Wafer Thk is OOS!")
|
|
END
|
|
|
|
MetResultReq = Get_Property(@WINDOW, '@MET_RESULT_REQ')
|
|
IF (MetResultReq = 0) THEN
|
|
SignatureReady = False$
|
|
ErrMsg("Warning: Verify ADE Thk Result!")
|
|
END
|
|
|
|
MUWaferThkRangeReq = Get_Property(@WINDOW, '@MU_WAFER_THK_RANGE_REQ')
|
|
IF (MUWaferThkRangeReq = 0) THEN
|
|
SignatureReady = False$
|
|
ErrMsg("Error: MU Wafer Thk is OOS!")
|
|
END
|
|
|
|
MultiMUWaferThickMissing = Get_Property(@WINDOW, '@MULTI_MU_BOX_RESULT_REQ')
|
|
If (MultiMUWaferThickMissing EQ 0) then
|
|
SignatureReady = False$
|
|
MUBoxesMissingResults = Get_Property(@WINDOW, '@MU_BOXES_MISSING_RESULTS')
|
|
Swap @VM with ',' in MUBoxesMissingResults
|
|
ErrorMessage = "Error: Makeup wafers from two different makeup boxes have been used. "
|
|
ErrorMessage := "At least one thickness measurement is required for each makeup box. "
|
|
ErrorMessage := "Thickness measurements are missing from the following makeup boxes: ":MUBoxesMissingResults:"."
|
|
ErrMsg(ErrorMessage)
|
|
end else
|
|
MUWaferThkMissingReq = Get_Property(@WINDOW, '@MU_WAFER_THK_MISSING_REQ')
|
|
IF (MUWaferThkMissingReq = 0) THEN
|
|
SignatureReady = False$
|
|
ErrMsg("Warning: MU Wafer Thk is missing!")
|
|
END
|
|
end
|
|
|
|
end
|
|
|
|
////////////////////////////////////////////////////////////////////////////
|
|
|
|
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:'.RDS_NO':@RM ; Props := 'DEFPROP':@RM
|
|
Ctrls := @WINDOW:'.MET_RESULT':@RM ; Props := 'DEFPROP':@RM
|
|
Ctrls := @WINDOW:'.MET_TEST':@RM ; Props := 'DEFPROP':@RM
|
|
Ctrls := @WINDOW:'.RUN_STEP':@RM ; Props := 'DEFPROP':@RM
|
|
Ctrls := @WINDOW:'.MET_STD_MAX':@RM ; Props := 'DEFPROP':@RM
|
|
Ctrls := @WINDOW:'.MET_STD_RESULT':@RM ; Props := 'DEFPROP':@RM
|
|
Ctrls := @WINDOW:'.MET_SPEC_SLOT' ; Props := 'DEFPROP'
|
|
|
|
Vals = Get_Property(Ctrls,Props)
|
|
|
|
WONo = Vals[1,@RM]
|
|
WOStep = Vals[COL2()+1,@RM]
|
|
CassNo = Vals[COL2()+1,@RM]
|
|
RDSNo = Vals[COL2()+1,@RM]
|
|
MetResult = Vals[COL2()+1,@RM]
|
|
SigKey = Vals[COL2()+1,@RM]
|
|
RunStep = Vals[COL2()+1,@RM]
|
|
StdMax = Vals[COL2()+1,@RM]
|
|
StdResult = Vals[COL2()+1,@RM]
|
|
Slot = Vals[COL2()+1,@RM]
|
|
|
|
MetLineIn = Get_Property(@WINDOW,'@MET_LINE_IN')
|
|
MetTest = MetLineIn<1,COL$MET_TEST>
|
|
OrigMetResult = MetLineIn<1,COL$MET_RESULT>
|
|
If (MetTest _EQC 'CRES') AND (OrigMetResult NE MetResult) then
|
|
Post_Metrology_Manual_Data_Entry_Log(@USER4, 'HgCRes', RDSNo : ' / ' : WONo : '*' : CassNo)
|
|
end
|
|
|
|
IF (SignatureReady = True$) THEN
|
|
|
|
Valid = Dialog_Box('NDW_VERIFY_USER', @Window, @User4)
|
|
Valid = Valid<1>
|
|
IF (Valid) THEN
|
|
ScanUser = @USER4
|
|
ScanDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTHS')
|
|
|
|
ScanUser = @USER4
|
|
ScanDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTHS')
|
|
|
|
// Sign each QA test all at once (i.e. loop through the slots)
|
|
WOMatQARec = Database_Services('ReadDataRow', 'WO_MAT_QA', WONo:'*':CassNo)
|
|
WOMatQAStages = WOMatQARec<WO_MAT_QA_STAGE$>
|
|
WOMatQASlots = WOMatQARec<WO_MAT_QA_SLOT$>
|
|
WOMatQAResults = WOMatQARec<WO_MAT_QA_RESULT$>
|
|
For each WOMatQAStage in WOMatQAStages using @VM setting vPos
|
|
WOMatQAResult = WOMatQAResults<0, vPos>
|
|
If WOMatQAResult NE '' then
|
|
// Attempt to sign the metrology test
|
|
If ( (WOMatQAStage EQ 'QA') or (WOMatQAStage EQ 'MO_QA') or (WOMatQAStage EQ 'UNLOAD' and MetTest EQ 'LW_RHO') ) then
|
|
WOMatQASlot = WOMatQASlots<0, vPos>
|
|
SigReady = Signature_Services('QAMetSigReady', RDSNo, WOMatQAStage, WOMatQASlot, WONo:'*':CassNo)
|
|
If SigReady then
|
|
Signature_Services('SignQAMet', RDSNo, WOMatQAStage, @User4, WOMatQASlot, WONo:'*':CassNo)
|
|
If Error_Services('HasError') then
|
|
ErrMsg(Error_Services('GetMessage'))
|
|
end
|
|
end else
|
|
ErrMsg(Error_Services('GetMessage'))
|
|
end
|
|
end
|
|
end
|
|
Next WOMatQAStage
|
|
|
|
BEGIN CASE
|
|
CASE RDSNo = '' ; Send_Event('WM_OUT','WRITE')
|
|
CASE RunStep = 'UNLOAD' ; Send_Event('RDS_UNLOAD','WRITE')
|
|
CASE RunStep = 'QA' ; Send_Event('RDS_POST_EPI','WRITE')
|
|
END CASE
|
|
|
|
BEGIN CASE
|
|
CASE RDSNo = '' ; obj_Appwindow('LoadFormKeys','WM_OUT':@RM:WONo:'*':WOStep:'*':CassNo)
|
|
CASE RunStep = 'UNLOAD' ; obj_Appwindow('LoadFormKeys','RDS_UNLOAD':@RM:RDSNo)
|
|
CASE RunStep = 'QA' ; obj_Appwindow('LoadFormKeys','RDS_POST_EPI':@RM:RDSNo)
|
|
END CASE
|
|
|
|
End_Window(@WINDOW,'')
|
|
|
|
END ;* End of check for Valid Signature
|
|
|
|
END ELSE ;* End of check for Signature Ready
|
|
|
|
BEGIN CASE
|
|
CASE RDSNo = '' ; Send_Event('WM_OUT','WRITE')
|
|
CASE RunStep = 'UNLOAD' ; Send_Event('RDS_UNLOAD','WRITE')
|
|
CASE RunStep = 'QA' ; Send_Event('RDS_POST_EPI','WRITE')
|
|
END CASE
|
|
|
|
BEGIN CASE
|
|
CASE RDSNo = '' ; obj_Appwindow('LoadFormKeys','WM_OUT':@RM:WONo:'*':WOStep:'*':CassNo)
|
|
CASE RunStep = 'UNLOAD' ; obj_Appwindow('LoadFormKeys','RDS_UNLOAD':@RM:RDSNo)
|
|
CASE RunStep = 'QA' ; obj_Appwindow('LoadFormKeys','RDS_POST_EPI':@RM:RDSNo)
|
|
END CASE
|
|
|
|
END
|
|
RETURN
|
|
|
|
|
|
*****
|
|
Exit:
|
|
*****
|
|
|
|
End_Window(@WINDOW,'')
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
SlotClick:
|
|
* * * * * * *
|
|
|
|
MetSlot = Get_Property(@WINDOW:'.MET_SLOT','DEFPROP')
|
|
|
|
CtrlName = @WINDOW:'.SLOT_FILL'
|
|
SlotList = Get_Property(CtrlName,'LIST')
|
|
|
|
SlotSelection = Get_Property(CtrlName,'SELPOS')
|
|
SelectedRow = SlotSelection<2>
|
|
|
|
IF (SlotList<SelectedRow,COL$EPI_MU_WFR_ID> NE '') THEN
|
|
Set_Property(@WINDOW:'.SLOT_FILL', 'CARETPOS', COL$MU_WAFER_THK_RESULT:@FM:SelectedRow)
|
|
|
|
END ELSE
|
|
Handle = Get_Property(CtrlName, 'HANDLE')
|
|
CALL sendMessage(Handle, DTM_SELROW$, 0, SelectedRow-1)
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
EpiSlotClick:
|
|
* * * * * * *
|
|
|
|
MetSlot = Get_Property(@WINDOW:'.MET_SLOT','DEFPROP')
|
|
|
|
CtrlName = @WINDOW:'.EPI_SLOT_FILL'
|
|
SlotList = Get_Property(CtrlName,'LIST')
|
|
|
|
SlotSelection = Get_Property(CtrlName,'SELPOS')
|
|
SelectedRow = SlotSelection<2>
|
|
|
|
IF SlotList<SelectedRow,COL$EPI_MU_WFR_ID> NE '' THEN
|
|
Set_Property(@WINDOW:'.EPI_SLOT_FILL', 'CARETPOS', COL$EPI_MU_WAFER_THK_RESULT:@FM:SelectedRow)
|
|
|
|
END ELSE
|
|
Handle = Get_Property(CtrlName, 'HANDLE')
|
|
CALL sendMessage(Handle, DTM_SELROW$, 0, SelectedRow-1)
|
|
END
|
|
|
|
RETURN
|
|
|
|
**********
|
|
InsertRow:
|
|
**********
|
|
|
|
NULL
|
|
|
|
RETURN
|
|
|
|
|
|
**********
|
|
DeleteRow:
|
|
**********
|
|
|
|
IF Get_Property(@WINDOW:'.SLOT_FILL', 'VISIBLE') THEN
|
|
CtrlEntID = @WINDOW:'.SLOT_FILL'
|
|
END ELSE
|
|
CtrlEntID = @WINDOW:'.EPI_SLOT_FILL'
|
|
END
|
|
stat = Send_Message(CtrlEntID, "INSERT", Parm1, Parm2)
|
|
GOSUB Refresh
|
|
|
|
RETURN
|
|
|
|
*********
|
|
TrapKeys:
|
|
*********
|
|
|
|
Message = Parm2
|
|
|
|
BEGIN CASE
|
|
|
|
CASE ( Message = ETM_INSERTROW$ )
|
|
* // Stop the insert here...
|
|
CALL set_WinMsgVal( TRUE$, 0 ) ; * // Force PS to return 0 to Windows
|
|
|
|
CASE ( Message = ETM_DELETEROW$ )
|
|
* // Stop the delete here...
|
|
CALL set_WinMsgVal( TRUE$, 0 ) ; * // Force PS to return 0 to Windows
|
|
|
|
END CASE
|
|
|
|
RETURN
|
|
|
|
***********
|
|
PubSaveClick:
|
|
***********
|
|
GoSub SaveThickness
|
|
if Error_Services('NoError') then
|
|
Message = ''
|
|
Message<MTEXT$> = 'Data Saved'
|
|
Message<MTYPE$> = 'T2.5'
|
|
Msg(@window, Message)
|
|
end else
|
|
Message = ''
|
|
Message<MTEXT$> = 'Data Saved'
|
|
Message<MTYPE$> = 'BO'
|
|
Message<MICON$> = 'H'
|
|
Msg(@window, Message)
|
|
end
|
|
|
|
RETURN
|
|
|