COMPILE FUNCTION obj_OEE(Method,Parms) /* Calculations methods for OEE 12/13/2004 JCH - Initial Coding Properties: Methods: ReactorDetail(StartDt,EndDt,Reactors,CustNo) ;* Returns 4 digit IR Fiscal year for date passed in */ DECLARE FUNCTION Get_Status, Msg, Utility, obj_Tables, obj_RDS, Set_Property DECLARE SUBROUTINE Set_Status, ErrMsg, obj_Tables, Btree.Extract, Make.List, Send_Info $INSERT MSG_EQUATES $INSERT POPUP_EQUATES $INSERT OEE_RESULTS_EQUATES $INSERT WO_MASTER_SCHED_EQU EQU YELLOW$ TO 255 + (255*256) + (0*65536) ;* Full yellow - non application standard ErrTitle = 'Error in Stored Procedure "obj_OEE"' 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 = 'ReactorDetail' ; GOSUB ReactorDetail CASE 1 ; ErrorMsg = 'Unknown method ':QUOTE(Method):' passed to routine' END CASE IF ErrorMsg NE '' THEN Set_Status(-1,ErrTitle:@SVM:ErrorMsg) RETURN '' END RETURN Result * * * * * * * ReactorDetail: * * * * * * * StartDt = Parms[1,@RM] ;* Always passed in OCONV'd format EndDt = Parms[COL2()+1,@RM] Reactors = Parms[COL2()+1,@RM] CustNo = Parms[COL2()+1,@RM] IF NOT(ASSIGNED(StartDt)) THEN ErrorMsg = 'Unassigned parameter "StartDt" passed to routine. (':Method:').' IF NOT(ASSIGNED(EndDt)) THEN ErrorMsg = 'Unassigned parameter "EndDt" passed to routine. (':Method:').' IF StartDt = '' THEN ErrorMsg = 'Null parameter "StartDt" passed to routine. (':Method:').' IF NOT(ASSIGNED(Reactors)) THEN Reactors = '' IF NOT(ASSIGNED(CustNo)) THEN CustNo = '' IF ErrorMsg NE '' THEN RETURN thisStartDt = ICONV(StartDt,'D') IF thisStartDt = '' THEN ErrorMsg = 'Invalid Date ':QUOTE(StartDt):' passed to routine. (':Method:').' END IF EndDt = '' THEN EndDt = OCONV(Date(),'D4/') thisEndDt = Date() END ELSE thisEndDt = ICONV(EndDt,'D') IF thisEndDt = '' THEN ErrorMsg = 'Invalid Date ':QUOTE(EndDt):' passed to routine. (':Method:').' END END IF ErrorMsg THEN RETURN OPEN 'CONFIG' TO ConfigTable ELSE ErrorMsg = 'Unable to open CONFIG table. (':Method:').' RETURN END OPEN 'REACT_UTIL' TO DataTable ELSE ErrorMsg = 'Unable to open REACT_UTIL Table. (':Method:').' RETURN END OPEN 'DICT.REACT_UTIL' TO @DICT ELSE ErrorMsg = 'Unable to open DICT.REACT_UTIL Table. (':Method:').' RETURN END ReactModeCodes = '' ReactModes = '' PopupData = XLATE('SYSREPOSPOPUPS','LSL2**REACTOR_MODE',8,'X') ;* Retrieve List of Reactor modes from Popup record Code = '' FOR I = 1 TO COUNT(PopupData,@VM) + (@VM NE '') Code = PopupData<1,I,1> Desc = PopupData<1,I,2> LOCATE Code IN ReactModeCodes BY 'AL' USING @FM Setting Pos ELSE ReactModeCodes = INSERT(ReactModeCodes,Pos,0,0,Code) ReactModes = INSERT(ReactModes,Pos,0,0,Desc) ;* Put description in second value END NEXT I ReactModeCnt = COUNT(ReactModeCodes,@FM) + (ReactModeCodes NE '') OrgColor = Set_Property(@WINDOW:'.STATUS_LINE','BACKCOLOR',YELLOW$) IF Reactors = '' THEN *READV MaxReacts FROM ConfigTable,'WO_MAST_SCHED',MaxReacts$ ELSE * DEBUG *END FOR I = 20 TO 74 Reactors<-1> = I NEXT I END ReactorCnt = COUNT(Reactors,@FM) + (Reactors NE '') ReactModeHrs = STR(@FM,ReactorCnt-1) ;* This is the reactor mode array that contains basic reactor mode hour totals FOR I = 1 TO ReactorCnt ReactModeHrs = STR(@VM,ReactModeCnt-1) NEXT I ReactTotalHrs = STR(@FM,ReactorCnt-1) ProdTime = STR(@FM,ReactorCnt-1) StandbyTime = STR(@FM,ReactorCnt-1) EngineeringTime = STR(@FM,ReactorCnt-1) SchedDownTime = STR(@FM,ReactorCnt-1) UnSchedDownTime = STR(@FM,ReactorCnt-1) NonSchedTime = STR(@FM,ReactorCnt-1) MaintTime = STR(@FM,ReactorCnt-1) OEETotalHours = STR(@FM,ReactorCnt-1) ManufTime = STR(@FM,ReactorCnt-1) EquipUpTime = STR(@FM,ReactorCnt-1) EquipDownTime = STR(@FM,ReactorCnt-1) SEMITime = STR(@FM,ReactorCnt-1) ProdPcnt = STR(@FM,ReactorCnt-1) StandbyPcnt = STR(@FM,ReactorCnt-1) EngineeringPcnt = STR(@FM,ReactorCnt-1) SchedDownPcnt = STR(@FM,ReactorCnt-1) UnSchedDownPcnt = STR(@FM,ReactorCnt-1) NonSchedPcnt = STR(@FM,ReactorCnt-1) ManufPcnt = STR(@FM,ReactorCnt-1) EquipUpPcnt = STR(@FM,ReactorCnt-1) EquipDownPcnt = STR(@FM,ReactorCnt-1) SEMIPcnt = STR(@FM,ReactorCnt-1) OperUptimePcnt = STR(@FM,ReactorCnt-1) OperUtilPcnt = STR(@FM,ReactorCnt-1) TotUtilPcnt = STR(@FM,ReactorCnt-1) FOR R = 1 TO ReactorCnt Reactor = Reactors Send_Info('Selecting Reactor ':Reactors:' Run Data Sheets....') ReactorSearch = 'REACTOR':@VM:Reactors:@FM * Find Last last REACT_UTIL record with a Start Date PRIOR to Report Start Date SearchDt = thisStartDt LOOP Search = ReactorSearch Search := 'START_DATE':@VM:'=':OCONV(SearchDt,'D'):@FM BTREE.EXTRACT(Search,'REACT_UTIL',@DICT,StartKeys,'',flag) IF Get_Status(errCode) THEN DEBUG UNTIL StartKeys NE '' OR (thisStartDt - SearchDt > 30) SearchDt -= 1 REPEAT IF SearchDt NE thisStartDt THEN FirstKey = StartKeys[-1,'B':@VM] END ELSE FirstKey = '' END * Begin Selections of keys with start dates and with end dates Search = ReactorSearch Search := 'END_DATE':@VM:OCONV(thisStartDt-1,'D'):'~':OCONV(thisEndDt+1,'D'):@FM IF CustNo NE '' THEN Search := 'CUST_NO':@VM:CustNo:@FM END BTREE.EXTRACT(Search,'REACT_UTIL',@DICT,ENDKeys,'',flag) IF Get_Status(errCode) THEN DEBUG Search = ReactorSearch Search := 'START_DATE':@VM:OCONV(thisStartDt-1,'D'):'~':OCONV(thisEndDt+1,'D'):@FM IF CustNo NE '' THEN Search := 'CUST_NO':@VM:CustNo:@FM END BTREE.EXTRACT(Search,'REACT_UTIL',@DICT,StartKeys,'',flag) IF Get_Status(errCode) THEN DEBUG FOR I = 1 TO COUNT(StartKeys,@VM) + (StartKeys NE '') StartKey = StartKeys<1,I> LOCATE StartKey IN ENDKeys BY 'AR' USING @VM SETTING POS ELSE ENDKeys = INSERT(ENDKeys,1,Pos,0,StartKey) END NEXT I IF FirstKey NE '' THEN LOCATE FirstKey IN ENDKeys USING @VM SETTING Dummy ELSE ENDKeys = INSERT(ENDKeys,1,1,0,FirstKey) END END CONVERT @VM TO @FM IN ENDKeys Make.List('0', ENDKeys, DataTable, @DICT) StartDTM = ICONV(StartDt:' 12:00AM','DT') IF ICONV(EndDt,'D') >= Date() THEN EndDTM = ICONV(OCONV(Date(),'D'):' ':OCONV(Time(),'MTHS'),'DT') END ELSE EndDTM = ICONV(EndDt:' 11:59:59PM','DT') END ProdTimeAddModes = 'P':@VM:'U':@VM:'V':@VM:'Y':@VM:'Z' StandbyTimeAddModes = 'C':@VM:'Q':@VM:'T':@VM:'W':@VM:'G':@VM:'I':@VM:'K' EngineeringTimeAddModes = 'A':@VM:'O':@VM:'P1' SchedDowntimeAddModes = 'F':@VM:'J':@VM:'K':@VM:'L':@VM:'N':@VM:'M':@VM:'R':@VM:'H' UnSchedDownTimeAddModes = 'B':@VM:'E':@VM:'L' NonSchedTimeModes = 'S':@VM:'D' MaintTimeModes = 'M':@VM:'N':@VM:'K':@VM:'L' Done = 0 Send_Info('Building CrossTab Table....') LOOP READNEXT @ID ELSE Done = 1 UNTIL Done READ @Record FROM DataTable,@ID ELSE Msg( '', 'Unable to read ':@ID:' Key From REACT_UTIL Table...' ) GOTO Bail END *Reactor = {REACTOR} LinePos = R ReactModeCode = {MODE} LOCATE ReactModeCode IN ReactModeCodes USING @FM SETTING ColPos ELSE ErrMsg('Unknown Reactor Mode Code ':QUOTE(ReactModeCode):' in EXPORT_OEE routine.') GOTO Bottom END ModeStartDate = {START_DATE} ModeStartTime = {START_TIME} ModeEndDate = {END_DATE} ModeEndTime = {END_TIME} IF ModeStartDate = ModeEndDate THEN IF ModeEndTime NE '' THEN IF (ModeStartTime > ModeEndTime) THEN * Awwww S__T! found in the data ModeStartTime = {END_TIME} ModeEndTime = {START_TIME} END END END ModeStartDate = OCONV(ModeStartDate,'D4/') ModeStartTime = OCONV(ModeStartTime,'MTHS') ModeStartDTM = ICONV(ModeStartDate:' ':ModeStartTime,'DT') ModeEndDate = OCONV(ModeEndDate,'D4/') ModeEndTime = OCONV(ModeEndTime,'MTHS') ModeEndDTM = ICONV(ModeEndDate:' ':ModeEndTime,'DT') IF ModeEndDTM = '' THEN ModeEndDTM = EndDTM ModeHours = (ModeEndDTM - ModeStartDTM) * 24 BEGIN CASE CASE ModeStartDTM < StartDTM AND ModeEndDTM > EndDTM ModeHours = (EndDTM - StartDTM) * 24 CASE ModeStartDTM < StartDTM ModeHours = (ModeEndDTM - StartDTM) * 24 CASE ModeEndDTM > EndDTM AND ModeStartDTM < EndDTM ModeHours = (EndDTM - ModeStartDTM) * 24 END CASE ModeHours = ICONV(ModeHours,'MD2') ReactModeHrs = ReactModeHrs + ModeHours ReactTotalHrs = SUM(ReactModeHrs) LOCATE ReactModeCode IN ProdTimeAddModes USING @VM SETTING Dummy THEN ProdTime = ProdTime + ModeHours END LOCATE ReactModeCode IN StandbyTimeAddModes USING @VM SETTING DUMMY THEN StandbyTime = StandbyTime + ModeHours END LOCATE ReactModeCode IN EngineeringTimeAddModes USING @VM SETTING DUMMY THEN EngineeringTime = EngineeringTime + ModeHours END LOCATE ReactModeCode IN SchedDowntimeAddModes USING @VM SETTING DUMMY THEN SchedDownTime = SchedDownTime + ModeHours END LOCATE ReactModeCode IN UnSchedDownTimeAddModes USING @VM SETTING DUMMY THEN UnSchedDownTime = UnSchedDownTime + ModeHours END LOCATE ReactModeCode IN NonSchedTimeModes USING @VM SETTING DUMMY THEN NonSchedTime = NonSchedTime + ModeHours END LOCATE ReactModeCode IN MaintTimeModes USING @VM SETTING DUMMY THEN MaintTime = MaintTime + ModeHours END OEETotalHours = ProdTime + StandbyTime + EngineeringTime + SchedDownTime OEETotalHours = OEETotalHours + UnSchedDownTime + NonSchedTime IF OEETotalHours <= 0 THEN OEETotalHours = 1 ;* Divide by zero raised it's ugly head ManufTime = ProdTime + StandbyTime EquipUpTime = ManufTime + EngineeringTime EquipDownTime = SchedDownTime + UnSchedDownTime SEMITime = OEETotalHours - NonSchedTime ProdPcnt = ICONV((ProdTime/OEETotalHours)*100,'MD2') StandbyPcnt = ICONV((StandbyTime/OEETotalHours)*100,'MD2') EngineeringPcnt = ICONV((EngineeringTime/OEETotalHours)*100,'MD2') SchedDownPcnt = ICONV((SchedDownTime/OEETotalHours)*100,'MD2') UnSchedDownPcnt = ICONV((UnSchedDownTime/OEETotalHours)*100,'MD2') NonSchedPcnt = ICONV((NonSchedTime/OEETotalHours)*100,'MD2') ManufPcnt = ICONV((ManufTime/OEETotalHours)*100,'MD2') EquipUpPcnt = ICONV((EquipUpTime/OEETotalHours)*100,'MD2') EquipDownPcnt = ICONV((EquipDownTime/OEETotalHours)*100,'MD2') SEMIPcnt = ICONV((SEMITime/OEETotalHours)*100,'MD2') TotalTimePcnt = ProdPcnt + StandbyPcnt + EngineeringPcnt + SchedDownPcnt + UnSchedDownPcnt TotalTimePcnt = TotalTimePcnt + NonSchedPcnt IF SEMIPcnt > 0 THEN OperUptimePcnt = ICONV((EquipUpPcnt/SEMIPcnt)*100,'MD2') OperUtilPcnt = ICONV((ProdPcnt/SEMIPcnt)*100,'MD2') END ELSE OperUptimePcnt = '0' OperUtilPcnt = '0' END IF TotalTimePcnt > 0 THEN TotUtilPcnt = ICONV((ProdPcnt/TotalTimePcnt)*100,'MD2') END ELSE TotUtilPcnt = '0' END * * * * * * * Bottom: * * * * * * * REPEAT NEXT R * Get maintanence incidents OPEN 'DICT.REACTOR_LOG' TO DictVar ELSE ErrorMsg = 'Unable to open "DICT.REACTOR_LOG" in routine. (':Method:').' GOTO Bail END DownTimeOccurences = 0 FOR I = 1 TO ReactorCnt Reactor = Reactors Send_Info('Reactor ':Reactor:' ':'Extracting Reactor Log Data...') Search = 'REACTOR':@VM:Reactor:@FM Search := 'ENTRY_DATE':@VM:OCONV(thisStartDt-1,'D'):'~':OCONV(thisEndDt+1,'D'):@FM Search := 'CATEGORY':@VM:'M':@FM Btree.Extract(Search,'REACTOR_LOG',DictVar,ReactorLogKeys,'',flag) IF Get_Status(errCode) THEN DEBUG FOR N = 1 TO COUNT(ReactorLogKeys,@VM) + (ReactorLogKeys NE '') SchedFlags = XLATE('REACTOR_LOG',ReactorLogKeys<1,N>,26,'X') *IF SchedFlags<1,1> = 0 THEN IF NOT(SchedFlags<1,1> = 1) THEN DownTimeOccurences += 1 END NEXT N NEXT I * Get wafer production information OPEN 'DICT.RDS' TO DictVar ELSE ErrorMsg = 'Unable to open "DICT.RDS" in routine. (':Method:').' GOTO Bail END WafersProdQtys = '' WafersRejQtys = '' WafersInQtys = '' ActualWaferRate = '' TargetWaferRate = '' FOR I = 1 TO ReactorCnt Reactor = Reactors Send_Info('Reactor ':Reactor:' ':'Extracting RDS Data...') Search = 'REACTOR':@VM:Reactor:@FM Search := 'DATE_IN':@VM:OCONV(thisStartDt-1,'D'):'~':OCONV(thisEndDt+1,'D'):@FM Btree.Extract(Search,'RDS',DictVar,RDSKeys,'',flag) IF Get_Status(errCode) THEN DEBUG WafersInQtys = SUM(XLATE('RDS',RDSKeys,41,'X')) ;* Wafers In WafersRejQtys = SUM(XLATE('RDS',RDSKeys,'TOT_REJ','X')) ;* Total Rejects WafersProdQtys = WafersInQtys - WafersRejQtys WfrsPerHourData = obj_RDS('WafersPerHour',RDSKeys) ;* Returns overall average results for all RDSNos passed in ActualWaferRate = WfrsPerHourData[1,@RM] ;* In OCONV'd MD2 format TargetWaferRate = WfrsPerHourData[COL2()+1,@RM] ;* In OCONV'd MD2 format NEXT I MTBFp = '' MTTRHours = '' OperAvail = '' ;* Operational Availability (Ao) OperUtil = '' ;* Operational Utilization (Uo) QualityRate = '' ;* Quality Rate (Qs) EquipEff = '' ;* Equip Efficiency OverallEquipEff = '' ;* Overall Equipment Efficiency (OEEBottlneck) FOR I = 1 TO ReactorCnt IF DownTimeOccurences <= 0 THEN DownTimeOccurence = 1 END ELSE DownTimeOccurence = DownTimeOccurences END MTBFp = ICONV((ProdTime / DownTimeOccurence),'MD0') MTTRHours = ICONV((MaintTime / DownTimeOccurence),'MD0') IF OEETotalHours <= 0 THEN OEETotalHours = 1 ;* Divide by zero raised it's ugly head OperAvail = ICONV(((OEETotalHours - (SchedDownTime + UnSchedDownTime))/OEETotalHours)*100,'MD2') Term1 = OCONV(ProdTime,'MD2')/OCONV(OEETotalHours,'MD2') Term2 = OCONV(SEMITime,'MD2') - OCONV(EquipDownTime,'MD2') Term3 = OCONV(SEMITime,'MD2') IF Term2 > 0 AND Term3 > 0 THEN OperUtil = ICONV((Term1/(Term2/Term3))*100,'MD2') END ELSE OperUtil = 0 END IF WafersInQtys > 0 THEN QualityRate = ICONV(((WafersInQtys - WafersRejQtys)/WafersInQtys)*100,'MD2') END ELSE QualityRate = 0 END IF TargetWaferRate > 0 THEN EquipEff = ICONV((ActualWaferRate/TargetWaferRate)*100,'MD2') END ELSE EquipEff = 0 END OverallEquipEff = OCONV(OperAvail/100,'MD2') * OCONV(EquipEff/100,'MD2') * OCONV(OperUtil/100,'MD2') * OCONV(QualityRate/100,'MD2') OverAllEquipEff = ICONV(OverAllEquipEff * 100,'MD2') NEXT I Send_Info(STR(' ',100)) *Set up column headers for result ColTitles = 'Reactor' FOR I = 1 TO COUNT(ReactModes,@FM) + (ReactModes NE '') ColTitles = ReactModes NEXT I ColTitles = 'Total Time' ColTitles = 'Production Time' ColTitles = 'Standby Time' ColTitles = 'Engineering Time' ColTitles = 'Sched DownTime' ColTitles = 'UnSched DownTime' ColTitles = 'NonSched Time' ColTitles = 'OEE Total Time' ColTitles = 'Manufact Time' ColTitles = 'Equip Uptime' ColTitles = 'Equip Downtime' ColTitles = 'Operations Time' ColTitles = 'Production' ColTitles = 'Standby' ColTitles = 'Engineering' ColTitles = 'Sched Down' ColTitles = 'Unsched Down' ColTitles = 'Non-Sched Down' ColTitles = 'Manufacturing' ColTitles = 'Equip Up' ColTitles = 'Equip Down' ColTitles = 'Operations' ColTitles = 'Operational Uptime' ColTitles = 'Operational Utilization' ColTitles = 'Total Utilization' ColTitles = 'MTBFp Hours' ColTitles = 'MTTR Hours' ColTitles = 'Oper Availablility (Ao)' ColTitles = 'Oper Utilization (Uo)' ColTitles = 'Quality Rate (Qs)' ColTitles = 'Equip Efficiency (E)' ColTitles = 'OEE Bottleneck' CONVERT @FM TO @VM IN ColTitles Result<-1> = ColTitles LineCount = COUNT(Reactors,@FM) + (Reactors NE '') ModeCount = COUNT(ReactModeCodes,@FM) + (ReactModeCodes NE '') FOR I = 1 TO LineCount PrintLine = Reactors FOR M = 1 TO ModeCount PrintLine<1,M+1> = OCONV(ReactModeHrs,'MD2') NEXT M PrintLine<1,M+1> = OCONV(ReactTotalHrs,'MD12') PrintLine<1,M+2> = OCONV(ProdTime,'MD12') PrintLine<1,M+3> = OCONV(StandbyTime,'MD12') PrintLine<1,M+4> = OCONV(EngineeringTime,'MD12') PrintLine<1,M+5> = OCONV(SchedDownTime,'MD12') PrintLine<1,M+6> = OCONV(UnSchedDownTime,'MD12') PrintLine<1,M+7> = OCONV(NonSchedTime,'MD12') PrintLine<1,M+8> = OCONV(OEETotalHours,'MD12') PrintLine<1,M+9> = OCONV(ManufTime,'MD12') PrintLine<1,M+10> = OCONV(EquipUpTime,'MD12') PrintLine<1,M+11> = OCONV(EquipDownTime,'MD12') PrintLine<1,M+12> = OCONV(SEMITime,'MD12') PrintLine<1,M+13> = OCONV(ProdPcnt,'MD2S%') PrintLine<1,M+14> = OCONV(StandbyPcnt,'MD2S%') PrintLine<1,M+15> = OCONV(EngineeringPcnt,'MD2S%') PrintLine<1,M+16> = OCONV(SchedDownPcnt,'MD2S%') PrintLine<1,M+17> = OCONV(UnSchedDownPcnt,'MD2S%') PrintLine<1,M+18> = OCONV(NonSchedPcnt,'MD2S%') PrintLine<1,M+19> = OCONV(ManufPcnt,'MD2S%') PrintLine<1,M+20> = OCONV(EquipUpPcnt,'MD2S%') PrintLine<1,M+21> = OCONV(EquipDownPcnt,'MD2S%') PrintLine<1,M+22> = OCONV(SEMIPcnt,'MD2S%') PrintLine<1,M+23> = OCONV(OperUptimePcnt,'MD2S%') PrintLine<1,M+24> = OCONV(OperUtilPcnt,'MD2S%') PrintLine<1,M+25> = OCONV(TotUtilPcnt,'MD2S%') PrintLine<1,M+26> = OCONV(MTBFp,'MD12') PrintLine<1,M+27> = OCONV(MTTRHours,'MD12') PrintLine<1,M+28> = OCONV(OperAvail,'MD2S%') PrintLine<1,M+29> = OCONV(OperUtil,'MD2S%') PrintLine<1,M+30> = OCONV(QualityRate,'MD2S%') PrintLine<1,M+31> = OCONV(EquipEff,'MD2S%') PrintLine<1,M+32> = OCONV(OverallEquipEff,'MD2S%') Result<-1> = PrintLine NEXT I * * * * * * * BAIL: * * * * * * * Dummy = Set_Property(@WINDOW:'.STATUS_LINE','BACKCOLOR',OrgColor) RETURN