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
2154 lines
72 KiB
Plaintext
2154 lines
72 KiB
Plaintext
COMPILE FUNCTION GAN_PROD_SPEC(Instruction, Parm1,Parm2)
|
|
#pragma precomp SRP_PreCompiler
|
|
|
|
/*
|
|
Commuter module for PROD_SPEC (Product Specification) window
|
|
|
|
09/20/2004 - John C. Henry, J.C. Henry & Co., Inc.
|
|
03/11/2019 - djs - Updated "StatusClick" subroutine to call "NDW_MAKEUP_WAFER_NCR" when a PSN is inactivated.
|
|
Also updated two lines using an undefined equate statement PRS_PROP_UNITS$ to use the defined
|
|
equate statement PRS_PROP_UNITS_ORG$.
|
|
06/06/2020 - djs - Cutover to CR-004 and CR-005
|
|
*/
|
|
|
|
DECLARE SUBROUTINE Set_Property, End_Dialog, Send_Event, Set_Status, Center_Window, Post_Event, obj_Tables
|
|
DECLARE SUBROUTINE ErrMsg, Send_Message, Set_Property, Send_Event, Btree.Extract, obj_AppWindow, Make.List
|
|
DECLARE SUBROUTINE Database_Services, Error_Services, Dialog_Box, Start_Window
|
|
DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, Utility, Center_Window, Popup, Collect.Ixvals, Error_Services
|
|
DECLARE FUNCTION Send_Message, obj_PR_Spec, Msg, Security_Check, obj_Tables, obj_Popup, MemberOf, Database_Services
|
|
DECLARE FUNCTION RowExists, Datetime, SRP_Array, SQL_Services
|
|
|
|
$INSERT POPUP_EQUATES
|
|
$INSERT LOGICAL
|
|
$INSERT MSG_EQUATES
|
|
$INSERT APPCOLORS
|
|
$INSERT RTI_STYLE_EQUATES
|
|
$INSERT QUOTE_SIGS_EQU
|
|
$INSERT QUOTE_SPEC_EQU
|
|
$INSERT LSL_USERS_EQU
|
|
$INSERT PROD_SPEC_EQUATES
|
|
$INSERT PRS_LAYER_EQUATES
|
|
$INSERT PRS_PROP_EQUATES
|
|
$INSERT DICT_EQUATES
|
|
$INSERT CUST_EPI_PART_EQUATES
|
|
$INSERT EPI_PART_EQUATES
|
|
$INSERT PROD_VER_EQUATES
|
|
$INSERT COMPANY_EQUATES
|
|
$INSERT RLIST_EQUATES
|
|
$INSERT PROD_SPEC_REV_HIST_EQUATES
|
|
$INSERT GAN_PARAM_CONFIG_EQUATES
|
|
$INSERT GAN_PARAMS_EQUATES
|
|
|
|
|
|
EQU EDITABLE$ TO 4
|
|
EQU PROTECTED$ TO 8 ;* Protected - Edittable COLSTYLE constants
|
|
EQU MULTILINE_STYLE$ TO 512 ;* MultiLine Select
|
|
EQU LOCKED$ TO 8192
|
|
EQU DROPDOWN_STYLE$ TO 131072
|
|
|
|
EQU CRLF$ TO \0D0A\
|
|
|
|
EQU COL$LAYER TO 1
|
|
EQU COL$LS_ID TO 2
|
|
EQU COL$TYPE TO 3
|
|
EQU COL$RECIPE TO 4
|
|
EQU COL$DOPANT TO 5
|
|
EQU COL$THICK_MIN TO 6
|
|
EQU COL$THICK_MAX TO 7
|
|
EQU COL$THICK_UNITS TO 8
|
|
EQU COL$THICKA_MIN TO 9
|
|
EQU COL$THICKA_MAX TO 10
|
|
EQU COL$THICKA_UNITS TO 11
|
|
EQU COL$RES_MIN TO 12
|
|
EQU COL$RES_MAX TO 13
|
|
EQU COL$RES_UNITS TO 14
|
|
EQU COL$SRES_MIN TO 15
|
|
EQU COL$SRES_MAX TO 16
|
|
EQU COL$SRES_UNITS TO 17
|
|
|
|
EQU COL$CEP_KEY TO 1;* Used in .CEP_KEYS control
|
|
EQU COL$CEP_CUST_NAME TO 2
|
|
EQU COL$CEP_CUST_PART_NO TO 3
|
|
EQU COL$CEP_CUST_PART_DESC TO 4
|
|
EQU COL$CEP_CUST_PN_INBOUND TO 5
|
|
|
|
EQU HIDDEN$ TO 32
|
|
EQU SKIPPED$ TO 4100
|
|
|
|
|
|
*************************************************
|
|
|
|
EQU COL$CUST_PART_NO TO 1
|
|
EQU COL$CUST_PART_REV TO 2
|
|
EQU COL$CUST_PART_DESC TO 3
|
|
EQU COL$INBOUND_CUST_PN TO 4
|
|
|
|
EQU COL$SPEC_NO TO 1
|
|
EQU COL$SPEC_DESC TO 2
|
|
EQU COL$SPEC_REV TO 3
|
|
EQU COL$SPEC_REV_DT TO 4
|
|
EQU COL$SPEC_HARDCOPY TO 5
|
|
|
|
EQU COL$EP_SUB_PART_NO TO 1
|
|
EQU COL$EP_SUB_PART_REV TO 2
|
|
EQU COL$EP_SUB_MFR TO 3
|
|
|
|
EQU COL$PROD_VER_NO TO 1
|
|
EQU COL$DESC TO 2
|
|
EQU COL$STATUS TO 3
|
|
EQU COL$SUB_PART_NO TO 4
|
|
EQU COL$REACT_TYPE TO 5
|
|
EQU COL$STEP_PSN TO 6
|
|
EQU COL$CUST_NO TO 7
|
|
EQU COL$EPI_PART_NO TO 8
|
|
|
|
|
|
EQU COL$QA_MET_STAGE TO 1 ;* Used in GetQAMet data structure return variable and the edit table 'QA_STAGE'
|
|
EQU COL$QA_MET_TEST TO 2
|
|
EQU COL$QA_MET_TEST_DESC TO 3
|
|
EQU COL$QA_MET_RECIPE TO 4
|
|
EQU COL$QA_MET_RECIPE_PATTERN TO 5
|
|
EQU COL$QA_MET_MIN TO 6
|
|
EQU COL$QA_MET_MAX TO 7
|
|
EQU COL$QA_MET_SLOT TO 8
|
|
EQU COL$QA_MET_INTERVAL TO 9
|
|
EQU COL$QA_MET_START TO 10
|
|
EQU COL$QA_MET_SEQUENCE TO 11
|
|
|
|
EQU COL$MODE_CODE TO 1
|
|
EQU COL$MODE_SIG TO 2
|
|
EQU COL$MODE_SIG_DTM TO 3
|
|
|
|
EQU COL$STAGE TO 1
|
|
EQU COL$STAGE_CLEAN_TOOL TO 2
|
|
EQU COL$STAGE_BRIGHTLIGHT TO 3
|
|
EQU COL$STAGE_MICROSCOPE TO 4
|
|
EQU COL$STAGE_SURFSCAN_RECIPE TO 5
|
|
|
|
Equ COL$SIG_STAGE To 1
|
|
Equ COL$SIG_STAGE_DESC To 2
|
|
|
|
EQU OHMS_SQUARE$ TO CHAR(234):'/':CHAR(220) ;* Ohms/Square
|
|
|
|
ErrCode = ''
|
|
ErrorMsg = ''
|
|
ErrTitle = 'Error in Comm_Prod_Spec'
|
|
|
|
|
|
Result = ''
|
|
|
|
BEGIN CASE
|
|
CASE Instruction = 'GAN_PROD_SPEC' ; Null
|
|
CASE Instruction = 'CLOSE' ; GOSUB Close
|
|
CASE Instruction = 'Create' ; GOSUB Create
|
|
CASE Instruction = 'Refresh' ; GOSUB Refresh
|
|
CASE Instruction = 'Page' ; GOSUB Page
|
|
CASE Instruction = 'Clear' ; GOSUB Clear
|
|
CASE Instruction = 'Read' ; GOSUB Read
|
|
CASE Instruction = 'SurfScanClick' ; GOSUB SurfScanClick
|
|
CASE Instruction = 'LoadSurfScanDefaults' ; GOSUB LoadSurfScanDefaults
|
|
CASE Instruction = 'LUTestPointMap' ; GOSUB LUTestPointMap
|
|
CASE Instruction = 'StatusClick' ; GOSUB StatusClick
|
|
CASE Instruction = 'LUEpiPart' ; GOSUB LUEpiPart
|
|
CASE Instruction = 'ViewCustEpiPart' ; GOSUB ViewCustEpiPart
|
|
CASE Instruction = 'ViewEpiPart' ; GOSUB ViewEpiPart
|
|
CASE Instruction = 'ViewCust' ; GOSUB ViewCust
|
|
CASE Instruction = 'ProdVer_DC' ; GOSUB ProdVerDC
|
|
CASE Instruction = 'ProdVerPC' ; GOSUB ProdVerPC
|
|
CASE Instruction = 'LayerSpecDC' ; GOSUB LayerSpecDC
|
|
CASE Instruction = 'StageSpecDC' ; GOSUB StageSpecDC
|
|
CASE Instruction = 'WipStageClick' ; GOSUB WipStageClick
|
|
CASE Instruction = 'SignNextMode' ; GOSUB SignNextMode
|
|
CASE Instruction = 'UnsignCurrMode' ; GOSUB UnsignCurrMode
|
|
CASE Instruction = 'NewStage' ; GOSUB NewStage
|
|
CASE Instruction = 'ViewCurr' ; GOSUB ViewCurr
|
|
CASE Instruction = 'CepPC' ; GOSUB CepPC
|
|
CASE Instruction = 'FixCEPClick' ; GOSUB FixCEPClick
|
|
Case Instruction = 'LUWipStage' ; Gosub LUWipStage
|
|
CASE Instruction = 'LUToolSeq' ; GOSUB LUToolSeq
|
|
CASE Instruction = 'UpdateRevHist' ; GOSUB UpdateRevHist
|
|
|
|
CASE 1
|
|
ErrorMsg = 'Unknown Instruction passed to routine.'
|
|
ErrMsg(ErrorMsg)
|
|
END CASE
|
|
|
|
RETURN Result
|
|
|
|
Close:
|
|
|
|
|
|
return
|
|
|
|
|
|
* * * * * *
|
|
Create:
|
|
* * * * * *
|
|
|
|
obj_AppWindow('Create')
|
|
|
|
IF (MemberOf(@USER4,'OI_ADMIN') OR MemberOf(@USER4, 'OI_SUPERUSER')) THEN
|
|
Set_Property(@WINDOW:'.FIX_CEP','VISIBLE',1)
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.FIX_CEP','VISIBLE',0)
|
|
End
|
|
|
|
if (MemberOf(@USER4,'EXPORT_CONTROL_ADMINS')) then
|
|
Set_Property(@WINDOW:'.EXPORT_CONTROL','VISIBLE',1)
|
|
end else
|
|
Set_Property(@WINDOW:'.EXPORT_CONTROL','VISIBLE',0)
|
|
end
|
|
|
|
GoSub Setup_OLE_Controls
|
|
|
|
RETURN
|
|
|
|
|
|
|
|
* * * * * *
|
|
Refresh:
|
|
* * * * * *
|
|
|
|
CtrlID = @WINDOW:'.MODE_CODE'
|
|
ModeArray = Get_Property(CtrlID,'DEFPROP')
|
|
|
|
IF ModeArray<1,1> = '' THEN
|
|
* Set the Mode Codes
|
|
atRec = Get_Property(@WINDOW,'ATRECORD')
|
|
ReactorType = Get_Property(@Window:'.RTYPE', 'DEFPROP')
|
|
If ReactorType EQ 'GAN' then
|
|
atRec<PROD_SPEC_MODE_CODE$> = 'Q':@VM:'P'
|
|
end else
|
|
atRec<PROD_SPEC_MODE_CODE$> = 'U':@VM:'Q':@VM:'E':@VM:'P'
|
|
end
|
|
|
|
Set_Property(@WINDOW,'ATRECORD',atRec)
|
|
ModeArray = Get_Property(CtrlID,'ARRAY')
|
|
END
|
|
|
|
BEGIN CASE
|
|
CASE ModeArray<COL$MODE_SIG,4> NE '' ; ModeCode = 'P' ; NextMode = '' ; UnsignMode = ModeArray<COL$MODE_CODE,4>
|
|
CASE ModeArray<COL$MODE_SIG,3> NE '' ; ModeCode = 'E' ; NextMode = ModeArray<COL$MODE_CODE,4> ; UnsignMode = ModeArray<COL$MODE_CODE,3>
|
|
CASE ModeArray<COL$MODE_SIG,2> NE '' ; ModeCode = 'Q' ; NextMode = ModeArray<COL$MODE_CODE,3> ; UnsignMode = ModeArray<COL$MODE_CODE,2>
|
|
CASE ModeArray<COL$MODE_SIG,1> NE '' ; ModeCode = 'U' ; NextMode = ModeArray<COL$MODE_CODE,2> ; UnsignMode = ModeArray<COL$MODE_CODE,1>
|
|
CASE 1 ; ModeCode = '' ; NextMode = ModeArray<COL$MODE_CODE,1> ; UnsignMode = ''
|
|
|
|
END CASE
|
|
|
|
IF NextMode = '' THEN
|
|
Set_Property(@WINDOW:'.SIGN_MODE','ENABLED',0)
|
|
Set_Property(@WINDOW:'.SIGN_MODE','TEXT','Signed')
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.SIGN_MODE','ENABLED',1)
|
|
Set_Property(@WINDOW:'.SIGN_MODE','TEXT','Sign ':NextMode)
|
|
END
|
|
|
|
IF UnsignMode = '' THEN
|
|
Set_Property(@WINDOW:'.UNSIGN_MODE','ENABLED',0)
|
|
Set_Property(@WINDOW:'.UNSIGN_MODE','TEXT','None Signed')
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.UNSIGN_MODE','ENABLED',1)
|
|
Set_Property(@WINDOW:'.UNSIGN_MODE','TEXT','Unsign ':UnsignMode)
|
|
END
|
|
|
|
|
|
CurrStatus = Get_Property(@WINDOW:'.STATUS','DEFPROP')
|
|
EntryID = Get_Property(@WINDOW:'.ENTRY_ID','DEFPROP')
|
|
|
|
IF CurrStatus = 'I' AND EntryID NE '' THEN
|
|
Set_Property(@WINDOW:'.STATUS','BACKCOLOR',RED$)
|
|
Set_Property(@WINDOW:'.STATUS.ACTIVE','BACKCOLOR',RED$)
|
|
Set_Property(@WINDOW:'.STATUS.INACTIVE','BACKCOLOR',RED$)
|
|
END ELSE
|
|
DefColor = Get_Property(@WINDOW,'BACKCOLOR')
|
|
Set_Property(@WINDOW:'.STATUS','BACKCOLOR',DefColor)
|
|
Set_Property(@WINDOW:'.STATUS.ACTIVE','BACKCOLOR',DefColor)
|
|
Set_Property(@WINDOW:'.STATUS.INACTIVE','BACKCOLOR',DefColor)
|
|
END
|
|
|
|
BuriedLayer = Get_Property(@WINDOW:'.BURIED_LAYER','INVALUE')
|
|
|
|
IF BuriedLayer = '' THEN
|
|
Set_Property(@WINDOW:'.PRE_EPI_V','ENABLED',0)
|
|
Set_Property(@WINDOW:'.POST_EPI_V','ENABLED',0)
|
|
Set_Property(@WINDOW:'.PRE_EPI_BL','ENABLED',0)
|
|
Set_Property(@WINDOW:'.POST_EPI_BL','ENABLED',0)
|
|
END ELSE
|
|
IF BuriedLayer = 1 THEN
|
|
Set_Property(@WINDOW:'.PRE_EPI_BL','ENABLED',1)
|
|
Set_Property(@WINDOW:'.POST_EPI_BL','ENABLED',1)
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.PRE_EPI_V','ENABLED',1)
|
|
Set_Property(@WINDOW:'.POST_EPI_V','ENABLED',1)
|
|
END
|
|
END
|
|
|
|
Props = 'ENABLED':@RM:'ENABLED':@RM:'ENABLED'
|
|
Ctrls = @WINDOW:'.PRE_SURFSCAN_RECIPE':@RM:@WINDOW:'.PRE_SURF_DEFECTS':@RM:@WINDOW:'.PRE_SURF_HAZE'
|
|
|
|
IF Get_Property(@WINDOW:'.PRE_SURFSCAN','CHECK') THEN
|
|
Vals = '1':@RM:'1':@RM:'1'
|
|
END ELSE
|
|
Vals = '0':@RM:'0':@RM:'0'
|
|
END
|
|
Set_Property(Ctrls,Props,Vals)
|
|
|
|
|
|
Ctrls = @WINDOW:'.POST_SURFSCAN_RECIPE':@RM:@WINDOW:'.POST_SURF_DEFECTS':@RM:@WINDOW:'.POST_SURF_HAZE'
|
|
|
|
IF Get_Property(@WINDOW:'.POST_SURFSCAN','CHECK') THEN
|
|
Vals = '1':@RM:'1':@RM:'1'
|
|
END ELSE
|
|
Vals = '0':@RM:'0':@RM:'0'
|
|
END
|
|
Set_Property(Ctrls,Props,Vals)
|
|
|
|
|
|
Ctrls = @WINDOW:'.CLEAN_SURFSCAN_RECIPE':@RM:@WINDOW:'.CLEAN_SURF_DEFECTS':@RM:@WINDOW:'.CLEAN_SURF_HAZE'
|
|
|
|
IF Get_Property(@WINDOW:'.CLEAN_SURFSCAN','CHECK') THEN
|
|
Vals = '1':@RM:'1':@RM:'1'
|
|
END ELSE
|
|
Vals = '0':@RM:'0':@RM:'0'
|
|
END
|
|
Set_Property(Ctrls,Props,Vals)
|
|
|
|
|
|
ReactorType = Get_Property(@WINDOW:'.RTYPE','VALUE')
|
|
|
|
Ctrls = @WINDOW:'.CASS_SHIP_QTY_LABEL':@RM ; Props = 'ENABLED':@RM
|
|
Ctrls := @WINDOW:'.CASS_SHIP_QTY':@RM ; Props := 'ENABLED':@RM
|
|
Ctrls := @WINDOW:'.WMO_LOAD_CNT_LABEL':@RM ; Props := 'ENABLED':@RM
|
|
Ctrls := @WINDOW:'.WMO_LOAD_CNT' ; Props := 'ENABLED'
|
|
|
|
BEGIN CASE
|
|
CASE ReactorType = 'HTR' ; Vals = '1':@RM:'1':@RM:'0':@RM:'0'
|
|
CASE ReactorType = 'EPP' ; Vals = '1':@RM:'1':@RM:'1':@RM:'1'
|
|
CASE 1 ; Vals = '1':@RM:'1':@RM:'0':@RM:'0'
|
|
END CASE
|
|
|
|
|
|
Set_Property(Ctrls,Props,Vals)
|
|
|
|
****************************************************************************************************
|
|
|
|
// Fill Revision History Edit Table
|
|
PSNo = Get_Property(@Window : '.PROD_SPEC_ID', 'DEFPROP')
|
|
RevHistRec = Database_Services('ReadDataRow', 'PROD_SPEC_REV_HIST', PSNo)
|
|
List = ''
|
|
|
|
RevisionCol = 1
|
|
UsernameCol = 2
|
|
DateCol = 3
|
|
TimeCol = 4
|
|
|
|
For each Field in RevHistRec using @FM setting fPos
|
|
For Each Value in Field using @VM setting vPos
|
|
Begin Case
|
|
Case fPos EQ 1
|
|
List<vPos, UsernameCol> = Value
|
|
Case fPos EQ 2
|
|
List<vPos, DateCol> = OConv(Value, 'D2/HS')
|
|
Case fPos EQ 3
|
|
List<vPos, TimeCol> = OConv(Value, 'MTH')
|
|
Case fPos EQ 4
|
|
List<vPos, RevisionCol> = Value
|
|
End Case
|
|
Next Value
|
|
Next Field
|
|
Set_Property(@Window : '.EDT_REV_HIST', 'LIST', List)
|
|
|
|
|
|
****************************************************************************************************
|
|
|
|
LSArray = Get_Property(@WINDOW:'.LAYER_SPEC','ARRAY')
|
|
|
|
* Remove blank lines from display
|
|
|
|
LOOP
|
|
UNTIL LSArray[-1,1] NE @VM OR LSArray = ''
|
|
LSArray[-1,1] = ''
|
|
REPEAT
|
|
|
|
LSKeys = Get_Property(@WINDOW:'.PRS_LAYER_KEY','ARRAY')
|
|
|
|
LOOP
|
|
UNTIL LSKeys[-1,1] NE @VM OR LSKeys = ''
|
|
LSKeys[-1,1] = ''
|
|
REPEAT
|
|
|
|
|
|
LSCnt = COUNT(LSKeys,@VM) + (LSKeys NE '')
|
|
|
|
AllProps = ''
|
|
apCnt = 0
|
|
|
|
FOR I = 1 TO LSCnt
|
|
LSKey = LSKeys<1,I>
|
|
LSProps = XLATE('PRS_LAYER',LSKey,PRS_LAYER_PRS_PROP_KEY$,'X')
|
|
PropCnt = COUNT(LSProps,@VM) + (LSProps NE '')
|
|
FOR N = 1 TO PropCnt
|
|
LSProp = FIELD(LSProps<1,N>,'*',3) ;* 3 part key prop code is on the end
|
|
LOCATE LSProp IN AllProps USING @VM SETTING Dummy ELSE
|
|
apCnt += 1
|
|
AllProps = INSERT(AllProps,1,apCnt,0,LSProp)
|
|
END
|
|
NEXT N
|
|
NEXT I
|
|
|
|
ShowCols = ''
|
|
|
|
FOR I = 1 TO apCnt
|
|
Prop = AllProps<1,I>
|
|
BEGIN CASE
|
|
CASE Prop = 'THICK' ; ShowCols := COL$THICK_MIN:@VM:COL$THICK_MAX:@VM:COL$THICK_UNITS:@VM
|
|
CASE Prop = 'THICKA' ; ShowCols := COL$THICKA_MIN:@VM:COL$THICKA_MAX:@VM:COL$THICKA_UNITS:@VM
|
|
CASE Prop = 'RES' ; ShowCols := COL$RES_MIN:@VM:COL$RES_MAX:@VM:COL$RES_UNITS:@VM
|
|
CASE Prop = 'SRES' ; ShowCols := COL$SRES_MIN:@VM:COL$SRES_MAX:@VM:COL$SRES_UNITS:@VM
|
|
|
|
END CASE
|
|
NEXT I
|
|
|
|
IF ShowCols[-1,1] = @VM THEN ShowCols[-1,1] = ''
|
|
|
|
HideCols = ''
|
|
hcCnt = 0
|
|
FOR I = 6 TO 18
|
|
LOCATE I IN ShowCols USING @VM SETTING DUMMY ELSE
|
|
hcCnt += 1
|
|
HideCols<1,hcCnt> = I
|
|
END
|
|
NEXT I
|
|
|
|
LSStyles = Send_Message(@WINDOW:'.LAYER_SPEC','COLSTYLE',0,'')
|
|
|
|
scCnt = COUNT(ShowCols,@VM) + (ShowCols NE '')
|
|
|
|
FOR I = 1 TO scCnt
|
|
ShowCol = ShowCols<1,I>
|
|
LSStyles<ShowCol> = BitAnd(LSStyles<ShowCol>,BitNot(HIDDEN$))
|
|
NEXT I
|
|
|
|
FOR I = 1 TO hcCnt
|
|
HideCol = HideCols<1,I>
|
|
LSStyles<HideCol> = BitOr(LSStyles<HideCol>,HIDDEN$)
|
|
NEXT I
|
|
|
|
Send_Message(@WINDOW:'.LAYER_SPEC','COLSTYLE',0,LSStyles)
|
|
|
|
CtrlEntID = @WINDOW:'.PROD_VER'
|
|
ProdVerNos = Get_Property(CtrlEntID,'ARRAY')<COL$PROD_VER_NO>
|
|
|
|
LOOP
|
|
TestChar = ProdVerNos[-1,1]
|
|
UNTIL TestChar NE @VM OR TestChar = '' ;* Strip off trailing @VM's
|
|
ProdVerNos[-1,1] = ''
|
|
REPEAT
|
|
|
|
LastRow = COUNT(ProdVerNos,@VM) + (ProdVerNos NE '')
|
|
|
|
IF LastRow = 0 THEN LastRow = 1
|
|
|
|
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
|
|
Set_Property(CtrlEntID,'SELPOS',CurrCol:@FM:LastRow)
|
|
|
|
|
|
GOSUB ProdVerPC:
|
|
|
|
****************************************************
|
|
|
|
|
|
* Turn edit table symbolic column backgrounds to green
|
|
|
|
ETSymbolics = Get_Property(@WINDOW,'@ET_SYMBOLICS') ;* Loaded during 'Create' in obj_Appwindow
|
|
|
|
ETCtrls = ETSymbolics<1>
|
|
ETCols = ETSymbolics<2>
|
|
|
|
FOR I = 1 TO COUNT(ETCtrls,@VM) + (ETCtrls NE '')
|
|
ETCtrl = ETCtrls<1,I>
|
|
IF ETCtrl NE 'PROD_SPEC.LAYER_SPEC' AND ETCtrl NE 'PROD_SPEC.PROD_VER' THEN
|
|
ETList = Get_Property(ETCtrl,'LIST')
|
|
FOR Line = 1 TO COUNT(ETList,@FM) + (ETList NE '')
|
|
IF ETList<Line,1> NE '' THEN
|
|
FOR N = 1 TO COUNT(ETCols<1,I>,@SVM) + (ETCols<1,I> NE '')
|
|
stat = Send_Message(ETCtrl,'COLOR_BY_POS',ETCols<1,I,N>,Line,GREEN$)
|
|
NEXT N
|
|
END
|
|
NEXT Line
|
|
END
|
|
NEXT I
|
|
|
|
|
|
SpecCtrl = @WINDOW:'.LAYER_SPEC'
|
|
LSList = Get_Property(SpecCtrl,'LIST')
|
|
LSCnt = COUNT(LSList,@FM) + (LSList NE '')
|
|
|
|
FOR Line = 1 TO LSCnt
|
|
BEGIN CASE
|
|
CASE LSList<Line,COL$LS_ID> = 'L1' ; LineColor = LS1_GREEN$
|
|
CASE LSList<Line,COL$LS_ID> = 'L2' ; LineColor = LS2_GREEN$
|
|
CASE LSList<Line,COL$LS_ID> = 'L3' ; LineColor = LS3_GREEN$
|
|
CASE NUM(LSList<Line,COL$LS_ID>) ; LineColor = CMB_YELLOW$
|
|
CASE 1 ;LineColor = WHITE$
|
|
END CASE
|
|
stat = Send_Message(SpecCtrl,'COLOR_BY_POS',0,Line,LineColor)
|
|
NEXT Line
|
|
|
|
GOSUB CepPC
|
|
|
|
|
|
PVCtrl = @WINDOW:'.PROD_VER'
|
|
PVList = Get_Property(PVCtrl,'LIST')
|
|
|
|
PVCnt = COUNT(PVList,@FM) + (PVList NE '')
|
|
|
|
FOR Line = 1 TO PVCnt
|
|
|
|
LineStatus = PVList<Line,COL$STATUS>
|
|
|
|
BEGIN CASE
|
|
CASE LineStatus = 'A' ; LineColor = GREEN$
|
|
CASE LineStatus = 'I' ; LineColor = RED$
|
|
CASE 1 ; LineColor = GREEN$
|
|
|
|
END CASE
|
|
stat = Send_Message(PVCtrl,'COLOR_BY_POS',0,Line,LineColor)
|
|
|
|
NEXT Line
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
Page:
|
|
* * * * * * *
|
|
|
|
Page = Parm1
|
|
|
|
IF Page = '' THEN
|
|
Page = Get_Property(@WINDOW:'.TAB_MAIN','VALUE')
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.TAB_MAIN','VALUE',Page)
|
|
END
|
|
|
|
Set_Property(@WINDOW,'VPOSITION', Page)
|
|
|
|
GOSUB Refresh
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
Read:
|
|
* * * * * * *
|
|
|
|
ReactorType = Get_Property(@Window:'.RTYPE', 'DEFPROP')
|
|
If ReactorType EQ 'GAN' then
|
|
PSNo = Get_Property(@Window:'.PROD_SPEC_ID', 'TEXT')
|
|
Parent = Get_Property(@Window, 'PARENT')
|
|
Set_Property(@Window, '@START_GAN', True$)
|
|
Post_Event(@Window, 'CLOSE')
|
|
end else
|
|
Set_Property(@WINDOW:'.TAB_MAIN','VALUE',1)
|
|
Send_Event(@WINDOW,'PAGE',1)
|
|
GOSUB Refresh
|
|
end
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
Clear:
|
|
* * * * * * *
|
|
|
|
Set_Property(@WINDOW:'.TAB_MAIN','VALUE',1)
|
|
|
|
Send_Event(@WINDOW,'PAGE',1)
|
|
|
|
GOTO Refresh
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * *
|
|
SurfScanClick:
|
|
* * * * * *
|
|
|
|
CurrCtrl = Parm1
|
|
|
|
PrePostClean = CurrCtrl[-1,'B.']
|
|
PrePostClean = PrePostClean[1,'_']
|
|
|
|
IF Get_Property( @WINDOW:'.':PrePostClean:'_SURFSCAN', 'CHECK' ) THEN
|
|
Set_Property( @WINDOW:'.':PrePostClean:"_SURFSCAN_RECIPE", "ENABLED", 1 )
|
|
Set_Property( @WINDOW:'.':PrePostClean:"_SURF_DEFECTS", "ENABLED", 1 )
|
|
Set_Property( @WINDOW:'.':PrePostClean:"_SURF_HAZE", "ENABLED", 1 )
|
|
END ELSE
|
|
Set_Property( @WINDOW:'.':PrePostClean:"_SURFSCAN_RECIPE", "TEXT", '' )
|
|
Set_Property( @WINDOW:'.':PrePostClean:"_SURF_DEFECTS", "TEXT", '' )
|
|
Set_Property( @WINDOW:'.':PrePostClean:"_SURF_HAZE", "TEXT", '' )
|
|
Set_Property( @WINDOW:'.':PrePostClean:"_SURFSCAN_RECIPE", "ENABLED", 0 )
|
|
Set_Property( @WINDOW:'.':PrePostClean:"_SURF_DEFECTS", "ENABLED", 0 )
|
|
Set_Property( @WINDOW:'.':PrePostClean:"_SURF_HAZE", "ENABLED", 0 )
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
LoadSurfScanDefaults:
|
|
* * * * * * *
|
|
|
|
PreCtrls = @WINDOW:'.PRE_PITS':@RM ; PreProps = 'INVALUE':@RM ; PreVirginVals = '1':@RM ; PreBLVals = '10':@RM
|
|
PreCtrls := @WINDOW:'.PRE_MOUNDS':@RM ; PreProps := 'INVALUE':@RM ; PreVirginVals := '1':@RM ; PreBLVals := '10':@RM
|
|
PreCtrls := @WINDOW:'.PRE_BL_DEFECTS':@RM ; PreProps := 'INVALUE':@RM ; PreVirginVals := '1':@RM ; PreBLVals := '10':@RM
|
|
PreCtrls := @WINDOW:'.PRE_SPOTS':@RM ; PreProps := 'INVALUE':@RM ; PreVirginVals := '1':@RM ; PreBLVals := '5':@RM
|
|
PreCtrls := @WINDOW:'.PRE_FOV':@RM ; PreProps := 'INVALUE':@RM ; PreVirginVals := '1':@RM ; PreBLVals := '2':@RM
|
|
PreCtrls := @WINDOW:'.PRE_SCRATCHES':@RM ; PreProps := 'INVALUE':@RM ; PreVirginVals := '1':@RM ; PreBLVals := '1':@RM
|
|
PreCtrls := @WINDOW:'.PRE_SCRATCH_LEN':@RM ; PreProps := 'INVALUE':@RM ; PreVirginVals := '1':@RM ; PreBLVals := '1':@RM
|
|
PreCtrls := @WINDOW:'.PRE_LPD':@RM ; PreProps := 'INVALUE':@RM ; PreVirginVals := '10':@RM ; PreBLVals := '10':@RM
|
|
PreCtrls := @WINDOW:'.PRE_MICROSCOPE':@RM ; PreProps := 'INVALUE':@RM ; PreVirginVals := '0':@RM ; PreBLVals := '1':@RM
|
|
PreCtrls := @WINDOW:'.PRE_BRIGHTLIGHT' ; PreProps := 'INVALUE' ; PreVirginVals := '1' ; PreBLVals := '1'
|
|
|
|
PostCtrls = @WINDOW:'.POST_PITS':@RM ; PostProps = 'INVALUE':@RM ; PostVirginVals = '1':@RM ; PostBLVals = '20':@RM
|
|
PostCtrls = @WINDOW:'.POST_MOUNDS':@RM ; PostProps := 'INVALUE':@RM ; PostVirginVals := '1':@RM ; PostBLVals := '20':@RM
|
|
PostCtrls := @WINDOW:'.POST_BL_DEFECTS':@RM ; PostProps := 'INVALUE':@RM ; PostVirginVals := '1':@RM ; PostBLVals := '20':@RM
|
|
PostCtrls := @WINDOW:'.POST_STACK_FAULTS':@RM ; PostProps := 'INVALUE':@RM ; PostVirginVals := '20':@RM ; PostBLVals := '20':@RM
|
|
PostCtrls := @WINDOW:'.POST_SPOTS':@RM ; PostProps := 'INVALUE':@RM ; PostVirginVals := '1':@RM ; PostBLVals := '1':@RM
|
|
PostCtrls := @WINDOW:'.POST_FOV':@RM ; PostProps := 'INVALUE':@RM ; PostVirginVals := '1':@RM ; PostBLVals := '1':@RM
|
|
PostCtrls := @WINDOW:'.POST_SPIKES':@RM ; PostProps := 'INVALUE':@RM ; PostVirginVals := '5':@RM ; PostBLVals := '5':@RM
|
|
PostCtrls := @WINDOW:'.POST_SCRATCHES':@RM ; PostProps := 'INVALUE':@RM ; PostVirginVals := '2':@RM ; PostBLVals := '1':@RM
|
|
PostCtrls := @WINDOW:'.POST_SCRATCH_LEN':@RM ; PostProps := 'INVALUE':@RM ; PostVirginVals := '1':@RM ; PostBLVals := '1':@RM
|
|
PostCtrls := @WINDOW:'.POST_LPD':@RM ; PostProps := 'INVALUE':@RM ; PostVirginVals := '20':@RM ; PostBLVals := '20':@RM
|
|
PostCtrls := @WINDOW:'.POST_MICROSCOPE':@RM ; PostProps := 'INVALUE':@RM ; PostVirginVals := '1':@RM ; PostBLVals := '1':@RM
|
|
PostCtrls := @WINDOW:'.POST_BRIGHTLIGHT' ; PostProps := 'INVALUE' ; PostVirginVals := '1' ; PostBLVals := '1'
|
|
|
|
CurrButton = Parm1[-1,'B.']
|
|
|
|
BEGIN CASE
|
|
CASE CurrButton = 'PRE_EPI_V'
|
|
Ctrls = PreCtrls
|
|
Props = PreProps
|
|
Vals = PreVirginVals
|
|
MsgText = ' Pre Epi Virgin'
|
|
|
|
CASE CurrButton = 'PRE_EPI_BL'
|
|
Ctrls = PreCtrls
|
|
Props = PreProps
|
|
Vals = PreBLVals
|
|
MsgText = ' Pre Epi Buried Layer'
|
|
|
|
CASE CurrButton = 'POST_EPI_V'
|
|
Ctrls = PostCtrls
|
|
Props = PostProps
|
|
Vals = PostVirginVals
|
|
MsgText = 'Post Epi Virgin'
|
|
|
|
CASE CurrButton = 'POST_EPI_BL'
|
|
Ctrls = PostCtrls
|
|
Props = PostProps
|
|
Vals = PostBLVals
|
|
MsgText = 'Post Epi Buried Layer'
|
|
|
|
END CASE
|
|
|
|
CurrVals = Get_Property(Ctrls,Props)
|
|
|
|
CONVERT @RM TO '' IN CurrVals
|
|
|
|
Response = 1
|
|
IF LEN(TRIM(CurrVals)) AND CurrVals NE 0 THEN
|
|
|
|
MsgInfo = ''
|
|
MsgText = 'There is already data in the':MsgText:'section...':CrLf$:'Do you wish to overwrite with the standards?'
|
|
MsgInfo<MTEXT$> = MsgText
|
|
MsgInfo<MICON$> = '?'
|
|
MsgInfo<MTYPE$> = 'BNY'
|
|
Response = Msg( @WINDOW, MsgInfo )
|
|
END
|
|
|
|
IF Response THEN
|
|
Set_Property(Ctrls,Props,Vals)
|
|
IF CurrButton = 'POST_EPI_BL' THEN
|
|
Set_Property( @WINDOW:'.CLEAN_BRIGHTLIGHT', 'INVALUE', 1 )
|
|
END
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
LUTestPointMap:
|
|
* * * * * * *
|
|
|
|
MapKey = Popup(@WINDOW,'','TEST_POINT_MAP')
|
|
|
|
IF MapKey NE '' THEN
|
|
Set_Property(@WINDOW:'.TEST_POINT_MAP','DEFPROP',MapKey)
|
|
Send_Event(@WINDOW:'.TP_MAP_DESC','CALCULATE')
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
StatusClick:
|
|
* * * * * * *
|
|
|
|
/* DPC 1/28/19 - when PSN is statused (any status), want to add entry to PROD_SPEC_REV_HIST (history) table */
|
|
|
|
ReactorType = Get_Property(@WINDOW:'.RTYPE','DEFPROP')
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
NewStatus = Get_Property(@WINDOW:'.STATUS','DEFPROP')
|
|
|
|
IF PSNo = '' THEN RETURN
|
|
|
|
IF NewStatus = 'I' THEN
|
|
|
|
MsgInfo = ''
|
|
MsgInfo<mtype$> = 'BNY'
|
|
MsgInfo<micon$> = '?'
|
|
MsgInfo<mtext$> = 'Inactivating this PSN will clear the signatures...Do you wish to continue???'
|
|
|
|
Resp = msg( '', MsgInfo )
|
|
|
|
IF Resp THEN
|
|
|
|
ModeArray = Get_Property(@WINDOW:'.MODE_CODE','DEFPROP')
|
|
ModeArray<COL$MODE_SIG> = STR(@VM,3) ;* Clears Mode Signatures 8/22/2012 JCH
|
|
ModeArray<COL$MODE_SIG_DTM> = STR(@VM,3) ;* Clears Mode Sig Timestamps 8/22/2012 JCH
|
|
Set_Property(@WINDOW:'.MODE_CODE','DEFPROP',ModeArray)
|
|
|
|
* From here down goes away
|
|
|
|
SpecEpi = Get_Property(@WINDOW:'.SPEC_EPI','TEXT')
|
|
SpecEpi<1,QSEpiRecipe$> = '' ;* Clear the recipe number
|
|
SpecEpi<1,QSEpiRecipeName$> = '' ;* and name
|
|
Set_Property(@WINDOW:'.SPEC_EPI','TEXT',SpecEpi)
|
|
SpecAddtl = Get_Property(@WINDOW:'.SPEC_ADDL','TEXT') ;* Clear signatures'
|
|
|
|
Set_Property(@WINDOW:'.SPEC_ADDL','TEXT',SpecAddtl)
|
|
SpecSub = Get_Property(@WINDOW:'.SPEC_SUBSTRATE','TEXT')
|
|
SpecSub<1,QSSubSpecType$> = '' ;* Clear Spec Type
|
|
Set_Property(@WINDOW:'.SPEC_SUBSTRATE','TEXT',SpecSub)
|
|
|
|
* Call Auto-NCR form to provide the user an easy way to automatically NCR all makeup wafers
|
|
* associated with the now inactivated PSN.
|
|
|
|
Dialog_Box( 'NDW_MAKEUP_WAFER_NCR', @WINDOW, PSNo)
|
|
If Error_Services('HasError') then
|
|
ErrorMessage = 'An errror occurred during the Automatic NCR process for PSN '
|
|
Error = Error_Services('GetMessage')
|
|
ErrMsg(ErrorMessage : PSNo : @SVM : 'Please notify OpenInsight administrator. Error message:':Error)
|
|
end
|
|
|
|
END ELSE
|
|
|
|
Set_Property(@WINDOW:'.STATUS','VALUE','A')
|
|
RETURN
|
|
|
|
END
|
|
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
LUEpiPart:
|
|
* * * * * * *
|
|
|
|
TypeOver = ''
|
|
TypeOver<PSELECT$> = 1
|
|
|
|
EpiPartNo = Popup(@WINDOW,TypeOver,'EPI_PART_NOS')
|
|
|
|
IF EpiPartNo NE '' THEN
|
|
obj_AppWindow('LUValReturn',@WINDOW:@RM:@WINDOW:'.EPI_PART_NO')
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ViewEpiPart:
|
|
* * * * * * *
|
|
|
|
EpiPartNo = Get_Property(@WINDOW:'.CEP_EPI_PART_NO','DEFPROP')
|
|
|
|
IF EpiPartNo = '' THEN RETURN
|
|
|
|
obj_AppWindow('ViewRelated','EPI_PART':@RM:EpiPartNo)
|
|
|
|
Set_Property('EPI_PART.TAB_CONTROL','VALUE',3)
|
|
|
|
Send_Event('EPI_PART.TAB_CONTROL','CLICK')
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ViewCust:
|
|
* * * * * * *
|
|
|
|
CustNo = Get_Property(@WINDOW:'.CEP_CUST_NO','DEFPROP')
|
|
|
|
IF CustNo = '' THEN RETURN
|
|
|
|
obj_AppWindow('ViewRelated','CUSTOMER_EPI':@RM:CustNo)
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ViewCustEpiPart:
|
|
* * * * * * *
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
IF PSNo = '' THEN RETURN
|
|
|
|
CtrlEntID = @WINDOW:'.CEP_KEYS'
|
|
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
CurrRow = CurrPos<2>
|
|
|
|
CEPKey = Get_Property(CtrlEntID,'CELLPOS',COL$CEP_KEY:@FM:CurrRow)
|
|
|
|
IF CEPKey NE '' THEN
|
|
|
|
Send_Event(@WINDOW,'WRITE')
|
|
|
|
DetWindow = 'CUST_EPI_PART'
|
|
DetKeys = CEPKey
|
|
DefaultRec = ''
|
|
RetKey = PSNo
|
|
RetPage = 2
|
|
RetCtrl = @WINDOW:'.CEP_KEYS'
|
|
RetPos = CurrPos
|
|
|
|
oAParms = DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos
|
|
|
|
obj_AppWindow('ViewNewDetail',oAParms)
|
|
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ProdVerDC:
|
|
* * * * * * *
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
IF PSNo = '' THEN RETURN
|
|
|
|
|
|
CtrlEntID = @WINDOW:'.PROD_VER'
|
|
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
CurrRow = CurrPos<2>
|
|
|
|
|
|
IF CurrCol = COL$PROD_VER_NO THEN
|
|
ProdVerNo = Get_Property(CtrlEntID,'CELLPOS',COL$PROD_VER_NO:@FM:CurrRow)
|
|
|
|
IF PSNo NE '' THEN
|
|
|
|
Send_Event(@WINDOW,'WRITE')
|
|
|
|
DetWindow = 'PROD_VER'
|
|
DetKeys = ProdVerNo
|
|
DefaultRec = ''
|
|
RetKey = PSNo
|
|
RetPage = 2
|
|
RetCtrl = CtrlEntID
|
|
RetPos = CurrPos
|
|
|
|
oAParms = DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos
|
|
|
|
obj_AppWindow('ViewNewDetail',oAParms)
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
END
|
|
END ;* End of ItemNo column
|
|
|
|
|
|
IF CurrCol = COL$EPI_PART_NO THEN
|
|
EpiPN = Get_Property(CtrlEntID,'CELLPOS',COL$EPI_PART_NO:@FM:CurrRow)
|
|
|
|
IF PSNo NE '' THEN
|
|
|
|
Send_Event(@WINDOW,'WRITE')
|
|
|
|
DetWindow = 'EPI_PART'
|
|
DetKeys = EpiPN
|
|
DefaultRec = ''
|
|
RetKey = PSNo
|
|
RetPage = 2
|
|
RetCtrl = CtrlEntID
|
|
RetPos = CurrPos
|
|
|
|
oAParms = DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos
|
|
|
|
obj_AppWindow('ViewNewDetail',oAParms)
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
END
|
|
|
|
END
|
|
|
|
|
|
IF CurrCol = COL$CUST_NO THEN
|
|
EpiPN = Get_Property(CtrlEntID,'CELLPOS',COL$EPI_PART_NO:@FM:CurrRow)
|
|
CustNo = Get_Property(CtrlEntID,'CELLPOS',COL$CUST_NO:@FM:CurrRow)
|
|
|
|
IF EpiPN NE '' AND CustNo NE '' AND PSNo NE '' THEN
|
|
|
|
Send_Event(@WINDOW,'WRITE')
|
|
|
|
DetWindow = 'CUST_EPI_PART'
|
|
DetKeys = CustNo:'*':EpiPN
|
|
DefaultRec = ''
|
|
RetKey = PSNo
|
|
RetPage = 2
|
|
RetCtrl = CtrlEntID
|
|
RetPos = CurrPos
|
|
|
|
oAParms = DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos
|
|
|
|
obj_AppWindow('ViewNewDetail',oAParms)
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
END ;* End of check for all parameters needed
|
|
END
|
|
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ProdVerPC:
|
|
* * * * * * *
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
IF PSNo = '' THEN RETURN
|
|
|
|
|
|
CtrlEntID = @WINDOW:'.PROD_VER'
|
|
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
CurrRow = CurrPos<2>
|
|
|
|
ProdVerNo = Get_Property(CtrlEntID,'CELLPOS',COL$PROD_VER_NO:@FM:CurrRow)
|
|
EpiPN = Get_Property(CtrlEntID,'CELLPOS',COL$EPI_PART_NO:@FM:CurrRow)
|
|
CustNo = Get_Property(CtrlEntID,'CELLPOS',COL$CUST_NO:@FM:CurrRow)
|
|
|
|
CEPKey = CustNo:'*':EpiPN
|
|
|
|
CEPKeys = Get_Property(@WINDOW:'.CEP_KEYS','ARRAY')<COL$CEP_KEY>
|
|
|
|
LOCATE CEPKey IN CEPKeys USING @VM SETTING Pos THEN
|
|
Set_Property(@WINDOW:'.CEP_KEYS','SELPOS',COL$CEP_KEY:@FM:Pos)
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
QAStagePC:
|
|
* * * * * * *
|
|
|
|
RETURN
|
|
|
|
* Can be removed after test of the PRS_STAGE window dropdowns JCH * * * * * * ** * *
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
IF PSNo = '' THEN RETURN
|
|
|
|
* Get Last Layer No
|
|
|
|
LayerNos = Get_Property(@WINDOW:'.LAYER_SPEC','DEFPROP')<COL$LAYER>
|
|
|
|
LOOP
|
|
LayerNo = LayerNos[-1,'B':@VM]
|
|
UNTIL LayerNo NE ''
|
|
LayerNos[COL1(),5] = ''
|
|
REPEAT
|
|
|
|
|
|
CtrlEntID = @WINDOW:'.QA_STAGE'
|
|
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
CurrRow = CurrPos<2>
|
|
|
|
CurrLine = Get_Property(CtrlEntID,'LIST')<CurrRow>
|
|
|
|
DefProp = ''
|
|
BEGIN CASE
|
|
|
|
CASE CurrCol = COL$QA_MET_MIN AND CurrLine<1,COL$QA_MET_MIN> = ''
|
|
MetTest = CurrLine<1,COL$QA_MET_TEST>
|
|
|
|
BEGIN CASE
|
|
CASE MetTest = 'THICK_ONLY' OR MetTest = 'ADE'
|
|
|
|
DefProp = XLATE('PRS_PROP',PSNo:'*':LayerNo:'*THICK',PRS_PROP_RAW_MIN$,'X')
|
|
|
|
CASE MetTest = 'LW_RHO'
|
|
|
|
Units = OHMS_SQUARE$ ;* Resistivity units for 'ohms square' (see Metrology_Units popup)
|
|
EpiProps = XLATE('PRS_PROP',PSNo:'*':LayerNo:'*RES','','X')
|
|
IF EpiProps<PRS_PROP_UNITS_ORG$> = OHMS_SQUARE$ THEN
|
|
DefProp = EpiProps<PRS_PROP_RAW_MIN$>
|
|
END
|
|
|
|
CASE MetTest = 'SRP'
|
|
|
|
DefProp = XLATE('PRS_PROP',PSNo:'*':LayerNo:'*CONC',PRS_PROP_RAW_MIN$,'X')
|
|
|
|
END CASE
|
|
|
|
CASE CurrCol = = COL$QA_MET_MAX AND CurrLine<1,COL$QA_MET_MAX> = ''
|
|
|
|
MetTest = CurrLine<1,COL$QA_MET_TEST>
|
|
|
|
BEGIN CASE
|
|
CASE MetTest = 'THICK_ONLY' OR MetTest = 'ADE'
|
|
DefProp = XLATE('PRS_PROP',PSNo:'*':LayerNo:'*THICK',PRS_PROP_RAW_MAX$,'X')
|
|
|
|
CASE MetTest = 'LW_RHO'
|
|
Units = 'ê/Ü' ;* Resistivity units for 'ohms square' (see Metrology_Units popup)
|
|
EpiProps = XLATE('PRS_PROP',PSNo:'*':LayerNo:'*RES','','X')
|
|
IF EpiProps<PRS_PROP_UNITS_ORG$> = 'ê/Ü' THEN
|
|
DefProp = EpiProps<PRS_PROP_RAW_MAX$>
|
|
END
|
|
|
|
CASE MetTest = 'SRP'
|
|
|
|
DefProp = XLATE('PRS_PROP',PSNo:'*':LayerNo:'*CONC',PRS_PROP_RAW_MAX$,'X')
|
|
|
|
CASE 1
|
|
|
|
END CASE
|
|
|
|
END CASE
|
|
|
|
|
|
IF DefProp NE '' THEN
|
|
Set_Property(CtrlEntId,"CELLPOS",DefProp,CurrCol:@FM:CurrRow)
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
MetTestLF:
|
|
* * * * * * *
|
|
|
|
RETURN
|
|
|
|
** This needs moved to the PRS_STAGE window JCH 3/16/2015
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
IF PSNo = '' THEN RETURN
|
|
|
|
CtrlEntID = @WINDOW:'.QA_STAGE'
|
|
MetList = Get_Property(CtrlEntID,'LIST')
|
|
|
|
OrgRec = XLATE('PROD_SPEC',PSNo,'','X')
|
|
|
|
LOOP
|
|
TestLine = MetList[-1,'B':@FM]
|
|
UNTIL TestLine<1,COL$QA_MET_TEST> NE '' OR MetList = ''
|
|
MetList[COL1(),199] = ''
|
|
REPEAT
|
|
|
|
CurrArray = ''
|
|
LineCnt = COUNT(MetList,@FM) + (MetList NE '')
|
|
|
|
FOR Line = 1 TO LineCnt
|
|
CurrArray<1,Line> = MetList<Line,COL$QA_MET_TEST>
|
|
CurrArray<3,Line> = MetList<Line,COL$MET_MIN>
|
|
CurrArray<4,Line> = MetList<Line,COL$MET_MAX>
|
|
CurrArray<5,Line> = MetList<Line,COL$MET_SLOT>
|
|
CurrArray<6,Line> = MetList<Line,COL$MET_INTERVAL>
|
|
CurrArray<7,Line> = MetList<Line,COL$MET_START>
|
|
NEXT Line
|
|
|
|
Delta = 0
|
|
|
|
IF OrgRec<PROD_SPEC_MET_TEST$> NE CurrArray<1> THEN Delta = 1
|
|
IF OrgRec<PROD_SPEC_MET_INTERVAL$> NE CurrArray<6> THEN Delta = 1
|
|
IF OrgRec<PROD_SPEC_MET_START$> NE CurrArray<7> THEN Delta = 1
|
|
IF OrgRec<PROD_SPEC_MET_SLOT$> NE CurrArray<5> THEN Delta = 1
|
|
IF OrgRec<PROD_SPEC_MET_RUN_STEP$> NE CurrArray<2> THEN Delta = 1
|
|
IF OrgRec<PROD_SPEC_MET_MIN$> NE CurrArray<3> THEN Delta = 1
|
|
IF OrgRec<PROD_SPEC_MET_MAX$> NE CurrArray<4> THEN Delta = 1
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
LayerSpecDC:
|
|
* * * * * * *
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
IF PSNo = '' THEN RETURN
|
|
|
|
CtrlEntID = @WINDOW:'.LAYER_SPEC'
|
|
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
CurrRow = CurrPos<2>
|
|
|
|
|
|
IF CurrCol = COL$LAYER THEN
|
|
LayerNo = Get_Property(CtrlEntID,'CELLPOS',COL$LAYER:@FM:CurrRow)
|
|
|
|
IF PSNo NE '' THEN
|
|
|
|
|
|
Send_Event(@WINDOW,'WRITE')
|
|
|
|
DetWindow = 'PRS_LAYER'
|
|
DetKeys = PSNo:'*':LayerNo
|
|
DefaultRec = ''
|
|
RetKey = PSNo
|
|
RetPage = 1
|
|
RetCtrl = CtrlEntID
|
|
RetPos = CurrPos
|
|
|
|
oAParms = DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos
|
|
|
|
obj_AppWindow('ViewNewDetail',oAParms)
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
|
|
END
|
|
END ;* End of LayerNo Column
|
|
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
StageSpecDC:
|
|
* * * * * * *
|
|
|
|
If MemberOf(@USER4,'ENGINEERING') OR MemberOf(@USER4,'CONFIG_LIMITED') Else
|
|
ErrMsg('You must be authorized to change the specification.')
|
|
Return
|
|
END
|
|
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
IF PSNo = '' THEN RETURN
|
|
|
|
CtrlEntID = @WINDOW:'.STAGE_SPEC'
|
|
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
CurrRow = CurrPos<2>
|
|
|
|
|
|
IF CurrCol = COL$STAGE THEN
|
|
Stage = Get_Property(CtrlEntID,'CELLPOS',COL$STAGE:@FM:CurrRow)
|
|
|
|
IF PSNo NE '' THEN
|
|
|
|
|
|
Send_Event(@WINDOW,'WRITE')
|
|
|
|
DetWindow = 'PRS_STAGE'
|
|
DetKeys = PSNo:'*':Stage
|
|
DefaultRec = ''
|
|
RetKey = PSNo
|
|
RetPage = 5
|
|
RetCtrl = CtrlEntID
|
|
RetPos = CurrPos
|
|
|
|
oAParms = DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos
|
|
|
|
obj_AppWindow('ViewNewDetail',oAParms)
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
|
|
END
|
|
END ;* End of Stage Column
|
|
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
SignNextMode:
|
|
* * * * * * *
|
|
|
|
CtrlID = @WINDOW:'.MODE_CODE'
|
|
|
|
ModeArray = Get_Property(CtrlID,'DEFPROP')
|
|
|
|
BEGIN CASE
|
|
CASE ModeArray<COL$MODE_SIG,4> NE '' ; NextSigPos = ''
|
|
CASE ModeArray<COL$MODE_SIG,3> NE '' ; NextSigPos = 4 ; NextMode = ModeArray<COL$MODE_CODE,4>
|
|
CASE ModeArray<COL$MODE_SIG,2> NE '' ; NextSigPos = 3 ; NextMode = ModeArray<COL$MODE_CODE,3>
|
|
CASE ModeArray<COL$MODE_SIG,1> NE '' ; NextSigPos = 2 ; NextMode = ModeArray<COL$MODE_CODE,2>
|
|
CASE 1 ; NextSigPos = 1 ; NextMode = ModeArray<COL$MODE_CODE,1>
|
|
END CASE
|
|
|
|
SigInfo = XLATE('CONFIG','QUOTE_SIGS','','X')
|
|
|
|
BEGIN CASE
|
|
CASE NextSigPos = 4 ; QualUsers = SigInfo<PSNProdSigs$>
|
|
CASE NextSigPos = 3 ; QualUsers = SigInfo<PSNPreProdSigs$>
|
|
CASE NextSigPos = 2 ; QualUsers = SigInfo<PSNQualSigs$>
|
|
CASE NextSigPos = 1 ; QualUsers = SigInfo<PSNPreQualSigs$>
|
|
CASE 1 ; QualUsers = ''
|
|
END CASE
|
|
|
|
LOCATE @USER4 IN QualUsers USING @VM SETTING Pos THEN
|
|
Valid = Dialog_Box('NDW_VERIFY_USER', @Window, @User4)
|
|
Valid = Valid<1>
|
|
END ELSE
|
|
ErrorMsg = 'Current user is not an authorized ':NextMode:' signer.'
|
|
ErrMsg(ErrorMsg)
|
|
RETURN
|
|
END
|
|
|
|
IF Valid = 1 THEN
|
|
CurrDate = OCONV(Date(),'D4/')
|
|
CurrTime = OCONV(Time(),'MTHS')
|
|
CurrDTM = CurrDate:' ':CurrTime
|
|
|
|
Set_Property(CtrlID,'CELLPOS',@USER4,COL$MODE_SIG:@FM:NextSigPos)
|
|
Set_Property(CtrlID,'CELLPOS',CurrDTM,COL$MODE_SIG_DTM:@FM:NextSigPos)
|
|
END
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
Send_Event(@WINDOW,'WRITE')
|
|
|
|
obj_Appwindow('LUValReturn',PSNo:@RM:@WINDOW:'.PROD_SPEC_ID')
|
|
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
UnsignCurrMode:
|
|
* * * * * * *
|
|
|
|
CtrlID = @WINDOW:'.MODE_CODE'
|
|
|
|
ModeArray = Get_Property(CtrlID,'DEFPROP')
|
|
|
|
BEGIN CASE
|
|
CASE ModeArray<COL$MODE_SIG,4> NE '' ; UnsigPos = 4 ; UnsignMode = ModeArray<COL$MODE_CODE,4>
|
|
CASE ModeArray<COL$MODE_SIG,3> NE '' ; UnsigPos = 3 ; UnsignMode = ModeArray<COL$MODE_CODE,3>
|
|
CASE ModeArray<COL$MODE_SIG,2> NE '' ; UnsigPos = 2 ; UnsignMode = ModeArray<COL$MODE_CODE,2>
|
|
CASE ModeArray<COL$MODE_SIG,1> NE '' ; UnsigPos = 1 ; UnsignMode = ModeArray<COL$MODE_CODE,1>
|
|
CASE 1 ; UnsigPos = ''
|
|
END CASE
|
|
|
|
SigInfo = XLATE('CONFIG','QUOTE_SIGS','','X')
|
|
|
|
BEGIN CASE
|
|
CASE UnsigPos = 4 ; QualUsers = SigInfo<PSNProdSigs$>
|
|
CASE UnsigPos = 3 ; QualUsers = SigInfo<PSNPreProdSigs$>
|
|
CASE UnsigPos = 2 ; QualUsers = SigInfo<PSNQualSigs$>
|
|
CASE UnsigPos = 1 ; QualUsers = SigInfo<PSNPreQualSigs$>
|
|
CASE 1 ; QualUsers = ''
|
|
END CASE
|
|
|
|
LOCATE @USER4 IN QualUsers USING @VM SETTING Pos THEN
|
|
Valid = Dialog_Box('NDW_VERIFY_USER', @Window, @User4)
|
|
Valid = Valid<1>
|
|
END ELSE
|
|
ErrorMsg = 'Current user is not an authorized ':UnsignMode:' signer.'
|
|
ErrMsg(ErrorMsg)
|
|
RETURN
|
|
END
|
|
|
|
Valid = Dialog_Box('NDW_VERIFY_USER', @Window, @User4)
|
|
Valid = Valid<1>
|
|
|
|
IF Valid = 1 THEN
|
|
CurrDate = OCONV(Date(),'D4/')
|
|
CurrTime = OCONV(Time(),'MTHS')
|
|
CurrDTM = CurrDate:' ':CurrTime
|
|
|
|
Set_Property(CtrlID,'CELLPOS','',COL$MODE_SIG:@FM:UnsigPos)
|
|
Set_Property(CtrlID,'CELLPOS','',COL$MODE_SIG_DTM:@FM:UnsigPos)
|
|
END
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
Send_Event(@WINDOW,'WRITE')
|
|
|
|
obj_Appwindow('LUValReturn',PSNo:@RM:@WINDOW:'.PROD_SPEC_ID')
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * *
|
|
NewStage:
|
|
* * * * * *
|
|
|
|
StageArray = Get_Property(@WINDOW:'.STAGE_SPEC','ARRAY')
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
CurrStages = StageArray<COL$STAGE>
|
|
|
|
LOOP
|
|
UNTIL CurrStages[-1,1] NE @VM
|
|
CurrStages[-1,1] = ''
|
|
REPEAT
|
|
|
|
CurrStageCnt = COUNT(CurrStages,@VM) + (CurrStages NE '')
|
|
|
|
PopupID = @APPID<1>:'**STAGE'
|
|
PopupLiteral = XLATE('SYSREPOSPOPUPS',PopupID,PDISPLAY$,'X')
|
|
|
|
CONVERT @VM:@SVM TO @FM:@VM IN PopupLiteral
|
|
|
|
LOOP
|
|
CurrStage = CurrStages[1,@VM]
|
|
|
|
UNTIL CurrStage = ''
|
|
Done = 0
|
|
PopCnt = COUNT(PopupLiteral,@FM) + (PopupLiteral NE '')
|
|
FOR I = 1 TO PopCnt
|
|
IF PopupLiteral<I,1> = CurrStage THEN
|
|
PopupLiteral = DELETE(PopupLiteral,I,0,0) ;* Remove current stages from popup display literal
|
|
Done = 1
|
|
END
|
|
UNTIL Done
|
|
NEXT I
|
|
CurrStages[1,COL2()] = ''
|
|
REPEAT
|
|
|
|
CONVERT @FM:@VM TO @VM:@SVM IN PopupLiteral
|
|
|
|
TypeOver = ''
|
|
TypeOver<PDISPLAY$> = PopupLiteral
|
|
|
|
NewStage = Popup(@WINDOW,TypeOver,'STAGE')
|
|
|
|
Send_Event(@WINDOW,'WRITE')
|
|
|
|
StageKey = PSNo:'*':NewStage
|
|
|
|
DetWindow = 'PRS_STAGE'
|
|
DetKeys = StageKey
|
|
DefaultRec = ''
|
|
RetKey = PSNo
|
|
RetWin = @WINDOW
|
|
RetPage = 5
|
|
RetCtrl = @WINDOW:'.STAGE_SPEC'
|
|
RetPos = COL$STAGE:@FM:CurrStageCnt + 1
|
|
|
|
obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos)
|
|
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ViewCurr:
|
|
* * * * * * *
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
IF PSNo = '' THEN RETURN
|
|
|
|
CtrlEntID = @WINDOW:'.PROD_VER'
|
|
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
CurrRow = CurrPos<2>
|
|
|
|
ProdVerNo = Get_Property(CtrlEntID,'CELLPOS',COL$PROD_VER_NO:@FM:CurrRow)
|
|
EpiPN = Get_Property(CtrlEntID,'CELLPOS',COL$EPI_PART_NO:@FM:CurrRow)
|
|
CustNo = Get_Property(CtrlEntID,'CELLPOS',COL$CUST_NO:@FM:CurrRow)
|
|
|
|
CurrCtrl = Get_Property(@WINDOW,'FOCUS')
|
|
|
|
|
|
BEGIN CASE
|
|
CASE CurrCtrl = @WINDOW:'.PROD_VER_BUTTON' AND ProdVerNo NE ''
|
|
DetWindow = 'PROD_VER'
|
|
DetKeys = ProdVerNo
|
|
|
|
CASE CurrCtrl = @WINDOW:'.CUST_EPI_PART_BUTTON' AND CustNo NE '' AND EpiPN NE ''
|
|
DetWindow = 'CUST_EPI_PART'
|
|
DetKeys = CustNo:'*':EpiPN
|
|
|
|
CASE CurrCtrl = @WINDOW:'.EPI_PART_BUTTON'
|
|
DetWindow = 'EPI_PART'
|
|
DetKeys = EpiPN
|
|
|
|
CASE 1
|
|
DetWindow = ''
|
|
DetKeys = ''
|
|
|
|
END CASE
|
|
|
|
IF DetWindow NE '' THEN
|
|
|
|
Send_Event(@WINDOW,'WRITE')
|
|
|
|
DefaultRec = ''
|
|
RetKey = PSNo
|
|
RetPage = 2
|
|
RetCtrl = CtrlEntID
|
|
RetPos = CurrPos
|
|
|
|
oAParms = DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos
|
|
|
|
obj_AppWindow('ViewNewDetail',oAParms)
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
CepPC:
|
|
* * * * * * *
|
|
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
IF PSNo = '' THEN RETURN
|
|
|
|
CtrlEntID = @WINDOW:'.CEP_KEYS'
|
|
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
CurrRow = CurrPos<2>
|
|
|
|
CEPKey = Get_Property(CtrlEntID,'CELLPOS',COL$CEP_KEY:@FM:CurrRow)
|
|
CustNo = CEPKey[1,'*']
|
|
EpiPN = CEPKey[COL2()+1,'*']
|
|
|
|
CustEpiPartRec = XLATE('CUST_EPI_PART',CEPKey,'','X')
|
|
|
|
PSArray = ''
|
|
|
|
PSArray<COL$SPEC_NO> = CustEpiPartRec<CUST_EPI_PART_SPEC_NO$>
|
|
PSArray<COL$SPEC_DESC> = CustEpiPartRec<CUST_EPI_PART_SPEC_DESC$>
|
|
PSArray<COL$SPEC_REV> = CustEpiPartRec<CUST_EPI_PART_SPEC_REV$>
|
|
PSArray<COL$SPEC_REV_DT> = OCONV(CustEpiPartRec<CUST_EPI_PART_SPEC_REV_DT$>,'D4/')
|
|
PSArray<COL$SPEC_HARDCOPY> = OCONV(CustEpiPartRec<CUST_EPI_PART_SPEC_HARDCOPY$>,'B')
|
|
|
|
|
|
|
|
Ctrls = @WINDOW:'.CEP_CUST_NO':@RM ; Props = 'TEXT':@RM ; Vals = CustNo:@RM
|
|
Ctrls := @WINDOW:'.CEP_EPI_PART_NO':@RM ; Props := 'TEXT':@RM ; Vals := EpiPN:@RM
|
|
Ctrls := @WINDOW:'.CEP_SALES_NOTES':@RM ; Props := 'DEFPROP':@RM ; Vals := CustEpiPartRec<CUST_EPI_PART_SALES_NOTES$>:@RM
|
|
Ctrls := @WINDOW:'.CEP_SPEC':@RM ; Props := 'DEFPROP':@RM ; Vals := PSArray:@RM
|
|
Ctrls := @WINDOW:'.CEP_MAKEUP_WAFERS' ; Props := 'DEFPROP':@RM ; Vals := CustEpiPartRec<CUST_EPI_PART_MAKEUP_WAFERS$>
|
|
|
|
|
|
Set_Property(Ctrls,Props,Vals)
|
|
|
|
EpiPartRec = XLATE('EPI_PART',EpiPN,'','X')
|
|
|
|
|
|
Ctrls = @WINDOW:'.SUB_SUPP_BY':@RM ; Props = 'VALUE':@RM ; Vals = EpiPartRec<EPI_PART_SUB_SUPP_BY$>:@RM
|
|
|
|
Ctrls := @WINDOW:'.SUB_MAT_MANAGE':@RM ; Props := 'CHECK':@RM ; Vals := EpiPartRec<EPI_PART_SAP_MATERIAL$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_PRODUCT':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_PRODUCT$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_ORIENTATION':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_SUB_ORIENTATION$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_RESISTIVITY':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_SUB_RES$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_RES_UNITS':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_SUB_RES_UNITS$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_POLISH':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_SUB_POLISH$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_SIZE':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_SUB_WAFER_SIZE$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_DOPE_TYPE':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_SUB_DOPE_TYPE$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_OXIDE':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_SUB_OXIDE$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_MATERIAL':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_SUB_MATERIAL$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_DOPANT':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_SUB_DOPANT$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_THICKNESS':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_SUB_THICK$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_ANGSTROMS':@RM ; Props := 'DEFPROP':@RM ; Vals := EpiPartRec<EPI_PART_SUB_OXIDE_ANGSTROMS$>:@RM
|
|
Ctrls := @WINDOW:'.SUB_BACKSEAL' ; Props := 'DEFPROP' ; Vals := EpiPartRec<EPI_PART_SUB_BACKSEAL$>
|
|
|
|
Set_Property(Ctrls,Props,Vals)
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
FixCEPClick:
|
|
* * * * * * *
|
|
|
|
* Fixit routine to copy CUST_PART_NO data to Selected CUST_EPI_PART record during conversion data cleanup
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
IF PSNo = '' THEN RETURN
|
|
|
|
CtrlEntID = @WINDOW:'.CEP_KEYS'
|
|
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
CurrRow = CurrPos<2>
|
|
|
|
CEPKey = Get_Property(CtrlEntID,'CELLPOS',COL$CEP_KEY:@FM:CurrRow)
|
|
CustNo = CEPKey[1,'*']
|
|
EpiPN = CEPKey[COL2()+1,'*']
|
|
|
|
otParms = 'CUST_EPI_PART':@RM:CEPKey
|
|
CustEpiPartRec = obj_Tables('ReadRec',otParms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
RETURN
|
|
END
|
|
|
|
PSCustPartData = Get_Property(@WINDOW:'.CUST_PART_NO','ARRAY')
|
|
|
|
PSCustPartNos = PSCustPartData<1>
|
|
|
|
LOOP
|
|
TestChar = PSCustPartNos[-1,1]
|
|
UNTIL TestChar NE @VM OR PSCustPartNos = ''
|
|
PSCustPartNos[-1,1] = ''
|
|
REPEAT
|
|
|
|
|
|
PSCustPartDescs = PSCustPartData<2>
|
|
|
|
LOOP
|
|
TestChar = PSCustPartDescs[-1,1]
|
|
UNTIL TestChar NE @VM OR PSCustPartDescs = ''
|
|
PSCustPartDescs[-1,1] = ''
|
|
REPEAT
|
|
|
|
|
|
PSCustPartInbounds = PSCustPartData<3>
|
|
|
|
LOOP
|
|
TestChar = PSCustPartInbounds[-1,1]
|
|
UNTIL TestChar NE @VM OR PSCustPartInbounds = ''
|
|
PSCustPartInbounds[-1,1] = ''
|
|
REPEAT
|
|
|
|
CustEpiPartRec = XLATE('CUST_EPI_PART',CEPKey,'','X')
|
|
|
|
CustEpiPartRec<CUST_EPI_PART_CUST_PART_NO$> = PSCustPartNos
|
|
CustEpiPartRec<CUST_EPI_PART_CUST_PART_DESC$> = PSCustPartDescs
|
|
CustEpiPartRec<CUST_EPI_PART_CUST_PART_NO_INBOUND$> = PSCustPartInbounds
|
|
|
|
otParms = FieldStore(otParms, @RM, 4, 1, CustEpiPartRec)
|
|
obj_Tables('WriteRec',otParms)
|
|
|
|
Send_Event(@WINDOW,'READ')
|
|
|
|
|
|
Return
|
|
|
|
|
|
* * * * * * * *
|
|
LUWipStage:
|
|
* * * * * * * *
|
|
|
|
CtrlEntID = @WINDOW:'.':Parm1
|
|
|
|
|
|
Stages = Popup(@WINDOW,'','GAN_WIP_STAGES')
|
|
|
|
If Stages = '' Or Stages = CHAR(27) Then Return
|
|
|
|
CurrArray = Get_Property(CtrlEntID,'ARRAY')
|
|
|
|
CurrCodes = CurrArray<1> ;* 1st column has the codes in it
|
|
|
|
CurrArray<1> = Stages
|
|
|
|
Set_Property(CtrlEntID,'DEFPROP',CurrArray)
|
|
|
|
Send_Event(CtrlEntID,'CALCULATE',2)
|
|
Gosub Refresh
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
WiPStageClick:
|
|
* * * * * * *
|
|
|
|
If MemberOf(@USER4,'ENGINEERING') OR MemberOf(@USER4,'CONFIG_LIMITED') Else
|
|
ErrMsg('You must be authorized to change the specification.')
|
|
Return
|
|
END
|
|
|
|
|
|
PSNo = Get_Property(@WINDOW:'.PROD_SPEC_ID','DEFPROP')
|
|
|
|
CtrlEntID = Get_Property(@WINDOW,'FOCUS')
|
|
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
CurrRow = CurrPos<2>
|
|
|
|
IF CurrCol = COL$STAGE THEN
|
|
SigStage = Get_Property(CtrlEntID,'CELLPOS',COL$STAGE:@FM:CurrRow)
|
|
|
|
IF PSNo NE '' THEN
|
|
|
|
|
|
Send_Event(@WINDOW,'WRITE')
|
|
|
|
DetWindow = 'PRS_STAGE'
|
|
DetKeys = PSNo:'*':SigStage
|
|
DefaultRec = ''
|
|
RetKey = PSNo
|
|
RetPage = 5
|
|
RetCtrl = CtrlEntID
|
|
RetPos = CurrPos
|
|
|
|
oAParms = DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos
|
|
|
|
obj_AppWindow('ViewNewDetail',oAParms)
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
END
|
|
|
|
END
|
|
END ;* End of Stage Column
|
|
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
LUToolSeq:
|
|
* * * * * * *
|
|
|
|
CtrlEntID = @WINDOW:'.':Parm1
|
|
|
|
|
|
ToolIDs = Popup(@WINDOW,'','TOOL_CLASS_SEQ')
|
|
|
|
If ToolIDs = '' Or ToolIDs = CHAR(27) Then Return
|
|
|
|
|
|
CurrArray = Get_Property(CtrlEntID,'ARRAY')
|
|
|
|
CurrCodes = CurrArray<1> ;* 1st column has the codes in it
|
|
|
|
CurrArray<1> = ToolIDs
|
|
|
|
Set_Property(CtrlEntID,'DEFPROP',CurrArray)
|
|
|
|
Send_Event(CtrlEntID,'CALCULATE',2)
|
|
|
|
|
|
GOSUB Refresh
|
|
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
UpdateRevHist:
|
|
* * * * * * *
|
|
|
|
// Gather one line revision detail
|
|
Result = False$
|
|
Response = Dialog_Box('NDW_ADD_PSN_REVISION', @WINDOW)
|
|
Valid = Response<1>
|
|
RevisionDetail = Response<2>
|
|
If Valid then
|
|
// Update PROD_SPEC_REV_HIST record
|
|
If @Window EQ 'PRS_STAGE' then
|
|
CtrlName = @Window : '.PS_NO'
|
|
end
|
|
If @Window EQ 'PROD_SPEC' then
|
|
CtrlName = @Window : '.PROD_SPEC_ID'
|
|
end
|
|
PSNo = Get_Property(CtrlName,'DEFPROP')
|
|
If RowExists('PROD_SPEC_REV_HIST', PSNo) then
|
|
PSRevHistRec = Database_Services('ReadDataRow', 'PROD_SPEC_REV_HIST', PSNo)
|
|
end else
|
|
PSRevHistRec = ''
|
|
Database_Services('WriteDataRow', 'PROD_SPEC_REV_HIST', PSNo, PSRevHistRec, True$)
|
|
If Error_Services('NoError') then
|
|
// Rev Hist record created successfully
|
|
end else
|
|
Errmsg('Error creating PROD_SPEC_REV_HIST record: ' : PSNo : @SVM : 'Please notify OpenInsight administrator')
|
|
end
|
|
end
|
|
If Error_Services('NoError') then
|
|
Usernames = PSRevHistRec<PROD_SPEC_REV_HIST_MOD_USERNAME$>
|
|
Dates = PSRevHistRec<PROD_SPEC_REV_HIST_MOD_DATE$>
|
|
Times = PSRevHistRec<PROD_SPEC_REV_HIST_MOD_TIME$>
|
|
Revisions = PSRevHistRec<PROD_SPEC_REV_HIST_REVISION_DETAIL$>
|
|
ModUser = OConv( @user4, '[XLATE_CONV,LSL_USERS*FIRST_LAST]' )
|
|
ModDate = Date()
|
|
ModTime = Time()
|
|
ModRevision = RevisionDetail
|
|
PSRevHistRec<PROD_SPEC_REV_HIST_MOD_USERNAME$> = Insert(Usernames, 0, 1, 0, ModUser)
|
|
PSRevHistRec<PROD_SPEC_REV_HIST_MOD_DATE$> = Insert(Dates, 0, 1, 0, ModDate)
|
|
PSRevHistRec<PROD_SPEC_REV_HIST_MOD_TIME$> = Insert(Times, 0, 1, 0, ModTime)
|
|
PSRevHistRec<PROD_SPEC_REV_HIST_REVISION_DETAIL$> = Insert(Revisions, 0, 1, 0, ModRevision)
|
|
|
|
Database_Services('WriteDataRow', 'PROD_SPEC_REV_HIST', PSNo, PSRevHistRec, True$)
|
|
If Error_Services('NoError') then
|
|
Result = True$
|
|
end else
|
|
Errmsg('Error writing PROD_SPEC_REV_HIST record: ' : PSNo : @SVM : 'Please notify OpenInsight administrator')
|
|
end
|
|
end else
|
|
Errmsg('Error reading PROD_SPEC_REV_HIST record: ' : PSNo : @SVM : 'Please notify OpenInsight administrator')
|
|
end
|
|
end else
|
|
Errmsg('You must enter revision details in order to save changes to product specifications')
|
|
end
|
|
|
|
Return Result
|
|
|
|
|
|
////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
|
|
// Internal GoSubs
|
|
////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
|
|
|
|
|
|
Setup_OLE_Controls:
|
|
|
|
GoSub SetupTabCtrl
|
|
GoSub SetupDispStageCtrl
|
|
GoSub ReadCurrParams
|
|
GoSub FillDispStageCtrl
|
|
GoSub ColorTabs
|
|
GoSub HideTabs
|
|
GoSub EnableSaveButton
|
|
GoSub EnableImportButton
|
|
GoSub DisplayTimestamps
|
|
|
|
return
|
|
|
|
|
|
ResetColorArrays:
|
|
|
|
PSNo = Get_Property('PROD_SPEC.PROD_SPEC_ID', 'TEXT')
|
|
PartNo = Get_Property(@Window, '@CURR_PART_NO')
|
|
GaNParamStages = Get_Property(@Window, '@GAN_PARAM_STAGES')
|
|
CellColorArray = ''
|
|
For each Stage in GaNParamStages using @VM setting TabIndex
|
|
GaNParamConfigKey = PSNo:'*':PartNo:'*':Stage
|
|
GaNParamConfigRec = Database_Services('ReadDataRow', 'GAN_PARAM_CONFIG', GaNParamConfigKey)
|
|
ParamNames = GaNParamConfigRec<GAN_PARAM_CONFIG.PARAM_NAME$>
|
|
For each ParamName in ParamNames using @VM setting RowPos
|
|
CellColorArray<TabIndex, RowPos, 1> = 'None'
|
|
CellColorArray<TabIndex, RowPos, 2> = 'None'
|
|
CellColorArray<TabIndex, RowPos, 3> = 'None'
|
|
CellColorArray<TabIndex, RowPos, 4> = 'None'
|
|
CellColorArray<TabIndex, RowPos, 5> = 'None'
|
|
Next ParamName
|
|
Next Stage
|
|
Set_Property(@Window, '@COLOR_ARRAY', CellColorArray)
|
|
|
|
return
|
|
|
|
|
|
DisplayTimestamps:
|
|
|
|
PSNo = Get_Property('PROD_SPEC.PROD_SPEC_ID', 'TEXT')
|
|
If PSNo NE '' then
|
|
ProdSpecRec = Database_Services('ReadDataRow', 'PROD_SPEC', PSNo)
|
|
RevCPDTM = ProdSpecRec<PROD_SPEC_GAN_REV_CP_DTM$>
|
|
RevOIDTM = ProdSpecRec<PROD_SPEC_GAN_REV_OI_DTM$>
|
|
RevUser = ProdSpecRec<PROD_SPEC_GAN_REV_USER$>
|
|
RevCPDTM = OConv(RevCPDTM, 'DT2/^H')
|
|
RevOIDTM = OConv(RevOIDTM, 'DT2/^H')
|
|
Set_Property(@Window:'.TXT_OI_DTM', 'TEXT', RevOIDTM)
|
|
Set_Property(@Window:'.TXT_CP_DTM', 'TEXT', RevCPDTM)
|
|
Set_Property(@Window:'.TXT_USER', 'TEXT', OConv(RevUser, '[XLATE_CONV,LSL_USERS*FIRST_LAST]'))
|
|
end
|
|
|
|
return
|
|
|
|
|
|
SetupTabCtrl:
|
|
|
|
PSNo = Get_Property('PROD_SPEC.PROD_SPEC_ID', 'TEXT')
|
|
|
|
PartNos = Xlate('PROD_SPEC', PSNo, 'PROD_VER_EPI_PART_NO', 'X')
|
|
NumPartNos = DCount(PartNos, @VM)
|
|
CurrPartNo = Field(PartNos, @VM, NumPartNos)
|
|
Set_Property(@Window, '@CURR_PART_NO', CurrPartNo)
|
|
GaNParamStages = Xlate('APP_INFO', 'GAN_PARAM_STAGES', '', 'X')
|
|
TabCtrl = @Window:'.OLE_TAB'
|
|
Set_Property(TabCtrl, "OLE.TabCount", 12)
|
|
Convert @VM to ',' in GaNParamStages
|
|
Set_Property(TabCtrl, "OLE.CaptionList", GaNParamStages)
|
|
FontArray = 'Segoe UI':@SVM:9:@SVM:700
|
|
Set_Property(TabCtrl, "OLE.Font", FontArray)
|
|
Set_Property(TabCtrl, "OLE.SelectFont", FontArray)
|
|
|
|
// Qualify OLE events that we want to intercept
|
|
Qualifier = ''
|
|
Qualifier<1> = 1
|
|
Qualifier<4> = 0 ; * process synchronously (i.e. immediately)
|
|
Send_Message(TabCtrl, 'QUALIFY_EVENT', 'OLE.SelChanged', Qualifier)
|
|
|
|
Set_Property(TabCtrl, "OLE.FlickerFree", True$)
|
|
|
|
return
|
|
|
|
|
|
Update_Limits:
|
|
|
|
PSNo = Get_Property('PROD_SPEC.PROD_SPEC_ID', 'TEXT')
|
|
If PSNo NE '' then
|
|
CurrDTM = DateTime()
|
|
PartNos = Xlate('PROD_SPEC', PSNo, 'PROD_VER_EPI_PART_NO', 'X')
|
|
NumPartNos = DCount(PartNos, @VM)
|
|
CurrPartNo = Field(PartNos, @VM, NumPartNos)
|
|
If CurrPartNo EQ 'U014' then CurrPartNo = 'G5HTMV675AA'
|
|
Query = "SELECT [Parameter] " |
|
|
: ",[LSL] " |
|
|
: ",[Target] " |
|
|
: ",[USL] " |
|
|
: "FROM [ControlPlans].[dbo].[Part_Parameter] " |
|
|
: "WHERE [Part] = '":CurrPartNo:"' " |
|
|
: "ORDER BY [Parameter]"
|
|
Response = SQL_Services('PostSQLRequest', 'IQSDMS1', Query)
|
|
Convert @FM to @VM in Response
|
|
Convert @RM to @FM in Response
|
|
|
|
Response = SRP_Array('Rotate', Response, @FM, @VM)
|
|
ResponseParamList = Response<1>
|
|
|
|
// Get Control Plan data
|
|
GaNParamKeys = Xlate('PROD_SPEC', PSNo, 'GAN_PARAM_KEYS', 'X')
|
|
Stages = Database_Services('ReadDataRow', 'APP_INFO', 'GAN_PARAM_STAGES', 'X')
|
|
ParameterList = ''
|
|
ParamNameList = ''
|
|
CellColorArray = ''
|
|
|
|
For each Stage in Stages using @VM setting TabIndex
|
|
|
|
MetType = Stage
|
|
GaNParamConfigKey = PSNo:'*':CurrPartNo:'*':MetType
|
|
GaNParamConfigRec = Database_Services('ReadDataRow', 'GAN_PARAM_CONFIG', GaNParamConfigKey)
|
|
If Error_Services('NoError') then
|
|
ConfigMetNames = GaNParamConfigRec<GAN_PARAM_CONFIG.MET_NAME$>
|
|
ConfigParams = GaNParamConfigRec<GAN_PARAM_CONFIG.PARAM_NAME$>
|
|
EnabledArray = GaNParamConfigRec<GAN_PARAM_CONFIG.ENABLED$>
|
|
CurrVals = Get_Property(@Window, '@ORIG_VALUE_LIST')<TabIndex>
|
|
CurrNames = Get_Property(@Window, '@ORIG_MET_LIST')<TabIndex>
|
|
For each ParamName in ConfigParams using @VM setting RowPos
|
|
ParamEnabled = EnabledArray<0, RowPos>
|
|
If ParamEnabled EQ True$ then
|
|
NextRow = DCount(ParamNameList<TabIndex>, @VM) + 1
|
|
ParamNameList<TabIndex, NextRow> = ConfigMetNames<0, RowPos>
|
|
Locate ParamName in CurrNames using @VM setting CurrRow then
|
|
Locate ParamName in ResponseParamList using @VM setting vPos then
|
|
NewLSL = Response<2, vPos>
|
|
NewTarget = Response<3, vPos>
|
|
NewUSL = Response<4, vPos>
|
|
PrevLSL = CurrVals<0, CurrRow, 1>
|
|
PrevTarget = CurrVals<0, CurrRow, 2>
|
|
PrevUSL = CurrVals<0, CurrRow, 3>
|
|
|
|
If (PrevLSL EQ NewLSL) then
|
|
CellColorArray<TabIndex, NextRow, 1> = 'None'
|
|
end else
|
|
CellColorArray<TabIndex, NextRow, 1> = 'Yellow'
|
|
end
|
|
If (PrevTarget EQ NewTarget) then
|
|
CellColorArray<TabIndex, NextRow, 2> = 'None'
|
|
end else
|
|
CellColorArray<TabIndex, NextRow, 2> = 'Yellow'
|
|
end
|
|
If (PrevUSL EQ NewUSL) then
|
|
CellColorArray<TabIndex, NextRow, 3> = 'None'
|
|
end else
|
|
CellColorArray<TabIndex, NextRow, 3> = 'Yellow'
|
|
end
|
|
|
|
ParameterList<TabIndex, NextRow, 1> = NewLSL
|
|
ParameterList<TabIndex, NextRow, 2> = NewTarget
|
|
ParameterList<TabIndex, NextRow, 3> = NewUSL
|
|
end else
|
|
ParameterList<TabIndex, NextRow, 1> = 'None'
|
|
ParameterList<TabIndex, NextRow, 2> = 'None'
|
|
ParameterList<TabIndex, NextRow, 3> = 'None'
|
|
end
|
|
end else
|
|
// New parameter being added
|
|
Locate ParamName in ResponseParamList using @VM setting vPos then
|
|
NewLSL = Response<2, vPos>
|
|
NewTarget = Response<3, vPos>
|
|
NewUSL = Response<4, vPos>
|
|
ParameterList<TabIndex, NextRow, 1> = NewLSL
|
|
ParameterList<TabIndex, NextRow, 2> = NewTarget
|
|
ParameterList<TabIndex, NextRow, 3> = NewUSL
|
|
CellColorArray<TabIndex, NextRow, 1> = 'Yellow'
|
|
CellColorArray<TabIndex, NextRow, 2> = 'Yellow'
|
|
CellColorArray<TabIndex, NextRow, 3> = 'Yellow'
|
|
end
|
|
end
|
|
end
|
|
|
|
Next ParamName
|
|
end
|
|
Next Stage
|
|
end
|
|
|
|
Set_Property(@Window, '@NAME_LIST', ParamNameList)
|
|
Set_Property(@Window, '@VALUE_LIST', ParameterList)
|
|
Set_Property(@Window, '@COLOR_ARRAY', CellColorArray)
|
|
|
|
return
|
|
|
|
|
|
SetupDispStageCtrl:
|
|
|
|
DispStageCtrl = @Window:'.OLE_DISP_STAGE_EDT'
|
|
HeaderRowTitles = 'LSL':@VM:'Target':@VM:'USL'
|
|
DispStageDimArray = 5:@FM:1
|
|
Set_Property(DispStageCtrl, "OLE.Dimension", DispStageDimArray)
|
|
Set_Property(DispStageCtrl, "OLE.TitleList", HeaderRowTitles)
|
|
|
|
HeaderFontArray = 'Segoe UI':@SVM:8:@SVM:700
|
|
Set_Property(DispStageCtrl, "OLE.HeaderFont[All; All]", HeaderFontArray)
|
|
HeaderColArray = 180:@FM:True$:@FM:False$:@FM:False$
|
|
Set_Property(DispStageCtrl, "OLE.HeaderColumn[1]", HeaderColArray)
|
|
|
|
Set_Property(DispStageCtrl, "OLE.HeaderText[1; 1]", "Metrology Limits")
|
|
|
|
// Disable resizing of columns as there is no need for this on this form
|
|
StageColSize = Get_Property(DispStageCtrl, "OLE.DataColumn[1]")
|
|
StageColSize<1> = 100
|
|
StageColSize<3> = False$
|
|
Set_Property(DispStageCtrl, "OLE.DataColumn[All]", StageColSize)
|
|
Set_Property(DispStageCtrl, "OLE.CellProtection[All; All]", 'Read Only')
|
|
|
|
return
|
|
|
|
|
|
ReadCurrParams:
|
|
|
|
PSNo = Get_Property('PROD_SPEC.PROD_SPEC_ID', 'TEXT')
|
|
If PSNo NE '' then
|
|
GaNParamStages = Xlate('APP_INFO', 'GAN_PARAM_STAGES', '', 'X')
|
|
Set_Property(@Window, '@GAN_PARAM_STAGES', GaNParamStages)
|
|
|
|
GaNParamKeys = Xlate('PROD_SPEC', PSNo, 'GAN_PARAM_KEYS', 'X')
|
|
ParameterList = ''
|
|
ParamNameList = ''
|
|
MetNameList = ''
|
|
For each GaNParamKey in GaNParamKeys using @VM
|
|
MetType = Field(GaNParamKey, '*', 2)
|
|
Locate MetType in GaNParamStages using @VM setting TabPos then
|
|
|
|
GaNParamRec = Database_Services('ReadDataRow', 'GAN_PARAMS', GaNParamKey)
|
|
PartNo = Field(GaNParamKey, '*', 1)
|
|
|
|
ParamNames = GaNParamRec<GAN_PARAMS.PARAM_NAME$>
|
|
MetNames = GaNParamRec<GAN_PARAMS.MET_NAME$>
|
|
|
|
For each ParamName in ParamNames using @VM setting RowPos
|
|
|
|
MetNameList<TabPos, RowPos> = ParamName
|
|
ParamNameList<TabPos, RowPos> = MetNames<0, RowPos>
|
|
ParameterList<TabPos, RowPos, 1> = GaNParamRec<GAN_PARAMS.LSL$, RowPos>
|
|
ParameterList<TabPos, RowPos, 2> = GaNParamRec<GAN_PARAMS.TARGET$, RowPos>
|
|
ParameterList<TabPos, RowPos, 3> = GaNParamRec<GAN_PARAMS.USL$, RowPos>
|
|
|
|
Next ParamName
|
|
|
|
end
|
|
Next GaNParamKey
|
|
Set_Property(@Window, '@NAME_LIST', ParamNameList)
|
|
Set_Property(@Window, '@VALUE_LIST', ParameterList)
|
|
Set_Property(@Window, '@ORIG_VALUE_LIST', ParameterList)
|
|
Set_Property(@Window, '@ORIG_MET_LIST', MetNameList)
|
|
|
|
end
|
|
|
|
return
|
|
|
|
|
|
FillDispStageCtrl:
|
|
|
|
DispStageCtrl = @Window:'.OLE_DISP_STAGE_EDT'
|
|
TabCtrl = @Window:'.OLE_TAB'
|
|
TabIndex = Get_Property(TabCtrl, 'OLE.SelectedTab')
|
|
HeaderTitles = Get_Property(@Window, '@NAME_LIST')<TabIndex>
|
|
ParameterList = Get_Property(@Window, '@VALUE_LIST')<TabIndex>
|
|
CellColorArray = Get_Property(@Window, '@COLOR_ARRAY')<TabIndex>
|
|
NumCols = 3
|
|
NumRows = DCount(ParameterList, @VM)
|
|
DispStageDimArray = NumCols:@FM:NumRows
|
|
Set_Property(DispStageCtrl, "OLE.Dimension", DispStageDimArray)
|
|
Convert @VM to @FM in ParameterList
|
|
Convert @SVM to @VM in ParameterList
|
|
Set_Property(@Window:'.OLE_DISP_STAGE_EDT', 'OLE.LIST', ParameterList)
|
|
|
|
Convert @VM to @FM in HeaderTitles
|
|
Convert @SVM to @VM in HeaderTitles
|
|
For each HeaderTitle in HeaderTitles using @FM setting RowIndex
|
|
Set_Property(DispStageCtrl, "OLE.HeaderText[1; ":RowIndex + 1:"]", HeaderTitle)
|
|
Next HeaderTitle
|
|
|
|
Set_Property(DispStageCtrl, "OLE.HeaderAlignment[1; 2-":NumRows + 1:"]", 'C':@FM:'L':@FM:'L')
|
|
Set_Property(DispStageCtrl, "OLE.CellAlignment[All; All]", 'C':@FM:'R':@FM:'L')
|
|
Set_Property(DispStageCtrl, "OLE.HeaderAlignment[All; 1]", 'C':@FM:'C':@FM:'L')
|
|
|
|
GoSub ColorCells
|
|
|
|
return
|
|
|
|
|
|
EnableSaveButton:
|
|
|
|
ChangeDetected = False$
|
|
OrigVals = Get_Property(@Window, '@ORIG_VALUE_LIST')
|
|
CurrVals = Get_Property(@Window, '@VALUE_LIST')
|
|
ChangeDetected = (OrigVals NE CurrVals)
|
|
Set_Property(@Window:'.PUB_SAVE', 'ENABLED', ChangeDetected)
|
|
|
|
return
|
|
|
|
|
|
EnableImportButton:
|
|
|
|
PSNo = Get_Property('PROD_SPEC.PROD_SPEC_ID', 'TEXT')
|
|
CurrPartNo = Get_Property(@Window, '@CURR_PART_NO')
|
|
Stages = Get_Property(@Window, '@GAN_PARAM_STAGES')
|
|
DataToImport = False$
|
|
For each Stage in Stages using @VM setting TabIndex
|
|
GaNParamConfigKey = PSNo:'*':CurrPartNo:'*':Stage
|
|
GaNParamConfigRec = Database_Services('ReadDataRow', 'GAN_PARAM_CONFIG', GaNParamConfigKey)
|
|
If Error_Services('NoError') then
|
|
EnabledArray = GaNParamConfigRec<GAN_PARAM_CONFIG.ENABLED$>
|
|
DataToImport = (Sum(EnabledArray) > 0)
|
|
end
|
|
Until DataToImport EQ True$
|
|
Next Stage
|
|
Set_Property(@Window:'.PUB_IMPORT_CP', 'ENABLED', DataToImport)
|
|
|
|
return
|
|
|
|
|
|
ColorCells:
|
|
|
|
DispStageCtrl = @Window:'.OLE_DISP_STAGE_EDT'
|
|
DimArray = Get_Property(DispStageCtrl, "OLE.Dimension")
|
|
NumCols = DimArray<1>
|
|
NumRows = DimArray<2>
|
|
For Row = 1 to NumRows
|
|
For Col = 1 to NumCols
|
|
CellColor = CellColorArray<0, Row, Col>
|
|
Set_Property(DispStageCtrl, 'OLE.CellColors[':Col:';':Row:']', @FM:CellColor)
|
|
Next Col
|
|
Next Row
|
|
|
|
return
|
|
|
|
|
|
ColorTabs:
|
|
|
|
GaNParamStages = Get_Property(@Window, '@GAN_PARAM_STAGES')
|
|
CellColorArray = Get_Property(@Window, '@COLOR_ARRAY')
|
|
For each Stage in GaNParamStages using @VM setting TabIndex
|
|
ThisCellColorArray = CellColorArray<TabIndex>
|
|
GoSub ColorTab
|
|
Next Stage
|
|
|
|
return
|
|
|
|
|
|
HideTabs:
|
|
|
|
SelTabIndex = Get_Property(@Window:".OLE_TAB", "OLE.SelectedTab")
|
|
GaNParamStages = Get_Property(@Window, '@GAN_PARAM_STAGES')
|
|
NameArray = Get_Property(@Window, '@NAME_LIST')
|
|
For each Stage in GaNParamStages using @VM setting TabIndex
|
|
ThisNameArray = NameArray<TabIndex>
|
|
GoSub HideTab
|
|
Next Stage
|
|
|
|
SelTabVisible = Get_Property(@Window:'.OLE_TAB', 'OLE.TabVisible[':SelTabIndex:']')
|
|
If SelTabVisible EQ False$ then
|
|
For TabIndex = 1 to 12
|
|
TabVisible = Get_Property(@Window:'.OLE_TAB', 'OLE.TabVisible[':TabIndex:']')
|
|
Until TabVisible EQ True$
|
|
Next TabIndex
|
|
If TabVisible EQ True$ then Set_Property(@Window:".OLE_TAB", "OLE.SelectedTab", TabIndex)
|
|
end
|
|
|
|
return
|
|
|
|
|
|
HideTab:
|
|
|
|
If ThisNameArray EQ '' then
|
|
Set_Property(@Window:'.OLE_TAB', 'OLE.TabVisible[':TabIndex:']', False$)
|
|
end else
|
|
Set_Property(@Window:'.OLE_TAB', 'OLE.TabVisible[':TabIndex:']', True$)
|
|
end
|
|
|
|
return
|
|
|
|
|
|
ColorTab:
|
|
|
|
NumRows = DCount(ThisCellColorArray, @VM)
|
|
NumCols = DCount(ThisCellColorArray, @SVM)
|
|
|
|
ChangeDetected = False$
|
|
For Row = 1 to NumRows
|
|
For Col = 1 to NumCols
|
|
CellColor = ThisCellColorArray<0, Row, Col>
|
|
If CellColor EQ 'Yellow' then
|
|
ChangeDetected = True$
|
|
end
|
|
Until ChangeDetected EQ True$
|
|
Next Col
|
|
Until ChangeDetected EQ True$
|
|
Next Row
|
|
If ChangeDetected EQ False$ then
|
|
Colors = ""
|
|
Colors<1, 2> = "None"
|
|
Colors<2, 2> = "None"
|
|
Colors<3, 2> = "None"
|
|
Colors<4, 1> = "None"
|
|
Colors<4, 2> = "None"
|
|
Colors<5> = "None"
|
|
Set_Property(TabCtrl, "OLE.TabColors[":TabIndex:"]", Colors)
|
|
end else
|
|
Colors = ""
|
|
Colors<1, 2> = "Vertical(Gradient(Yellow L=80, Yellow L=90), Border(Yellow))"
|
|
Colors<2, 2> = "Vertical(Gradient(Yellow L=90, Yellow L=95), Border(Yellow))"
|
|
Colors<3, 2> = "Vertical(Gradient(Yellow L=85, Yellow L=95), Border(Yellow))"
|
|
Colors<4, 1> = "Gray"
|
|
Colors<4, 2> = "Vertical(Gradient(Gray L=80, Gray L=90), Border(Gray))"
|
|
Colors<5> = "Vertical(Gradient(Yellow L=95, Yellow L=80), Border(Yellow))"
|
|
Set_Property(TabCtrl, "OLE.TabColors[":TabIndex:"]", Colors)
|
|
end
|
|
|
|
return
|
|
|