COMPILE SUBROUTINE Print_Control_Plan( PSNo, WONo ) DECLARE SUBROUTINE ErrMsg DECLARE FUNCTION Set_Printer, Get_printer, Msg,obj_Install,Printer_Select, obj_Prod_Spec, obj_Recipe, obj_Popup DECLARE FUNCTION obj_Met_Prop, obj_PRS_Layer, obj_PRS_Prop $INSERT OIPRINT_EQUATES $INSERT PROD_SPEC_EQUATES $INSERT QUOTE_SPEC_EQU $INSERT WO_LOG_EQUATES $INSERT COMPANY_EQU $INSERT RECIPE_EQU $INSERT RDS_LAYER_EQUATES $INSERT PRS_PROP_EQUATES $INSERT RDS_TEST_EQUATES $INSERT PRS_LAYER_EQUATES $INSERT PRS_STAGE_EQUATES $INSERT RECIPE_PARMS_EQU $INSERT APPCOLORS $INSERT EPI_PART_EQUATES $INSERT CUST_EPI_PART_EQUATES $INSERT TOOL_CLASS_EQUATES $Insert LOGICAL 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_PSN$ TO 2 EQU STEP_PROCESS_NAME$ TO 3 EQU STEP_TOOL_TYPE$ TO 4 EQU STEP_PRODUCT$ TO 5 EQU STEP_EVAL_MEAS$ TO 6 EQU STEP_RECIPE$ TO 7 EQU STEP_SPEC_TOL$ TO 8 EQU STEP_SIZE$ TO 9 EQU STEP_FREQ$ TO 10 EQU STEP_CTRL_METHOD$ TO 11 EQU STEP_REACT_PLAN$ TO 12 EQU COL$PROCESS TO 1 ;* Used to parse popup data from PROCESS_TOOL_CONTROL_REACT_PLAN popup EQU COL$TOOL_GROUP TO 2 EQU COL$TOOL_CLASS TO 3 EQU COL$CONTROL_METHOD TO 4 EQU COL$REACT_PLAN TO 5 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> = '0' ;* Show all buttons. 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) IF WONo NE '' THEN WORec = XLATE('WO_LOG',WONo,'','X') ProdOrdNo = WORec EpiPartNo = WORec ProdVerNo = WORec SubPartNo = WORec CustNo = WORec CustName = XLATE('COMPANY',CustNo,COMPANY_CO_NAME$,'X') CustEpiPartRec = XLATE('CUST_EPI_PART',CustNo:'*':EpiPartNo,'','X') CustPartNos = CustEpiPartRec CustPartDescs = CustEpiPartRec EpiPartRec = XLATE('EPI_PART',EpiPartNo,'','X') Orientation = EpiPartRec ProdType = EpiPartRec END ELSE CustPartNos = '' CustPartDescs = '' CustName = '' ProdOrdNo = '' EpiPartNo = '' EpiPartRec = '' ProdVerNo = '' SubPartNo = '' Orientation = '' ProdType = '' END 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) END ELSE stat = Set_Printer('TEXTXY','PSN: ':PSNo:' - ':CustName,psnStartX:@FM:-0.60,font,1) END font<2> = 12 ;* Drop the font size font<5> = 0 ;* Italics off stat = Set_Printer('FOOTER',"Page 'P'":@VM:@VM:"'T' 'D'") * * * * Added 7/27/2015 by JCH * * * * * * * AppName = @APPID<1> PTCPlan = XLATE('SYSREPOSPOPUPS',AppName:'**PROCESS_TOOL_CONTROL_REACT_PLAN',8,'X') ;* Get literal data defined in poup CONVERT @VM TO @FM IN PTCPlan CONVERT @SVM TO @VM IN PTCPlan PTCPData = '' pCnt = COUNT(PTCPlan,@FM) + (PTCPlan NE '') FOR I = 1 TO pCnt PTCPData = PTCPlan PTCPData = PTCPLan PTCPData = PTCPlan PTCPData = PTCPlan PTCPData = PTCPlan NEXT I * * * * End of new section 7/27/2015 * Extract Prod Spec data WORec = XLATE('WO_LOG',WONo,'','X') PSNRec = XLATE('PROD_SPEC',PSNo,'','X') SpecType = XLATE('PROD_SPEC',PSNo,'SPEC_TYPE','X') ;* Aded 8/22/2012 HC SpecSubInfo = PSNRec ReactorType = OCONV(PSNRec ,'[REACT_TYPE_CONV,OPSREF]' ) SpecialInst = PSNRec ;* 3/25/2013 JCH ProveinInst = PSNRec ;* 3/25/2013 JCH EntryDt = OCONV(PSNRec,'D4/') RevDt = OCONV(PSNRec,'D4/') KeyContact = "Onsite Quality Representative (480) 668-4000" CoreTeam = 'Executive Director, Process Engineering Manager, Maintenance Engineering Manager, Manufacturing Manager (480) 668-4000' SpecTypeConv = '' BEGIN CASE CASE SpecType = 'U' Sig = PSNRec ;* Added 8/22/2012 JCH SigDt = PSNRec[1,'.'] ;* Added 8/22/2012 JCH SpecTypeConv = OCONV(SpecType,'[SPEC_TYPE_CONV]') CASE SpecType = 'Q' Sig = PSNRec ;* Added 8/22/2012 JCH SigDt = PSNRec[1,'.'] ;* Added 8/22/2012 JCH SpecTypeConv = OCONV(SpecType,'[SPEC_TYPE_CONV]') CASE SpecType = 'E' Sig = PSNRec ;* Added 8/22/2012 JCH SigDt = PSNRec[1,'.'] ;* Added 8/22/2012 JCH SpecTypeConv = OCONV(SpecType,'[SPEC_TYPE_CONV]') CASE SpecType = 'P' Sig = PSNRec ;* Added 8/22/2012 JRO SigDt = PSNRec[1,'.'] ;* Added 8/22/2012 JRO SpecTypeConv = OCONV(SpecType,'[SPEC_TYPE_CONV]') CASE SpecType = 'Prod' Sig = PSNRec ;* Added 8/22/2012 JRO SigDt = PSNRec[1,'.'] ;* Added 8/22/2012 JRO SpecTypeConv = 'Production' CASE SpecType = 'PreProd' Sig = PSNRec ;* Added 8/22/2012 JRO SigDt = PSNRec[1,'.'] ;* Added 8/22/2012 JRO SpecTypeConv = 'Pre-Production' CASE SpecType = 'Qual' Sig = PSNRec ;* Added 8/22/2012 JRO SigDt = PSNRec[1,'.'] ;* Added 8/22/2012 JRO SpecTypeConv = 'Qual' CASE SpecType = 'PreQual' Sig = PSNRec ;* Added 8/22/2012 JRO SigDt = PSNRec[1,'.'] ;* Added 8/22/2012 JRO SpecTypeConv = 'Pre-Qual' 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> = 'PSN':CRLF$:'Original Dt' ; colFormat<1,6> = '^1080' colHeader<1,7> = 'PSN':CRLF$:'Last Rev' ; colFormat<1,7> = '^1080' colData = PSNRec //colData<1,2> = OCONV(SpecType,'[SPEC_TYPE_CONV]') colData<1,2> = SpecTypeConv 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) ;* this goes away when done developing PRSLayerKeys = PSNRec lCnt = COUNT(PRSLayerKeys,@VM) + (PRSLayerKeys NE '') LSIDs = '' Dopants = '' colData = '' lsData = '' ;* Layer Set - Property data recData = '' ;* Layer Set - Recipe data stepData = '' ;* Layer Data for production Step section of report lsHeader = 'LS':CRLF$:'Id':@VM ; lsFormat = '^540':@VM lsHeader<1,2> = 'Dopant':@VM ; lsFormat<1,2> = '^1380':@VM lsHeader<1,3> = 'Measure':@VM ; lsFormat<1,3> = '<1560':@VM lsHeader<1,4> = 'Minimum':@VM ; lsFormat<1,4> = '^1440':@VM lsHeader<1,5> = 'Target':@VM ; lsFormat<1,5> = '^1440':@VM lsHeader<1,6> = 'Maximum':@VM ; lsFormat<1,6> = '^1440':@VM lsHeader<1,7> = 'Tool':@VM ; lsFormat<1,7> = '<1020':@VM lsHeader<1,8> = 'Monitor Type':@VM ; lsFormat<1,8> = '<1260':@VM lsHeader<1,9> = 'Recipe':@VM ; lsFormat<1,9> = '<1260':@VM lsHeader<1,10> = 'Pattern':@VM ; lsFormat<1,10> = '^1260':@VM lsHeader<1,11> = 'Frq':@VM ; lsFormat<1,11> = '^540':@VM lsHeader<1,12> = 'ProveIn Type' ; lsFormat<1,12> = '<1260' // Total twips = 14400 recHeader = 'LS':CRLF$:'Id':@VM ; recFormat = '^540':@VM recHeader<1,2> = 'Deposit':@VM ; recFormat<1,2> = '^1155':@VM recHeader<1,3> = 'Diluent':@VM ; recFormat<1,3> = '^1155':@VM recHeader<1,4> = 'Dopant Flow':@VM ; recFormat<1,4> = '^1155':@VM recHeader<1,5> = 'Bake Time':@VM ; recFormat<1,5> = '^1155':@VM recHeader<1,6> = 'H2 Flow':@VM ; recFormat<1,6> = '^1155':@VM recHeader<1,7> = 'Silane Flow':@VM ; recFormat<1,7> = '^1155':@VM recHeader<1,8> = 'Aux1 Flow':@VM ; recFormat<1,8> = '^1155':@VM recHeader<1,9> = 'F Offset':@VM ; recFormat<1,9> = '^1155':@VM recHeader<1,10> = 'S Offset':@VM ; recFormat<1,10> = '^1155':@VM recHeader<1,11> = 'R Offset':@VM ; recFormat<1,11> = '^1155':@VM recHeader<1,12> = 'Susc Etch':@VM ; recFormat<1,12> = '^1155':@VM recHeader<1,13> = 'Etch' ; recFormat<1,13> = '^1155' FOR I = 1 TO lCnt PRSLayerKey = PRSLayerKeys<1,I> PRSLayerRec = XLATE('PRS_LAYER',PRSLayerKey,'','X') ;* 1st layer record LayerNo = FIELD(PRSLayerKey,'*',2) LSID = PRSLayerRec RecipeNo = PRSLayerRec PropKeys = obj_PRS_Layer('SortPropKeys',PRSLayerKey:@RM:PRSLayerRec) RecipeRec = XLATE('RECIPE',RecipeNo,'','X') ;* 1st layer receipe Dopant = RecipeRec IF I = 1 THEN RecipeEntryDt = OCONV(RecipeRec,'D4/') RecipeLastModDt = OCONV(RecipeRec,'D4/') RecipeName = RecipeRec EpiGas = RecipeRec BEGIN CASE CASE EpiGas _EQC 'SiH4' ; EpiGasName = 'Silane' CASE EpiGas _EQC 'SiH2CL2' ; EpiGasName = 'DiChloroSilane (DCS)' CASE EpiGas _EQC 'SiHCL3' ; EpiGasName = 'TriChloroSilane (TCS)' CASE 1 ; EpiGasName = '' END CASE SWAP @VM WITH CRLF$ IN CustPartNos SWAP @VM WITH CRLF$ IN CustPartDescs colData<1,1> = 'Silcon Epitaxy' colData<1,2> = PSNo colData<1,3> = CustPartNos colData<1,4> = CustPartDescs colData<1,5> = RecipeNo colData<1,6> = Recipename colData<1,7> = RecipeEntryDt colData<1,8> = RecipeLastModDt colData<1,9> = EpiGas colData<1,10> = SubPartNo colData<1,11> = Orientation colData<1,12> = ProdType colHeader = 'Product' ; colFormat = '<2160' colHeader<1,2> = 'PSN' ; colFormat<1,2> = '^720' colHeader<1,3> = 'Cust Part No' ; colFormat<1,3> = '^1440' colHeader<1,4> = 'Part Desc' ; colFormat<1,4> = '<2160' colHeader<1,5> = 'Rec No' ; colFormat<1,5> = '^720' colHeader<1,6> = 'Recipe' ; colFormat<1,6> = '^1080' colHeader<1,7> = 'Org Dt' ; colFormat<1,7> = '^1080' colHeader<1,8> = 'Last Rev' ; colFormat<1,8> = '^1080' colHeader<1,9> = 'Epi Gas' ; colFormat<1,9> = '^1080' colHeader<1,10> = 'Prod Sub No' ; colFormat<1,10> = '^1440' colHeader<1,11> = 'Orient' ; colFormat<1,11> = '^720' colHeader<1,12> = 'Type' ; colFormat<1,12> = '^720' 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') END ;* End of check for 1st layaer IF I = 1 THEN lsDopant = Dopant end else lsDopant = '' end propCnt = COUNT(PropKeys,@VM) + (PropKeys NE '') FOR P = 1 TO propCnt PropKey = PropKeys<1,P> PropCd = FIELD(PropKey,'*',3) PropRec = XLATE('PRS_PROP',PropKey,'','X') MinTarMax = obj_PRS_Prop('GetMinTarMax',PropKey:@RM:PropRec) Units = obj_Popup('CodeDesc','MET_PROPERTY':@RM:PropCd:@RM:5) DescUnits = obj_Popup('CodeDesc','MET_PROPERTY':@RM:PropCd:@RM:6) IF P = 1 THEN lsData = LSID lsData = lsDopant lsData = OCONV(PropCd,'[CONV_CODE_DESC,MET_PROPERTY]') lsData = MinTarMax<1>:' ':Units lsData = MinTarMax<2>:' ':Units lsData = MinTarMax<3>:' ':Units lsData = PropRec lsData = PropRec lsData = PropRec lsData = PropRec lsData = PropRec lsData = PropRec END ELSE lsData = lsData:CRLF$ lsData = lsData:CRLF$ lsData = lsData:CRLF$:OCONV(PropCd,'[CONV_CODE_DESC,MET_PROPERTY]') lsData = lsData:CRLF$:MinTarMax<1>:' ':Units lsData = lsData:CRLF$:MinTarMax<2>:' ':Units lsData = lsData:CRLF$:MinTarMax<3>:' ':Units lsData = lsData:CRLF$:PropRec lsData = lsData:CRLF$:PropRec lsData = lsData:CRLF$:PropRec lsData = lsData:CRLF$:PropRec lsData = lsData:CRLF$:PropRec lsData = lsData:CRLF$:PropRec END IF ReactorType = 'EPP' THEN ReactorType = 'EpiPro' * * * * * * * * * * * ******************************************************************************************* LOCATE ReactorType IN PTCPData USING @VM SETTING Pos THEN CtrlMethod = PTCPData ReactPlan = PTCPData END ELSE CtrlMethod = '*Err*' ReactPlan = '*Err*' END //JRO If PropRec EQ 'SRP' then sdPointer = I + ( P - 1 ) StepData = '' ;* Step number filled in later StepData = PSNo StepData = 'Epitaxy Layer ':LayerNo StepData = ReactorType StepData = OCONV(PropCd,'[CONV_CODE_DESC,MET_PROPERTY]') StepData = PropRec StepData = 'Epi Growth' StepData = MinTarMax<1>:'- ':MinTarMax<3>:' ':DescUnits StepData = PropRec StepData = PropRec StepData = CtrlMethod StepData = ReactPlan end else sdPointer = I + ( P - 1 ) StepData = '' ;* Step number filled in later StepData = PSNo StepData = 'Epitaxy Layer ':LayerNo StepData = ReactorType StepData = CHAR(185):OCONV(PropCd,'[CONV_CODE_DESC,MET_PROPERTY]') StepData = PropRec StepData = 'Epi Growth' StepData = MinTarMax<1>:'- ':MinTarMax<3>:' ':DescUnits StepData = PropRec StepData = PropRec StepData = CtrlMethod StepData = ReactPlan end NEXT P FOR C = 1 TO 12 lsData = lsData:CRLF$ NEXT C RecLimits = obj_Recipe('GetLimits',RecipeNo:@RM:PSNo:@RM:LSID) IF RecLimits NE '' THEN RecDepTime = OCONV(RecLimits:@SVM:RecLimits,'MD1') IF RecLimits = '' THEN DiluentFlowMin = RecLimits END ELSE DiluentFlowMin = RecLimits END IF RecLimits = '' THEN DiluentFlowMax = RecLimits END ELSE DiluentFlowMax = RecLimits END RecDiluent = OCONV(DiluentFlowMin:@SVM:DiluentFlowMax,'MD2') RecDopantFlow = OCONV(RecLimits:@SVM:RecLimits,'MD2') RecBakeTime = RecLimits:@SVM:RecLimits RecH2Flow = OCONV(RecLimits:@SVM:RecLimits,'MD0') RecTCSFlow = OCONV(RecLimits:@SVM:RecLimits,'MD1') RecDCSFlow = OCONV(RecLimits:@SVM:RecLimits,'MD0') RecAux1Flow = OCONV(RecLimits:@SVM:RecLimits,'MD2') RecFOffset = OCONV(RecLimits:@SVM:RecLimits,'MD0') RecSOffset = OCONV(RecLimits:@SVM:RecLimits,'MD0') RecROffset = OCONV(RecLimits:@SVM:RecLimits,'MD0') RecSuscEtch = OCONV(RecLimits:@SVM:RecLimits,'MD1') RecEtch1 = RecLimits:@SVM:RecLimits RecEtch2 = RecLimits:@SVM:RecLimits RecEtch3 = RecLimits:@SVM:RecLimits IF RecDiluent = @SVM THEN RecDiluent = '' IF RecDopantFlow = @SVM THEN RecDopantFlow = '' IF RecBakeTime = @SVM THEN RecBakeTime = '' IF RecH2Flow = @SVM THEN RecH2Flow = '' IF RecTCSFlow = @SVM THEN RecTCSFlow = '' IF RecDCSFlow = @SVM THEN RecDCSFlow = '' IF RecAux1Flow = @SVM THEN RecAux1Flow = '' IF RecFOffset = @SVM THEN RecFOffset = '' IF RecSOffset = @SVM THEN RecSOffset = '' IF RecROffset = @SVM THEN RecROffset = '' IF RecSuscEtch = @SVM THEN RecSuscEtch = '' IF RecEtch1 = @SVM THEN RecEtch1 = '' IF RecEtch2 = @SVM THEN RecEtch2 = '' IF RecEtch3 = @SVM THEN RecEtch3 = '' recData = LSID recData = RecDepTime recData = RecDiluent recData = RecDopantFlow recData = RecBakeTime recData = RecH2Flow IF I = 1 THEN IF RecTCSFlow = '' THEN recHeader<1,7> = 'DCS Flow' recData = RecDCSFlow END ELSE recHeader<1,7> = 'TCS Flow' recData = RecTCSFlow END END recData = RecAux1Flow recData = RecFOffset recData = RecSOffset recData = RecROffset recData = RecSuscEtch recData = RecEtch1:CRLF$:RecEtch2:CRLF$:RecEtch3 FOR C = 1 TO 13 recData = recData:CRLF$ NEXT C SWAP @SVM WITH ' ~ ' IN RecData END ;* End of check for a deposit time NEXT I font = 'MS LineDraw' font = 8 ;* 10 point font = 0 ;* Bold stat = Set_Printer('FONT',font) stat = Set_Printer('ADDTABLE', lsFormat,lsHeader,'',LTGREY$,'',0,TB_ALL) stat = Set_Printer('ADDTABLE',lsFormat,'',lsData,LTGREY$,'',1,TB_ALL) stat = Set_Printer('TEXT') stat = Set_Printer('ADDTABLE', recFormat,recHeader,'',LTGREY$,'',0,TB_ALL) stat = Set_Printer('ADDTABLE',recFormat,'',recData,LTGREY$,'',1,TB_ALL) stat = Set_Printer('TEXT') Sigs = '' * Process Steps colHeader = '' ; colFormat = '' colHeader<1,STEP_STEP$> = 'Step':@VM ; colFormat<1,STEP_STEP$> = '^540':@VM colHeader<1,STEP_PSN$> = 'PSN':@VM ; colFormat<1,STEP_PSN$> = '^540':@VM colHeader<1,STEP_PROCESS_NAME$> = 'Process Name':@VM ; colFormat<1,STEP_PROCESS_NAME$> = '<1440':@VM colHeader<1,STEP_TOOL_TYPE$> = 'Tool Group':@VM ; colFormat<1,STEP_TOOL_TYPE$> = '^1080':@VM colHeader<1,STEP_PRODUCT$> = 'Measurement':@VM ; colFormat<1,STEP_PRODUCT$> = '^1440':@VM colHeader<1,STEP_EVAL_MEAS$> = 'Tool Class':@VM ; colFormat<1,STEP_EVAL_MEAS$> = '^1440':@VM colHeader<1,STEP_RECIPE$> = 'Recipe /':CRLF$:'Pattern':@VM ; colFormat<1,STEP_RECIPE$> = '^1800':@VM colHeader<1,STEP_SPEC_TOL$> = 'Spec Tolerance':@VM ; colFormat<1,STEP_SPEC_TOL$> = '^2160':@VM colHeader<1,STEP_SIZE$> = 'Size':@VM ; colFormat<1,STEP_SIZE$> = '^900':@VM colHeader<1,STEP_FREQ$> = 'Freq':@VM ; colFormat<1,STEP_FREQ$> = '^900':@VM colHeader<1,STEP_CTRL_METHOD$> = 'Control':CRLF$:'Method' ; colFormat<1,STEP_CTRL_METHOD$> = '^720':@VM colHeader<1,STEP_REACT_PLAN$> = 'React Plan' ; colFormat<1,STEP_REACT_PLAN$> = '^1440' StepNo = 1 * Receiving Step ProcName = 'Receiving' LOCATE ProcName IN PTCPData USING @VM SETTING Pos THEN CtrlMethod = PTCPData ReactPlan = PTCPData END ELSE CtrlMethod = '*Err*' ReactPlan = '*Err*' END colData = '' colData = StepNo colData = ProcName colData = 'Paperwork' colData = PSNo colData = 'Documentation' colData = 'Manual' colData = 'Consistent Data' colData = 'Visual' colData = 'Shipment' colData = 'Per Cass' colData = CtrlMethod colData = ReactPlan Stages = obj_Popup('AllCodes','STAGE') CONVERT @VM TO @FM IN Stages CIStages = Stages StageCnt = COUNT(CIStages,@FM) + (CIStages NE '') FOR I = 1 TO StageCnt Stage = CIStages StageRec = XLATE('PRS_STAGE',PSNo:'*':Stage,'','X') InspFreq = StageRec StageDesc = obj_Popup('CodeDesc','STAGE':@RM:Stage) IF Stage = 'PRE' THEN IF EpiPartRec = 1 THEN StepNo += 1 colData = StepNo colData = PSNo colData = 'HF Strip' colData = 'HF' colData = 'SC-1' colData = '20min or Dewet' colData = '-' colData = 'HF' colData = '1 Cass' colData = 'All' colData = 'WI' colData = 'OCAP' END ;* End of Check for SubOxide Flag END ;* End of check for PRE stage IF StageRec NE '' THEN IF StageRec NE '' THEN If Stage _NEC 'POST' or StageRec EQ True$ then StepNo += 1 colData = StepNo colData = PSNo colData = StageDesc CleanTools = StageRec SWAP @VM WITH ', ' IN CleanTools ToolGroup = 'Cleans' LOCATE ToolGroup IN PTCPData USING @VM SETTING Pos THEN CtrlMethod = PTCPData ReactPlan = PTCPData END ELSE CtrlMethod = '*Err*' ReactPlan = '*Err*' END colData = ToolGroup colData = CleanTools colData = '-' ;*StageRec colData = StageRec colData = '-' colData = '1 Cass' colData = '' colData = CtrlMethod colData = ReactPlan end END ;* End of check for Clean Tool IF StageRec = 1 THEN StepNo += 1 ToolClass = 'BRIGHTLIGHT' LOCATE ToolClass IN PTCPData USING @VM SETTING Pos THEN CtrlMethod = PTCPData ReactPlan = PTCPData END ELSE CtrlMethod = '*Err*' ReactPlan = '*Err*' END colData = StepNo colData = PSNo colData = StageDesc colData = XLATE('TOOL_CLASS','BRIGHTLIGHT',TOOL_CLASS_TOOL_TYPE$,'X') colData = ToolClass colData = "Surface Quality" colData = 'Visual' colData = '<':StageRec colData = '1' If InspFreq EQ '' then colData = 'Per Cass' end else colData = InspFreq end colData = CtrlMethod colData = ReactPlan END ;* End of check for Brightlight flag IF StageRec = 1 THEN StepNo += 1 ToolClass = 'MICROSCOPE' LOCATE ToolClass IN PTCPData USING @VM SETTING Pos THEN CtrlMethod = PTCPData ReactPlan = PTCPData END ELSE CtrlMethod = '*Err*' ReactPlan = '*Err*' END colData = StepNo colData = PSNo colData = StageDesc colData = XLATE('TOOL_CLASS','MICROSCOPE',TOOL_CLASS_TOOL_TYPE$,'X') colData = ToolClass colData = 'Surface Quality' colData = 'Visual' colData = 'PSN:':PSNo:' - Surface Spec' colData = '1' If InspFreq EQ '' then colData = 'Per Cass' end else colData = InspFreq end colData = CtrlMethod colData = ReactPlan END ;* End of check for Microscope flag IF StageRec NE '' THEN If Stage _NEC 'POST' or StageRec EQ True$ then StepNo += 1 ToolClass = 'TENCOR' LOCATE ToolClass IN PTCPData USING @VM SETTING Pos THEN CtrlMethod = PTCPData ReactPlan = PTCPData END ELSE CtrlMethod = '*Err*' ReactPlan = '*Err*' END colData = StepNo colData = PSNo colData = StageDesc colData = XLATE('TOOL_CLASS','TENCOR',TOOL_CLASS_TOOL_TYPE$,'X') colData = ToolClass colData = "LPD's" colData = StageRec colData = 'See Hard Copy Spec' colData = StageRec colData = 'Per Cass' colData = CtrlMethod colData = ReactPlan end END ;* End of check for Surfscan Recipe IF StageRec NE '' THEN metCnt = COUNT(StageRec,@VM) + (StageRec NE '') FOR M = 1 TO metCnt MetTest = StageRec *IF StageRec NE '' THEN * Size = StageRec *END ELSE * Size = StageRec *END IF MetTest NE '' THEN StepNo += 1 colData = StepNo colData = PSNo processName = obj_Popup('CodeDesc','STAGE':@RM:Stage) colData = processName ToolClassType = XLATE('TOOL_CLASS',StageRec,TOOL_CLASS_TOOL_TYPE$,'X') IF ToolClassType = 'Metrology' THEN ToolClassType = 'Met' ToolGroup = 'QA_Met' END LOCATE ToolGroup IN PTCPData USING @VM SETTING Pos THEN CtrlMethod = PTCPData ReactPlan = PTCPData END ELSE CtrlMethod = '*Err*' ReactPlan = '*Err*' END colData = ToolGroup colData = StageRec If StageRec EQ 'FLEXUS' then colData = obj_Met_Prop('GetPropDesc',StageRec) end else colData = CHAR(185):obj_Met_Prop('GetPropDesc',StageRec) end colData = StageRec:CRLF$:StageRec colData = StageRec:' - ':StageRec:' ':obj_Met_Prop('GetUnitsDesc',StageRec) colData = StageRec colData = StageRec if processName EQ 'FQA' then colData = "WI" colData = "EpiMSA WI-0485" end else colData = CtrlMethod colData = ReactPlan END END NEXT M END END ;* End of check for null stage record * Insert LayerSet step data after the LOAD stage IF Stage = 'LOAD' THEN FOR SDLine = 1 TO sdPointer StepNo += 1 colData = StepNo FOR Col = STEP_PSN$ TO STEP_REACT_PLAN$ colData = StepData NEXT Col NEXT SDLine END NEXT I //Added per request from Matt Treanor - 4/14/2020 JRO ProcName = 'Packaging and Labeling ' StepNo += 1 colData = StepNo colData = ProcName colData = 'Packaging' colData = PSNo colData = 'Barcode Match' colData = 'Barcode' colData = 'Consistent Data' colData = 'Scanner' colData = '1' colData = '1' colData = 'OI' colData = 'EpiMSA WI-0113' ProcName = 'Shipping' LOCATE ProcName IN PTCPData USING @VM SETTING Pos THEN CtrlMethod = PTCPData ReactPlan = PTCPData END ELSE CtrlMethod = '*Err*' ReactPlan = '*Err*' END StepNo += 1 colData = StepNo colData = ProcName colData = 'Paperwork' colData = PSNo colData = 'Documentation' colData = 'Manual' colData = 'Consistent Data' colData = 'Visual' colData = 'Shipment' colData = 'Per Cass' colData = CtrlMethod colData = ReactPlan 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 ;* 3/25/2013 JCH ProveinInst = PSNRec ;* 3/25/2013 JCH 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