COMPILE SUBROUTINE Print_Control_Plan_New( PSNo, WONo ) DECLARE SUBROUTINE ErrMsg DECLARE FUNCTION Set_Printer, Get_printer, Msg,obj_Install,Printer_Select, obj_Prod_Spec $INSERT OIPRINT_EQUATES $INSERT PROD_SPEC_EQU $INSERT QUOTE_SPEC_EQU $INSERT WO_LOG_EQU $INSERT ORDER_DET_EQU $INSERT COMPANY_EQU $INSERT RECIPE_EQU $INSERT RDS_LAYER_EQUATES $INSERT RDS_TEST_EQUATES $INSERT PRS_LAYER_EQU $INSERT APPCOLORS 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 FONT_NAME$ TO 1 EQU FONT_SIZE$ TO 2 EQU FONT_JUST$ TO 3 EQU FONT_BOLD$ TO 4 EQU FONT_ITALIC$ TO 5 EQU FONT_UNDERLINE$ TO 6 EQU STEP_STEP$ TO 1 EQU STEP_PROCESS_NAME$ TO 2 EQU STEP_MACHINE$ TO 3 EQU STEP_PSN$ TO 4 EQU STEP_PRODUCT$ TO 5 EQU STEP_PROCESS$ TO 6 EQU STEP_SPEC_TOL$ TO 7 EQU STEP_EVAL_MEAS$ TO 8 EQU STEP_SIZE$ TO 9 EQU STEP_FREQ$ TO 10 EQU STEP_CTRL_METHOD$ TO 11 EQU STEP_REACT_PLAN$ TO 12 IF NOT(ASSIGNED(PSNo)) THEN RETURN IF NOT(ASSIGNED(WONo)) THEN WONo = '' * * * PRINT SETUP * * * FileName = 'Print Control Plan' Title = 'Print Control Plan' 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 PageSetup = 1 ;* 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, 'Run Data Sheet',PageInfo,PageSetup,PrintSetup) Margins = Get_Printer('MARGIN') LMargin = Margins<1> TMargin = Margins<2> RMargin = Margins<3> BMargin = Margins<4> PageSize = Get_Printer('PAGESIZE') PageWidth = PageSize<1> PageHeight = PageSize<2> MaxPrintWidth = PageWidth - LMargin - RMargin MaxPrintHeight = PageHeight - TMargin - BMargin font = 'Arial' ;* Font basics font<2> = 10 font<4> = 0 stat = Set_Printer('FONTHEADFOOT', font) stat = Set_Printer('LINESTYLE', PS_SOLID:@FM:2) stat = Set_Printer('LINE', -0.1:@FM:-1.2:@FM:10.0:@FM:-1.2, 1) stat = Set_Printer('LINE', -0.1:@FM:-0.1:@FM:10.0:@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) RSideGraphicX = (1.57 - .15) RSideTextX = (MaxPrintWidth - 1.75) HeaderMidX = ((RSideTextX - RSideGraphicX)/2) + RSideGraphicX * * * * 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,RSideTextX:@FM:-1.15,font,1) stat = Set_Printer('TEXTXY',Division,RSideTextX:@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'), RSideTextX:@fm:-0.775, font,1) stat = Set_Printer('TEXTXY',obj_Install('Get_Prop','CSZC'), RSideTextX:@fm:-0.625, font,1) stat = Set_Printer('TEXTXY','Tel: ':obj_Install('Get_Prop','Phone'), RSideTextX:@fm:-0.475, font, 1) stat = Set_Printer('TEXTXY','FAX: ':obj_Install('Get_Prop','FAX'), RSideTextX:@fm:-0.325, font, 1) * * * * End of changes 10/8/2015 JCH * * * * font = 'Arial' font<2> = '18' ;* Big type font<4> = 1 ;* Bold on font<5> = 1 ;* Italics stat = Set_Printer('FONT',font) stat = Set_Printer("CALCTEXT", 'Control Plan') titleSize = Get_Printer("CALCTEXT") titleWidth = titleSize<1> titleHeight = titleSize<2> titleStartX = HeaderMidX - (titleWidth/2) stat = Set_Printer('TEXTXY','Control Plan',titleStartX:@FM:-1.0,font,1) font<2> = '16' font<4> = 0 stat = Set_Printer('FONT',font) CustName = XLATE('PROD_SPEC',PSNo,'CUST_NAME','X') stat = Set_Printer("CALCTEXT", 'PSN: ':PSNo:' - ':CustName) psnSize = Get_Printer("CALCTEXT") psnWidth = psnSize<1> psnHeight = psnSize<2> psnStartX = HeaderMidX - (psnWidth/2) stat = Set_Printer("CALCTEXT", 'Work Order No: ':WONo) woSize = Get_Printer("CALCTEXT") woWidth = woSize<1> woHeight = woSize<2> woStartX = HeaderMidX - (woWidth/2) IF WONo NE '' THEN stat = Set_Printer('TEXTXY','PSN: ':PSNo:' - ':CustName,psnStartX:@FM:-0.68,font,1) stat = Set_Printer('TEXTXY','Work Order No: ':WONo,woStartX:@FM:-0.40,font,1) WORec = XLATE('WO_LOG',WONo,'','X') Order = WORec OrdItem = WORec SubPartNo = XLATE('ORDER_DET',Order:'*':OrdItem,ORDER_DET_SUB_PART_NO$,'X') END ELSE stat = Set_Printer('TEXTXY','PSN: ':PSNo:' - ':CustName,psnStartX:@FM:-0.60,font,1) SubPartNo = '' END font<2> = 12 ;* Drop the font size font<5> = 0 ;* Italics off stat = Set_Printer('FOOTER',"Page 'P'":@VM:@VM:"'T' 'D'") * Extract Prod Spec data WORec = XLATE('WO_LOG',WONo,'','X') PSNRec = XLATE('PROD_SPEC',PSNo,'','X') SpecSubInfo = PSNRec SpecialInst = SpecSubInfo<1,QSSubInstructions$> Orientation = SpecSubInfo<1,QSSubOrientation$> ProdType = SpecSubInfo<1,QSSubType$> SpecAddtl = PSNRec ProveinInst = SpecAddtl<1,QSAddProveInInst$> EntryDt = OCONV(PSNRec,'D2/') RevDt = OCONV(PSNRec,'D2/') KeyContact = "Onsite Quality Representative (480) 668-4000" CoreTeam = 'Executive Director, Quality Manager, Process Engineering Manager, Maintenance Engineering Manager, Manufacturing Manager (480) 668-4000' *SWAP @TM WITH CRLF$ IN SpecialInst *SWAP @TM WITH CRLF$ IN ProveInInst SpecType = PSNrec BEGIN CASE CASE SpecType = 'U' Sig = PSNRec SigDt = PSNRec CASE SpecType = 'Q' Sig = PSNRec SigDt = PSNRec CASE SpecType = 'X' Sig = PSNRec SigDt = PSNRec CASE SpecType = 'P' Sig = PSNRec SigDt = PSNRec END CASE Font = 'Arial' Font = 'L' Font = 8 Font = 0 Font = 0 Void = Set_Printer( 'FONT', Font ) * First line of Specification colHeader = 'Description' ; colFormat = '^1440' colHeader<1,2> = 'Type' ; colFormat<1,2> = '^1440' colHeader<1,3> = 'Signed' ; colFormat<1,3> = '^1080' colHeader<1,4> = 'Key Contact' ; colFormat<1,4> = '^2520' colHeader<1,5> = 'Core Team' ; colFormat<1,5> = '^5760' colHeader<1,6> = 'Original Dt' ; colFormat<1,6> = '^1080' colHeader<1,7> = 'Last Rev' ; colFormat<1,7> = '^1080' colData = PSNRec colData<1,2> = OCONV(SpecType,'[SPEC_TYPE_CONV]') colData<1,3> = OCONV(SigDt,'D4/') colData<1,4> = KeyContact colData<1,5> = CoreTeam colData<1,6> = EntryDt colData<1,7> = RevDt stat = Set_Printer('ADDTABLE', colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL) stat = Set_Printer('TEXT') * Second line of Specification PSNLayerProps = obj_Prod_Spec('GetLayerProp',PSNo) LSIDs = '' Dopants = '' colData = '' FOR I = 1 TO COUNT(PSNLayerProps,@RM) + (PSNLayerProps NE '') LayerSet = FIELD(PSNLayerProps,@RM,I) LSIDs = LayerSet<1> LayerSet = FIELD(LayerSet,@FM,2,99) Dopants<1,I> = LayerSet IF I = 1 THEN RecipeNo = LayerSet RecipeRec = XLATE('RECIPE',RecipeNo,'','X') RecipeName = RecipeRec EpiGas = RecipeRec BEGIN CASE CASE EpiGas = 'SiH4' ; EpiGasName = 'Silane' CASE EpiGas = 'SiH2CL2' ; EpiGasName = 'DiChloroSilane (DCS)' CASE EpiGas = 'SiH1HCL3' ; EpiGasName = 'TriChloroSilane (TCS)' CASE 1 ; EpiGasName = '' END CASE CustPartNos = PSNRec CustPartDescs = PSNRec SWAP @VM WITH CRLF$ IN CustPartNos SWAP @VM WITH CRLF$ IN CustPartDescs colData = 'Silcon Epitaxy' colData = PSNo colData = CustPartNos colData = CustPartDescs colData = Recipename colData = EpiGas colData = SubPartNo colData = Orientation colData = ProdType END NEXT I colHeader = 'Product' ; colFormat = '<2160' colHeader<1,2> = 'Prod Spec' ; colFormat<1,2> = '^1440' colHeader<1,3> = 'Cust Part No' ; colFormat<1,3> = '^1440' colHeader<1,4> = 'Part Desc' ; colFormat<1,4> = '<2160' colHeader<1,5> = 'Recipe' ; colFormat<1,5> = '^1440' colHeader<1,6> = 'Epi Gas' ; colFormat<1,6> = '^1440' colHeader<1,7> = 'Prod Sub No' ; colFormat<1,7> = '^1440' colHeader<1,8> = 'Prod Orientation' ; colFormat<1,8> = '^1440' colHeader<1,9> = 'Prod Type' ; colFormat<1,9> = '^1440' stat = Set_Printer('ADDTABLE', colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL) colData = '' stat = Set_Printer('TEXT') colHeader = 'LS':CRLF$:'Id':@VM ; colFormat = '^540':@VM colHeader<1,2> = 'Dopant':@VM ; colFormat<1,2> = '^1440':@VM colHeader<1,3> = 'Measure':@VM ; colFormat<1,3> = '<1440':@VM colHeader<1,4> = 'Minimum':@VM ; colFormat<1,4> = '^1440':@VM colHeader<1,5> = 'Target':@VM ; colFormat<1,5> = '^1440':@VM colHeader<1,6> = 'Maximum':@VM ; colFormat<1,6> = '^1440':@VM colHeader<1,7> = 'Tool':@VM ; colFormat<1,7> = '<1080':@VM colHeader<1,8> = 'Monitor Type':@VM ; colFormat<1,8> = '<1440':@VM colHeader<1,9> = 'Recipe':@VM ; colFormat<1,9> = '<2160':@VM colHeader<1,10> = 'Frq':@VM ; colFormat<1,10> = '^540':@VM colHeader<1,11> = 'ProveIn Type' ; colFormat<1,11> = '<1440' * Build Step Data * * * * ReactorType = OCONV(PSNRec ,'[REACT_TYPE_CONV,OPSREF]' ) LayerCnt = COUNT(LSIDs,@FM) + (LSIDs NE '') SDIndex = 0 StepData = '' colData = '' FOR I = 1 TO LayerCnt LayerSet = LSIDs LayerSpecs = obj_Prod_Spec('GetLayerProp',PSNo:@RM:LayerSet:@RM:'') ;* Last parameter specifies no output conversion on return data LayerSpecs = FIELD(LayerSpecs,@FM,2,99) ;* Returns with the layer set ID in the first field of each line LSID = LSIDs ThickMin = LayerSpecs ThickTarget = LayerSpecs ThickMax = LayerSpecs ThickUnits = LayerSpecs ThickMTool = LayerSpecs ThickMType = LayerSpecs ThickMRecipe = LayerSpecs ThickMFreq = LayerSpecs ThickMPIType = LayerSpecs ThickMFirst = LayerSpecs ThickMLast = LayerSpecs ThickMSPC = LayerSpecs ThickMOvergrow = LayerSpecs ResMin = LayerSpecs ResTarget = LayerSpecs ResMax = LayerSpecs ResUnits = LayerSpecs ResMTool = LayerSpecs ResMType = LayerSpecs ResMRecipe = LayerSpecs ResMFreq = LayerSpecs ResMPIType = LayerSpecs ResMFirst = LayerSpecs ResMLast = LayerSpecs ResMSPC = LayerSpecs ResMOvergrow = LayerSpecs IF I = 1 THEN FirstResUnits = ResUnits ConMin = LayerSpecs ConTarget = LayerSpecs ConMax = LayerSpecs ConUnits = LayerSpecs ConMTool = LayerSpecs ConMType = LayerSpecs ConMRecipe = LayerSpecs ConMFreq = LayerSpecs ConMPIType = LayerSpecs ConMFirst = LayerSpecs ConMLast = LayerSpecs ConMSPC = LayerSpecs ConMOvergrow = LayerSpecs CResMin = LayerSpecs CResTarget = LayerSpecs CResMax = LayerSpecs CResUnits = LayerSpecs CResMTool = LayerSpecs CResMType = LayerSpecs CResMRecipe = LayerSpecs CResMFreq = LayerSpecs CResMPIType = LayerSpecs CResMFirst = LayerSpecs CResMLast = LayerSpecs CResMSPC = LayerSpecs CResMOvergrow = LayerSpecs colData = LSID colData = Dopants<1,I> colData = 'Thickness' colData = ThickMin:ThickUnits colData = ThickTarget:ThickUnits colData = ThickMax:ThickUnits colData = ThickMTool colData = ThickMType colData = ThickMRecipe colData = ThickMFreq colData = ThickMPIType IF ResTarget NE '' THEN colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$:'Resistivity' colData = colData:CRLF$:ResMin:ResUnits colData = colData:CRLF$:ResTarget:ResUnits colData = colData:CRLF$:ResMax:ResUnits colData = colData:CRLF$:ResMTool colData = colData:CRLF$:ResMType colData = colData:CRLF$:ResMRecipe colData = colData:CRLF$:ResMFreq colData = colData:CRLF$:ResMPIType END IF ConTarget NE '' THEN colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$:'Concentration' colData = colData:CRLF$:ConMin:ConUnits colData = colData:CRLF$:ConTarget:ConUnits colData = colData:CRLF$:ConMax:ConUnits colData = colData:CRLF$:ConMTool colData = colData:CRLF$:ConMType colData = colData:CRLF$:ConMRecipe colData = colData:CRLF$:ConMFreq colData = colData:CRLF$:ConMPIType END IF CResTarget NE '' THEN colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$:'CRes' colData = colData:CRLF$:CResMin:CResUnits colData = colData:CRLF$:CResTarget:CResUnits colData = colData:CRLF$:CResMax:CResUnits colData = colData:CRLF$:CResMTool colData = colData:CRLF$:CResMType colData = colData:CRLF$:CResMRecipe colData = colData:CRLF$:CResMFreq colData = colData:CRLF$:CResMPIType END colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$ colData = colData:CRLF$ IF ThickMTool NE '' THEN SDIndex += 1 SWAP 'æm' WITH 'um' in ThickUnits SWAP '' WITH 'A' in ThickUnits Freq = '' IF ThickMFirst NE '' THEN Freq = 'First, ' IF ThickMFreq NE '' THEN Freq := ThickMFreq:', ' IF ThickMLast NE '' THEN Freq := 'Last' IF ThickMSPC = '' THEN ThickMSPC = '0' stepData = SDIndex stepData = 'Epitaxy Layer ':I stepData = ReactorType stepData = PSNo stepData = CHAR(185):'Thickness' stepData = 'Epi Growth' stepData = ThickMin:' - ':ThickMax:ThickUnits stepData = ThickMTool stepData = ThickMType stepData = ThickMFreq stepData = OCONV(ThickMSPC, 'BSPC,WI' ) stepData = 'OCAP' END IF ResMTool NE '' THEN SDIndex += 1 SWAP 'ê-cm' WITH 'ohm.cm' in ResUnits SWAP 'ê/Ü' WITH 'ohm/sq' in ResUnits IF ResMtype = 'Prod' THEN ResMType = '1 Prod Wafer' Freq = '' IF ResMFirst NE '' THEN Freq = 'First, ' IF ResMFreq NE '' THEN Freq := ResMFreq:', ' IF ResMLast NE '' THEN Freq := 'Last' IF ResMSPC = '' THEN ResMSPC = '0' stepData = SDIndex stepData = 'Epitaxy Layer ':I stepData = ReactorType stepData = PSNo stepData = CHAR(185):'Resistivity' stepData = 'Epi Growth' stepData = ResMin:' - ':ResMax:ResUnits stepData = ResMTool stepData = ResMType stepData = ResMFreq stepData = OCONV(ResMSPC,'BSPC,WI') stepData = 'OCAP' END IF ConMTool NE '' THEN SDIndex += 1 SWAP 'ê-cm' WITH 'ohm.cm' in ConUnits SWAP 'ê/Ü' WITH 'ohm/sq' in ConUnits Freq = '' IF ConMFirst NE '' THEN Freq = 'First, ' IF ConMFreq NE '' THEN Freq := ConMFreq:', ' IF ConMLast NE '' THEN Freq := 'Last' IF ConMType = 'Prod' THEN ConMType = '1 Prod Wafer' IF ConMTool = 'SRP' THEN SpecTol = 'See Hard Copy Spec' Product = 'SRP' Frequency = 'Per Metrology' END ELSE SpecTol = ConMin:' - ':ConMax:ConUnits Product = 'Conductivity' Frequency = ConMFreq END IF ConMSPC = '' THEN ConMSPC = '0' stepData = SDIndex stepData = 'Epitaxy Layer ':I stepData = ReactorType stepData = PSNo stepData = Product stepData = 'Epi Growth' stepData = SpecTol stepData = ConMTool stepData = ConMType stepData = Frequency stepData = OCONV(ConMSPC,'BSPC,WI') stepData = 'OCAP' END IF CResMTool NE '' THEN SDIndex += 1 SWAP 'ê-cm' WITH 'ohm.cm' in CResUnits SWAP 'ê/Ü' WITH 'ohm/sq' in CResUnits IF CresMType = 'Prod' THEN CresMType = '1 Prod Wfr' Freq = '' IF CResMFirst NE '' THEN Freq = 'First, ' IF CResMFreq NE '' THEN Freq := CResMFreq:', ' IF CResMLast NE '' THEN Freq := 'Last' IF CResMSPC = '' THEN CResMSPC = '0' stepData = SDIndex stepData = 'Epitaxy Layer ':I stepData = ReactorType stepData = PSNo stepData = 'CRes' stepData = 'Epi Growth' stepData = CResMin:' - ':CResMax:CResUnits stepData = CResMTool stepData = CResMType stepData = CResMFreq stepData = OCONV(CResMSPC,'BSPC,WI') stepData = 'OCAP' END NEXT I font = 'MS LineDraw' font = 8 ;* 10 point font = 0 ;* Bold stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE', colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) Font = 0 Void = Set_Printer( 'FONT', Font ) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL) stat = Set_Printer('TEXT') Sigs = '' * Process Steps colHeader = 'Step':@VM ; colFormat = '^540':@VM colHeader<1,2> = 'Process Name':@VM ; colFormat<1,2> = '<1440':@VM colHeader<1,3> = 'Machine':@VM ; colFormat<1,3> = '<1080':@VM colHeader<1,4> = 'PSN':@VM ; colFormat<1,4> = '^540':@VM colHeader<1,5> = 'Product':@VM ; colFormat<1,5> = '^1440':@VM colHeader<1,6> = 'Process':@VM ; colFormat<1,6> = '^1800':@VM colHeader<1,7> = 'Spec Tolerance':@VM ; colFormat<1,7> = '<2160':@VM colHeader<1,8> = 'Evaluation Meas':@VM ; colFormat<1,8> = '<1440':@VM colHeader<1,9> = 'Size':@VM ; colFormat<1,9> = '^1080':@VM colHeader<1,10> = 'Freq':@VM ; colFormat<1,10> = '^1080':@VM colHeader<1,11> = 'Control':CRLF$:'Method' ; colFormat<1,11> = '^720' colHeader<1,12> = 'React Plan' ; colFormat<1,12> = '^1080' StepNo = 1 colData = '' colData = StepNo colData = 'Receiving' colData = 'Paperwork' colData = PSNo colData = 'Paperwork' colData = 'Manual' colData = 'Consistent Data' colData = 'Visual' colData = 'Shipment' colData = 'Per Cass' colData = 'WI' colData = 'Pass/Fail' * * Pre Epi Cleaning and Inspection * * SCSubOxide = PSNRec SCAngstroms = PSNRec SCTool = PSNRec SCToolRecipe = PSNRec IF SCTool[1,2] _EQC 'NO' THEN SCTool = '' SBrightLight = PSNRec SMicroscope = PSNRec SSurfscan = PSNRec SSurfscanRecipe = PSNRec * Sub Oxide Strip IF SCSubOxide = 1 THEN StepNo += 1 colData = StepNo colData = 'HF Strip' colData = 'HF' colData = PSNo colData = 'SC-1' colData = '20min or Dewet' colData = 'NA' colData = 'HF' colData = '1 Cass' colData = 'All' colData = 'WI' colData = 'OCAP' END * Pre Clean - Done ****** IF SCTool NE '' OR SCToolRecipe NE '' THEN IF SCTool = 'If Necessary' THEN SCTool = 'Akrion' StepNo += 1 colData = StepNo colData = 'Pre-epi Clean' colData = SCTool colData = PSNo colData = 'Cleaning' colData = SCToolRecipe colData = 'NA' colData = 'Visual' colData = '1 Cass' colData = 'Per Cass' colData = 'WI' colData = 'OCAP' END * Pre Brightlight - Done ***** IF SBrightLight = 1 THEN StepNo += 1 colData = StepNo colData = 'Pre-epi Insp' colData = 'Brightlight' colData = PSNo colData = CHAR(185):"LPD's" colData = 'Visual' colData = '<':PSNRec colData = 'Brightlight' colData = '1 Prod Wfr' colData = 'Per Cass' colData = 'WI' colData = 'OCAP' END * Pre Microscope - Done ***** IF SMicroscope = 1 THEN StepNo += 1 colData = StepNo colData = 'Pre-epi Insp' colData = 'Microscope' colData = PSNo colData = 'Surface Quality' colData = 'Visual' colData = 'PSN:':PSNo:' - Surface Spec' colData = 'Microscope' colData = '1 Prod Wfr' colData = 'Per Cass' colData = 'WI' colData = 'OCAP' END * Pre Surface Scan - Done ***** IF SSurfscan = 1 OR SSurfscanRecipe NE '' THEN StepNo += 1 colData = StepNo colData = 'Pre-epi Insp' colData = 'SurfScan' colData = PSNo colData = CHAR(185):"LPD's" colData = SSurfscanRecipe colData = 'See Hard Copy Spec' colData = 'SurfScan' colData = '1 Prod Wfr' colData = 'Per Cass' colData = 'WI' colData = 'OCAP' END FOR I = 1 TO SDIndex StepNo += 1 colData = StepData colData = StepNo NEXT I * * First/Last Wafer Cleaning and Inspection * * Spec_FWI_LWI = PSNRec ;* FWI OR LWI SCTool = PSNRec SCToolRecipe = PSNRec IF SCTool[1,2] _EQC 'NO' THEN SCTool = '' IF SCToolRecipe[1,2] _EQC 'NO' THEN SCToolRecipe = '' SBrightLight = PSNRec SMicroscope = PSNRec SSurfscan = PSNRec SSurfscanRecipe = PSNRec * FirstWafer Brightlight - Done ***** IF Spec_FWI_LWI = 'LWI' THEN ProcessName = 'Last Wafer Insp' END ELSE ProcessName = 'First Wafer Insp' END IF SBrightLight = 1 THEN StepNo += 1 colData = StepNo colData = ProcessName colData = 'Brightlight' colData = PSNo colData = CHAR(185):"LPD's" colData = 'Visual' colData = '<':PSNRec colData = 'Brightlight' colData = '1 Prod Wfr' colData = 'Per Cass' colData = 'WI' colData = 'OCAP' END * FirstWafer Microscope - Done ***** IF SMicroscope = 1 THEN StepNo += 1 colData = StepNo colData = ProcessName colData = 'Microscope' colData = PSNo colData = 'Surface Quality' colData = 'Visual' colData = 'PSN:':PSNo:' - Surface Spec' colData = 'Microscope' colData = '1 Prod Wfr' colData = 'Per Cass' colData = 'WI' colData = 'OCAP' END * First SurfScan - Done ***** IF SSurfscan = 1 OR SSurfscanRecipe NE '' THEN StepNo += 1 colData = StepNo colData = ProcessName colData = 'SurfScan' colData = PSNo colData = CHAR(185):"LPD's" colData = SSurfscanRecipe colData = 'See Hard Copy Spec' colData = 'Surf Scan' colData = '1 Prod Wfr' colData = 'Per Cass' colData = 'WI' colData = 'OCAP' END * * Post Epi Cleaning and Inspection * * SBrightLight = PSNRec SSurfscan = PSNRec SSurfscanRecipe = PSNRec SCTool = PSNRec SCToolRecipe = PSNRec FirstLPDLimit = PSNRec * Post Cleaning - Done ***** IF SCTool NE '' OR SCToolRecipe NE '' THEN IF SCTool = 'If Necessary' THEN Process = 'Akrion' StepNo += 1 colData = StepNo colData = 'Post-epi Clean' colData = SCTool colData = PSNo colData = 'Cleaning' colData = SCToolRecipe colData = 'NA' colData = 'Visual' colData = '1 Cass' colData = 'Per Cass' colData = 'WI' colData = 'OCAP' END * Post Epi Brightlight - Done **** IF SBrightLight = 1 THEN StepNo += 1 colData = StepNo colData = 'Post-epi Insp' colData = 'Brightlight' colData = PSNo colData = CHAR(185):"LPD's" colData = 'Visual' colData = '<':FirstLPDLimit colData = 'Brightlight' colData = '1 Prod Wfr' colData = 'Per Cass' colData = 'WI' colData = 'OCAP' END * Post Epi SurfScan - Not found below! IF SSurfscan = 1 OR SSurfscanRecipe NE '' THEN StepNo += 1 colData = StepNo colData = 'Post-epi Insp' colData = 'SurfScan' colData = PSNo colData = CHAR(185):"LPD's" colData = SSurfscanRecipe colData = 'See Hard Copy Spec' colData = 'SurfScan' colData = PSNRec colData = 'Per Cass' colData = 'WI' colData = 'OCAP' END StepNo += 1 colData = StepNo colData = 'Shipping' colData = 'Paperwork' colData = PSNo colData = 'Paperwork' colData = 'Manual' colData = 'Consistent Data' colData = 'Visual' colData = 'Shipment' colData = 'Per Cass' colData = 'WI' colData = 'Pass/Fail' Font = 'Arial' Font = 'L' Font = 8 Font = 0 Font = 0 Void = Set_Printer( 'FONT', Font ) stat = Set_Printer('ADDTABLE', colFormat,colHeader,'',LTGREY$,'',0,TB_ALL) stat = Set_Printer('ADDTABLE',colFormat,'',colData,LTGREY$,'',1,TB_ALL) *************************************************** stat = Set_Printer("CALCTEXT",CHAR(185):'Note: Special Characteristics') noteSize = Get_Printer("CALCTEXT") noteWidth = noteSize<1> noteHeight = noteSize<2> stat = Set_Printer('TEXT') stat = Set_Printer('TEXT',CHAR(185):'Note: Special Characteristics') stat = Set_Printer('TEXT') SpecialInst = PSNRec ProveinInst = PSNRec SWAP @TM WITH CRLF$ IN SpecialInst SWAP @TM WITH CRLF$ IN ProveInInst colHeader = 'Special Instructions' colFmt = '^14400' colData = SpecialInst stat = Set_Printer('CALCTABLE',colFmt:@FM:colData) TableSize = Get_Printer('CALCTABLE') TableHeight = TableSize<2> CurrY = Get_Printer('POS')<2> IF CurrY + noteHeight + TableHeight > MaxPrintHeight THEN stat = Set_Printer('PAGEBREAK') END Font<2> = 10 Font<4> = 0 Void = Set_Printer( 'FONT', Font ) stat = Set_Printer('ADDTABLE', colFmt,colHeader,'',LTGREY$,'',0,TB_ALL) colFmt = '<14400' stat = Set_Printer('ADDTABLE',colFmt,'',colData,LTGREY$,'',1,TB_ALL) stat = Set_Printer('TEXT') colHeader = 'Prove-In Instructions' colFmt = '^14400' colData = ProveinInst stat = Set_Printer('CALCTABLE',colFmt:@FM:colData) TableSize = Get_Printer('CALCTABLE') TableHeight = TableSize<2> CurrY = Get_Printer('POS')<2> IF CurrY + noteHeight + TableHeight > MaxPrintHeight THEN stat = Set_Printer('PAGEBREAK') END Font<2> = 10 Font<4> = 0 Void = Set_Printer( 'FONT', Font ) stat = Set_Printer('ADDTABLE', colFmt,colHeader,'',LTGREY$,colData,0,TB_ALL) colFmt = '<14400' stat = Set_Printer('ADDTABLE',colFmt,'',colData,LTGREY$,'',1,TB_ALL) stat = set_printer( 'TERM' ) RETURN