COMPILE SUBROUTINE Print_Passdown(Yesterday,ReactNo) /* Print Passdown 09/25/2013 - John C. Henry, J.C. Henry, Inc. - Initial coding */ DECLARE SUBROUTINE Reduce,MSG,Utility,ErrMsg, Set_Status, Btree.Extract, RList, Make.List DECLARE FUNCTION Set_Printer,Get_Printer,Msg, Get_Status, Dialog_Box, obj_Install DECLARE FUNCTION FieldCount,Get_Status,Set_Status,Set_FSError,Printer_Select $INSERT OIPRINT_EQUATES $INSERT REACT_MODE_EQUATES $INSERT REACT_EVENT_EQUATES $INSERT APPCOLORS $INSERT MSG_EQUATES $INSERT RLIST_EQUATES ErrorTitle = 'Error in Store Procedure Print_Passdown' OPEN 'REACT_EVENT' TO ReactEventTable ELSE ErrorMsg = 'Unable to Open "REACT_EVENT" table!' Set_Status(1,ErrorTitle:@SVM:ErrorMsg) RETURN END OPEN 'DICT.REACT_EVENT' TO @DICT ELSE ErrorMsg = 'Unable to Open "DICT.REACT_EVENT" table!' Set_Status(1,ErrorTitle:@SVM:ErrorMsg) RETURN END IF NOT(ASSIGNED(Yesterday)) THEN Yesterday = OCONV(Date() - 1,'D4/') END IF NOT(Assigned(ReactNo)) THEN ReactNo = '' IF Yesterday NE '' THEN IF ReactNo NE '' THEN SelectString = 'SELECT REACT_EVENT WITH EVENT_DT GE ':QUOTE(Yesterday):'AND WITH REACT_NO EQ ':QUOTE(ReactNo):' BY-DSND EVENT_DTM' END ELSE SelectString = 'SELECT REACT_EVENT WITH EVENT_DT GE ':QUOTE(Yesterday):'BY REACT_NO BY-DSND EVENT_DTM' END RList(SelectString,TARGET_ACTIVELIST$,'','','') errCode = '' IF Get_Status(errCode) THEN ErrMsg(errCode) RETURN END EventKeys = '' Done = 0 LOOP READNEXT EventKey ELSE Done = 1 UNTIL Done EventKeys := EventKey:@VM REPEAT EventKeys[-1,1] = '' ReactNos = ReactNo StartDt = Yesterday EndDt = OCONV(Date(),'D4/') RptHeader = 'Reactor Events Since ':Yesterday:' 00:00:01AM' END ELSE ReportParms = Dialog_Box('DIALOG_PASSDOWN_RPT',@WINDOW) If ( (ReportParms NE 'CANCEL') and (ReportParms NE '') ) then EventKeys = ReportParms<1> ReactNos = ReportParms<2> StartDt = ReportParms<3> EndDt = ReportParms<4> RptHeader = ' Reactor Passdown Report ' end else Return 0 end END Today = OCONV(Date(),'D4/') **START PRINTING PROCESS** FileName = 'Print Reactor Passdown Report':@VM:'6' Title = 'Printing Reactor Passdown':@VM:'Report' TopMargin = 0.5 BottomMargin = 0.5 LeftMargin = 0.25 RightMargin = 0.25 Margins = LeftMargin:@FM:TopMargin:@FM:RightMargin:@FM:BottomMargin PageSetup = '1' ;* LandScape PrintSetup = '2' ;* Preview Normal PrintSetup<1,2> = '5' ;* Print & PDF buttons PrintSetup<1,5> = '1' ;* Page Range PrintSetup<1,6> = 7 ;* full mouse and keyboard support PrintPath = Printer_Select('',1) ;* Get Default printer path stat = Set_Printer("INIT",FileName,Title,Margins,PageSetup,PrintSetup,PrintPath) IF stat < 0 THEN GOTO OIPrint_Err * Header * DateRange = '' BEGIN CASE CASE StartDt NE '' AND EndDt = '' DateRange = 'With Event Dates From ':StartDt:' To ':Today CASE StartDt = '' AND EndDt NE '' DateRange = 'With Event Dates From Earliest To ':EndDt CASE StartDt NE '' AND EndDt NE '' DateRange = 'With Event Dates From ':StartDt:' Thru ':EndDt CASE 1 DateRange = 'All Event Dates' END CASE IF ReactNos = '' THEN SelectedReactors = 'All Reactors' END ELSE ReactCnt = COUNT(ReactNos,@VM) + (ReactNos NE '') IF INDEX(ReactNos,@VM,1) THEN SelectedReactors = ReactNos SWAP @VM WITH ', ' IN SelectedReactors SelectedReactors = 'Reactors ':SelectedReactors END ELSE SelectedReactors = 'Reactor ':ReactNos END END Header = @VM:obj_Install('Get_Prop','CompTitle'):RptHeader IF INDEX(RptHeader,'Passdown',1) THEN Header<2> = @VM:DateRange Header<3> = SelectedReactors END ELSE Header<2> = SelectedReactors END font = 'Arial' font<2> = '10' font<4> = 1 ;* Bold stat = Set_Printer("FONTHEADFOOT", font) stat = Set_Printer("HEADER",Header) * Footer * Footer = " 'D' 'T'":@VM:@VM:" Page: 'P'" ColFooter = " " stat = Set_Printer("FOOTER",Footer,ColFooter) FirstLine = 1 RecCnt = COUNT(EventKeys,@VM) + (EventKeys NE '') FOR RecNo = 1 TO RecCnt @ID = EventKeys<1,RecNo> READ @RECORD FROM ReactEventTable,@ID THEN ReactNo = @ID[1,'*'] EventDtm = OCONV(@ID[COL2()+1,'*'],'DT2/^') EventType = {EVENT_TYPE} EventTypeDesc = {TYPE_DESC} EventUser = {EVENT_USER} ReactMode = OCONV(@RECORD,'[REACT_MODE_CONV]') ReactEscHrs = OCONV(@RECORD,'MD2,') WONo = @RECORD WfrCntDTM = OCONV(@RECORD,'DT2/^') WfrCnt = OCONV(@RECORD,'MD0,') TypeNote = {TYPE_NOTE} SWAP @TM WITH CRLF$ IN TypeNote ;* @TM shows in the report as a question mark. colHeader = 'React':CRLF$:'No' ; colFmt = '^720' colHeader<1,2> = 'Event DTM' ; colFmt<1,2> = '^1260' colHeader<1,3> = 'Event Type' ; colFmt<1,3> = '^1260' colHeader<1,4> = 'User Name' ; colFmt<1,4> = '<1520' colHeader<1,5> = 'ReactMode' ; colFmt<1,5> = '<1440' colHeader<1,6> = 'Wfr Cnt' ; colFmt<1,6> = '>1080' colHeader<1,7> = 'Cnt Dtm' ; colFmt<1,7> = '^1260' colHeader<1,8> = 'Esc Hrs' ; colFmt<1,8> = '>1080' colHeader<1,9> = 'WO No' ; colFmt<1,9> = '^1080' colHeader<1,10> = 'Type Notes' ; colFmt<1,10> = '=4520' colData = ReactNo colData<1,2> = EventDTM colData<1,3> = EventTypeDesc colData<1,4> = EventUser colData<1,5> = ReactMode colData<1,6> = WfrCnt colData<1,7> = WfrCntDTM colData<1,8> = ReactEscHrs colData<1,9> = WONo colData<1,10> = TypeNote fontSpacing = 100 GOSUB PrintTable END ;* End of READ NEXT RecNo GOTO Bail * * * * * * Bail: * * * * * * stat = Set_Printer("TERM") ;* Terminiate this printing session IF stat < 0 THEN GOTO OIPrint_Err Utility('CURSOR','A') RETURN * * * * * * * OIPrint_Err: * * * * * * * *Set Error for OIPrint function and return to calling procedure Msg('',stat) Error_Msg = 'Set_Printer Returned Error Status: ':QUOTE(stat) IF Get_Status(errCode) THEN Stat = Set_Status(-1,'STPROC',ErrorTitle:@SVM:Error_Msg) END ELSE Stat = Set_Status(1,'STPROC',ErrorTitle:@SVM:Error_Msg) END stat = Set_Printer('TERM',1) RETURN * * * * * * PrintTable: * * * * * * stat = Set_Printer('CALCTABLE',colFmt:@FM:colData) TableSize = Get_Printer('CALCTABLE') TableHeight = TableSize<2> Test = Get_Printer('POS')<2> IF Get_Printer('POS')<2> + TableHeight > 7.00 OR FirstLine THEN IF NOT(FirstLine) THEN stat = Set_Printer('PAGEBREAK') END FirstLine = 0 font<2> = 8 font<4> = 1 ;* Bold stat = Set_Printer('FONT',font,'100') stat = Set_Printer('ADDTABLE',colFmt,colHeader,'',LTGREY$,'',0,TB_ALL) font<4> = 0 stat = Set_Printer('FONT',font,fontSpacing) stat = Set_Printer('ADDTABLE',colFmt,'',colData,LTGREY$,'',0,7) END ELSE font<2> = 8 font<4> = 0 stat = Set_Printer('FONT',font,fontSpacing) stat = Set_Printer('ADDTABLE',colFmt,'',colData,LTGREY$,'',1,TB_ALL) END RETURN