added LSL2 stored procedures
This commit is contained in:
		
							
								
								
									
										668
									
								
								LSL2/STPROC/PRINT_PALLET_LABELS.txt
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										668
									
								
								LSL2/STPROC/PRINT_PALLET_LABELS.txt
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,668 @@ | ||||
| COMPILE SUBROUTINE Print_Pallet_Labels( Dummy ) | ||||
|  | ||||
| /* | ||||
| 	Prints pallet labels from CoC screen | ||||
| 	09/16/2003 John C. Henry - J.C. Henry & Co., Inc. | ||||
| */ | ||||
|  | ||||
| DECLARE FUNCTION FieldCount, Msg, Key_Sort, entid | ||||
| DECLARE FUNCTION Repository, Utility, Dialog_Box, obj_Install | ||||
| DECLARE FUNCTION Get_Status, Printer_Select, Msg, Set_Printer, Direct_Print, Environment_Services | ||||
|  | ||||
| DECLARE SUBROUTINE Set_Status,  ErrMsg, Make.List, Msg | ||||
|  | ||||
|  | ||||
| $INSERT WO_LOG_EQU | ||||
| $INSERT COC_EQU | ||||
| $INSERT RDS_EQU | ||||
| $INSERT PROD_SPEC_EQU | ||||
| $INSERT ORDER_EQU | ||||
| $INSERT OIPRINT_EQUATES | ||||
|  | ||||
|  | ||||
| EQU COL$ORDER_NO	TO 1		;* Structure of cassette data in dialog box return | ||||
| EQU COL$LINE_NO		TO 2 | ||||
| EQU COL$RDS_NO		TO 3 | ||||
| EQU COL$PART_NO		TO 4 | ||||
| EQU COL$LOT_NO		TO 5 | ||||
| EQU COL$REACTOR		TO 6 | ||||
| EQU COL$REJECT		TO 7 | ||||
| EQU COL$WAFER_QTY	TO 8 | ||||
|  | ||||
| EQU PI$LEFT		TO 1			;* Printer page setup equates | ||||
| 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 | ||||
|  | ||||
| ErrorMsg = '' | ||||
|  | ||||
| COCKeys = dialog_box( 'COC_QUERY', @window, '' )			;* Select COC's for day/customer | ||||
| IF COCKeys NE '' THEN | ||||
| 	PopId = entid( @appid<1>, 'POPUP', '', 'COC_QUERY' ) | ||||
| 	OverRide = '' | ||||
| 	Make.List( 0, COCKeys, '', '' ) | ||||
| 	COCIds = repository( "EXECUTE", PopId, @window, OverRide )  | ||||
| 	IF COCIds = '' THEN RETURN | ||||
| END ELSE | ||||
| 	RETURN | ||||
| END | ||||
|  | ||||
| COCCnt = COUNT(COCIds,@VM) + (COCIds NE '') | ||||
|  | ||||
| IF COCCnt < 1 THEN RETURN | ||||
|  | ||||
| PartNos = '' | ||||
| PartQtys = '' | ||||
|  | ||||
| FOR I = 1 TO COCCnt | ||||
| 	COCId = COCIds<1,I> | ||||
| 	COCRec = XLATE('COC',COCId,'','X') | ||||
| 	IF I = 1 THEN | ||||
| 	 | ||||
| 		* Extract constants | ||||
| 		 | ||||
| 		CustNo		= COCRec<COC_CUST_NO$> | ||||
| 		 | ||||
| 		OrderNo	 	= COCRec<COC_ORDER_NO$,1>	;* This is multivalued | ||||
| 		OrderRec	= XLATE('ORDER',OrderNo,'','X') | ||||
| 		ShipToName	= OrderRec<ORDER_SHIP_TO_ATTN$> | ||||
| 		ShipToAddr	= OrderRec<ORDER_SHIP_TO_ADDRESS$>		; * This is MV's needs work | ||||
| 		ShipToAddr	= ShipToAddr[-1,'B':@VM]				; * Try extracting the LAST line | ||||
| 		ShipToCity	= OrderRec<ORDER_SHIP_TO_CITY$> | ||||
| 		ShipToST	= OrderRec<ORDER_SHIP_TO_STATE$> | ||||
| 		ShipToZIP	= OrderRec<ORDER_SHIP_TO_ZIP$> | ||||
|  | ||||
| 		WorkOrderNo	= COCRec<COC_WO$,1>						;* This is multivalued | ||||
| 		PSNId		= XLATE('WO_LOG',WorkOrderNo,WO_LOG_PROD_SPEC_ID$,'X')<1,1> | ||||
| 		SupplierCd	= XLATE('PROD_SPEC',PSNId, PROD_SPEC_SUPPLIER_CODE$, 'X' ) | ||||
| 		IF SupplierCd = '' THEN | ||||
| 			SupplierCd = obj_Install('Get_Prop','Duns')	;* DUNS number | ||||
| 		END | ||||
| 		 | ||||
| 		ShipDt		= OCONV(COCRec<COC_ENTRY_DATE$>, 'D4/' ) | ||||
| 	 | ||||
| 	END	;* End of check for 1st item | ||||
|  | ||||
| 	LineCnt = COUNT(COCRec<COC_PART_NUM$>,@VM) + (COCRec<COC_PART_NUM$> NE '')  | ||||
| 	FOR LineNo = 1 TO LineCnt | ||||
| 		PartNo	= COCRec<COC_PART_NUM$,LineNo> | ||||
| 		PartQty	= COCRec<COC_WAFER_QTY$,LineNo> | ||||
| 		LOCATE PartNo IN PartNos SETTING Pos THEN | ||||
| 			PartQtys<1,Pos> = PartQtys<1,Pos> + PartQty | ||||
| 		END ELSE | ||||
| 			PartNos = INSERT(PartNos,1,Pos,0,PartNo) | ||||
| 			PartQtys = INSERT(PartQtys,1,Pos,0,PartQty) | ||||
| 		END | ||||
| 	NEXT LineNo | ||||
| 		 | ||||
| NEXT I | ||||
|  | ||||
| PartNoCnt = COUNT(PartNos,@VM) + (PartNos NE '') | ||||
|  | ||||
|  | ||||
| * Initializes OIPI and then prints block grid | ||||
|  | ||||
| FileName 	= "Printing Label" | ||||
| Title       = "Printing Label"	;* Initialize Printing | ||||
|  | ||||
| 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 = '\\FMSA001\PMSAZ_BR2'			;* Print Server Change	 | ||||
| PrinterID = '\\mesirwfp001\MESZBRPRT001'	;* Site specific label printer ID - Skips popup	 | ||||
|  | ||||
| PrintPath	= Printer_Select(PrinterID)		;* Select printer - Displays popup if PrinterPort not found  | ||||
|  | ||||
| IF PrintPath = '' THEN | ||||
| 	Def = "" | ||||
| 	Def<MTYPE$> = "TA3" | ||||
| 	Def<MTEXT$> = 'Destination Printer not Selected..' | ||||
| 	Def<MCAPTION$> = '' | ||||
| 	Def<MICON$> = '*' | ||||
| 	Msg(@WINDOW, Def, '') | ||||
| 	RETURN | ||||
| END | ||||
|  | ||||
| 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 GOSUB OIPrint_Err | ||||
|  | ||||
| BitMap = obj_Install('Get_Prop','ZebraGRF')			;* Substitute company logo converted to .GRF (Zebra graphics format) | ||||
| OSREAD ImageData FROM BitMap ELSE | ||||
| 	ErrMsg('Unable to Read ':BitMap:' graphic for use on Carton Labels.') | ||||
| END | ||||
| GRFName = FIELD(BitMap,'.',1) | ||||
|  | ||||
|  | ||||
| IF PartNoCnt > 1 THEN | ||||
|  | ||||
| 	* Mixed Load Label | ||||
| 	 | ||||
| 	Parms		= SupplierCd		;* Customer supplied Vend ID	- 12 alphanumeric | ||||
| 	Parms<2>	= ShipToName		;* Customer ship to Name		- 25 alphanumeric | ||||
| 	Parms<3>	= ShipToAddr		;* Customer ship to Address		- 25 alphanumeric | ||||
| 	Parms<4>	= ShipToCity		;* Customer ship to City		- 20 alphanumeric | ||||
| 	Parms<5>	= ShipToST			;* Customer ship to State		- 2  alpha | ||||
| 	Parms<6>	= ShipToZIP			;* Customer ship to ZIP			- 7  alphanumeric | ||||
| 	Parms<7>	= ''				;* EDI transaction serial no	- 9  alpha  | ||||
| 	Parms<8>	= ''				;* Plant & Dock designator		- 7  character | ||||
| 	Parms<9>	= ''				;* Storage Bin at Customer		- 30 character | ||||
| 	Parms<10>	= ''				;* Ship to Plant Name			- 30 character | ||||
| 	Parms<11>	= ''				;* Ship to Plant City			- 30 character | ||||
| 	Parms<12>	= ShipDt								;* Ship Date			- MM/DD/YYYY | ||||
| 	Parms<13>	= obj_Install('Get_Prop','CompAddr')	;* Manufacturer			- 30 character | ||||
| 	Parms<14>	= obj_Install('Get_Prop','City')		;* Mfr City				- 20 character | ||||
| 	Parms<15>	= obj_Install('Get_Prop','State')		;* Mfr State code		- 2  character) | ||||
| 	Parms<16>	= obj_Install('Get_Prop','ZIPShort')	;* ZIP code				- 7  character | ||||
| 	Parms<17>	= PartNos								;* Customer Part No(s)	- 18 alphanumeric | ||||
| 	Parms<18>	= PartQtys								;* Part Qty(s) 			- 6  numeric | ||||
|  | ||||
| 	IF CustNo = '6622' OR CustNo = '562' THEN | ||||
| 		* This is Delphi | ||||
| 		Parms<9> = ' '								;* Storage Bin - try with a space for now. | ||||
| 		Parms<10> = 'Delphi Delco Electronics'		;* Ship to Plant Name | ||||
| 		Parms<11> = 'Kokomo'						;* Ship to Plant City | ||||
| 	 | ||||
| 	END | ||||
|  | ||||
| 	CONVERT @FM TO @RM IN Parms | ||||
| 	 | ||||
| 	GOSUB MixedLoadLabel	;* Print two labels | ||||
| 	GOSUB MixedLoadLabel | ||||
| 	 | ||||
| END ELSE | ||||
|  | ||||
| 	Parms		= PartNos					;* Customer Part No				- 18 alphanumeric | ||||
| 	Parms<2>	= PartQtys					;* Part Qty 					- 6  numeric | ||||
| 	Parms<3>	= SupplierCd				;* Delivery Location			- 8  char (VARIOUS is OK) | ||||
| 	Parms<5>	= ''						;* EDI transaction serial no	- 9  alpha  | ||||
|  | ||||
| 	Parms<6>	= ''						;* Plant & Dock designator		- 7  character | ||||
| 	Parms<7>	= ''						;* Storage Bin at Customer		- 30 character | ||||
| 	Parms<8>	= ''						;* Ship to Plant Name			- 30 character | ||||
| 	Parms<9>	= ''						;* Ship to Plant City			- 30 character | ||||
| 	Parms<10>	= ShipDt					;* Ship Date					- MM/DD/YYYY | ||||
| 	Parms<11>	= 'Epitaxial Layer(s)'		;* Part Description				- 25 character | ||||
| 	 | ||||
| 	Parms<12>	= obj_Install('Get_Prop','CompAddr')	;* Manufacturer			- 30 character | ||||
| 	Parms<13>	= obj_Install('Get_Prop','City')		;* Mfr City				- 20 character | ||||
| 	Parms<14>	= obj_Install('Get_Prop','State')		;* Mfr State code		- 2  character | ||||
| 	Parms<15>	= obj_Install('Get_Prop','ZIPShort')	;* ZIP code				- 7  character | ||||
| 	Parms<16>	= obj_Install('Get_Prop','Country')		;* Country of origin	- 10 character | ||||
| 	 | ||||
| 	IF CustNo = '6622' OR CustNo = '562' THEN | ||||
| 		* This is Delphi | ||||
| 		Parms<7> = ' '								;* Storage Bin - try with a space for now. | ||||
| 		Parms<8> = 'Delphi Delco Electronics'		;* Ship to Plant Name | ||||
| 		Parms<9> = 'Kokomo'							;* Ship to Plant City | ||||
| 	 | ||||
| 	END | ||||
| 	 | ||||
| 	CONVERT @FM TO @RM IN Parms | ||||
| 	 | ||||
| 	GOSUB MasterLabel	;* Print two labels | ||||
| 	GOSUB MasterLabel | ||||
| 	 | ||||
| END | ||||
|  | ||||
| * * * * * * * | ||||
| OIPrint_Err: | ||||
| * * * * * * * | ||||
|  | ||||
| * Local method to terminate print job | ||||
|  | ||||
| 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  | ||||
| * * * * * * * * * * * * * * * * * * * * * * * * * * * * * | ||||
|  | ||||
| * * * * * * * | ||||
| MasterLabel: | ||||
| * * * * * * * | ||||
|  | ||||
| CustPartNo		= Parms[1,@RM]			;* Customer Part No				- 18 alphanumeric | ||||
| PartQty			= Parms[COL2()+1,@RM]	;* Part Qty 					- 6  numeric | ||||
| SupplierCd		= Parms[COL2()+1,@RM]	;* Customer supplied Vend ID	- 12 alphanumeric | ||||
| DeliveryLoc		= Parms[COL2()+1,@RM]	;* Delivery Location			- 8  char (VARIOUS is OK) | ||||
| SerialNo		= Parms[COL2()+1,@RM]	;* EDI transaction serial no	- 9  alpha  | ||||
|  | ||||
| PlantDock		= Parms[COL2()+1,@RM]	;* Plant & Dock designator		- 7  character | ||||
| StorageBin		= Parms[COL2()+1,@RM]	;* Storage Bin at Customer		- 30 character | ||||
| PlantName		= Parms[COL2()+1,@RM]	;* Ship to Plant Name			- 30 character | ||||
| PlantCity		= Parms[COL2()+1,@RM]	;* Ship to Plant City			- 30 character | ||||
| ShipDt			= Parms[COL2()+1,@RM]	;* Ship Date					- MM/DD/YYYY | ||||
| PartDesc		= Parms[COL2()+1,@RM]	;* Part Description				- 25 character | ||||
|  | ||||
| * optional parms | ||||
|  | ||||
| Manufacturer	= Parms[COL2()+1,@RM]	;* Manufacturer					- 30 character | ||||
| City			= Parms[COL2()+1,@RM]	;* Mfr City						- 20 character | ||||
| ST				= Parms[COL2()+1,@RM]	;* Mfr State code				- 2  character | ||||
| ZIP				= Parms[COL2()+1,@RM]	;* ZIP code						- 7  character | ||||
| Country			= Parms[COL2()+1,@RM]	;* Country of origin			- 10 character | ||||
|  | ||||
| IF CustPartNo	= '' THEN ErrorMsg = ErrTitle:@SVM:'Null parm CustPartNo passed to routine.' | ||||
| IF PartQty		= '' THEN ErrorMsg = ErrTitle:@SVM:'Null parm PartQty passed to routine.' | ||||
| IF SupplierCd	= '' THEN ErrorMsg = ErrTitle:@SVM:'Null parm SupplierCd passed to routine.' | ||||
| IF ShipDt		= '' THEN ErrorMsg = ErrTitle:@SVM:'Null parm ShipDate passed to routine.' | ||||
| IF PartDesc		= '' THEN ErrorMsg = ErrTitle:@SVM:'Null parm PartDesc passed to routine.' | ||||
|  | ||||
| * Null defaults for shipper info | ||||
|  | ||||
| IF Manufacturer	= '' THEN Manufacturer = obj_Install('Get_Prop','CompAddr') | ||||
| IF City			= '' THEN City = obj_Install('Get_Prop','City') | ||||
| IF ST			= '' THEN ST = obj_Install('Get_Prop','State') | ||||
| IF ZIP			= '' THEN ZIP = obj_Install('Get_Prop','ZIPShort') | ||||
| IF Country		= '' THEN Country = obj_Install('Get_Prop','Country') | ||||
|  | ||||
| IF ErrorMsg NE '' THEN | ||||
| 	ErrMsg(ErrorMsg) | ||||
| 	RETURN | ||||
| END | ||||
|  | ||||
| *Start Printing Process | ||||
|  | ||||
| GOSUB Label6x4	;* Zebra printer setup and background lines for labels  | ||||
|  | ||||
| * * * * * * * | ||||
| * Top Block Left - Customer Part Number | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO230,0^FR^GB800,0,50,B^FS':CRLF$				;* Black background for title  | ||||
| LabelString := '^FO270,5,^A0,45,120^FR^FDMASTER LOAD ^FS':CRLF$ | ||||
|  | ||||
| LabelString := '^BY2':CRLF$						;* This is Code 128 Barcode - change ratio | ||||
|  | ||||
| LabelString := '^FO0,0^A0,25^FDPart #:^FS':CRLF$					;* Label Line 1 | ||||
| LabelString := '^FO0,30^A0,25^FDCust(P)^FS':CRLF$					;* Label Line 2 | ||||
| LabelString := '^FO100,55^A0,60^FD':CustPartNo:'^FS':CRLF$			;* Readable | ||||
| LabelString := '^FO100,100^BC,100,N^FDP':CustPartNo:'^FS':CRLF$		;* Code 128 | ||||
|  | ||||
| LabelString := '^BY3,3.0':CRLF$					;* Reset narrow bar width and Ratio | ||||
|  | ||||
| * * * * * * * | ||||
| * Top Block Right - Quantity | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO700,155^A0,25^FDQuantity:^FS':CRLF$			;* Label Line 1 | ||||
| LabelString := '^FO700,180^A0,25^FD(Q)^FS':CRLF$				;* Label Line 2 | ||||
| LabelString := '^FO810,150^A0,60,70^FD':PartQty:'^FS':CRLF$		;* Readable | ||||
| LabelString := '^FO700,50^B3,,100,N^FDQ':PartQty:'^FS':CRLF$	;* Code 39 | ||||
|  | ||||
| * * * * * * * | ||||
| * 2nd Block Left - Supplier Code | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO0,208^A0,25^FDSupplier:^FS':CRLF$				;* Label Line 1 | ||||
| LabelString := '^FO0,238^A0,25^FD(V)^FS':CRLF$						;* Label Line 2 | ||||
| LabelString := '^FO100,208^A0,120,80^FD':SupplierCd:'^FS':CRLF$		;* Readable | ||||
|  | ||||
| LabelString := '^FO100,303^BY2^B3,,90,N^FDV':SupplierCd:'^FS':CRLF$	;* Code 39 - 2 dot bar | ||||
| LabelString := '^BY3':CRLF$											;* Reset to 3 dot bar | ||||
|  | ||||
|  | ||||
| * * * * * * * | ||||
| * 2nd Block Right - Delivery Location | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO615,208^A0,25^FDDLOC^FS':CRLF$					;* Label Line 1 | ||||
| LabelString := '^FO665,258^A0,120,80^FD':DeliveryLoc:'^FS':CRLF$	;* Readable | ||||
|  | ||||
|  | ||||
|  | ||||
| * * * * * * * | ||||
| * 3rd Block Left - Serial Number | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO0,408^A0,25^FDSerial #:^FS':CRLF$				;* Label Line 1 | ||||
| LabelString := '^FO0,438^A0,25^FD(4S)^FS':CRLF$						;* Label Line 2 | ||||
| LabelString := '^FO100,408^A0,120,80^FD':SerialNo:'^FS':CRLF$		;* Readable | ||||
| LabelString := '^FO50,503^BY2^B3,,90,N^FD4S':SerialNo:'^FS':CRLF$	;* Code 39 2 dot bar | ||||
| LabelString := '^BY3':CRLF$											;* Reset to 3 dot bar | ||||
|  | ||||
|  | ||||
| * * * * * * * | ||||
| * 3rd Block Right - Plant & Dock, Bin, Plant Name and Plant City | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO615,408^A0,25^FDPLT.DOC^FS':CRLF$			;* Label Line 1 | ||||
| LabelString := '^FO775,408^A0,120,80^FD':PlantDock:'^FS':CRLF$	;* Readable | ||||
|  | ||||
| IF StorageBin NE '' THEN | ||||
| 	LabelString := '^FO615,508^A0,25^FDStorage Bin:^FS':CRLF$		;* Storage Bin Label | ||||
| 	LabelString := '^FO775,508^A0,25^FD':StorageBin:'^FS':CRLF$		;* Storage Bin Readable | ||||
| END | ||||
|  | ||||
| IF PlantName NE '' THEN | ||||
| 	LabelString := '^FO615,542^A0,25^FDPlant Name:^FS':CRLF$		;* Plant Name Label | ||||
| 	LabelString := '^FO775,542^A0,25^FD':PlantName:'^FS':CRLF$		;* Plant Name Readable | ||||
| END | ||||
|  | ||||
| IF PlantCity NE '' THEN | ||||
| 	LabelString := '^FO615,576^A0,25^FDPlant City:^FS':CRLF$		;* Plant City Label | ||||
| 	LabelString := '^FO775,576^A0,25^FD':PlantCity:'^FS':CRLF$		;* Plant City Readable | ||||
| END | ||||
|  | ||||
| * * * * * * * | ||||
| * 4th Block Left -  | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO20,612^XGR:':GRFName:',1,1^FS'			;* Company Logo | ||||
|  | ||||
|  | ||||
| * * * * * * * | ||||
| * 4th Block Right - Supplier and Description info | ||||
| * * * * * * * | ||||
|  | ||||
| * Ship Date | ||||
|  | ||||
| LabelString := '^FO615,612^A0,25,28^FDShip Date:^FS' | ||||
| LabelString := '^FO815,612^A0,65^FD':ShipDt:'^FS' | ||||
|  | ||||
| * Part Description | ||||
|  | ||||
| LabelString := '^FO620,670^A0,40,30^FDDesc: ':PartDesc:'^FS':CRLF$ | ||||
|  | ||||
| * Manufacturer Name, City, ST, ZIP | ||||
|  | ||||
| LabelString := '^FO620,720^A0,50,28^FD':Manufacturer:'^FS' | ||||
| LabelString := '^FO620,768^A0,25,28^FD':City:' ':ST:' ':ZIP:'^FS' | ||||
|  | ||||
| * Country (Made In) | ||||
|  | ||||
| LabelString := '^FO1060,743^A0,25,28^FDMade In:^FS' | ||||
| LabelString := '^FO1060,768^A0,25,28^FD':Country:'^FS' | ||||
|  | ||||
| LabelString := '^XZ' | ||||
|  | ||||
| If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then | ||||
|     stat = Set_Printer('TEXT',LabelString) | ||||
| end else | ||||
|     stat = Direct_Print('PRINT', LabelString) | ||||
| end | ||||
|  | ||||
| RETURN | ||||
|  | ||||
|  | ||||
|  | ||||
| * * * * * * * | ||||
| MixedLoadLabel: | ||||
| * * * * * * * | ||||
|  | ||||
| SupplierCd		= Parms[1,@RM]			;* Customer supplied Vend ID	- 12 alphanumeric | ||||
| ShipToName		= Parms[COL2()+1,@RM]	;* Customer ship to Name		- 25 alphanumeric | ||||
| ShipToAddr		= Parms[COL2()+1,@RM]	;* Customer ship to Address		- 25 alphanumeric | ||||
| ShipToCity		= Parms[COL2()+1,@RM]	;* Customer ship to City		- 20 alphanumeric | ||||
| ShipToST		= Parms[COL2()+1,@RM]	;* Customer ship to State		- 2  alpha | ||||
| ShipToZIP		= Parms[COL2()+1,@RM]	;* Customer ship to ZIP			- 7  alphanumeric | ||||
| SerialNo		= Parms[COL2()+1,@RM]	;* EDI transaction serial no	- 9  alpha  | ||||
| PlantDock		= Parms[COL2()+1,@RM]	;* Plant & Dock designator		- 7  character | ||||
| StorageBin		= Parms[COL2()+1,@RM]	;* Storage Bin at Customer		- 30 character | ||||
| PlantName		= Parms[COL2()+1,@RM]	;* Ship to Plant Name			- 30 character | ||||
| PlantCity		= Parms[COL2()+1,@RM]	;* Ship to Plant City			- 30 character | ||||
| ShipDt			= Parms[COL2()+1,@RM]	;* Ship Date					- MM/DD/YYYY | ||||
| Manufacturer	= Parms[COL2()+1,@RM]	;* Manufacturer					- 30 character | ||||
| City			= Parms[COL2()+1,@RM]	;* Mfr City						- 20 character | ||||
| ST				= Parms[COL2()+1,@RM]	;* Mfr State code				- 2  character | ||||
| ZIP				= Parms[COL2()+1,@RM]	;* ZIP code						- 7  character | ||||
| PartNos			= Parms[COL2()+1,@RM]	;* Customer Part No(s)			- 18 alphanumeric | ||||
| PartQtys		= Parms[COL2()+1,@RM]	;* Part Qty(s) 					- 6  numeric | ||||
|  | ||||
| IF SupplierCd	= ''	THEN ErrorMsg = 'Null parm SupplierCd passed to routine (':Method:').' | ||||
| IF LEN(SupplierCd) > 12	THEN ErrorMsg = 'Supplier Code exceeds 12 characters (':Method:').' | ||||
| IF LEN(SerialNo) > 9 	THEN ErrorMsg = 'Supplier Code exceeds 9 characters (':Method:').' | ||||
|  | ||||
| * Null defaults for shipper info | ||||
|  | ||||
| IF Manufacturer	= '' THEN Manufacturer = obj_Install('Get_Prop','CompAddr') | ||||
| IF City			= '' THEN City = obj_Install('Get_Prop','City') | ||||
| IF ST			= '' THEN ST = obj_Install('Get_Prop','State') | ||||
| IF ZIP			= '' THEN ZIP = obj_Install('Get_Prop','ZIPShort') | ||||
|  | ||||
|  | ||||
| *Start Printing Process | ||||
|  | ||||
| GOSUB Label6x4	;* Zebra printer setup and background lines for labels  | ||||
|  | ||||
| * * * * * * * | ||||
| * Top Block  | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO10,0^FR^GB1180,0,190,B^FS':CRLF$				;* Black background for title  | ||||
| LabelString := '^FO20,5,^A0,220,220^FR^FDMIXED LOAD^FS':CRLF$ | ||||
|  | ||||
| * * * * * * * | ||||
| * 2nd Block Left - Supplier Code | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO0,208^A0,25^FDSupplier:^FS':CRLF$				;* Label Line 1 | ||||
| LabelString := '^FO0,238^A0,25^FD(V)^FS':CRLF$						;* Label Line 2 | ||||
| LabelString := '^FO100,208^A0,120,80^FD':SupplierCd:'^FS':CRLF$		;* Readable | ||||
|  | ||||
| LabelString := '^FO100,303^BY2^B3,,90,N^FDV':SupplierCd:'^FS':CRLF$	;* Code 39 - 2 dot bar | ||||
| LabelString := '^BY3':CRLF$											;* Reset to 3 dot bar | ||||
|  | ||||
| * * * * * * * | ||||
| * 2nd Block Right - Ship to Address | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO615,208^A0,25^FDShip To:^FS':CRLF$				;* Label Line 1 | ||||
| LabelString := '^FO630,240^A0,45,30^FD':ShipToName:'^FS':CRLF$ | ||||
| LabelString := '^FO630,290^A0,45,30^FD':ShipToAddr:'^FS':CRLF$ | ||||
| LabelString := '^FO630,340^A0,45,30^FD':ShipToCity:' ':ShipToST:' ':ShipToZIP:'^FS':CRLF$ | ||||
|  | ||||
| * * * * * * * | ||||
| * 3rd Block Left - Serial Number | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO0,408^A0,25^FDSerial #:^FS':CRLF$				;* Label Line 1 | ||||
| LabelString := '^FO0,438^A0,25^FD(5S)^FS':CRLF$						;* Label Line 2 | ||||
| LabelString := '^FO100,408^A0,120,80^FD':SerialNo:'^FS':CRLF$		;* Readable | ||||
| LabelString := '^FO50,503^BY2^B3,,90,N^FD5S':SerialNo:'^FS':CRLF$	;* Code 39 2 dot bar | ||||
| LabelString := '^BY3':CRLF$											;* Reset to 3 dot bar | ||||
|  | ||||
| * * * * * * * | ||||
| * 3rd Block Right - Plant & Dock, Bin, Plant Name and Plant City | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO615,408^A0,25^FDPLT.DOC^FS':CRLF$			;* Label Line 1 | ||||
| LabelString := '^FO775,408^A0,120,80^FD':PlantDock:'^FS':CRLF$	;* Readable | ||||
|  | ||||
| IF StorageBin NE '' THEN | ||||
| 	LabelString := '^FO615,508^A0,25^FDStorage Bin:^FS':CRLF$		;* Storage Bin Label | ||||
| 	LabelString := '^FO775,508^A0,25^FD':StorageBin:'^FS':CRLF$		;* Storage Bin Readable | ||||
| END | ||||
|  | ||||
| IF PlantName NE '' THEN | ||||
| 	LabelString := '^FO615,542^A0,25^FDPlant Name:^FS':CRLF$		;* Plant Name Label | ||||
| 	LabelString := '^FO775,542^A0,25^FD':PlantName:'^FS':CRLF$		;* Plant Name Readable | ||||
| END | ||||
|  | ||||
| IF PlantCity NE '' THEN | ||||
| 	LabelString := '^FO615,576^A0,25^FDPlant City:^FS':CRLF$		;* Plant City Label | ||||
| 	LabelString := '^FO775,576^A0,25^FD':PlantCity:'^FS':CRLF$		;* Plant City Readable | ||||
| END | ||||
|  | ||||
| * * * * * * * | ||||
| * 4th Block Left -  | ||||
| * * * * * * * | ||||
|  | ||||
| LabelString := '^FO20,612^XGR:':GRFName:',1,1^FS':CRLF$			;* Company Logo | ||||
|  | ||||
| * * * * * * * | ||||
| * 4th Block Right - Supplier and Description info | ||||
| * * * * * * * | ||||
|  | ||||
| * Ship Date | ||||
|  | ||||
| LabelString := '^FO615,612^A0,27,20^FDShip Date:^FS':CRLF$ | ||||
| LabelString := '^FO815,612^A0,65^FD':ShipDt:'^FS':CRLF$ | ||||
|  | ||||
| * Manufacturer Name, City, ST, ZIP | ||||
|  | ||||
| LabelString := '^FO620,680^A0,45,30^FD':Manufacturer:'^FS':CRLF$ | ||||
| LabelString := '^FO620,730^A0,45,30^FD':City:' ':ST:' ':ZIP:'^FS':CRLF$ | ||||
|  | ||||
| LabelString := '^XZ':CRLF$ | ||||
|  | ||||
| TopLabel = LabelString	;* End of top label | ||||
|  | ||||
| PartCnt = COUNT(PartNos,@VM) + (PartNos NE '') | ||||
|  | ||||
| * Put 6 part number / qty pairs on the second label | ||||
|  | ||||
| LabelString  = '^XA'				;* Start of label format | ||||
| LabelString := '^LH10,30'			;* Label home offset (needed to get onto the label medium) | ||||
| LabelString := '^BY3'				;* Set narrow Bar Code line width to 3 dots | ||||
| LabelString := '^PR2'				;* Print speed = 2 IPS | ||||
| LabelString := '^LL812.8':CRLF$		;* Label Length in Dots @ 8 Dots per Inch | ||||
|  | ||||
| FOR I = 1 TO 6 | ||||
| 	IF PartNos<1,I> NE '' THEN | ||||
| 		YSpacer = (I - 1) * 135 | ||||
| 		Y1 = 0 + YSpacer | ||||
| 		Y2 = 30 + YSpacer | ||||
| 		Y3 = 60 + YSpacer | ||||
| 		Y4 = 75 + YSpacer | ||||
| 		Y5 = 105 + YSpacer | ||||
| 		Y6 = 0 + YSpacer | ||||
| 		S1 = 130 + YSpacer | ||||
| 		 | ||||
| 		IF I < 6 THEN | ||||
| 			LabelString := '^FO0,':S1:'^GB1200,0,3,B^FS':CRLF$	;* horizontal line under fields | ||||
| 		END | ||||
| 		 | ||||
| 		LabelString := '^BY2':CRLF$						;* This is Code 128 Barcode - change ratio | ||||
|  | ||||
| 		LabelString := '^FO0,':Y1:'^A0,25^FDPart #:^FS':CRLF$					;* Label Line 1 | ||||
| 		LabelString := '^FO0,':Y2:'^A0,25^FDCust(P)^FS':CRLF$					;* Label Line 2 | ||||
| 		LabelString := '^FO100,':Y1:'^A0,63,45^FD':PartNos<1,I>:'^FS':CRLF$		;* Readable | ||||
| 		LabelString := '^FO100,':Y3:'^BC,65,N^FDP':PartNos<1,I>:'^FS':CRLF$		;* Code 128 | ||||
|  | ||||
| 		LabelString := '^BY3,3.0':CRLF$					;* Reset narrow bar width and Ratio | ||||
|  | ||||
| 		LabelString := '^FO700,':Y4:'^A0,25^FDQuantity:^FS':CRLF$				;* Label Line 1 | ||||
| 		LabelString := '^FO700,':Y5:'^A0,25^FD(Q)^FS':CRLF$						;* Label Line 2 | ||||
| 		LabelString := '^FO810,':Y4:'^A0,63,45^FD':PartQtys<1,I>:'^FS':CRLF$	;* Readable | ||||
| 		LabelString := '^FO700,':Y6:'^B3,,65,N^FDQ':PartQtys<1,I>:'^FS':CRLF$	;* Code 39 | ||||
| 	END | ||||
| NEXT I | ||||
|  | ||||
| LabelString := '^XZ':CRLF$ | ||||
| SecondLabel = LabelString | ||||
| ThirdLabel = '' | ||||
|  | ||||
| IF PartCnt > 6 THEN | ||||
|  | ||||
| 	* Put 6 more part number / qty pairs on the third | ||||
|  | ||||
| 	LabelString  = '^XA'				;* Start of label format | ||||
| 	LabelString := '^LH10,30'			;* Label home offset (needed to get onto the label medium) | ||||
| 	LabelString := '^BY3'				;* Set narrow Bar Code line width to 3 dots | ||||
| 	LabelString := '^PR2'				;* Print speed = 2 IPS | ||||
| 	LabelString := '^LL812.8':CRLF$		;* Label Length in Dots @ 8 Dots per Inch | ||||
|  | ||||
| 	FOR I = 7 TO 12 | ||||
| 		IF PartNos<1,I> NE '' THEN | ||||
| 			YSpacer = ((I-6) - 1) * 135 | ||||
| 			Y1 = 0 + YSpacer | ||||
| 			Y2 = 30 + YSpacer | ||||
| 			Y3 = 60 + YSpacer | ||||
| 			Y4 = 75 + YSpacer | ||||
| 			Y5 = 105 + YSpacer | ||||
| 			Y6 = 0 + YSpacer | ||||
| 			S1 = 130 + YSpacer | ||||
| 			 | ||||
| 			IF I < 12 THEN | ||||
| 				LabelString := '^FO0,':S1:'^GB1200,0,3,B^FS':CRLF$	;* horizontal line under fields | ||||
| 			END | ||||
| 			 | ||||
| 			LabelString := '^BY2':CRLF$						;* This is Code 128 Barcode - change ratio | ||||
|  | ||||
| 			LabelString := '^FO0,':Y1:'^A0,25^FDPart #:^FS':CRLF$					;* Label Line 1 | ||||
| 			LabelString := '^FO0,':Y2:'^A0,25^FDCust(P)^FS':CRLF$					;* Label Line 2 | ||||
| 			LabelString := '^FO100,':Y1:'^A0,63,45^FD':PartNos<1,I>:'^FS':CRLF$		;* Readable | ||||
| 			LabelString := '^FO100,':Y3:'^BC,65,N^FDP':PartNos<1,I>:'^FS':CRLF$		;* Code 128 | ||||
|  | ||||
| 			LabelString := '^BY3,3.0':CRLF$					;* Reset narrow bar width and Ratio | ||||
|  | ||||
| 			LabelString := '^FO700,':Y4:'^A0,25^FDQuantity:^FS':CRLF$				;* Label Line 1 | ||||
| 			LabelString := '^FO700,':Y5:'^A0,25^FD(Q)^FS':CRLF$						;* Label Line 2 | ||||
| 			LabelString := '^FO810,':Y4:'^A0,63,45^FD':PartQtys<1,I>:'^FS':CRLF$	;* Readable | ||||
| 			LabelString := '^FO700,':Y6:'^B3,,65,N^FDQ':PartQtys<1,I>:'^FS':CRLF$	;* Code 39 | ||||
| 		END | ||||
| 	NEXT I | ||||
|  | ||||
| 	LabelString := '^XZ':CRLF$ | ||||
| 	ThirdLabel = LabelString | ||||
|  | ||||
| END	;* End of check for 7 or more part numbers | ||||
|  | ||||
| IF ThirdLabel NE '' THEN | ||||
|     If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then | ||||
|         stat = Set_Printer('TEXT',ThirdLabel:SecondLabel:TopLabel) | ||||
|     end else | ||||
|         stat = Direct_Print('PRINT', ThirdLabel:SecondLabel:TopLabel) | ||||
|     end | ||||
| END ELSE | ||||
|     If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then | ||||
|         stat = Set_Printer('TEXT',SecondLabel:TopLabel) | ||||
|     end else | ||||
|         stat = Direct_Print('PRINT', SecondLabel:TopLabel) | ||||
|     end | ||||
| END | ||||
|  | ||||
| RETURN | ||||
|  | ||||
|  | ||||
|  | ||||
| * * * * * * * | ||||
| Label6x4: | ||||
| * * * * * * *  | ||||
|  | ||||
| If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then | ||||
|     stat = Set_Printer('TEXT',ImageData) | ||||
| end else | ||||
|     stat = Direct_Print('PRINT', ImageData) | ||||
| end | ||||
|  | ||||
| * Label is 1218 x 812 dots at 8dots/mm (203 dots/inch) | ||||
| * Leave periodic spaces in Label String - OIPrint interface wraps text on spaces and will cut off  | ||||
| * the LabelString if there aren't any spaces.  Printer Width needs to be set to 132 or greater | ||||
|  | ||||
| LabelString  = '^XA'				;* Start of label format | ||||
| LabelString := '^LH10,30'			;* Label home offset (needed to get onto the label medium) | ||||
| LabelString := '^BY3'				;* Set narrow Bar Code line width to 3 dots | ||||
| LabelString := '^PR2'				;* Print speed = 2 IPS | ||||
| LabelString := '^LL812.8':CRLF$		;* Label Length in Dots @ 8 Dots per Inch | ||||
|  | ||||
| LabelString := '^FO0,200^GB1200,0,3,B^FS':CRLF$	;* 1st horizontal line (bottom of 1st cell) | ||||
| LabelString := '^FO0,403^GB1200,0,3,B^FS':CRLF$	;* 2nd horizontal line (bottom of 2nd cell) | ||||
| LabelString := '^FO0,606^GB1200,0,3,B^FS':CRLF$	;* 3rd horizontal line (bottom of 3rd cell) | ||||
| LabelString := '^FO606,200^GB0,606,3,B^FS':CRLF$	;* Middle vertical line | ||||
|  | ||||
| RETURN | ||||
|  | ||||
|  | ||||
|  | ||||
		Reference in New Issue
	
	Block a user