Thursday, March 26, 2009

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

End Sub

No comments:

Post a Comment