874 lines
24 KiB
Plaintext
874 lines
24 KiB
Plaintext
COMPILE FUNCTION Comm_Dialog_Load_Epi_Pro(Method, Parm1, Parm2)
|
|
|
|
/*
|
|
Commuter module for Dialog_Load_Epi_Pro window.
|
|
|
|
03/13/2006 - John C. Henry, J.C. Henry & Co., Inc.
|
|
*/
|
|
|
|
DECLARE SUBROUTINE Set_Property, End_Dialog, Set_Status, ErrMsg, obj_RDS2, Send_Event, RDS_React_Run
|
|
DECLARE SUBROUTINE obj_Appwindow, Start_Window, Msg, End_Dialog, Send_Message, obj_WM_IN, obj_WM_Wfrs, obj_React_Status
|
|
DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, Popup, obj_WM_In, Send_Message, obj_NCR, obj_WM_Wfrs
|
|
|
|
EQU CRLF$ TO \0D0A\
|
|
|
|
$INSERT POPUP_EQUATES
|
|
$INSERT LOGICAL
|
|
$INSERT MSG_EQUATES
|
|
$INSERT RDS_EQU
|
|
$INSERT RDS_TEST_EQUATES
|
|
$INSERT EPI_SUSCEPTOR_EQUATES
|
|
$INSERT RDS_EPILOAD
|
|
$INSERT WO_STEP_EQU
|
|
$INSERT NCR_EQU
|
|
$INSERT APPCOLORS
|
|
|
|
EQU COL$WM_CASS_IN TO 1
|
|
EQU COL$WM_SLOT_IN TO 2
|
|
|
|
EQU COL$POCKET TO 1
|
|
EQU COL$USAGE TO 2
|
|
EQU COL$ZONE TO 3
|
|
EQU COL$IN_CASS TO 4
|
|
EQU COL$IN_SLOT TO 5
|
|
EQU COL$WAFER_TYPE TO 6
|
|
|
|
EQU COL$NCR_NO TO 1
|
|
EQU COL$CASS_NO TO 2
|
|
EQU COL$SLOT_NO TO 3
|
|
|
|
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
|
|
|
|
|
|
|
|
ErrTitle = 'Error in Comm_Dialog_Load_Epi_Pro'
|
|
ErrorMsg = ''
|
|
|
|
Result = ''
|
|
|
|
BEGIN CASE
|
|
CASE Method = 'Create' ; GOSUB Create
|
|
CASE Method = 'Done' ; GOSUB Done
|
|
CASE Method = 'Close' ; GOSUB Close
|
|
CASE Method = 'Refresh' ; GOSUB Refresh
|
|
CASE Method = 'WMinClick' ; GOSUB WMinClick
|
|
CASE Method = 'UpdateWMIn' ; GOSUB UpdateWMIn
|
|
CASE Method = 'LoadMat' ; GOSUB LoadMat
|
|
CASE Method = 'RejMat' ; GOSUB RejMat
|
|
CASE Method = 'UnloadMat' ; GOSUB UnloadMat
|
|
CASE Method = 'ReactPC' ; GOSUB ReactPC
|
|
CASE Method = 'ReactLF' ; GOSUB ReactLF
|
|
CASE Method = 'ReactIR' ; GOSUB ReactIR
|
|
CASE Method = 'ReactDR' ; GOSUB ReactDR
|
|
|
|
CASE 1
|
|
ErrMsg(ErrTitle:@SVM:'Unknown method ':QUOTE(Method):' passed to routine.')
|
|
|
|
END CASE
|
|
|
|
|
|
RETURN Result
|
|
|
|
|
|
|
|
* * * * * * *
|
|
Create:
|
|
* * * * * * *
|
|
|
|
obj_AppWindow('Create')
|
|
|
|
* get the current style
|
|
|
|
Style = Get_Property(@WINDOW:'.WM_IN', 'STYLE')
|
|
|
|
IF Style [1,2] _EQC "0x" THEN
|
|
CONVERT @LOWER.CASE TO @UPPER.CASE IN STYLE
|
|
Style = ICONV(Style [3,99], "MX")
|
|
END
|
|
|
|
Style = BitOr(Style, MULTILINE_STYLE$)
|
|
Set_Property(@WINDOW:'.WM_IN', "STYLE", Style)
|
|
|
|
ReactorStyles = Send_Message(@WINDOW:'.REACTOR_TABLE','COLSTYLE',0,'')
|
|
ReactorStyles<COL$USAGE> = BitOr(ReactorStyles<COL$USAGE>,DROPDOWN_STYLE$)
|
|
Send_Message(@WINDOW:'.REACTOR_TABLE','COLSTYLE',0,ReactorStyles)
|
|
Send_Message(@WINDOW:'.REACTOR_TABLE','COLFORMAT',COL$USAGE,'TEST':@VM:'PROD':@VM:'DUMMY')
|
|
|
|
RDSNo = FIELD(Parm1,@FM,1)
|
|
CurrentLoad = FIELD(Parm1,@FM,2,99)
|
|
|
|
IF RDSNo = '' THEN
|
|
ErrMsg('Null RDS No passed to Dialog Box...')
|
|
End_Dialog(@WINDOW,'')
|
|
END
|
|
|
|
RDSRec = XLATE('RDS',RDSNo,'','X')
|
|
|
|
ReactorNo = RDSRec<RDS_REACTOR$>
|
|
WONo = RDSRec<RDS_WO$>
|
|
WOStep = FIELD(RDSRec<RDS_WO_STEP_KEY$>,'*',2)
|
|
|
|
Ctrls = @WINDOW:'.RDS_NO':@RM:@WINDOW:'.WO_NO':@RM:@WINDOW:'.WO_STEP':@RM:@WINDOW:'.REACTOR_NO'
|
|
Props = 'DEFPROP':@RM: 'DEFPROP':@RM: 'DEFPROP':@RM: 'DEFPROP'
|
|
Vals = RDSNo:@RM:WONo:@RM:WOStep:@RM:ReactorNo
|
|
|
|
Set_Property(Ctrls,Props,Vals)
|
|
|
|
RCtrl = @WINDOW:'.REACTOR_TABLE'
|
|
IF CurrentLoad<1,1> = '' THEN
|
|
PSNo = XLATE('WO_STEP',WONo:'*':WOStep,WO_STEP_PROD_SPEC_ID$,'X')
|
|
PSNWaferSize = XLATE('PROD_SPEC',PSNo,'SUB_WAFER_SIZE','X')
|
|
|
|
BEGIN CASE
|
|
CASE PSNWaferSize = '150 mm 6 in'
|
|
EpiSusceptor = XLATE('EPI_SUSCEPTOR','6','','X')
|
|
|
|
CASE PSNWaferSize = '125 mm 5 in'
|
|
EpiSusceptor = XLATE('EPI_SUSCEPTOR','5','','X')
|
|
|
|
CASE PSNWaferSize = '200 mm 8 in'
|
|
EpiSusceptor = XLATE('EPI_SUSCEPTOR','8','','X')
|
|
|
|
CASE 1
|
|
ErrorMsg = 'PSN: ':QUOTE(PSNo):' has a wafer size of ':PSNWaferSize:'.':CRLF$:CRLF$
|
|
ErrorMsg := 'The EpiPRO reactors cannot process wafers of this size.'
|
|
|
|
ErrMsg(ErrorMsg)
|
|
|
|
End_Dialog(@WINDOW,'')
|
|
|
|
END CASE
|
|
|
|
Pockets = EpiSusceptor<EPI_SUSCEPTOR_POCKET_NO$>
|
|
Zones = EpiSusceptor<EPI_SUSCEPTOR_POCKET_ZONE$>
|
|
PTypes = EpiSusceptor<EPI_SUSCEPTOR_POCKET_TYPE$>
|
|
|
|
FOR I = 1 TO COUNT(Pockets,@VM) + (Pockets NE '')
|
|
Set_Property(RCtrl,'CELLPOS',Pockets<1,I>,COL$POCKET:@FM:I)
|
|
Set_Property(RCtrl,'CELLPOS',PTypes<1,I>,COL$USAGE:@FM:I)
|
|
Set_Property(RCtrl,'CELLPOS',Zones<1,I>,COL$ZONE:@FM:I)
|
|
NEXT I
|
|
|
|
Set_Property(@WINDOW,'@LAST_POCKET',I-1)
|
|
|
|
END ELSE
|
|
|
|
FOR I = 1 TO COUNT(CurrentLoad<1>,@VM) + (CurrentLoad<1> NE '')
|
|
Set_Property(RCtrl,'CELLPOS',CurrentLoad<COL$POCKET,I>,COL$POCKET:@FM:I)
|
|
Set_Property(RCtrl,'CELLPOS',CurrentLoad<COL$USAGE,I>,COL$USAGE:@FM:I)
|
|
Set_Property(RCtrl,'CELLPOS',CurrentLoad<COL$ZONE,I>,COL$ZONE:@FM:I)
|
|
Set_Property(RCtrl,'CELLPOS',CurrentLoad<COL$IN_CASS,I>,COL$IN_CASS:@FM:I)
|
|
Set_Property(RCtrl,'CELLPOS',CurrentLoad<COL$IN_SLOT,I>,COL$IN_SLOT:@FM:I)
|
|
Set_Property(RCtrl,'CELLPOS',CurrentLoad<COL$WAFER_TYPE,I>,COL$WAFER_TYPE:@FM:I)
|
|
NEXT I
|
|
END
|
|
|
|
GOSUB UpdateWMIn
|
|
GOSUB UpdateNCR
|
|
|
|
WMInList = Get_Property(WMICtrl,'LIST')
|
|
|
|
IF WMInList<1,1> = '' THEN
|
|
|
|
* Reactor table has been loaded
|
|
|
|
Send_Message(@WINDOW:'.REACTOR_TABLE','COLFORMAT',COL$WAFER_TYPE,'')
|
|
Set_Property('SYSTEM','FOCUS',@WINDOW:'.REACTOR_TABLE')
|
|
|
|
ReactorStyles = Send_Message(@WINDOW:'.REACTOR_TABLE','COLSTYLE',0,'')
|
|
|
|
ReactorStyles<COL$WAFER_TYPE> = BitAnd(ReactorStyles<COL$WAFER_TYPE>,BitNot(DROPDOWN_STYLE$))
|
|
|
|
ReactorStyles<COL$POCKET> = BitOr(ReactorStyles<COL$POCKET>,PROTECTED$)
|
|
ReactorStyles<COL$ZONE> = BitOr(ReactorStyles<COL$ZONE>,PROTECTED$)
|
|
ReactorStyles<COL$IN_CASS> = BitOr(ReactorStyles<COL$IN_CASS>,PROTECTED$)
|
|
ReactorStyles<COL$IN_SLOT> = BitOr(ReactorStyles<COL$IN_SLOT>,PROTECTED$)
|
|
ReactorStyles<COL$WAFER_TYPE> = BitOr(ReactorStyles<COL$WAFER_TYPE>,PROTECTED$)
|
|
|
|
Send_Message(@WINDOW:'.REACTOR_TABLE','COLSTYLE',0,ReactorStyles)
|
|
|
|
|
|
END ELSE
|
|
|
|
* Reactor table is not yet loaded
|
|
|
|
|
|
ReactorStyles = Send_Message(@WINDOW:'.REACTOR_TABLE','COLSTYLE',0,'')
|
|
|
|
ReactorStyles<COL$WAFER_TYPE> = BitOr(ReactorStyles<COL$WAFER_TYPE>,DROPDOWN_STYLE$)
|
|
|
|
ReactorStyles<COL$POCKET> = BitAnd(ReactorStyles<COL$POCKET>,BitNot(PROTECTED$))
|
|
ReactorStyles<COL$ZONE> = BitAnd(ReactorStyles<COL$ZONE>,BitNot(PROTECTED$))
|
|
ReactorStyles<COL$IN_CASS> = BitAnd(ReactorStyles<COL$IN_CASS>,BitNot(PROTECTED$))
|
|
ReactorStyles<COL$IN_SLOT> = BitAnd(ReactorStyles<COL$IN_SLOT>,BitNot(PROTECTED$))
|
|
ReactorStyles<COL$WAFER_TYPE> = BitAnd(ReactorStyles<COL$WAFER_TYPE>,BitNot(PROTECTED$))
|
|
|
|
Send_Message(@WINDOW:'.REACTOR_TABLE','COLSTYLE',0,ReactorStyles)
|
|
Send_Message(@WINDOW:'.REACTOR_TABLE','COLFORMAT',COL$WAFER_TYPE,'':@VM:'TEST')
|
|
Set_Property('SYSTEM','FOCUS',@WINDOW:'.REACTOR_TABLE')
|
|
END
|
|
|
|
WOStepKey = RDSRec<RDS_WO_STEP_KEY$>
|
|
|
|
WONo = WOStepKey[1,'*']
|
|
WOStep = WOStepKey[COL2()+1,'*']
|
|
|
|
GOSUB Refresh
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
Close:
|
|
* * * * * * *
|
|
|
|
OKtoClose = Get_Property(@WINDOW:'.DONE_BUTTON','ENABLED')
|
|
|
|
IF NOT(OKtoClose) THEN
|
|
ErrMsg('All information needed to load the reactor has not been entered.')
|
|
Result = 0
|
|
RETURN
|
|
END
|
|
|
|
|
|
* * * * * * *
|
|
Done:
|
|
* * * * * * *
|
|
|
|
RCtrl = @WINDOW:'.REACTOR_TABLE'
|
|
ReactorList = Get_Property(RCtrl,'LIST')
|
|
WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP')
|
|
Reactor = Get_Property(@WINDOW:'.REACTOR_NO','DEFPROP')
|
|
|
|
|
|
|
|
Pockets = ''
|
|
PocketChars = ''
|
|
Zones = ''
|
|
InCassettes = ''
|
|
InSlots = ''
|
|
WaferChars = ''
|
|
|
|
LoadCnt = 1
|
|
TestCnt = 0
|
|
|
|
FOR I = 1 TO COUNT(ReactorList,@FM) + (ReactorList NE '')
|
|
IF ReactorList<I,COL$POCKET> NE '' THEN
|
|
Pockets<1,LoadCnt> = ReactorList<I,COL$POCKET>
|
|
|
|
Usage = ReactorList<I,COL$USAGE>
|
|
|
|
IF LEN(Usage) < 2 THEN Usage = ''
|
|
PocketChars<1,LoadCnt> = Usage
|
|
|
|
Zones<1,LoadCnt> = ReactorList<I,COL$ZONE>
|
|
InCassettes<1,LoadCnt> = ReactorList<I,COL$IN_CASS>
|
|
InSlots<1,LoadCnt> = ReactorList<I,COL$IN_SLOT>
|
|
WaferChars<1,LoadCnt> = ReactorList<I,COL$WAFER_TYPE>
|
|
LoadCnt += 1
|
|
|
|
IF Usage = 'TEST' AND ReactorList<I,COL$WAFER_TYPE> = 'PROD' THEN
|
|
TestCnt += 1
|
|
END
|
|
END
|
|
NEXT I
|
|
|
|
IF TestCnt = 0 THEN
|
|
Resp = Msg(@WINDOW,'','EPI_PRO_TEST_QTY')
|
|
IF Resp = '' THEN
|
|
ErrMsg('You must enter the number of product test wafers to continue.')
|
|
RETURN
|
|
END
|
|
IF Resp NE 0 THEN
|
|
ErrMsg('There are no pockets setup for Product Test Wafers.')
|
|
RETURN
|
|
END
|
|
END
|
|
|
|
RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP')
|
|
|
|
orParms = RDSNo:@RM:Pockets:@RM:PocketChars:@RM:Zones:@RM:InCassettes:@RM:InSlots:@RM:WaferChars
|
|
|
|
obj_RDS2('LoadEpi',orParms)
|
|
|
|
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
RETURN
|
|
|
|
WMILocks = Get_Property(@WINDOW,'@LOCKED_WFRS')
|
|
obj_WM_Wfrs('UnlockSet','WMI_WFRS':@RM:WMILocks) ; * Remove locks on the wafer slots
|
|
|
|
END ELSE
|
|
|
|
|
|
* Update Reactor Status with load data * * * * * * ;* Added 11/14/2008 JCH
|
|
|
|
LoadDTM = OCONV( Date(), 'D2/' ):' ':OCONV( Time(), 'MTH' )
|
|
|
|
WfrCnt = COUNT(InCassettes,@VM) + (InCassettes NE '')
|
|
CassIDs = ''
|
|
FOR I = 1 TO WfrCnt
|
|
InCass = Incassettes<1,I>
|
|
LOCATE InCass IN CassIDs USING @VM SETTING Pos ELSE
|
|
CassIDs = INSERT(CassIDs,1,Pos,0,InCass)
|
|
END
|
|
NEXT I
|
|
|
|
*obj_React_Status('ReactorLoad',Reactor:@RM:WONo:@RM:CassIDs:@RM:LoadDTM)
|
|
|
|
IF Get_Status(errCode) THEN ErrMsg(errCode)
|
|
END
|
|
|
|
WMILocks = Get_Property(@WINDOW,'@LOCKED_WFRS')
|
|
|
|
IF WMILocks NE '' THEN
|
|
obj_WM_Wfrs('UnlockSet','WMI_WFRS':@RM:WMILocks) ; * Remove locks on the wafer slots
|
|
END
|
|
|
|
Set_Property(@WINDOW,'@LOCKED_WFRS','')
|
|
|
|
End_Dialog(@WINDOW,'')
|
|
|
|
RDS_React_Run(RDSNo) ;* Hook to conversion code JCH 9/25/2008 **************************************
|
|
|
|
|
|
Set_Property('RDS.RDS_NO','DEFPROP',RDSNo)
|
|
Send_Event('RDS','READ')
|
|
|
|
|
|
RETURN
|
|
|
|
|
|
|
|
* * * * * * *
|
|
Refresh:
|
|
* * * * * * *
|
|
|
|
RCtrl = @WINDOW:'.REACTOR_TABLE'
|
|
WMICtrl = @WINDOW:'.WM_IN'
|
|
|
|
ReactorList = Get_Property(RCtrl,'LIST')
|
|
WMInList = Get_Property(WMICtrl,'LIST')
|
|
|
|
LastPocket = Get_Property(@WINDOW,'@LAST_POCKET')
|
|
OpenTestCnt = 0
|
|
OpenProdCnt = 0
|
|
|
|
FOR I = 1 TO COUNT(ReactorList,@FM) + (ReactorList NE '')
|
|
|
|
IF ReactorList<I,COL$POCKET> NE '' THEN
|
|
|
|
/*
|
|
IF ReactorList<I,COL$IN_CASS> NE '' AND ReactorList<I,COL$IN_SLOT> NE '' THEN
|
|
IF ReactorList<I,COL$WAFER_TYPE> = 'TEST' OR ReactorList<I,COL$WAFER_TYPE> = '' THEN
|
|
* Somebody changed the wafer type after loading the wafers
|
|
* Put the wafer back into WM_IN
|
|
|
|
WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP')
|
|
WOStep = Get_Property(@WINDOW:'.WO_STEP','DEFPROP')
|
|
CassNo = ReactorList<I,COL$IN_CASS>
|
|
SlotNo = ReactorList<I,COL$IN_SLOT>
|
|
|
|
obj_WM_In('ReplaceWafer',WONo:@RM:WOStep:@RM:CassNo:@RM:SlotNo)
|
|
|
|
Set_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS','',COL$IN_CASS:@FM:I)
|
|
Set_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS','',COL$IN_SLOT:@FM:I)
|
|
Set_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS','',COL$WAFER_TYPE:@FM:I)
|
|
|
|
GOTO UpdateWMIn
|
|
|
|
END
|
|
END
|
|
|
|
IF ReactorList<I,COL$IN_CASS> = '' AND ReactorList<I,COL$IN_SLOT> = '' THEN
|
|
IF ReactorList<I,COL$WAFER_TYPE> = 'PROD' THEN
|
|
* Wafer Type changed to 'PROD', Set WaferType to '' and give a message
|
|
Set_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS','',COL$WAFER_TYPE:@FM:I)
|
|
Mesg = "Product wafers may only be loaded using the 'Load Material Button'"
|
|
ErrMsg(Mesg)
|
|
END
|
|
END
|
|
*/
|
|
IF ReactorList<I,COL$USAGE> = 'TEST' THEN
|
|
Send_Message(RCtrl,'COLOR_BY_POS',0,I,YELLOW$)
|
|
IF ReactorList<I,COL$WAFER_TYPE> = '' THEN OpenTestCnt += 1
|
|
END
|
|
|
|
IF ReactorList<I,COL$USAGE> = 'DUMMY' THEN
|
|
Send_Message(RCtrl,'COLOR_BY_POS',0,I,WHITE$)
|
|
END
|
|
|
|
IF ReactorList<I,COL$USAGE> = 'PROD' OR ReactorList<I,COL$USAGE> = '' THEN
|
|
Set_Property(RCtrl,'CELLPOS','',COL$USAGE:@FM:I)
|
|
Zone = ReactorList<I,COL$ZONE>
|
|
IF Zone = 1 THEN LineColor = RCV_BLUE$
|
|
IF Zone = 2 THEN LineColor = PRE_BLUE$
|
|
IF Zone = 3 THEN LineColor = INP_BLUE$
|
|
IF Zone = 4 THEN LineColor = POS_BLUE$
|
|
Send_Message(RCtrl,'COLOR_BY_POS',0,I,LineColor)
|
|
END
|
|
|
|
IF (ReactorList<I,COL$USAGE> = '' OR ReactorList<I,COL$USAGE> = 'PROD') AND ReactorList<I,COL$WAFER_TYPE> = '' THEN OpenProdCnt += 1
|
|
END
|
|
NEXT I
|
|
|
|
Set_Property(@WINDOW:'.OPEN_PROD_POCKETS','DEFPROP',OpenProdCnt)
|
|
Set_Property(@WINDOW:'.OPEN_TEST_POCKETS','DEFPROP',OpenTestCnt)
|
|
|
|
|
|
IF OpenProdCnt > 0 THEN
|
|
Set_Property(@WINDOW:'.OPEN_PROD_POCKETS','BACKCOLOR',RED$)
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.OPEN_PROD_POCKETS','BACKCOLOR',GREEN$)
|
|
END
|
|
|
|
IF OpenTestCnt > 0 THEN
|
|
Set_Property(@WINDOW:'.OPEN_TEST_POCKETS','BACKCOLOR',RED$)
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.OPEN_TEST_POCKETS','BACKCOLOR',GREEN$)
|
|
END
|
|
|
|
IF @USERNAME = 'BRYCE_BARB' OR @USER4 = 'CANDICE_C' THEN
|
|
Set_Property(@WINDOW:'.DONE_BUTTON','ENABLED',1)
|
|
END ELSE
|
|
IF OpenProdCnt > 0 OR OpenTestCnt > 0 THEN
|
|
Set_Property(@WINDOW:'.DONE_BUTTON','ENABLED',0)
|
|
END ELSE
|
|
Set_Property(@WINDOW:'.DONE_BUTTON','ENABLED',1)
|
|
END
|
|
END
|
|
|
|
|
|
SelectedReactors = Get_Property(RCtrl,'SELPOS')
|
|
|
|
IF SelectedReactors<2> NE '' THEN
|
|
Set_Property(RCtrl,'SELPOS',@FM)
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ReactPC:
|
|
* * * * * * *
|
|
|
|
GOSUB UpdateWMIn
|
|
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ReactLF:
|
|
* * * * * * *
|
|
|
|
GOSUB UpdateWMIn
|
|
|
|
RETURN
|
|
|
|
|
|
|
|
* * * * * * *
|
|
WMinClick:
|
|
* * * * * * *
|
|
|
|
* This fills in any 'unselected' lines if the user skips a line in the selection process ************ dead ************
|
|
|
|
|
|
RETURN
|
|
|
|
CurrCtrl = @WINDOW:'.WM_IN'
|
|
|
|
SelectedRows = Get_Property(@WINDOW:'.WM_IN','SELPOS')<2>
|
|
LastSelPos = SelectedRows[-1,'B':@VM]
|
|
|
|
|
|
TestSelList = ''
|
|
FOR I = 1 TO LastSelPos
|
|
LOCATE I IN SelectedRows USING @VM SETTING Dummy ELSE
|
|
TestSelList<1,-1> = I
|
|
END
|
|
NEXT I
|
|
IF TestSelList NE '' THEN
|
|
Set_Property(@WINDOW:'.WM_IN','SELPOS',1:@FM:TestSelList)
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
LoadMat:
|
|
* * * * * * *
|
|
|
|
WMInLoadList = Get_Property(@WINDOW:'.WM_IN','LIST')
|
|
ReactorLoadList = Get_Property(@WINDOW:'.REACTOR_TABLE','LIST')
|
|
WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP')
|
|
WOStep = Get_Property(@WINDOW:'.WO_STEP','DEFPROP')
|
|
RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP')
|
|
|
|
SelectedRows = ''
|
|
WMIWaferKeys = ''
|
|
|
|
FOR I = 1 TO COUNT(WMInLoadList,@FM) + (WMInLoadList NE '')
|
|
IF WMInLoadList<I,COL$WM_CASS_IN> NE '' AND WMInLoadList<I,COL$WM_SLOT_IN> NE '' THEN
|
|
SelectedRows<-1> = I
|
|
WMIWaferKeys<1,-1> = WONo:'*':WOStep:'*':WMInLoadList<I,COL$WM_CASS_IN>:'*':WMInLoadList<I,COL$WM_SLOT_IN>
|
|
END
|
|
NEXT I
|
|
|
|
SelCnt = COUNT(SelectedRows,@FM) + (SelectedRows NE '')
|
|
IF SelCnt = 0 THEN RETURN
|
|
|
|
LockedWMIKeys = Get_Property(@WINDOW,'@LOCKED_WFRS')
|
|
|
|
IF LockedWMIKeys = '' THEN
|
|
|
|
Set_Status(0)
|
|
LockedWMIKeys = obj_WM_Wfrs('LockSet','WMI_WFRS':@RM:WMIWaferKeys) ;* Lock all WMI slots showing in the WM_In list
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
LoadSlotsLocked = 0
|
|
END ELSE
|
|
Set_Property(@WINDOW,'@LOCKED_WFRS',LockedWMIKeys)
|
|
LoadSlotsLocked = 1
|
|
END
|
|
END ELSE
|
|
LoadSlotsLocked = 1
|
|
END
|
|
|
|
IF LoadSlotsLocked THEN
|
|
|
|
SelLine = 1
|
|
|
|
FOR RL = 1 TO COUNT(ReactorLoadList,@FM) + (ReactorLoadList NE '')
|
|
IF ReactorLoadList<RL,COL$IN_CASS> = '' AND ReactorLoadList<RL,COL$WAFER_TYPE> = '' AND ReactorLoadList<RL,COL$USAGE> NE 'DUMMY' THEN
|
|
|
|
WMInCass = WMInLoadList<SelectedRows<SelLine>,COL$WM_CASS_IN>
|
|
WMInSlot = WMInLoadList<SelectedRows<SelLine>,COL$WM_SLOT_IN>
|
|
|
|
|
|
Set_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS',WMInCass,COL$IN_CASS:@FM:RL)
|
|
Set_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS',WMInSlot,COL$IN_SLOT:@FM:RL)
|
|
Set_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS','PROD',COL$WAFER_TYPE:@FM:RL)
|
|
|
|
SelLine += 1
|
|
|
|
PocketNo = Get_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS',COL$POCKET:@FM:RL)
|
|
Zone = Get_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS',COL$ZONE:@FM:RL)
|
|
|
|
oWParms = WONo:@RM:WOStep:@RM:WMInCass:@RM:WMInSlot:@RM:RDSNo:@RM:PocketNo:@RM:Zone
|
|
|
|
Set_Status(0)
|
|
|
|
obj_WM_In('RemoveWafer',oWParms)
|
|
IF Get_Status(errCode) THEN
|
|
* What do we do now Pierre?
|
|
END
|
|
|
|
END
|
|
UNTIL SelLine > SelCnt
|
|
NEXT RL
|
|
|
|
GOSUB UpdateWMIn
|
|
|
|
* Reactor table has been loaded
|
|
|
|
ReactorStyles = Send_Message(@WINDOW:'.REACTOR_TABLE','COLSTYLE',0,'')
|
|
|
|
ReactorStyles<COL$WAFER_TYPE> = BitAnd(ReactorStyles<COL$WAFER_TYPE>,BitNot(DROPDOWN_STYLE$))
|
|
|
|
ReactorStyles<COL$POCKET> = BitOr(ReactorStyles<COL$POCKET>,PROTECTED$)
|
|
ReactorStyles<COL$ZONE> = BitOr(ReactorStyles<COL$ZONE>,PROTECTED$)
|
|
ReactorStyles<COL$IN_CASS> = BitOr(ReactorStyles<COL$IN_CASS>,PROTECTED$)
|
|
ReactorStyles<COL$IN_SLOT> = BitOr(ReactorStyles<COL$IN_SLOT>,PROTECTED$)
|
|
ReactorStyles<COL$WAFER_TYPE> = BitOr(ReactorStyles<COL$WAFER_TYPE>,PROTECTED$)
|
|
|
|
Send_Message(@WINDOW:'.REACTOR_TABLE','COLSTYLE',0,ReactorStyles)
|
|
|
|
ReactorLoad = Get_Property(@WINDOW:'.REACTOR_TABLE','ARRAY')
|
|
|
|
WaferTypeColParms = Send_Message(@WINDOW:'.REACTOR_TABLE', 'DELETECOL', COL$WAFER_TYPE)
|
|
dummy = Send_Message(@WINDOW:'.REACTOR_TABLE', 'INSERTCOL',COL$WAFER_TYPE,WaferTypeColParms ) ;* This doesn't work correctly
|
|
columnwidth = Send_Message(@WINDOW:'.REACTOR_TABLE', "COLWIDTH", COL$WAFER_TYPE, WaferTypeColParms<4>)
|
|
|
|
Set_Property(@WINDOW:'.REACTOR_TABLE','ARRAY',ReactorLoad)
|
|
|
|
END ELSE
|
|
GOSUB UpdateWMIn ; * Couldn't get all of the locks, refresh the WM_IN List for a retry
|
|
END ;* End of check for LoadSlotsLocked
|
|
|
|
GOSUB REFRESH
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
UnloadMat:
|
|
* * * * * * *
|
|
|
|
ReactCtrl = @WINDOW:'.REACTOR_TABLE'
|
|
WMInCtrl = @WINDOW:'.WM_IN'
|
|
ReactorList = Get_Property(ReactCtrl,'LIST')
|
|
WONo = Get_Property(@WINDOW:'.WO_NO','TEXT')
|
|
WOStep = Get_Property(@WINDOW:'.WO_STEP','TEXT')
|
|
|
|
* Get PROD wafers in the reactor
|
|
|
|
LoadedMaterial = ''
|
|
WMIWaferKeys = ''
|
|
|
|
FOR I = COUNT(ReactorList,@FM) + (ReactorList NE '') TO 1 STEP -1
|
|
IF ReactorList<I,COL$WAFER_TYPE> = 'PROD' THEN
|
|
LoadedMaterial = INSERT(LoadedMaterial,1,0,0,I:@VM:ReactorList<I,COL$IN_CASS>:@VM:ReactorList<I,COL$IN_SLOT>)
|
|
END
|
|
NEXT I
|
|
|
|
LoadCount = COUNT(LoadedMaterial,@FM) + (LoadedMaterial NE '')
|
|
|
|
LoadSlotsLocked = Get_Property(@WINDOW,'@LOCKED_WFRS')
|
|
|
|
IF LoadSlotsLocked NE '' THEN
|
|
|
|
Set_Status(0)
|
|
LockedWMOKeys = obj_WM_Wfrs('UnlockSet','WMI_WFRS':@RM:LoadSlotsLocked)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
LoadSlotsUnlocked = 0
|
|
END ELSE
|
|
Set_Property(@WINDOW,'@LOCKED_WFRS','')
|
|
LoadSlotsUnlocked = 1
|
|
END
|
|
END ELSE
|
|
LoadSlotsUnlocked = 1
|
|
END
|
|
|
|
IF LoadSlotsUnlocked THEN
|
|
|
|
FOR I = LoadCount TO 1 STEP -1
|
|
ReactorLine = LoadedMaterial<I,1>
|
|
CassNo = LoadedMaterial<I,2>
|
|
SlotNo = LoadedMaterial<I,3>
|
|
|
|
Set_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS','',COL$IN_CASS:@FM:ReactorLine)
|
|
Set_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS','',COL$IN_SLOT:@FM:ReactorLine)
|
|
Set_Property(@WINDOW:'.REACTOR_TABLE','CELLPOS','',COL$WAFER_TYPE:@FM:ReactorLine)
|
|
|
|
obj_WM_In('ReplaceWafer',WONo:@RM:WOStep:@RM:CassNo:@RM:SlotNo)
|
|
|
|
NEXT I
|
|
|
|
GOSUB UpdateWMIn
|
|
|
|
ReactorStyles = Send_Message(@WINDOW:'.REACTOR_TABLE','COLSTYLE',0,'')
|
|
|
|
ReactorStyles<COL$WAFER_TYPE> = BitOr(ReactorStyles<COL$WAFER_TYPE>,DROPDOWN_STYLE$)
|
|
|
|
ReactorStyles<COL$POCKET> = BitAnd(ReactorStyles<COL$POCKET>,BitNot(PROTECTED$))
|
|
ReactorStyles<COL$ZONE> = BitAnd(ReactorStyles<COL$ZONE>,BitNot(PROTECTED$))
|
|
ReactorStyles<COL$IN_CASS> = BitAnd(ReactorStyles<COL$IN_CASS>,BitNot(PROTECTED$))
|
|
ReactorStyles<COL$IN_SLOT> = BitAnd(ReactorStyles<COL$IN_SLOT>,BitNot(PROTECTED$))
|
|
ReactorStyles<COL$WAFER_TYPE> = BitAnd(ReactorStyles<COL$WAFER_TYPE>,BitNot(PROTECTED$))
|
|
|
|
Send_Message(@WINDOW:'.REACTOR_TABLE','COLSTYLE',0,ReactorStyles)
|
|
Send_Message(@WINDOW:'.REACTOR_TABLE','COLFORMAT',COL$WAFER_TYPE,'':@VM:'TEST')
|
|
|
|
END ;* End of check for LoadSlotsLocked
|
|
|
|
GOSUB Refresh
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
RejMat:
|
|
* * * * * * *
|
|
RETURN ;* Dead on 1/22/07 JCH
|
|
|
|
WMInList = Get_Property(@WINDOW:'.WM_IN','LIST')
|
|
|
|
SelectedRows = Get_Property(@WINDOW:'.WM_IN','SELPOS')<2> ;* Returns list of selected row numbers
|
|
|
|
CONVERT @VM TO @FM in SelectedRows
|
|
|
|
SelCnt = COUNT(SelectedRows,@FM) + (SelectedRows NE '')
|
|
IF SelCnt = 0 THEN RETURN
|
|
|
|
WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP')
|
|
WOStep = Get_Property(@WINDOW:'.WO_STEP','DEFPROP')
|
|
RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP')
|
|
Reactor = Get_Property(@WINDOW:'.REACTOR_NO','DEFPROP')
|
|
|
|
WMInCassNos = ''
|
|
WMInSlots = ''
|
|
FOR I = 1 TO SelCnt
|
|
WMInCassNos<1,I> = WMInList<SelectedRows<I>,COL$WM_CASS_IN>
|
|
WMInSlots<1,I> = WMInList<SelectedRows<I>,COL$WM_SLOT_IN>
|
|
NEXT I
|
|
|
|
ncrParms = WONo:@RM
|
|
ncrParms := WOStep:@RM
|
|
ncrParms := '':@RM ;* Place holder for WO_MAT_CASS_NO
|
|
ncrParms := RDSNo:@RM
|
|
ncrParms := Reactor:@RM
|
|
ncrParms := 'PRE':@RM
|
|
ncrParms := WMInCassNos:@RM
|
|
ncrParms := WMINSlots:@RM
|
|
ncrParms := '':@RM ;* Pocket numbers for Post Epi NCR
|
|
|
|
Set_Status(0)
|
|
|
|
NCRNo = obj_NCR('Create',ncrParms) ;* Create new NCR for this wafer/group of wafers
|
|
|
|
Send_Message(@WINDOW:'.NCR_TABLE','INSERT',1,NCRNo)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
RETURN
|
|
END
|
|
|
|
FOR WMS = 1 TO COUNT(WMInCassNos,@VM) + (WMInCassNos NE '')
|
|
|
|
WMInCass = WMInCassNos<1,WMS>
|
|
WMInSlot = WMInSlots<1,WMS>
|
|
|
|
oWParms = WONo:@RM:WOStep:@RM:WMInCass:@RM:WMInSlot:@RM:'':@RM:'':@RM:'':@RM:NCRNo
|
|
|
|
Set_Status(0)
|
|
|
|
obj_WM_In('RemoveWafer',oWParms)
|
|
|
|
GOSUB UpdateWMIn
|
|
GOSUB UpdateNCR
|
|
|
|
NEXT WMS
|
|
|
|
Set_Property(@WINDOW:'.WM_IN','SELPOS',SelectedRows) ;* Toggle WM_IN select off
|
|
|
|
DetWindow = 'NCR'
|
|
DetKeys = NCRNo
|
|
DefaultRec = ''
|
|
RetKey = ''
|
|
RetWin = @WINDOW
|
|
RetPage = 1
|
|
RetCtrl = @WINDOW:'.WM_IN'
|
|
RetPos = 1:@FM:1
|
|
|
|
obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos)
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
ReactIR:
|
|
* * * * * * *
|
|
|
|
RowIndex = Parm1
|
|
|
|
IF RowIndex = '' THEN RETURN
|
|
|
|
CtrlID = @WINDOW:'.REACTOR_TABLE'
|
|
|
|
Dummy = Send_Message(CtrlID,'DELETE',RowIndex)
|
|
|
|
GOSUB Refresh
|
|
|
|
RETURN
|
|
|
|
|
|
|
|
* * * * * * *
|
|
ReactDR:
|
|
* * * * * * *
|
|
|
|
RowIndex = Parm1
|
|
RowData = Parm2
|
|
|
|
IF RowIndex = '' THEN RETURN
|
|
|
|
CtrlID = @WINDOW:'.REACTOR_TABLE'
|
|
|
|
Dummy = Send_Message(CtrlID, "INSERT", RowIndex, RowData)
|
|
|
|
GOSUB Refresh
|
|
|
|
RETURN
|
|
|
|
|
|
|
|
* * * * * * *
|
|
UpdateWMIn:
|
|
* * * * * * *
|
|
|
|
GOSUB Refresh
|
|
|
|
WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP')
|
|
WOStep = Get_Property(@WINDOW:'.WO_STEP','DEFPROP')
|
|
|
|
RemainingWafers = obj_WM_In('RemainingSlots',WONo:@RM:WoStep)
|
|
|
|
OpenProdPockets = Get_Property(@WINDOW:'.OPEN_PROD_POCKETS','DEFPROP')
|
|
OpenTestPockets = Get_Property(@WINDOW:'.OPEN_TEST_POCKETS','DEFPROP')
|
|
|
|
OpenPockets = OpenProdPockets + OpenTestPockets
|
|
|
|
NeededProduct = FIELD(RemainingWafers,@FM,1,OpenPockets)
|
|
|
|
FOR M = 1 TO OpenPockets
|
|
Set_Property(@WINDOW:'.WM_IN','CELLPOS',NeededProduct<M,1>,1:@FM:M)
|
|
Set_Property(@WINDOW:'.WM_IN','CELLPOS',NeededProduct<M,2>,2:@FM:M)
|
|
NEXT M
|
|
|
|
*SelectedRows = Get_Property(@WINDOW:'.WM_IN','SELPOS')<2>
|
|
|
|
FOR M = OpenPockets + 1 TO 25
|
|
Set_Property(@WINDOW:'.WM_IN','CELLPOS','',1:@FM:M)
|
|
Set_Property(@WINDOW:'.WM_IN','CELLPOS','',2:@FM:M)
|
|
NEXT M
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
UpdateNCR:
|
|
* * * * * * *
|
|
|
|
RDSNo = Get_Property(@WINDOW:'.RDS_NO','DEFPROP')
|
|
|
|
RDSRec = XLATE('RDS',RDSNo,'','X')
|
|
|
|
NCRKeys = RDSRec<RDS_NCR_KEYS$>
|
|
|
|
CONVERT @VM TO @FM IN NCRKeys
|
|
|
|
SlotNos = XLATE('NCR',NCRKeys,NCR_SLOT_NO$,'X')
|
|
CassNos = XLATE('NCR',NCRKeys,NCR_CASS_NO$,'X')
|
|
|
|
DispCnt = 1
|
|
FOR I = 1 TO COUNT(NCRKeys,@FM) + (NCRKeys NE '')
|
|
FOR N = 1 TO COUNT(CassNos<I>,@VM) + (CassNos<I> NE '')
|
|
Set_Property(@WINDOW:'.NCR_TABLE','CELLPOS',NCRKeys<I>,COL$NCR_NO:@FM:DispCnt)
|
|
Set_Property(@WINDOW:'.NCR_TABLE','CELLPOS',CassNos<I,N>,COL$CASS_NO:@FM:DispCnt)
|
|
Set_Property(@WINDOW:'.NCR_TABLE','CELLPOS',SlotNos<I,N>,COL$SLOT_NO:@FM:DispCnt)
|
|
DispCnt += 1
|
|
NEXT N
|
|
NEXT I
|
|
|
|
FOR M = DispCnt + 1 TO 25
|
|
Set_Property(@WINDOW:'.NCR_TABLE','CELLPOS','',COL$NCR_NO:@FM:M)
|
|
Set_Property(@WINDOW:'.NCR_TABLE','CELLPOS','',COL$CASS_NO:@FM:M)
|
|
Set_Property(@WINDOW:'.NCR_TABLE','CELLPOS','',COL$SLOT_NO:@FM:M)
|
|
NEXT M
|
|
|
|
RETURN
|
|
|
|
|
|
|