open-insight/LSL2/STPROC/OBJ_OEE_ORG.txt
2024-05-22 14:06:46 -07:00

635 lines
20 KiB
Plaintext

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
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
IF Reactors = '' THEN LimitReactors = 0 ELSE LimitReactors = 1
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
OrgColor = Set_Property(@WINDOW:'.STATUS_LINE','BACKCOLOR',YELLOW$)
Send_Info('Selecting Run Data Sheets....')
* Begin Selections of keys with start dates and with end dates
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 = 'START_DATE':@VM:OCONV(thisStartDt-1,'D'):'~':OCONV(thisEndDt+1,'D'):@FM
Search = 'START_DATE':@VM:OCONV(thisStartDt-10,'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
CONVERT @VM TO @FM IN ENDKeys
Make.List('0', ENDKeys, DataTable, @DICT)
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 '')
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'
StandbyTimeAddModes = 'C':@VM:'Q':@VM:'T':@VM:'W'
EngineeringTimeAddModes = 'A':@VM:'O'
SchedDowntimeAddModes = 'F':@VM:'J':@VM:'K':@VM:'L':@VM:'N':@VM:'M':@VM:'R'
UnSchedDownTimeAddModes = 'B':@VM:'E':@VM:'G':@VM:'H':@VM:'I'
NonSchedTimeModes = 'S':@VM:'D'
MaintTimeModes = 'M':@VM:'K':@VM:'L':@VM:'N'
Done = 0
IF LimitReactors THEN
ReactorCnt = COUNT(Reactors,@FM) + (Reactors NE '')
ReactModeHrs = STR(@FM,ReactorCnt-1) ;* This is the reactor mode array that contains basic reactor mode hour totals <ReactLine,ModeCol>
FOR I = 1 TO ReactorCnt
ReactModeHrs<I> = 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)
END ELSE
ReactModeHrs = '' ;* This is the reactor mode array that contains basic reactor mode hour totals <ReactLine,ModeCol>
ReactTotalHrs = ''
ProdTime = '' ;* Buckets for OEE results @FM'd by reactor
StandbyTime = ''
EngineeringTime = ''
SchedDownTime = ''
UnSchedDownTime = ''
NonSchedTime = ''
MaintTime = ''
OEETotalHours = ''
ManufTime = ''
EquipUpTime = ''
EquipDownTime = ''
SEMITime = ''
ProdPcnt = ''
StandbyPcnt = ''
EngineeringPcnt = ''
SchedDownPcnt = ''
UnSchedDownPcnt = ''
NonSchedPcnt = ''
ManufPcnt = ''
EquipUpPcnt = ''
EquipDownPcnt = ''
SEMIPcnt = ''
OperUptimePcnt = ''
OperUtilPcnt = ''
TotUtilPcnt = ''
END
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}
IF LimitReactors THEN
LOCATE Reactor IN Reactors BY 'AR' USING @FM SETTING LinePos ELSE
GOTO Bottom ;* Report only on the Reactors entered in the collector window
END
END ELSE
LOCATE Reactor IN Reactors BY 'AR' USING @FM SETTING LinePos ELSE
Reactors = INSERT(Reactors,LinePos,0,0,Reactor)
ReactModeHrs = INSERT(ReactModeHrs,LinePos,0,0,STR(@VM,ReactModeCnt-1))
ProdTime = INSERT(ProdTime,LinePos,0,0,'')
StandbyTime = INSERT(StandbyTime,LinePos,0,0,'')
EngineeringTime = INSERT(EngineeringTime,LinePos,0,0,'')
SchedDownTime = INSERT(SchedDownTime,LinePos,0,0,'')
UnSchedDownTime = INSERT(UnSchedDownTime,LinePos,0,0,'')
NonSchedTime = INSERT(NonSchedTime,LinePos,0,0,'')
OEETotalHours = INSERT(OEETotalHours,LinePos,0,0,'')
ManufTime = INSERT(ManufTime,LinePos,0,0,'')
EquipUpTime = INSERT(EquipUpTime,LinePos,0,0,'')
EquipDownTime = INSERT(EquipDownTime,LinePos,0,0,'')
SEMITime = INSERT(SEMITime,LinePos,0,0,'')
ProdPcnt = INSERT(ProdPcnt,LinePos,0,0,'')
StandbyPcnt = INSERT(StandbyPcnt,LinePos,0,0,'')
EngineeringPcnt = INSERT(EngineeringPcnt,LinePos,0,0,'')
SchedDownPcnt = INSERT(SchedDownPcnt,LinePos,0,0,'')
UnSchedDownPcnt = INSERT(UnSchedDownPcnt,LinePos,0,0,'')
NonSchedPcnt = INSERT(NonSchedPcnt,LinePos,0,0,'')
ManufPcnt = INSERT(ManufPcnt,LinePos,0,0,'')
EquipUpPcnt = INSERT(EquipUpPcnt,LinePos,0,0,'')
EquipDownPcnt = INSERT(EquipDownPcnt,LinePos,0,0,'')
SEMIPcnt = INSERT(SEMIPcnt,LinePos,0,0,'')
OperUptimePcnt = INSERT(OperUptimePcnt,LinePos,0,0,'')
OperUtilPcnt = INSERT(OperUtilPcnt,LinePos,0,0,'')
TotUtilPcnt = INSERT(TotUtilPcnt,LinePos,0,0,'')
END
END
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<LinePos,ColPos> = ReactModeHrs<LinePos,ColPos> + ModeHours
ReactTotalHrs<LinePos> = SUM(ReactModeHrs<LinePos>)
LOCATE ReactModeCode IN ProdTimeAddModes USING @VM SETTING Dummy THEN
ProdTime<LinePos> = ProdTime<LinePos> + ModeHours
END
LOCATE ReactModeCode IN StandbyTimeAddModes USING @VM SETTING DUMMY THEN
StandbyTime<LinePos> = StandbyTime<LinePos> + ModeHours
END
LOCATE ReactModeCode IN EngineeringTimeAddModes USING @VM SETTING DUMMY THEN
EngineeringTime<LinePos> = EngineeringTime<LinePos> + ModeHours
END
LOCATE ReactModeCode IN SchedDowntimeAddModes USING @VM SETTING DUMMY THEN
SchedDownTime<LinePos> = SchedDownTime<LinePos> + ModeHours
END
LOCATE ReactModeCode IN UnSchedDownTimeAddModes USING @VM SETTING DUMMY THEN
UnSchedDownTime<LinePos> = UnSchedDownTime<LinePos> + ModeHours
END
LOCATE ReactModeCode IN NonSchedTimeModes USING @VM SETTING DUMMY THEN
NonSchedTime<LinePos> = NonSchedTime<LinePos> + ModeHours
END
LOCATE ReactModeCode IN MaintTimeModes USING @VM SETTING DUMMY THEN
MaintTime<LinePos> = MaintTime<LinePos> + ModeHours
END
OEETotalHours<LinePos> = ProdTime<LinePos> + StandbyTime<LinePos> + EngineeringTime<LinePos> + SchedDownTime<LinePos>
OEETotalHours<LinePos> = OEETotalHours<LinePos> + UnSchedDownTime<LinePos> + NonSchedTime<LinePos>
IF OEETotalHours<LinePos> <= 0 THEN OEETotalHours<LinePos> = 1 ;* Divide by zero raised it's ugly head
ManufTime<LinePos> = ProdTime<LinePos> + StandbyTime<LinePos>
EquipUpTime<LinePos> = ManufTime<LinePos> + EngineeringTime<LinePos>
EquipDownTime<LinePos> = SchedDownTime<LinePos> + UnSchedDownTime<LinePos>
SEMITime<LinePos> = OEETotalHours<LinePos> - NonSchedTime<LinePos>
ProdPcnt<LinePos> = ICONV((ProdTime<LinePos>/OEETotalHours<LinePos>)*100,'MD2')
StandbyPcnt<LinePos> = ICONV((StandbyTime<LinePos>/OEETotalHours<LinePos>)*100,'MD2')
EngineeringPcnt<LinePos> = ICONV((EngineeringTime<LinePos>/OEETotalHours<LinePos>)*100,'MD2')
SchedDownPcnt<LinePos> = ICONV((SchedDownTime<LinePos>/OEETotalHours<LinePos>)*100,'MD2')
UnSchedDownPcnt<LinePos> = ICONV((UnSchedDownTime<LinePos>/OEETotalHours<LinePos>)*100,'MD2')
NonSchedPcnt<LinePos> = ICONV((NonSchedTime<LinePos>/OEETotalHours<LinePos>)*100,'MD2')
ManufPcnt<LinePos> = ICONV((ManufTime<LinePos>/OEETotalHours<LinePos>)*100,'MD2')
EquipUpPcnt<LinePos> = ICONV((EquipUpTime<LinePos>/OEETotalHours<LinePos>)*100,'MD2')
EquipDownPcnt<LinePos> = ICONV((EquipDownTime<LinePos>/OEETotalHours<LinePos>)*100,'MD2')
SEMIPcnt<LinePos> = ICONV((SEMITime<LinePos>/OEETotalHours<LinePos>)*100,'MD2')
TotalTimePcnt = ProdPcnt<LinePos> + StandbyPcnt<LinePos> + EngineeringPcnt<LinePos> + SchedDownPcnt<LinePos> + UnSchedDownPcnt<LinePos>
TotalTimePcnt = TotalTimePcnt + NonSchedPcnt<LinePos>
IF SEMIPcnt<LinePos> > 0 THEN
OperUptimePcnt<LinePos> = ICONV((EquipUpPcnt<LinePos>/SEMIPcnt<LinePos>)*100,'MD2')
OperUtilPcnt<LinePos> = ICONV((ProdPcnt<LinePos>/SEMIPcnt<LinePos>)*100,'MD2')
END ELSE
OperUptimePcnt<LinePos> = '0'
OperUtilPcnt<LinePos> = '0'
END
IF TotalTimePcnt > 0 THEN
TotUtilPcnt<LinePos> = ICONV((ProdPcnt<LinePos>/TotalTimePcnt)*100,'MD2')
END ELSE
TotUtilPcnt<LinePos> = '0'
END
* * * * * * *
Bottom:
* * * * * * *
REPEAT
ReactorCnt = COUNT(Reactors,@FM) + (Reactors NE '')
* 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<I>
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<I>
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<I> = SUM(XLATE('RDS',RDSKeys,41,'X')) ;* Wafers In
WafersRejQtys<I> = SUM(XLATE('RDS',RDSKeys,'TOT_REJ','X')) ;* Total Rejects
WafersProdQtys<I> = WafersInQtys<I> - WafersRejQtys<I>
WfrsPerHourData = obj_RDS('WafersPerHour',RDSKeys) ;* Returns overall average results for all RDSNos passed in
ActualWaferRate<I> = WfrsPerHourData[1,@RM] ;* In OCONV'd MD2 format
TargetWaferRate<I> = 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<I> <= 0 THEN
DownTimeOccurence = 1
END ELSE
DownTimeOccurence = DownTimeOccurences<I>
END
MTBFp<I> = ICONV((ProdTime<I> / DownTimeOccurence),'MD0')
MTTRHours<I> = ICONV((MaintTime<I> / DownTimeOccurence),'MD0')
OperAvail<I> = ICONV(((OEETotalHours<I> - (SchedDownTime<I> + UnSchedDownTime<I>))/OEETotalHours<I>)*100,'MD2')
Term1 = OCONV(ProdTime<I>,'MD2')/OCONV(OEETotalHours<I>,'MD2')
Term2 = OCONV(SEMITime<I>,'MD2') - OCONV(EquipDownTime<I>,'MD2')
Term3 = OCONV(SEMITime<I>,'MD2')
IF Term2 > 0 AND Term3 > 0 THEN
OperUtil<I> = ICONV((Term1/(Term2/Term3))*100,'MD2')
END ELSE
OperUtil<I> = 0
END
IF WafersInQtys<I> > 0 THEN
QualityRate<I> = ICONV(((WafersInQtys<I> - WafersRejQtys<I>)/WafersInQtys<I>)*100,'MD2')
END ELSE
QualityRate<I> = 0
END
IF TargetWaferRate<I> > 0 THEN
EquipEff<I> = ICONV((ActualWaferRate<I>/TargetWaferRate<I>)*100,'MD2')
END ELSE
EquipEff<I> = 0
END
OverallEquipEff<I> = OCONV(OperAvail<I>/100,'MD2') * OCONV(EquipEff<I>/100,'MD2') * OCONV(OperUtil<I>/100,'MD2') * OCONV(QualityRate<I>/100,'MD2')
OverAllEquipEff<I> = ICONV(OverAllEquipEff<I> * 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<I+1> = ReactModes<I>
NEXT I
ColTitles<I+1> = 'Total Time'
ColTitles<I+2> = 'Production Time'
ColTitles<I+3> = 'Standby Time'
ColTitles<I+4> = 'Engineering Time'
ColTitles<I+5> = 'Sched DownTime'
ColTitles<I+6> = 'UnSched DownTime'
ColTitles<I+7> = 'NonSched Time'
ColTitles<I+8> = 'OEE Total Time'
ColTitles<I+9> = 'Manufact Time'
ColTitles<I+10> = 'Equip Uptime'
ColTitles<I+11> = 'Equip Downtime'
ColTitles<I+12> = 'Operations Time'
ColTitles<I+13> = 'Production'
ColTitles<I+14> = 'Standby'
ColTitles<I+15> = 'Engineering'
ColTitles<I+16> = 'Sched Down'
ColTitles<I+17> = 'Unsched Down'
ColTitles<I+18> = 'Non-Sched Down'
ColTitles<I+19> = 'Manufacturing'
ColTitles<I+20> = 'Equip Up'
ColTitles<I+21> = 'Equip Down'
ColTitles<I+22> = 'Operations'
ColTitles<I+23> = 'Operational Uptime'
ColTitles<I+24> = 'Operational Utilization'
ColTitles<I+25> = 'Total Utilization'
ColTitles<I+26> = 'MTBFp Hours'
ColTitles<I+27> = 'MTTR Hours'
ColTitles<I+28> = 'Oper Availablility (Ao)'
ColTitles<I+29> = 'Oper Utilization (Uo)'
ColTitles<I+30> = 'Quality Rate (Qs)'
ColTitles<I+31> = 'Equip Efficiency (E)'
ColTitles<I+32> = '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<I>
FOR M = 1 TO ModeCount
PrintLine<1,M+1> = OCONV(ReactModeHrs<I,M>,'MD2')
NEXT M
PrintLine<1,M+1> = OCONV(ReactTotalHrs<I>,'MD12')
PrintLine<1,M+2> = OCONV(ProdTime<I>,'MD12')
PrintLine<1,M+3> = OCONV(StandbyTime<I>,'MD12')
PrintLine<1,M+4> = OCONV(EngineeringTime<I>,'MD12')
PrintLine<1,M+5> = OCONV(SchedDownTime<I>,'MD12')
PrintLine<1,M+6> = OCONV(UnSchedDownTime<I>,'MD12')
PrintLine<1,M+7> = OCONV(NonSchedTime<I>,'MD12')
PrintLine<1,M+8> = OCONV(OEETotalHours<I>,'MD12')
PrintLine<1,M+9> = OCONV(ManufTime<I>,'MD12')
PrintLine<1,M+10> = OCONV(EquipUpTime<I>,'MD12')
PrintLine<1,M+11> = OCONV(EquipDownTime<I>,'MD12')
PrintLine<1,M+12> = OCONV(SEMITime<I>,'MD12')
PrintLine<1,M+13> = OCONV(ProdPcnt<I>,'MD2S%')
PrintLine<1,M+14> = OCONV(StandbyPcnt<I>,'MD2S%')
PrintLine<1,M+15> = OCONV(EngineeringPcnt<I>,'MD2S%')
PrintLine<1,M+16> = OCONV(SchedDownPcnt<I>,'MD2S%')
PrintLine<1,M+17> = OCONV(UnSchedDownPcnt<I>,'MD2S%')
PrintLine<1,M+18> = OCONV(NonSchedPcnt<I>,'MD2S%')
PrintLine<1,M+19> = OCONV(ManufPcnt<I>,'MD2S%')
PrintLine<1,M+20> = OCONV(EquipUpPcnt<I>,'MD2S%')
PrintLine<1,M+21> = OCONV(EquipDownPcnt<I>,'MD2S%')
PrintLine<1,M+22> = OCONV(SEMIPcnt<I>,'MD2S%')
PrintLine<1,M+23> = OCONV(OperUptimePcnt<I>,'MD2S%')
PrintLine<1,M+24> = OCONV(OperUtilPcnt<I>,'MD2S%')
PrintLine<1,M+25> = OCONV(TotUtilPcnt<I>,'MD2S%')
PrintLine<1,M+26> = OCONV(MTBFp<I>,'MD12')
PrintLine<1,M+27> = OCONV(MTTRHours<I>,'MD12')
PrintLine<1,M+28> = OCONV(OperAvail<I>,'MD2S%')
PrintLine<1,M+29> = OCONV(OperUtil<I>,'MD2S%')
PrintLine<1,M+30> = OCONV(QualityRate<I>,'MD2S%')
PrintLine<1,M+31> = OCONV(EquipEff<I>,'MD2S%')
PrintLine<1,M+32> = OCONV(OverallEquipEff<I>,'MD2S%')
Result<-1> = PrintLine
NEXT I
* * * * * * *
BAIL:
* * * * * * *
Dummy = Set_Property(@WINDOW:'.STATUS_LINE','BACKCOLOR',OrgColor)
RETURN