Issue Grabbing Printer Settings from Windows Printer Selection Box

I originally created this post a while ago : How to set Paper Size being passed from Printer Selection , and I never got it to work.

Here is my code:

PREPARE-PRINTER-WITH-STANDARD-PRINTER-DIALOG.
CALL "P$SETDIALOG" USING PrintDialog.
CALL "P$DisplayDialog".

IF DIALOG-RETURN = 0
    move SET-DEFAULT-PRINTER to default-option
    move dpb-len of MyDefaultPrinterBrowser to dp-len
    move dpb-body of MyDefaultPrinterBrowser(1:dp-len) o dp-body
    call "PC_PRINTER_SET_DEFAULT" using by value default-option
                                                                 by reference MyDefaultPrinter
     PERFORM OPEN-PRINTER-PARA
END-IF.

What I would like to do is grab what was changed in the Windows Printer selection box, and have it print correctly from my printer.  I found that there was a patch back in 2022 that fixed the issues I was having with this: https://portal.microfocus.com/s/article/KM000011471?language=en_US

But it does not tell me how to implement it.  I know I need to send an "PC_PRINTER_DEFAULT_PROPERTIES" command to the printer before setting the "PC_PRINTER_SET_DEFAULT", but I am not sure how to grab the information I need.   In RM COBOL we didn't need to do this - it just automatically did it. 

 

Because of all of this - We had to create our own printer dialog box - and it is not working correctly either - In that program - Whenever I select to change the number of copies - it overrides the Paper Orientation that was set in the program and uses what the default is on the printer. 

  • 0

    I would also like to add that "P$DISPLAYDIALOG" in my program is a program.  This is what it does.

    ENTRY "P$DisplayDialog".
           move BROWSE-DEFAULT-PRINTER to default-option
           move 127 to dp-len
           call "PC_PRINTER_SET_DEFAULT" using by value default-option
                                                                       by reference MyDefaultPrinterBrowser
                                                                       returning Printer-RetCode

           IF PRINTER-RETCODE = 0
                    MOVE 0 TO DIALOG-RETURN
           ELSE
                    MOVE 1 TO DIALOG-RETURN
           END-IF.

    goback.

    BROWSE-DEFAULT-PRINTER is set to h"0002" - which calls an old looking version of the printer selection box.  Is there another command I can send to bring up the newer one? 

    I know there was an "P$DISPLAYDIALOG" program in RM COBOL - but I can't find any documentation on what that did. 

  • Suggested Answer

    0   in reply to 

    Hi Amy,

    The PC_PRINTER_SET_DEFAULT call was fixed in V5.0 PU26 and higher versions so that when you make the first call to browse for the printer any changes made to the properties in the Printer dialog box will be set for the printer when you do the second call to set the defaults.

    We also changed the Printer dialog box that is used in managed code, so it is the standard one used in native code as well.

    I am not sure if the dialog box change made it into the PU26 or if it is only available in later product release.

    I just tested the following program here and it all worked fine under 9.0

           identification division.
           program-id. Program1.
    
           environment division.
           configuration section.
               select print-file assign to PRINTER
                                 file status is file-status.
           data division.
           file section.
           fd print-file.
           01 print-rec  pic x(20).
           working-storage section.
           01 file-status pic x(2) value spaces.
           01 printer-default.
              03 pd-printer-name-grp.
                 05 pd-printer-name-len    pic x(2) comp-5.
                 05 pd-printer-name        pic x(128).
              03 pd-printer-browse REDEFINES pd-printer-name-grp.
                 05 pd-printer-browse-hwnd pic x(4) comp-5.
                 05 pd-printer-browse-namelen pic x(2) comp-5.
                 05 pd-reserved            pic x(2) comp-5.
                 05 pd-printer-browse-name pic x(128).
    
           01 Printer-RetCode         pic 9(4) comp-5.
           01 default-option          pic x(4) comp-5.
              
           78 SET-DEFAULT-PRINTER     value h"0001".
           78 BROWSE-DEFAULT-PRINTER  value h"0002".
           01 name-len                 pic x(2) comp-5 value zeroes.
           procedure division.
                  
               perform 2 times
                  move BROWSE-DEFAULT-PRINTER to default-option
                  initialize printer-default
                  move zeroes to pd-printer-browse-hwnd
                  call "PC_PRINTER_SET_DEFAULT" using
                     by value default-option
                     by reference printer-default
                     returning Printer-RetCode
                  end-call
    
                  if Printer-RetCode not equal zero
                     display "Unable to browse for a default printer"
                     display " + Retcode = " Printer-RetCode
                     stop run
                  end-if
                  
                  display "Browse Printer : "
                     pd-printer-name(1:pd-printer-name-len)
    
                  move SET-DEFAULT-PRINTER to default-option
                  
                  call "PC_PRINTER_SET_DEFAULT" using
                         by value default-option
                         by reference pd-printer-name-grp
                         returning Printer-RetCode
                  end-call
    
                  if Printer-RetCode not equal zero
                     display "Unable to set a default printer"
                     display " + Retcode = " Printer-RetCode
                     stop run
                  end-if
                  open output print-file
                  display file-status
                  move all "A" to print-rec
                  write print-rec
                  display file-status
                  close print-file
               end-perform
               goback.
    
    .

    Chris Glazier
    Rocket Software - Principal Technical Support Specialist
    If you found this post useful, give it a “Like” or click on "Verify Answer" under the "More" button