777 lines
21 KiB
Plaintext
777 lines
21 KiB
Plaintext
COMPILE SUBROUTINE Print_WO_Mat_Out_Labels(WONo,CassNos)
|
||
#pragma precomp SRP_PreCompiler
|
||
|
||
$INSERT LOGICAL
|
||
$INSERT MSG_EQUATES
|
||
$INSERT OIPRINT_EQUATES
|
||
$INSERT PROD_SPEC_EQUATES
|
||
$INSERT POPUP_EQUATES
|
||
$INSERT QUOTE_SPEC_EQU
|
||
$INSERT WO_LOG_EQUATES
|
||
$INSERT WO_STEP_EQU
|
||
$INSERT WO_MAT_EQUATES
|
||
$INSERT ORDER_EQU
|
||
$INSERT ORDER_DET_EQU
|
||
$INSERT WM_IN_EQUATES
|
||
$INSERT CUST_EPI_PART_EQUATES
|
||
|
||
DECLARE FUNCTION Msg, Get_Printer, Set_Printer, Utility, obj_Install, Printer_Select, FieldCount, Popup
|
||
DECLARE FUNCTION MemberOF, Direct_Print, Environment_Services
|
||
DECLARE SUBROUTINE Btree.Extract, ErrMsg
|
||
|
||
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(CassNos)) THEN CassNos = ''
|
||
|
||
CassCnt = COUNT(CassNos,@VM) + (CassNos NE '')
|
||
|
||
BEGIN CASE
|
||
|
||
CASE CassNos = ''
|
||
|
||
WOMatKeys = XLATE('WO_LOG',WONo,WO_LOG_WO_MAT_KEY$,'X')
|
||
wmCnt = COUNT(WOMatKeys,@VM) + (WOMatKeys NE '')
|
||
|
||
TypeOver = ''
|
||
TypeOver<PDISPLAY$> = WOMatKeys
|
||
TypeOver<PTITLE$> = 'WO Material - Outbound Cassettes'
|
||
|
||
WOMatKeys = Popup(@WINDOW,TypeOver,'PRINT_WO_MAT_OUT_LABELS')
|
||
|
||
|
||
CASE CassCnt = 1
|
||
WOMatKeys = WONo:'*':CassNos
|
||
|
||
CASE 1
|
||
|
||
SWAP @VM WITH @VM:WONo:'*' IN CassNos
|
||
WOMatKeys = WONo:'*':CassNos
|
||
|
||
|
||
END CASE
|
||
|
||
|
||
IF WOMatKeys = '' THEN RETURN
|
||
|
||
|
||
FileName = "Printing Label"
|
||
Title = "Printing Label"
|
||
|
||
PageInfo = ''
|
||
PageInfo<PI$LEFT> = 0.1
|
||
PageInfo<PI$TOP> = 0.1
|
||
PageInfo<PI$RIGHT> = 0.1
|
||
PageInfo<PI$BOTTOM> = 0.1
|
||
|
||
|
||
PageSetup = '1' ;* Landscape
|
||
PrintSetup = '' ;* Preview
|
||
|
||
PrinterID = ''
|
||
PrintPath = Printer_Select(PrinterID) ;* Popup is skipped IF Printer ID is passed
|
||
|
||
If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then
|
||
stat = Set_Printer("INIT",FileName,Title,PageInfo,PageSetup,PrintSetup,PrintPath)
|
||
end else
|
||
stat = Direct_Print('START', PrintPath<1>, '', '')
|
||
end
|
||
|
||
IF stat < 0 THEN GOTO OIPrint_Error
|
||
|
||
CLOrientation = '' ;* used for printing on cleanroom labels
|
||
|
||
Void = Utility( 'CURSOR', 'H' )
|
||
|
||
WOStepKeys = XLATE('WO_LOG',WONo,WO_LOG_WO_STEP_KEY$,'X')
|
||
|
||
WOStep = 1 ;* Step is always 1 for material being received
|
||
|
||
IF INDEX(WOStepKeys,@VM,1) THEN
|
||
PrintWONo = WONo:'.':WOStep
|
||
END ELSE
|
||
PrintWONo = WONo
|
||
END
|
||
|
||
WORec = XLATE('WO_LOG',WONo,'','X')
|
||
|
||
ReqShipDate = OCONV(WORec<WO_LOG_PROMISE_SHIP_DT$>,'D2/')
|
||
|
||
CustNo = WORec<WO_LOG_CUST_NO$>
|
||
CustName = XLATE('COMPANY',CustNo,'ABBREV_OR_CO_NAME','X')
|
||
Captive = XLATE('COMPANY',CustNo,'CAPTIVE','X')
|
||
PONo = WORec<WO_LOG_CUST_PO_NO$>
|
||
|
||
PSNo = XLATE('WO_STEP',WONo:'*':WOStep,WO_STEP_PROD_SPEC_ID$,'X')
|
||
PSRec = XLATE('PROD_SPEC',PSNo,'','X')
|
||
|
||
CustSpecNo = ''
|
||
IF Captive THEN
|
||
CustSpecNos = PSRec<PROD_SPEC_SPEC_NUM$>
|
||
CustSpecDescs = PSRec<PROD_SPEC_SPEC_DESC$>
|
||
CustSpecRevNos = PSRec<PROD_SPEC_REV_NUM$>
|
||
CustSpecRevDts = PSRec<PROD_SPEC_REV_DATE$>
|
||
|
||
SpecCnt = COUNT(CustSpecNos,@VM) + (CustSpecNos NE '')
|
||
|
||
FOR I = 1 TO SpecCnt
|
||
IF CustSpecDescs<1,I> _EQC 'GENERAL' THEN
|
||
CustSpecNo = CustSpecNos<1,I>
|
||
CustSpecDesc = CustSpecDescS<1,I>
|
||
CustSpecRevNo = CustSpecRevNos<1,I>
|
||
CustSpecRevDt = OCONV(CustSpecRevDts<1,I>,'D4/')
|
||
END
|
||
UNTIL CustSpecNo NE ''
|
||
|
||
NEXT I
|
||
END
|
||
|
||
|
||
EpiPartNo = WORec<WO_LOG_EPI_PART_NO$>
|
||
CustEpiPartRec = XLATE('CUST_EPI_PART',CustNo:'*':EpiPartNo,'','X')
|
||
|
||
ShipBagReq = CustEpiPartRec<CUST_EPI_PART_SHIP_BAG_REQ$>
|
||
|
||
PreSurfscan = PSRec<PROD_SPEC_PRE_SURFSCAN$>
|
||
FirstSurfscan = PSRec<PROD_SPEC_FIRST_SURFSCAN$>
|
||
PostCleanSurfScan = PSRec<PROD_SPEC_POST_CLEAN_SURFSCAN$>
|
||
|
||
SubPreClean = XLATE( 'PROD_SPEC', PSNo, 'SUB_PRE_CLEAN', 'X' )
|
||
SubPostClean = XLATE( 'PROD_SPEC', PSNo, 'SUB_POST_CLEAN', 'X' )
|
||
|
||
PreCleanTool = SubPreClean ;* Temporary for 2x4 -> 4x4 conversion
|
||
PostCleanTool = SubPostClean
|
||
|
||
PreAkrionRecipe = XLATE( 'PROD_SPEC', PSNo, 'PRE_AKRION_RECIPE', 'X' )
|
||
PostAkrionRecipe = XLATE( 'PROD_SPEC', PSNo, 'POST_AKRION_RECIPE', 'X' )
|
||
|
||
RecipeNo = XLATE( 'PROD_SPEC', PSNo, 'RECIPE_NO_L1', 'X' )
|
||
RecipeName = XLATE( 'PROD_SPEC', PSNo, 'RECIPE_NAME_L1', 'X' )
|
||
|
||
SpecType = OCONV( XLATE( 'PROD_SPEC', PSNo, 'SPEC_TYPE', 'X' ), '[SPEC_TYPE_CONV]' )
|
||
SubOxide = OCONV( XLATE( 'PROD_SPEC', PSNo, 'SUB_OXIDE_STRIP', 'X' ), 'B' )
|
||
ThickTarget = OCONV( XLATE( 'PROD_SPEC', PSNo, 'THICK_TARGET_ALL', 'X' ), 'MD2' )
|
||
ResTarget = OCONV( XLATE( 'PROD_SPEC', PSNo, 'RES_TARGET_ALL', 'X' ), 'MD3' )
|
||
|
||
ThickUnit = XLATE( 'PROD_SPEC', PSNo, 'THICK_UNITS_ALL', 'X' )
|
||
ResUnit = XLATE( 'PROD_SPEC', PSNo , 'RES_UNITS_ALL', 'X' )
|
||
|
||
Dopant = XLATE( 'PROD_SPEC', PSNo, 'DOPANT_L1', 'X' )
|
||
RecipeNo = XLATE( 'PROD_SPEC', PSNo, 'RECIPE_NO', 'X' )
|
||
RecipeInfo = XLATE( 'RECIPE', RecipeNo, 'RECIPE_NAME_NO', 'X' )
|
||
|
||
CleaningReqs = ''
|
||
|
||
ThickCnt = FIELDCOUNT( ThickTarget<1>, @VM )
|
||
PrintThickTargets = ''
|
||
FOR J = 1 TO ThickCnt
|
||
PrintThickTargets<1,J> = ThickTarget<1,J>:ThickUnit<1,J>
|
||
NEXT J
|
||
|
||
ResCnt = FIELDCOUNT( ResTarget<1>, @VM )
|
||
PrintResTargets = ''
|
||
FOR J = 1 TO ResCnt
|
||
IF ResTarget<1,J>[1,1] = '.' THEN
|
||
TargetVal = '0':ResTarget<1,J>
|
||
END ELSE
|
||
TargetVal = ResTarget<1,J>
|
||
END
|
||
PrintResTargets<1,J> = TargetVal:ResUnit<1,J>
|
||
NEXT J
|
||
|
||
APreRec = ''
|
||
APostRec = ''
|
||
IF ( PreAkrionRecipe<1> <> '' ) THEN
|
||
APreRec = ' ':PreAkrionRecipe:' '
|
||
SubOxide = 'No' ;* If Akrion then no oxide strip
|
||
END
|
||
|
||
IF ( PostAkrionRecipe<1> <> '' ) THEN
|
||
APostRec = ' ':PostAkrionRecipe
|
||
END
|
||
|
||
PrintCleaningReqs = TRIM( 'Strip:':SubOxide:' Pre:':SubPreClean:APreRec:' Post:':SubPostClean:APostRec )
|
||
|
||
|
||
swap 'æm' with 'um' in PrintThickTargets
|
||
swap 'ê-cm' with 'ohm.cm' in PrintThickTargets
|
||
swap 'ê/Ü' with 'ohm/sq' in PrintThickTargets
|
||
swap '' with 'A' in PrintThickTargets
|
||
swap 'æm' with 'um' in PrintResTargets
|
||
swap 'ê-cm' with 'ohm.cm' in PrintResTargets
|
||
swap 'ê/Ü' with 'ohm/sq' in PrintResTargets
|
||
swap '' with 'A' in PrintResTargets
|
||
|
||
WMIBoxCnt = COUNT( WOMatKeys, @VM ) + (WOMatKeys NE '')
|
||
|
||
GOSUB PrintCleanRoomLabels
|
||
|
||
GOSUB PrintWOLabels ;* Activated WO label printing again -dkk 12/3/14
|
||
|
||
MonitorWafer = CustEpiPartRec<CUST_EPI_PART_MONITOR_WAFER_LABEL$>
|
||
|
||
IF MonitorWafer THEN
|
||
GOSUB PrintMonitorLabels
|
||
END
|
||
|
||
* * * * * *
|
||
OIPrint_Error:
|
||
* * * * * *
|
||
|
||
If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then
|
||
stat = Set_Printer("TERM")
|
||
end else
|
||
stat = Direct_Print('STOP')
|
||
end
|
||
|
||
RETURN
|
||
|
||
|
||
|
||
* * * * * * * * * * * *` L o c a l S u b r o u t i n e s * * * * * * * * * * * *
|
||
|
||
* * * * * * *
|
||
PrintCleanRoomLabels:
|
||
* * * * * * *
|
||
|
||
|
||
FOR I = 1 TO WMIBoxCnt
|
||
|
||
WOMatKey = WOMatKeys<1,I>
|
||
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
||
MakeupBox = ''
|
||
PrintWOMatKey = WOMatKey
|
||
CONVERT '*' TO '.' IN PrintWOMatKey
|
||
|
||
CassNo = WOMatKey[-1,'B*']
|
||
LotNo = WOMatRec<WO_MAT_LOT_NO$>
|
||
WfrQty = WOMatRec<WO_MAT_WAFER_QTY$>
|
||
CustPartNo = WOMatRec<WO_MAT_CUST_PART_NO$>
|
||
SubPartNo = WOMatRec<WO_MAT_SUB_PART_NO$>
|
||
OrderItem = WOMatRec<WO_MAT_ORDER_ITEM$>
|
||
OrderDetKey = WORec<WO_LOG_ORDER_NO$>:'*':OrderItem
|
||
SubVendCode = WORec<WO_LOG_EXP_VEND_CD$>
|
||
|
||
LOCATE CustPartNo IN CustEpiPartRec<CUST_EPI_PART_CUST_PART_NO$> USING @VM SETTING Pos THEN
|
||
CustPartDesc = CustEpiPartRec<CUST_EPI_PART_CUST_PART_DESC$,Pos>
|
||
END ELSE
|
||
CustPartDesc = ''
|
||
END
|
||
|
||
PartNo = CustPartNo ;* Temporary for 4x2 to 4x4 conversion
|
||
PartDesc = CustPartDesc ;* Temporary for 4x2 to 4x4 conversion
|
||
SuppCd = XLATE('WO_LOG',WONo,'EXP_VEND_CD','X')
|
||
Vendor = XLATE('SEMI_VEND_CODE', SubVendCode, 'EPI_VEND_CD', 'X')
|
||
|
||
GOSUB PrintLabel
|
||
|
||
NEXT I
|
||
|
||
RETURN
|
||
|
||
* * * * * * *
|
||
PrintLabel:
|
||
* * * * * * *
|
||
Str = ''
|
||
For cnt = 1 to 2
|
||
***** Start of label ZPL
|
||
Str := '^XA'
|
||
Str := '^LH0,0'
|
||
Str := '^PR2' ;* Print speed 2 inches per second
|
||
Str := '^LL406' ;* Label length @203 dpi
|
||
Str := '^PW900'
|
||
Str := '^MD15' ;* Media darkness
|
||
Str := '^MMT' ;* Media mode t=tear off mode
|
||
//Str := '^PQ2' ;* Print 2 labels for each pass through here
|
||
Str := '^FWN':CRLF$ ;* Normal orientation
|
||
|
||
Str := '^FO10,5^GB795,398,3,B^FS':CRLF$ ;* Border
|
||
|
||
****** First Line
|
||
Company = 'IFX Epi Services'
|
||
Str := '^FO30,20^A0,45,36^FD':Company:'^FS':CRLF$
|
||
Str := '^FO290,25^AC,18^FDWO No:^FS':CRLF$
|
||
Str := '^FO370,20^A045,36^FD':PrintWONo:'^FS':CRLF$
|
||
|
||
IF CassNo = 1 THEN
|
||
Str := '^FO535,15^GB120,40,40,,3^FS':CRLF$
|
||
Str := '^FO540,25^AC,18^FR^FDCass:^FS':CRLF$
|
||
Str := '^FO600,20^A045,36^FR^FD':CassNo:'^FS':CRLF$
|
||
END ELSE
|
||
Str := '^FO540,25^AC,18^FDCass:^FS':CRLF$
|
||
Str := '^FO600,20^A045,36^FD':CassNo:'^FS':CRLF$
|
||
END
|
||
Str:= '^FO665,20^A045,36^FDWM Out^FS':CRLF$
|
||
|
||
****** Second Line
|
||
Str:= '^FO30,70^AC,18^FDWM Out:^FS':CRLF$
|
||
Str:= '^FO120,65^A050,30^FD':PrintWOMatKey:'^FS':CRLF$
|
||
Str := '^BY2,2.0':CRLF$
|
||
|
||
Str := '^FO300,58^B3,,37,N^FD':'O':PrintWOMatKey:'^FS':CRLF$
|
||
Str := '^BY2,3.0':CRLF$
|
||
|
||
Str:= '^FO700,60^AC,18^FDQty:^FS':CRLF$
|
||
Str:= '^FO760,60^A045,25^FD':WfrQty:'^FS':CRLF$
|
||
|
||
****** Third Line
|
||
Str:= '^FO30,100^AC,18^FDShip Dt:^FS':CRLF$
|
||
Str:= '^FO140,100^A045,25^FD':ReqShipDate:'^FS':CRLF$
|
||
|
||
Str:= '^FO250,100^AC,18^FDCust:^FS':CRLF$
|
||
Str:= '^FO320,100^A045,25^FD':CustName:'^FS':CRLF$
|
||
|
||
Str:= '^FO560,100^AC,18^FDPO:^FS':CRLF$
|
||
Str:= '^FO600,100^A045,25^FD':PONo:'^FS':CRLF$
|
||
|
||
****** Separator bar
|
||
Str:= '^FO15,125^GB790,1^FS':CRLF$
|
||
|
||
****** Fourth Line
|
||
Str := '^FO30,130^AC,18^FDLot No:^FS':CRLF$
|
||
Str := '^FO120,130^A0,20^FD':LotNo:'^FS':CRLF$
|
||
Str := '^FO410,130^AC,18^FDPart No:^FS':CRLF$
|
||
Str := '^FO510,130^A0,20^FD':PartNo:'^FS':CRLF$
|
||
|
||
****** Fifth Line
|
||
Str := '^FO30,155^AC,18^FDSub PN:^FS':CRLF$
|
||
Str := '^FO120,155^A0,20^FD':SubPartNo:'^FS':CRLF$
|
||
|
||
IF SuppCd NE '' THEN
|
||
Str := '^FO410,155^AC,18^FDSupp Cd:^FS':CRLF$ ;* Label ;* Added 8/17/2005 JCH - J.C.Henry & Co.
|
||
Str := '^FO510,155^A0,20^FD':SuppCd:'^FS':CRLF$ ;* Data
|
||
Str := '^BY2,2.0':CRLF$
|
||
Str := '^FO610,155^A040,20^B3,,23,N^FD':SuppCd:'^FS':CRLF$
|
||
Str := '^BY2,3.0':CRLF$
|
||
END
|
||
|
||
****** Separator bar
|
||
Str := '^FO15,180^GB790,1^FS':CRLF$
|
||
|
||
IF MakeupBox THEN
|
||
Str := '^FO410,190^A0,30^FD* * * M a k e u p B o x * * *^FS':CRLF$
|
||
END ELSE
|
||
Str := '^FO410,190^AC,18^FDReact Type:^FS':CRLF$ ;* Added 12/17/2008 - JCH
|
||
Str := '^FO560,190^A0,20^FDGaN^FS':CRLF$ ;* Added 12/17/2008 - JCH
|
||
END
|
||
|
||
****** Seventh Line
|
||
Str := '^FO30,190^AC,18^FDPre:^FS':CRLF$
|
||
Str := '^FO90,190^A0,20^FD':SubPreClean:'^FS':CRLF$
|
||
|
||
IF PreAkrionRecipe NE '' THEN
|
||
Str := '^FO210,190^AC,18^FDAkrion:^FS':CRLF$
|
||
Str := '^FO300,190^A0,20^FD':PreAkrionRecipe:'^FS':CRLF$
|
||
|
||
Str := '^BY2,2.0':CRLF$
|
||
Str := '^FO450,190^A040,20^B3,,23,N^FD':PreAkrionRecipe:'^FS':CRLF$
|
||
Str := '^BY2,3.0':CRLF$
|
||
END
|
||
|
||
****** Eighth Line
|
||
Str := '^FO30,225^AC,18^FDRecipe:^FS':CRLF$
|
||
Str := '^FO120,225^A0,20^FD':RecipeInfo:'^FS':CRLF$
|
||
|
||
Str := '^FO410,225^AC,18^FDEpi Dopant:^FS':CRLF$
|
||
Str := '^FO560,225^A040,20^FD':Dopant:'^FS':CRLF$
|
||
|
||
****** Tenth, Eleventh and Twelfth Lines
|
||
Str := '^FO30,260^AC,18^FDThk Spec:^FS':CRLF$
|
||
|
||
FOR M = 1 TO COUNT(PrintThickTargets,@VM) + (PrintThickTargets NE '')
|
||
BaseLine = 260 + (M-1)*20
|
||
Str := '^FO140,':BaseLine:'^A0,20^FD':PrintThickTargets<1,M>:'^FS':CRLF$
|
||
NEXT M
|
||
|
||
Str := '^FO410,260^AC,18^FDRes Spec:^FS':CRLF$
|
||
|
||
FOR M = 1 TO COUNT(PrintResTargets,@VM) + (PrintResTargets NE '')
|
||
BaseLine = 260 + (M-1)*20
|
||
Str := '^FO520,':BaseLine:'^A0,20^FD':PrintResTargets<1,M>:'^FS':CRLF$
|
||
NEXT M
|
||
|
||
****** The Line with No Name
|
||
IF PostAkrionRecipe NE '' THEN
|
||
Str := '^FO30,335^AC,18^FDPost:^FS':CRLF$
|
||
Str := '^FO90,335^A0,20^FD':SubPostClean:'^FS':CRLF$
|
||
Str := '^FO210,335^AC,18^FDAkrion:^FS':CRLF$
|
||
Str := '^FO300,335^A0,20^FD':PostAkrionRecipe:'^FS':CRLF$
|
||
Str := '^BY2,2.0':CRLF$
|
||
Str := '^FO450,335^A040,20^B3,,23,N^FD':PostAkrionRecipe:'^FS':CRLF$
|
||
Str := '^BY2,3.0':CRLF$
|
||
END ELSE
|
||
Str := '^FO30,335^AC,18^FDPost:^FS':CRLF$
|
||
Str := '^FO120,335^A0,20^FD':SubPostClean:'^FS':CRLF$
|
||
END
|
||
|
||
****** Separator bar
|
||
Str := '^FO15,365^GB790,1^FS':CRLF$
|
||
|
||
****** Data Matrix barcode
|
||
Str := '^FO720,280^CI28':CRLF$
|
||
Str := '^BXN,2,200^FDP':PartNo:'|S':SubPartNo:'|1T':PrintWOMatKey:'|2T':LotNo:'|':PSNo:'|Q':WfrQty:'|1V':Vendor:'|SEQ':Cnt:'^FS':CRLF$
|
||
|
||
****** Fourteenth Line
|
||
Str := '^FO30,375^AC,18^FDProd Spec No:^FS':CRLF$
|
||
Str := '^FO190,375^A0,25^FD':PSNo:'^FS':CRLF$
|
||
|
||
IF SpecType = 'Production' THEN SpecType = 'Prod'
|
||
IF SpecType = 'Pre-Production' THEN SpecType = 'Pre'
|
||
|
||
Str := '^FO250,375^AC,18^FDSpec Type:^FS':CRLF$
|
||
Str := '^FO375,375^A0,25^FD':SpecType:'^FS':CRLF$
|
||
|
||
Str:= '^FO500,375^AC,18^FDBag:^FS':CRLF$
|
||
Str:= '^FO550,375^A0,20^FD':ShipBagReq:'^FS':CRLF$
|
||
|
||
Str:= '^XZ':CRLF$
|
||
Next
|
||
|
||
If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then
|
||
stat = Set_Printer('TEXT',Str)
|
||
end else
|
||
stat = Direct_Print('PRINT', Str)
|
||
end
|
||
|
||
|
||
RETURN
|
||
|
||
|
||
* * * * * * *
|
||
PrintBigLabel:
|
||
* * * * * * *
|
||
|
||
Str = '^XA' ;* Start of label format
|
||
Str := '^LH22,70' ;* Label home offset (needed to get onto the label medium)
|
||
Str := '^BY3' ;* Set narrow Bar Code line width to 3 dots
|
||
Str := '^PR2' ;* Print speed = 2 IPS
|
||
Str := '^PQ2'
|
||
|
||
|
||
Str := '^FO15,15^GB795,786,3,B^FS' ;* Border
|
||
|
||
*Str:= '^FO670,25^A0,36^FDWM Out^FS'
|
||
Str:= '^FO680,25^A0,36^FDWM In^FS'
|
||
|
||
****** First Line
|
||
|
||
Str := '^FO30,25^A0,,36^FD':obj_Install('Get_Prop','Company'):'^FS'
|
||
|
||
|
||
Str := '^FO290,25^AC,18^FDWO No:^FS':CRLF$ ;* Label
|
||
Str := '^FO370,25^A045,36^FD':PrintWONo:'^FS':CRLF$ ;* Data
|
||
|
||
IF CassNo = 1 THEN
|
||
Str := '^FO535,20^GB120,40,40,,3^FS':CRLF$
|
||
Str := '^FO540,25^AC,18^FR^FDCass:^FS':CRLF$ ;* Label
|
||
Str := '^FO600,25^A045,36^FR^FD':CassNo:'^FS':CRLF$ ;* Data
|
||
END ELSE
|
||
Str := '^FO540,25^AC,18^FDCass:^FS':CRLF$ ;* Label
|
||
Str := '^FO600,25^A045,36^FD':CassNo:'^FS':CRLF$ ;* Data
|
||
END
|
||
|
||
|
||
****** Second Line
|
||
|
||
Str:= '^FO30,70^AC,18^FDWM In:^FS':CRLF$
|
||
Str:= '^FO120,70^A050,30^FD':PrintWOMatKey:'^FS':CRLF$
|
||
|
||
Str := '^BY2,2.0':CRLF$
|
||
Str := '^FO300,70^B3,,23,N^FD':'I':PrintWOMatKey:'^FS':CRLF$
|
||
Str := '^BY2,3.0':CRLF$
|
||
|
||
Str:= '^FO700,70^AC,18^FDQty:^FS':CRLF$ ;* Label
|
||
Str:= '^FO760,70^A045,25^FD':WfrQty:'^FS':CRLF$ ;* Data
|
||
|
||
|
||
****** Third Line
|
||
|
||
Str:= '^FO30,105^AC,18^FDShip Dt:^FS' ;* Label
|
||
Str:= '^FO140,105^A0,,25^FD':ReqShipDate:'^FS':CRLF$ ;* Data
|
||
|
||
Str:= '^FO250,105^AC,18^FDCust:^FS':CRLF$ ;* Label
|
||
Str:= '^FO320,105^A045,25^FD':CustName:'^FS':CRLF$ ;* Data
|
||
|
||
Str:= '^FO560,105^AC,18^FDPO:^FS':CRLF$
|
||
Str:= '^FO600,105^A045,25^FD':PONo:'^FS':CRLF$
|
||
|
||
|
||
****** Separator bar
|
||
|
||
Str:= '^FO15,128^GB795,1^FS'
|
||
|
||
|
||
****** Fourth Line
|
||
|
||
LineY = 135
|
||
|
||
Str := '^FO30,':LineY:'^AC,18^FDLot No:^FS':CRLF$
|
||
Str := '^FO120,':LineY:'^A0,20^FD':LotNo:'^FS':CRLF$
|
||
|
||
****** Fifth Line
|
||
|
||
LineY += 25
|
||
|
||
Str := '^FO30,':LineY:'^AC,18^FDSub PN:^FS':CRLF$
|
||
Str := '^FO120,':LineY:'^A0,20^FD':SubPartNo:'^FS':CRLF$
|
||
|
||
IF SuppCd NE '' THEN
|
||
|
||
Str := '^FO410,':LineY:'^AC,18^FDSupp Cd:^FS':CRLF$ ;* Label ;* Added 8/17/2005 JCH - J.C.Henry & Co.
|
||
Str := '^FO510,':LineY:'^A0,20^FD':SuppCd:'^FS':CRLF$ ;* Data
|
||
|
||
Str := '^BY2,2.0':CRLF$
|
||
Str := '^FO610,':LineY:'^A040,20^B3,,23,N^FD':SuppCd:'^FS':CRLF$
|
||
Str := '^BY2,3.0':CRLF$
|
||
END
|
||
|
||
****** New Part Number line
|
||
|
||
LineY += 25
|
||
|
||
Str := '^FO30,':LineY:'^AC,18^FDCust Part No:^FS':CRLF$
|
||
Str := '^FO200,':LineY:'^A0,20^FD':CustPartNo:' ':CustPartDesc:'^FS':CRLF$
|
||
|
||
|
||
****** Customer Spec Line
|
||
|
||
LineY += 25
|
||
|
||
IF CustSpecNo NE '' THEN
|
||
|
||
Str := '^FO30,':LineY:'^AC,18^FDCust Spec No:^FS':CRLF$
|
||
Str := '^FO200,':LineY:'^A0,20^FD':CustSpecNo:' ':CustSpecDesc:'^FS':CRLF$
|
||
|
||
Str := '^FO475,':LineY:'^AC,18^FDRev:^FS':CRLF$
|
||
Str := '^FO525,':LineY:'^A0,20^FD':CustSpecRevNo:'^FS':CRLF$
|
||
|
||
Str := '^FO615,':LineY:'^AC,18^FDRev Dt:^FS':CRLF$
|
||
Str := '^FO700,':LineY:'^A0,20^FD':CustSpecRevDt:'^FS':CRLF$
|
||
|
||
END
|
||
|
||
|
||
****** Separator bar
|
||
|
||
LineY += 23
|
||
|
||
Str := '^FO15,':LineY:'^GB795,1^FS'
|
||
|
||
|
||
****** Sixth Line
|
||
|
||
LineY += 7
|
||
|
||
|
||
****** Seventh Line
|
||
|
||
LineY += 25
|
||
|
||
Str := '^FO30,':LineY:'^AC,18^FDPre:^FS':CRLF$
|
||
Str := '^FO90,':LineY:'^A0,20^FD':PreCleanTool:'^FS':CRLF$
|
||
|
||
LineY += 25
|
||
|
||
IF PreAkrionRecipe NE '' THEN
|
||
Str := '^FO30,':LineY:'^AC,18^FDAkrion:^FS':CRLF$
|
||
Str := '^FO120,':LineY:'^A0,20^FD':PreAkrionRecipe:'^FS':CRLF$
|
||
|
||
Str := '^BY2,2.0':CRLF$
|
||
Str := '^FO400,':LineY:'^A040,20^B3,,23,N^FD':PreAkrionRecipe:'^FS':CRLF$
|
||
Str := '^BY2,3.0':CRLF$
|
||
END
|
||
|
||
****** Eighth Line
|
||
|
||
LineY += 35
|
||
|
||
Str := '^FO30,':LineY:'^AC,18^FDRecipe:^FS':CRLF$
|
||
Str := '^FO120,':LineY:'^A0,20^FD':RecipeInfo:'^FS':CRLF$
|
||
|
||
Str := '^FO410,':LineY:'^AC,18^FDEpi Dopant:^FS':CRLF$
|
||
Str := '^FO560,':LineY:'^A040,20^FD':Dopant:'^FS':CRLF$
|
||
|
||
|
||
****** Ninth Line
|
||
|
||
LineY += 25
|
||
|
||
****** Tenth, Eleventh and Twelfth Lines
|
||
|
||
LineY += 25
|
||
|
||
Str := '^FO30,':LineY:'^AC,18^FDThk Spec:^FS':CRLF$
|
||
|
||
FOR M = 1 TO COUNT(PrintThickTargets,@VM) + (PrintThickTargets NE '')
|
||
BaseLine = LineY + (M-1)*20
|
||
Str := '^FO140,':BaseLine:'^A040,20^FD':PrintThickTargets<1,M>:'^FS':CRLF$
|
||
NEXT M
|
||
|
||
|
||
Str := '^FO410,':LineY:'^AC,18^FDRes Spec:^FS':CRLF$
|
||
|
||
FOR M = 1 TO COUNT(PrintResTargets,@VM) + (PrintResTargets NE '')
|
||
BaseLine = LineY + (M-1)*20
|
||
Str := '^FO520,':BaseLine:'^A040,20^FD':PrintResTargets<1,M>:'^FS':CRLF$
|
||
NEXT M
|
||
|
||
LineY = 625
|
||
|
||
****** Separator bar
|
||
|
||
Str := '^FO15,738^GB795,1^FS'
|
||
|
||
|
||
****** Lines 15 and 16
|
||
|
||
Str := '^FO30,775^AC,18^FDProd Spec No:^FS':CRLF$ ;* Label
|
||
Str := '^FO190,775^A0,25^FD':PSNo:'^FS':CRLF$ ;* Data
|
||
|
||
IF SpecType = 'Production' THEN SpecType = 'Prod'
|
||
IF SpecType = 'Pre-Production' THEN SpecType = 'Pre'
|
||
|
||
Str := '^FO275,775^AC,18^FDSpec Type:^FS':CRLF$ ;* Label
|
||
Str := '^FO400,775^A0,25^FD':SpecType:'^FS':CRLF$ ;* Data
|
||
|
||
Str:= '^XZ'
|
||
|
||
If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then
|
||
stat = Set_Printer('TEXT',Str)
|
||
end else
|
||
stat = Direct_Print('PRINT', Str)
|
||
end
|
||
|
||
|
||
|
||
|
||
RETURN
|
||
|
||
***************************************************
|
||
|
||
|
||
* * * * * * *
|
||
PrintWOLabels:
|
||
* * * * * * *
|
||
|
||
* * * * * * *
|
||
PrintWO:
|
||
* * * * * * *
|
||
|
||
Str = '^XA^CFD'
|
||
*Str := '^LH20,70'
|
||
Str := '^LH0,0'
|
||
Str := '^PR2' ;* Print speed 2 inches per second
|
||
Str := '^LL325' ;* Label length in dots
|
||
Str := '^MD15' ;* Media darkness
|
||
Str := '^PQ2' ;* Print 2 labels for each pass through here
|
||
STR := '^MMT':CRLF$ ;* Media mode t=tear off mode
|
||
|
||
|
||
IF INDEX(PrintWONo,'.',1) THEN
|
||
Str:= '^FO10,30^A0,220,210^FD':PrintWONo:'^FS':CRLF$
|
||
END ELSE
|
||
Str:= '^FO70,30^A0,220,210^FD':PrintWONo:'^FS':CRLF$
|
||
END
|
||
|
||
CharCnt = LEN(CustName)
|
||
NameLength = CharCnt*72
|
||
WhiteSpace = INT(((2103 - NameLength)/2103) * 806)
|
||
StartingXPos = INT(WhiteSpace/2)
|
||
|
||
Str:= '^FO':StartingXPos:',230^A0,75,72^FD':CustName:'^FS':CRLF$
|
||
|
||
Str:= '^FO160,320^A080,50^FD':'Commit Date: ':OCONV( XLATE( 'WO_LOG', WONo, WO_LOG_COMMIT_DATE$, 'X' ), 'D2/' ):'^FS':CRLF$
|
||
Str:= '^XZ'
|
||
|
||
If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then
|
||
stat = Set_Printer('TEXT',Str)
|
||
end else
|
||
stat = Direct_Print('PRINT', Str)
|
||
end
|
||
|
||
RETURN
|
||
|
||
|
||
|
||
* * * * * * *
|
||
PrintMonitorLabels:
|
||
* * * * * * *
|
||
|
||
FOR I = 1 TO WMIBoxCnt
|
||
|
||
Str = '^XA^CFD'
|
||
Str:= '^LH0,0'
|
||
Str:= '^PR2' ;* Print speed 2 inches per second
|
||
Str:= '^LL325' ;* Label length in dots
|
||
Str:= '^MD15' ;* Media darkness
|
||
Str:= '^MMT':CRLF$ ;* Media mode t=tear off mode
|
||
Str:= '^FO30,30^A060,40^FDMonitor Wafer^FS':CRLF$
|
||
Str:= '^FO550,30^A060,40^FDReactor#_____^FS':CRLF$
|
||
Str:= '^FO30,70^A060,40^FDDate_____________^FS':CRLF$
|
||
Str:= '^FO30,130^A060,40^FDCustomer Name: ':CustName<I>:'^FS':CRLF$
|
||
Str:= '^FO30,190^A060,40^FDRDS#: ':RDSIds<I>:'^FS':CRLF$
|
||
Str:= '^FO400,190^A060,40^FDLot#: ':LotNo<I>:'^FS':CRLF$
|
||
Str:= '^FO30,250^A060,40^FDThick Avg__________^FS':CRLF$
|
||
Str:= '^FO400,250^A060,40^FDWafer Type__________^FS':CRLF$
|
||
Str:= '^FO30,280^A060,40^FDRes Avg____________^FS':CRLF$
|
||
Str:= '^FO400,280^A060,40^FDWafer Type__________^FS':CRLF$
|
||
Str:= '^XZ'
|
||
|
||
If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then
|
||
stat = Set_Printer('TEXT',Str)
|
||
end else
|
||
stat = Direct_Print('PRINT', Str)
|
||
end
|
||
|
||
NEXT I
|
||
|
||
RETURN
|
||
|
||
|
||
* * * * * * *
|
||
PrintSurfscanLabels:
|
||
* * * * * * *
|
||
|
||
FOR I = 1 TO WMIBoxCnt
|
||
Str = '^XA^CFD'
|
||
Str:= '^LH0,0'
|
||
Str:= '^PR2' ;* Print speed 2 inches per second
|
||
Str:= '^LL325' ;* Label length in dots
|
||
Str:= '^MD15' ;* Media darkness
|
||
Str:= '^MMT' ;* Media mode t=tear off mode
|
||
Str:= '^FO30,30^A060,40^FDSurfscan Required^FS'
|
||
*Str:= '^FO550,30^A060,40^FDRDS#':RDSIds<I>:'^FS'
|
||
IF PreSurfscan THEN
|
||
Str:= '^FO30,130^A060,40^FDPre Epi:^FS'
|
||
Str:= '^FO250,130^A060,40^FDDefects________^FS'
|
||
Str:= '^FO500,130^A060,40^FDHaze________^FS'
|
||
END
|
||
IF FirstSurfscan THEN
|
||
Str:= '^FO30,190^A060,40^FDFirst Wafer^FS'
|
||
Str:= '^FO250,190^A060,40^FDDefects________^FS'
|
||
Str:= '^FO500,190^A060,40^FDHaze________^FS'
|
||
END
|
||
IF PostCleanSurfscan THEN
|
||
Str:= '^FO30,250^A060,40^FDPost Epi:^FS'
|
||
Str:= '^FO250,250^A060,40^FDDefects________^FS'
|
||
Str:= '^FO500,250^A060,40^FDHaze________^FS'
|
||
END
|
||
Str:= '^XZ'
|
||
|
||
If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then
|
||
stat = Set_Printer('TEXT',Str)
|
||
end else
|
||
stat = Direct_Print('PRINT', Str)
|
||
end
|
||
|
||
|
||
NEXT I
|
||
|
||
|
||
RETURN
|