COMPILE SUBROUTINE Print_Cass_Data( WMOutKeys, PrintOnly, PrintPath, PDFFileName, PrinterInitialized) $INSERT MSG_EQUATES $INSERT RDS_EQU $INSERT RDS_LAYER_INFO_EQU $INSERT PROD_SPEC_EQU $INSERT OIPRINT_EQUATES $INSERT NCR_EQU $INSERT POPUP_EQUATES $INSERT LOGICAL $INSERT COA $INSERT RDS_TEST_EQUATES $INSERT RDS_LAYER_EQUATES $INSERT WO_LOG_EQUATES $INSERT WO_MAT_EQUATES $INSERT WO_STEP_EQU $INSERT WM_OUT_EQUATES $INSERT SURFACE_SCAN_EQUATES $INSERT CUST_EPI_PART_EQUATES $INSERT EPI_PART_EQUATES 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 EQU LTGREY$ TO 229 + (229*256) + (229*65536) DECLARE FUNCTION FieldCount, Msg, Set_Printer, Get_Printer, obj_RDS_Test DECLARE FUNCTION Printer_Select, obj_Install,obj_RDS DECLARE SUBROUTINE extract_si_keys, record_lock, Btree.Extract IF NOT(ASSIGNED(PrintPath)) THEN PrintPath = '' IF NOT(ASSIGNED(PDFFileName)) THEN PDFFileName = '' IF NOT(ASSIGNED(PrinterInitialized)) THEN PrinterInitialized = 0 CassCnt = COUNT(WMOutKeys,@FM) + (WMOutKeys NE '') WOStepKey = FIELD(WMOutKeys<1,1>,'*',1,2) WONo = WOStepKey[1,'*'] WORec = XLATE('WO_LOG',WONo,'','X') CustNo = WORec CustName = XLATE('COMPANY',CustNo,4,'X') EpiPartNo = WORec CleanRoomPaper = XLATE('CUST_EPI_PART',CustNo:'*':EpiPartNo,CUST_EPI_PART_CUST_RDS_CLEANROOM_PAPER$,'X') IF CleanRoomPaper THEN MsgInfo = '' Mtext = "This customer's specification requires cleanroom paper RDSs":CrLf$:'Please place ':CassCnt:' piece(s) of cleanroom paper in the printer and then click OK' MsgInfo = Mtext MsgInfo = '!' Void = msg( '', MsgInfo ) END * * * PRINT SETUP * * * FileName = 'Print Cassette Data Sheet' Title = 'Print Cassette Data Sheet' PageInfo = '' ; * Default is .5 inch margins and 8.5 x 11 paper PageInfo = 0.5 PageInfo = 1.5 PageInfo = 0.5 PageInfo = 0.5 PageInfo = LETTER MaxPrintLength = 11 - PageInfo - PageInfo PageSetup = 0 ;* 1 = Landscape mode PrintSetup = 0 ;* 0 = No Preview, 2 = Preview FOR BoxNo = 1 TO RDSCnt WMOutKey = WMOutKeys WMOutRec = XLATE('WM_OUT',WMOutKey,'','X') IF NOT(PrinterInitialized) THEN PrintSetup = '' PrintSetup<1,1> = '2' ;* Specific Location 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, 'Run Data Sheet',PageInfo,PageSetup , PrintSetup) END ELSE stat = Set_Printer('PAGEBREAK') END GOSUB PrintSheet IF NOT(PrinterInitialized) THEN stat = Set_Printer( 'TERM' ) END NEXT BoxNo RETURN * * * * * * PrintSheet: * * * * * * font = 'Arial' ;* Font basics font<2> = 10 font<4> = 0 stat = Set_Printer('FONTHEADFOOT', font) font = 'Arial' font<2> = '18' ;* Big type font<4> = 1 ;* Bold on font<5> = 1 ;* Italics stat = Set_Printer('TEXTXY','Cassette Data Sheet',2.50:@FM:-0.80,font,0) font<2> = 12 ;* Drop the font size font<5> = 0 ;* Italics off IF NOT(PrinterInitialized) THEN 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.5:@FM:-1.2, 1) stat = Set_Printer('LINE', -0.1:@FM:-0.1:@FM:7.5:@FM:-0.1, 1) location = -0.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('TEXT') END colHeader = 'Cassette ID' ; colFormat = '^1440' colHeader<1,2> = 'WO No' ; colFormat<1,2> = '^1440' colHeader<1,3> = 'WO Step' ; colFormat<1,3> = '^1400' colHeader<1,4> = 'Cass No' ; colFormat<1,4> = '^1440' colHeader<1,5> = 'Customer' ; colFormat<1,5> = '<4320' CassID = WMOutKey CONVERT '*' TO '.' IN CassID WONo = WMOutKey[1,'*'] WOStep = WMOutKey[COL2()+1,'*'] CassNo = WMOutKey[COL2()+1,'*'] colData = CassID colData<1,2> = WONo colData<1,3> = WOStep colData<1,4> = CassNo colData<1,5> = CustName font<2> = 10 font<4> = 1 ;* Bold on stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) font<2> = 10 font<4> = 0 stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_NONE) stat = Set_Printer('TEXT') IF RDSRec<1,1> NE '' THEN Stat = Set_Printer('PAGEBREAK') font = 'Arial' font<2> = '18' ;* Big type font<4> = 1 ;* Bold on font<5> = 1 ;* Italics stat = Set_Printer('TEXTXY','Run Data Sheet',2.65:@FM:-0.80,font,0) font<2> = 12 ;* Drop the font size font<4> = 0 ;* Bold Off font<5> = 0 ;* Italics off colHeader = '' ; colFormat = '^720' colHeader<1,2> = 'Reactor' ; colFormat<1,2> = '^3240' colHeader<1,3> = '' ; colFormat<1,3> = '^2520' colHeader<1,4> = '' ; colFormat<1,4> = '^2520' colHeader<1,5> = 'Material In' ; colFormat<1,5> = '^1440' font<2> = 8 font<4> = 1 ;* Bold on stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) colHeader = 'Slot' ; colFormat = '^720' colHeader<1,2> = 'RDS' ; colFormat<1,2> = '^1080' colHeader<1,3> = 'Pocket' ; colFormat<1,3> = '^1080' colHeader<1,4> = 'Zone' ; colFormat<1,4> = '^1080' colHeader<1,5> = 'Lot No' ; colFormat<1,5> = '^2520' colHeader<1,6> = 'Part No' ; colFormat<1,6> = '^2520' colHeader<1,7> = 'Cass' ; colFormat<1,7> = '^720' colHeader<1,8> = 'Slot' ; colFormat<1,8> = '^720' colData = '' WORec = XLATE('WO_LOG',WONo,'','X') RDSNos = WMOutRec ReactPockets = WMOutRec ReactZones = WMOutRec InCassNos = WMOutRec InSlotNos = WMOutRec OutSlotNos = WMOutRec LineCnt = 1 FOR I = 1 TO COUNT(InCassNos,@VM) + (InCassNos NE '') IF OutCassNos<1,I> NE '' THEN WOMatRec = XLATE('WO_MAT',WONo:'*':InCassNos<1,I>,'','X') colData = OutSlotNos<1,I> colData = RDSNos<1,I> colData = ReactPockets<1,I> colData = ReactZones<1,I> colData = WOMatRec colData = WOMatRec colData = InCassNos<1,I> colData = InSlotNos<1,I> LineCnt += 1 END NEXT I stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) font<2> = 8 font<4> = 0 ;* Bold off stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL) END *IF XLATE('RDS',RdsId,'MU_WFRS_ADDED','X') > 0 THEN IF 1 = 0 THEN colData<3,4> = 0 ;* Makeup wafers added MakeupWaferFlag = 1 END ELSE colData<3,4> = xlate( 'RDS', RdsId, 'TOT_REJ', 'X' ) MakeupWaferFlag = 0 END font<2> = 10 font<4> = 1 ;* Bold on stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) font<2> = 10 font<4> = 0 ;* Bold off stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL) stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') colHeader = 'Light Point Defects' ; colFormat = '<2160' colHeader<1,2> = 'Preclean' ; colFormat<1,2> = '^2160' colHeader<1,3> = 'Post Preclean' ; colFormat<1,3> = '^2160' colHeader<1,4> = 'First Wafer' ; colFormat<1,4> = '^2160' colHeader<1,5> = 'Postclean' ; colFormat<1,5> = '^2160' colData = 'Quantity' colData<1,2> = RdsRec colData<1,3> = RdsRec colData<1,4> = RdsRec colData<1,5> = RdsRec font<4> = 1 ;* Bold on stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) font<4> = 0 ;* Bold off stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL) stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') colHeader = 'First Wafer':CRLF$:'Data Points' ; colFormat = '^1080' colHeader<1,2> = 'Thickness' ; colFormat<1,2> = '^1080' colHeader<1,3> = 'Sheet Rho' ; colFormat<1,3> = '^1080' colHeader<1,4> = 'Resistivity' ; colFormat<1,4> = '^1080' * 1st Wafer surface Defects colHeader = '1st Wafer Surface Defects' ; ColFormat = '<2880' colHeader<1,2> = 'Quantity' ; ColFormat<1,2> = '^2160' DataPoints = 'Pits,Mounds,BL Defects,Stack Faults,Spikes,Spots,FOV,Scratches,Scratch Length,' DataPoints := 'Bright Light LPD' CONVERT ',' TO @FM IN DataPoints colData = DataPoints colData<1,2> = RdsRec colData<2,2> = RdsRec colData<3,2> = RdsRec colData<4,2> = RdsRec colData<5,2> = RdsRec colData<6,2> = RdsRec colData<7,2> = RdsRec colData<8,2> = RdsRec colData<9,2> = RdsRec colData<10,2> = RdsRec ;* Use manual inspection results TotalSurfDefects = 0 TotalSurfDefects = TotalSurfDefects + RdsRec TotalSurfDefects = TotalSurfDefects + RdsRec TotalSurfDefects = TotalSurfDefects + RdsRec TotalSurfDefects = TotalSurfDefects + RdsRec TotalSurfDefects = TotalSurfDefects + RdsRec TotalSurfDefects = TotalSurfDefects + RdsRec TotalSurfDefects = TotalSurfDefects + colData<10,2> colData<13,1> = 'Total Surface Defects' colData<13,2> = TotalSurfDefects font<2> = 8 font<4> = 1 ;* Bold on stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',LTGREY$,'',0,TB_ALL:@FM:3.2) font<2> = 8 font<4> = 0 ;* Bold off stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL:@FM:3.2) * Check for Surfscan results * SurfScanKeys = '' OPEN 'DICT.SURFACE_SCAN' TO DictVar THEN SearchString = 'RDS_NO':@VM:RdsId:@FM Option = '' Flag = '' Btree.Extract(SearchString, 'SURFACE_SCAN', DictVar, SurfScanKeys, Option, Flag) END ELSE debug *ErrMsg('Unable to open DICT.SURFACE_SCAN in Print_Cust_Rds routine.') END IF SurfScanKeys <> '' THEN GOSUB SurfScanResults END * Non-Conformance Reports for this RDS * * * * * * * * * * * * * * * * * * * * MakeupWaferFlag = 1 IF NOT(MakeupWaferFlag) THEN NCRKeys = XLATE('RDS',RdsId,RDS_NCR_KEYS$,'X') ;* does this work?????? NCRKeyCnt = COUNT(NCRKeys,@vm) + (NCRKeys NE '') FOR I = 1 TO NCRKeyCnt stat = Set_Printer('PAGEBREAK') NCRKey = NCRKeys<1,I> NCRRec = XLATE('NCR',NCRKey,'','X') LossDesc = XLATE('NCR',NCRKey,'LOSS_DESC','X') font<2> = 10 stat = Set_Printer('FONT',font) stat = Set_Printer('TEXT') RejCnt = XLATE( 'NCR', NCRKey, 'REJ_CNT', 'X' ) IF RejCnt = 1 THEN RejText = RejCnt:' Wafer Rejected for ':LossDesc END ELSE RejText = RejCnt:' Wafer(s) Rejected for ':LossDesc END ColHeader = RejText ; colFormat = '^11000' font<2> = 12 font<4> = 0 ;* Bold on stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) stat = Set_Printer('TEXT') stat = Set_Printer('TEXT') colHeader = 'Reject Wafer':CRLF$:'Data Points' ; colFormat = '^1080' colHeader<1,2> = 'Thickness' ; colFormat<1,2> = '^1080' colHeader<1,3> = 'Sheet Rho' ; colFormat<1,3> = '^1080' colHeader<1,4> = 'Resistivity' ; colFormat<1,4> = '^1080' DataPoints = '80mm,70mm,60mm,50mm,40mm,30mm,20mm,10mm,Center,10mm,20mm,30mm,40mm,50mm,60mm,70mm,80mm' CONVERT ',' TO @FM IN DataPoints colData = DataPoints ResReadings = xlate( 'NCR', NCRKey, 'RES_READ', 'X' ) Test = ResReadings IF Test NE '' THEN FOR DP = 1 to 17 colData = oconv( NCRRec, 'MD2' ) colData = oconv( NCRRec, 'MD2' ) colData = oconv( ResReadings<1,DP>, 'MD3' ) NEXT DP LeftTablePos = Get_Printer('POS') font<2> = 8 font<4> = 1 ;* Bold on stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) font<2> = 8 font<4> = 0 ;* Bold off stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL) stat = Set_Printer('TEXT') colHeader = 'Statistical Results' ; colFormat = '^2160' colHeader<1,2> = 'Thickness' ; colFormat<1,2> = '^1080' colHeader<1,3> = 'Resistivity' ; colFormat<1,3> = '^1080' colData = '' colData<1,1> = 'Average' ; colData<1,2> = oconv( NCRRec, 'MD2' ) colData<2,1> = 'Standard Deviation' ; colData<2,2> = oconv( NCRRec, 'MD3' ) colData<3,1> = 'Maximum' ; colData<3,2> = oconv( NCRRec, 'MD2' ) colData<4,1> = 'Minimum' ; colData<4,2> = oconv( NCRRec, 'MD2' ) colData<5,1> = 'Uniformity' ; colData<5,2> = oconv( NCRRec, 'MD2S%' ) colData<1,3> = oconv( NCRRec, 'MD3' ) colData<2,3> = oconv( NCRRec, 'MD3' ) colData<3,3> = oconv( NCRRec, 'MD3' ) colData<4,3> = oconv( NCRRec, 'MD3' ) colData<5,3> = oconv( NCRRec, 'MD2S%' ) stat = Set_Printer('CALCTABLE',colFormat:@FM:colData) TableSize = Get_Printer('CALCTABLE') TableHeight = TableSize<2> IF Get_Printer('POS')<2> + Tableheight > MaxPrintLength THEN stat = Set_Printer('PAGEBREAK') END font<2> = 8 font<4> = 1 ;* Bold on stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) font<2> = 8 font<4> = 0 ;* Bold off stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL) LeftTableXPos = LeftTablePos<1> RightTableXPos = LeftTableXPos + 3.2 stat = Set_Printer('POS',LeftTablePos) ;* This moves the vertical to the top of the data point table ;* Position stuff is not documented correctly colHeader = 'Surface Defects' ; ColFormat = '<2160' colHeader<1,2> = 'Quantity' ; ColFormat<1,2> = '^2160' DataPoints = 'Pits,Mounds,BL Defects,Stack Faults,Spikes,Spots,FOV,Scratches,Scratch Length,Surf Defects,Surf Haze' CONVERT ',' TO @FM IN DataPoints colData = DataPoints colData<1,2> = OCONV(NCRRec,'MD0') colData<2,2> = OCONV(NCRRec,'MD0') colData<3,2> = OCONV(NCRRec,'MD0') colData<4,2> = OCONV(NCRRec,'MD0') colData<5,2> = OCONV(NCRRec,'MD0') colData<6,2> = OCONV(NCRRec,'MD0') colData<7,2> = OCONV(NCRRec,'MD0') colData<8,2> = OCONV(NCRRec,'MD0') colData<9,2> = OCONV(NCRRec,'MD0') colData<10,2> = OCONV(NCRRec,'MD0') colData<11,2> = OCONV(NCRRec,'MD2S%') TotalSurfaceDefects = 0 FOR L = 1 TO 10 IF L NE 9 THEN TotalSurfaceDefects += colData END NEXT L colData<13,1> = 'Total Surface Defects' colData<13,2> = TotalSurfaceDefects font<2> = 8 font<4> = 1 ;* Bold on stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',LTGREY$,'',0,TB_ALL:@FM:3.2) font<2> = 8 font<4> = 0 ;* Bold off stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL:@FM:3.2) END ;* End of check for datapoints NEXT I END ;* End of check for Makeup Wafer Flag RETURN * * * * * * * SurfScanResults: * * * * * * * * We have surface scan results colFormat = '<2880' colFormat<1,2> = '>900' colFormat<1,3> = '>900' colFormat<1,4> = '>900' colFormat<1,5> = '>900' PSId = RDSRec PSRec = XLATE('PROD_SPEC',PSId,'','X') PreEpiHazeAvgSpec = PSRec<101> FirstWaferHazeAvgSpec = PSRec<103> PostCleanHazeAvgSpec = PSRec<105> PreEpiDefectSpec = PSRec<100> FirstWaferDefectSpec = PSRec<102> PostCleanDefectSpec = PSRec<104> stat = Set_Printer('TEXT') FOR SurfScanNo = 1 TO COUNT(SurfScanKeys,@VM) + (SurfScanKeys NE '') SurfScanKey = SurfScanKeys<1,SurfScanNo> SurfScanRec = XLATE('SURFACE_SCAN',SurfScanKey,'','X') Stage = FIELD(SurfScanKey,'*',4) PopupData = XLATE('SYSREPOSPOPUPS','LSL2**STAGE',8,'X') StageDesc = '' FOR I = 1 TO COUNT(PopupData,@VM) + (PopupData NE '') PopCode = PopupData<1,I,1> IF PopCode = Stage THEN StageDesc = PopupData<1,I,2> UNTIL PopupData<1,I,1> = Stage NEXT I Tool = SurfScanRec colHeader = StageDesc:' - ':Tool:CRLF$:'Surface Scan Results' colHeader<1,2> = 'Spec' colHeader<1,3> = 'Min' colHeader<1,4> = 'Max' colHeader<1,5> = 'Avg' BEGIN CASE CASE Stage = 'PE' HazeSpec = PreEpiHazeAvgSpec DefectSpec = PreEpiDefectSpec CASE Stage = 'FW' HazeSpec = FirstWaferHazeAvgSpec DefectSpec = FirstWaferDefectSpec CASE Stage = 'PC' HazeSpec = PostCleanHazeAvgSpec DefectSpec = PostCleanDefectSpec END CASE colData = '' IF RdsRec = '6872' THEN colData<1,1> = 'Sum of Defects > .02':CHAR(230):'m' END ELSE colData<1,1> = 'Sum of Defects' END colData<1,2> = DefectSpec colData<1,3> = SurfScanRec colData<1,4> = SurfScanRec colData<1,5> = OCONV(SurfScanRec,'MD3') colData<2,1> = 'Surface Haze Avg (ppm)' colData<2,2> = HazeSpec colData<2,3> = SurfScanRec colData<2,4> = SurfScanRec colData<2,5> = OCONV(SurfScanRec,'MD3') font<2> = 8 font<4> = 1 ;* Bold on stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,colHeader,'',LTGREY$,'',0,TB_ALL:@FM:3.2) font<1> = 'MS LineDraw' ;* This font contains the omega symbol font<4> = 0 ;* Bold off stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL:@FM:3.2) font<1> = 'Arial' ;* Reset font to normal stat = Set_Printer('FONT',font) NEXT SurfScanNo RETURN