Const STANDARD_RIGHTS_REQUIRED = 0xF0000
Const PRINTER_ACCESS_USE = 0x00008
Const PRINTER_NORMAL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or PRINTER_ACCESS_USE)
In my testing, this worked fine on a local printer but when trying to
change the settings on a network printer I was getting “access denied”
errors.
In short, the problem was I didn’t have full administrative access to
the network printers in question; I could only change local print
preferences. To accomodate this, a lower access level needs to be
passed to the function call. Here’s the full range of available levels:
'Access levels for interacting with a device
Const DELETE = &H10000
Const READ_CONTROL = &H20000 ' Read device information
Const WRITE_DAC = &H40000 ' Write Device Access Control info
Const WRITE_OWNER = &H80000 ' Change the object owner
' Combining these for full access to the device
Const STANDARD_RIGHTS_REQUIRED = &HF0000
'Access rights to print servers
Const SERVER_ACCESS_ADMINISTER = &H1
Const SERVER_ACCESS_ENUMERATE = &H2
'Access rights for printers
Const PRINTER_ACCESS_ADMINISTER = &H4
Const PRINTER_ACCESS_USE = &H8
For me the following seemed to work:
' Access which allows you to set duplex on or off
Const PRINTER_NORMAL_ACCESS = (READ_CONTROL Or PRINTER_ACCESS_USE)
This would be useful to know when making calls to other API functions
where the security levels need to be taken into account, in a network
Here’s the full code,
Option Explicit
Private Type PRINTER_DEFAULTS
pDatatype As Long
pDevmode As Long
DesiredAccess As Long
End Type
Private Type PRINTER_INFO_2
pServerName As Long
pPrinterName As Long
pShareName As Long
pPortName As Long
pDriverName As Long
pComment As Long
pLocation As Long
pDevmode As Long ' Pointer to DEVMODE
pSepFile As Long
pPrintProcessor As Long
pDatatype As Long
pParameters As Long
pSecurityDescriptor As Long ' Pointer to 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
Private Type DEVMODE
dmDeviceName As String * 32
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 * 32
dmUnusedPadding As Integer
dmBitsPerPel As Integer
dmPelsWidth As Long
dmPelsHeight As Long
dmDisplayFlags As Long
dmDisplayFrequency As Long
dmICMMethod As Long
dmICMIntent As Long
dmMediaType As Long
dmDitherType As Long
dmReserved1 As Long
dmReserved2 As Long
End Type
Private Const DM_ORIENTATION = &H1
Private Const DM_PAPERSIZE = &H2
Private Const DM_PAPERLENGTH = &H4
Private Const DM_PAPERWIDTH = &H8
Private Const DM_DEFAULTSOURCE = &H200
Private Const DM_PRINTQUALITY = &H400
Private Const DM_COLOR = &H800
Private Const DM_DUPLEX = &H1000
Private Const DM_IN_BUFFER = 8
Private Const DM_OUT_BUFFER = 2
Private Const DELETE = &H10000
Private Const READ_CONTROL = &H20000 ' Allowed to read device information
Private Const WRITE_DAC = &H40000 ' Allowed to write device access control info
Private Const WRITE_OWNER = &H80000 ' Allowed to change the object owner
' Combining these for full access to a device (DELETE + READ_CONTROL + WRITE_DAC + WRITE_OWNER):
Private Const STANDARD_RIGHTS_REQUIRED = &HF0000
Private Const SERVER_ACCESS_ADMINISTER = &H1 ' Access rights to administer print servers.
Private Const SERVER_ACCESS_ENUMERATE = &H2 ' Access rights to enumerate print servers.
Private Const PRINTER_ACCESS_ADMINISTER = &H4 ' Access rights for printers to perform administrative tasks.
Private Const PRINTER_ACCESS_USE = &H8 ' Access rights for printers for general use (printing, querying).
' Access which allows you to set duplex on or off
Private Const PRINTER_NORMAL_ACCESS = (READ_CONTROL Or PRINTER_ACCESS_USE)
Private Const PRINTER_ENUM_CONNECTIONS = &H4
Private Const PRINTER_ENUM_LOCAL = &H2
Private Declare Function ClosePrinter Lib "winspool.drv" _
(ByVal hPrinter As Long) As Long
Private Declare Function DocumentProperties Lib "winspool.drv" _
Alias "DocumentPropertiesA" (ByVal hwnd As Long, _
ByVal hPrinter As Long, ByVal pDeviceName As String, _
ByVal pDevModeOutput As Long, ByVal pDevModeInput As Long, _
ByVal fMode As Long) As Long
Private Declare Function GetPrinter Lib "winspool.drv" Alias _
"GetPrinterA" (ByVal hPrinter As Long, ByVal Level As Long, _
pPrinter As Byte, ByVal cbBuf As Long, pcbNeeded As Long) As Long
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 Byte, ByVal Command As Long) As Long
Private Declare Function EnumPrinters Lib "winspool.drv" _
Alias "EnumPrintersA" _
(ByVal flags As Long, ByVal name As String, ByVal Level As Long, _
pPrinterEnum As Long, ByVal cdBuf As Long, pcbNeeded As Long, _
pcReturned As Long) As Long
Private Declare Function PtrToStr Lib "kernel32" Alias "lstrcpyA" _
(ByVal RetVal As String, ByVal Ptr As Long) As Long
Private Declare Function StrLen Lib "kernel32" Alias "lstrlenA" _
(ByVal Ptr As Long) As Long
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _
(pDest As Any, pSource As Any, ByVal cbLength As Long)
Private Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Private Declare Function DeviceCapabilities Lib "winspool.drv" _
Alias "DeviceCapabilitiesA" (ByVal lpDeviceName As String, _
ByVal lpPort As String, ByVal iIndex As Long, lpOutput As Any, _
ByVal dev As Long) As Long
Public Sub SetColorMode(ByVal sPrinterName As String, iColorMode As Long)
SetPrinterProperty sPrinterName, DM_COLOR, iColorMode
End Sub
Public Function GetColorMode(ByVal sPrinterName As String) As Long
GetColorMode = GetPrinterProperty(sPrinterName, DM_COLOR)
End Function
Public Sub SetDuplex(ByVal sPrinterName As String, iDuplex As Long)
SetPrinterProperty sPrinterName, DM_DUPLEX, iDuplex
End Sub
Public Function GetDuplex(ByVal sPrinterName As String) As Long
GetDuplex = GetPrinterProperty(sPrinterName, DM_DUPLEX)
End Function
Public Sub SetPrintQuality(ByVal sPrinterName As String, iQuality As Long)
SetPrinterProperty sPrinterName, DM_PRINTQUALITY, iQuality
End Sub
Public Function GetPrintQuality(ByVal sPrinterName As String) As Long
GetPrintQuality = GetPrinterProperty(sPrinterName, DM_PRINTQUALITY)
End Function
Private Function SetPrinterProperty(ByVal sPrinterName As String, ByVal iPropertyType As Long, _
ByVal iPropertyValue As Long) As Boolean
'Code adapted from Microsoft KB article Q230743
Dim hPrinter As Long 'handle for the current printer
Dim pd As PRINTER_DEFAULTS
Dim pinfo As PRINTER_INFO_2
Dim dm As DEVMODE
Dim yDevModeData() As Byte 'Byte array to hold contents
'of DEVMODE structure
Dim yPInfoMemory() As Byte 'Byte array to hold contents
'of PRINTER_INFO_2 structure
Dim iBytesNeeded As Long
Dim iRet As Long
Dim iJunk As Long
Dim iCount As Long
On Error GoTo cleanup
pd.DesiredAccess = PRINTER_NORMAL_ACCESS
iRet = OpenPrinter(sPrinterName, hPrinter, pd)
If (iRet = 0) Or (hPrinter = 0) Then
'Can't access current printer. Bail out doing nothing
Exit Function
End If
'Get the size of the DEVMODE structure to be loaded
iRet = DocumentProperties(0, hPrinter, sPrinterName, 0, 0, 0)
If (iRet < style="color: rgb(0, 0, 128);">Then
'Can't access printer properties.
GoTo cleanup
End If
'Make sure the byte array is large enough
'Some printer drivers lie about the size of the DEVMODE structure they
'return, so an extra 100 bytes is provided just in case!
ReDim yDevModeData(0 To iRet + 100) As Byte
'Load the byte array
iRet = DocumentProperties(0, hPrinter, sPrinterName, _
VarPtr(yDevModeData(0)), 0, DM_OUT_BUFFER)
If (iRet < style="color: rgb(0, 0, 128);">Then
GoTo cleanup
End If
'Copy the byte array into a structure so it can be manipulated
Call CopyMemory(dm, yDevModeData(0), Len(dm))
If dm.dmFields And iPropertyType = 0 Then
'Wanted property not available. Bail out.
GoTo cleanup
End If
'Set the property to the appropriate value
Select Case iPropertyType
Case DM_ORIENTATION
dm.dmOrientation = iPropertyValue
Case DM_PAPERSIZE
dm.dmPaperSize = iPropertyValue
Case DM_PAPERLENGTH
dm.dmPaperLength = iPropertyValue
Case DM_PAPERWIDTH
dm.dmPaperWidth = iPropertyValue
Case DM_DEFAULTSOURCE
dm.dmDefaultSource = iPropertyValue
Case DM_PRINTQUALITY
dm.dmPrintQuality = iPropertyValue
Case DM_COLOR
dm.dmColor = iPropertyValue
Case DM_DUPLEX
dm.dmDuplex = iPropertyValue
End Select
'Load the structure back into the byte array
Call CopyMemory(yDevModeData(0), dm, Len(dm))
'Tell the printer about the new property
iRet = DocumentProperties(0, hPrinter, sPrinterName, _
VarPtr(yDevModeData(0)), VarPtr(yDevModeData(0)), _
DM_IN_BUFFER Or DM_OUT_BUFFER)
If (iRet < style="color: rgb(0, 0, 128);">Then
GoTo cleanup
End If
'The code above *ought* to be sufficient to set the property
'correctly. Unfortunately some brands of Postscript printer don't
'seem to respond correctly. The following code is used to make
'sure they also respond correctly.
Call GetPrinter(hPrinter, 2, 0, 0, iBytesNeeded)
If (iBytesNeeded = 0) Then
'Couldn't access shared printer settings
GoTo cleanup
End If
'Set byte array large enough for PRINTER_INFO_2 structure
ReDim yPInfoMemory(0 To iBytesNeeded + 100) As Byte
'Load the PRINTER_INFO_2 structure into byte array
iRet = GetPrinter(hPrinter, 2, yPInfoMemory(0), iBytesNeeded, iJunk)
If (iRet = 0) Then
'Couldn't access shared printer settings
GoTo cleanup
End If
'Copy byte array into the structured type
Call CopyMemory(pinfo, yPInfoMemory(0), Len(pinfo))
'Load the DEVMODE structure with byte array containing
'the new property value
pinfo.pDevmode = VarPtr(yDevModeData(0))
'Set security descriptor to null
pinfo.pSecurityDescriptor = 0
'Copy the PRINTER_INFO_2 structure back into byte array
Call CopyMemory(yPInfoMemory(0), pinfo, Len(pinfo))
'Send the new details to the printer
iRet = SetPrinter(hPrinter, 2, yPInfoMemory(0), 0)
'Indicate whether it all worked or not!
SetPrinterProperty = CBool(iRet)
cleanup:
'Release the printer handle
If (hPrinter <> 0) Then Call ClosePrinter(hPrinter)
'Flush the message queue. If you don't do this,
'you can get page fault errors when you try to
'print a document immediately after setting a printer property.
For iCount = 1 To 20
DoEvents
Next iCount
End Function
Private Function GetPrinterProperty(ByVal sPrinterName As String, ByVal iPropertyType As Long) As Long
'Code adapted from Microsoft KB article Q230743
Dim hPrinter As Long
Dim pd As PRINTER_DEFAULTS
Dim dm As DEVMODE
Dim yDevModeData() As Byte
Dim iRet As Long
On Error GoTo cleanup
pd.DesiredAccess = PRINTER_NORMAL_ACCESS
'Get the printer handle
iRet = OpenPrinter(sPrinterName, hPrinter, pd)
If (iRet = 0) Or (hPrinter = 0) Then
'Couldn't access the printer
Exit Function
End If
'Find out how many bytes needed for the printer properties
iRet = DocumentProperties(0, hPrinter, sPrinterName, 0, 0, 0)
If (iRet < style="color: rgb(0, 0, 128);">Then
'Couldn't access printer properties
GoTo cleanup
End If
'Make sure the byte array is large enough, including the
'100 bytes extra in case the printer driver is lying.
ReDim yDevModeData(0 To iRet + 100) As Byte
'Load the printer properties into the byte array
iRet = DocumentProperties(0, hPrinter, sPrinterName, _
VarPtr(yDevModeData(0)), 0, DM_OUT_BUFFER)
If (iRet < style="color: rgb(0, 0, 128);">Then
'Couldn't access printer properties
GoTo cleanup
End If
'Copy the byte array to the DEVMODE structure
Call CopyMemory(dm, yDevModeData(0), Len(dm))
If Not dm.dmFields And iPropertyType = 0 Then
'Requested property not available on this printer.
GoTo cleanup
End If
'Get the value of the requested property
Select Case iPropertyType
Case DM_ORIENTATION
GetPrinterProperty = dm.dmOrientation
Case DM_PAPERSIZE
GetPrinterProperty = dm.dmPaperSize
Case DM_PAPERLENGTH
GetPrinterProperty = dm.dmPaperLength
Case DM_PAPERWIDTH
GetPrinterProperty = dm.dmPaperWidth
Case DM_DEFAULTSOURCE
GetPrinterProperty = dm.dmDefaultSource
Case DM_PRINTQUALITY
GetPrinterProperty = dm.dmPrintQuality
Case DM_COLOR
GetPrinterProperty = dm.dmColor
Case DM_DUPLEX
GetPrinterProperty = dm.dmDuplex
End Select
cleanup:
'Release the printer handle
If (hPrinter <> 0) Then Call ClosePrinter(hPrinter)
End Function
environment.
Thursday, March 26, 2009
Changing Printer settings using the Windows API
PRINTER_INFO_2 samples
My Display Printer_Info_2 data:
'constants for Status member of PRINTER_INFO_2
Public Const PRINTER_STATUS_PAUSED = &H1 '1
Public Const PRINTER_STATUS_ERROR = &H2 '2
Public Const PRINTER_STATUS_PENDING_DELETION = &H4 '4
Public Const PRINTER_STATUS_PAPER_JAM = &H8 '8
Public Const PRINTER_STATUS_PAPER_OUT = &H10 '16
Public Const PRINTER_STATUS_MANUAL_FEED = &H20 '32
Public Const PRINTER_STATUS_PAPER_PROBLEM = &H40 '64
Public Const PRINTER_STATUS_OFFLINE = &H80 '128
Public Const PRINTER_STATUS_IO_ACTIVE = &H100 '256
Public Const PRINTER_STATUS_BUSY = &H200 '512
Public Const PRINTER_STATUS_PRINTING = &H400 '1024
Public Const PRINTER_STATUS_OUTPUT_BIN_FULL = &H800 '2048
Public Const PRINTER_STATUS_NOT_AVAILABLE = &H1000 '4096
Public Const PRINTER_STATUS_WAITING = &H2000 '8192
Public Const PRINTER_STATUS_PROCESSING = &H4000 '16384
Public Const PRINTER_STATUS_INITIALIZING = &H8000 '32768
Public Const PRINTER_STATUS_WARMING_UP = &H10000 '65536
Public Const PRINTER_STATUS_TONER_LOW = &H20000 '131072
Public Const PRINTER_STATUS_NO_TONER = &H40000 '262144
Public Const PRINTER_STATUS_PAGE_PUNT = &H80000 '524288
Public Const PRINTER_STATUS_USER_INTERVENTION = &H100000 '1048576
Public Const PRINTER_STATUS_OUT_OF_MEMORY = &H200000 '2097152
Public Const PRINTER_STATUS_DOOR_OPEN = &H400000 '4194304
'access-control lists type for SECURITY_DESCRIPTOR
Type ACL
AclRevision As Byte
Sbz1 As Byte
AclSize As Integer
AceCount As Integer
Sbz2 As Integer
End Type
'type for PRINTER_INFO_2
Type SECURITY_DESCRIPTOR
Revision As Byte
Sbz1 As Byte
Control As Long
Owner As Long 'security identifier (sid)
Group As Long 'security identifier (sid) primary group
Sacl As ACL 'system acl (access-control list)
Dacl As ACL 'discretionary acl (access-control list)
End Type
'constants form DEVMODE structure
Public Const CCHDEVICENAME = 32
Public Const CCHFORMNAME = 32
'type for PRINTER_INFO_2
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 Integer
dmPelsWidth As Long
dmPelsHeight As Long
dmDisplayFlags As Long
dmDisplayFrequency As Long
End Type
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
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
Declare Function lstrcpy Lib "Kernel32" Alias "lstrcpyA" _
(ByVal lpString1 As String, ByVal lpString2 As Any) As Long
Private Declare Function GlobalLock Lib "Kernel32" (ByVal hMem As Long) As
Long
Private Declare Function GlobalUnlock Lib "Kernel32" (ByVal hMem As Long)
As Long
Private Declare Sub CopyMemory Lib "Kernel32" Alias "RtlMoveMemory" _
(hpvDest As Any, hpvSource As Any, ByVal cbCopy As Long)
'**************************************************************************
******
' NAME: sStringTrimNull
' NOTES: Find the first vbNullChar in a string, and return
' : everything prior to that character. Extremely
' : useful when combined with the Windows API function calls.
' : From "VBA Developer's Handbook"
' : by Ken Getz and Mike Gilbert
' : Copyright 1997; Sybex, Inc. All rights reserved.
' PARAM: strValue : string to trim
' RETURN: trimmed string
' DATE: 7/17/97 : copied from CD
'**************************************************************************
******
Private Function sStringTrimNull(ByVal strValue As String) As String
Dim intPos As Integer
Dim RetVal As String
intPos = InStr(strValue, vbNullChar)
Select Case intPos
Case 0
' Not found at all, so just
' return the original value.
RetVal = strValue
Case 1
' Found at the first position, so return
' an empty string.
RetVal = ""
Case Is > 1
' Found in the string, so return the portion
' up to the null character.
RetVal = Left$(strValue, intPos - 1)
End Select
sStringTrimNull = RetVal
End Function
'**************************************************************************
' NAME: PtrCtoVbString
' NOTES: Converts a pointer to a string to a VB string
' : Taken from Microsoft Knowledge Base article Q167735
' : (Be sure this is declared as follows:
' : Declare Function lstrcpy Lib "kernel32" Alias "lstrcpyA" _
' : (ByVal lpString1 As String, ByVal lpString2 As Any) As Long
' PARAM: Add : pointer-to-string to convert
' DATE: 9/29/97
'**************************************************************************
Private Function PtrCtoVbString(Add As Long) As String
Dim sTemp As String * 512
Dim i As Long
i = lstrcpy(sTemp, Add)
If (InStr(1, sTemp, Chr(0)) = 0) Then
PtrCtoVbString = ""
Else
PtrCtoVbString = Left(sTemp, InStr(1, sTemp, Chr(0)) - 1)
End If
End Function
'**************************************************************************
' NAME: PrinterInfo2
' NOTES: Get Printer Info 2 structure on a printer
' PARAM: hPrinter : handle of printer to set as default
' : bShowError : display an error message if printer is not
available?
' RETURN: Printer_Info_2 structure
' DATE: 10/29/97
'**************************************************************************
Public Function PrinterInfo2(hPrinter As Long, bShowError As Boolean) As
PRINTER_INFO_2
Dim i As Long
Dim lpAddress As Long 'address returned by GlobalLock
Dim BufferSize As Long
Dim Temp() As Long
Dim pInfo2 As PRINTER_INFO_2 'your PRINTER_INFO structure
'make an initial call to GetPrinter, requesting Level 2
'(PRINTER_INFO_2) information, to determine how many bytes needed
i = GetPrinter(hPrinter, 2, ByVal 0&, 0, BufferSize)
'don't want to check GetLastError here - it's supposed to fail
'with a 122 - ERROR_INSUFFICIENT_BUFFER
'redim t as large as you need
ReDim Temp((BufferSize \ 4)) As Long
'and call GetPrinter for keepers this time
i = GetPrinter(hPrinter, 2, Temp(0), BufferSize, BufferSize)
'failed the GetPrinter
If i = False Then
If bShowError Then MsgBox ("Failed to GetPrinter")
Exit Function
End If
'set the members of the pInfo2 structure for use with SetPrinter
'PtrCtoVbString copies the memory pointed at by the two string
'pointers contained in the Temp() array into a VB string.
'The other three elements are just dWords (long integers) and
'don't require any conversion
pInfo2.pServerName = PtrCtoVbString(Temp(0))
pInfo2.pPrinterName = PtrCtoVbString(Temp(1))
pInfo2.pShareName = PtrCtoVbString(Temp(2))
pInfo2.pPortName = PtrCtoVbString(Temp(3))
pInfo2.pDriverName = PtrCtoVbString(Temp(4))
pInfo2.pComment = PtrCtoVbString(Temp(5))
pInfo2.pLocation = PtrCtoVbString(Temp(6))
'copy devmode structure from its memory address to the pInfo2 pdevmode
member
lpAddress = GlobalLock(Temp(7))
CopyMemory pInfo2.pDevMode, ByVal lpAddress, Len(pInfo2.pDevMode)
lpAddress = GlobalUnlock(Temp(7))
pInfo2.pDevMode.dmDeviceName =
sStringTrimNull(pInfo2.pDevMode.dmDeviceName)
pInfo2.pDevMode.dmFormName = sStringTrimNull(pInfo2.pDevMode.dmFormName)
pInfo2.pSepFile = PtrCtoVbString(Temp(8))
pInfo2.pPrintProcessor = PtrCtoVbString(Temp(9))
pInfo2.pDatatype = PtrCtoVbString(Temp(10))
pInfo2.pParameters = PtrCtoVbString(Temp(11))
'pInfo2.pSecurityDescriptor = Temp(12)
'copy securitydescriptor structure from its memory address to the pInfo2
psecuritydescriptor member
lpAddress = GlobalLock(Temp(12))
CopyMemory pInfo2.pSecurityDescriptor, ByVal lpAddress,
Len(pInfo2.pSecurityDescriptor)
lpAddress = GlobalUnlock(Temp(12))
pInfo2.Attributes = Temp(13)
pInfo2.Priority = Temp(14)
pInfo2.DefaultPriority = Temp(15)
pInfo2.StartTime = Temp(16)
pInfo2.UntilTime = Temp(17)
pInfo2.Status = Temp(18)
pInfo2.cJobs = Temp(19)
pInfo2.AveragePPM = Temp(20)
PrinterInfo2 = pInfo2
End Function
Call it like this:
'**************************************************************************
' NAME: btnInfo2_Click
' NOTES: Get all Info2 for selected printer
' DATE: 10/29/97
'**************************************************************************
Private Sub btnInfo2_Click()
Dim pInfo2 As PRINTER_INFO_2
Dim hPrinter As Long
Dim sPrinterName As String
Dim i As Integer
Dim s As String
'Get a handle to the printer
sPrinterName = Mid(lboxPrinters.List(lboxPrinters.ListIndex), 2,
InStr(lboxPrinters.List(lboxPrinters.ListIndex), "=") - 2)
hPrinter = hPrinterOpen(sPrinterName, True)
pInfo2 = PrinterInfo2(hPrinter, True)
MsgBox Title:="Printer Info 2", _
Prompt:="ServerName:" & Chr(9) & pInfo2.pServerName & vbCrLf & _
"PrinterName: " & Chr(9) & pInfo2.pPrinterName & vbCrLf & _
"ShareName: " & Chr(9) & pInfo2.pShareName & vbCrLf & _
"PortName: " & Chr(9) & pInfo2.pPortName & vbCrLf & _
"DriverName: " & Chr(9) & pInfo2.pDriverName & vbCrLf & _
"Comment: " & Chr(9) & pInfo2.pComment & vbCrLf & _
"Location: " & Chr(9) & pInfo2.pLocation & vbCrLf & _
"DevMode: " & Chr(9) & "(next screen)" & vbCrLf & _
"SepFile: " & Chr(9) & pInfo2.pSepFile & vbCrLf & _
"PrintProcessor: " & Chr(9) & pInfo2.pPrintProcessor & vbCrLf & _
"Datatype: " & Chr(9) & pInfo2.pDatatype & vbCrLf & _
"Parameters: " & Chr(9) & pInfo2.pParameters & vbCrLf & _
"SecurityDescriptor: " & Chr(9) & "(next screen)" & vbCrLf & _
"Attributes: " & Chr(9) & Str(pInfo2.Attributes) & vbCrLf & _
"Priority: " & Chr(9) & Chr(9) & Str(pInfo2.Priority) & vbCrLf &
_
"DefaultPriority: " & Chr(9) & Str(pInfo2.DefaultPriority) &
vbCrLf & _
"StartTime: " & Chr(9) & Str(pInfo2.StartTime) & vbCrLf & _
"UntilTime: " & Chr(9) & Str(pInfo2.UntilTime) & vbCrLf & _
"Status: " & Chr(9) & Chr(9) & Str(pInfo2.Status) & vbCrLf & _
"cJobs: " & Chr(9) & Chr(9) & Str(pInfo2.cJobs) & vbCrLf & _
"AveragePPM: " & Chr(9) & Str(pInfo2.AveragePPM)
MsgBox Title:="Printer Info 2 DevMode", _
Prompt:="DeviceName:" & Chr(9) & pInfo2.pDevMode.dmDeviceName &
vbCrLf & "SpecVersion: " & Chr(9) & Str(pInfo2.pDevMode.dmSpecVersion) &
vbCrLf & _
"DriverVersion: " & Chr(9) & Str(pInfo2.pDevMode.dmDriverVersion)
& vbCrLf & "Size: " & Chr(9) & Chr(9) & Str(pInfo2.pDevMode.dmSize) &
vbCrLf & _
"DriverExtra: " & Chr(9) & Str(pInfo2.pDevMode.dmDriverExtra) &
vbCrLf & _
"Fields: " & Chr(9) & Chr(9) & Str(pInfo2.pDevMode.dmFields) &
vbCrLf & _
"Orientation: " & Chr(9) & Str(pInfo2.pDevMode.dmOrientation) &
vbCrLf & _
"PaperSize: " & Chr(9) & Str(pInfo2.pDevMode.dmPaperSize) &
vbCrLf & _
"PaperLength: " & Chr(9) & Str(pInfo2.pDevMode.dmPaperLength) &
vbCrLf & _
"PaperWidth: " & Chr(9) & Str(pInfo2.pDevMode.dmPaperWidth) &
vbCrLf & _
"Scale: " & Chr(9) & Chr(9) & Str(pInfo2.pDevMode.dmScale) &
vbCrLf & _
"Copies: " & Chr(9) & Chr(9) & Str(pInfo2.pDevMode.dmCopies) &
vbCrLf & _
"DefaultSource: " & Chr(9) & Str(pInfo2.pDevMode.dmDefaultSource)
& vbCrLf & _
"PrintQuality: " & Chr(9) & Str(pInfo2.pDevMode.dmPrintQuality) &
vbCrLf & _
"Color: " & Chr(9) & Chr(9) & Str(pInfo2.pDevMode.dmColor) &
vbCrLf & _
"Duplex: " & Chr(9) & Chr(9) & Str(pInfo2.pDevMode.dmDuplex) &
vbCrLf & _
"YResolution: " & Chr(9) & Str(pInfo2.pDevMode.dmYResolution) &
vbCrLf & _
"TTOption: " & Chr(9) & Str(pInfo2.pDevMode.dmTTOption) & vbCrLf
& _
"Collate: " & Chr(9) & Chr(9) & Str(pInfo2.pDevMode.dmCollate) &
vbCrLf & _
"FormName: " & Chr(9) & Chr(9) & pInfo2.pDevMode.dmFormName &
vbCrLf & _
"UnusedPadding: " & Chr(9) & Str(pInfo2.pDevMode.dmUnusedPadding)
& vbCrLf & _
"BitsPerPel: " & Chr(9) & Str(pInfo2.pDevMode.dmBitsPerPel) &
vbCrLf & _
"PelsWidth: " & Chr(9) & Str(pInfo2.pDevMode.dmPelsWidth) &
vbCrLf & _
"PelsHeight: " & Chr(9) & Str(pInfo2.pDevMode.dmPelsHeight) &
vbCrLf & "DisplayFlags: " & Chr(9) & Str(pInfo2.pDevMode.dmDisplayFlags) &
vbCrLf & _
"DisplayFreq: " & Chr(9) &
Str(pInfo2.pDevMode.dmDisplayFrequency)
' MsgBox Title:="Printer Info 2 Security Descriptor", _
' Prompt:="Revision:" & Chr(9) &
Str(pInfo2.pSecurityDescriptor.Revision) & vbCrLf & _
' "Sbz1: " & Chr(9) & Str(pInfo2.pSecurityDescriptor.Sbz1)
& vbCrLf & _
' "Control: " & Chr(9) &
Str(pInfo2.pSecurityDescriptor.Control) & vbCrLf & _
' "Owner: " & Chr(9) &
Str(pInfo2.pSecurityDescriptor.Owner) & vbCrLf & _
' "Group: " & Chr(9) &
Str(pInfo2.pSecurityDescriptor.Group) & vbCrLf & _
' "Sac1: " & Chr(9) & "(not available)" & vbCrLf & _
' "Dacl: " & Chr(9) & "(not available)"
Call ClosePrinter(hPrinter)
lboxPrinters.SetFocus
VB API DEVMODE Structure
DEVMODE Structure
Type DEVMODE
dmDeviceName As String * 32
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 * 32
dmUnusedPadding As Integer
dmBitsPerPixel As Integer
dmPelsWidth As Long
dmPelsHeight As Long
dmDisplayFlags As Long
dmDisplayFrequency As Long
' The following only appear in Windows 95, 98, 2000
dmICMMethod As Long
dmICMIntent As Long
dmMediaType As Long
dmDitherType As Long
dmReserved1 As Long
dmReserved2 As Long
' The following only appear in Windows 2000
dmPanningWidth As Long
dmPanningHeight As Long
End Type
Description & Usage
The DEVMODE structure stores information about various settings and properties of a device, such as a printer. Some of the properties only apply to certain devices; for example, the dmDisplayFrequency has no relevant meaning for a printer. To determine which data members of the structure contain useful information, check the flags set in dwFields.
Visual Basic-Specific Information
None.
Data Members
- dmDeviceName
- The name of the device.
- dmSpecVersion
- The version number of the device's initialization information specification.
- dmDriverVersion
- The version number of the device driver.
- dmSize
- The size of the structure, in bytes.
- dmDriverExtra
- The number of bytes of information trailing the structure in memory.
- dmFields
- A combination of the following flags specifying which of the rest of the structure's members contain information about the device:
- DM_ORIENTATION
- dmOrientation contains information.
- DM_PAPERSIZE
- dmPaperSize contains information.
- DM_PAPERLENGTH
- dmPaperLength contains information.
- DM_PAPERWIDTH
- dmPaperWidth contains information.
- DM_SCALE
- dmScale contains information.
- DM_COPIES
- dmCopies contains information.
- DM_DEFAULTSOURCE
- dmDefaultSource contains information.
- DM_PRINTQUALITY
- dmPrintQuality contains information.
- DM_COLOR
- dmColor contains information.
- DM_DUPLEX
- dmDuplex contains information.
- DM_YRESOLUTION
- dmYResolution contains information.
- DM_TTOPTION
- dmTTOption contains information.
- DM_COLLATE
- dmCollate contains information.
- DM_FORMNAME
- dmFormName contains information.
- DM_LOGPIXELS
- dmLogPixels contains information.
- DM_BITSPERPEL
- dmBitsPerPel contains information.
- DM_PELSWIDTH
- dmPelsWidth contains information.
- DM_PELSHEIGHT
- dmPelsHeight contains information.
- DM_DISPLAYFLAGS
- dmDisplayFlags contains information.
- DM_DISPLAYFREQUENCY
- dmDisplayFrequency contains information.
- DM_ICMMETHOD
- Win 95/98 only: dmICMMethod contains information.
- DM_ICMINTENT
- Windows 95, 98, 2000: dmICMIntent contains information.
- DM_MEDIATYPE
- Windows 95, 98, 2000: dmMediaType contains information.
- DM_DITHERTYPE
- Windows 95, 98, 2000: dmDitherType contains information.
- DM_PANNINGWIDTH
- Windows 2000: dmPanningWidth contains information.
- DM_PANNINGHEIGHT
- Windows 2000: dmPanningHeight contains information.
- dmOrientation
- One of the following flags specifying the orientation of the printer paper:
- DMORIENT_PORTRAIT
- Portrait (tall) mode.
- DMORIENT_LANDSCAPE
- Landscape (wide) mode.
- dmPaperSize
- If nonzero, one of the following flags specifying the size of the printer paper (or some other value specifying a paper size). If zero, the paper size is determined by dmPaperLength and dmPaperWidth.
- DMPAPER_LETTER
- Letter, 8.5 x 11 inches.
- DMPAPER_LEGAL
- Legal, 8.5 x 14 inches.
- DMPAPER_10X11
- 10 x 11 inches.
- DMPAPER_10X14
- 10 x 14 inches.
- DMPAPER_11X17
- 11 x 17 inches.
- DMPAPER_15X11
- 15 x 11 inches.
- DMPAPER_9X11
- 9 x 11 inches.
- DMPAPER_A_PLUS
- A plus sheet.
- DMPAPER_A2
- A2 sheet.
- DMPAPER_A3
- A3 sheet, 297 x 420 millimeters.
- DMPAPER_A3_EXTRA
- A3 extra sheet.
- DMPAPER_A3_EXTRA_TRANSVERSE
- A3 extra transverse sheet.
- DMPAPER_A3_TRANSVERSE
- A3 transverse sheet.
- DMPAPER_A4
- A4 sheet, 210 x 297 millimeters.
- DMPAPER_A4_EXTRA
- A4 extra sheet.
- DMPAPER_A4_PLUS
- A4 plus sheet.
- DMPAPER_A4_TRANSVERSE
- A4 transverse sheet.
- DMPAPER_A4SMALL
- A4 small sheet, 210 x 297 millimeters.
- DMPAPER_A5
- A5 sheet, 148 x 210 millimeters.
- DMPAPER_A5_EXTRA
- A5 extra sheet.
- DMPAPER_A5_TRANSVERSE
- A5 transverse sheet.
- DMPAPER_B_PLUS
- B plus sheet.
- DMPAPER_B4
- B4 sheet, 250 x 354 millimeters.
- DMPAPER_B5
- B5 sheet, 192 x 257 millimeters.
- DMPAPER_B5_EXTRA
- B5 extra sheet.
- DMPAPER_B5_TRANSVERSE
- B5 transverse sheet.
- DMPAPER_CSHEET
- C sheet, 17 x 22 inches.
- DMPAPER_DSHEET
- D sheet, 22 x 34 inches.
- DMPAPER_ENV_10
- #10 envelope, 4.125 x 9.5 inches.
- DMPAPER_ENV_11
- #11 envelope, 4.5 x 10.375 inches.
- DMPAPER_ENV_12
- #12 envelope, 4.75 x 11 inches.
- DMPAPER_ENV_14
- #14 envelope, 5 x 11.5 inches.
- DMPAPER_ENV_9
- #9 envelope, 3.875 x 8.875 inches.
- DMPAPER_ENV_B4
- B4 envelope, 250 x 353 millimeters.
- DMPAPER_ENV_B5
- B5 envelope, 176 x 250 millimeters.
- DMPAPER_ENV_B6
- B6 envelope, 176 x 125 millimeters.
- DMPAPER_ENV_C3
- C3 envelope, 324 x 458 millimeters.
- DMPAPER_ENV_C4
- C4 envelope, 229 x 324 millimeters.
- DMPAPER_ENV_C5
- C5 envelope, 162 x 229 millimeters.
- DMPAPER_ENV_C6
- C6 envelope, 114 x 162 millimeters.
- DMPAPER_ENV_C65
- C65 envelope, 114 x 229 millimeters.
- DMPAPER_ENV_DL
- DL envelope, 110 x 220 millimeters.
- DMPAPER_ENV_INVITE
- Invitation envelope.
- DMPAPER_ENV_ITALY
- Italy envelope, 110 x 230 millimeters.
- DMPAPER_ENV_MONARCH
- Monarch envelope, 3.875 x 7.5 inches.
- DMPAPER_ENV_PERSONAL
- Personal (6.75) envelope, 3.625 x 6.5 inches.
- DMPAPER_ESHEET
- E sheet, 34 x 44 inches.
- DMPAPER_EXECUTIVE
- Executive, 7.25 x 10.5 inches.
- DMPAPER_FANFOLD_LGL_GERMAN
- German legal fanfold, 8.5 x 13 inches.
- DMPAPER_FANFOLD_STD_GERMAN
- German standard fanfold, 8.5 x 12 inches.
- DMPAPER_FANFOLD_US
- US standard fanfold, 14.875 x 11 inches.
- DMPAPER_FIRST
- Same as DMPAPER_LETTER.
- DMPAPER_FOLIO
- Folio, 8.5 x 13 inches.
- DMPAPER_ISO_B4
- ISO B4 sheet.
- DMPAPER_JAPANESE_POSTCARD
- Japanese postcard.
- DMPAPER_LAST
- Same as DMPAPER_FANFOLD_LGL_GERMAN.
- DMPAPER_LEDGER
- Ledger, 17 x 11 inches.
- DMPAPER_LEGAL_EXTRA
- Legal extra.
- DMPAPER_LETTER_EXTRA
- Letter extra.
- DMPAPER_LETTER_EXTRA_TRANSVERSE
- Letter extra transverse.
- DMPAPER_LETTER_PLUS
- Letter plus.
- DMPAPER_LETTER_TRANSVERSE
- Letter transverse.
- DMPAPER_LETTERSMALL
- Letter small, 8.5 x 11 inches.
- DMPAPER_NOTE
- Note, 8.5 x 11 inches.
- DMPAPER_QUARTO
- Quarto, 215 x 275 millimeters.
- DMPAPER_STATEMENT
- Statement, 5.5 x 8.5 inches.
- DMPAPER_TABLOID
- Tabloid, 11 x 17 inches.
- DMPAPER_TABLOID_EXTRA
- Tabloid extra.
- DMPAPER_USER
- User-defined size.
- dmPaperLength
- The length of the printer paper, measured in tenths of a millimeter.
- dmPaperWidth
- The width of the printer paper, measured in tenths of a millimeter.
- dmScale
- The scale percentage factor (e.g., 100 means 100%, or no, scaling; 200 means two times the size, etc.).
- dmCopies
- The number of document copies to print, if the device supports it.
- dmDefaultSource
- One of the following flags specifying the printer's source of paper:
- DMBIN_ONLYONE
- There is only one paper source.
- DMBIN_UPPER
- Upper bin.
- DMBIN_LOWER
- Lower bin.
- DMBIN_MIDDLE
- Middle bin.
- DMBIN_MANUAL
- Manual loading.
- DMBIN_ENVELOPE
- Envelope bin.
- DMBIN_ENVMANUAL
- Manual-loading envelope.
- DMBIN_AUTO
- Automatic loading.
- DMBIN_TRACTOR
- Tractor loading.
- DMBIN_SMALLFMT
- Small format loading.
- DMBIN_LARGEFMT
- Large format loading.
- DMBIN_LARGECAPACITY
- Large-capacity bin.
- DMBIN_CASSETTE
- Cassette.
- DMBIN_FORMSOURCE
- Form paper source.
- dmPrintQuality
- Either one of the following flags specifying the printer's print quality setting, or a positive value specifying the printer's dots per inch (DPI) rating.
- DMRES_DRAFT
- Draft-quality output.
- DMRES_LOW
- Low-quality output.
- DMRES_MEDIUM
- Medium-quality output.
- DMRES_HIGH
- High-quality output.
- dmColor
- One of the following flags specifying whether the device supports color:
- DMCOLOR_MONOCHROME
- The device does not support color output.
- DMCOLOR_COLOR
- The device supports color output.
- dmDuplex
- One of the following flags specifying the printer's double-sided (duplex) printing capability:
- DMDUP_SIMPLEX
- Configured for single-sided printing.
- DMDUP_VERTICAL
- Configured for double-sided printing with vertical page turning.
- DMDUP_HORIZONTAL
- Configured for double-sided printing with horizontal page turning.
- dmYResolution
- The number of the vertical dots per inch of the printer. If this value contains useful data, the number of horizontal dots per inch is inside dmPrintQuality.
- dmTTOption
- One of the following flags specifying how the printer prints TrueType fonts:
- DMTT_BITMAP
- The printer prints TrueType fonts as graphics (default for dot-matrix printers).
- DMTT_DOWNLOAD
- The printer downloads TrueType fonts as soft fonts (default for Hewlett-Packerd printers using Printer Control Language).
- DMTT_SUBDEV
- The printer substitutes device fonts for TrueType fonts (default for PostScript printers).
- dmUnusedPadding
- Reserved -- set to 0. This member merely takes up space to align other members in memory.
- dmCollate
- One of the following flags specifying whether the printer can collate copies:
- DMCOLLATE_FALSE
- Does not collate pages when printing multiple copies.
- DMCOLLATE_TRUE
- Does collate pages when printing multiple copies.
- dmFormName
- Windows NT, 2000: The name of the type of paper loaded in the printer.
- dmBitsPerPel
- The number of color bits used per pixel on the display device.
- dmPelsWidth
- The width of the display, measured in pixels.
- dmPelsHeight
- The height of the display, measured in pixels.
- dmDisplayFlags
- A combination of the following flags specifying the device's display mode:
- DM_GRAYSCALE
- The display does not support color. (If this flag is omitted, assume color is supported.)
- DM_INTERLACED
- The display is interlaced.
- dmDisplayFrequency
- The display frequency of the display, measured in Hz.
- dmICMMethod
- Windows 95, 98, 2000: Either one of the following flags specifying how image color matching (ICM) is supported, or a device-defined value greater than 256:
- DMICMMETHOD_NONE
- ICM is disabled.
- DMICMMETHOD_SYSTEM
- ICM is handled by Windows.
- DMICMMETHOD_DRIVER
- ICM is handled by the device driver.
- DMICMMETHOD_DEVICE
- ICM is handled by the device.
- dmICMIntent
- Windows 95, 98, 2000: Either one of the following flags specifying the image color matching (ICM) method used when ICM is not intrinsically supported, or a device-defined value greater than 256:
- DMICM_SATURATE
- Color matching attempts to optimize color saturation.
- DMICM_CONTRAST
- Color matching attempts to optimize color contrast.
- DMICM_COLORMETRIC
- Color matching attempts to match the exact color requested.
- dmMediaType
- Windows 95, 98, 2000: Either one of the following flags specifying what type of medium the printer is printing on, or a device-defined value greater than 256:
- DMMEDIA_STANDARD
- Plain paper.
- DMMEDIA_GLOSSY
- Glossy paper.
- DMMEDIA_TRANSPARECNY
- Transparent film.
- dmDitherType
- Windows 95, 98, 2000: Either one of the following flags specifying the dithering method used by the device, or a device-defined value greater than 256:
- DMDITHER_NONE
- No dithering.
- DMDITHER_COARSE
- Dithering with a coarse brush.
- DMDITHER_FINE
- Dithering with a fine brush.
- DMDITHER_LINEART
- Line art dithering, which makes well-defined borders between black, white, and gray.
- DMDITHER_GRAYSCALE
- Grayscaling.
- dmReserved1
- Windows 95, 98, 2000: Reserved -- set to 0.
- dmReserved2
- Windows 95, 98, 2000: Reserved -- set to 0.
- dmPanningWidth
- Windows 2000: Reserved -- set to 0.
- dmPanningHeight
- Windows 2000: Reserved -- set to 0.
Constant Definitions
Const DM_ORIENTATION = &H1
Const DM_PAPERSIZE = &H2
Const DM_PAPERLENGTH = &H4
Const DM_PAPERWIDTH = &H8
Const DM_SCALE = &H10
Const DM_COPIES = &H100
Const DM_DEFAULTSOURCE = &H200
Const DM_PRINTQUALITY = &H400
Const DM_COLOR = &H800
Const DM_DUPLEX = &H1000
Const DM_YRESOLUTION = &H2000
Const DM_TTOPTION = &H4000
Const DM_COLLATE = &H8000
Const DM_FORMNAME = &H10000
Const DM_LOGPIXELS = &H20000
Const DM_BITSPERPEL = &H40000
Const DM_PELSWIDTH = &H80000
Const DM_PELSHEIGHT = &H100000
Const DM_DISPLAYFLAGS = &H200000
Const DM_DISPLAYFREQUENCY = &H400000
Const DM_ICMMETHOD = &H800000
Const DM_ICMINTENT = &H1000000
Const DM_MEDIATYPE = &H2000000
Const DM_DITHERTYPE = &H4000000
Const DM_PANNINGWIDTH = &H20000000
Const DM_PANNINGHEIGHT = &H40000000
Const DMORIENT_PORTRAIT = 1
Const DMORIENT_LANDSCAPE = 2
Const DMPAPER_LETTER = 1
Const DMPAPER_LEGAL = 5
Const DMPAPER_10X11 = 45
Const DMPAPER_10X14 = 16
Const DMPAPER_11X17 = 17
Const DMPAPER_15X11 = 46
Const DMPAPER_9X11 = 44
Const DMPAPER_A_PLUS = 57
Const DMPAPER_A2 = 66
Const DMPAPER_A3 = 8
Const DMPAPER_A3_EXTRA = 63
Const DMPAPER_A3_EXTRA_TRANSVERSE = 68
Const DMPAPER_A3_TRANSVERSE = 67
Const DMPAPER_A4 = 9
Const DMPAPER_A4_EXTRA = 53
Const DMPAPER_A4_PLUS = 60
Const DMPAPER_A4_TRANSVERSE = 55
Const DMPAPER_A4SMALL = 10
Const DMPAPER_A5 = 11
Const DMPAPER_A5_EXTRA = 64
Const DMPAPER_A5_TRANSVERSE = 61
Const DMPAPER_B_PLUS = 58
Const DMPAPER_B4 = 12
Const DMPAPER_B5 = 13
Const DMPAPER_B5_EXTRA = 65
Const DMPAPER_B5_TRANSVERSE = 62
Const DMPAPER_CSHEET = 24
Const DMPAPER_DSHEET = 25
Const DMPAPER_ENV_10 = 20
Const DMPAPER_ENV_11 = 21
Const DMPAPER_ENV_12 = 22
Const DMPAPER_ENV_14 = 23
Const DMPAPER_ENV_9 = 19
Const DMPAPER_ENV_B4 = 33
Const DMPAPER_ENV_B5 = 34
Const DMPAPER_ENV_B6 = 35
Const DMPAPER_ENV_C3 = 29
Const DMPAPER_ENV_C4 = 30
Const DMPAPER_ENV_C5 = 28
Const DMPAPER_ENV_C6 = 31
Const DMPAPER_ENV_C65 = 32
Const DMPAPER_ENV_DL = 27
Const DMPAPER_ENV_INVITE = 47
Const DMPAPER_ENV_ITALY = 36
Const DMPAPER_ENV_MONARCH = 37
Const DMPAPER_ENV_PERSONAL = 38
Const DMPAPER_ESHEET = 26
Const DMPAPER_EXECUTIVE = 7
Const DMPAPER_FANFOLD_LGL_GERMAN = 41
Const DMPAPER_FANFOLD_STD_GERMAN = 40
Const DMPAPER_FANFOLD_US = 39
Const DMPAPER_FIRST = 1
Const DMPAPER_FOLIO = 14
Const DMPAPER_ISO_B4 = 42
Const DMPAPER_JAPANESE_POSTCARD = 43
Const DMPAPER_LAST = 41
Const DMPAPER_LEDGER = 4
Const DMPAPER_LEGAL_EXTRA = 51
Const DMPAPER_LETTER_EXTRA = 50
Const DMPAPER_LETTER_EXTRA_TRANSVERSE = 56
Const DMPAPER_LETTER_PLUS = 59
Const DMPAPER_LETTER_TRANSVERSE = 54
Const DMPAPER_LETTERSMALL = 2
Const DMPAPER_NOTE = 18
Const DMPAPER_QUARTO = 15
Const DMPAPER_STATEMENT = 6
Const DMPAPER_TABLOID = 3
Const DMPAPER_TABLOID_EXTRA = 52
Const DMPAPER_USER = 256
Const DMBIN_ONLYONE = 1
Const DMBIN_UPPER = 1
Const DMBIN_LOWER = 2
Const DMBIN_MIDDLE = 3
Const DMBIN_MANUAL = 4
Const DMBIN_ENVELOPE = 5
Const DMBIN_ENVMANUAL = 6
Const DMBIN_AUTO = 7
Const DMBIN_TRACTOR = 8
Const DMBIN_SMALLFMT = 9
Const DMBIN_LARGEFMT = 10
Const DMBIN_LARGECAPACITY = 11
Const DMBIN_CASSETTE = 14
Const DMBIN_FORMSOURCE = 15
Const DMRES_DRAFT = -1
Const DMRES_LOW = -2
Const DMRES_MEDIUM = -3
Const DMRES_HIGH = -4
Const DMCOLOR_MONOCHROME = 1
Const DMCOLOR_COLOR = 2
Const DMDUP_SIMPLEX = 1
Const DMDUP_VERTICAL = 2
Const DMDUP_HORIZONTAL = 3
Const DMTT_BITMAP = 1
Const DMTT_DOWNLOAD = 2
Const DMTT_SUBDEV = 4
Const DMCOLLATE_FALSE = 0
Const DMCOLLATE_TRUE = 1
Const DM_GRAYSCALE = 1
Const DM_INTERLACED = 2
Const DMICMMETHOD_NONE = 1
Const DMICMMETHOD_SYSTEM = 2
Const DMICMMETHOD_DRIVER = 3
Const DMICMMETHOD_DEVICE = 4
Const DMICM_SATURATE = 1
Const DMICM_CONTRAST = 2
Const DMICM_COLORMETRIC = 3
Const DMMEDIA_STANDARD = 1
Const DMMEDIA_GLOSSY = 2
Const DMMEDIA_TRANSPARECNY = 3
Const DMDITHER_NONE = 1
Const DMDITHER_COARSE = 2
Const DMDITHER_FINE = 3
Const DMDITHER_LINEART = 4
Const DMDITHER_GRAYSCALE = 5
Used By
ChangeDisplaySettings, CreateDC, EnumDisplaySettings, JOB_INFO_2, PRINTDLG_TYPE, PRINTER_DEFAULTS, PRINTER_INFO_2
Wednesday, March 25, 2009
Get User Name & Computer Name
Declare Function GetUserName Lib "advapi32.dll" Alias "GetUserNameA" (ByVal lpBuffer As String, nSize As Long) As Long
Declare Function GetComputerName Lib "kernel32" Alias "GetComputerNameA" (ByVal lpBuffer As String, nSize As Long) As Long
Public Sub Main()
Dim sUser As String
Dim sComputer As String
Dim lpBuff As String * 1024
'Get the Login User Name
GetUserName lpBuff, Len(lpBuff)
sUser = Left$(lpBuff, (InStr(1, lpBuff, vbNullChar)) - 1)
lpBuff = ""
'Get the Computer Name
GetComputerName lpBuff, Len(lpBuff)
sComputer = Left$(lpBuff, (InStr(1, lpBuff, vbNullChar)) - 1)
lpBuff = ""
MsgBox "Login User: " & sUser & vbCrLf & _
"Computer Name: " & sComputer
End
End Sub
Or try this...
sUser = VBA.Environ("USERNAME")
sComputer = VBA.Environ("COMPUTERNAME")
Tuesday, March 24, 2009
Printer Spooling Monitor
Const CCHDEVICENAME = 32
Const CCHFORMNAME = 32
Public Const PRINTER_ACCESS_USE = &H8
Public Const PRINTER_ACCESS_ADMINISTER = &H4
Type SYSTEMTIME
wYear As Integer
wMonth As Integer
wDayOfWeek As Integer
wDay As Integer
wHour As Integer
wMinute As Integer
wSecond As Integer
wMilliseconds As Integer
End Type
Type JOB_INFO_1
JobId As Long
pPrinterName As
pMachineName As String
pUserName As String
pDocument As String
pDatatype As String
pStatus As String
Priority As Long
Position As Long
TotalPages As Long
PagesPrinted As Long
Submitted As SYSTEMTIME
End Type
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 Integer
dmPelsWidth As Long
dmPelsHeight As Long
dmDisplayFlags As Long
dmDisplayFrequency As Long
End Type
Type PRINTER_DEFAULTS
pDatatype As String
pDevMode As DEVMODE
DesiredAccess As Long
End Type
Type PRINTER_INFO_2
pServerName As Long
pPrinterName As Long
pShareName As Long
pPortName As Long
pDriverName As Long
pComment As Long
pLocation As Long
pDevMode As Long '
pSepFile As Long
pPrintProcessor As Long
pDatatype As Long
pParameters As Long
pSecurityDescriptor As Long ' Pointer to 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
Type MY_PRINTER_INFO 'UDT to store INFO
pServerName As String
Status As String
pPrinterName As String
pShareName As String
pPortName As String
pDriverName As String
pComment As String
pLocation As String
pSepFile As String
pPrintProcessor As String
pDatatype As String
pParameters As String
Attributes As String
Priority As Long
DefaultPriority As Long
StartTime As Long
UntilTime As Long
cJobs As Long
AveragePPM As Long
Orientation As String
PagesTotal(127) As Long
PagesPrinted(127) As Long
End Type
Public Const PRINTER_ATTRIBUTE_DEFAULT = &H4
Public Const PRINTER_ATTRIBUTE_DIRECT = &H2
Public Const PRINTER_ATTRIBUTE_ENABLE_B
Public Const PRINTER_ATTRIBUTE_LOCAL = &H40
Public Const PRINTER_ATTRIBUTE_NETWORK = &H10
Public Const PRINTER_ATTRIBUTE_QUEUED = &H1
Public Const PRINTER_ATTRIBUTE_SHARED = &H8
Public Const PRINTER_ENUM_DEFAULT = &H1
Public Const PRINTER_ENUM_LOCAL = &H2
Public Const PRINTER_ENUM_CONNECTIONS = &H4
Public Const PRINTER_ENUM_FAVORITE = &H4
Public Const PRINTER_ENUM_NAME = &H8
Public Const PRINTER_ENUM_REMOTE = &H10
Public Const PRINTER_ENUM_SHARED = &H20
Public Const PRINTER_ENUM_NETWORK = &H40
Public Const PRINTER_STATUS_BUSY = &H200
Public Const PRINTER_STATUS_ERROR = &H2
Public Const PRINTER_STATUS_PAPER_OUT = &H10
'You can use other const from apiviewer
Public Const JOB_STATUS_PAUSED = &H1
Public Const JOB_STATUS_ERROR = &H2
'You can use other const from apiviewer
Private Declare Function apiEnumPrinters Lib "winspool.drv" Alias "EnumPrintersA" (ByVal Flags As Long, ByVal Name As String, ByVal Level As Long, pPrinterEnum As Byte, ByVal cdBuf As Long, pcbNeeded As Long, pcReturned As Long) As Long
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 apiEnumJobs Lib "winspool.drv" Alias "EnumJobsA" (ByVal hPrinter As Long, ByVal FirstJob As Long, ByVal NoJobs As Long, ByVal Level As Long, pJob As Byte, ByVal cdBuf As Long, pcbNeeded As Long, pcReturned As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Declare Function CopyPointer2String Lib "kernel32" Alias "lstrcpyA" (ByVal NewString As String, ByVal OldString As Long) As Long
Private JI1 As JOB_INFO_1
Private PI2 As PRINTER_INFO_2
Public MyInfo() As MY_PRINTER_INFO
Public Function EnumPrinters() As Long
Dim pName As String
Dim Flags As Long, lRet As Long
Dim ResBuffer() As Byte, tmpBuf As Byte
Dim ByteNeed As Long, nPrinters As Long
Dim i As Integer, p As Long
pName = vbNullString
Flags = PRINTER_ENUM_LOCAL
lRet = apiEnumPrinters(Flags, pName, 2&, tmpBuf, 0&, ByteNeed, nPrinters)
ReDim ResBuffer(ByteNeed) As Byte
lRet = apiEnumPrinters(Flags, pName, 2&, ResBuffer(0), ByteNeed, ByteNeed, nPrinters)
ReDim MyInfo(nPrinters)
p = VarPtr(ResBuffer(0))
For i = 0 To nPrinters - 1
CopyMemory PI2, ByVal p, LenB(PI2)
FillInfoPrn i
p = p + LenB(PI2)
Next i
EnumPrinters = nPrinters
End Function
Private Sub FillInfoPrn(idx As Integer)
Dim DM As DEVMODE
MyInfo(idx).pServerName = PointerToString(PI2.pServe
MyInfo(idx).pPrinterName = PointerToString(PI2.pPrint
MyInfo(idx).Status = GetPrnStatus(PI2.Status)
MyInfo(idx).cJobs = PI2.cJobs
MyInfo(idx).pPortName = PointerToString(PI2.pPortN
MyInfo(idx).Attributes = GetAttributes(PI2.Attribut
MyInfo(idx).pComment = PointerToString(PI2.pComme
'and so on - you can fill any info you need
'if it's string - use PointerToString function
'you can get a lot of info you need from DV structure
'Then you can add a member to your MY_PRINTER_INFO struct.
'For example I add Orientation
CopyMemory DM, ByVal PI2.pDevMode, LenB(DM)
MyInfo(idx).Orientation = IIf(DM.dmOrientation = 1, "Portrait", "Landscape")
End Sub
Private Function PointerToString(p As Long) As String
Dim s As String
s = String(255, Chr$(0))
CopyPointer2String s, p
PointerToString = Left(s, InStr(s, Chr$(0)) - 1)
End Function
Private Function GetPrnStatus(flg As Long) As String
Dim s As String
s = ""
If (flg And PRINTER_STATUS_BUSY) Then s = s & "Busy;"
If (flg And PRINTER_STATUS_ERROR) Then s = s & "Error;"
If (flg And PRINTER_STATUS_PAPER_OUT) Then s = s & "Paper out;"
' and so on for all flags you need
GetPrnStatus = s
End Function
Private Function GetJobStatus(flg As Long) As String
Dim s As String
s = ""
If (flg And JOB_STATUS_PAUSED) Then s = s & "Paused;"
If (flg And JOB_STATUS_ERROR) Then s = s & "Error;"
' and so on for all flags you need
GetJobStatus = s
End Function
Private Function GetAttributes(flg As Long) As String
Dim s As String
s = ""
If (flg And PRINTER_ATTRIBUTE_DEFAULT)
If (flg And PRINTER_ATTRIBUTE_QUEUED) Then s = s & "Queued;"
If (flg And PRINTER_ATTRIBUTE_SHARED) Then s = s & "Shared;"
If (flg And PRINTER_ATTRIBUTE_NETWORK)
If (flg And PRINTER_ATTRIBUTE_LOCAL) Then s = s & "Local;"
' and so on for all flags you need
GetAttributes = s
End Function
Public Function EnumJobs(pNum As Integer) As Long
Dim ResBuffer(0 To 127) As Byte, tmpBuf As Byte
Dim ByteNeed As Long, nJobs As Long
Dim i As Integer, p As Long
Dim lRet As Long
Dim PD As PRINTER_DEFAULTS
pName = MyInfo(pNum).pPrinterName
PD.DesiredAccess = PRINTER_ACCESS_USE
PD.pDatatype = vbNullString
PD.pDevMode.dmSize = LenB(PD.pDevMode)
lRet = OpenPrinter(pName, hPrn, PD)
lRet = apiEnumJobs(hPrn, 0&, 127&, 1&, tmpBuf, 0&, ByteNeed, nJobs)
If ByteNeed = 0 Then
EnumJobs = 0
Else
lRet = apiEnumJobs(hPrn, 0&, 127&, 1&, ResBuffer(0), ByteNeed, ByteNeed, nJobs)
p = VarPtr(ResBuffer(0))
For i = 0 To nJobs - 1
CopyMemory JI1, ByVal p, LenB(JI1)
FillInfoJobs pNum, i
p = p + LenB(JI1)
Next i
EnumJobs = nJobs
End If
lRet = CloseHandle(hPrn)
End Function
Private Sub FillInfoJobs(prnNum As Integer, idx As Integer)
'You can add members to your UDT or make another UDT for JobData. I use existing UDT
MyInfo(prnNum).Status = GetJobStatus(JI1.Status)
MyInfo(prnNum).PagesTotal(
MyInfo(prnNum).PagesPrinte
'e.t.c
End Sub