425 lines
11 KiB
Plaintext
425 lines
11 KiB
Plaintext
COMPILE FUNCTION obj_React_Graphite(Method,Parms)
|
|
|
|
/*
|
|
Methods for REACT_GRAPHITE Graphite table
|
|
|
|
09/03/2013 JCH - Initial Coding
|
|
|
|
Properties:
|
|
|
|
Methods:
|
|
|
|
GraphChange(Reactor,Date,ReactLogID) ;* Creates new Line item for Graph Change
|
|
ReactUnload(Reactor,WafersOut) ;* Bumps Wafer Count on current (top) line item by WafersOut
|
|
|
|
*/
|
|
|
|
|
|
DECLARE FUNCTION Get_Status, Utility, obj_Tables
|
|
DECLARE SUBROUTINE Set_Status, ErrMsg, obj_Tables, Send_Dyn, obj_Graph, Btree.Extract
|
|
|
|
$INSERT REACTOR_EQUATES
|
|
$INSERT REACT_GRAPHITE_EQUATES
|
|
$INSERT GRAPHITE_EQUATES
|
|
$INSERT REACT_READS_EQUATES
|
|
|
|
ErrTitle = 'Error in Stored Procedure "obj_React_Graphite"'
|
|
ErrorMsg = ''
|
|
|
|
IF NOT(ASSIGNED(Method)) THEN ErrorMsg = 'Unassigned parameter "Method" passed to subroutine'
|
|
IF NOT(ASSIGNED(Parms)) THEN Parms = ''
|
|
|
|
IF ErrorMsg NE '' THEN
|
|
Set_Status(-1,ErrTitle:@SVM:ErrorMsg)
|
|
RETURN ''
|
|
END
|
|
|
|
Result = ''
|
|
|
|
BEGIN CASE
|
|
CASE Method = 'GraphChange' ; GOSUB GraphChange
|
|
CASE Method = 'ReactUnload' ; GOSUB ReactUnload
|
|
CASE Method = 'ServiceHrs' ; GOSUB ServiceHrs
|
|
CASE Method = 'ServiceWfrCnt' ; GOSUB ServiceWfrCnt
|
|
CASE Method = 'ServicePCRC' ; GOSUB ServicePCRC
|
|
|
|
CASE 1
|
|
ErrorMsg = 'Unknown Method ':Method:' passed to object routine.'
|
|
|
|
END CASE
|
|
|
|
IF ErrorMsg NE '' THEN
|
|
Set_Status(-1,ErrTitle:@SVM:ErrorMsg)
|
|
END
|
|
|
|
RETURN Result
|
|
|
|
|
|
* * * * * * *
|
|
GraphChange:
|
|
* * * * * * *
|
|
|
|
* This method is called from the WRITE event on the REACTOR_LOG window 10/1/2009 JCH
|
|
|
|
ReactorNo = Parms[1,@RM]
|
|
ChangeDtm = Parms[COL2()+1,@RM]
|
|
ReactLogID = Parms[COL2()+1,@RM]
|
|
NewGraphSerial = Parms[COL2()+1,@RM]
|
|
ReactHrs = Parms[COL2()+1,@RM]
|
|
ReactWfrCnt = Parms[COL2()+1,@RM]
|
|
|
|
IF ReactorNo = '' THEN ErrorMsg = 'Null Parameter "ReactorNo" passed to routine. (':Method:')'
|
|
IF ChangeDtm = '' THEN ErrorMsg = 'Null Parameter "ChangeDtm" passed to routine. (':Method:')'
|
|
IF ReactLogID = '' THEN ErrorMsg = 'Null Parameter "ReactLogID" passed to routine. (':Method:')'
|
|
IF InstGraphNo = '' THEN ErrorMsg = 'Null Parameter "InstGraphNo" passed to routine. (':Method:')'
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
thisChangeDtm = ICONV(ChangeDtm,'DT')
|
|
IF thisChangeDtm = '' THEN
|
|
ErrorMsg = 'Invalid value ':QUOTE(ChangeDtm):' passed in parameter "ChangeDtm". (':Method:')'
|
|
RETURN
|
|
END
|
|
|
|
DEBUG
|
|
|
|
** Convert NewGraphNo from Serial No to GraphNo
|
|
|
|
|
|
OPEN 'REACT_GRAPHITE' TO ReactGraphiteTable ELSE
|
|
DEBUG
|
|
RETURN
|
|
END
|
|
|
|
OPEN 'DICT.REACT_GRAPHITE' TO DictReactGraphite ELSE
|
|
RETURN
|
|
END
|
|
|
|
SearchString = 'REACT_NO':@VM:ReactorNo:@FM
|
|
Option = ''
|
|
Flag = ''
|
|
Btree.Extract(SearchString,'REACT_GRAPHITE',DictReactGraphite,RGKeys,Option,Flag)
|
|
|
|
IF Get_Status(ErrCode) THEN
|
|
DEBUG
|
|
END
|
|
|
|
|
|
* Get Currently Installed Graphite of this type currently installed in the reactor to be removed *
|
|
|
|
|
|
CurrInstGraphiteKeys = XLATE('REACTOR',ReactorNo,REACTOR_CURR_INST_GRAPHITE$,'X') ;* All graphites installed
|
|
|
|
cigCnt = COUNT(CurrInstGraphiteKeys,@VM) + (CurrInstGraphiteKeys NE '')
|
|
|
|
CurrInstGraphiteKey = ''
|
|
|
|
FOR I = 1 TO cigCnt
|
|
CurrInstGraphiteKey = CurrInstGraphiteKeys<1,I>
|
|
UNTIL FIELD(CurrInstGraphiteKey,'*',2) = GraphiteType ;* graphite with the same type
|
|
|
|
NEXT I
|
|
|
|
|
|
**** Close out the Reactor Service History log record *****
|
|
IF CurrInstGraphiteKey NE '' THEN
|
|
|
|
OtParms = 'REACT_GRAPHITE':@RM:CurrInstReactGraphKey
|
|
ReactGraphRec = obj_Tables('ReadRec',OtParms) ;* Read and lock REACT_GRAPHITE record.
|
|
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',OtParms)
|
|
RETURN
|
|
END
|
|
|
|
* Close out Graphite being removed
|
|
|
|
ReactGraphRec<REACT_GRAPHITE_REM_DTM$> = thisChangeDTM
|
|
ReactGraphRec<REACT_GRAPHITE_REM_RL_ID$> = ReactLogID
|
|
ReactGraphRec<REACT_GRAPHITE_REM_REACT_HRS$> = ReactHrs
|
|
ReactGraphRec<REACT_GRAPHITE_REM_REACT_WFR_CNT$> = ReactWfrCnt
|
|
|
|
OtParms = 'REACT_GRAPHITE':@RM:InstReactReactGraphKey
|
|
ReactGraphRec = obj_Tables('ReadRec',OtParms) ;* Read and lock REACT_GRAPHITE record.
|
|
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',OtParms)
|
|
RETURN
|
|
END
|
|
END ;* End of Reactor Graphite history Close
|
|
|
|
NewGraphiteKey = ReactorNo:'*':GraphiteType:'*':thisChangeDtm
|
|
|
|
|
|
NewGraphiteRec = XLATE('GRAPHITE',NewGraphNo,'','X')
|
|
NewGraphiteType = GraphiteRec<GRAPHITE_GR_TYPE$>
|
|
|
|
|
|
|
|
* Close out Graphite being removed
|
|
|
|
ReactGraphRec<REACT_GRAPHITE_REM_DTM$,1> = thisChangeDTM
|
|
ReactGraphRec<REACT_GRAPHITE_REM_RL_ID$,1> = ReactLogID
|
|
ReactGraphRec<REACT_GRAPHITE_REM_REACT_HRS$,1> = ReactHrs
|
|
ReactGraphRec<REACT_GRAPHITE_REM_REACT_WFR_CNT$,1> = ReactWfrCnt
|
|
|
|
IF ReactGraphRec<REACT_GRAPHITE_GR_NO$,1> NE '' THEN
|
|
|
|
Parms = ReactGraphRec<REACT_GRAPHITE_GR_NO$,1>:@RM
|
|
Parms := ReactorNo:@RM
|
|
Parms := ChangeDTM:@RM
|
|
Parms := ReactHrs:@RM
|
|
Parms := ReactWfrCnt:@RM
|
|
Parms := ReactLogID:@RM
|
|
Parms := ReactGraphRec<REACT_GRAPHITE_RDS_WAFER_CNT$,1>
|
|
|
|
Set_Status(0)
|
|
obj_Graph('Remove',Parms) ;* Update the existing tube record
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
obj_Tables('UnlockRec',OtParms)
|
|
RETURN
|
|
END
|
|
END
|
|
|
|
|
|
Parms = GraphNo:@RM
|
|
Parms := ReactorNo:@RM
|
|
Parms := ChangeDTM:@RM
|
|
Parms := ReactHrs:@RM
|
|
Parms := ReactWfrCnt:@RM
|
|
Parms := ReactLogID
|
|
|
|
Set_Status(0)
|
|
|
|
obj_Graph('Install',Parms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
ErrMsg(errCode)
|
|
|
|
obj_Graph('ClearRemove',GraphNo:@RM:ReactorNo) ;* Back out the Graph Remove already done
|
|
|
|
obj_Tables('UnlockRec',OtParms)
|
|
RETURN
|
|
END
|
|
|
|
* Insert new line item at top of list for new tube record
|
|
|
|
ReactGraphRec = INSERT(ReactGraphRec,REACT_GRAPHITE_INST_DTM$,1,0,thisChangeDtm)
|
|
ReactGraphRec = INSERT(ReactGraphRec,REACT_GRAPHITE_GR_NO$,1,0,GraphNo)
|
|
ReactGraphRec = INSERT(ReactGraphRec,REACT_GRAPHITE_INST_RL_ID$,1,0,ReactLogID)
|
|
ReactGraphRec = INSERT(ReactGraphRec,REACT_GRAPHITE_RDS_WAFER_CNT$,1,0,0) ;* Set Wafer Count to 0
|
|
|
|
ReactGraphRec = INSERT(ReactGraphRec,REACT_GRAPHITE_INST_REACT_HRS$,1,0,ReactHrs)
|
|
ReactGraphRec = INSERT(ReactGraphRec,REACT_GRAPHITE_INST_REACT_WFR_CNT$,1,0,ReactWfrCnt)
|
|
|
|
ReactGraphRec = INSERT(ReactGraphRec,REACT_GRAPHITE_REM_DTM$,1,0,'')
|
|
ReactGraphRec = INSERT(ReactGraphRec,REACT_GRAPHITE_REM_RL_ID$,1,0,'')
|
|
ReactGraphRec = INSERT(ReactGraphRec,REACT_GRAPHITE_REM_REACT_HRS$,1,0,'')
|
|
ReactGraphRec = INSERT(ReactGraphRec,REACT_GRAPHITE_INST_REACT_WFR_CNT$,1,0,'')
|
|
|
|
|
|
OtParms = FieldStore(OtParms,@RM,4,0,ReactGraphRec) ;* Put record in 4th field of OtParms
|
|
obj_Tables('WriteRec',OtParms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',OtParms)
|
|
END
|
|
|
|
RETURN
|
|
|
|
|
|
|
|
* * * * * * *
|
|
ReactUnload:
|
|
* * * * * * *
|
|
|
|
* This method is called from the Unload Signature Button Click event on the RDS window
|
|
|
|
ReactorNo = Parms[1,@RM]
|
|
WaferQty = Parms[COL2()+1,@RM]
|
|
|
|
IF ReactorNo = '' THEN ErrorMsg = 'Null Parameter "ReactorNo" passed to routine. (':Method:')'
|
|
IF WaferQty = '' THEN RETURN
|
|
|
|
IF ErrorMsg NE '' THEN RETURN
|
|
|
|
IF NOT(NUM(WaferQty)) THEN
|
|
ErrorMsg = 'Non-Numeric data ':QUOTE(WaferQty):' passed in parameter "WaferQty". (':Method:')'
|
|
RETURN
|
|
END
|
|
|
|
CurrInstGraphKeys = XLATE('REACTOR',ReactorNo,REACTOR_CURR_INST_GRAPHITE$,'X')
|
|
|
|
CIGCnt = COUNT(CurrInstGraphKeys,@VM) + (CurrInstGraphKeys NE '')
|
|
|
|
FOR I = 1 TO CIGCnt
|
|
|
|
CurrInstGraphKey = CurrInstGraphKeys<1,I>
|
|
|
|
OtParms = 'REACT_GRAPHITE':@RM:CurrInstGraphKey
|
|
ReactGraphRec = obj_Tables('ReadRec',OtParms) ;* Read and lock configuration record
|
|
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',OtParms)
|
|
RETURN
|
|
END
|
|
|
|
IF ReactGraphRec<REACT_GRAPHITE_RDS_WAFER_CNT$,1> = '' THEN ReactGraphRec<REACT_GRAPHITE_RDS_WAFER_CNT$,1> = 0 ;* Just in case stuff happens
|
|
|
|
ReactGraphRec<REACT_GRAPHITE_RDS_WAFER_CNT$,1> = ReactGraphRec<REACT_GRAPHITE_RDS_WAFER_CNT$,1> + WaferQty
|
|
|
|
OtParms = FieldStore(OtParms,@RM,4,0,ReactGraphRec) ;* Put record in 4th field of OtParms
|
|
obj_Tables('WriteRec',OtParms)
|
|
|
|
IF Get_Status(errCode) THEN
|
|
obj_Tables('UnlockRec',OtParms)
|
|
END
|
|
NEXT I
|
|
|
|
RETURN
|
|
|
|
|
|
|
|
* * * * * * *
|
|
ServiceHrs:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(ReactGraphKey)) THEN ReactGraphKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(ReactGraphRec)) THEN ReactGraphRec = Parms[COL2()+1,@RM]
|
|
|
|
IF ReactGraphKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
IF ReactGraphRec = '' THEN ReactGraphRec = XLATE('REACT_GRAPHITE',ReactNo,'','X')
|
|
|
|
ReactNo = @ID
|
|
LastReadDTM = XLATE('REACTOR',ReactNo,25,'X')
|
|
LastReadHrs = XLATE('REACT_READS',ReactNo:'*':LastReadDTM,1,'X')
|
|
|
|
Ans = ''
|
|
|
|
IRCnt = COUNT(ReactGraphRec<REACT_GRAPHITE_INST_REACT_HRS$>,@VM) + (ReactGraphRec<REACT_GRAPHITE_INST_REACT_HRS$> NE '')
|
|
|
|
FOR I = 1 TO IRCnt
|
|
|
|
RemReactHrs = ReactGraphRec<REACT_GRAPHITE_REM_REACT_HRS$,I>
|
|
InstReactHrs = ReactGraphRec<REACT_GRAPHITE_INST_REACT_HRS$,I>
|
|
|
|
IF I = 1 THEN
|
|
RemReactHrs = LastReadHrs
|
|
END
|
|
|
|
IF RemReactHrs > InstReactHrs AND NUM(InstReactHrs) AND NUM(RemReactHrs) THEN
|
|
Ans<1,I> = RemReactHrs - InstReactHrs
|
|
END ELSE
|
|
Ans<1,I> = ''
|
|
END
|
|
NEXT I
|
|
|
|
Result = Ans
|
|
|
|
RETURN
|
|
|
|
|
|
|
|
|
|
|
|
* * * * * * *
|
|
ServiceWfrCnt:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(ReactGraphKey)) THEN ReactGraphKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(ReactGraphRec)) THEN ReactGraphRec = Parms[COL2()+1,@RM]
|
|
|
|
IF ReactGraphKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
IF ReactGraphRec = '' THEN ReactGraphRec = XLATE('REACT_GRAPHITE',ReactNo,'','X')
|
|
|
|
ReactNo = @ID
|
|
LastReadDTM = XLATE('REACTOR',ReactNo,REACTOR_LAST_READ_WFRS_DTM$,'X')
|
|
LastReadWfrCnt = XLATE('REACT_READS',ReactNo:'*':LastReadDTM,REACT_READS_WAFER_CNT$,'X')
|
|
|
|
Ans = ''
|
|
|
|
IRCnt = COUNT(ReactGraphRec<REACT_GRAPHITE_INST_REACT_WFR_CNT$>,@VM) + (ReactGraphRec<REACT_GRAPHITE_INST_REACT_WFR_CNT$> NE '')
|
|
|
|
|
|
IF IRCnt = 0 THEN
|
|
Ans = LastReadWfrCnt
|
|
END ELSE
|
|
|
|
FOR I = 1 TO IRCnt
|
|
|
|
RemReactWfrCnt = ReactGraphRec<REACT_GRAPHITE_REM_REACT_WFR_CNT$,I>
|
|
InstReactWfrCnt = ReactGraphRec<REACT_GRAPHITE_INST_REACT_WFR_CNT$,I>
|
|
|
|
IF I = 1 THEN
|
|
RemReactWfrCnt = LastReadWfrCnt
|
|
END
|
|
|
|
IF RemReactWfrCnt > InstReactWfrCnt AND NUM(InstReactWfrCnt) AND NUM(RemReactWfrCnt) THEN
|
|
Ans<1,I> = RemReactWfrCnt - InstReactWfrCnt
|
|
END ELSE
|
|
Ans<1,I> = ''
|
|
END
|
|
|
|
NEXT I
|
|
END
|
|
|
|
Result = Ans
|
|
|
|
RETURN Result
|
|
|
|
|
|
|
|
|
|
|
|
|
|
* * * * * * *
|
|
ServicePCRC:
|
|
* * * * * * *
|
|
|
|
IF NOT(ASSIGNED(ReactGraphKey)) THEN ReactGraphKey = Parms[1,@RM]
|
|
IF NOT(ASSIGNED(ReactGraphRec)) THEN ReactGraphRec = Parms[COL2()+1,@RM]
|
|
|
|
IF ReactGraphKey = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter
|
|
|
|
IF ReactGraphRec = '' THEN ReactGraphRec = XLATE('REACT_GRAPHITE',ReactNo,'','X')
|
|
|
|
ReactNo = ReactGraphKey[1,'*']
|
|
LastReadDTM = XLATE('REACTOR',ReactNo,REACTOR_LAST_READ_WFRS_DTM$,'X')
|
|
LastReadWfrCnt = XLATE('REACT_READS',ReactNo:'*':LastReadDTM,REACT_READS_WAFER_CNT$,'X')
|
|
|
|
Ans = ''
|
|
|
|
IRCnt = COUNT(ReactGraphRec<REACT_GRAPHITE_INST_REACT_WFR_CNT$>,@VM) + (ReactGraphRec<REACT_GRAPHITE_INST_REACT_WFR_CNT$> NE '')
|
|
|
|
IF IRCnt = 0 THEN
|
|
Ans = LastReadWfrCnt - ReactGraphRec<REACT_GRAPHITE_RDS_WAFER_CNT$,1>
|
|
END ELSE
|
|
FOR I = 1 TO IRCnt
|
|
|
|
RemReactWfrCnt = ReactGraphRec<REACT_GRAPHITE_REM_REACT_WFR_CNT$,I>
|
|
InstReactWfrCnt = ReactGraphRec<REACT_GRAPHITE_INST_REACT_WFR_CNT$,I> ;* This should always be set to zero
|
|
|
|
IF I = 1 THEN
|
|
RemReactWfrCnt = LastReadWfrCnt
|
|
END
|
|
|
|
IF RemReactWfrCnt > InstReactWfrCnt AND NUM(InstReactWfrCnt) AND NUM(RemReactWfrCnt) THEN
|
|
Ans<1,I> = RemReactWfrCnt - InstReactWfrCnt - ReactGraphRec<REACT_GRAPHITE_RDS_WAFER_CNT$,I>
|
|
END ELSE
|
|
Ans<1,I> = ''
|
|
END
|
|
|
|
NEXT I
|
|
END
|
|
|
|
Result = Ans
|
|
|
|
RETURN
|
|
|
|
|
|
|