updated 100% stratus to auto calculate std dev

This commit is contained in:
Infineon\StieberD
2024-09-19 11:43:27 -07:00
committed by Stieber Daniel (IT FI MES)
parent b0b127cd87
commit 2dc8a264c2
8 changed files with 24560 additions and 3666 deletions

View File

@ -13,7 +13,7 @@ DECLARE SUBROUTINE Start_Window, End_Window, Post_Metrology_Manual_Data_Entry_Lo
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
Declare Function Wo_Mat_Qa_Services, SRP_Array, Math_Services
$INSERT APPCOLORS
$INSERT LSL_USERS_EQU
@ -162,18 +162,14 @@ Create:
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
@ -193,20 +189,11 @@ Create:
Set_Property(@WINDOW:'.MET_RESULT','DEFPROP',MetResult)
Set_Property(@WINDOW:'.MET_STD_RESULT','DEFPROP',MetStdResult)
*IF MetSpecSlot = 'A' THEN
* Set_Property(@WINDOW:'.TEST_SLOT','ENABLED',0)
* Set_Property(@WINDOW:'.TEST_SLOT','BACKCOLOR',GREY$)
*END ELSE
* Set_Property(@WINDOW:'.TEST_SLOT','ENABLED',1)
* Set_Property(@WINDOW:'.TEST_SLOT','BACKCOLOR',WHITE$)
*END
Set_Property(@WINDOW:'.MET_STD_RESULT', 'ENABLED', False$)
IF MetStdMax = '' THEN
Set_Property(@WINDOW:'.MET_STD_RESULT','ENABLED',0)
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',GREY$)
END ELSE
Set_Property(@WINDOW:'.MET_STD_RESULT','ENABLED',1)
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',WHITE$)
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',GREEN$)
END
IF ((MetResult < MetMin) OR (MetResult > MetMax)) then
@ -317,13 +304,17 @@ 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)
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)
@ -341,6 +332,33 @@ Refresh:
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 '')
@ -428,10 +446,9 @@ Refresh:
IF FormMUWaferThkResult NE '' AND ((FormMUWaferThkResult < MetMin) OR (FormMUWaferThkResult > MetMax)) then
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, RED$)
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
end else
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, WHITE$)
end
/*end else
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, GREEN$)
end */
END
END
END
@ -446,6 +463,33 @@ Refresh:
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 '')
@ -533,10 +577,9 @@ Refresh:
IF FormMUWaferThkResult NE '' AND ((FormMUWaferThkResult < MetMin) OR (FormMUWaferThkResult > MetMax)) then
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, RED$)
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
end else
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, WHITE$)
end
/*end else
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, GREEN$)
end */
END
END
END
@ -665,23 +708,15 @@ SaveThickness:
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
* WOMatQARec<WO_MAT_QA_SIG$,vPos> = @USER4
* WOMatQARec<WO_MAT_QA_SIG_DTM$,vPos> = Datetime()
end
Until Found EQ True$
Next ProfStep
* Set_Status(0)
* Parameters = 'WO_MAT_QA':@RM:WOMatQAKey:@RM:'':@RM:WOMatQARec
* obj_Tables('WriteRec', Parameters)
Database_Services('WriteDataRow', 'WO_MAT_QA', WOMatQAKey, WOMatQARec, True$, False$, False$)
If Error_Services('HasError') then
ErrMsg(Error_Services('GetMessage'))
end
* IF Get_Status(errCode) THEN
* ErrMsg(errCode)
* END
RETURN
@ -690,71 +725,37 @@ RETURN
ResultLF:
* * * * * * *
MetLine = Get_Property(@WINDOW,'@MET_LINE_IN')
MetResult = TRIM(Get_Property(@WINDOW:'.MET_RESULT','DEFPROP'))
MetStdEnabled = Get_Property(@WINDOW:'.MET_STD_RESULT','ENABLED')
IF MetStdEnabled THEN
MetStdResult = Get_Property(@WINDOW:'.MET_STD_RESULT','DEFPROP')
MetStdMax = Get_Property(@WINDOW:'.MET_STD_MAX','DEFPROP')
END ELSE
MetStdResult = ''
END
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
IF MetStdEnabled = 1 THEN
IF MetStdResult NE '' THEN
*Set_Property(@WINDOW:'.SIGN','ENABLED',1)
Set_Property(@WINDOW, '@MET_RESULT_REQ', 1)
END ELSE
*Set_Property(@WINDOW:'.SIGN','ENABLED',0)
Set_Property(@WINDOW, '@MET_RESULT_REQ', 0)
END
END ELSE
*Set_Property(@WINDOW:'.SIGN','ENABLED',1)
Set_Property(@WINDOW, '@MET_RESULT_REQ', 1)
END
Set_Property(@WINDOW, '@MET_RESULT_REQ', 1)
END ELSE
*Set_Property(@WINDOW:'.SIGN','ENABLED',0)
Set_Property(@WINDOW, '@MET_RESULT_REQ', 0)
END
IF (MetResult NE '') THEN
BEGIN CASE
CASE (MetResult < MetLine<1,COL$MET_MIN>) OR (MetResult > MetLine<1,COL$MET_MAX>)
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',RED$)
CASE 1
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 1)
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',GREEN$)
END CASE
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:'.SIGN','ENABLED',0)
Set_Property(@WINDOW, '@MET_RESULT_REQ', 0)
END
IF (MetStdEnabled) THEN
IF (MetStdResult NE '') THEN
BEGIN CASE
CASE MetStdResult > MetStdMax
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',RED$)
Set_Property(@WINDOW, '@ADE_STD_RESULT_REQ', 0)
CASE 1
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',GREEN$)
Set_Property(@WINDOW, '@ADE_STD_RESULT_REQ', 1)
END CASE
END ELSE
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',WHITE$)
*Set_Property(@WINDOW:'.SIGN','ENABLED',0)
Set_Property(@WINDOW, '@MET_RESULT_REQ', 0)
END
END ;* End of check for enable MET_STD_RESULT
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
@ -882,12 +883,6 @@ Sign:
ErrMsg("Error: ADE Wafer Thk is OOS!")
END
ADEStdResultReq = Get_Property(@WINDOW, '@ADE_STD_RESULT_REQ')
IF (ADEStdResultReq = 0) THEN
SignatureReady = False$
ErrMsg("Error: ADE Std Result is OOS!")
END
MetResultReq = Get_Property(@WINDOW, '@MET_RESULT_REQ')
IF (MetResultReq = 0) THEN
SignatureReady = False$
@ -1024,27 +1019,6 @@ RETURN
Exit:
*****
/*
WONo = Get_Property(@WINDOW:'.WO_NO', 'DEFPROP')
WOStep = Get_Property(@WINDOW:'.PROC_STEP_NO', 'DEFPROP')
CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO', 'DEFPROP')
RDSNo = Get_Property(@WINDOW:'.RDS_NO', 'DEFPROP')
RunStep = Get_Property(@WINDOW:'.RUN_STEP', 'DEFPROP')
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_Dialog(@WINDOW,'')
End_Window(@WINDOW,'')
RETURN
@ -1055,7 +1029,6 @@ SlotClick:
* * * * * * *
MetSlot = Get_Property(@WINDOW:'.MET_SLOT','DEFPROP')
*TestSlot = Get_Property(@WINDOW:'.TEST_SLOT','DEFPROP')
CtrlName = @WINDOW:'.SLOT_FILL'
SlotList = Get_Property(CtrlName,'LIST')
@ -1063,20 +1036,10 @@ SlotClick:
SlotSelection = Get_Property(CtrlName,'SELPOS')
SelectedRow = SlotSelection<2>
*PreviousSlotSelection = Get_Property(CtrlName,'PREVPOS')
*PreviousSelectedRow = PreviousSlotSelection<2>
IF (SlotList<SelectedRow,COL$EPI_MU_WFR_ID> NE '') THEN
*Set_Property(@WINDOW:'.MET_RESULT', 'ENABLED', -1)
*Set_Property(@WINDOW:'.TEST_SLOT', 'ENABLED', -1)
Set_Property(@WINDOW:'.SLOT_FILL', 'CARETPOS', COL$MU_WAFER_THK_RESULT:@FM:SelectedRow)
END ELSE
*Set_Property(@WINDOW:'.MET_RESULT', 'ENABLED', 1)
* Set_Property(@WINDOW:'.TEST_SLOT', 'ENABLED', 1)
* Set_Property(@WINDOW:'.TEST_SLOT', 'DEFPROP', SelectedRow)
* stat = Send_Message(CtrlName, 'COLOR_BY_POS', '', PreviousSelectedRow, GREEN$)
* stat = Send_Message(CtrlName, 'COLOR_BY_POS', '', SelectedRow, YELLOW$)
Handle = Get_Property(CtrlName, 'HANDLE')
CALL sendMessage(Handle, DTM_SELROW$, 0, SelectedRow-1)
END
@ -1089,7 +1052,6 @@ EpiSlotClick:
* * * * * * *
MetSlot = Get_Property(@WINDOW:'.MET_SLOT','DEFPROP')
*TestSlot = Get_Property(@WINDOW:'.TEST_SLOT','DEFPROP')
CtrlName = @WINDOW:'.EPI_SLOT_FILL'
SlotList = Get_Property(CtrlName,'LIST')
@ -1097,20 +1059,10 @@ EpiSlotClick:
SlotSelection = Get_Property(CtrlName,'SELPOS')
SelectedRow = SlotSelection<2>
*PreviousSlotSelection = Get_Property(CtrlName,'PREVPOS')
*PreviousSelectedRow = PreviousSlotSelection<2>
IF SlotList<SelectedRow,COL$EPI_MU_WFR_ID> NE '' THEN
*Set_Property(@WINDOW:'.MET_RESULT', 'ENABLED', -1)
*Set_Property(@WINDOW:'.TEST_SLOT', 'ENABLED', -1)
Set_Property(@WINDOW:'.EPI_SLOT_FILL', 'CARETPOS', COL$EPI_MU_WAFER_THK_RESULT:@FM:SelectedRow)
END ELSE
* Set_Property(@WINDOW:'.MET_RESULT', 'ENABLED', 1)
* Set_Property(@WINDOW:'.TEST_SLOT', 'ENABLED', 1)
* Set_Property(@WINDOW:'.TEST_SLOT', 'DEFPROP', SelectedRow)
* stat = Send_Message(CtrlName, 'COLOR_BY_POS', '', PreviousSelectedRow, GREEN$)
* stat = Send_Message(CtrlName, 'COLOR_BY_POS', '', SelectedRow, YELLOW$)
Handle = Get_Property(CtrlName, 'HANDLE')
CALL sendMessage(Handle, DTM_SELROW$, 0, SelectedRow-1)
END
@ -1179,4 +1131,3 @@ PubSaveClick:
RETURN