Consulting

Results 1 to 5 of 5

Thread: VB "The Printer is not connected"

  1. #1
    VBAX Expert Dave's Avatar
    Joined
    Mar 2005
    Posts
    835
    Location

    VB "The Printer is not connected"

    How to use VB to determine if there is actually a printer connected to the pc? I'd like to be able to provide the user a warning message and exit the task if a printer is not actually connected to the pc. I've been kicking this around occasionally for several years now. Listing the available printers and their status apparently can be done. So it seems that whether a printer is physically connected should be easy... seems not. I don't understand the spooler thing and I was hoping that someone had already invented the wheel. I would be very gratefule to resolve this before I become too old and senile to remember what the the question is. If anyone has a wheel or maybe some sound advice on why to give up this project, I'd really appreciate your input. Dave

  2. #2
    VBAX Tutor
    Joined
    Mar 2014
    Posts
    210
    Location
    Here's some code to list the printers.

    Private Const HWND_BROADCAST As Long = &HFFFF&
    Private Const WM_WININICHANGE As Long = &H1A
    ' The following code allows one to read, and write to the WIN.INI files
    ' In win 2000 the printer settings are actually in the registry. However, windows
    ' handles this correctly
    '
    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 WriteProfileString Lib "kernel32" _
       Alias "WriteProfileStringA" _
      (ByVal lpszSection As String, _
       ByVal lpszKeyName As String, _
       ByVal lpszString As String) As Long
    Private Declare Function SendMessage Lib "user32" _
       Alias "SendMessageA" _
      (ByVal hwnd As Long, _
       ByVal wMsg As Long, _
       ByVal wParam As Long, _
       lparam As Any) As Long
    
    
    Public Sub ListPrinters()
       Debug.Print GetDefaultPrinter
       Debug.Print GetPrinters
       
    End Sub
    Function GetPrinters() As String
       
       ' this routine returns a list of printers, separated by
       ' a ";", and thus the results are suitable for stuffing into a combo box
       
       Dim strBuffer  As String
       Dim strOnePtr  As String
       Dim intPos     As Integer
       Dim lngChars   As Long
       
       strBuffer = Space(2048)
       lngChars = GetProfileString("PrinterPorts", vbNullString, "", strBuffer, Len(strBuffer))
       
       If lngChars > 0 Then
          intPos = InStr(strBuffer, Chr(0))
         Do While intPos > 1
            strOnePtr = Left(strBuffer, intPos - 1)
            strBuffer = Mid(strBuffer, intPos + 1)
            If GetPrinters <> "" Then GetPrinters = GetPrinters & vbCrLf
            'Debug.Print strOnePtr
            GetPrinters = GetPrinters & strOnePtr
            intPos = InStr(strBuffer, Chr(0))
            
         Loop
       Else
          GetPrinters = ""
       End If
       
     End Function

  3. #3
    VBAX Expert Dave's Avatar
    Joined
    Mar 2005
    Posts
    835
    Location
    Thanks ranman256. The code posted works well to list the available printers. Unfortunately, this is not the same as providing some indication as to whether a printer is actually connected to the pc. I'm still looking for some way to determine if the printer is physically connected to the pc. Dave

  4. #4
    VBAX Expert Dave's Avatar
    Joined
    Mar 2005
    Posts
    835
    Location
    Kicking around a new approach. Maybe with a timer, check and see if the print job is still waiting to be printed. If it is then kill it and provide the user with a msgbox notification that the printer failed. How to kill it I'm guessing will be the hard part. Maybe the great Google has the answers. I'll post if I resolve this and of course I'm still looking for any sound advice. Dave

  5. #5
    VBAX Expert Dave's Avatar
    Joined
    Mar 2005
    Posts
    835
    Location
    I'm going to use up a bit of webspace as it seems there is no easy "The Printer is not connected" code. This code seems to do what I want it to do... it will identify the default printer error and then remove the print job from from the print queue. I'm currently using XL03 and Vista with an HP printer. There doesn't seem to be that much communication between this printer and OS in that the printer may be on error but the print queue will still indicate that the job is printing. Anyways, the code contains some Wait commands which I don't like but seem to need for the OS and printer to communicate. I'm guessing PC speed and communication speed with the printer may alter the time needed to Wait. There are also many varied approaches to setting up a printer (like a network printer) and I have no idea whether this code is useful. I will gladly appreciate if anyone would trial the code in a blank wb and post there outcome along with their XL version, OS, printer and print set up. Thanks for any assistance. Dave
    Module code.....
    Option Explicit
    Public JobNumber As Long
    Public NameOfPrinter As String
    Private JobCnt As Integer
    Private PrinterStr As String
    Private JobStr As String
    Private PrevJobError As Boolean
    Private Declare Function lstrcpy Lib "kernel32" _
    Alias "lstrcpyA" _
    (ByVal lpString1 As String, _
    ByVal lpString2 As String) _
    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 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 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 SetJob Lib "winspool.drv" Alias _
               "SetJobA" (ByVal hPrinter As Long, _
                          ByVal JobId As Long, _
                          ByVal Level As Long, _
                          pJob As Long, _
                          ByVal Command As Long) As Long
    Private Declare Function EnumJobs 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
    ' constants for PRINTER_DEFAULTS structure
    Private Enum PrinterAccessRights
    PRINTER_ACCESS_ADMINISTER = &H4
    PRINTER_ACCESS_USE = &H8
    PRINTER_ALL_ACCESS = &HF000C
    End Enum
    Private Enum PrintJobControlCommands
    JOB_CONTROL_PAUSE = 1
    JOB_CONTROL_RESUME = 2
    JOB_CONTROL_cancel = 3
    JOB_CONTROL_RESTART = 4
    JOB_CONTROL_delete = 5
    JOB_CONTROL_SENT_TO_PRINTER = 6
    JOB_CONTROL_LAST_PAGE_EJECTED = 7
    End Enum
    Private Type PRINTER_DEFAULTS
    pDatatype As String
    pDevMode As Long
    DesiredAccess As Long
    End Type
    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_2
    JobId As Long
    pPrinterName As Long
    pMachineName As Long
    pUserName As Long
    pDocument As Long
    pNotifyName As Long
    pDatatype As Long
    pPrintProcessor As Long
    pParameters As Long
    pDriverName As Long
    pDevMode As Long
    pStatus As Long
    pSecurityDescriptor As Long
    Status As Long
    Priority As Long
    Position As Long
    StartTime As Long
    UntilTime As Long
    TotalPages As Long
    Size As Long
    Submitted As SYSTEMTIME
    time As Long
    PagesPrinted 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
    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 Const ERROR_INSUFFICIENT_BUFFER = 122
    Private Const PRINTER_STATUS_BUSY = &H200
    Private Const PRINTER_STATUS_DOOR_OPEN = &H400000
    Private Const PRINTER_STATUS_ERROR = &H2
    Private Const PRINTER_STATUS_INITIALIZING = &H8000
    Private Const PRINTER_STATUS_IO_ACTIVE = &H100
    Private Const PRINTER_STATUS_MANUAL_FEED = &H20
    Private Const PRINTER_STATUS_NO_TONER = &H40000
    Private Const PRINTER_STATUS_NOT_AVAILABLE = &H1000
    Private Const PRINTER_STATUS_OFFLINE = &H80
    Private Const PRINTER_STATUS_OUT_OF_MEMORY = &H200000
    Private Const PRINTER_STATUS_OUTPUT_BIN_FULL = &H800
    Private Const PRINTER_STATUS_PAGE_PUNT = &H80000
    Private Const PRINTER_STATUS_PAPER_JAM = &H8
    Private Const PRINTER_STATUS_PAPER_OUT = &H10
    Private Const PRINTER_STATUS_PAPER_PROBLEM = &H40
    Private Const PRINTER_STATUS_PAUSED = &H1
    Private Const PRINTER_STATUS_PENDING_DELETION = &H4
    Private Const PRINTER_STATUS_PRINTING = &H400
    Private Const PRINTER_STATUS_PROCESSING = &H4000
    Private Const PRINTER_STATUS_TONER_LOW = &H20000
    Private Const PRINTER_STATUS_USER_INTERVENTION = &H100000
    Private Const PRINTER_STATUS_WAITING = &H2000
    Private Const PRINTER_STATUS_WARMING_UP = &H10000
    Private Const JOB_STATUS_PAUSED = &H1
    Private Const JOB_STATUS_ERROR = &H2
    Private Const JOB_STATUS_DELETING = &H4
    Private Const JOB_STATUS_SPOOLING = &H8
    Private Const JOB_STATUS_PRINTING = &H10
    Private Const JOB_STATUS_OFFLINE = &H20
    Private Const JOB_STATUS_PAPEROUT = &H40
    Private Const JOB_STATUS_PRINTED = &H80
    Private Const JOB_STATUS_DELETED = &H100
    Private Const JOB_STATUS_BLOCKED_DEVQ = &H200
    Private Const JOB_STATUS_USER_INTERVENTION = &H400
    Private Const JOB_STATUS_RESTART = &H800
    Private Function PtrCtoVbString(Add As Long) As String
    Dim sTemp As String * 512
    Dim x As Long
    x = 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
    Private Function CheckPrinterStatus(PI2Status As Long) As String
    Dim TempStr As String
    If PI2Status = 0 Then   ' Return "Ready"
    CheckPrinterStatus = "Printer Status = Ready" & vbCrLf
    Else
    TempStr = vbNullString
    If (PI2Status And PRINTER_STATUS_BUSY) Then
    TempStr = TempStr & "Busy  "
    End If
    If (PI2Status And PRINTER_STATUS_DOOR_OPEN) Then
    TempStr = TempStr & "Printer Door Open  "
    End If
    If (PI2Status And PRINTER_STATUS_ERROR) Then
    TempStr = TempStr & "Printer Error  "
    End If
    If (PI2Status And PRINTER_STATUS_INITIALIZING) Then
    TempStr = TempStr & "Initializing  "
    End If
    If (PI2Status And PRINTER_STATUS_IO_ACTIVE) Then
    TempStr = TempStr & "I/O Active  "
    End If
    If (PI2Status And PRINTER_STATUS_MANUAL_FEED) Then
    TempStr = TempStr & "Manual Feed  "
    End If
    If (PI2Status And PRINTER_STATUS_NO_TONER) Then
    TempStr = TempStr & "No Toner  "
    End If
    If (PI2Status And PRINTER_STATUS_NOT_AVAILABLE) Then
    TempStr = TempStr & "Not Available  "
    End If
    If (PI2Status And PRINTER_STATUS_OFFLINE) Then
    TempStr = TempStr & "Off Line  "
    End If
    If (PI2Status And PRINTER_STATUS_OUT_OF_MEMORY) Then
    TempStr = TempStr & "Out of Memory  "
    End If
    If (PI2Status And PRINTER_STATUS_OUTPUT_BIN_FULL) Then
    TempStr = TempStr & "Output Bin Full  "
    End If
    If (PI2Status And PRINTER_STATUS_PAGE_PUNT) Then
    TempStr = TempStr & "Page Punt  "
    End If
    If (PI2Status And PRINTER_STATUS_PAPER_JAM) Then
    TempStr = TempStr & "Paper Jam  "
    End If
    If (PI2Status And PRINTER_STATUS_PAPER_OUT) Then
    TempStr = TempStr & "Paper Out  "
    End If
    If (PI2Status And PRINTER_STATUS_OUTPUT_BIN_FULL) Then
    TempStr = TempStr & "Output Bin Full  "
    End If
    If (PI2Status And PRINTER_STATUS_PAPER_PROBLEM) Then
    TempStr = TempStr & "Page Problem  "
    End If
    If (PI2Status And PRINTER_STATUS_PAUSED) Then
    TempStr = TempStr & "Paused  "
    End If
    If (PI2Status And PRINTER_STATUS_PENDING_DELETION) Then
    TempStr = TempStr & "Pending Deletion  "
    End If
    If (PI2Status And PRINTER_STATUS_PRINTING) Then
    TempStr = TempStr & "Printing  "
    End If
    If (PI2Status And PRINTER_STATUS_PROCESSING) Then
    TempStr = TempStr & "Processing  "
    End If
    If (PI2Status And PRINTER_STATUS_TONER_LOW) Then
    TempStr = TempStr & "Toner Low  "
    End If
    If (PI2Status And PRINTER_STATUS_USER_INTERVENTION) Then
    TempStr = TempStr & "User Intervention  "
    End If
    If (PI2Status And PRINTER_STATUS_WAITING) Then
    TempStr = TempStr & "Waiting  "
    End If
    If (PI2Status And PRINTER_STATUS_WARMING_UP) Then
    TempStr = TempStr & "Warming Up  "
    End If
    'Did you find a known status?
    If Len(TempStr) = 0 Then
    TempStr = "Unknown Status of " & PI2Status
    End If
    'Return the Status
    CheckPrinterStatus = "Printer Status = " & TempStr & vbCrLf
    End If
    End Function
    Private Function CheckPrinter(PrinterName) As String
    Dim hPrinter As Long
    Dim ByteBuf As Long
    Dim BytesNeeded As Long
    Dim PI2 As PRINTER_INFO_2
    Dim JI2 As JOB_INFO_2
    Dim PrinterInfo() As Byte
    Dim JobInfo() As Byte
    Dim result As Long
    Dim LastError As Long
    Dim TempStr As String
    Dim NumJI2 As Long
    Dim pDefaults As PRINTER_DEFAULTS
    Dim I As Integer
    'Set a default return value if no errors occur.
    CheckPrinter = "Printer info retrieved"
    'Set desired access security setting.
    pDefaults.DesiredAccess = PRINTER_ACCESS_USE
    'Call API to get a handle to the printer.
    result = OpenPrinter(PrinterName, hPrinter, pDefaults)
    If result = 0 Then
    'If an error occurred, display an error and exit sub.
    CheckPrinter = "Cannot open printer " & PrinterName & _
    ", Error: " & Err.LastDllError
    Exit Function
    End If
    'Init BytesNeeded
    BytesNeeded = 0
    'Clear the error object of any errors.
    Err.Clear
    'Determine the buffer size that is needed to get printer info.
    result = GetPrinter(hPrinter, 2, 0&, 0&, BytesNeeded)
    'Check for error calling GetPrinter.
    If Err.LastDllError <> ERROR_INSUFFICIENT_BUFFER Then
    'Display an error message, close printer, and exit sub.
    CheckPrinter = " > GetPrinter Failed on initial call! <"
    ClosePrinter hPrinter
    Exit Function
    End If
    ReDim PrinterInfo(1 To BytesNeeded)
    ByteBuf = BytesNeeded
    'Call GetPrinter to get the status.
    result = GetPrinter(hPrinter, 2, PrinterInfo(1), ByteBuf, _
    BytesNeeded)
    'Check for errors.
    If result = 0 Then
    'Determine the error that occurred.
    LastError = Err.LastDllError()
    'Display error message, close printer, and exit sub.
    CheckPrinter = "Couldn't get Printer Status!  Error = " _
    & LastError
    ClosePrinter hPrinter
    Exit Function
    End If
    'Copy contents of printer status byte array into a
    'PRINTER_INFO_2 structure to separate the individual elements.
    CopyMemory PI2, PrinterInfo(1), Len(PI2)
    'Check if printer is in ready state.
    PrinterStr = CheckPrinterStatus(PI2.Status)
    'Call API to get size of buffer that is needed.
    result = EnumJobs(hPrinter, 0&, &HFFFFFFFF, 2, ByVal 0&, 0&, _
    BytesNeeded, NumJI2)
    'Check if there are no current jobs, and then display appropriate message.
    If BytesNeeded = 0 Then
    JobStr = "No Print Jobs!"
    Else
    'Redim byte array to hold info about print job.
    ReDim JobInfo(0 To BytesNeeded)
    'Call API to get print job info.
    result = EnumJobs(hPrinter, 0&, &HFFFFFFFF, 2, JobInfo(0), _
    BytesNeeded, ByteBuf, NumJI2)
    'Check for errors.
    If result = 0 Then
    'Get and display error, close printer, and exit sub.
    LastError = Err.LastDllError
    CheckPrinter = " > EnumJobs Failed on second call! <  Error = " _
      & LastError
    ClosePrinter hPrinter
    Exit Function
    End If
    JobCnt = 0
    'Copy contents of print job info byte array into a
    'JOB_INFO_2 structure to separate the individual elements.
    For I = 0 To NumJI2 - 1   ' Loop through jobs and walk the buffer
    CopyMemory JI2, JobInfo(I * Len(JI2)), Len(JI2)
    JobNumber = JI2.JobId
    JobCnt = JobCnt + 1
    TempStr = vbNullString
    'Check for a ready state.
    If JI2.pStatus = 0& Then   ' If pStatus is Null, check Status.
    If JI2.Status = 0 Then
    TempStr = TempStr & "Ready!  " & vbCrLf
    Else  'Check for the various print job states.
    If (JI2.Status And JOB_STATUS_SPOOLING) Then
    TempStr = TempStr & "Spooling  "
    End If
    If (JI2.Status And JOB_STATUS_OFFLINE) Then
    TempStr = TempStr & "Off line  "
    End If
    If (JI2.Status And JOB_STATUS_PAUSED) Then
    TempStr = TempStr & "Paused  "
    End If
    If (JI2.Status And JOB_STATUS_ERROR) Then
    TempStr = TempStr & "Error  "
    End If
    If (JI2.Status And JOB_STATUS_PAPEROUT) Then
    TempStr = TempStr & "Paper Out  "
    End If
    If (JI2.Status And JOB_STATUS_PRINTING) Then
    TempStr = TempStr & "Printing  "
    End If
    If (JI2.Status And JOB_STATUS_USER_INTERVENTION) Then
    TempStr = TempStr & "User Intervention Needed  "
    End If
    If Len(TempStr) = 0 Then
    TempStr = "Unknown Status of " & JI2.Status
    End If
    End If
    Else
    ' Dereference pStatus.
    TempStr = PtrCtoVbString(JI2.pStatus)
    End If
    'Report the Job status.
    JobStr = JobStr & TempStr & vbCrLf
    Next I
    End If
    'Close the printer handle.
    ClosePrinter hPrinter
    End Function
    Public Sub PrintRng(InputRng As Range)
    'prints range "InputRng"
    On Error Resume Next
    InputRng.PrintOut Copies:=1
    If Err.Number <> 0 Then
    On Error GoTo 0
    MsgBox "No Printer available ERROR!"
    Exit Sub
    End If
    'check if Print job successful
    If Not RunPrintRoutine Then
    'remove unsuccessful print job from queue
    Call KillPrintJob(NameOfPrinter, JobNumber)
    End If
    End Sub
    Public Function RunPrintRoutine() As Boolean
    'check if Print job successful
    'true = print job success
    'false = print job error
    Dim Temp As Variant
    PrevJobError = False
    JobStr = vbNullString
    Temp = Split(Application.ActivePrinter, "on")
    NameOfPrinter = Left(Temp(0), Len(Temp(0)) - 1)
    'check for communication with printer
    If CheckPrinter(NameOfPrinter) = "Printer info retrieved" Then
    JobStr = vbNullString
    'wait for printer status update AFTER the print command
    Application.Wait (Now + TimeValue("0:00:02"))
    'return the printer status AFTER the print command
    CheckPrinter (NameOfPrinter)
    If Left(JobStr, 5) = "Error" Then
    RunPrintRoutine = False
    'check for previous job error
    If JobCnt <> 1 Then
    MsgBox "Previous Printing Job Error!" & vbCrLf _
    & "Print Job Removed from Queue!"
    'if error is "ERROR - Sent to Printer"
    'no persistant print job exists
    If Left(Right(JobStr, 12), 8) <> "Printing" Then
    'delete from queue only once
    PrevJobError = True
    End If
    End If
    End If
    If Left(Right(PrinterStr, 7), 5) <> "Ready" Then
    RunPrintRoutine = False
    Else
    If Left(JobStr, 14) = "No Print Jobs!" Then
    RunPrintRoutine = True
    MsgBox "Print Job Success!"
    Else
    If Left(JobStr, 8) = "Printing" Then
    'If more than 1 job on queue
    If JobCnt <> 1 Then
    '*Possible error re. Printer maybe stalled on previous task.
    'even though Print job sent to queue success
    RunPrintRoutine = False
    PrevJobError = True
    MsgBox "Previous Printing Job Error!" & vbCrLf _
    & "Print Job Removed from Queue!"
    Else
    RunPrintRoutine = True
    MsgBox "Print Job Success!"
    End If
    End If
    End If
    End If
    Else 'CheckPrinter NOT successful (no printer retrieved)
    MsgBox "Communication Error with Printer!"
    End If
    End Function
    Public Sub KillPrintJob(ByVal PrinterDeviceName As String, ByVal idJob As Long)
    'Remove Print Job from queue
    Dim lRet As Long
    Dim mhPrinter As Long
    Dim paAll As PRINTER_DEFAULTS
    paAll.DesiredAccess = PRINTER_ALL_ACCESS
    Call OpenPrinter(PrinterDeviceName, mhPrinter, paAll)
    If mhPrinter <> 0 Then
    'remove print job from queue
    lRet = SetJob(mhPrinter, idJob, 0, 0, JOB_CONTROL_delete)
    'if error caused by this print job (ie.not a Previous Print job)
    If Not PrevJobError Then
    'remove persistant Error to printer msg
    Application.Wait (Now + TimeValue("0:00:10"))
    lRet = SetJob(mhPrinter, idJob, 0, 0, JOB_CONTROL_delete)
    If JobCnt = 1 Then
    MsgBox "The Printer had an Error!" & vbCrLf _
    & "Print Job Removed from Queue!"
    End If
    End If
    Call ClosePrinter(mhPrinter)
    End If
    End Sub
    To operate...
    'set range address to suite
    Call PrintRng(Sheets("sheet1").Range("A1:J47"))
    ***Please note that much of the code is "borrowed" and I apologize if I have not properly acknowleged others contibutions.

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •