added LSL2 stored procedures
This commit is contained in:
652
LSL2/STPROC/PRINT_CARTON_LABELS.txt
Normal file
652
LSL2/STPROC/PRINT_CARTON_LABELS.txt
Normal file
@ -0,0 +1,652 @@
|
||||
COMPILE SUBROUTINE Print_Carton_Labels( ShipNo )
|
||||
#pragma precomp SRP_PreCompiler
|
||||
|
||||
/*
|
||||
Prints carton labels from CoC screen
|
||||
09/16/2003 John C. Henry - J.C. Henry & Co., Inc.
|
||||
04/23/2004 John C. Henry - Modified to include obj_Zebra160s functionality - Problems skipping labels
|
||||
07/14/2006 John C. Henry - Modified to single shipment and changes for WM_OUT instead of RDS based cassettes
|
||||
*/
|
||||
|
||||
DECLARE FUNCTION FieldCount, Msg, Key_Sort, obj_WM_Out
|
||||
DECLARE FUNCTION Repository, Utility, Dialog_Box, obj_Install
|
||||
DECLARE FUNCTION Get_Status, Printer_Select, Set_Printer, Direct_Print, Environment_Services
|
||||
|
||||
DECLARE SUBROUTINE Set_Status, ErrMsg, Msg
|
||||
|
||||
$INSERT WO_LOG_EQU
|
||||
$INSERT COC_EQU
|
||||
$INSERT RDS_EQU
|
||||
$INSERT PROD_SPEC_EQU
|
||||
$INSERT OIPRINT_EQUATES
|
||||
$INSERT MSG_EQUATES
|
||||
|
||||
EQU COL$ORDER_NO TO 1 ;* Structure of cassette data in dialog box return
|
||||
EQU COL$LINE_NO TO 2
|
||||
EQU COL$WO_STEP TO 3
|
||||
EQU COL$CASS_NO TO 4
|
||||
EQU COL$RDS_NO TO 5
|
||||
EQU COL$PART_NO TO 6
|
||||
EQU COL$LOT_NO TO 7
|
||||
EQU COL$REJECT TO 8
|
||||
EQU COL$WAFER_QTY TO 9
|
||||
|
||||
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 ShipNo = '' THEN RETURN
|
||||
|
||||
|
||||
PrintTime = ''
|
||||
|
||||
* * * * * * *
|
||||
PrintShippingLabels:
|
||||
* * * * * * *
|
||||
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)
|
||||
|
||||
ShipRec = XLATE('COC',ShipNo,'','X')
|
||||
|
||||
ShipDt = OCONV(ShipRec<COC_ENTRY_DATE$>, 'D4/' )
|
||||
RdsNos = ShipRec<COC_RDS_NO$>
|
||||
WOStepNos = ShipRec<COC_WO_STEP$>
|
||||
CassNos = ShipRec<COC_CASS_NO$>
|
||||
WONo = ShipRec<COC_WO$>
|
||||
|
||||
OrderNo = XLATE('WO_LOG',WONo,29,'X')
|
||||
CustNo = XLATE('ORDER',OrderNo,2,'X')
|
||||
CustomerName = XLATE('ORDER', OrderNo, 'CUST_NAME', 'X' )
|
||||
PONo = XLATE('ORDER',OrderNo,'PO_NO','X' )
|
||||
|
||||
CassPartNos = ''
|
||||
CassQtys = ''
|
||||
PSNos = ''
|
||||
RevLvls = ''
|
||||
|
||||
WMOutKeys = ''
|
||||
|
||||
FOR I = 1 TO COUNT(WOStepNos,@VM) + (WOStepNos NE '')
|
||||
|
||||
PSNos<1,I> = XLATE('WO_STEP',WONo:'*':WOStepNos<1,I>,1,'X')
|
||||
|
||||
RevLvls<1,I> = XLATE('PROD_SPEC',PSNos<1,I>,PROD_SPEC_REV_NUM$,'X')[-1,'B':@VM] ;* Take only the last revision level in the list
|
||||
|
||||
IF RdsNos<1,I> = '' THEN
|
||||
WMOutKey = WONo:'*':WOStepNos<1,I>:'*':CassNos<1,I>
|
||||
WMOutKeys<1,I> = WMOutKey
|
||||
WMOutPartQtys = obj_WM_Out('GetPartNoQtys',WMOutKey)
|
||||
PartNos = WMOutPartQtys<1>
|
||||
Qtys = WMOutPartQtys<2>
|
||||
|
||||
IF INDEX(PartNos,@VM,1) THEN
|
||||
PartNos = 'Mixed'
|
||||
Qtys = SUM(Qtys)
|
||||
END
|
||||
|
||||
CassPartNos<1,I> = PartNos
|
||||
CassQtys<1,I> = Qtys
|
||||
END ELSE
|
||||
CassPartNos<1,I> = XLATE('RDS',RdsNos<1,I>,RDS_PART_NUM$,'X' )
|
||||
CassQtys<1,I> = XLATE('RDS',RdsNos<1,I>,'WFRS_OUT','X')
|
||||
END
|
||||
|
||||
NEXT I
|
||||
|
||||
EDISerialNo = RdsNos<1,1>
|
||||
|
||||
SupplierCd = XLATE( 'PROD_SPEC', PSNos<1,1>, PROD_SPEC_SUPPLIER_CODE$, 'X' )
|
||||
IF SupplierCd = '' THEN
|
||||
SupplierCd = obj_Install('Get_Prop','Duns') ;* DUNS number
|
||||
END
|
||||
|
||||
AllCartonData = Dialog_Box('DIALOG_CARTON_PACK',@WINDOW,ShipNo)
|
||||
|
||||
IF AllCartonData = 'Cancel' THEN RETURN
|
||||
|
||||
* Got all data now we can print
|
||||
|
||||
* Internal method that selects printer, 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 = '\\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
|
||||
|
||||
CartonCnt = COUNT(AllCartonData,@FM) + (AllCartonData NE '')
|
||||
|
||||
FOR CtnNo = 1 TO CartonCnt
|
||||
CassCnt = COUNT(AllCartonData<CtnNo>,@VM) + (AllCartonData<CtnNo> NE '')
|
||||
PartNos = ''
|
||||
PartQtys = ''
|
||||
|
||||
FOR J = 1 TO CassCnt
|
||||
CassPartNo = AllCartonData<CtnNo,J,COL$PART_NO>
|
||||
CassWaferQty = AllCartonData<CtnNo,J,COL$WAFER_QTY>
|
||||
LOCATE CassPartNo IN PartNos SETTING Pos THEN
|
||||
PartQtys<1,Pos> = PartQtys<1,Pos> + CassWaferQty
|
||||
END ELSE
|
||||
PartNos = INSERT(PartNos,1,Pos,0,CassPartNo)
|
||||
PartQtys = INSERT(PartQtys,1,Pos,0,CassWaferQty)
|
||||
END
|
||||
Next J
|
||||
|
||||
|
||||
CompProps = 'Company':@FM:'AddrSingle':@FM:'City':@FM:'State':@FM:'ZIPShort':@FM:'Country'
|
||||
|
||||
CompNameAddr = obj_Install('Get_Prop',CompProps)
|
||||
|
||||
PartNoCnt = COUNT(PartNos,@VM) + (PartNos NE '')
|
||||
FOR Label = 1 to PartNoCnt
|
||||
|
||||
Parms = PartNos<1,Label> ;* Customer Part No - 18 alphanumeric
|
||||
Parms<2> = PartQtys<1,Label> ;* Part Qty - 6 numeric
|
||||
Parms<3> = PoNo ;* Purchase Order No - 12 alphanumeric
|
||||
Parms<4> = RevLvls<1,Label> ;* Engineering Change or Rev - 3 alpha
|
||||
Parms<5> = SupplierCd ;* Customer supplied Vend ID - 12 alphanumeric
|
||||
Parms<6> = '' ;* Delivery Location - 8 char (VARIOUS is OK)
|
||||
Parms<7> = '' ;* EDI transaction serial no - 9 alpha
|
||||
Parms<8> = '' ;* Plant & Dock designator - 7 character
|
||||
Parms<9> = '' ;* Vendor Lot Number - 10 character
|
||||
Parms<10> = '' ;* Storage Bin at Customer - 30 character
|
||||
Parms<11> = '' ;* Ship to Plant Name - 30 character
|
||||
Parms<12> = '' ;* Ship to Plant City - 30 character
|
||||
Parms<13> = ShipDt ;* Date of Manufacture - MM/DD/YYYY
|
||||
Parms<14> = 'Epitaxial Layer(s)' ;* Part Description - 25 character
|
||||
Parms<15> = CtnNo ;* Carton Sequence Number
|
||||
Parms<16> = CartonCnt ;* Total cartons in group
|
||||
Parms<17> = CompNameAddr<1>:', ':CompNameAddr<2> ;* Manufacturer - 30 character
|
||||
Parms<18> = CompNameAddr<3> ;* Mfr City - 20 character
|
||||
Parms<19> = CompNameAddr<4> ;* Mfr State code - 2 character
|
||||
Parms<20> = CompNameAddr<5> ;* ZIP code - 7 character
|
||||
Parms<21> = CompNameAddr<6> ;* Country of origin - 10 character
|
||||
|
||||
IF CustNo = '562' THEN
|
||||
* This is Delphi
|
||||
Parms<4> = '' ;* No Rev Level
|
||||
Parms<6> = 'FAB 5' ;* Delivery Location
|
||||
Parms<7> = EDISerialNo
|
||||
Parms<8> = 'DAIC' ;* Plant and Dock Designator
|
||||
Parms<10> = '0001 ' ;* Storage Bin - try with a space for now.
|
||||
Parms<11> = 'Delphi Delco Electronics' ;* Ship to Plant Name
|
||||
Parms<12> = 'Kokomo' ;* Ship to Plant City
|
||||
EDISerialNo += 1
|
||||
END
|
||||
|
||||
IF CustNo = '6622' OR CustNo = '406' THEN
|
||||
* This is another Delphi
|
||||
Parms<4> = ''
|
||||
Parms<6> = 'FAB 3' ;* Delivery Location
|
||||
Parms<7> = EDISerialNo
|
||||
Parms<8> = 'DAIC'
|
||||
EDISerialNo += 1
|
||||
END
|
||||
|
||||
CONVERT @FM TO @RM IN Parms
|
||||
|
||||
GOSUB ContainerLabel ;* Print two labels
|
||||
GOSUB ContainerLabel
|
||||
|
||||
NEXT Label
|
||||
NEXT CtnNo
|
||||
|
||||
|
||||
* * * * * * *
|
||||
OIPrint_Err:
|
||||
* * * * * * *
|
||||
|
||||
* Local method to terminate print job
|
||||
|
||||
IF stat < 0 THEN DEBUG ;************
|
||||
|
||||
If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then
|
||||
stat = Set_Printer("TERM")
|
||||
end else
|
||||
stat = Direct_Print('STOP')
|
||||
end
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
ContainerLabel:
|
||||
* * * * * * *
|
||||
|
||||
CustPartNo = Parms[1,@RM] ;* Customer Part No - 18 alphanumeric
|
||||
PartQty = Parms[COL2()+1,@RM] ;* Part Qty - 6 numeric
|
||||
PONo = Parms[COL2()+1,@RM] ;* Purchase Order No - 12 alphanumeric
|
||||
RevLvl = Parms[COL2()+1,@RM] ;* Engineering Change or Rev - 3 alpha
|
||||
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
|
||||
LotNo = Parms[COL2()+1,@RM] ;* Vendor Lot Number - 10 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
|
||||
MfgDt = Parms[COL2()+1,@RM] ;* Date of Manufacture - MM/DD/YYYY
|
||||
PartDesc = Parms[COL2()+1,@RM] ;* Part Description - 25 character
|
||||
CartonNo = Parms[COL2()+1,@RM] ;* Carton sequence number
|
||||
CartonQty = Parms[COL2()+1,@RM] ;* Total cartons in group
|
||||
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
|
||||
|
||||
|
||||
ErrorMsg = ''
|
||||
IF CustPartNo = '' THEN ErrorMsg = 'Null parm CustPartNo passed to routine.'
|
||||
IF PartQty = '' THEN ErrorMsg = 'Null parm PartQty passed to routine.'
|
||||
IF SupplierCd = '' THEN ErrorMsg = 'Null parm SupplierCd passed to routine.'
|
||||
IF MfgDt = '' THEN ErrorMsg = 'Null parm MfgDate passed to routine.'
|
||||
IF PartDesc = '' THEN ErrorMsg = 'Null parm PartDesc passed to routine.'
|
||||
|
||||
IF ErrorMsg NE '' THEN
|
||||
ErrMsg(ErrorMsg)
|
||||
RETURN
|
||||
END
|
||||
|
||||
GOTO PrintSideways
|
||||
|
||||
* * * * * * * * * * * * * * * * * * *
|
||||
|
||||
RETURN
|
||||
|
||||
*Start Printing Process
|
||||
|
||||
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 @ 203 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
|
||||
|
||||
* * * * * * *
|
||||
* Top Block Left - Customer Part Number
|
||||
* * * * * * *
|
||||
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,0^A0,120,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,105^A0,25^FDQuantity:^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO700,135^A0,25^FD(Q)^FS':CRLF$ ;* Label Line 2
|
||||
LabelString := '^FO810,105^A0,120,60^FD':PartQty:'^FS':CRLF$ ;* Readable
|
||||
LabelString := '^FO700,0^B3,,100,N^FDQ':PartQty:'^FS':CRLF$ ;* Code 39
|
||||
|
||||
* * * * * * *
|
||||
* 2nd Block Left - PO No
|
||||
* * * * * * *
|
||||
LabelString := '^FO0,208^A0,25^FDP.O.:^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO0,238^A0,25^FD(K)^FS':CRLF$ ;* Label Line 2
|
||||
LabelString := '^FO100,208^A0,120,60^FD':PONo:'^FS':CRLF$ ;* Readable
|
||||
|
||||
IF LEN(PONo) > 8 THEN
|
||||
LabelString := '^BY2':CRLF$ ;* Min bar width to 2 dots
|
||||
LabelString := '^FO100,303^BC,100,N^FDK':PONo:'^FS':CRLF$ ;* Code 128
|
||||
LabelString := '^BY3,3.0':CRLF$ ;* Reset bar width and Ratio
|
||||
END ELSE
|
||||
LabelString := '^FO100,303^B3,,100,N^FDK':PONo:'^FS':CRLF$ ;* Code 39
|
||||
END
|
||||
|
||||
* * * * * * *
|
||||
* 2nd Block Right - Revision Level & Delivery Location
|
||||
* * * * * * *
|
||||
IF RevLvl NE '' THEN
|
||||
LabelString := '^FO615,233^A0,25^FDRev.Lvl:^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO615,263^A0,25^FD(2P)^FS':CRLF$ ;* Label Line 2
|
||||
LabelString := '^FO720,233^A0,60,48^FD':RevLvl:'^FS':CRLF$ ;* Readable
|
||||
LabelString := '^FO830,203^B3,,100,N^FD2P':RevLvl:'^FS':CRLF$ ;* Code 39
|
||||
END
|
||||
|
||||
LabelString := '^FO615,308^A0,25^FDDLOC^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO700,308^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(3S)^FS':CRLF$ ;* Label Line 2
|
||||
|
||||
IF SerialNo NE '' THEN
|
||||
LabelString := '^FO100,408^A0,120,80^FD':SerialNo:'^FS':CRLF$ ;* Readable
|
||||
LabelString := '^FO50,503^BY2^B3,,90,N^FD3S':SerialNo:'^FS':CRLF$ ;* Code 39 2 dot bar
|
||||
LabelString := '^BY3':CRLF$ ;* Reset to 3 dot bar
|
||||
END
|
||||
|
||||
|
||||
* * * * * * *
|
||||
* 3rd Block Right - Plant/Dock, Storage Bin, Plant Name, Plant City & Lot #
|
||||
* * * * * * *
|
||||
IRC_CustNos = '408':@VM:'6593':@VM:'6874':@VM:'6797':@VM:'7034':@VM:'7035':@VM:'7058' ;* 7034 & 7035 are Vishay customer numbers 5/11/2007 JCH
|
||||
|
||||
LOCATE CustNo IN IRC_CustNos USING @VM SETTING Dummy THEN
|
||||
|
||||
LabelString := '^FO700,510^A0,25^FDWO No:^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO810,510^A0,120,60^FD':WONo:'^FS':CRLF$ ;* Readable
|
||||
LabelString := '^FO700,405^B3,,100,N^FD':WONo:'^FS':CRLF$ ;* Code 39
|
||||
|
||||
END ELSE
|
||||
|
||||
LabelString := '^FO615,428^A0,25^FDPLT./DOCK^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO615,453^A0,100,80^FD':PlantDock:'^FS':CRLF$ ;* Readable
|
||||
|
||||
IF LotNo NE '' THEN
|
||||
LabelString := '^FO850,408^BY2^BC,40,N^FD1T':LotNo:'^FS':CRLF$ ;* Code 128
|
||||
LabelString := '^BY3':CRLF$
|
||||
LabelString := '^FO900,453^A0,25^FDLOT NO:^FS':CRLF$
|
||||
LabelString := '^FO900,478^A0,25^FD(1T)^FS':CRLF$
|
||||
LabelString := '^FO1000,453^A030,40^FD':LotNo:'^FS':CRLF$
|
||||
END
|
||||
|
||||
IF StorageBin NE '' THEN
|
||||
LabelString := '^FO615,534^A0,25^FDSTORAGE BIN:^FS':CRLF$ ;* Storage Bin Label
|
||||
LabelString := '^FO775,534^A0,25^FD':StorageBin:'^FS':CRLF$ ;* Storage Bin Readable
|
||||
END
|
||||
|
||||
IF PlantName NE '' THEN
|
||||
LabelString := '^FO615,559^A0,25^FDPLANT NAME:^FS':CRLF$ ;* Plant Name Label
|
||||
LabelString := '^FO775,559^A0,25^FD':PlantName:'^FS':CRLF$ ;* Plant Name Readable
|
||||
END
|
||||
|
||||
IF PlantCity NE '' THEN
|
||||
LabelString := '^FO615,584^A0,25^FDPLANT CITY:^FS':CRLF$ ;* Plant City Label
|
||||
LabelString := '^FO775,584^A0,25^FD':PlantCity:'^FS':CRLF$ ;* Plant City Readable
|
||||
END
|
||||
END
|
||||
|
||||
* * * * * * *
|
||||
* 4th Block Left -
|
||||
* * * * * * *
|
||||
LabelString := '^FO20,612^XGR:':GRFName:',1,1^FS':CRLF$ ;* Company Logo in GRF format
|
||||
LabelString:= '^FO0,700^A050,35^FDCarton: ':CartonNo:' of ':CartonQty:'^FS':CRLF$
|
||||
|
||||
* * * * * * *
|
||||
* 4th Block Right - Supplier and Description info
|
||||
* * * * * * *
|
||||
|
||||
* Supplier Code
|
||||
LabelString := '^FO620,660^A0,25^FDSupplier (V):^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO780,660^A0,45,30^FD':SupplierCd:'^FS':CRLF$ ;* Readable
|
||||
LabelString := '^FO650,606^BY2^B3,,50,N^FDV':SupplierCd:'^FS':CRLF$ ;* Code 39
|
||||
LabelString := '^BY3'
|
||||
|
||||
* Part Description
|
||||
LabelString := '^FO620,700^A0,40,30^FDDesc: ':PartDesc:'^FS':CRLF$
|
||||
|
||||
* Manufacture Date
|
||||
LabelString := '^FO1060,690^A0,25,28^FDMfg.Date:^FS':CRLF$
|
||||
LabelString := '^FO1060,715^A0,25,28^FD':MfgDt:'^FS':CRLF$
|
||||
|
||||
* Manufacturer Name, City, ST, ZIP
|
||||
LabelString := '^FO620,743^A0,25,28^FD':Manufacturer:'^FS':CRLF$
|
||||
LabelString := '^FO620,768^A0,25,28^FD':City:' ':ST:' ':ZIP:'^FS'
|
||||
|
||||
* Country (Made In)
|
||||
LabelString := '^FO1060,743^A0,25,28^FDMade In:^FS':CRLF$
|
||||
LabelString := '^FO1060,768^A0,25,28^FD':Country:'^FS':CRLF$
|
||||
|
||||
* * * * *
|
||||
LabelString := '^XZ'
|
||||
* END ZPL
|
||||
|
||||
If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then
|
||||
stat = Set_Printer('TEXT',LabelString)
|
||||
end else
|
||||
stat = Direct_Print('PRINT', LabelString)
|
||||
end
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
PrintSideways:
|
||||
* * * * * * *
|
||||
|
||||
*Start Printing Process
|
||||
|
||||
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 := '^FWR' ;* Rotate 90 degrees
|
||||
LabelString := '^LH0,0' ;* 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 @ 203 Dots per Inch
|
||||
|
||||
|
||||
LabelString := '^FO595,0^GB0,1200,3,B^FS':CRLF$ ;* 1st horizontal line (bottom of 1st cell)
|
||||
LabelString := '^FO390,0^GB0,1200,3,B^FS':CRLF$ ;* 2nd horizontal line (bottom of 2nd cell)
|
||||
LabelString := '^FO205,0^GB0,1200,3,B^FS':CRLF$ ;* 3rd horizontal line (bottom of 3rd cell)
|
||||
LabelString := '^FO0,606^GB595,0,3,B^FS':CRLF$ ;* Middle vertical line
|
||||
|
||||
* * * * * * *
|
||||
* Top Block Left - Customer Part Number
|
||||
* * * * * * *
|
||||
|
||||
LabelString := '^BY2':CRLF$ ;* This is Code 128 Barcode - change ratio
|
||||
|
||||
LabelString := '^FO760,15^A0,25^FDPart #:^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO735,15^A0,25^FDCust(P)^FS':CRLF$ ;* Label Line 2
|
||||
LabelString := '^FO670,100^A0,120,60^FD':CustPartNo:'^FS':CRLF$ ;* Readable
|
||||
LabelString := '^FO595,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 := '^FO635,700^A0,25^FDQuantity:^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO600,700^A0,25^FD(Q)^FS':CRLF$ ;* Label Line 2
|
||||
LabelString := '^FO570,805^A0,120,60^FD':PartQty:'^FS':CRLF$ ;* Readable
|
||||
LabelString := '^FO690,700^B3,,100,N^FDQ':PartQty:'^FS':CRLF$ ;* Code 39
|
||||
|
||||
|
||||
* * * * * * *
|
||||
* 2nd Block Left - PO No
|
||||
* * * * * * *
|
||||
|
||||
LabelString := '^FO555,15^A0,25^FDP.O.:^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO530,15^A0,25^FD(K)^FS':CRLF$ ;* Label Line 2
|
||||
LabelString := '^FO465,100^A0,120,60^FD':PONo:'^FS':CRLF$ ;* Readable
|
||||
|
||||
IF LEN(PONo) > 8 THEN
|
||||
LabelString := '^BY2':CRLF$ ;* Min bar width to 2 dots
|
||||
LabelString := '^FO390,100^BC,100,N^FDK':PONo:'^FS':CRLF$ ;* Code 128
|
||||
LabelString := '^BY3,3.0':CRLF$ ;* Reset bar width and Ratio
|
||||
END ELSE
|
||||
LabelString := '^FO390,100^B3,,100,N^FDK':PONo:'^FS':CRLF$ ;* Code 39
|
||||
END
|
||||
|
||||
|
||||
|
||||
|
||||
* * * * * * *
|
||||
* 2nd Block Right - Revision Level & Delivery Location
|
||||
* * * * * * *
|
||||
|
||||
|
||||
IF RevLvl NE '' THEN
|
||||
LabelString := '^FO560,615^A0,25^FDRev.Lvl:^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO535,615^A0,25^FD(2P)^FS':CRLF$ ;* Label Line 2
|
||||
LabelString := '^FO535,720^A0,60,48^FD':RevLvl:'^FS':CRLF$ ;* Readable
|
||||
LabelString := '^FO495,830^B3,,100,N^FD2P':RevLvl:'^FS':CRLF$ ;* Code 39
|
||||
END
|
||||
|
||||
LabelString := '^FO460,615^A0,25^FDDLOC^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO370,705^A0,120,80^FD':DeliveryLoc:'^FS':CRLF$ ;* Readable
|
||||
|
||||
|
||||
* * * * * * *
|
||||
* 3rd Block Left - Serial Number
|
||||
* * * * * * *
|
||||
|
||||
LabelString := '^FO350,15^A0,25^FDSerial #:^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO320,15^A0,25^FD(3S)^FS':CRLF$ ;* Label Line 2
|
||||
|
||||
|
||||
IF SerialNo NE '' THEN
|
||||
LabelString := '^FO270,100^A0,120,80^FD':SerialNo:'^FS':CRLF$ ;* Readable
|
||||
LabelString := '^FO205,50^BY2^B3,,90,N^FD3S':SerialNo:'^FS':CRLF$ ;* Code 39 2 dot bar
|
||||
LabelString := '^BY3':CRLF$ ;* Reset to 3 dot bar
|
||||
END
|
||||
|
||||
|
||||
* * * * * * *
|
||||
* 3rd Block Right - Plant/Dock, Storage Bin, Plant Name, Plant City & Lot #
|
||||
* * * * * * *
|
||||
|
||||
IRC_CustNos = '408':@VM:'6593':@VM:'6874':@VM:'6797':@VM:'7034':@VM:'7035':@VM:'7058' ;* 7034 & 7035 are Vishay customer numbers 5/11/2007 JCH
|
||||
|
||||
|
||||
LOCATE CustNo IN IRC_CustNos USING @VM SETTING Dummy THEN
|
||||
|
||||
LabelString := '^FO350,700^A0,25^FDWO No:^FS':CRLF$ ;* Label Line 1
|
||||
*LabelString := '^FO320,700^A0,25^FD(Q)^FS':CRLF$ ;* Label Line 2 ;* Find out what letter is used here
|
||||
LabelString := '^FO270,810^A0,120,60^FD':WONo:'^FS':CRLF$ ;* Readable
|
||||
LabelString := '^FO205,700^B3,,90,N^FD':WONo:'^FS':CRLF$ ;* Code 39
|
||||
|
||||
END ELSE
|
||||
|
||||
LabelString := '^FO360,615^A0,25^FDPLT./DOCK^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO255,615^A0,100,80^FD':PlantDock:'^FS':CRLF$ ;* Readable
|
||||
|
||||
IF LotNo NE '' THEN
|
||||
LabelString := '^FO350,850^BY2^BC,40,N^FD1T':LotNo:'^FS':CRLF$ ;* Code 128
|
||||
LabelString := '^BY3':CRLF$
|
||||
LabelString := '^FO320,900^A0,25^FDLOT NO:^FS':CRLF$
|
||||
LabelString := '^FO295,900^A0,25^FD(1T)^FS':CRLF$
|
||||
LabelString := '^FO310,990^A030,40^FD':LotNo:'^FS':CRLF$
|
||||
END
|
||||
|
||||
IF StorageBin NE '' THEN
|
||||
LabelString := '^FO514,615^A0,25^FDSTORAGE BIN:^FS':CRLF$ ;* Storage Bin Label
|
||||
LabelString := '^FO514,775^A0,25^FD':StorageBin:'^FS':CRLF$ ;* Storage Bin Readable
|
||||
END
|
||||
|
||||
IF PlantName NE '' THEN
|
||||
LabelString := '^FO539,615^A0,25^FDPLANT NAME:^FS':CRLF$ ;* Plant Name Label
|
||||
LabelString := '^FO539,775^A0,25^FD':PlantName:'^FS':CRLF$ ;* Plant Name Readable
|
||||
END
|
||||
|
||||
IF PlantCity NE '' THEN
|
||||
LabelString := '^FO564,615^A0,25^FDPLANT CITY:^FS':CRLF$ ;* Plant City Label
|
||||
LabelString := '^FO564,775^A0,25^FD':PlantCity:'^FS':CRLF$ ;* Plant City Readable
|
||||
END
|
||||
END
|
||||
|
||||
|
||||
* * * * * * *
|
||||
* 4th Block Left -
|
||||
* * * * * * *
|
||||
|
||||
*LabelString := '^FO185,30^XGR:':GRFName:',1,1^FS':CRLF$ ;* Company Logo in GRF format
|
||||
|
||||
LabelString:= '^FO90,15^A050,35^FDCarton: ':CartonNo:' of ':CartonQty:'^FS':CRLF$
|
||||
|
||||
* * * * * * *
|
||||
* 4th Block Right - Supplier and Description info
|
||||
* * * * * * *
|
||||
|
||||
* Supplier Code
|
||||
|
||||
LabelString := '^FO120,620^A0,25^FDSupplier (V):^FS':CRLF$ ;* Label Line 1
|
||||
LabelString := '^FO100,780^A0,45,30^FD':SupplierCd:'^FS':CRLF$ ;* Readable
|
||||
LabelString := '^FO155,650^BY2^B3,,50,N^FDV':SupplierCd:'^FS':CRLF$ ;* Code 39
|
||||
LabelString := '^BY3'
|
||||
|
||||
* Part Description
|
||||
|
||||
LabelString := '^FO60,620^A0,40,30^FDDesc: ':PartDesc:'^FS':CRLF$
|
||||
|
||||
* Manufacture Date
|
||||
|
||||
LabelString := '^FO75,1060^A0,25,28^FDMfg.Date:^FS':CRLF$
|
||||
LabelString := '^FO50,1060^A0,25,28^FD':MfgDt:'^FS':CRLF$
|
||||
|
||||
* Manufacturer Name, City, ST, ZIP
|
||||
|
||||
LabelString := '^FO25,620^A0,25,28^FD':Manufacturer:'^FS':CRLF$
|
||||
LabelString := '^FO0,620^A0,25,28^FD':City:' ':ST:' ':ZIP:'^FS'
|
||||
|
||||
* Country (Made In)
|
||||
|
||||
LabelString := '^FO25,1060^A0,25,28^FDMade In:^FS':CRLF$
|
||||
LabelString := '^FO0,1060^A0,25,28^FD':Country:'^FS':CRLF$
|
||||
|
||||
|
||||
|
||||
LabelString := '^XZ'
|
||||
|
||||
If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then
|
||||
stat = Set_Printer('TEXT',LabelString)
|
||||
end else
|
||||
stat = Direct_Print('PRINT', LabelString)
|
||||
end
|
||||
|
||||
RETURN
|
||||
|
||||
|
Reference in New Issue
Block a user