您的位置:首页 > 编程语言 > VB

针对VB打印的一些常用设置

2010-06-07 17:06 435 查看
我们平时在做票据打印的时候常常遇到如何设置纸张,默认大小,边距等问题。拼命的到处提问,搜索,以下代码就可以帮助你解决部分问题。

1、调用API函数设置打印的方向

'Constants used in the DevMode structure
Private Const CCHDEVICENAME = 32
Private Const CCHFORMNAME = 32

'Constants for NT security
Private Const STANDARD_RIGHTS_REQUIRED = &HF0000
Private Const PRINTER_ACCESS_ADMINISTER = &H4
Private Const PRINTER_ACCESS_USE = &H8
Private Const PRINTER_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or PRINTER_ACCESS_ADMINISTER Or PRINTER_ACCESS_USE)

'Constants used to make changes to the values contained in the DevMode
Private Const DM_MODIFY = 8
Private Const DM_IN_BUFFER = DM_MODIFY
Private Const DM_COPY = 2
Private Const DM_OUT_BUFFER = DM_COPY
Private Const DM_DUPLEX = &H1000&
Private Const DMDUP_SIMPLEX = 1
Private Const DMDUP_VERTICAL = 2
Private Const DMDUP_HORIZONTAL = 3
Private Const DM_ORIENTATION = &H1&
Private PageDirection As Integer
'------USER DEFINED TYPES

'The DevMode structure contains printing parameters.
'Note that this only represents the PUBLIC portion of the DevMode.
' The full DevMode also contains a variable length PRIVATE section
' which varies in length and content between printer drivers.
'NEVER use this User Defined Type directly with any API call.
' Always combine it into a FULL DevMode structure and then send the
' full DevMode to the API call.
Private Type DEVMODE
dmDeviceName As String * CCHDEVICENAME
dmSpecVersion As Integer
dmDriverVersion As Integer
dmSize As Integer
dmDriverExtra As Integer
dmFields As Long
dmOrientation As Integer
dmPaperSize As Integer
dmPaperLength As Integer
dmPaperWidth As Integer
dmScale As Integer
dmCopies As Integer
dmDefaultSource As Integer
dmPrintQuality As Integer
dmColor As Integer
dmDuplex As Integer
dmYResolution As Integer
dmTTOption As Integer
dmCollate As Integer
dmFormName As String * CCHFORMNAME
dmLogPixels As Integer
dmBitsPerPel As Long
dmPelsWidth As Long
dmPelsHeight As Long
dmDisplayFlags As Long
dmDisplayFrequency As Long
dmICMMethod As Long ' // Windows 95 only
dmICMIntent As Long ' // Windows 95 only
dmMediaType As Long ' // Windows 95 only
dmDitherType As Long ' // Windows 95 only
dmReserved1 As Long ' // Windows 95 only
dmReserved2 As Long ' // Windows 95 only
End Type

Private Type PRINTER_DEFAULTS
'Note:
' The definition of Printer_Defaults in the VB5 API viewer is incorrect.
' Below, pDevMode has been corrected to LONG.
pDatatype As String
pDevMode As Long
DesiredAccess As Long
End Type

'------DECLARATIONS

Private Declare Function OpenPrinter Lib "winspool.drv" Alias "OpenPrinterA" (ByVal pPrinterName As String, phPrinter As Long, pDefault As PRINTER_DEFAULTS) As Long
Private Declare Function SetPrinter Lib "winspool.drv" Alias "SetPrinterA" (ByVal hPrinter As Long, ByVal Level As Long, pPrinter As Any, ByVal Command As Long) As Long
Private Declare Function GetPrinter Lib "winspool.drv" Alias "GetPrinterA" (ByVal hPrinter As Long, ByVal Level As Long, pPrinter As Any, ByVal cbBuf As Long, pcbNeeded As Long) As Long
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (hpvDest As Any, hpvSource As Any, ByVal cbCopy As Long)
Private Declare Function ClosePrinter Lib "winspool.drv" (ByVal hPrinter As Long) As Long

'The following is an unusual declaration of DocumentProperties:
' pDevModeOutput and pDevModeInput are usually declared ByRef. They are declared
' ByVal in this program because we're using a Printer_Info_2 structure.
' The pi2 structure contains a variable of type LONG which contains the address
' of the DevMode structure (this is called a pointer). This LONG variable must
' be passed ByVal.
' Normally this function is called with a BYTE ARRAY which contains the DevMode
' structure and the Byte Array is passed ByRef.
Private Declare Function DocumentProperties Lib "winspool.drv" Alias "DocumentPropertiesA" (ByVal hwnd As Long, ByVal hPrinter As Long, ByVal pDeviceName As String, ByVal pDevModeOutput As Any, ByVal pDevModeInput As Any, ByVal fMode As Long) As Long

Private Sub SetOrientation(NewSetting As Long, chng As Integer, ByVal frm As Form)
Dim PrinterHandle As Long
Dim PrinterName As String
Dim pd As PRINTER_DEFAULTS
Dim MyDevMode As DEVMODE
Dim Result As Long
Dim Needed As Long
Dim pFullDevMode As Long
Dim pi2_buffer() As Long 'This is a block of memory for the Printer_Info_2 structure
'If you need to use the Printer_Info_2 User Defined Type, the
' definition of Printer_Info_2 in the API viewer is incorrect.
' pDevMode and pSecurityDescriptor should be defined As Long.

PrinterName = Printer.DeviceName
If PrinterName = "" Then
Exit Sub
End If

pd.pDatatype = vbNullString
pd.pDevMode = 0&
'Printer_Access_All is required for NT security
pd.DesiredAccess = PRINTER_ALL_ACCESS

Result = OpenPrinter(PrinterName, PrinterHandle, pd)

'The first call to GetPrinter gets the size, in bytes, of the buffer needed.
'This value is divided by 4 since each element of pi2_buffer is a long.
Result = GetPrinter(PrinterHandle, 2, ByVal 0&, 0, Needed)
ReDim pi2_buffer((Needed \ 4))
Result = GetPrinter(PrinterHandle, 2, pi2_buffer(0), Needed, Needed)

'The seventh element of pi2_buffer is a Pointer to a block of memory
' which contains the full DevMode (including the PRIVATE portion).
pFullDevMode = pi2_buffer(7)

'Copy the Public portion of FullDevMode into our DevMode structure
Call CopyMemory(MyDevMode, ByVal pFullDevMode, Len(MyDevMode))

'Make desired changes
MyDevMode.dmDuplex = NewSetting
MyDevMode.dmFields = DM_DUPLEX Or DM_ORIENTATION
MyDevMode.dmOrientation = chng

'Copy our DevMode structure back into FullDevMode
Call CopyMemory(ByVal pFullDevMode, MyDevMode, Len(MyDevMode))

'Copy our changes to "the PUBLIC portion of the DevMode" into "the PRIVATE portion of the DevMode"
Result = DocumentProperties(frm.hwnd, PrinterHandle, PrinterName, ByVal pFullDevMode, ByVal pFullDevMode, DM_IN_BUFFER Or DM_OUT_BUFFER)

'Update the printer's default properties (to verify, go to the Printer folder
' and check the properties for the printer)
Result = SetPrinter(PrinterHandle, 2, pi2_buffer(0), 0&)

Call ClosePrinter(PrinterHandle)

'Note: Once "Set Printer = " is executed, anywhere in the code, after that point
' changes made with SetPrinter will ONLY affect the system-wide printer --
' -- the changes will NOT affect the VB printer object.
' Therefore, it may be necessary to reset the printer object's parameters to
' those chosen in the devmode.
Dim p As Printer
For Each p In Printers
If p.DeviceName = PrinterName Then
Set Printer = p
Exit For
End If
Next p
Printer.Duplex = MyDevMode.dmDuplex
End Sub

Public Sub ChngPrinterOrientationLandscape(ByVal frm As Form)
PageDirection = 2 '2 为纵打
Call SetOrientation(DMDUP_SIMPLEX, PageDirection, frm)
End Sub

Public Sub ResetPrinterOrientation(ByVal frm As Form)

If PageDirection = 1 Then
PageDirection = 2
Else
PageDirection = 1
End If
Call SetOrientation(DMDUP_SIMPLEX, PageDirection, frm)
End Sub

Public Sub ChngPrinterOrientationPortrait(ByVal frm As Form)

PageDirection = 1 '1 为横打
Call SetOrientation(DMDUP_SIMPLEX, PageDirection, frm)
End Sub

'调用方式 from 输入你的窗体名称即可
Call ChngPrinterOrientationPortrait(from)

2、以下代码是为打印机新建一个纸张类型、但是并没有设置其为默认

Option Explicit

Public Declare Function EnumForms Lib "winspool.drv" Alias "EnumFormsA" (ByVal hPrinter As Long, ByVal Level As Long, ByRef pForm As Any, ByVal cbBuf As Long, ByRef pcbNeeded As Long, ByRef pcReturned As Long) As Long

Public Declare Function AddForm Lib "winspool.drv" Alias "AddFormA" (ByVal hPrinter As Long, ByVal Level As Long, pForm As Byte) As Long

Public Declare Function DeleteForm Lib "winspool.drv" Alias "DeleteFormA" (ByVal hPrinter As Long, ByVal pFormName As String) As Long

Public Declare Function OpenPrinter Lib "winspool.drv" Alias "OpenPrinterA" (ByVal pPrinterName As String, phPrinter As Long, ByVal pDefault As Long) As Long

Public Declare Function ClosePrinter Lib "winspool.drv" (ByVal hPrinter As Long) As Long

Public Declare Function DocumentProperties Lib "winspool.drv" Alias "DocumentPropertiesA" (ByVal hwnd As Long, ByVal hPrinter As Long, ByVal pDeviceName As String, pDevModeOutput As Any, pDevModeInput As Any, ByVal fMode As Long) As Long

Public Declare Function ResetDC Lib "gdi32" Alias "ResetDCA" (ByVal hdc As Long, lpInitData As Any) As Long

Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (hpvDest As Any, hpvSource As Any, ByVal cbCopy As Long)

Public Declare Function lstrcpy Lib "kernel32" Alias "lstrcpyA" (ByVal lpString1 As String, ByRef lpString2 As Long) As Long

' Optional functions not used in this sample, but may be useful.
Public Declare Function GetForm Lib "winspool.drv" Alias "GetFormA" (ByVal hPrinter As Long, ByVal pFormName As String, ByVal Level As Long, pForm As Byte, ByVal cbBuf As Long, pcbNeeded As Long) As Long

Public Declare Function SetForm Lib "winspool.drv" Alias "SetFormA" (ByVal hPrinter As Long, ByVal pFormName As String, ByVal Level As Long, pForm As Byte) As Long

' Constants for DEVMODE
Public Const CCHFORMNAME = 32
Public Const CCHDEVICENAME = 32
Public Const DM_FORMNAME As Long = &H10000
Public Const DM_ORIENTATION = &H1&

' Constants for PRINTER_DEFAULTS.DesiredAccess
Public Const PRINTER_ACCESS_ADMINISTER = &H4
Public Const PRINTER_ACCESS_USE = &H8
Public Const STANDARD_RIGHTS_REQUIRED = &HF0000
Public Const PRINTER_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or PRINTER_ACCESS_ADMINISTER Or PRINTER_ACCESS_USE)

' Constants for DocumentProperties() call
Public Const DM_MODIFY = 8
Public Const DM_IN_BUFFER = DM_MODIFY
Public Const DM_COPY = 2
Public Const DM_OUT_BUFFER = DM_COPY

' Custom constants for this sample's SelectForm function
Public Const FORM_NOT_SELECTED = 0
Public Const FORM_SELECTED = 1
Public Const FORM_ADDED = 2

Public Type RECTL
Left As Long
top As Long
Right As Long
Bottom As Long
End Type

Public Type SIZEL
cx As Long
cy As Long
End Type

Public Type SECURITY_DESCRIPTOR
Revision As Byte
Sbz1 As Byte
Control As Long
Owner As Long
Group As Long
Sacl As Long ' ACL
Dacl As Long ' ACL
End Type

' The two definitions for FORM_INFO_1 make the coding easier.
Public Type FORM_INFO_1
Flags As Long
pName As Long ' String
Size As SIZEL
ImageableArea As RECTL
End Type

Public Type sFORM_INFO_1
Flags As Long
pName As String
Size As SIZEL
ImageableArea As RECTL
End Type

Public Type DEVMODE
dmDeviceName As String * CCHDEVICENAME
dmSpecVersion As Integer
dmDriverVersion As Integer
dmSize As Integer
dmDriverExtra As Integer
dmFields As Long
dmOrientation As Integer
dmPaperSize As Integer
dmPaperLength As Integer
dmPaperWidth As Integer
dmScale As Integer
dmCopies As Integer
dmDefaultSource As Integer
dmPrintQuality As Integer
dmColor As Integer
dmDuplex As Integer
dmYResolution As Integer
dmTTOption As Integer
dmCollate As Integer
dmFormName As String * CCHFORMNAME
dmUnusedPadding As Integer
dmBitsPerPel As Long
dmPelsWidth As Long
dmPelsHeight As Long
dmDisplayFlags As Long
dmDisplayFrequency As Long
End Type

Public Type PRINTER_DEFAULTS
pDatatype As String
pDevMode As Long ' DEVMODE
DesiredAccess As Long
End Type

Public Type PRINTER_INFO_2
pServerName As String
pPrinterName As String
pShareName As String
pPortName As String
pDriverName As String
pComment As String
pLocation As String
pDevMode As DEVMODE
pSepFile As String
pPrintProcessor As String
pDatatype As String
pParameters As String
pSecurityDescriptor As SECURITY_DESCRIPTOR
Attributes As Long
Priority As Long
DefaultPriority As Long
StartTime As Long
UntilTime As Long
Status As Long
cJobs As Long
AveragePPM As Long
End Type

Public Function GetFormName(ByVal PrinterHandle As Long, FormSize As SIZEL, FormName As String) As Integer
Dim NumForms As Long, i As Long
Dim FI1 As FORM_INFO_1
Dim aFI1() As FORM_INFO_1 ' Working FI1 array
Dim Temp() As Byte ' Temp FI1 array
Dim FormIndex As Integer
Dim BytesNeeded As Long
Dim RetVal As Long

FormName = vbNullString
FormIndex = 0
ReDim aFI1(1)
' First call retrieves the BytesNeeded.
RetVal = EnumForms(PrinterHandle, 1, aFI1(0), 0&, BytesNeeded, NumForms)
ReDim Temp(BytesNeeded)
ReDim aFI1(BytesNeeded / Len(FI1))
' Second call actually enumerates the supported forms.
RetVal = EnumForms(PrinterHandle, 1, Temp(0), BytesNeeded, BytesNeeded, NumForms)
Call CopyMemory(aFI1(0), Temp(0), BytesNeeded)
For i = 0 To NumForms - 1
With aFI1(i)
If .Size.cx = FormSize.cx And .Size.cy = FormSize.cy Then
' Found the desired form
FormName = PtrCtoVbString(.pName)
FormIndex = i + 1
Exit For
End If
End With
Next i
GetFormName = FormIndex ' Returns non-zero when form is found.
End Function

Public Function AddNewForm(PrinterHandle As Long, FormSize As SIZEL, _
FormName As String) As String
Dim FI1 As sFORM_INFO_1
Dim aFI1() As Byte
Dim RetVal As Long

With FI1
.Flags = 0
.pName = FormName
With .Size
.cx = FormSize.cx
.cy = FormSize.cy
End With
With .ImageableArea
.Left = 0
.top = 0
.Right = FI1.Size.cx
.Bottom = FI1.Size.cy
End With
End With
ReDim aFI1(Len(FI1))
Call CopyMemory(aFI1(0), FI1, Len(FI1))
RetVal = AddForm(PrinterHandle, 1, aFI1(0))
If RetVal = 0 Then
If Err.LastDllError = 5 Then
MsgBox "You do not have permissions to add a form to " & _
Printer.DeviceName, vbExclamation, "Access Denied!"
Else
MsgBox "Error: " & Err.LastDllError, "Error Adding Form"
End If
AddNewForm = "none"
Else
AddNewForm = FI1.pName
End If
End Function

Public Function PtrCtoVbString(ByVal Add As Long) As String
Dim sTemp As String * 512, X As Long

X = lstrcpy(sTemp, ByVal Add)
If (InStr(1, sTemp, Chr(0)) = 0) Then
PtrCtoVbString = ""
Else
PtrCtoVbString = Left(sTemp, InStr(1, sTemp, Chr(0)) - 1)
End If
End Function

Public Function SelectForm(FormName As String, ByVal MyhWnd As Long) _
As Integer
Dim nSize As Long ' Size of DEVMODE
Dim pDevMode As DEVMODE
Dim PrinterHandle As Long ' Handle to printer
Dim hPrtDC As Long ' Handle to Printer DC
Dim PrinterName As String
Dim aDevMode() As Byte ' Working DEVMODE
Dim FormSize As SIZEL

PrinterName = Printer.DeviceName ' Current printer
hPrtDC = Printer.hdc ' hDC for current Printer
SelectForm = FORM_NOT_SELECTED ' Set for failure unless reset in code.

' Get a handle to the printer.
If OpenPrinter(PrinterName, PrinterHandle, 0&) Then
' Retrieve the size of the DEVMODE.
nSize = DocumentProperties(MyhWnd, PrinterHandle, PrinterName, 0&, _
0&, 0&)
' Reserve memory for the actual size of the DEVMODE.
ReDim aDevMode(1 To nSize)

' Fill the DEVMODE from the printer.
nSize = DocumentProperties(MyhWnd, PrinterHandle, PrinterName, _
aDevMode(1), 0&, DM_OUT_BUFFER)
' Copy the Public (predefined) portion of the DEVMODE.
Call CopyMemory(pDevMode, aDevMode(1), Len(pDevMode))

' If FormName is "MyCustomForm", we must make sure it exists
' before using it. Otherwise, it came from our EnumForms list,
' and we do not need to check first. Note that we could have
' passed in a Flag instead of checking for a literal name.

'这里是新建一个MyCustomForm的自定义纸张,下面是其的规格设置,看下代码即可修改
If FormName = "MyCustomForm" Then
' Use form "MyCustomForm", adding it if necessary.
' Set the desired size of the form needed.
With FormSize ' Given in thousandths of millimeters
' .cx = 240000 ' width
' .cy = 140000 ' height
.cx = 257000
.cy = 200000
End With
If GetFormName(PrinterHandle, FormSize, FormName) = 0 Then
' Form not found - Either of the next 2 lines will work.
'FormName = AddNewForm(PrinterHandle, FormSize, "MyCustomForm")
AddNewForm PrinterHandle, FormSize, "MyCustomForm"
If GetFormName(PrinterHandle, FormSize, FormName) = 0 Then
ClosePrinter (PrinterHandle)
SelectForm = FORM_NOT_SELECTED ' Selection Failed!
Exit Function
Else
SelectForm = FORM_ADDED ' Form Added, Selection succeeded!
End If
End If
End If

' Change the appropriate member in the DevMode.
' In this case, you want to change the form name.
pDevMode.dmFormName = FormName & Chr(0) ' Must be NULL terminated!
' Set the dmFields bit flag to indicate what you are changing.
pDevMode.dmFields = DM_FORMNAME

' Copy your changes back, then update DEVMODE.
Call CopyMemory(aDevMode(1), pDevMode, Len(pDevMode))
nSize = DocumentProperties(MyhWnd, PrinterHandle, PrinterName, _
aDevMode(1), aDevMode(1), DM_IN_BUFFER Or DM_OUT_BUFFER)

nSize = ResetDC(hPrtDC, aDevMode(1)) ' Reset the DEVMODE for the DC.

' Close the handle when you are finished with it.
ClosePrinter (PrinterHandle)
' Selection Succeeded! But was Form Added?
If SelectForm <> FORM_ADDED Then SelectForm = FORM_SELECTED
Else
SelectForm = FORM_NOT_SELECTED ' Selection Failed!
End If
End Function

'这个函数是找出你需要纸张类型的序号
'A4一般都是为 9 ;A3 = 8
Public Function GetFormNum(strFormName As String)

Dim NumForms As Long, i As Long
Dim FI1 As FORM_INFO_1
Dim aFI1() As FORM_INFO_1 ' Working FI1 array
Dim Temp() As Byte ' Temp FI1 array
Dim BytesNeeded As Long
Dim PrinterName As String ' Current printer
Dim PrinterHandle As Long ' Handle to printer
Dim FormItem As String ' For ListBox
Dim RetVal As Long
Dim FormSize As SIZEL ' Size of desired form

Dim PrintNum As Integer

PrinterName = Printer.DeviceName ' Current printer
If OpenPrinter(PrinterName, PrinterHandle, 0&) Then
With FormSize ' Desired page size
.cx = 257000
.cy = 200000
End With
ReDim aFI1(1)
RetVal = EnumForms(PrinterHandle, 1, aFI1(0), 0&, BytesNeeded, _
NumForms)
ReDim Temp(BytesNeeded)
ReDim aFI1(BytesNeeded / Len(FI1))
RetVal = EnumForms(PrinterHandle, 1, Temp(0), BytesNeeded, _
BytesNeeded, NumForms)
Call CopyMemory(aFI1(0), Temp(0), BytesNeeded)
For i = 0 To NumForms - 1
With aFI1(i)

If strFormName = PtrCtoVbString(.pName) Then
PrintNum = i + 1
End If

End With
Next i
ClosePrinter (PrinterHandle)

End If

GetFormNum = PrintNum

End Function

3、判断某个纸张类型是否存在

以上代码有,修改一下既可

4、默认某个纸张

Private Const CCHDEVICENAME = 32
Private Const CCHFORMNAME = 32
Private Type DEVMODE
dmDeviceName As String * CCHDEVICENAME
dmSpecVersion As Integer
dmDriverVersion As Integer
dmSize As Integer
dmDriverExtra As Integer
dmFields As Long
dmOrientation As Integer
dmPaperSize As Integer
dmPaperLength As Integer
dmPaperWidth As Integer
dmScale As Integer
dmCopies As Integer
dmDefaultSource As Integer
dmPrintQuality As Integer
dmColor As Integer
dmDuplex As Integer
dmYResolution As Integer
dmTTOption As Integer
dmCollate As Integer
dmFormName As String * CCHFORMNAME
dmUnusedPadding As Integer
dmBitsPerPel As Long
dmPelsWidth As Long
dmPelsHeight As Long
dmDisplayFlags As Long
dmDisplayFrequency As Long
End Type

Private Type PRINTER_DEFAULTS
pDatatype As String
pDevMode As DEVMODE
DesiredAccess As Long
End Type

Private Declare Function OpenPrinter Lib "winspool.drv" Alias "OpenPrinterA" (ByVal pPrinterName As String, phPrinter As Long, pDefault As PRINTER_DEFAULTS) As Long
Private Declare Function GetPrinter Lib "winspool.drv" Alias "GetPrinterA" (ByVal hPrinter As Long, ByVal Level As Long, buffer As Any, ByVal pbSize As Long, pbSizeNeeded As Long) As Long
Private Declare Function ClosePrinter Lib "winspool.drv" (ByVal hPrinter As Long) As Long
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Private Declare Function SetPrinter Lib "winspool.drv" Alias "SetPrinterA" (ByVal hPrinter As Long, ByVal Level As Long, pPrinter As Any, ByVal Command As Long) As Long

Public Sub SetPrintDefault(ByVal FormName As String, PaperSize As Integer)
Dim SizeNeeded As Long, buffer() As Long
Dim pDef As PRINTER_DEFAULTS
Dim X As DEVMODE
Dim lret As Long
Dim mhPrinter As Long
Dim str As String

pDef.DesiredAccess = PRINTER_ALL_ACCESS
lret = OpenPrinter(Printer.DeviceName, mhPrinter, pDef)

ReDim Preserve buffer(0 To 0)

lret = GetPrinter(mhPrinter, 9, buffer(0), 0, SizeNeeded)

ReDim Preserve buffer(0 To (SizeNeeded / 4) + 3) As Long

lret = GetPrinter(mhPrinter, 9, buffer(0), UBound(buffer) * 4, SizeNeeded)

CopyMemory X, ByVal buffer(0), Len(X)
X.dmFields = &H10000 Or 2
X.dmFormName = FormName & vbNullChar
X.dmPaperSize = PaperSize
CopyMemory ByVal buffer(0), X, Len(X)

lret = SetPrinter(mhPrinter, 9, buffer(0), 0)

ClosePrinter mhPrinter

End Sub

'调用------------------
'GetFormNum(FormName) 这个是纸张的序号
SetPrintDefault "MyCustomForm", GetFormNum(FormName)

5、如何删除一个纸张类型

'函数名:DeleteCustomPrintSetting(FormName As String)
'
'参 数:FormName 选择纸张类型的名称
'
'功 能:定义纸张的类型
Private Sub DeleteCustomPrintSetting(FormName As String)

Dim RetVal As Long
Dim PrinterHandle As Long ' Handle to printer
Dim PrinterName As String
Dim Continue As Long

' Delete form that is selected in ListBox.
PrinterName = Printer.DeviceName ' Current printer
If OpenPrinter(PrinterName, PrinterHandle, 0&) Then

On Error GoTo ListBoxERR ' Trap for no selection.
RetVal = DeleteForm(PrinterHandle, FormName & Chr(0))
If RetVal <> 0 Then ' DeleteForm succeeded.
' MsgBox FormName & " deleted!", vbInformation, "Success!"
Else
' MsgBox FormName & " not deleted!" & vbCrLf & vbCrLf & _
"Error code: " & Err.LastDllError, vbInformation, "Failure!"
End If
ClosePrinter (PrinterHandle)
End If

Exit Sub
ListBoxERR:
MsgBox "Select a printer from the ListBox before using this option.", _
vbExclamation
ClosePrinter (PrinterHandle)

End Sub

以上为个人的总结,部分代码摘录于网上,本人只用VB两个星期,有错误指出敬请原谅。
在98的打印设置,在之前的一篇文章有写,可以去查看一下作为参考。

另外给点个人建议,设置纸张大小的时候,最好比原纸张大一点,由于每个打印机对于这些设置都有不同的变化,打印纸张必须在打印机的打印大小的允许范围内,否则就会出错,对于网络打印机是无法新建自定义纸张类型(没测试过)

8888 希望大家别碰上我遇到那样的问题。就是在一台打印机上做出了自己的纸张类型,但是打印不完全,其次在其他打印机上是正常的,,晕倒~~~~~
内容来自用户分享和网络整理,不保证内容的准确性,如有侵权内容,可联系管理员处理 点击这里给我发消息
标签: