compile SUBROUTINE Print_RX_Voucher( WONo ) DECLARE FUNCTION SECURITY_CHECK, SET_PRINTER, GET_PRINTER, MSG, FIELDCOUNT, ENTID, REPOSITORY, PRINTER_SELECT DECLARE FUNCTION OBJ_INSTALL, obj_Order_Det DECLARE SUBROUTINE SECURITY_ERR_MSG $INSERT SECURITY_RIGHTS_EQU $INSERT OIPRINT_EQUATES $INSERT MSG_EQUATES $INSERT QUOTE_EQU $INSERT ORDER_EQU $INSERT ORDER_DET_EQUATES $INSERT COMPANY_EQU $INSERT WO_LOG_EQUATES $INSERT WO_MAT_EQUATES $INSERT APPCOLORS $INSERT COC_EQU EQU PI$LEFT TO 1 EQU PI$TOP TO 2 EQU PI$RIGHT TO 3 EQU PI$BOTTOM TO 4 EQU PI$WIDTH TO 5 EQU PI$HEIGHT TO 6 EQU PI$SIZE TO 7 IF NOT(ASSIGNED(WONo)) THEN RETURN WORec = XLATE('WO_LOG',WONo,'','X') * * * PRINT SETUP * * * PageInfo = '' PageInfo = 0.5 ;* Margins PageInfo = 1.35 PageInfo = 0.5 PageInfo = 0.50 PageInfo = LETTER PageSetup = 0 ;* 1 = Landscape mode PrintSetup = '' PrintSetup<1,1> = '2' ;* Preview Normal PrintSetup<1,2> = '5' ;* Show Print and PDF, hide Print Setup PrintSetup<1,3> = '0' ;* Show the printing window PDFParms = 'Printing PDF Document':@FM: '' :@FM:'':@FM: '' stat = Set_Printer( 'INIT', PDFParms, 'Wafer Receiving Voucher',PageInfo,PageSetup,PrintSetup) PageSize = Get_Printer('PAGESIZE') PageHeight = PageSize<2> MaxPrintLength = PageHeight - PageInfo - PageInfo font = 'Arial' ;* Font basics font<2> = 10 font<4> = 0 stat = Set_Printer('FONTHEADFOOT', font) stat = Set_Printer('FOOTER',"Page 'P' Received by:__________________________________________ Qty issued:________ ":@VM:@VM:"'T' 'D'") stat = Set_Printer('LINESTYLE', PS_SOLID:@FM:2) stat = Set_Printer('LINE', -0.1:@FM:-1.2:@FM:7.5:@FM:-1.2, 1) stat = Set_Printer('LINE', -0.1:@FM:-0.1:@FM:7.5:@FM:-0.1, 1) location = -.15:@fm:-1.150:@fm:1.57:@fm:1 stat = Set_Printer('BMP',obj_Install('Get_Prop','ColorBMP'),location, 0,1) * * * * Added 10/8/2015 JCH - Updated 'CONFIG','COMPANY' * * * * InstDat = obj_Install('Get_Prop','Company':@FM:'Division') Company = InstDat<1> Division = InstDat<2> font = 'Arial' font<2> = '12' ;* Big type font<4> = 1 ;* Bold on font<5> = 0 ;* Italics stat = Set_Printer('TEXTXY',Company,5.7:@FM:-1.15,font,1) stat = Set_Printer('TEXTXY',Division,5.7:@FM:-0.970,font,1) font<2> = 10 ;* 10 point font font<4> = 0 ;* Bold off font<5> = 0 ;* Italics Off stat = Set_Printer('TEXTXY',obj_Install('Get_Prop','Address'), 5.7:@fm:-0.775, font,1) stat = Set_Printer('TEXTXY',obj_Install('Get_Prop','CSZC'), 5.7:@fm:-0.625, font,1) stat = Set_Printer('TEXTXY','Tel: ':obj_Install('Get_Prop','Phone'), 5.7:@fm:-0.475, font, 1) stat = Set_Printer('TEXTXY','FAX: ':obj_Install('Get_Prop','FAX'), 5.7:@fm:-0.325, font, 1) * * * * End of changes 10/8/2015 JCH * * * * stat = Set_Printer('TEXTXY','Work Order No: ':WONo,2.7:@FM:-0.325,font,1) font<2> = '18' ;* Big type font<4> = 1 ;* Bold on font<5> = 1 ;* Italics stat = Set_Printer('TEXTXY','WO Receiving Voucher',2.1:@FM:-0.80,font,0) font<2> = 12 ;* Drop the font size font<4> = 0 ;* Bold off font<5> = 0 ;* Italics off WORec = XLATE('WO_LOG',WONo,'','X') CustNo = WORec OrderNo = WORec ProdOrdNo = WORec WOLotDetail = '' bcLotDetail = '' IF ProdOrdNo = '' THEN CustBillToInfo = XLATE('ORDER',OrderNo,'BILL_TO_INFO','X') ;** SAP change needed CustShipToInfo = XLATE('ORDER',OrderNo,'SHIP_TO_INFO','X') ;** SAP change needed OrderRec = XLATE('ORDER',OrderNo,'','X') ;** SAP change needed VisionOrderNo = '' ProdOrderNo = '' IF OrderRec = '' THEN PONo = WORec ProdOrderNo = WORec POLine = '' PORel = '' VisionOrderNo = '' END ELSE VisionOrderNo = OrderRec PONo = OrderRec POLine = OrderRec PORel = OrderRec END IF POLine NE '' THEN PONo := CRLF$:'Line ':POLine END IF PORel NE '' THEN PONo := CRLF$:'Rel ':PORel END SWAP @TM WITH CRLF$ IN CustBillToInfo SWAP @TM WITH CRLF$ IN CustShipToInfo WOSummary = '' CustPN = WORec SubPN = WORec ItemQty = WORec ;* Changed to WO_QTY$ to use WO qty and not original SAP_ORD_QTY$ - dkk 7/24/14 EpiPN = WORec CustLotNos = WORec CustLotQtys = WORec DetLineCnt = 1 FOR N = 1 TO COUNT(CustLotNos,@VM) + (CustLotNos NE '') WOLotDetail = CustLotNos<1,N> WOLotDetail = CustLotQtys<1,N> bcLotDetail = '*':CustLotNos<1,N>:'*' IF CustLotQtys<1,N> <= 25 THEN bcLotDetail = '*':CustLotQtys<1,N>:'*' END ELSE bcLotDetail = '' END DetLineCnt += 1 NEXT N OrderLine = OrderLineItem:@VM ;** SAP change needed OrderLine := ItemDesc:@VM OrderLine := CustPN:@VM OrderLine := SubPN:@VM *OrderLine := EpiPN:@VM OrderLine := ItemQty:@VM:@VM ;* Trailing VM's are for calculated columns in next section WOSummary = OrderLine END ELSE CustPONo = WORec CustNo = WORec CustRec = XLATE('COMPANY',CustNo,'','X') ShipToAttn = CustRec ShipToCo = CustRec ShipToAddr = CustRec ShipToCity = CustRec ShiptoState = CustRec ShipToZip = CustRec CustData = '' IF ShipToAttn NE '' THEN CustData := ShipToAttn:CRLF$ IF ShiptoCo NE '' THEN CustData := ShiptoCo:CRLF$ IF ShipToAddr NE '' THEN CustData := ShipToAddr:CRLF$ IF ShipToCity NE '' THEN CustData := ShipToCity:', ' IF ShipToState NE ''THEN CustData := ShipToState:' ':OCONV(ShipToZip,'[ZIP_FORMAT]') WOSummary = '' EpiPN = WORec CustPN = WORec SubPN = WORec ItemQty = WORec ;* Changed to WO_QTY$ to use WO qty and not original SAP_ORD_QTY$ - dkk 7/24/14 CustLotNos = WORec CustLotQtys = WORec DetLineCnt = 1 FOR N = 1 TO COUNT(CustLotNos,@VM) + (CustLotNos NE '') WOLotDetail = CustLotNos<1,N> WOLotDetail = CustLotQtys<1,N> bcLotDetail = '*':CustLotNos<1,N>:'*' IF CustLotQtys<1,N> <= 25 THEN bcLotDetail = '*':CustLotQtys<1,N>:'*' END ELSE bcLotDetail = '' END DetLineCnt += 1 NEXT N WOSummary = EpiPN WOSummary<1,2> = CustPN WOSummary<1,3> = SubPN WOSummary<1,4> = ItemQty QuoteNo = '' OrderNo = '' END * This sections changed from WO_LOG to WOMat on 1/16/2008 by JCH CassDetail = '' WOMatKeys = WORec FOR I = 1 TO COUNT(WOMatKeys,@VM) + (WOMatKeys NE '') WOMatKEy = WOMatKeys<1,I> WOMatRec = XLATE('WO_MAT',WOMatKey,'','X') IF ProdOrdNo = '' THEN CassOrdItem = WOMatRec ;** SAP change needed LOCATE CassOrdItem IN OrderLineItems USING @VM Setting Pos THEN WOSummary = WOSummary + WOMatRec WOSummary = WOSummary - WOSummary END ELSE WOSummary = INSERT(WOSummary,Pos,6,0,WOMatRec) END END ELSE WOSummary<1,5> = WOSummary<1,5> + WOMatRec WOSummary<1,6> = WOSummary<1,4> - WOSummary<1,5> END CassLine = WOMatKey[-1,'B*']:@VM ;* CassNo CassLine := WOMatRec:@VM CassLine := WOMatRec:@VM CassLine := WOMatRec:@VM CassLine := WOMatRec:@VM CassLine := '' ;* SubInvID - Not Used CassDetail = CassLine NEXT I WOStepKeys = WORec WOSteps = '' FOR I = 1 TO COUNT(WOStepKeys,@VM) + (WOStepKeys NE '') WOStepKey = WOStepKeys<1,I> WOSteps<1,I> = FIELD(WOStepKey,'*',2) NEXT I WOStepPSNs = XLATE('WO_STEP',WOStepKeys,1,'X') WOStepDescs = XLATE('WO_STEP',WOStepKeys,8,'X') ReactType = XLATE('PROD_SPEC',WOStepPSNs<1,1>,'REACTOR_TYPE','X') ReactType = OCONV(ReactType,'[REACT_TYPE_CONV,OPSREF]') SWAP @VM WITH CRLF$ IN WOSteps SWAP @VM WITH CRLF$ IN WOStepPSNs SWAP @VM WITH CRLF$ IN WOStepDescs IF ProdOrdNo = '' THEN colHeader = 'Order No' ; colFormat = '^1080' colHeader<1,2> = 'Vision Order No' ; colFormat<1,2> = '^1440' colHeader<1,3> = 'Quote No' ; colFormat<1,3> = '^1440' colHeader<1,4> = 'PO No' ; colFormat<1,4> = '^1800' colHeader<1,5> = 'Step No' ; colFormat<1,5> = '^720' colHeader<1,6> = 'PSN' ; colFormat<1,6> = '^720' colHeader<1,7> = 'Step Description' ; colFormat<1,7> = '<2520' colHeader<1,8> = 'React Type' ; colFormat<1,8> = '^1080' colData = OrderNo colData<1,2> = VisionOrderNo colData<1,3> = Quote colData<1,4> = PONo colData<1,5> = WOSteps colData<1,6> = WOStepPSNs colData<1,7> = WOStepDescs colData<1,8> = ReactType END ELSE colHeader = 'Prod Order No' ; colFormat = '^1800' colHeader<1,2> = 'Cust PO No' ; colFormat<1,2> = '^2160' colHeader<1,3> = 'Step No' ; colFormat<1,3> = '^720' colHeader<1,4> = 'PSN' ; colFormat<1,4> = '^720' colHeader<1,5> = 'Step Description' ; colFormat<1,5> = '<2520' colHeader<1,6> = 'React Type' ; colFormat<1,6> = '^1080' colData = ProdOrdNo colData<1,2> = CustPONo colData<1,3> = WOSteps colData<1,4> = WOStepPSNs colData<1,5> = WOStepDescs colData<1,6> = ReactType END font = 'Arial' ;* Font basics font<2> = 10 font<4> = 0 TableFormat = TB_ALL HeaderFormat = TB_ALL TablePos = 'L' HdrShade = LTGREY$ PrintHeads = 1 BoldHeader = 0 ULHeader = 0 ItalicHeader = 0 PrintHeads = 1 * Basic Order Information GOSUB PrintTable stat = Set_Printer('TEXT') * Bill to and Ship to Information * IF ProdOrdNo = '' THEN colHeader = 'Bill To' ; colFormat = '<5400' colHeader<1,2> = 'Ship To' ; colFormat<1,2> = '<5400' colData = CustBillToInfo colData<1,2> = CustShipToInfo END ELSE colHeader = 'Ship To' ; colFormat = '<5400' ; colData = CustData END PrintHeads = 1 GOSUB PrintTable stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') * WO Summary Information * colHeader = 'Epi Part No' ; colFormat = '<2880' colHeader<1,2> = 'Cust Part No' ; colFormat<1,2> = '<2880' colHeader<1,3> = 'Substrate PN' ; colFormat<1,3> = '<1840' colHeader<1,4> = 'WO':CRLF$:'Qty' ; colFormat<1,4> = '^720' colHeader<1,5> = 'Rcvd':CRLF$:'Qty' ; colFormat<1,5> = '^720' colHeader<1,6> = 'Rem':CRLF$:'Qty' ; colFormat<1,6> = '^720' colData = WOSummary font<2> = 10 ;* 10 point font<4> = 1 ;* Bold stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE','^10800','E x p e c t e d M a t e r i a l','','','',0,7) ;;** SAP change needed PrintHeads = 1 GOSUB PrintTable stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') * * * * * * Print Expected Lot Detail and Quantity and Associated Bar Codes * * * * * * Pass = 0 LOOP colHeader = 'Lot No' ; colFormat = '<2160' colHeader<1,2> = 'Qty' ; colFormat<1,2> = '^900' TopOfLots = Get_Printer('POS') ;* Y position for top of tables Delta = MaxPrintLength - TopOfLots<2> AvailLines = INT(Delta/.35) colData = FIELD(WOLotDetail,@FM,1,AvailLines) WOLotDetail[1,COL2()] = '' FontSpacing = 100 font<4> = 0 ;* Bold stat = Set_Printer('FONT',font,FontSpacing) IF NOT(Pass) THEN stat = Set_Printer('ADDTABLE', colFormat,colHeader,'',LTGREY$,'',0,TB_TOP_BOTTOM) ;* Print column headings bold w/grey background END FontSpacing = 210 font<4> = 0 ;* Bold stat = Set_Printer('FONT',font,FontSpacing) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',0,TB_TOP_BOTTOM) ;* Print column data BottomOfLots = Get_Printer('POS') IF (BottomOfLots<2> < TopOfLots<2>) THEN TopOfLots = '0.0000':@FM:'0.0000' END stat = Set_Printer('POS',TopOfLots) ;* Move back to top of Lot table bcFormat = '^5760':@VM:'^2160' ;* Change the column widths font<4> = 0 ;* Bold stat = Set_Printer('FONT',font,100) IF NOT(Pass) THEN stat = Set_Printer('ADDTABLE', bcFormat,colHeader,'',LTGREY$,'',0,TB_TOP_BOTTOM:@FM:2.25) ;* Print column headings bold w/grey background END bcFont = '' bcFont<1> = '3 of 9 Barcode' bcFont<2> = '24' bcFont<3> = 'R' bcFont<4> = '0' bcFontSpacing = 130 colData = FIELD(bcLotDetail,@FM,1,AvailLines) bcLotDetail[1,COL2()] = '' stat = Set_Printer('FONT',bcFont,bcFontSpacing) stat = Set_Printer('ADDTABLE',bcFormat,'',colData,'','',0,TB_TOP_BOTTOM:@FM:2.25) stat = Set_Printer('FONT',Font,'100') Pass += 1 UNTIL WOLotDetail = '' REPEAT stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') ************************************ * Wafers Received Information * colHeader = 'Cass':CRLF$:'No' ; colFormat = '^720' colHeader<1,2> = 'Lot No' ; colFormat<1,2> = '<2880' colHeader<1,3> = 'Wafer':CRLF$:'Qty' ; colFormat<1,3> = '>720' colHeader<1,4> = 'Part No' ; colFormat<1,4> = '<1800' colHeader<1,5> = 'Substrate PN' ; colFormat<1,5> = '<1800' colHeader<1,6> = 'Inventory ID' ; colFormat<1,6> = '<2880' colData = CassDetail FontSpacing = 100 font<2> = 10 ;* 10 point font<4> = 1 ;* Bold stat = Set_Printer('FONT',font,FontSpacing) stat = Set_Printer('ADDTABLE','^10800','R e c e i v e d M a t e r i a l','','','',0,7) PrintHeads = 1 GOSUB PrintTable /* font<4> = 0 ;* Bold stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE', colFormat,colHeader,'',LTGREY$,'',0,7) ;* Print column headings bold w/grey background font<4> = 0 ;* Bold off stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,7) ;* Print column data */ Void = set_printer( 'TEXT', '' ) Void = set_printer( 'TEXT', '' ) Void = Set_Printer('TERM',0) RETURN * * * * * * PrintTable: * * * * * * FOR I = 1 TO COUNT(colData,@FM) + (colData NE '') stat = Set_Printer('CALCTABLE',colFormat:@FM:colData) TableSize = Get_Printer('CALCTABLE') TableHeight = TableSize<2> YPos = Get_Printer('POS')<2> IF YPos + TableHeight > MaxPrintLength THEN FirstLine = 0 stat = Set_Printer('PAGEBREAK') font<2> = 10 IF BoldHeader THEN font<4> = 1 ELSE font<4> = 0 IF ULHeader THEN font<6> = 1 ELSE font<6> = 0 IF ItalicHeader THEN font<5> = 1 ELSE font<5> = 0 stat = Set_Printer('FONT',font,'100') IF HeaderFormat = '' THEN HeaderFormat = TableFormat stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',HdrShade,'',0,HeaderFormat:@FM:TablePos) font<4> = 0 font<5> = 0 font<6> = 0 stat = Set_Printer('FONT',font,fontSpacing) stat = Set_Printer('ADDTABLE',colFormat,'',colData,HdrShade,'',0,TableFormat:@FM:TablePos) END ELSE IF PrintHeads THEN IF BoldHeader THEN font<4> = 1 ELSE font<4> = 0 IF ULHeader THEN font<6> = 1 ELSE font<6> = 0 IF ItalicHeader THEN font<5> = 1 ELSE font<5> = 0 stat = Set_Printer('FONT',font,'100') IF HeaderFormat = '' THEN HeaderFormat = TableFormat stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',HdrShade,'',0,HeaderFormat:@FM:TablePos) PrintHeads = 0 END font<2> = 10 font<4> = 0 font<5> = 0 font<6> = 0 stat = Set_Printer('FONT',font,fontSpacing) stat = Set_Printer('ADDTABLE',colFormat,'',colData,HdrShade,'',1,TableFormat:@FM:TablePos) END NEXT I RETURN