COMPILE SUBROUTINE Print_Cass_Ship_Label( WONo,WOSteps,CassNos,RDSNos ) #pragma precomp SRP_PreCompiler //Complete Rewrite for EpiPRO 06/11/2006 by John C. Henry, J.C. Henry & Co., Inc. $INSERT LOGICAL $INSERT MSG_EQUATES $INSERT RDS_EQU $INSERT PROD_VER_EQUATES $INSERT OIPRINT_EQUATES $INSERT PROD_SPEC_EQU $INSERT PRS_LAYER_EQU $INSERT WO_LOG_EQUATES $INSERT WO_STEP_EQU $INSERT WO_MAT_EQUATES $INSERT WM_OUT_EQUATES $INSERT ORDER_EQU $INSERT ORDER_DET_EQU $INSERT REACTOR_EQUATES $INSERT REACT_RUN_EQUATES DECLARE FUNCTION Msg, Get_Printer, Set_Printer, obj_Prod_Spec DECLARE FUNCTION Get_Status, Utility, Printer_Select, obj_Install, Direct_Print, Environment_Services DECLARE SUBROUTINE Set_Status, Msg, errMsg, obj_Zebra105SL 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 ErrorMsg = '' IF NOT(ASSIGNED(WONo)) THEN ErrorMsg = 'Unassigned parameter "WONo" passed to PRINT_CASS_SHIP_LABEL routine.' IF NOT(ASSIGNED(WOSteps)) THEN ErrorMsg = 'Unassigned parameter "WOSteps" passed to PRINT_CASS_SHIP_LABEL routine.' IF NOT(ASSIGNED(CassNos)) THEN ErrorMsg = 'Unassigned parameter "CassNos" passed to PRINT_CASS_SHIP_LABEL routine.' IF NOT(ASSIGNED(RDSNos)) THEN ErrorMsg = 'Unassigned parameter "RDSNos" passed to PRINT_CASS_SHIP_LABEL routine.' IF ErrorMsg NE '' THEN ErrMsg(ErrorMsg) RETURN END PrinterID = '\\mesirwfp001\MESZBRPRT003' ;* This is the 105SL - This is the production 1 * Initialize the printer FileName = "Printing Label" Title = "Printing Label" ;* Initialize Printing PageInfo = '' PageInfo = 0.1 PageInfo = 0.1 PageInfo = 0.1 PageInfo = 0.1 PageSetup = '1' ;* Landscape PrintSetup = '0' ;* Print to specific location PrintPath = Printer_Select(PrinterID) ;* Select printer - Displays popup if PrinterPort not found IF PrintPath = '' THEN Def = "" Def = "TA3" Def = 'Destination Printer not Selected..' Def = '' Def = '*' 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 ;* Bail = couldn't initialize the printer 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:' file for BarCode Label') END GRFName = FIELD(BitMap,'.',1) ReactNos = XLATE('REACT_RUN',RDSNos,REACT_RUN_REACTOR$,'X') ;* Added 12/16/2008 - JCH - Adding Reactor Type codes to cassette labels ReactTypes = OCONV(XLATE('REACTOR',ReactNos,REACTOR_REACT_TYPE$,'X'),'[REACT_TYPE_CONV,OPSREF]') ;* Added 12/16/2008 - JCH - Adding Reactor Type codes to cassette labels WORec = XLATE('WO_LOG',WONo,'','X') ReqShipDt = OCONV( WORec, 'D2/' ) ProdOrdNo = WORec ProdVerNo = WORec IF ProdOrdNo NE '' THEN PONo = ProdOrdNo ProdVerRec = XLATE('PROD_VER',ProdVerNo,'','X') CustNo = ProdVerRec ReactTypes = OCONV(ProdVerRec,'[REACT_TYPE_CONV,OPSREF]') ;*************************************************** fix this OrderItems = '' VisionOrderNo = '' VisionLineNos = '' END ELSE OrderNo = WORec OrderItems = WORec OrderRec = XLATE('ORDER',OrderNo,'','X') PONo = OrderRec CustNo = OrderRec VisionOrderNo = OrderRec VisionLineNos = XLATE('ORDER_DET',OrderItems,ORDER_DET_VISION_LINE_NO$,'X') END CustName = XLATE('COMPANY',CustNo,4,'X') CassCnt = COUNT(CassNos,@VM) + (CassNos NE '') FOR I = 1 TO CassCnt WOStep = WOSteps<1,I> ProdSpecID = XLATE('WO_STEP',WONo:'*':WOStep,WO_STEP_PROD_SPEC_ID$,'X') RevLvl = XLATE('PROD_SPEC',ProdSpecID,PROD_SPEC_REV_NUM$,'X')[-1,'B':@VM] ;* Take only the last revision level CassNo = CassNos<1,I> RDSNo = RDSNos<1,I> WOMatRec = XLATE('WO_MAT',WONo:'*':CassNo,'','X') SAPBatchNo = WOMatRec IF RDSNo NE '' THEN CassIDLabel = 'RDSNo:' CassID = RDSNo ReactType = ReactTypes<1,I> MakeupBox = WOMatRec PartNo = WOMatRec LotNo = WOMatRec SubstrPartNo = WOMatRec CassOrderItem = WOMatRec ;*************************************** IF ProdVerNo = '' THEN CustPNDesc = XLATE( 'ORDER_DET',OrderNo:'*':CassOrderItem,'CUST_PN_DESC','X') ;*************************************** END ELSE CustPNDesc = XLATE('PROD_VER',ProdVerNo,PROD_VER_CUST_PART_DESC$,'X') END SupVerify = XLATE( 'RDS', RDSNo, 'SUP_VER_SIG_NAME', 'X' ) SupVerifyDt = OCONV(XLATE('WO_MAT',WONo:'*':CassNo,'SHIP_SUP_VER_SIG_DT','X'),'D2/') WfrsOut = XLATE( 'RDS', RDSNo, 'WFRS_OUT', 'X' ) MUWfrsRemQty = XLATE( 'RDS', RDSNo, 'MU_WFRS_REMOVED','X' ) MUWfrsAddQty = XLATE( 'RDS', RDSNo, 'MU_WFRS_ADDED','X' ) ResultThickL1 = OCONV( XLATE( 'RDS', RDSNo, 'TTHICK_AVG', 'X' ), 'MD2' ) ResultThickL2 = OCONV( XLATE( 'RDS', RDSNo, 'TTHICK_AVG_L2', 'X' ), 'MD2' ) ResultThickL3 = OCONV( XLATE( 'RDS', RDSNo, 'TTHICK_AVG_L3', 'X' ), 'MD2' ) TargetThickL1 = OCONV( XLATE( 'RDS', RDSNo, 'THICK_TARGET', 'X' ), 'MD2' ) TargetThickL2 = OCONV( XLATE( 'RDS', RDSNo, 'THICK_TARGET_L2', 'X' ), 'MD2' ) TargetThickL3 = OCONV( XLATE( 'RDS', RDSNo, 'THICK_TARGET_L3', 'X' ), 'MD2' ) IF ResultThickL1 = '' THEN ResultThickL1 = TargetThickL1 IF ResultThickL2 = '' THEN ResultThickL2 = TargetThickL2 IF ResultThickL3 = '' THEN ResultThickL3 = TargetThickL3 ThickUnitsL1 = XLATE( 'RDS', RDSNo, 'THICK_UNITS', 'X' ) ThickUnitsL2 = XLATE( 'RDS', RDSNo, 'THICK_UNITS_L2', 'X' ) ThickUnitsL3 = XLATE( 'RDS', RDSNo, 'THICK_UNITS_L3', 'X' ) ResultThick = ResultThickL1 IF ResultThickL2 NE '' THEN ResultThick := '/':ResultThickL2 IF ResultThickL3 NE '' THEN ResultThick := '/':ResultThickL3 IF ResultThick NE '' THEN ResultThick := ThickUnitsL1 ResultResL1 = XLATE( 'RDS', RDSNo, 'TRES_AVG', 'X' ) ResultResL2 = XLATE( 'RDS', RDSNo, 'TRES_AVG_L2', 'X' ) ResultResL3 = XLATE( 'RDS', RDSNo, 'TRES_AVG_L3', 'X' ) TargetResL1 = OCONV( XLATE( 'RDS', RDSNo, 'RES_TARGET', 'X' ), 'MD3' ) TargetResL2 = OCONV( XLATE( 'RDS', RDSNo, 'RES_TARGET_L2', 'X' ), 'MD3' ) TargetResL3 = OCONV( XLATE( 'RDS', RDSNo, 'RES_TARGET_L3', 'X' ), 'MD3' ) IF ResultResL1 = '' THEN ResultResL1 = TargetResL1 IF ResultResL2 = '' THEN ResultResL2 = TargetResL2 IF ResultResL3 = '' THEN ResultResL3 = TargetResL3 ResUnitsL1 = XLATE( 'RDS', RDSNo, 'RES_UNITS', 'X' ) ResUnitsL2 = XLATE( 'RDS', RDSNo, 'RES_UNITS_L2', 'X' ) ResUnitsL3 = XLATE( 'RDS', RDSNo, 'RES_UNITS_L3', 'X' ) ResultRes = ResultResL1 IF ResultResL2 NE '' THEN ResultRes := '/':ResultResL2 IF ResultResL3 NE '' THEN ResultRes := '/':ResultResL3 IF ResultRes NE '' THEN ResultRes := ResUnitsL1 TargetConL1 = OCONV( XLATE( 'RDS', RDSNo, 'CON_TARGET', 'X' )<1,1>, 'MS21' ) TargetConL2 = OCONV( XLATE( 'RDS', RDSNo, 'CON_TARGET_L2', 'X' ), 'MS21' ) TargetConL3 = OCONV( XLATE( 'RDS', RDSNo, 'CON_TARGET_L3', 'X' ), 'MS21' ) ConUnitsL1 = XLATE( 'RDS', RDSNo, 'CON_UNITS', 'X' ) ConUnitsL2 = XLATE( 'RDS', RDSNo, 'CON_UNITS_L2', 'X' ) ConUnitsL3 = XLATE( 'RDS', RDSNo, 'CON_UNITS_L3', 'X' ) ResultCon = TargetConL1 IF TargetConL2 NE '' THEN ResultCon := '/':TargetConL2 IF TargetConL3 NE '' THEN ResultCon := '/':TargetConL3 IF ResultCon NE '' THEN ResultCon := ConUnitsL1 END ELSE WMOutKey = WONo:'*':WOStep:'*':CassNo WMOutRec = XLATE('WM_OUT',WMOutKey,'','X') MakeupBox = WMOutRec CassIDLabel = 'WMONo:' CassID = WMOutKey CONVERT '*' TO '.' IN CassID ReactType = 'EpiPro' ;* * * * 12/17/2008 Harded coded reactor type for EpiPro reactors SupVerify = WMOutRec SupVerifyDt = OCONV(XLATE('WO_MAT',WONo:'*':CassNo,'SHIP_SUP_VER_SIG_DT','X'),'D2/') InCassNo1 = '' InSlotNo1 = '' MUWoNo1 = '' MUCassNo1 = '' MUSlotNo1 = '' PartNo = '' LotNo = '' SubstrPartNo = '' CassOrderItem = '' CustPNDesc = '' Pointer = 1 LOOP IF WMOutRec = '' THEN InCassNo1 = WMOutRec InSlotNo1 = WMoutRec END ELSE IF MUWoNo1 = '' THEN MUWoNo1 = WMOutRec MUCassNo1 = WMOutRec MUSlotNo1 = WMOutRec END END UNTIL InCassNo1 NE '' OR Pointer > 25 Pointer += 1 REPEAT IF InCassNo1 NE '' THEN WOMatRec = XLATE('WO_MAT',WONo:'*':InCassNo1,'','X') PartNo = WOMatRec LotNo = WOMatRec SubstrPartNo = WOMatRec CassOrderItem = WOMatRec CustPNDesc = XLATE( 'ORDER_DET',OrderNo:'*':CassOrderItem,'CUST_PN_DESC','X') END ELSE IF MUWoNo1 NE '' AND MUCassNo1 NE '' THEN MUWOMatRec = XLATE('WO_MAT',MUWoNo1:'*':MUCassNo1,'','X') PartNo = MUWOMatRec LotNo = MUWOMatRec SubstrPartNo = MUWOMatRec CassOrderItem = MUWOMatRec CustPNDesc = XLATE( 'ORDER_DET',OrderNo:'*':CassOrderItem,'CUST_PN_DESC','X') END END WfrsOut = XLATE('WM_OUT',WMOutKey,'WFRS_OUT','X') MUWfrsRemQty = '' MUWfrsAddQty = '' Specs = obj_Prod_Spec('GetLayerProp',ProdSpecID) ResultThick = '' ResultRes = '' ResultCon = '' LayerCount = COUNT(Specs,@RM) + (Specs NE '') FOR Layer = 1 TO LayerCount LayerSpecs = FIELD(Specs,@RM,Layer) LayerSpecs = FIELD(LayerSpecs,@FM,2,99) ;* Pull of the layer set ID IF LayerSpecs NE '' THEN ResultThick := LayerSpecs END IF LayerSpecs NE '' THEN ResultRes := LayerSpecs END IF LayerSpecs NE '' THEN ResultCon := LayerSpecs END IF Layer < LayerCount THEN IF ResultThick NE '' THEN ResultThick := '/' IF ResultRes NE '' THEN ResultRes := '/' IF ResultCon NE '' THEN ResultCon := '/' END ELSE IF ResultThick NE '' THEN ResultThick := LayerSpecs IF ResultRes NE '' THEN ResultRes := LayerSpecs IF ResultCon NE '' THEN ResultCon := LayerSpecs END NEXT Layer END IF ProdVerNo NE '' THEN CassIDLabel = 'CassID:' END GOSUB PrintLabel NEXT I * * * * * * * OIPrint_Err: * * * * * * * If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then stat = Set_Printer("TERM") end else stat = Direct_Print('STOP') end RETURN * * * * * * * * PrintLabel: * * * * * * * * MULabel = '' IF MakeupBox = 1 THEN MULabel = '** Makeup Box **' *IF MUWfrsRemQty > 0 THEN MULabel = '** Makeup Box **' ;* Decided to ship a makeup box 6/3/2009 JCH IF MUWfrsAddQty > 0 THEN MULabel = 'Merged Lot' SuppCd = SubstrPartNo[-1,'B-'] ;* Added 8/17/2005 JCH - J.C. Henry & Co. IF LEN(SuppCd) NE 2 THEN SuppCd = '' ;* Should be either IW, IS or IM * Check bar coded data for validity for length ErrorMsg = '' IF LEN(PartNo) > 18 THEN ErrorMsg = 'CustPartNo parameter exceeds 18 characters.' IF LEN(RevLvl) > 3 THEN ErrorMsg = 'RevLvl parameter exceeds 3 characters.' IF LEN(WfrsOut) > 6 THEN ErrorMsg = 'PartQty parameter exceeds 6 characters.' IF NOT(NUM(WfrsOut)) THEN ErrorMsg = 'PartQty parameter is not a number.' IF ErrorMsg THEN ErrMsg(ErrorMsg) END ELSE * Good to go on the label print If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then stat = Set_Printer('TEXT',ImageData) end else stat = Direct_Print('PRINT', ImageData) end * Label is 812 x 608 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 := '^LH30,70' ;* 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 := '^FO0,156^GB809,0,3,B^FS':@FM ;* 'Top' of 4x3 Label LabelString := '^FO0,308^GB809,0,3,B^FS':@FM ;* 1st 'horizontal' line (bottom of 1st cell) LabelString := '^FO0,460^GB809,0,3,B^FS':@FM ;* 2nd 'horizontal' line (bottom of 2nd cell) * Block 1 Left (Cust Part) LabelString := '^FO0,10^A0,25^FDCust Part(1P):^FS':CRLF$ ;* Label Line 1 LabelString := '^FO15,45^A0,50,40^FD':PartNo:'^FS':CRLF$ ;* Readable LabelString := '^FO15,95^BY2^BC,60,N^FDP':PartNo:'^FS':CRLF$ ;* Code 128 LabelString := '^BY3,3.0':CRLF$ * Block 1 Right (Rev Lvl) LabelString := '^FO508,0^BY2^B3,,60,N^FD2P':RevLvl:'^FS':CRLF$ ;* Code 39 LabelString := '^BY3,3.0':CRLF$ LabelString := '^FO508,70^A0,25^FDRev.Level (2P):^FS':CRLF$ ;* Label Line 1 LabelString := '^FO680,70^A0,50,48^FD':RevLvl:'^FS':CRLF$ ;* Readable * Block 2 Left (Quantity) LabelString := '^FO0,165^A0,25^FDQuantity (Q):^FS':CRLF$ ;* Label Line 1 LabelString := '^FO15,195^A0,50,40^FD':WfrsOut:'^FS':CRLF$ ;* Readable LabelString := '^FO15,245^BY2^B3,,60,N^FDQ':WfrsOut:'^FS':CRLF$ ;* Code 39 LabelString := '^BY3,3.0':CRLF$ * Block 3 Left (Customer Lot) LabelString := '^FO0,315^A0,25^FDCustomer Lot:^FS':CRLF$ ;* Label Line 1 LabelString := '^FO15,350^A0,50,40^FD':LotNo:'^FS':CRLF$ ;* Readable LabelString := '^FO15,400^BY2^B3,,60,N^FD':LotNo:'^FS':CRLF$ ;* Code 39 LabelString := '^BY3,3.0':CRLF$ * Block 3 Right (Supplier) LabelString := '^FO360,320^XGR:':GRFName:',1,1^FS' ;* Horizontal Company Logo * Block 4 LabelString := '^FO0,470^A0,25^FDCustomer:^FS':CRLF$ ;* Label Line LabelString := '^FO120,470^A0,45,25^FD':CustName:'^FS':CRLF$ ;* Readable LabelString := '^FO0,515^A0,25^FD':CassIDLabel:'^FS':CRLF$ ;* Label Line LabelString := '^FO100,515^A0,36,40^FD':CassID:'^FS':CRLF$ ;* Readable LabelString := '^FO300,515^BY2^B3,,50,N^FD':CassID:'^FS':CRLF$ ;* Code 39 (This is the Cass ID) LabelString := '^BY3,3.0':CRLF$ IF SuppCd NE '' THEN LabelString := '^FO600,515^A0,25^FDSupp Cd:^FS':CRLF$ ;* Label Line - Added 8/17/2005 JCH Supplier Code Info LabelString := '^FO710,515^A0,36,40^FD':SuppCd:'^FS':CRLF$ ;* Readable LabelString := '^FO600,460^BY2^B3,,50,N^FD':SuppCd:'^FS':CRLF$ ;* Code 39 Supplier Code LabelString := '^BY3,3.0':CRLF$ END LabelString := '^FO0,570^A0,25^FDPO No:^FS':CRLF$ ;* Label Line IF ProdVerNo = '' THEN LabelString := '^FO80,570^A0,36,20^FD':PONo:'^FS':CRLF$ ;* Readable END ELSE LabelString := '^FO80,570^A0,36,40^FD':PONo:'^FS':CRLF$ ;* Readable END LabelString := '^FO280,570^A0,25^FDWO No:^FS':CRLF$ ;* Label Line LabelString := '^FO360,570^A0,36^FD':WONo:'^FS':CRLF$ ;* Readable LabelString := '^FO500,570^A0,25^FDReq Ship Dt:^FS':CRLF$ ;* Label Line LabelString := '^FO640,570^A0,36^FD':ReqShipDt:'^FS':CRLF$ ;* Readable IF CustNo = '6775' OR CustNo = '7053' THEN LabelString := '^FO0,610^A0,25^FDComp Dt:^FS':CRLF$ ;* Label Line LabelString := '^FO100,610^A0,36^FD':SupVerifyDt:'^FS':CRLF$ ;* Readable END LabelString := '^FO280,610^A0,25^FDReact Type:^FS':CRLF$ ;* Label Line Added 12/16/2008 - JCH LabelString := '^FO420,610^A0,36^FD':ReactType:'^FS':CRLF$ ;* Readable Added 12/16/2008 - JCH IF MULabel NE '' THEN LabelString := '^FO450,470^A0,40^FD':MULabel:'^FS':CRLF$ END IF SAPBatchNo = '' THEN ConcLabelString = FMT(PartNo,"L#15"):FMT(CassID,"L#12"):FMT(WfrsOut,"R#6") END ELSE ConcLabelString = FMT(PartNo,"L#15"):FMT(SAPBatchNo,"L#12"):FMT(WfrsOut,"R#6") END LabelString := '^FO20,650^BY2^BAN,90,N,N,N^FD':ConcLabelString:'^FS':CRLF$ ;* Code 93 LabelString := '^XZ' If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then stat = Set_Printer('TEXT',LabelString) end else stat = Direct_Print('PRINT', LabelString) end END RETURN