COMPILE SUBROUTINE Print_Shipment(ShipNo, ShipRec, AutoPrint) DECLARE FUNCTION Msg,Set_Printer, Dialog_Box, Security_Check, FieldCount, ex_vm_rem, obj_WM_Out DECLARE FUNCTION Utility, Send_Event, Popup, Printer_Select, obj_Install,obj_RDS, obj_Shipment, Get_Property DECLARE SUBROUTINE Msg, extract_si_keys, record_lock, security_err_msg, ErrMsg, Start_Window DECLARE SUBROUTINE Print_Packing_Slip, Print_SRP, Print_Coc_Back, Print_Cust_Rds, Print_Vend_CofA, Print_NCR DECLARE SUBROUTINE Create_Note, Btree.Extract, Print_Cass_Out, obj_Export, Set_Status, obj_Notes $INSERT APPCOLORS $INSERT COMPANY_EQUATES $INSERT COC_EQUATES $INSERT EXPORTS_EQU $INSERT LOGICAL $INSERT LSL_USERS_EQU $INSERT MSG_EQUATES $INSERT POPUP_EQUATES $INSERT PROD_SPEC_EQUATES $INSERT RDS_EQU $INSERT RDS_LAYER_INFO_EQU $INSERT QUOTE_EQU $INSERT QUOTE_SIGS_EQU $INSERT QUOTE_SPEC_EQU $INSERT SCHEDULE_EQU $INSERT SECURITY_RIGHTS_EQU $INSERT OIPRINT_EQUATES $INSERT RDS_TEST_EQUATES $INSERT RDS_LAYER_EQUATES $INSERT WO_STEP_EQU $INSERT WO_LOG_EQUATES equ OutSpecThickLossCode$ to 'D1' equ OutSpecResLossCode$ to 'D2' EQU PI$LEFT TO 1 ;* OIPI page parameters 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(ShipNo)) THEN RETURN IF NOT(ASSIGNED(ShipRec)) THEN ShipRec = '' If Not(Assigned(AutoPrint)) Then AutoPrint = '' IF ShipNo = '' THEN RETURN IF ShipRec = '' THEN ShipRec = XLATE('COC',ShipNo,'','X') ShipWONo = ShipRec ShipRdsKeys = ShipRec ShipWOStepNos = ShipRec ShipCassNos = ShipRec ShipDt = OCONV(ShipRec,'D4/') WORec = XLATE('WO_LOG',ShipWONo,'','X') CustNo = WORec EpiPartNo = WORec WOStepKeys = WORec ProdOrdNo = WORec WMOutKeys = '' FOR I = 1 TO COUNT(ShipWOStepNos,@VM) + (ShipWOStepNos NE '') WMOutKeys<1,I> = ShipWONo:'*':ShipWOStepNos<1,I>:'*':ShipCassNos<1,I> ;* These will drive this process when update of the RDS process is completed JCH 6/14/2006 NEXT I * Get printing options PrintOpts = '' If AutoPrint = 1 Then CompRec = Xlate('COMPANY', CustNo, '','X') PrintOpts<1,1> = '' PrintOpts<1,2> = CompRec PrintOpts<1,3> = '' PrintOpts<1,4> = CompRec PrintOpts<1,5> = '' PrintOpts<1,6> = CompRec PrintOpts<1,7> = CompRec PrintOpts<1,8> = '' PrintOpts<1,9> = CompRec TestPrintOpts = PrintOpts Convert @VM To '' In TestPrintOpts * * * Test code * * * Recipients = 'DAN_CR' SentFrom = @USER4 Subject = 'Auto Print_Shipment Called - ShipNo: ':ShipNo Message = 'PrintOpts: ':QUOTE(PrintOpts):' -> TestPrintOpts Variable: ':QUOTE(TestPrintOpts) AttachWindow = 'SAP_SHIPMENT' AttachKey = ShipNo SendToGroup = '' Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup obj_Notes('Create',Parms) * * * End of test code * * * IF TestPrintOpts = '' THEN Return End ELSE PrintOpts = Dialog_Box( 'DIALOG_SHIP_PRINT_OPTS', @WINDOW, CustNo:'*':EpiPartNo ) IF PrintOpts = '' THEN RETURN End ;* End of Check for AutoPrint Flag PrintFrontPage = PrintOpts<1,1> FrontPageCopies = PrintOpts<1,2> PrintBackPage = PrintOpts<1,3> BackPageCopies = PrintOpts<1,4> ShipType = PrintOpts<1,5> CustRDSs = PrintOpts<1,6> NCRRejCnt = PrintOpts<1,7> PrintPDF = PrintOpts<1,8> ;* 01/27/04 JCH VendorCOA = PrintOpts<1,9> ;* 04/02/04 JCH * Following Fills PageCopies if PrintOpts were entered by the Dialog Box and the PageCopies was not filled in If FrontPageCopies = '' Then ;* If PrintFrontPage = 1 Then FrontPageCopies = 1 End Else FrontPageCopies = 0 End End If BackPageCopies = '' Then If PrintBackPage = 1 Then BackPageCopies = 1 End Else BackPageCopies = 0 End End If FrontPageCopies = '' Then FrontPageCopies = 0 ;* This stays after the dialog box is updated If BackPageCopies = '' Then BackPageCopies = 0 * Initialize Common Printer parms PageInfo = '' PageInfo = 0.5 ;* Margins PageInfo = 1.35 PageInfo = 0.5 PageInfo = 0.25 PageSetup = '0' ;* Portrait PrintSetup = '2' ;* Print to printer without preview IF PrintPDF THEN PDFParms = 'Printing PDF Document':@FM: '' :@FM:'':@FM: '' PrintSetup = '' PrintSetup<1,1> = '2' ;* Preview Normal PrintSetup<1,2> = '5' ;* Display all buttons except Printer Setup PrintSetup<1,3> = '0' ;* Display Printing Window PrintSetup<1,6> = '7' ;* Preview window - keyboard and mouse support stat = Set_Printer( 'INIT', PDFParms, 'Shipping Documents',PageInfo,PageSetup , PrintSetup) END ELSE PrintSetup = '0' ;* Print to printer without preview stat = Set_Printer( 'INIT','Printing','Shipping Documents', PageInfo,PageSetup,PrintSetup ) END PrinterInitialized = 1 font = 'Arial' ;* Font basics font<2> = 10 font<4> = 0 stat = Set_Printer('FONTHEADFOOT', font) *stat = Set_Printer('FOOTER',"Page 'P'":@VM:@VM:"'T' 'D'") stat = Set_Printer('LINESTYLE', PS_SOLID:@FM:2) stat = Set_Printer('LINE', -0.1:@FM:-1.2:@FM:7.7:@FM:-1.2, 1) stat = Set_Printer('LINE', -0.1:@FM:-0.1:@FM:7.7:@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','Shipment No: ':ShipNo,3.0:@FM:-0.325,font,1) IF ShipRec NE '' THEN SAPDelNo = ShipRec stat = Set_Printer('TEXTXY','SAP Delivery No: ':SAPDelNo,2.8:@FM:-0.525,font,1) END WOStepCnt = COUNT(WOStepKeys,@VM) + (WOStepKeys NE '') FOR WOStep = 1 TO WOStepCnt IF WOStep > 1 THEN stat = Set_Printer('PAGEBREAK') END IF WOStep NE WOStepCnt THEN Parms = ShipNo:@RM:WOStep:@RM:ShipRDSKeys:@RM:ShipRec PrintRDSKeys = obj_Shipment('PrevStepRDSNos',Parms) PrintWMOutKeys = '' FOR I = 1 TO COUNT(PrintRDSKeys,@VM) + (PrintRDSKeys NE '') LOCATE PrintRDSKeys<1,I> IN ShipRDSKeys USING @VM SETTING Pos THEN PrintWMOutKeys<1,I> = WMOutKeys<1,Pos> END NEXT I END ELSE PrintRdsKeys = ShipRdsKeys PrintWMOutKeys = WMOutKeys END IF WOStep = 1 THEN Print_Packing_Slip( ShipNo, '', '', PrinterInitialized) ;* Two copies of the packing slip /* stat = Set_Printer('PAGEBREAK') Print_Packing_Slip( ShipNo, '', '', PrinterInitialized) ;* Stop the second copy of Packing Slip from printing. - dkk 5/30/14 */ END IF FrontPageCopies > 0 THEN stat = Set_Printer('PAGEBREAK') FOR H = 1 TO FrontPageCopies font = 'Arial' font<2> = '18' ;* Big type font<4> = 1 ;* Bold on font<5> = 1 ;* Italics stat = Set_Printer('TEXTXY','Certificate of Compliance',2.1:@FM:-0.80,font,0) font<2> = 12 ;* Normal size font<4> = 0 ;* Bold off font<5> = 0 ;* Italics off GOSUB PrintCocFront NEXT H END IF BackPageCopies > 0 THEN FOR H = 1 TO BackPageCopies stat = Set_Printer('PAGEBREAK') Print_Coc_Back( PrintRdsKeys, PrintWMOutKeys, false$, '', PrintOnly, ShipDt ) ;* false for not prelim, is is a full shipment and no email addresses NEXT H END IF CustRDSs THEN CustRDSPrintRdsKeys = PrintRdsKeys CONVERT @VM TO @FM IN CustRDSPrintRdsKeys Print_Cust_Rds( CustRDSPrintRdsKeys, PrintWMOutKeys, PrintOnly, PrintPath, PDFFileName,PrinterInitialized ) END IF WMOutKeys NE '' THEN PrintCDSKeys = WMOutKeys CONVERT @VM TO @FM IN PrintCDSKeys Print_Cass_Out( PrintCDSKeys, PrintOnly, PrintPath, PDFFileName,PrinterInitialized ) END IF VendorCOA THEN AllLotNos = XLATE('RDS',PrintRdsKeys,rds_lot_num$,'X') VendLotNos = '' FOR A = 1 TO COUNT(AllLotNos,@VM) + (AllLotNos NE '') AllLotNo = AllLotNos<1,A> LOCATE AllLotNo IN VendLotNos BY 'AR' USING @VM SETTING Pos ELSE VendLotNos = INSERT(VendLotNos,1,Pos,0,AllLotNo) END NEXT A OPEN 'DICT.COA' TO DictVar THEN SearchString = 'LOT_NO':@VM:VendLotNos:@FM CoaKey = '' Option = '' Flag = '' Btree.Extract(SearchString, 'COA', DictVar, CoaKeys, Option, Flag) FOR VendCoa = 1 TO COUNT(CoaKeys,@VM) + (CoaKeys NE '') Print_Vend_CofA(CoaKeys<1,VendCoa>,PrintPath, PDFFileName, PrinterInitialized) NEXT VendCoa END END NCRRDsPrintIDs = '' IF ( NCRRejCnt <> '' ) THEN NCRRDSPrintRdsKeys = PrintRdsKeys CONVERT @VM TO @FM IN NCRRDSPrintRdsKeys Ncnt = COUNT( NCRRDSPrintRdsKeys, @FM ) + (NCRRDSPrintRdsKeys NE '') NCRPrn = '' FOR I = 1 TO Ncnt NCRIds = XLATE('RDS',NCRRDSPrintRdsKeys,RDS_NCR_KEYS$,'X') RDSRejCnt = SUM(XLATE('NCR',NCRIds,'REJ_CNT','X')) IF RDSRejCnt >= NCRRejCnt THEN NCRPrn<1,-1> = NCRIds END NEXT I CONVERT @VM TO @FM IN NCRPrn SuppliedBy = XLATE( 'PROD_SPEC', xlate( 'RDS', PrintRdsKeys<1,1>, rds_prod_spec_id$, 'X' ), 'SUB_SUPPLIED_BY', 'X' ) IF SuppliedBy = 'C' THEN ;* Wafers are supplied by the customer so print the NCRS IF NCRPrn <> '' THEN * Print the NCRs that are over the ncr_rej cnt IF Security_Check( 'NCR', Print$ ) THEN Print_NCR( NCRPrn, '', PrintOnly, PrintPath, PDFFileName ,PrinterInitialized) END ELSE Security_Err_Msg( 'NCR', Print$ ) END END END ;* End of check for SuppliedBy = 'C' END ;* End of check for NCRRecCnt NE '' * Now print the SRP plot if there are any SRPScanPrintRdsKeys = PrintRdsKeys CONVERT @VM TO @FM IN SRPScanPrintRdsKeys SRPPointers = xlate( 'RDS', SRPScanPrintRdsKeys, 'SRP_PROFILE_PATH', 'X' ) SRPCnt = COUNT( SRPPointers, @fm ) + (SRPPointers NE '') FOR I = 1 TO SRPCnt TheseSRPs = SRPPointers Pcnt = COUNT( TheseSRPs, @vm ) + (TheseSRPs NE '') FOR J = 1 TO Pcnt ThisSRP = TheseSRPs<1,J> IF ThisSRP NE '' THEN Print_SRP( ThisSRP, PrintPath, PDFFileName , PrinterInitialized) END NEXT J NEXT I NEXT WOStep Stat = Set_Printer('TERM') CustID = XLATE( 'RDS', PrintRdsKeys<1,1>, rds_cust_no$, 'X' ) CustNameOrAbrev = XLATE( 'COMPANY', CustNo, 'ABBREV_OR_CO_NAME', 'X' ) ExportTemplate = XLATE( 'COMPANY', CustID, company_shipping_export_template$, 'X' ) IF ( ExportTemplate <> '' ) AND ( XLATE( 'RDS', PrintRdsKeys<1,1>, rds_layer_info$, 'X' ) <> '' ) THEN ExportTemplate:= 2 END IF ShipRdsKeys = '' THEN * This is an EpiPRO order ExportTemplate = 'IRC_SYSTEM_EPIPRO' PrintRdsKeys = obj_WM_Out('CassRDSNos',WMOutKeys) CONVERT @VM TO ' ' IN PrintRdsKeys OPEN 'EXPORTS' TO ExportTable ELSE void = msg( '', 'Unable to open EXPORTS...' ) RETURN END *ExcelFileName = 'N:\Materials\DeptData\Shipping\DATA\Vishay\PL':ShipNo:'.xls' ExcelFileName = 'C:\PL':ShipNo:'.xls' WRITEV "= ":PrintRdsKeys ON ExportTable, ExportTemplate, EXPORTS_QUERY_COL_FILTER$ ELSE msg( '', 'Unable to write to "EXPORTS" ':quote(ExportTemplate):'...contact MIS.' ) return END WRITEV ExcelFileName ON ExportTable, ExportTemplate, EXPORTS_PATH$ ELSE msg( '', 'Unable to write to "EXPORTS" ':quote(ExportTemplate):'...contact MIS.' ) return END Void = send_event( 'EXPORTS', 'CLOSE' ) * Problem is right here If Get_Property('NDW_MAIN', 'VISIBLE') then AppMain = 'NDW_MAIN' end else AppMain = 'LSL_MAIN2' end Start_Window ( 'EXPORTS', AppMain, 'SYSTEM_GENERATED*':ExportTemplate:'*':CustNameOrAbrev, '', '' ) Done = true$ ;* Have to exit cause calling the popup above will cause problems when calling excel /* MetKeysZ1 = XLATE('RDS',PrintRdsKeys,'MET_KEYS_Z1','X') MetKeysZ2 = XLATE('RDS',PrintRdsKeys,'MET_KEYS_Z2','X') ShipMetKeys = '' FOR I = 1 TO COUNT(PrintRdsKeys,@FM) + (PrintRdsKeys NE '') IF MetKeysZ1 NE '' THEN ShipMetKeys<1,-1> = FIELD(MetKeysZ1,@VM,1,2) END IF MetKeysZ2 NE '' THEN ShipMetKeys<1,-1> = FIELD(MetKeysZ2,@VM,1,2) END NEXT I KeyList = PrintRdsKeys ;*ShipMetKeys ExportID = ExportTemplate *ExcelFileName = 'N:\Materials\DeptData\Shipping\DATA\Vishay\PL ':ShipNo:'.xls' ExcelFileName = 'C:\PL ':ShipNo:'.xls' CONVERT @VM TO ' ' IN KeyList CONVERT @FM TO ' ' IN KeyList TypeOver = '' TypeOver = ExcelFileName TypeOver = '' TypeOver = '' TypeOver = 'RDS_NO' TypeOver = '= ':KeyList Set_Status(0) obj_Export('ExportTemplate',ExportID:@RM:TypeOver) IF Get_Status(errCode) THEN ErrMsg(errCode) END */ END ELSE IF ExportTemplate THEN OPEN 'EXPORTS' TO ExportTable ELSE void = msg( '', 'Unable to open EXPORTS...' ) RETURN END WRITEV "= ":ShipWoNo ON ExportTable, ExportTemplate, exports_query_col_filter$ ELSE msg( '', 'Unable to write to "EXPORTS" ':quote(ExportTemplate):'...contact MIS.' ) return END ExpPrintRdsKeys = PrintRdsKeys CONVERT @FM TO ' ' IN ExpPrintRdsKeys CONVERT @VM TO ' ' IN ExpPrintRdsKeys WRITEV "= ":ExpPrintRdsKeys ON ExportTable, ExportTemplate, exports_nquery_col_filter$ ELSE msg( '', 'Unable to write to "EXPORTS" ':quote(ExportTemplate):'...contact MIS.' ) return END Void = send_event( 'EXPORTS', 'CLOSE' ) If Get_Property('NDW_MAIN', 'VISIBLE') then AppMain = 'NDW_MAIN' end else AppMain = 'LSL_MAIN2' end * Problem is right here Start_Window ( 'EXPORTS', AppMain, 'SYSTEM_GENERATED*':ExportTemplate:'*':CustNameOrAbrev, '', '' ) Done = true$ ;* Have to exit cause calling the popup above will cause problems when calling excel END ;* End of check for ExportTemplate END RETURN * * * * * * * PrintCocFront: * * * * * * * ShipDt = OCONV(ShipRec,'D4/') IF XLATE('COC',ShipNo,'WO_CUST_NO','X') = '7067' THEN CustAddrInfo = XLATE('COC',ShipNo,'ORD_SHIP_TO_INFO','X') ;* Added customer specific code 3/4/2010 JCH END ELSE CustAddrInfo = XLATE('COC',ShipNo,'ORD_BILL_TO_INFO','X') END SWAP @TM WITH CRLF$ IN CustAddrInfo * Bill to and Ship to information stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') colFormat = '>1440' colFormat<1,2> = '<9360' colData = 'Ship Dt:' colData<1,2> = ShipDt colData<3,1> = 'Customer:' colData<3,2> = CustAddrInfo font<1> = 'Courier New' font<2> = 12 font<4> = 0 stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,'','',1,TB_NONE) stat = Set_Printer('TEXT') PSNo = XLATE('WO_STEP',ShipWONo:'*':WOStep,WO_STEP_PROD_SPEC_ID$,'X') Dopant = XLATE('PROD_SPEC',PSNo,'DOPANT_L1','X') Recipe = XLATE('PROD_SPEC',PSNo,'RECIPE_NAME','X') stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') colFormat = '<10800' colData = 'The enclosed material has been manufactured, inspected and/or tested in the' colData := ' U.S.A. in accordance with specifications outlined on your purchase order.' font<1> = 'Courier New' font<2> = 10 font<4> = 0 ;* Bold off font<5> = 0 ;* Italic off stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,'','',1,TB_NONE) stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') IF WOStepCnt = 1 THEN PrintWO = ShipWONo END ELSE PrintWO = ShipWONo:'.':WOStep END font<1> = 'Courier New' font<2> = 10 font<4> = 1 ;* Bold on stat = Set_Printer('FONT',font) IF ProdOrdNo = '' THEN colData = 'This material was processed as Work Order Number: ':quote( PrintWO ):' and manufactured under process control recipe ':quote(Recipe):'.' END ELSE colData = 'This material was released as Production Order No: ':QUOTE(ProdOrdNo):', processed as Work Order Number: ':quote( PrintWO ) colData :=' and manufactured under process control recipe ':quote(Recipe):'.' END stat = Set_Printer('ADDTABLE',colFormat,'',colData,'','',1,TB_NONE) stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') font<2> = 10 font<4> = 0 ;* Bold off stat = Set_Printer('FONT',font) colData = 'Pertinent test and/or inspection records are on file and available for review' IF PrintBackPage THEN colData := ' under run numbers specified in the following page(s) of this document.' END ELSE colData := '.' END stat = Set_Printer('ADDTABLE',colFormat,'',colData,'','',1,TB_NONE) stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') colHeading = 'Approved By:' ; colFormat = '<7200' colHeading<1,2> = 'Date:' ; colFormat<1,2> = '<2880' colData = '' colData<3,2> = OCONV(Date(),'D4,HL') colData<5,1> = 'Document Control' stat = Set_Printer('ADDTABLE',colFormat,colHeading,'','','',0,TB_BOTTOM) stat = Set_Printer('ADDTABLE',colFormat,'',colData,'','',1,TB_NONE) for k = 1 to 7 Void = set_printer( 'TEXT', '' ) next k Font<4> = 1 Void = set_printer( 'FONT', Font ) * PrintWO is set about twenty lines up TextOut = 'Quality Assurance Registration Number ':quote( PrintWO ) Void = set_printer( 'TEXT', TextOut ) Font<4> = 0 Void = set_printer( 'FONT', Font ) RETURN