Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Multiple Bugs in MSKB: Q173981 PRB: Working with Print Dialog and Printer Object under NT 4.0

30 views
Skip to first unread message

René Malingré

unread,
Jul 2, 2001, 10:15:42 PM7/2/01
to
After having a lot of trouble printing under Wndows NT using VB6 API-only
print routines, I discovered my problems related to the sample code I was
using from MSKB (Q173981).

This code has some serious bugs, probably because it was ported from 16 bit
code:

As I am not very experience in Win API, feedback would be appreciated


** The declaration below does not allow enough space for long printer names
allowed under NT:
Type DEVNAMES_TYPE
wDriverOffset As Integer
wDeviceOffset As Integer
wOutputOffset As Integer
wDefault As Integer
extra As String * 100 '(suggest change to 3 * MAX_PATH to allow
space (too much, really!) for long printer name and device and port names)
End Type

** Hows this one! Using an INTEGER to receive a LONG return value!
Dim bReturn As Integer

** This bug puts the devname input offsets into the wrong order!
' Set the current driver, device, and port name strings
With DevName
.wDriverOffset = 8
.wDeviceOffset = .wDriverOffset + 1 + Len(Printer.DriverName)
.wOutputOffset = .wDeviceOffset + 1 + Len(Printer.Port) ' This
should be ... + Len(Printer.DeviceName)!!!
.wDefault = 0
End With


** This next bug ignores the fact that a printer device name can be longer
than 32 characters under NT!
** The printer name should be returned from the DevName (unlimited in length
of strings returned) structure rather than the DevMode structure (limited to
32 characters)!
** Using the DevName structure will also allow the Port and Driver to be
returned (provided the offsets are correctly used!)
NewPrinterName = UCase$(Left(DevMode.dmDeviceName,
InStr(DevMode.dmDeviceName, Chr$(0)) - 1)) 'too bad if it is a long printer
name!


These bugs have wasted 4 days of my life, but at least I know a bit more
about API calling (and not to trust someone else's code!)


Rene Malingre

Andy stewartson

unread,
Jul 3, 2001, 5:18:35 AM7/3/01
to
René

I can't be much help but I have also had a problem with NT and long
printer names being clipped at 32 characters.
If you come across a solution I would be very interested.


--
Best regards

Andy Stewartson

+------------------------------+---------------------------------------+
Andy Stewartson, | Tel: +44 1634 844400 ext. 4562
Senior Mechanical Engineer | Fax: +44 1634 816360
Mechanical Design Engineering |
Mission Systems Division |
BAE SYSTEMS Avionics Ltd | E-mail: andy.st...@baesystems.com
Rochester, ME1 2XX |

René Malingré

unread,
Jul 4, 2001, 3:06:06 AM7/4/01
to
Andy, two methods below (I don't guarantee that I have included all
constants, types and declarations! a quick cut and paste also requires my
memory to be good!)

I only program for hobby, not profit, but I volunteered to write a program
for my company's head office. I develop on Win98, they have WinNT 4, and
they are half way across the continent. It has been very frustrating
debugging the program without NT to test it on!

Doing a search of Dejanews, lots of people have had this problem, and
problems related to CreateDC under WinNT (probably due to
truncated printer names!). I couldn't find any post that
solved it, and had to piece it together from various MSKB articles, Dan
Appleman's book, and other snippets from various web sites. I think I am
there now...

Sorry about the line breaks being all over the place in this post...

Rene Malingre
Optometrist
Professional Services Manager
OPSM
Adelaide, Australia
mali...@ozemail.com.au

*************************************
This code will enumerate printers, using long names
*********************************
Private Declare Function lstrcpyA Lib "kernel32" (ByVal retVal As String,
ByVal Ptr As Long) As Long
Private Declare Function lstrlenA Lib "kernel32" (ByVal Ptr As Any) As Long
Public 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 ' LPDEVMODE
pSepFile As Long
pPrintProcessor As Long
pDatatype As Long
pParameters As Long
pSecurityDescriptor As Long ' PSECURITY_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 Declare Function EnumPrintersNew Lib "winspool.drv" Alias
"EnumPrintersA" (ByVal Flags As Long, _
ByVal Name As String, _
ByVal Level As Long, _
pPrinterEnum As Any, _
ByVal cdBuf As Long, _
pcbNeeded As Long, _
pcReturned As Long) As Long
'
'EnumPrinters Parameters:
'Flags - Specifies the types of print objects that the function should
enumerate.
Private Const PRINTER_ENUM_DEFAULT = &H1 'Windows 95: The function
returns
'information about the default
printer.
Private Const PRINTER_ENUM_LOCAL = &H2 'function ignores the Name
parameter,
'and enumerates the locally
installed
'printers. Windows 95: The
function will
'also enumerate network printers
because
'they are handled by the local
print provider
Private Const PRINTER_ENUM_CONNECTIONS = &H4 'Windows NT/2000: The function
enumerates the
'list of printers to which the
user has made
'previous connections
Private Const PRINTER_ENUM_NAME = &H8 'enumerates the printer
identified by Name.
'This can be a server, a domain,
or a print
'provider. If Name is NULL, the
function
'enumerates available print
providers
Private Const PRINTER_ENUM_REMOTE = &H10 'Windows NT/2000: The function
enumerates network
'printers and print servers in
the computer's domain.
'This value is valid only if
Level is 1
Private Const PRINTER_ENUM_SHARED = &H20 'enumerates printers that have
the shared attribute.
'Cannot be used in isolation;
use an OR operation
'to combine with another
PRINTER_ENUM type
Private Const PRINTER_ENUM_NETWORK = &H40 'Windows NT/2000: The function
enumerates network
'printers in the computer's
domain. This value is
'valid only if Level is 1.
Private Const PRINTER_ATTRIBUTE_DEFAULT = &H4
Private Const PRINTER_ATTRIBUTE_DIRECT = &H2
Private Const PRINTER_ATTRIBUTE_ENABLE_BIDI = &H800&
Private Const PRINTER_ATTRIBUTE_LOCAL = &H40
Private Const PRINTER_ATTRIBUTE_NETWORK = &H10
Private Const PRINTER_ATTRIBUTE_QUEUED = &H1
Private Const PRINTER_ATTRIBUTE_SHARED = &H8
Private Const PRINTER_ATTRIBUTE_WORK_OFFLINE = &H400
Private Declare Function DeleteDC Lib "gdi32" (ByVal hDC As Long) As Long
Private Const DM_ORIENTATION = &H1&
Private Const DM_PAPERSIZE = &H2&
Private Const DM_DEFAULTSOURCE = &H200&
Private Const DMORIENT_PORTRAIT = 1
Private Const DMORIENT_LANDSCAPE = 2
Private Const GMEM_MOVEABLE = &H2
Private Const GMEM_ZEROINIT = &H40
'
'
' size of a device name string
Private Const CCHDEVICENAME = 32
' size of a form name string
Private Const CCHFORMNAME = 32
'
Private Declare Function GetProfileString Lib "kernel32" Alias
"GetProfileStringA" (ByVal lpAppName As String, ByVal lpKeyName As String,
ByVal lpDefault As String, ByVal lpReturnedString As String, ByVal nSize As
Long) As Long
Private Declare Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long,
ByVal dwBytes As Long) As Long
Private Declare Function GlobalFree Lib "kernel32" (ByVal hMem As Long) 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
'
' ' Constants for PrintDialog
Private Const PD_PRINTSETUP = &H40
Private Const PD_RETURNDC = &H100


Private Type PRINTDLG_TYPE
lStructSize As Long
hwndOwner As Long
hDevMode As Long
hDevNames As Long
hDC As Long
Flags As Long
nFromPage As Integer
nToPage As Integer
nMinPage As Integer
nMaxPage As Integer
nCopies As Integer
hInstance As Long
lCustData As Long
lpfnPrintHook As Long
lpfnSetupHook As Long
lpPrintTemplateName As String
lpSetupTemplateName As String
hPrintTemplate As Long
hSetupTemplate As Long
End Type

Private Type DEVNAMES_TYPE


wDriverOffset As Integer
wDeviceOffset As Integer
wOutputOffset As Integer
wDefault As Integer

extra As String * 780 '3* Max_Path (under NT, can have long
names)
End Type

Private Type DEVMODE_TYPE
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
'
' ' API declarations:
Private Declare Function PrintDialog Lib "comdlg32.dll" Alias
"PrintDlgA" (pPrintDlg As PRINTDLG_TYPE) As Long
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory"
(hpvDest As Any, hpvSource As Any, ByVal cbCopy As Long)
Private Declare Function apiCommDlgExtendedError Lib "comdlg32.dll"
Alias "CommDlgExtendedError" () As Long

Public Function EnumPrintersLevel2() As Variant
Dim Success As Boolean
Dim cbRequired As Long
Dim cbBuffer As Long
Dim pntr() As PRINTER_INFO_2
Dim nEntries As Long
Dim c As Long
Dim sAttr As String
Dim varReturn() As Variant
Dim dummy As PRINTER_INFO_2

#If Not fishDebug Then 'set fishDebug to true when in IDE to break on
errors
On Error Resume Next
#End If

'To determine the required buffer size, call EnumPrinters with
'cbBuffer set to zero. EnumPrinters fails, and Err.LastDLLError
'returns ERROR_INSUFFICIENT_BUFFER, filling in the cbRequired
'parameter with the size, in bytes, of the buffer required to
'hold the array of structures and their data.
Call EnumPrintersNew(PRINTER_ENUM_CONNECTIONS Or PRINTER_ENUM_LOCAL,
vbNullString, PRINTER_LEVEL2, 0, 0, cbRequired, nEntries)

'The strings pointed to by each PRINTER_INFO_2 struct's members
'reside in memory after the end of the array of structs. So we're
'not only allocating memory for the structs themselves, but all the
'strings pointed to by each struct's member as well.
ReDim pntr((cbRequired \ Len(dummy)))

'Set cbBuffer equal to the size of the buffer
cbBuffer = cbRequired

'Enumerate the printers. If the function succeeds,
'the return value is nonzero. If the function fails,
'the return value is zero.
If EnumPrintersNew(PRINTER_ENUM_CONNECTIONS Or PRINTER_ENUM_LOCAL,
vbNullString, PRINTER_LEVEL2, pntr(0), cbBuffer, cbRequired, nEntries) Then
ReDim varReturn(0 To nEntries - 1, 1 To 4)
For c = 0 To nEntries - 1

With pntr(c)
sAttr = ""
If (.Attributes And PRINTER_ATTRIBUTE_DEFAULT) Then sAttr =
"default "
If (.Attributes And PRINTER_ATTRIBUTE_DIRECT) Then sAttr = sAttr
& "direct "
If (.Attributes And PRINTER_ATTRIBUTE_ENABLE_BIDI) Then sAttr =
sAttr & "bidirectional "
If (.Attributes And PRINTER_ATTRIBUTE_LOCAL) Then sAttr = sAttr
& "local "
If (.Attributes And PRINTER_ATTRIBUTE_NETWORK) Then sAttr =
sAttr & "net "
If (.Attributes And PRINTER_ATTRIBUTE_QUEUED) Then sAttr = sAttr
& "queued "
If (.Attributes And PRINTER_ATTRIBUTE_SHARED) Then sAttr = sAttr
& "shared "
If (.Attributes And PRINTER_ATTRIBUTE_WORK_OFFLINE) Then sAttr =
sAttr & "offline "

varReturn(c, 1) = GetStrFromPtrA(.pPrinterName)
varReturn(c, 2) = GetStrFromPtrA(.pPortName)
varReturn(c, 3) = GetStrFromPtrA(.pDriverName)
varReturn(c, 4) = GetStrFromPtrA(.pShareName)

End With

Next c

Else
'Error enumerating printers.
End If 'EnumPrinters

EnumPrintersLevel2 = varReturn

End Function

Public Function GetStrFromPtrA(ByVal lpszA As Long) As String
GetStrFromPtrA = String$(lstrlenA(ByVal lpszA), 0)
Call lstrcpyA(ByVal GetStrFromPtrA, ByVal lpszA)
End Function

'***********************************
'Method 2
'this shows the printer setup dialog box, returning the long printer name,
driver name and port name (+ other stuff)
'**********************************
Public Function ShowPrinter(frmOwner As Form, ByVal PrintFlags As Long,
ByRef sPrinterName As String, ByRef sDriverName As String, ByRef sPortName
As String, ByRef lngOrientation As Long, ByRef lngPaperSize As Long, ByRef
lngPaperBin As Long) As Boolean
Dim pPrintDlg As PRINTDLG_TYPE
Dim pDevMode As DEVMODE_TYPE
Dim pDevName As DEVNAMES_TYPE

Dim lpDevMode As Long, lpDevName As Long
Dim bReturn As Long
Dim strSetting As String
Dim pDeviceName As Long
Dim nDeviceNameLen As Long
Dim pPrinterName As String
Dim pDriverName As String
Dim pPortName As String

#If Not fishDebug Then
On Error Resume Next
#End If

' Use PrintSetupDialog to get the handle to a memory
' block with a DevMode and DevName structures
pPrintDlg.lStructSize = Len(pPrintDlg)
pPrintDlg.hwndOwner = frmOwner.hWnd
pPrintDlg.Flags = PrintFlags

' Set the current orientation setting
pDevMode.dmDeviceName = sPrinterName
pDevMode.dmSize = Len(pDevMode)
pDevMode.dmFields = DM_ORIENTATION Or DM_PAPERSIZE Or DM_DEFAULTSOURCE
'set the flag indicating changing orientation, papersize, bin
pDevMode.dmOrientation = lngOrientation
pDevMode.dmPaperSize = lngPaperSize
pDevMode.dmDefaultSource = lngPaperBin

' Allocate memory for the initialization hDevMode structure
' and copy the settings gathered above into this memory
pPrintDlg.hDevMode = GlobalAlloc(GMEM_MOVEABLE Or GMEM_ZEROINIT,
Len(pDevMode))
lpDevMode = GlobalLock(pPrintDlg.hDevMode)
If lpDevMode > 0 Then
CopyMemory ByVal lpDevMode, pDevMode, Len(pDevMode)
bReturn = GlobalUnlock(pPrintDlg.hDevMode)
End If

' Set the current driver, device, and port name strings

With pDevName
.wDriverOffset = 8 'length of initial structure; driver name
exists after the initial structure
.wDeviceOffset = .wDriverOffset + 1 + Len(sDriverName) 'device
name exists after driver name and Chr$(0)
.wOutputOffset = .wDeviceOffset + 1 + Len(sPrinterName) 'port
name exists after device name and chr$(0) 'this was wrong in MSKB!
.wDefault = 0
.extra = sDriverName & Chr(0) & sPrinterName & Chr(0) & sPortName
& Chr(0)
End With

'Allocate memory for the initial hDevName structure
'and copy the settings gathered above into this memory
pPrintDlg.hDevNames = GlobalAlloc(GMEM_MOVEABLE Or GMEM_ZEROINIT,
Len(pDevName))
lpDevName = GlobalLock(pPrintDlg.hDevNames)
If lpDevName > 0 Then
CopyMemory ByVal lpDevName, pDevName, Len(pDevName)
bReturn = GlobalUnlock(lpDevName)
End If

' Call the print dialog up and let the user make changes
If PrintDialog(pPrintDlg) Then
If pPrintDlg.hDC <> 0 Then 'paranoia to avoid creating handles
that don't get used or destroyed (isn't necessary unless use return DC flag)
DeleteDC pPrintDlg.hDC
End If

' First get the DevName structure.
lpDevName = GlobalLock(pPrintDlg.hDevNames) 'returns pointer to
the devname structure
CopyMemory pDevName, ByVal lpDevName, Len(pDevName)

'under WinNT and above, printers can have long names. Must get
'names from the DevName structure, rather than the devmode
structre
'Get the device name from the pDevName structure
pDeviceName = lpDevName + pDevName.wDeviceOffset
pPrinterName = GetStrFromPtrA(pDeviceName)
'get the port from the pDevName structure
pDeviceName = lpDevName + pDevName.wOutputOffset
pPortName = GetStrFromPtrA(pDeviceName)
'get the driver from the pDevName structure
pDeviceName = lpDevName + pDevName.wDriverOffset
pDriverName = GetStrFromPtrA(pDeviceName)
'free up the memory
bReturn = GlobalUnlock(lpDevName)
GlobalFree pPrintDlg.hDevNames


' Next get the DevMode structure and set the printer
' properties appropriately
lpDevMode = GlobalLock(pPrintDlg.hDevMode)
CopyMemory pDevMode, ByVal lpDevMode, Len(pDevMode)
bReturn = GlobalUnlock(pPrintDlg.hDevMode)
GlobalFree pPrintDlg.hDevMode
lngOrientation = pDevMode.dmOrientation
lngPaperSize = pDevMode.dmPaperSize
lngPaperBin = pDevMode.dmDefaultSource
'could use devmode structure to return truncated printer name (as
per MSKB!) - this will cause problems under NT!

'return the values from devname to byref variables
sPrinterName = pPrinterName
sPortName = pPortName
sDriverName = pDriverName

ShowPrinter = True
Else
bReturn = apiCommDlgExtendedError()
If bReturn <> 0 Then
LogError bReturn, "An error occurred calling PrintDialog",
"modPrinting:ShowPrinter" 'my custom error logging routine
End If
ShowPrinter = False
End If

End Function

Have fun!


"Andy stewartson" <andy.st...@baesystems.com> wrote in message
news:3B418DEB...@baesystems.com...

Andy stewartson

unread,
Jul 4, 2001, 7:55:29 AM7/4/01
to
René

Thanks for code, I did not managed to get it working, do you have a copy
which you could email to me?

Ralf Maul

unread,
Jul 6, 2001, 11:14:36 AM7/6/01
to
Hello to all,

my name is Ralf and i am programming
a Setup - Guide for a special driver. In
this case i need to find a functionality which
can tell me if the current user on any machine
has administrator permissions.
Can anyone of you please help me ?

ralf...@viper-systems.com


Hercules Gunter

unread,
Jul 6, 2001, 12:21:40 PM7/6/01
to
I asked a similar question, and was referred here:
http://aisalogic.com/codedocs/, where there are code samples
which allow you to do things like enumerate user
permissions.

Hercules Gunter

Brad Martinez

unread,
Jul 6, 2001, 2:04:45 PM7/6/01
to
Ralf

>i need to find a functionality which
>can tell me if the current user on any machine
>has administrator permissions.

There are these, but all are undocumented. The first:

' returns a BOOL
Declare Function IsUserAnAdmin Lib "shell32" Alias "#680" () As Long

is exported only in NT versions of shell32.dll and should be error
trapped as VB will throw Err.Number 453 "Specified DLL function
not found" when called on Win9x/ME.

Then there's also:

' rtns BOOL, sets ERROR_CALL_NOT_IMPLEMENTED (120) error code on Win9x
Declare Function IsUserAdmin Lib "setupapi" () As Long

that I believe (but am not completely certain) is exported in all
Setupapi.dll versions. The only hitch is that though Setupapi.dll
is distributed and installed with most major MS software and SPs
(IE4, VS, Office) and all OSs beginning with Win95 OSR 2.5, it
is not included as part of stock Win95. Ergo it's call should also
be error trapped.

Finally there's the "IsNTAdmin" export in Advpack.dll that takes
8 bytes (two Long) for params, but I have yet to figure out what
the call's param want to be. And though Advpack.dll is even more
prevalent than Setupapi.dll but still not included as part of stock
Win95, and given the above two calls, its usefulness is pretty
redundant...

--
Brad Martinez, http://www.mvps.org
Please direct questions/replies to the newsgroup

Michael (michka) Kaplan

unread,
Jul 6, 2001, 2:15:41 PM7/6/01
to
I have used the advpack.dll function in the past, passing Byval 0& for both
params, and it has always worked.

Later I just converted a routine to VB to do the job directly. :-)


--
MichKa

Michael Kaplan
Trigeminal Software, Inc.
http://www.trigeminal.com/


"Brad Martinez" <bt...@msn.com.nospam> wrote in message
news:OWkXTYkBBHA.1916@tkmsftngp07...

0 new messages