updated 100% stratus to auto calculate std dev
This commit is contained in:
committed by
Stieber Daniel (IT FI MES)
parent
b0b127cd87
commit
2dc8a264c2
File diff suppressed because it is too large
Load Diff
File diff suppressed because it is too large
Load Diff
@ -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 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 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 APPCOLORS
|
||||||
$INSERT LSL_USERS_EQU
|
$INSERT LSL_USERS_EQU
|
||||||
@ -162,18 +162,14 @@ Create:
|
|||||||
MetStdMax = MetLineIn<1,COL$MET_STD_MAX>
|
MetStdMax = MetLineIn<1,COL$MET_STD_MAX>
|
||||||
MetStdResult = MetLineIn<1,COL$MET_STD_RESULT>
|
MetStdResult = MetLineIn<1,COL$MET_STD_RESULT>
|
||||||
MetWfrQty = MetLineIn<1,COL$MET_WFR_QTY>
|
MetWfrQty = MetLineIn<1,COL$MET_WFR_QTY>
|
||||||
|
|
||||||
IF MetStdMax = '' THEN
|
IF MetStdMax = '' THEN
|
||||||
IF MetTest = 'ADE' THEN
|
IF MetTest = 'ADE' THEN
|
||||||
IF MetSpecSlot = 'A' OR MetWfrQty = 'A' OR MetWfrQty > 5 THEN
|
IF MetSpecSlot = 'A' OR MetWfrQty = 'A' OR MetWfrQty > 5 THEN
|
||||||
|
|
||||||
* Standard Deviation Required
|
* Standard Deviation Required
|
||||||
|
|
||||||
MetStdMax = ((MetMin + MetMax) / 2) * (0.02)
|
MetStdMax = ((MetMin + MetMax) / 2) * (0.02)
|
||||||
MetStdMax = ICONV(MetStdMax,'MD3')
|
MetStdMax = ICONV(MetStdMax,'MD3')
|
||||||
|
|
||||||
Set_Property(@WINDOW:'.MET_STD_MAX','DEFPROP',OCONV(MetStdMax,'MD3'))
|
Set_Property(@WINDOW:'.MET_STD_MAX','DEFPROP',OCONV(MetStdMax,'MD3'))
|
||||||
|
|
||||||
END
|
END
|
||||||
END ;* End of check for ADE test
|
END ;* End of check for ADE test
|
||||||
END ELSE
|
END ELSE
|
||||||
@ -193,20 +189,11 @@ Create:
|
|||||||
Set_Property(@WINDOW:'.MET_RESULT','DEFPROP',MetResult)
|
Set_Property(@WINDOW:'.MET_RESULT','DEFPROP',MetResult)
|
||||||
Set_Property(@WINDOW:'.MET_STD_RESULT','DEFPROP',MetStdResult)
|
Set_Property(@WINDOW:'.MET_STD_RESULT','DEFPROP',MetStdResult)
|
||||||
|
|
||||||
*IF MetSpecSlot = 'A' THEN
|
Set_Property(@WINDOW:'.MET_STD_RESULT', 'ENABLED', False$)
|
||||||
* 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
|
|
||||||
|
|
||||||
IF MetStdMax = '' THEN
|
IF MetStdMax = '' THEN
|
||||||
Set_Property(@WINDOW:'.MET_STD_RESULT','ENABLED',0)
|
|
||||||
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',GREY$)
|
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',GREY$)
|
||||||
END ELSE
|
END ELSE
|
||||||
Set_Property(@WINDOW:'.MET_STD_RESULT','ENABLED',1)
|
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',GREEN$)
|
||||||
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',WHITE$)
|
|
||||||
END
|
END
|
||||||
|
|
||||||
IF ((MetResult < MetMin) OR (MetResult > MetMax)) then
|
IF ((MetResult < MetMin) OR (MetResult > MetMax)) then
|
||||||
@ -317,13 +304,17 @@ RETURN
|
|||||||
Refresh:
|
Refresh:
|
||||||
********
|
********
|
||||||
|
|
||||||
WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP')
|
WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP')
|
||||||
CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP')
|
CassNo = Get_Property(@WINDOW:'.OUT_CASS_NO','DEFPROP')
|
||||||
TestSlot = Get_Property(@WINDOW:'.TEST_SLOT','DEFPROP')
|
TestSlot = Get_Property(@WINDOW:'.TEST_SLOT','DEFPROP')
|
||||||
MetMin = Get_Property(@WINDOW:'.MET_MIN','DEFPROP',MetMin)
|
MetMin = Get_Property(@WINDOW:'.MET_MIN','DEFPROP',MetMin)
|
||||||
MetMax = Get_Property(@WINDOW:'.MET_MAX','DEFPROP',MetMax)
|
MetMax = Get_Property(@WINDOW:'.MET_MAX','DEFPROP',MetMax)
|
||||||
MetResult = Get_Property(@WINDOW:'.MET_MAX','DEFPROP',MetResult)
|
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_WAFER_THK_RANGE_REQ', 1)
|
||||||
Set_Property(@WINDOW, '@ADE_STD_RESULT_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_RANGE_REQ', 1)
|
||||||
@ -341,6 +332,33 @@ Refresh:
|
|||||||
SlotCtrl = @WINDOW:'.SLOT_FILL'
|
SlotCtrl = @WINDOW:'.SLOT_FILL'
|
||||||
SlotList = Get_Property(SlotCtrl,'LIST')
|
SlotList = Get_Property(SlotCtrl,'LIST')
|
||||||
CtrlCols = Get_Property(SlotCtrl,'COLUMN')
|
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 '')
|
SlotCnt = COUNT(SlotList,@FM) + (SlotList NE '')
|
||||||
ColCnt = COUNT(CtrlCols,@SVM) + (CtrlCols NE '')
|
ColCnt = COUNT(CtrlCols,@SVM) + (CtrlCols NE '')
|
||||||
@ -428,10 +446,9 @@ Refresh:
|
|||||||
IF FormMUWaferThkResult NE '' AND ((FormMUWaferThkResult < MetMin) OR (FormMUWaferThkResult > MetMax)) then
|
IF FormMUWaferThkResult NE '' AND ((FormMUWaferThkResult < MetMin) OR (FormMUWaferThkResult > MetMax)) then
|
||||||
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, RED$)
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, RED$)
|
||||||
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
|
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
|
||||||
|
end else
|
||||||
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, WHITE$)
|
||||||
end
|
end
|
||||||
/*end else
|
|
||||||
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, GREEN$)
|
|
||||||
end */
|
|
||||||
END
|
END
|
||||||
END
|
END
|
||||||
END
|
END
|
||||||
@ -446,6 +463,33 @@ Refresh:
|
|||||||
SlotList = Get_Property(SlotCtrl,'LIST')
|
SlotList = Get_Property(SlotCtrl,'LIST')
|
||||||
CtrlCols = Get_Property(SlotCtrl,'COLUMN')
|
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 '')
|
SlotCnt = COUNT(SlotList,@FM) + (SlotList NE '')
|
||||||
ColCnt = COUNT(CtrlCols,@SVM) + (CtrlCols NE '')
|
ColCnt = COUNT(CtrlCols,@SVM) + (CtrlCols NE '')
|
||||||
|
|
||||||
@ -533,10 +577,9 @@ Refresh:
|
|||||||
IF FormMUWaferThkResult NE '' AND ((FormMUWaferThkResult < MetMin) OR (FormMUWaferThkResult > MetMax)) then
|
IF FormMUWaferThkResult NE '' AND ((FormMUWaferThkResult < MetMin) OR (FormMUWaferThkResult > MetMax)) then
|
||||||
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, RED$)
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, RED$)
|
||||||
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
|
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
|
||||||
|
end else
|
||||||
|
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, WHITE$)
|
||||||
end
|
end
|
||||||
/*end else
|
|
||||||
stat = Send_Message(SlotCtrl, 'COLOR_BY_POS', '', Line, GREEN$)
|
|
||||||
end */
|
|
||||||
END
|
END
|
||||||
END
|
END
|
||||||
END
|
END
|
||||||
@ -665,23 +708,15 @@ SaveThickness:
|
|||||||
WOMatQARec<WO_MAT_QA_RESULT$,vPos> = MetResult
|
WOMatQARec<WO_MAT_QA_RESULT$,vPos> = MetResult
|
||||||
WOMatQARec<WO_MAT_QA_STD_MAX$,vPos> = ICONV(StdMax,'MD3')
|
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_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
|
end
|
||||||
|
|
||||||
Until Found EQ True$
|
Until Found EQ True$
|
||||||
Next ProfStep
|
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$)
|
Database_Services('WriteDataRow', 'WO_MAT_QA', WOMatQAKey, WOMatQARec, True$, False$, False$)
|
||||||
If Error_Services('HasError') then
|
If Error_Services('HasError') then
|
||||||
ErrMsg(Error_Services('GetMessage'))
|
ErrMsg(Error_Services('GetMessage'))
|
||||||
end
|
end
|
||||||
* IF Get_Status(errCode) THEN
|
|
||||||
* ErrMsg(errCode)
|
|
||||||
* END
|
|
||||||
|
|
||||||
RETURN
|
RETURN
|
||||||
|
|
||||||
@ -690,71 +725,37 @@ RETURN
|
|||||||
ResultLF:
|
ResultLF:
|
||||||
* * * * * * *
|
* * * * * * *
|
||||||
|
|
||||||
MetLine = Get_Property(@WINDOW,'@MET_LINE_IN')
|
MetLine = Get_Property(@WINDOW,'@MET_LINE_IN')
|
||||||
MetResult = TRIM(Get_Property(@WINDOW:'.MET_RESULT','DEFPROP'))
|
MetResult = Trim(Get_Property(@WINDOW:'.MET_RESULT','DEFPROP'))
|
||||||
MetStdEnabled = Get_Property(@WINDOW:'.MET_STD_RESULT','ENABLED')
|
MetStdResult = Get_Property(@WINDOW:'.MET_STD_RESULT','DEFPROP')
|
||||||
|
MetStdMax = Get_Property(@WINDOW:'.MET_STD_MAX','DEFPROP')
|
||||||
IF MetStdEnabled THEN
|
|
||||||
MetStdResult = Get_Property(@WINDOW:'.MET_STD_RESULT','DEFPROP')
|
|
||||||
MetStdMax = Get_Property(@WINDOW:'.MET_STD_MAX','DEFPROP')
|
|
||||||
END ELSE
|
|
||||||
MetStdResult = ''
|
|
||||||
END
|
|
||||||
|
|
||||||
IF MetResult NE '' THEN
|
IF MetResult NE '' THEN
|
||||||
IF MetStdEnabled = 1 THEN
|
Set_Property(@WINDOW, '@MET_RESULT_REQ', 1)
|
||||||
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
|
|
||||||
|
|
||||||
END ELSE
|
END ELSE
|
||||||
*Set_Property(@WINDOW:'.SIGN','ENABLED',0)
|
|
||||||
Set_Property(@WINDOW, '@MET_RESULT_REQ', 0)
|
Set_Property(@WINDOW, '@MET_RESULT_REQ', 0)
|
||||||
END
|
END
|
||||||
|
|
||||||
IF (MetResult NE '') THEN
|
IF (MetResult NE '') THEN
|
||||||
|
If ( (MetResult < MetLine<1,COL$MET_MIN>) OR (MetResult > MetLine<1,COL$MET_MAX>) ) then
|
||||||
BEGIN CASE
|
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
|
||||||
CASE (MetResult < MetLine<1,COL$MET_MIN>) OR (MetResult > MetLine<1,COL$MET_MAX>)
|
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',RED$)
|
||||||
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 0)
|
end else
|
||||||
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',RED$)
|
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 1)
|
||||||
CASE 1
|
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',GREEN$)
|
||||||
Set_Property(@WINDOW, '@ADE_WAFER_THK_RANGE_REQ', 1)
|
end
|
||||||
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',GREEN$)
|
|
||||||
END CASE
|
|
||||||
|
|
||||||
END ELSE
|
END ELSE
|
||||||
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',WHITE$)
|
Set_Property(@WINDOW:'.MET_RESULT','BACKCOLOR',WHITE$)
|
||||||
*Set_Property(@WINDOW:'.SIGN','ENABLED',0)
|
|
||||||
Set_Property(@WINDOW, '@MET_RESULT_REQ', 0)
|
Set_Property(@WINDOW, '@MET_RESULT_REQ', 0)
|
||||||
END
|
END
|
||||||
|
|
||||||
|
IF (MetStdResult NE '') THEN
|
||||||
IF (MetStdEnabled) THEN
|
If (MetStdResult > MetStdMax) then
|
||||||
IF (MetStdResult NE '') THEN
|
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',RED$)
|
||||||
BEGIN CASE
|
end else
|
||||||
CASE MetStdResult > MetStdMax
|
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',GREEN$)
|
||||||
Set_Property(@WINDOW:'.MET_STD_RESULT','BACKCOLOR',RED$)
|
END
|
||||||
Set_Property(@WINDOW, '@ADE_STD_RESULT_REQ', 0)
|
END
|
||||||
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
|
|
||||||
|
|
||||||
RETURN
|
RETURN
|
||||||
|
|
||||||
@ -882,12 +883,6 @@ Sign:
|
|||||||
ErrMsg("Error: ADE Wafer Thk is OOS!")
|
ErrMsg("Error: ADE Wafer Thk is OOS!")
|
||||||
END
|
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')
|
MetResultReq = Get_Property(@WINDOW, '@MET_RESULT_REQ')
|
||||||
IF (MetResultReq = 0) THEN
|
IF (MetResultReq = 0) THEN
|
||||||
SignatureReady = False$
|
SignatureReady = False$
|
||||||
@ -1024,27 +1019,6 @@ RETURN
|
|||||||
Exit:
|
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,'')
|
End_Window(@WINDOW,'')
|
||||||
|
|
||||||
RETURN
|
RETURN
|
||||||
@ -1055,7 +1029,6 @@ SlotClick:
|
|||||||
* * * * * * *
|
* * * * * * *
|
||||||
|
|
||||||
MetSlot = Get_Property(@WINDOW:'.MET_SLOT','DEFPROP')
|
MetSlot = Get_Property(@WINDOW:'.MET_SLOT','DEFPROP')
|
||||||
*TestSlot = Get_Property(@WINDOW:'.TEST_SLOT','DEFPROP')
|
|
||||||
|
|
||||||
CtrlName = @WINDOW:'.SLOT_FILL'
|
CtrlName = @WINDOW:'.SLOT_FILL'
|
||||||
SlotList = Get_Property(CtrlName,'LIST')
|
SlotList = Get_Property(CtrlName,'LIST')
|
||||||
@ -1063,20 +1036,10 @@ SlotClick:
|
|||||||
SlotSelection = Get_Property(CtrlName,'SELPOS')
|
SlotSelection = Get_Property(CtrlName,'SELPOS')
|
||||||
SelectedRow = SlotSelection<2>
|
SelectedRow = SlotSelection<2>
|
||||||
|
|
||||||
*PreviousSlotSelection = Get_Property(CtrlName,'PREVPOS')
|
|
||||||
*PreviousSelectedRow = PreviousSlotSelection<2>
|
|
||||||
|
|
||||||
IF (SlotList<SelectedRow,COL$EPI_MU_WFR_ID> NE '') THEN
|
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)
|
Set_Property(@WINDOW:'.SLOT_FILL', 'CARETPOS', COL$MU_WAFER_THK_RESULT:@FM:SelectedRow)
|
||||||
|
|
||||||
END ELSE
|
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')
|
Handle = Get_Property(CtrlName, 'HANDLE')
|
||||||
CALL sendMessage(Handle, DTM_SELROW$, 0, SelectedRow-1)
|
CALL sendMessage(Handle, DTM_SELROW$, 0, SelectedRow-1)
|
||||||
END
|
END
|
||||||
@ -1089,7 +1052,6 @@ EpiSlotClick:
|
|||||||
* * * * * * *
|
* * * * * * *
|
||||||
|
|
||||||
MetSlot = Get_Property(@WINDOW:'.MET_SLOT','DEFPROP')
|
MetSlot = Get_Property(@WINDOW:'.MET_SLOT','DEFPROP')
|
||||||
*TestSlot = Get_Property(@WINDOW:'.TEST_SLOT','DEFPROP')
|
|
||||||
|
|
||||||
CtrlName = @WINDOW:'.EPI_SLOT_FILL'
|
CtrlName = @WINDOW:'.EPI_SLOT_FILL'
|
||||||
SlotList = Get_Property(CtrlName,'LIST')
|
SlotList = Get_Property(CtrlName,'LIST')
|
||||||
@ -1097,20 +1059,10 @@ EpiSlotClick:
|
|||||||
SlotSelection = Get_Property(CtrlName,'SELPOS')
|
SlotSelection = Get_Property(CtrlName,'SELPOS')
|
||||||
SelectedRow = SlotSelection<2>
|
SelectedRow = SlotSelection<2>
|
||||||
|
|
||||||
*PreviousSlotSelection = Get_Property(CtrlName,'PREVPOS')
|
|
||||||
*PreviousSelectedRow = PreviousSlotSelection<2>
|
|
||||||
|
|
||||||
IF SlotList<SelectedRow,COL$EPI_MU_WFR_ID> NE '' THEN
|
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)
|
Set_Property(@WINDOW:'.EPI_SLOT_FILL', 'CARETPOS', COL$EPI_MU_WAFER_THK_RESULT:@FM:SelectedRow)
|
||||||
|
|
||||||
END ELSE
|
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')
|
Handle = Get_Property(CtrlName, 'HANDLE')
|
||||||
CALL sendMessage(Handle, DTM_SELROW$, 0, SelectedRow-1)
|
CALL sendMessage(Handle, DTM_SELROW$, 0, SelectedRow-1)
|
||||||
END
|
END
|
||||||
@ -1179,4 +1131,3 @@ PubSaveClick:
|
|||||||
|
|
||||||
RETURN
|
RETURN
|
||||||
|
|
||||||
|
|
||||||
|
@ -230,21 +230,21 @@ Event PUB_OK.CLICK()
|
|||||||
Valid = WritePrivateProfileString(lpszSection, lpszEntry, lpszValue, lpszFileName)
|
Valid = WritePrivateProfileString(lpszSection, lpszEntry, lpszValue, lpszFileName)
|
||||||
End_Dialog(@Window, AccessLevel)
|
End_Dialog(@Window, AccessLevel)
|
||||||
end else
|
end else
|
||||||
Set_Property(@Window : '.EDL_USERNAME', 'FOCUS', True$)
|
Set_Property(@Window : '.EDL_PASSWORD', 'FOCUS', True$)
|
||||||
Set_Property(@Window : '.EDL_USERNAME', 'SELECTION', 1 : @FM : 999)
|
Set_Property(@Window : '.EDL_PASSWORD', 'SELECTION', 1 : @FM : 999)
|
||||||
Message = 'Unable to validate username. Please re-enter.'
|
Message = 'Unable to validate username. Please re-enter.'
|
||||||
Form_Services('DisplayControlMessage', Message, 'MES Logon', @Window : '.EDL_USERNAME', 'VALIDATION', 'RGB(229,20,0)')
|
Form_Services('DisplayControlMessage', Message, 'MES Logon', @Window : '.EDL_USERNAME', 'VALIDATION', 'RGB(229,20,0)')
|
||||||
end
|
end
|
||||||
end else
|
end else
|
||||||
Set_Property(@Window : '.EDL_USERNAME', 'FOCUS', True$)
|
Set_Property(@Window : '.EDL_PASSWORD', 'FOCUS', True$)
|
||||||
Set_Property(@Window : '.EDL_USERNAME', 'SELECTION', 1 : @FM : 999)
|
Set_Property(@Window : '.EDL_PASSWORD', 'SELECTION', 1 : @FM : 999)
|
||||||
Message = Error_Services('GetMessage')
|
Message = Error_Services('GetMessage')
|
||||||
If Message EQ '' then Message = 'Unable to validate username. Please re-enter.'
|
If Message EQ '' then Message = 'Unable to validate username. Please re-enter.'
|
||||||
Form_Services('DisplayControlMessage', Message, 'MES Logon', @Window : '.EDL_USERNAME', 'VALIDATION', 'RGB(229,20,0)')
|
Form_Services('DisplayControlMessage', Message, 'MES Logon', @Window : '.EDL_USERNAME', 'VALIDATION', 'RGB(229,20,0)')
|
||||||
end
|
end
|
||||||
end else
|
end else
|
||||||
Set_Property(@Window : '.EDL_USERNAME', 'FOCUS', True$)
|
Set_Property(@Window : '.EDL_PASSWORD', 'FOCUS', True$)
|
||||||
Set_Property(@Window : '.EDL_USERNAME', 'SELECTION', 1 : @FM : 999)
|
Set_Property(@Window : '.EDL_PASSWORD', 'SELECTION', 1 : @FM : 999)
|
||||||
Message = Error_Services('GetMessage')
|
Message = Error_Services('GetMessage')
|
||||||
If Message EQ '' then Message = 'System unavailable.'
|
If Message EQ '' then Message = 'System unavailable.'
|
||||||
Form_Services('DisplayControlMessage', Message, 'MES Logon', @Window : '.EDL_USERNAME', 'VALIDATION', 'RGB(229,20,0)')
|
Form_Services('DisplayControlMessage', Message, 'MES Logon', @Window : '.EDL_USERNAME', 'VALIDATION', 'RGB(229,20,0)')
|
||||||
@ -265,6 +265,3 @@ Setup_OLE_Controls:
|
|||||||
|
|
||||||
return
|
return
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
@ -95,7 +95,7 @@ Declare subroutine Tool_Services, Mona_Services
|
|||||||
Declare function SRP_Sort_Array, Metrology_Services, obj_RDS_Test, obj_Test_Point_Map, Database_Services, UCase
|
Declare function SRP_Sort_Array, Metrology_Services, obj_RDS_Test, obj_Test_Point_Map, Database_Services, UCase
|
||||||
Declare function Work_Order_Services, SRP_JSON, Logging_Services, Environment_Services, SRP_Trim, Min, Max
|
Declare function Work_Order_Services, SRP_JSON, Logging_Services, Environment_Services, SRP_Trim, Min, Max
|
||||||
Declare function QA_Services, SRP_Join_Arrays, Get_Status, Obj_Clean_Insp, Datetime, SRP_Datetime
|
Declare function QA_Services, SRP_Join_Arrays, Get_Status, Obj_Clean_Insp, Datetime, SRP_Datetime
|
||||||
Declare function Httpclient_Services, PM_Services, Signature_Services
|
Declare function Httpclient_Services, PM_Services, Signature_Services, SRP_Array, Math_Services
|
||||||
|
|
||||||
LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\Metrology'
|
LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\Metrology'
|
||||||
LogDate = Oconv(Date(), 'D4/')
|
LogDate = Oconv(Date(), 'D4/')
|
||||||
@ -494,16 +494,32 @@ Service ImportStratusData(RunData)
|
|||||||
Case Otherwise$
|
Case Otherwise$
|
||||||
Error_Services('Add', 'Unrecognized cassette ID ':Cassette:'.')
|
Error_Services('Add', 'Unrecognized cassette ID ':Cassette:'.')
|
||||||
End Case
|
End Case
|
||||||
// Update WO_MAT record
|
|
||||||
If Error_Services('NoError') then
|
If Error_Services('NoError') then
|
||||||
WOMatKey = WorkOrderNo : '*' : CassNo
|
|
||||||
WOMatRec = Database_Services('ReadDataRow', 'WO_MAT', WOMatKey)
|
// Update WO_MAT record
|
||||||
|
StdDev = ''
|
||||||
|
WOMatKey = WorkOrderNo : '*' : CassNo
|
||||||
|
WOMatRec = Database_Services('ReadDataRow', 'WO_MAT', WOMatKey)
|
||||||
If Error_Services('NoError') then
|
If Error_Services('NoError') then
|
||||||
|
NumVals = 0
|
||||||
For each Position in Positions using @VM setting vPos
|
For each Position in Positions using @VM setting vPos
|
||||||
If Position NE '' then
|
If Position NE '' then
|
||||||
WOMatRec<WO_MAT_MU_WAFER_THK_RESULT$, Position> = DataPoints<0, vPos>
|
WOMatRec<WO_MAT_MU_WAFER_THK_RESULT$, Position> = DataPoints<0, vPos>
|
||||||
|
NumVals += 1
|
||||||
end
|
end
|
||||||
Next Position
|
Next Position
|
||||||
|
If NumVals EQ 25 then
|
||||||
|
StdDevType = 'POPULATION'
|
||||||
|
end else
|
||||||
|
StdDevType = 'SAMPLE'
|
||||||
|
end
|
||||||
|
If NumVals GT 0 then
|
||||||
|
Vals = WOMatRec<WO_MAT_MU_WAFER_THK_RESULT$>
|
||||||
|
Vals = SRP_Array('Clean', Vals, 'Trim', @VM)
|
||||||
|
StdDev = Math_Services('GetStdDev', Vals, StdDevType)
|
||||||
|
StdDev = OConv(IConv(StdDev, 'MD3'), 'MD3')
|
||||||
|
end
|
||||||
Database_Services('WriteDataRow', 'WO_MAT', WOMatKey, WOMatRec, True$, False$, True$)
|
Database_Services('WriteDataRow', 'WO_MAT', WOMatKey, WOMatRec, True$, False$, True$)
|
||||||
If Error_Services('HasError') then
|
If Error_Services('HasError') then
|
||||||
Metrology_Services('LogResults', RDSNo@, Machine, 'UID001', Service : ' : ' : Error_Services('GetMessage'))
|
Metrology_Services('LogResults', RDSNo@, Machine, 'UID001', Service : ' : ' : Error_Services('GetMessage'))
|
||||||
@ -511,17 +527,34 @@ Service ImportStratusData(RunData)
|
|||||||
end else
|
end else
|
||||||
Metrology_Services('LogResults', RDSNo@, Machine, 'UID001', Service : ' : ' : Error_Services('GetMessage'))
|
Metrology_Services('LogResults', RDSNo@, Machine, 'UID001', Service : ' : ' : Error_Services('GetMessage'))
|
||||||
end
|
end
|
||||||
//Update the WM_OUT record for EpiPro
|
// Update the WM_OUT record for EpiPro
|
||||||
if IsEpiPro then
|
If IsEpiPro then
|
||||||
WMORec = Database_Services('ReadDataRow', 'WM_OUT', RDSNo@)
|
NumVals = 0
|
||||||
for each wafer in Positions using @VM setting dPos
|
WMORec = Database_Services('ReadDataRow', 'WM_OUT', RDSNo@)
|
||||||
WMORec<WM_OUT_MU_WAFER_THK_RESULT$, wafer> = DataPoints<0, dPos>
|
For each Wafer in Positions using @VM setting dPos
|
||||||
Next wafer
|
If Wafer NE '' then
|
||||||
|
WMORec<WM_OUT_MU_WAFER_THK_RESULT$, Wafer> = DataPoints<0, dPos>
|
||||||
|
NumVals += 1
|
||||||
|
end
|
||||||
|
Next Wafer
|
||||||
|
If NumVals EQ 25 then
|
||||||
|
StdDevType = 'POPULATION'
|
||||||
|
end else
|
||||||
|
StdDevType = 'SAMPLE'
|
||||||
|
end
|
||||||
|
If NumVals GT 0 then
|
||||||
|
Vals = WMORec<WM_OUT_MU_WAFER_THK_RESULT$>
|
||||||
|
Vals = SRP_Array('Clean', Vals, 'Trim', @VM)
|
||||||
|
StdDev = Math_Services('GetStdDev', Vals, StdDevType)
|
||||||
|
StdDev = OConv(IConv(StdDev, 'MD3'), 'MD3')
|
||||||
|
end
|
||||||
Database_Services('WriteDataRow', 'WM_OUT', RDSNo@, WMORec, True$, False$, True$)
|
Database_Services('WriteDataRow', 'WM_OUT', RDSNo@, WMORec, True$, False$, True$)
|
||||||
end
|
end
|
||||||
|
|
||||||
// Update WO_MAT_QA record
|
// Update WO_MAT_QA record
|
||||||
WOMatQAID = WorkOrderNo : '*' : CassNo
|
StdDevMax = ''
|
||||||
WOMatQARec = Database_Services('ReadDataRow', 'WO_MAT_QA', WOMatQAID)
|
WOMatQAID = WorkOrderNo : '*' : CassNo
|
||||||
|
WOMatQARec = Database_Services('ReadDataRow', 'WO_MAT_QA', WOMatQAID)
|
||||||
If Error_Services('NoError') then
|
If Error_Services('NoError') then
|
||||||
SpecRecipes = WOMatQARec<WO_MAT_QA_RECIPE$>
|
SpecRecipes = WOMatQARec<WO_MAT_QA_RECIPE$>
|
||||||
ProfSteps = ''
|
ProfSteps = ''
|
||||||
@ -529,11 +562,20 @@ Service ImportStratusData(RunData)
|
|||||||
ProfileCnt = DCount(WOMatQARec<WO_MAT_QA_PROFILE$>, @VM)
|
ProfileCnt = DCount(WOMatQARec<WO_MAT_QA_PROFILE$>, @VM)
|
||||||
Stages = WOMatQARec<WO_MAT_QA_STAGE$>
|
Stages = WOMatQARec<WO_MAT_QA_STAGE$>
|
||||||
Slots = WOMatQARec<WO_MAT_QA_SLOT$>
|
Slots = WOMatQARec<WO_MAT_QA_SLOT$>
|
||||||
|
SpecQty = WOMatQARec<WO_MAT_QA_WFR_QTY$>
|
||||||
pPos = ''
|
pPos = ''
|
||||||
For each Profile in Profiles using @VM setting pPos
|
For each Profile in Profiles using @VM setting pPos
|
||||||
Stage = Stages<0, pPos>
|
Stage = Stages<0, pPos>
|
||||||
If ( (Profile EQ '1ADE') and ( (Stage EQ 'QA') or (Stage EQ 'MO_QA') ) ) then
|
If ( (Profile EQ '1ADE') and ( (Stage EQ 'QA') or (Stage EQ 'MO_QA') ) ) then
|
||||||
Slot = Slots<0, pPos>
|
Slot = Slots<0, pPos>
|
||||||
|
If ( (Slot EQ 'A') or (SpecQty EQ 'A') or (SpecQty GT 5) ) then
|
||||||
|
MetMin = WOMatQARec<WO_MAT_QA_MIN$, pPos>
|
||||||
|
MetMax = WOMatQARec<WO_MAT_QA_MAX$, pPos>
|
||||||
|
StdDevMax = ((MetMin + MetMax) / 2) * (0.02)
|
||||||
|
StdDevMax = IConv(StdDevMax,'MD3')
|
||||||
|
WOMatQARec<WO_MAT_QA_STD_RESULT$, pPos> = StdDev
|
||||||
|
WOMatQARec<WO_MAT_QA_STD_MAX$, pPos> = StdDevMax
|
||||||
|
end
|
||||||
Begin Case
|
Begin Case
|
||||||
Case Slot EQ '1'
|
Case Slot EQ '1'
|
||||||
WaferIndex = 1
|
WaferIndex = 1
|
||||||
@ -544,10 +586,6 @@ Service ImportStratusData(RunData)
|
|||||||
Case Otherwise$
|
Case Otherwise$
|
||||||
WaferIndex = Slot
|
WaferIndex = Slot
|
||||||
End Case
|
End Case
|
||||||
* If Slot EQ '1' then WaferIndex = 1
|
|
||||||
* If Slot EQ 'L' then WaferIndex = 25
|
|
||||||
* //Running into Slot "A" in some PSN's and QA records. Translating slot "A" to slot 1
|
|
||||||
* If Slot EQ 'A' then WaferIndex = 1
|
|
||||||
Locate WaferIndex in Positions using @VM setting dPos then
|
Locate WaferIndex in Positions using @VM setting dPos then
|
||||||
WOMatQARec<WO_MAT_QA_RESULT$, pPos> = DataPoints<0, dPos>
|
WOMatQARec<WO_MAT_QA_RESULT$, pPos> = DataPoints<0, dPos>
|
||||||
end
|
end
|
||||||
@ -561,10 +599,11 @@ Service ImportStratusData(RunData)
|
|||||||
end
|
end
|
||||||
end else
|
end else
|
||||||
Metrology_Services('LogResults', RDSNo@, Machine, 'UID001', Service : ' : ' : Error_Services('GetMessage'))
|
Metrology_Services('LogResults', RDSNo@, Machine, 'UID001', Service : ' : ' : Error_Services('GetMessage'))
|
||||||
end
|
end
|
||||||
end else
|
end else
|
||||||
Metrology_Services('LogResults', RDSNo@, Machine, 'UID001', Service : ' : ' : Error_Services('GetMessage'))
|
Metrology_Services('LogResults', RDSNo@, Machine, 'UID001', Service : ' : ' : Error_Services('GetMessage'))
|
||||||
end
|
end
|
||||||
|
|
||||||
end service
|
end service
|
||||||
|
|
||||||
|
|
||||||
@ -2819,20 +2858,3 @@ LoadRunDataToDatabase:
|
|||||||
|
|
||||||
return
|
return
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
@ -300,6 +300,3 @@ SetDelay:
|
|||||||
|
|
||||||
return
|
return
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
@ -280,6 +280,17 @@ FOR WOStepNo = 1 TO StepCnt
|
|||||||
WOMatQARec<WO_MAT_QA_SHIP_DOC$,MetLine> = QAMetData<COL$QA_MET_SHIP_DOC,StageNo> ;* StageRec<PRS_STAGE_MET_SHIP_DOC$,StageNo>
|
WOMatQARec<WO_MAT_QA_SHIP_DOC$,MetLine> = QAMetData<COL$QA_MET_SHIP_DOC,StageNo> ;* StageRec<PRS_STAGE_MET_SHIP_DOC$,StageNo>
|
||||||
WOMatQARec<WO_MAT_QA_PHASE_MIN$,MetLine> = QAMetData<COL$QA_MET_PHASE_MIN,StageNo>
|
WOMatQARec<WO_MAT_QA_PHASE_MIN$,MetLine> = QAMetData<COL$QA_MET_PHASE_MIN,StageNo>
|
||||||
|
|
||||||
|
MetTest = QAMetData<COL$QA_MET_TEST,StageNo>
|
||||||
|
IF MetTest = 'ADE' THEN
|
||||||
|
MetSpecSlot = QAMetData<COL$QA_MET_SLOT,StageNo>
|
||||||
|
MetWfrQty = QAMetData<COL$QA_MET_WFR_QTY,StageNo>
|
||||||
|
IF ( (MetSpecSlot = 'A') OR (MetWfrQty = 'A') OR (MetWfrQty > 5) ) THEN
|
||||||
|
* Standard Deviation Required
|
||||||
|
MetStdMax = ((MetMin + MetMax) / 2) * (0.02)
|
||||||
|
MetStdMax = ICONV(MetStdMax,'MD3')
|
||||||
|
WOMatQARec<WO_MAT_QA_STD_MAX$> = MetStdMax
|
||||||
|
END
|
||||||
|
END ;* End of check for ADE test
|
||||||
|
|
||||||
* Retrieve any existing results from the WO_MAT record
|
* Retrieve any existing results from the WO_MAT record
|
||||||
|
|
||||||
@ -600,6 +611,7 @@ NEXT I
|
|||||||
otParms = 'WO_MAT_QA':@RM:WONo:'*':CassNo
|
otParms = 'WO_MAT_QA':@RM:WONo:'*':CassNo
|
||||||
WOMatQARec = obj_Tables('ReadRec',otParms)
|
WOMatQARec = obj_Tables('ReadRec',otParms)
|
||||||
|
|
||||||
|
errCode = ''
|
||||||
IF Get_Status(errCode) THEN
|
IF Get_Status(errCode) THEN
|
||||||
RETURN
|
RETURN
|
||||||
END
|
END
|
||||||
|
@ -38,9 +38,6 @@ Declare function Get_Property, RDS_Services, EpiPro_Services, DateTime, Signa
|
|||||||
Declare subroutine Scan_Services, Memory_Services, Database_Services, SRP_JSON, Security_Services, obj_Notes
|
Declare subroutine Scan_Services, Memory_Services, Database_Services, SRP_JSON, Security_Services, obj_Notes
|
||||||
Declare subroutine obj_WO_Mat_Log, obj_WO_Mat, Set_Status, SAP_Services, Rds_Services, Wm_Out_Services, Hold_Services
|
Declare subroutine obj_WO_Mat_Log, obj_WO_Mat, Set_Status, SAP_Services, Rds_Services, Wm_Out_Services, Hold_Services
|
||||||
|
|
||||||
//TODO - flag used during cutover, delete from APP_INFO and removed commented lines reference Use2DBarcode
|
|
||||||
*Use2DBarcode = Database_Services('ReadDataRow', 'APP_INFO', 'USE_PACKAGING_2D')
|
|
||||||
|
|
||||||
GoToService else
|
GoToService else
|
||||||
Error_Services('Add', Service : ' is not a valid service request within the ' : ServiceModule : ' module.')
|
Error_Services('Add', Service : ' is not a valid service request within the ' : ServiceModule : ' module.')
|
||||||
end
|
end
|
||||||
@ -105,8 +102,6 @@ Service CompletePackaging(CassetteID, OperatorID, BaggerIdentifier)
|
|||||||
|
|
||||||
InvDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
|
InvDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
|
||||||
Set_Status(0)
|
Set_Status(0)
|
||||||
* aiParms = 'WO_MAT':@RM:WONo:@RM:CassNo:@RM:WhCd:'*':LocCd:@RM:Action:@RM:InvDTM:@RM:UserID:@RM:Tag:@RM:ToolID
|
|
||||||
* obj_WO_Mat('AddInvTrans', aiParms)
|
|
||||||
|
|
||||||
LogDate = OCONV( Date(), 'D2/' )
|
LogDate = OCONV( Date(), 'D2/' )
|
||||||
LogTime = OCONV( Time(), 'MTS' )
|
LogTime = OCONV( Time(), 'MTS' )
|
||||||
@ -131,11 +126,6 @@ Service CompletePackaging(CassetteID, OperatorID, BaggerIdentifier)
|
|||||||
WOMLParms := ToolID
|
WOMLParms := ToolID
|
||||||
|
|
||||||
obj_WO_Mat_Log('Create',WOMLParms)
|
obj_WO_Mat_Log('Create',WOMLParms)
|
||||||
* errCode = ''
|
|
||||||
* IF Get_Status(errCode) THEN
|
|
||||||
* ErrorMsg = 'Error calling obj_WO_Mat_Log("Create"). Error code: ':errCode
|
|
||||||
* Error_Services('Add', ErrorMsg)
|
|
||||||
* end
|
|
||||||
errCode = ''
|
errCode = ''
|
||||||
IF Get_Status(errCode) THEN
|
IF Get_Status(errCode) THEN
|
||||||
swap @SVM with CRLF$ in errCode
|
swap @SVM with CRLF$ in errCode
|
||||||
@ -148,14 +138,6 @@ Service CompletePackaging(CassetteID, OperatorID, BaggerIdentifier)
|
|||||||
// Add CassComp transaction to SAP queue
|
// Add CassComp transaction to SAP queue
|
||||||
SAPBatchNo = Xlate('WO_MAT', WOMatKey, 'SAP_BATCH_NO', 'X')
|
SAPBatchNo = Xlate('WO_MAT', WOMatKey, 'SAP_BATCH_NO', 'X')
|
||||||
If SAPBatchNo EQ '' then SAP_Services('AddCassCompTransaction', WOMatKey)
|
If SAPBatchNo EQ '' then SAP_Services('AddCassCompTransaction', WOMatKey)
|
||||||
* Begin Case
|
|
||||||
* Case CommentEntity = 'RDS'
|
|
||||||
* CommentText = 'Packaging completed for RDS ' :CassetteID: ' by user ' : OperatorID
|
|
||||||
* Rds_Services('AddComment', CassetteID, CommentText, OperatorID)
|
|
||||||
* Case CommentEntity = 'WM_OUT'
|
|
||||||
* CommentText = 'Packaging completed for WM_OUT ' :CassetteID: ' by user ' : OperatorID
|
|
||||||
* Wm_Out_Services('AddComment', CassetteID, CommentText, OperatorID)
|
|
||||||
* End Case
|
|
||||||
end
|
end
|
||||||
end
|
end
|
||||||
|
|
||||||
@ -255,7 +237,6 @@ Service ProcessScanData(ScanData, ScanType = SCAN_TYPES, Param1, Param2, Param3)
|
|||||||
CtrlEntID = False$ ;* Control checked/unchecked
|
CtrlEntID = False$ ;* Control checked/unchecked
|
||||||
OriginFlag = 'P' ;* Flag to indicate a hold initiated from the packagaing form
|
OriginFlag = 'P' ;* Flag to indicate a hold initiated from the packagaing form
|
||||||
Parms = WOMatKey:@RM:HoldEntity:@RM:HoldEntityID:@RM:CtrlEntID:@RM:OriginFlag:@RM:OperatorID
|
Parms = WOMatKey:@RM:HoldEntity:@RM:HoldEntityID:@RM:CtrlEntID:@RM:OriginFlag:@RM:OperatorID
|
||||||
//obj_WO_Mat('ToggleHold', Parms)
|
|
||||||
Hold_Services('ToggleHold', WOMatKey, HoldEntity, HoldEntityID, CtrlEntID, OriginFlag, '', OperatorID)
|
Hold_Services('ToggleHold', WOMatKey, HoldEntity, HoldEntityID, CtrlEntID, OriginFlag, '', OperatorID)
|
||||||
|
|
||||||
// Write fail packaging record in material log for first cassette ID
|
// Write fail packaging record in material log for first cassette ID
|
||||||
@ -365,22 +346,17 @@ Service ProcessScanData(ScanData, ScanType = SCAN_TYPES, Param1, Param2, Param3)
|
|||||||
// Assume this is intended to be a Cassette ID scan (either WMO or RDS). Only if this is a
|
// Assume this is intended to be a Cassette ID scan (either WMO or RDS). Only if this is a
|
||||||
// non-existent carrier will the scan data be considered invalid.
|
// non-existent carrier will the scan data be considered invalid.
|
||||||
|
|
||||||
//if using 2D, CassetteId is buried in barcode
|
cnt = DCount(ScanData, '|')
|
||||||
*If Use2DBarcode then
|
if cnt NE 8 then
|
||||||
cnt = DCount(ScanData, '|')
|
CassetteID = 0
|
||||||
if cnt NE 8 then
|
Error_Services('Add', 'Invalid Lot Label Scan.')
|
||||||
CassetteID = 0
|
return
|
||||||
Error_Services('Add', 'Invalid Lot Label Scan.')
|
end else
|
||||||
return
|
//RDS should be 3rd position
|
||||||
end else
|
CassetteID = Field(ScanData, '|', 3)
|
||||||
//RDS should be 3rd position
|
Seq1 = Field(ScanData, '|', 8)
|
||||||
CassetteID = Field(ScanData, '|', 3)
|
Set_Property(@Window:'.EDL_SEQUENCE1', 'TEXT', Seq1)
|
||||||
Seq1 = Field(ScanData, '|', 8)
|
end
|
||||||
Set_Property(@Window:'.EDL_SEQUENCE1', 'TEXT', Seq1)
|
|
||||||
end
|
|
||||||
*end else
|
|
||||||
* CassetteID = ScanData
|
|
||||||
*end
|
|
||||||
|
|
||||||
// Strip '1T', 'I', and 'O' prefixes.
|
// Strip '1T', 'I', and 'O' prefixes.
|
||||||
If CassetteID[1, 2] EQ '1T' then
|
If CassetteID[1, 2] EQ '1T' then
|
||||||
@ -486,20 +462,16 @@ Service ProcessScanData(ScanData, ScanType = SCAN_TYPES, Param1, Param2, Param3)
|
|||||||
// Assume this is intended to be a Cassette ID scan (either WMO or RDS). Only if this is a
|
// Assume this is intended to be a Cassette ID scan (either WMO or RDS). Only if this is a
|
||||||
// non-existent carrier will the scan data be considered invalid.
|
// non-existent carrier will the scan data be considered invalid.
|
||||||
|
|
||||||
*If Use2DBarcode then
|
cnt = DCount(ScanData, '|')
|
||||||
cnt = DCount(ScanData, '|')
|
if cnt NE 8 then
|
||||||
if cnt NE 8 then
|
CassetteID = 0
|
||||||
CassetteID = 0
|
Error_Services('Add', 'Invalid Lot Label Scan.')
|
||||||
Error_Services('Add', 'Invalid Lot Label Scan.')
|
return
|
||||||
return
|
end else
|
||||||
end else
|
//RDS should be 3rd position
|
||||||
//RDS should be 3rd position
|
SecondCassID = Field(ScanData, '|', 3)
|
||||||
SecondCassID = Field(ScanData, '|', 3)
|
Seq2 = Field(ScanData, '|', 8)
|
||||||
Seq2 = Field(ScanData, '|', 8)
|
end
|
||||||
end
|
|
||||||
*end else
|
|
||||||
* SecondCassID = ScanData
|
|
||||||
*end
|
|
||||||
|
|
||||||
// Strip '1T', 'I', and 'O' prefixes.
|
// Strip '1T', 'I', and 'O' prefixes.
|
||||||
If SecondCassID[1, 2] EQ '1T' then
|
If SecondCassID[1, 2] EQ '1T' then
|
||||||
@ -510,13 +482,12 @@ Service ProcessScanData(ScanData, ScanType = SCAN_TYPES, Param1, Param2, Param3)
|
|||||||
|
|
||||||
If ScanData[1, 3] EQ 'PWD' then ScanData = '********'
|
If ScanData[1, 3] EQ 'PWD' then ScanData = '********'
|
||||||
|
|
||||||
//SecondCassID = ScanData
|
FirstCassID = Param1
|
||||||
FirstCassID = Param1
|
OperatorID = Param2
|
||||||
OperatorID = Param2
|
Seq1 = Param3
|
||||||
Seq1 = Param3
|
ValidCassID = False$ ; // Assume Cassette ID is not valid for now.
|
||||||
ValidCassID = False$ ; // Assume Cassette ID is not valid for now.
|
|
||||||
ScanMismatch = False$
|
ScanMismatch = False$
|
||||||
SeqMismatch = False$
|
SeqMismatch = False$
|
||||||
Convert '*' to '.' in FirstCassID
|
Convert '*' to '.' in FirstCassID
|
||||||
|
|
||||||
If Error_Services('NoError') then
|
If Error_Services('NoError') then
|
||||||
@ -589,7 +560,6 @@ Service ProcessScanData(ScanData, ScanType = SCAN_TYPES, Param1, Param2, Param3)
|
|||||||
CtrlEntID = False$ ;* Control checked/unchecked
|
CtrlEntID = False$ ;* Control checked/unchecked
|
||||||
OriginFlag = 'P' ;* Flag to indicate a hold initiated from the packagaing form
|
OriginFlag = 'P' ;* Flag to indicate a hold initiated from the packagaing form
|
||||||
Parms = WOMatKey:@RM:HoldEntity:@RM:HoldEntityID:@RM:CtrlEntID:@RM:OriginFlag:@RM:OperatorID
|
Parms = WOMatKey:@RM:HoldEntity:@RM:HoldEntityID:@RM:CtrlEntID:@RM:OriginFlag:@RM:OperatorID
|
||||||
//obj_WO_Mat('ToggleHold', Parms)
|
|
||||||
Hold_Services('ToggleHold', WOMatKey, HoldEntity, HoldEntityID, CtrlEntID, OriginFlag, '', OperatorID)
|
Hold_Services('ToggleHold', WOMatKey, HoldEntity, HoldEntityID, CtrlEntID, OriginFlag, '', OperatorID)
|
||||||
|
|
||||||
// Check if second cassette ID is a valid RDS or WM_OUT key
|
// Check if second cassette ID is a valid RDS or WM_OUT key
|
||||||
@ -648,7 +618,6 @@ Service ProcessScanData(ScanData, ScanType = SCAN_TYPES, Param1, Param2, Param3)
|
|||||||
CtrlEntID = False$ ;* Control checked/unchecked
|
CtrlEntID = False$ ;* Control checked/unchecked
|
||||||
OriginFlag = 'P' ;* Flag to indicate a hold initiated from the packagaing form
|
OriginFlag = 'P' ;* Flag to indicate a hold initiated from the packagaing form
|
||||||
Parms = WOMatKey:@RM:HoldEntity:@RM:HoldEntityID:@RM:CtrlEntID:@RM:OriginFlag:@RM:OperatorID
|
Parms = WOMatKey:@RM:HoldEntity:@RM:HoldEntityID:@RM:CtrlEntID:@RM:OriginFlag:@RM:OperatorID
|
||||||
//obj_WO_Mat('ToggleHold', Parms)
|
|
||||||
Hold_Services('ToggleHold', WOMatKey, HoldEntity, HoldEntityID, CtrlEntID, OriginFlag, '', OperatorID)
|
Hold_Services('ToggleHold', WOMatKey, HoldEntity, HoldEntityID, CtrlEntID, OriginFlag, '', OperatorID)
|
||||||
end
|
end
|
||||||
|
|
||||||
@ -671,7 +640,7 @@ Service ProcessScanData(ScanData, ScanType = SCAN_TYPES, Param1, Param2, Param3)
|
|||||||
Error_Services('Add', Message)
|
Error_Services('Add', Message)
|
||||||
|
|
||||||
end else if SeqMismatch EQ True$ then
|
end else if SeqMismatch EQ True$ then
|
||||||
//do sequence mismatch stuff here
|
// Do sequence mismatch stuff here
|
||||||
Message = 'RDS Label verification failed at packaging due to operator double-scanning barcode.':CRLF$ |
|
Message = 'RDS Label verification failed at packaging due to operator double-scanning barcode.':CRLF$ |
|
||||||
: 'RDS: ':FirstCassID:CRLF$ |
|
: 'RDS: ':FirstCassID:CRLF$ |
|
||||||
: 'Operator: ':OperatorID
|
: 'Operator: ':OperatorID
|
||||||
@ -693,3 +662,4 @@ Service ProcessScanData(ScanData, ScanType = SCAN_TYPES, Param1, Param2, Param3)
|
|||||||
end
|
end
|
||||||
|
|
||||||
end service
|
end service
|
||||||
|
|
||||||
|
Reference in New Issue
Block a user