COMPILE FUNCTION obj_Graphite(Method,Parms) /* Methods for GRAPHITE table 08/20/2013 JCH - Initial Coding Properties: Methods: Install(GraphNo,ReactNo,DTM,ReactHrs,ReactWfrs,RL_Id) ;* Adds Reactor Installation line item to record Remove(GraphNo,ReactNo,DTM,ReactHrs,ReactWfrs,RL_Id,RDSWfrCnt) ;* Adds Removal information to Reactor Installation line item */ DECLARE FUNCTION Get_Status, Msg, Utility, obj_Tables, Send_Dyn, obj_Popup DECLARE SUBROUTINE Set_Status, Msg, obj_Tables, Send_Dyn DECLARE SUBROUTINE ErrMsg, Btree.Extract $INSERT MSG_EQUATES $INSERT GRAPHITE_EQUATES $INSERT REACTOR_EQUATES $INSERT REACT_READS_EQUATES EQU CRLF$ TO \0D0A\ EQU TAB$ TO CHAR(9) ErrTitle = 'Error in Stored Procedure "obj_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 = 'Install' ; GOSUB Install CASE Method = 'Remove' ; GOSUB Remove CASE Method = 'ClearRemove' ; GOSUB ClearRemove CASE Method = 'CurrStatus' ; GOSUB CurrStatus CASE Method = 'ServiceHrs' ; GOSUB ServiceHrs CASE Method = 'ServiceWfrs' ; GOSUB ServiceWfrs CASE Method = 'ServicePCRC' ; GOSUB ServicePCRC CASE Method = 'Serial_GRNo' ; GOSUB Serial_GRNo CASE Method = 'SplitSerial' ; GOSUB SplitSerial CASE Method = 'ReactWfrCnt' ; GOSUB ReactWfrCnt CASE Method = 'ReactHrs' ; GOSUB ReactHrs Case Method = 'CalcDesc' ; Gosub CalcDesc CASE 1 ErrorMsg = 'Unknown Method ':QUOTE(Method):' passed to routine.' END CASE IF ErrorMsg NE '' THEN Set_Status(-1,ErrTitle:@SVM:ErrorMsg) END RETURN Result * * * * * * * Install: * * * * * * * GraphNo = Parms[1,@RM] ReactNo = Parms[COL2()+1,@RM] ActionDTM = Parms[COL2()+1,@RM] ReactHrs = Parms[COL2()+1,@RM] ReactWfrs = Parms[COL2()+1,@RM] RL_Id = Parms[COL2()+1,@RM] IF GraphNo = '' THEN ErrorMsg = 'Null Parameter "GraphNo" passed to routine. (':Method:')' IF ReactNo = '' THEN ErrorMsg = 'Null Parameter "ReactNo" passed to routine. (':Method:')' IF ActionDTM = '' THEN ErrorMsg = 'Null Parameter "ActionDTM" passed to routine. (':Method:')' *IF ReactHrs = '' THEN ErrorMsg = 'Null Parameter "ReactHrs" passed to routine. (':Method:')' *IF ReactWfrs = '' THEN ErrorMsg = 'Null Parameter "ReactWfrs" passed to routine. (':Method:')' IF RL_Id = '' THEN ErrorMsg = 'Null Parameter "RL_Id" passed to routine. (':Method:')' IF ErrorMsg NE '' THEN RETURN thisActionDTM = ICONV(ActionDTM,'DT') IF thisActionDTM = '' THEN ErrorMsg = 'Invalid parameter ActionDTM ':QUOTE(ActionDTM):' passed to routine. (':Method:')' RETURN END otParms = 'GRAPHITE':@RM:GraphNo GraphiteRec = obj_Tables('ReadRec',otParms) IF Get_Status(errCode) THEN Set_Status(0) GraphiteRec = '' END /* IF GraphiteRec = ReactNo THEN ErrorMsg = 'GraphNo ':QUOTE(GraphNo):' is already in service in reactor ':ReactNo:'.' obj_Tables('UnlockRec',otParms) RETURN END */ GraphiteRec = INSERT(GraphiteRec,GRAPHITE_REACT_NO$,1,0,ReactNo) GraphiteRec = INSERT(GraphiteRec,GRAPHITE_INST_DTM$,1,0,thisActionDTM) GraphiteRec = INSERT(GraphiteRec,GRAPHITE_INST_REACT_HRS$,1,0,ReactHrs) GraphiteRec = INSERT(GraphiteRec,GRAPHITE_INST_REACT_WFRS$,1,0,ReactWfrs) GraphiteRec = INSERT(GraphiteRec,GRAPHITE_INST_RL_ID$,1,0,RL_Id) GraphiteRec = INSERT(GraphiteRec,GRAPHITE_RDS_WFR_CNT$,1,0,'') GraphiteRec = INSERT(GraphiteRec,GRAPHITE_REM_DTM$,1,0,'') GraphiteRec = INSERT(GraphiteRec,GRAPHITE_REM_REACT_HRS$,1,0,'') GraphiteRec = INSERT(GraphiteRec,GRAPHITE_REM_REACT_WFRS$,1,0,'') GraphiteRec = INSERT(GraphiteRec,GRAPHITE_REM_RL_ID$,1,0,'') otParms = FIELDSTORE(OtParms,@RM,4,0,GraphiteRec) obj_Tables('WriteRec',otParms) RETURN * * * * * * * Remove: * * * * * * * GraphNo = Parms[1,@RM] ReactNo = Parms[COL2()+1,@RM] ActionDTM = Parms[COL2()+1,@RM] ReactHrs = Parms[COL2()+1,@RM] ReactWfrs = Parms[COL2()+1,@RM] RL_Id = Parms[COL2()+1,@RM] RDSWfrCnt = Parms[COL2()+1,@RM] IF GraphNo = '' THEN ErrorMsg = 'Null Parameter "GraphNo" passed to routine. (':Method:')' IF ReactNo = '' THEN ErrorMsg = 'Null Parameter "ReactNo" passed to routine. (':Method:')' IF ActionDTM = '' THEN ErrorMsg = 'Null Parameter "ActionDTM" passed to routine. (':Method:')' *IF ReactHrs = '' THEN ErrorMsg = 'Null Parameter "ReactHrs" passed to routine. (':Method:')' *IF ReactWfrs = '' THEN ErrorMsg = 'Null Parameter "ReactWfrs" passed to routine. (':Method:')' *IF RL_Id = '' THEN ErrorMsg = 'Null Parameter "RL_Id" passed to routine. (':Method:')' *IF RDSWfrCnt = '' THEN ErrorMsg = 'Null Parameter "RDSWfrCnt" passed to routine. (':Method:')' IF ErrorMsg NE '' THEN RETURN thisActionDTM = ICONV(ActionDTM,'DT') IF thisActionDTM = '' THEN ErrorMsg = 'Invalid parameter ActionDTM ':QUOTE(ActionDTM):' passed to routine. (':Method:')' RETURN END otParms = 'GRAPHITE':@RM:GraphNo GraphiteRec = obj_Tables('ReadRec',otParms) IF Get_Status(errCode) THEN Set_Status(0) GraphiteRec = '' END IF GraphiteRec NE ReactNo THEN GraphiteRec = INSERT(GraphiteRec,GRAPHITE_REACT_NO$,1,0,ReactNo) GraphiteRec = INSERT(GraphiteRec,GRAPHITE_INST_DTM$,1,0,'') GraphiteRec = INSERT(GraphiteRec,GRAPHITE_INST_REACT_HRS$,1,0,'') GraphiteRec = INSERT(GraphiteRec,GRAPHITE_INST_REACT_WFRS$,1,0,'') GraphiteRec = INSERT(GraphiteRec,GRAPHITE_INST_RL_ID$,1,0,'') GraphiteRec = INSERT(GraphiteRec,GRAPHITE_RDS_WFR_CNT$,1,0,RDSWfrCnt) GraphiteRec = INSERT(GraphiteRec,GRAPHITE_REM_DTM$,1,0,thisActionDTM) GraphiteRec = INSERT(GraphiteRec,GRAPHITE_REM_REACT_HRS$,1,0,ReactHrs) GraphiteRec = INSERT(GraphiteRec,GRAPHITE_REM_REACT_WFRS$,1,0,ReactWfrs) GraphiteRec = INSERT(GraphiteRec,GRAPHITE_REM_RL_ID$,1,0,RL_Id) otParms = FIELDSTORE(OtParms,@RM,4,0,GraphiteRec) obj_Tables('WriteRec',otParms) *ErrorMsg = 'GraphNo ':QUOTE(GraphNo):' is not in service in reactor ':ReactNo:'.' *obj_Tables('UnlockRec',otParms) RETURN END GraphiteRec = RDSWfrCnt GraphiteRec = thisActionDTM GraphiteRec = ReactHrs GraphiteRec = ReactWfrs GraphiteRec = RL_Id otParms = FIELDSTORE(OtParms,@RM,4,0,GraphiteRec) obj_Tables('WriteRec',otParms) RETURN * * * * * * * ClearRemove: * * * * * * * GraphNo = Parms[1,@RM] ReactNo = Parms[COL2()+1,@RM] IF GraphNo = '' THEN ErrorMsg = 'Null Parameter "GraphNo" passed to routine. (':Method:')' IF ReactNo = '' THEN ErrorMsg = 'Null Parameter "ReactNo" passed to routine. (':Method:')' IF ErrorMsg NE '' THEN RETURN otParms = 'GRAPHITE':@RM:GraphNo GraphiteRec = obj_Tables('ReadRec',otParms) IF GraphiteRec = ReactNo THEN GraphiteRec = '' GraphiteRec = '' GraphiteRec = '' GraphiteRec = '' GraphiteRec = '' END otParms = FIELDSTORE(OtParms,@RM,4,0,GraphiteRec) obj_Tables('WriteRec',otParms) RETURN * * * * * * * CurrStatus: * * * * * * * IF NOT(ASSIGNED(GraphNo)) THEN GraphNo = Parms[1,@RM] IF NOT(ASSIGNED(GraphiteRec)) THEN GraphiteRec = Parms[COL2()+1,@RM] IF GraphNo = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter IF GraphiteRec = '' THEN GraphiteRec = XLATE('GRAPHITE',GraphNo,'','X') InstDTM = GraphiteRec RemDTM = GraphiteRec RetireDt = GraphiteRec Notes = GraphiteRec CONVERT @LOWER_CASE TO @UPPER_CASE IN NOtes BEGIN CASE CASE RetireDt NE '' ; Result = 'R' CASE InstDTM NE '' AND RemDTM = '' ; Result = 'I' CASE InstDTM NE '' AND RemDTM NE '' OR INDEX(Notes,'USED',1) ; Result = 'U' CASE InstDTM = '' AND RemDTM = '' ; Result = 'N' CASE 1 ; Result = '?' END CASE RETURN * * * * * * * ServiceHrs: * * * * * * * IF NOT(ASSIGNED(GraphNo)) THEN GraphNo = Parms[1,@RM] IF NOT(ASSIGNED(GraphiteRec)) THEN GraphiteRec = Parms[COL2()+1,@RM] IF GraphNo = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter IF GraphiteRec = '' THEN GraphiteRec = XLATE('GRAPHITE',GraphNo,'','X') LastRemDtm = GraphiteRec IF LastRemDTM = '' THEN ReactNo = GraphiteRec LastReadDTM = XLATE('REACTOR',ReactNo,REACTOR_LAST_READ_HRS_DTM$,'X') LastReadHrs = XLATE('REACT_READS',ReactNo:'*':LastReadDTM,REACT_READS_HOURS$,'X') END ELSE LastReadHrs = '' END Ans = '' IRCnt = COUNT(GraphiteRec,@VM) + (GraphiteRec NE '') FOR I = 1 TO IRCnt RemReactHrs = GraphiteRec InstReactHrs = GraphiteRec IF I = 1 AND LastReadHrs NE '' THEN ReactNo = GraphiteRec LastReadDTM = XLATE('REACTOR',ReactNo,25,'X') LastReadHrs = XLATE('REACT_READS',ReactNo:'*':LastReadDTM,1,'X') 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 * * * * * * * ServiceWfrs: * * * * * * * IF NOT(ASSIGNED(GraphNo)) THEN GraphNo = Parms[1,@RM] IF NOT(ASSIGNED(GraphiteRec)) THEN GraphiteRec = Parms[COL2()+1,@RM] IF GraphNo = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter IF GraphiteRec = '' THEN GraphiteRec = XLATE('GRAPHITE',GraphNo,'','X') LastRemDtm = GraphiteRec IF LastRemDTM = '' THEN ReactNo = GraphiteRec LastReadDTM = XLATE('REACTOR',ReactNo,REACTOR_LAST_READ_WFRS_DTM$,'X') LastReadWfrs = XLATE('REACT_READS',ReactNo:'*':LastReadDTM,REACT_READS_WAFER_CNT$,'X') END ELSE LastReadWfrs = '' END Ans = '' IRCnt = COUNT(GraphiteRec,@VM) + (GraphiteRec NE '') IF IRCnt = 0 THEN Ans = LastReadWfrs END ELSE FOR I = 1 TO IRCnt RemReactWfrs = GraphiteRec InstReactWfrs = GraphiteRec IF I = 1 AND LastReadWfrs NE '' THEN RemReactWfrs = LastReadWfrs END IF RemReactWfrs > InstReactWfrs AND NUM(InstReactWfrs) AND NUM(RemReactWfrs) THEN Ans<1,I> = RemReactWfrs - InstReactWfrs END ELSE Ans<1,I> = '' END NEXT I END Result = Ans RETURN Result * * * * * * * ServicePCRC: * * * * * * * IF NOT(ASSIGNED(GraphNo)) THEN GraphNo = Parms[1,@RM] IF NOT(ASSIGNED(GraphiteRec)) THEN GraphiteRec = Parms[COL2()+1,@RM] IF GraphNo = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter IF GraphiteRec = '' THEN GraphiteRec = XLATE('GRAPHITE',GraphNo,'','X') LastRemDtm = GraphiteRec IF LastRemDTM = '' THEN ReactNo = GraphiteRec LastReadDTM = XLATE('REACTOR',ReactNo,REACTOR_LAST_READ_WFRS_DTM$,'X') LastReadWfrs = XLATE('REACT_READS',ReactNo:'*':LastReadDTM,REACT_READS_WAFER_CNT$,'X') END ELSE LastReadWfrs = '' END Ans = '' IRCnt = COUNT(GraphiteRec,@VM) + (GraphiteRec NE '') IF IRCnt = 0 THEN Ans = LastReadWfrs END ELSE FOR I = 1 TO IRCnt RemReactWfrs = GraphiteRec InstReactWfrs = GraphiteRec ;* This should always be set to zero IF I = 1 AND LastReadWfrs NE ''THEN RemReactWfrs = LastReadWfrs END IF RemReactWfrs > InstReactWfrs AND NUM(InstReactWfrs) AND NUM(RemReactWfrs) THEN Ans<1,I> = RemReactWfrs - InstReactWfrs - GraphiteRec END ELSE Ans<1,I> = '' END NEXT I END Result = Ans RETURN * * * * * * * ReactWfrCnt: * * * * * * * IF NOT(ASSIGNED(GraphNo)) THEN GraphNo = Parms[1,@RM] IF NOT(ASSIGNED(GraphiteRec)) THEN GraphiteRec = Parms[COL2()+1,@RM] IF GraphNo = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter IF GraphiteRec = '' THEN GraphiteRec = XLATE('GRAPHITE',GraphNo,'','X') ReactNos = GraphiteRec ReactCnt = COUNT(ReactNos,@VM) + (ReactNos NE '') Ans = '' FOR I = 1 TO ReactCnt ReactNo = ReactNos<1,I> InstWfrCnt = GraphiteRec RemWfrCnt = GraphiteRec IF I = 1 AND RemWfrCnt = '' THEN LastReadDTM = XLATE( 'REACTOR', ReactNo, REACTOR_LAST_READ_WFRS_DTM$, 'X' ) RemWfrCnt = XLATE( 'REACT_READS' ,ReactNo:'*':LastReadDTM, REACT_READS_WAFER_CNT$, 'X' ) END Delta = '' IF InstWfrCnt NE '' THEN IF RemWfrCnt NE '' THEN IF RemWfrCnt >= InstWfrCnt THEN Delta = RemWfrCnt - InstWfrCnt END END ;* End of check for RemWfrCnt END ;* End of check for InstWfrCnt Ans<1,I> = Delta NEXT I Result = Ans RETURN * * * * * * * ReactHrs: * * * * * * * IF NOT(ASSIGNED(GraphNo)) THEN GraphNo = Parms[1,@RM] IF NOT(ASSIGNED(GraphiteRec)) THEN GraphiteRec = Parms[COL2()+1,@RM] IF GraphNo = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter IF GraphiteRec = '' THEN GraphiteRec = XLATE('GRAPHITE',GraphNo,'','X') ReactNos = GraphiteRec ReactCnt = COUNT(ReactNos,@VM) + (ReactNos NE '') Ans = '' FOR I = 1 TO ReactCnt ReactNo = ReactNos<1,I> InstHrs = GraphiteRec RemHrs = GraphiteRec IF I = 1 AND RemHrs = '' THEN LastReadDTM = XLATE( 'REACTOR', ReactNo, REACTOR_LAST_READ_HRS_DTM$, 'X' ) RemHrs = XLATE( 'REACT_READS' ,ReactNo:'*':LastReadDTM, REACT_READS_HOURS$, 'X' ) END Delta = '' IF InstHrs NE '' THEN IF RemHrs NE '' THEN IF RemHrs >= InstHrs THEN Delta = RemHrs - InstHrs END END ;* End of check for RemHrs END ;* End of check for InstHrs Ans<1,I> = Delta NEXT I Result = Ans return * * * * * * * Serial_GRNo: * * * * * * * * Temporary for conversion SerialNos = Parms[1,@RM] IF SerialNos = '' THEN RETURN OPEN 'DICT.GRAPHITE' TO DictGraphite ELSE RETURN END snCnt = COUNT(SerialNos,@VM) + (SerialNos NE '') FOR I = 1 TO snCnt SerialNo = SerialNos<1,I> IF SerialNo NE '' THEN SearchString = 'SERIAL':@VM:SerialNo:@FM Option = '' Flag = '' Btree.Extract(SearchString,'GRAPHITE',DictGraphite,GraphNo,Option,Flag) IF INDEX(GraphNo,@VM,1) THEN GraphNo = FIELD(GraphNo,@VM,1,3) Result<1,I> = GraphNo END ;* End of check for null SerialNo NEXT I RETURN * * * * * * * SplitSerial: * * * * * * * PartNo = Parms[1,@RM] IF PartNo = '' THEN ErrorMsg = 'Null Parameter "PartNo" passed to routine. (':Method:')' IF ErrorMsg NE '' THEN RETURN OPEN 'DICT.GRAPHITE' TO DictGraphite ELSE DEBUG RETURN END SelectSent = 'SERIAL':@VM:'[':PartNo:']':@FM Option = '' Flag = '' Btree.Extract(SelectSent,'GRAPHITE',DictGraphite,GraphNos,Option,Flag) IF Get_Status(errCode) THEN ErrMsg(errCode) RETURN END grCnt = COUNT(GraphNos,@VM) + (GraphNos NE '') FOR I = 1 TO grCnt GraphNo = GraphNos<1,I> otParms = 'GRAPHITE':@RM:GraphNo GraphiteRec = obj_Tables('ReadRec',otParms) Serial = GraphiteRec SWAP PartNo WITH '' IN Serial *Serial[1,LEN(PartNo)] = '' IF Serial[1,1] = '-' THEN Serial[1,1] = '' GraphiteRec = Serial GraphiteRec = PartNo otParms = FIELDSTORE(OtParms,@RM,4,0,GraphiteRec) obj_Tables('WriteRec',otParms) NEXT I Result = GraphNos RETURN * * * * * * * CalcDesc: * * * * * * * IF NOT(ASSIGNED(GraphNo)) THEN GraphNo = Parms[1,@RM] IF NOT(ASSIGNED(GraphiteRec)) THEN GraphiteRec = Parms[COL2()+1,@RM] IF GraphNo = '' THEN RETURN ;* This is used in the dictionary -> don't throw an error for a null parmeter IF GraphiteRec = '' THEN GraphiteRec = XLATE('GRAPHITE',GraphNo,'','X') Desc = GraphiteRec GRTypeDesc = obj_Popup('CodeDesc','GRAPHITE_TYPES':@RM:GraphiteRec) SuscSize = GraphiteRec PktQty = GraphiteRec PktSize = GraphiteRec IF INDEX(Desc,'2000',1) THEN CalcDesc = 'Kit 2000, ':GRTypeDesc END ELSE CalcDesc = GRTypeDesc END CalcDesc := ', ':SuscSize:'in' PktLabel = '' IF PktQty = 1 THEN PktLabel = ', Pkt' IF PktQty > 1 THEN PktLabel = ', Pkts' BEGIN CASE CASE PktSize NE '' AND PktQty NE '' ; CalcDesc := PktLabel:': ':PktQty:' at ':PktSize:'in' CASE PktSize EQ '' AND PktQty NE '' ; CalcDesc := PktLabel:': ':PktQty CASE PktSize NE '' AND PktQty EQ '' ; CalcDesc := ', ':PktSize:'in Pkt' CASE PktSize EQ '' AND PktQty EQ '' ; NULL END CASE Result = CalcDesc RETURN