barcode. Implemented 2D barcode verification in PTI and FQA Label Check Operations. Bug fixes Changed WMI 2D barcode to have 8 fields to keep code base simpler minor changes to error message verbiage Refactored code to use post log. Refactored code to not use multiple returns. Modfield input form fields to force upper case only. changed LSL password verification to be case insensitive to avoid barcode scanning issues when caps lock is on temporary change to allow 1D WMI scans at PTI while we exhaust current supply
482 lines
15 KiB
Plaintext
482 lines
15 KiB
Plaintext
COMPILE SUBROUTINE Print_WMO_Labels(WONo,WOStep)
|
|
#pragma precomp SRP_PreCompiler
|
|
|
|
******************************************************************************
|
|
*
|
|
* Name : Material_Movement_Services
|
|
*
|
|
* Description : Handler program for all material movement services.
|
|
*
|
|
* History : (date, initials, notes)
|
|
* 05/18/06 jch Cloned from Print_Cass_Labels
|
|
* 10/18/21 DPC updated PrintLabel, added datamatrix and sequencing
|
|
*
|
|
******************************************************************************
|
|
|
|
$INSERT LOGICAL
|
|
$INSERT MSG_EQUATES
|
|
$INSERT OIPRINT_EQUATES
|
|
$INSERT POPUP_EQUATES
|
|
$INSERT PROD_SPEC_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_OUT_EQUATES
|
|
$INSERT EPI_PART_EQUATES
|
|
$INSERT CUST_EPI_PART_EQUATES
|
|
$INSERT PRS_STAGE_EQUATES
|
|
$insert UNIT_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
|
|
|
|
Main:
|
|
|
|
IF NOT(ASSIGNED(WONo)) THEN RETURN
|
|
IF WONo = '' THEN RETURN
|
|
|
|
IF NOT(ASSIGNED(WOStep)) THEN WOStep = 1
|
|
|
|
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 GE 0 THEN
|
|
|
|
CLOrientation = '' ;* used for printing on cleanroom labels
|
|
WMOutKeys = XLATE('WO_STEP',WONo:'*':WOStep,WO_STEP_WM_OUT_KEYS$,'X')
|
|
|
|
TypeOver = ''
|
|
TypeOver<PDISPLAY$> = WMOutKeys
|
|
TypeOver<PTITLE$> = 'WM_OUT - Outbound Cassettes'
|
|
TypeOver<PSHOWGAUGE$> = True$
|
|
|
|
WMoutKeys = Popup(@WINDOW,TypeOver,'PRINT_WM_LABELS')
|
|
CONVERT '.' TO '*' IN WMOutKeys
|
|
|
|
IF WMOutKeys = '' THEN RETURN
|
|
|
|
Void = Utility( 'CURSOR', 'H' )
|
|
|
|
WOStepKeys = XLATE('WO_LOG',WONo,WO_LOG_WO_STEP_KEY$,'X')
|
|
|
|
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 = XLATE('PRS_STAGE',PSNo:'*PRE',PRS_STAGE_SURFSCAN_SIG_REQ$,'X')
|
|
FirstSurfscan = XLATE('PRS_STAGE',PSNo:'*WFR',PRS_STAGE_SURFSCAN_SIG_REQ$,'X')
|
|
PostCleanSurfScan = XLATE('PRS_STAGE',PSNo:'*POST',PRS_STAGE_SURFSCAN_SIG_REQ$,'X')
|
|
|
|
PostCleanSSSampleQty = XLATE('PRS_STAGE',PSNo:'*POST',PRS_STAGE_SS_SAMP_QTY$, 'X' )
|
|
PostCleanSurfscanRecipe = XLATE('PRS_STAGE',PSNo:'*POST',PRS_STAGE_SURFSCAN_RECIPE$,'X')
|
|
PostCleanSurfDefects = XLATE('PRS_STAGE',PSNo:'*POST',PRS_STAGE_SURF_DEFECTS$,'X')
|
|
PostCleanSurfHaze = OCONV(XLATE('PRS_STAGE',PSNo:'*POST',PRS_STAGE_SURF_HAZE$,'X'),'MD2')
|
|
|
|
SubPreClean = XLATE('PRS_STAGE',PSNo:'*PRE','TOOL_DISPLAY','X')
|
|
SubPostClean = XLATE('PRS_STAGE',PSNo:'*POST','TOOL_DISPLAY','X')
|
|
|
|
PreCleanTool = XLATE('PRS_STAGE',PSNo:'*PRE','TOOL_DISPLAY','X')
|
|
PostCleanTool = XLATE('PRS_STAGE',PSNo:'*POST','TOOL_DISPLAY','X')
|
|
|
|
PreAkrionRecipe = XLATE('PRS_STAGE',PSNo:'*PRE',PRS_STAGE_CLEAN_RECIPE$,'X')
|
|
PostAkrionRecipe = XLATE('PRS_STAGE',PSNo:'*POST',PRS_STAGE_CLEAN_RECIPE$,'X')
|
|
|
|
|
|
* * * * * * * * Following needs update to point to the PRS_LAYER & PRS_STAGE tables as required.
|
|
* * * * * * * * It's the required part that needs sorted out JCH 1/28/2014
|
|
|
|
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' ), 'MD3' )
|
|
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 UNIT_MICROMETER$ with 'um' in PrintThickTargets
|
|
swap UNIT_OHM_CM$ with 'ohm.cm' in PrintThickTargets
|
|
swap UNIT_OHM_PER_SQ$ with 'ohm/sq' in PrintThickTargets
|
|
swap UNIT_A$ with 'A' in PrintThickTargets
|
|
|
|
swap UNIT_MICROMETER$ with 'um' in PrintResTargets
|
|
swap UNIT_OHM_CM$ with 'ohm.cm' in PrintResTargets
|
|
swap UNIT_OHM_PER_SQ$ with 'ohm/sq' in PrintResTargets
|
|
swap UNIT_A$ with 'A' in PrintResTargets
|
|
|
|
WMOBoxCnt = COUNT( WMOutKeys, @VM ) + (WMOutKeys NE '')
|
|
|
|
GOSUB PrintCleanRoomLabels
|
|
GOSUB PrintWOLabels ;* Activated WO label printing again -dkk 12/3/14
|
|
|
|
Void = UTILITY( 'CURSOR', 'A' )
|
|
|
|
end
|
|
|
|
GoSub EndPrint
|
|
|
|
return
|
|
|
|
|
|
* * * * * *
|
|
EndPrint:
|
|
* * * * * *
|
|
|
|
If Environment_Services('GetLabelPrintMethod') _EQC 'OIPI' then
|
|
stat = Set_Printer("TERM")
|
|
end else
|
|
stat = Direct_Print('STOP')
|
|
end
|
|
|
|
RETURN
|
|
|
|
|
|
************ Local Subroutines ************
|
|
|
|
* * * * * * *
|
|
PrintCleanRoomLabels:
|
|
* * * * * * *
|
|
|
|
FOR I = 1 TO WMOBoxCnt
|
|
|
|
WMOutKey = WMOutKeys<1,I>
|
|
|
|
MakeupBox = XLATE('WM_OUT',WMOutKey,WM_OUT_MAKEUP_BOX$ ,'X')
|
|
|
|
PrintWMOutKey = WMOutKey
|
|
CONVERT '*' TO '.' IN PrintWMOutKey
|
|
|
|
CassNo = FIELD(WMOutKey,'*',3)
|
|
|
|
LotNo = 'Multiple'
|
|
WfrQty = XLATE('WM_OUT',WMOutKey,'WFRS_SCHED','X')
|
|
|
|
SubPartNo = WORec<WO_LOG_ORD_SUB_PART_NO$>
|
|
CustPartNo = WORec<WO_LOG_CUST_PART_NO$>
|
|
EpiPartNo = WORec<WO_LOG_EPI_PART_NO$>
|
|
CustPartDesc = XLATE('EPI_PART',EpiPartNo,EPI_PART_EPI_PART_DESC$,'X')
|
|
PartNo = CustPartNo ;* Temporary for 4x2 to 4x4 conversion
|
|
PartDesc = CustPartDesc ;* Temporary for 4x2 to 4x4 conversion
|
|
SubVendCode = WORec<WO_LOG_EXP_VEND_CD$>
|
|
Vendor = XLATE('SEMI_VEND_CODE', SubVendCode, 'EPI_VEND_CD', 'X')
|
|
|
|
SuppCd = TRIM(SubPartNo[-1,'B-'])
|
|
IF LEN(SuppCd) NE '2' THEN SuppCd =''
|
|
|
|
GOSUB PrintLabel
|
|
|
|
NEXT I
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
PrintLabel:
|
|
* * * * * * *
|
|
Str = ''
|
|
For cnt = 1 to 2
|
|
***** Start of label ZPL
|
|
Str := '^XA'
|
|
|
|
***** Label setup
|
|
Str := '^LH0,0'
|
|
Str := '^PR2' ;* Print speed 2 inches per second
|
|
Str := '^LL406' ;* Label length 203 dpi
|
|
Str := '^PW900' ;* Print width 900 dpi
|
|
Str := '^MD2' ;* Media darkness
|
|
Str := '^MMT':CRLF$ ;* Media mode t=tear off mode
|
|
//Str := '^PQ2' ;* Print 2 labels for each pass through here
|
|
|
|
***** Border
|
|
Str := '^FO10,5^GB795,398,3,B^FS':CRLF$
|
|
|
|
****** 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':PrintWMOutKey:'^FS':CRLF$
|
|
Str := '^BY2,2.0':CRLF$
|
|
Str := '^FO300,58^B3,,37,N^FD':'O':PrintWMOutKey:'^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^A0,,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$
|
|
Str := '^FO510,155^A0,20^FD':SuppCd:'^FS':CRLF$
|
|
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^A050,30^FD* * * M a k e u p B o x * * *^FS':CRLF$
|
|
END ELSE
|
|
Str := '^FO410,190^AC,18^FDReact Type:^FS':CRLF$
|
|
Str := '^FO560,190^A0,20^FDEpiPro^FS':CRLF$
|
|
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$
|
|
|
|
|
|
****** Ninth, Tenth and Eleventh 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:'^A040,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:'^A040,20^FD':PrintResTargets<1,M>:'^FS':CRLF$
|
|
NEXT M
|
|
|
|
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':PrintWMOutKey:'|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 := '^FO275,375^AC,18^FDSpec Type:^FS':CRLF$
|
|
Str := '^FO400,375^A0,25^FD':SpecType:'^FS':CRLF$
|
|
Str:= '^FO480,375^AC,18^FDBag:^FS':CRLF$
|
|
Str:= '^FO530,375^A0,20^FD':ShipBagReq:'^FS':CRLF$
|
|
|
|
***** End of Label
|
|
Str:= '^XZ'
|
|
Next
|
|
|
|
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 := '^LH0,0'
|
|
Str := '^PR2' ;* Print speed 2 inches per second
|
|
Str := '^LL325' ;* Label length in dots
|
|
Str := '^MD2' ;* 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
|
|
|