Announcement

Collapse
No announcement yet.

DDE help needed with PDF silent printing

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

  • DDE help needed with PDF silent printing

    Don't know DDE but Acrobat Reader supports a FilePrintSlient message which is all I'm interested in.
    Code:
    DDE messages
    Adobe Reader supports the following DDE messages:
    ●AppExit
    ●CloseAllDocs
    ●DocClose
    ●DocGoTo
    ●DocGoToNameDest
    ●DocOpen
    ●FileOpen
    ●FileOpenEx
    ●FilePrint
    ●FilePrintEx
    ●FilePrintSilent
    ●FilePrintSilentEx
    ●FilePrintTo
    ●FilePrintToEx
    COM

    PDF browser controls are available through the AxAcroPDFLib.AxAcroPDF interface, which provides the following methods used to programmatically control the PDF document window:

    The COM library is AxAcroPDFLib.AxAcroPDF interface, but I can find where it's located. It doesn't show in the PB COM browser though I've installed Adobe Reader.

    Need a tutorial on DDE. Tried Florent's post. It compiled under 4.01 but it could not find the entry point in USER32.DLL.

    Like a million other people I'd like to find a way I could package into my program a silent printing of PDF's I create that would be compatible with Adobe reader 5-9.

    Bob Mechler

  • #2
    Can't help with the COM, but ...

    There are DDE examples in source code forum
    AND
    Here is something I recently wrote for myself to test a third-party DDE server (sounds familiar?) to see exactly what the heck it was doing...
    Code:
    #IF 0
    ' FILE: DDETEST2.BAS for PB/CC 5.0
    '  FROM: DDECLNT2.BAS for PB/CC v 2.0  (2001)
    ' 11.14.08
    ' from original program, disable attempt to start server
    ' and prompt for BOTH Topic and ITem
    
    #ENDIF
    
    ' don't allow PB to assign REGISTER variables.
    #REGISTER NONE
    #DEBUG    ERROR ON
    #INCLUDE "win32api.inc"     ' <<< SEE NOTES BELOW, AS THERE ARE VARIATIONS IN THE PB-SUPPLIED WIN32API.INC
    
    ' TEXT MESSAGES FROM GETLASTERROR
    DECLARE FUNCTION SystemErrorMessageText (BYVAL ECode AS LONG) AS STRING
    FUNCTION SystemErrorMessageText (BYVAL ECode AS LONG) AS STRING
      LOCAL Buffer AS ASCIIZ * 255
      FormatMessage %FORMAT_MESSAGE_FROM_SYSTEM, BYVAL %NULL, ECode, %NULL, buffer, SIZEOF(buffer), BYVAL %NULL
      FUNCTION = FORMAT$(ECode, "(#####) ") & Buffer
    END FUNCTION
    
    
    DECLARE FUNCTION DDEClientCC () AS LONG
    DECLARE FUNCTION DDEErrorText (BYVAL DMLERR AS LONG) AS STRING
    
    FUNCTION Dde_CallbackFunc(BYVAL uType AS DWORD, BYVAL uFmt AS LONG, BYVAL hConv AS LONG, BYVAL hszTopic AS LONG, BYVAL hszItem AS LONG, BYVAL hData AS LONG, BYVAL dwData1 AS DWORD, BYVAL dwData2 AS DWORD) AS LONG
        'for monitoring and server apps
    END FUNCTION
    ' DECLARE not in my pB/CC Win32API.INC file
    DECLARE FUNCTION ShellExecuteEx LIB "SHELL32.DLL" ALIAS "ShellExecuteExA" (lpShellInfo AS SHELLEXECUTEINFO) AS LONG
    
    FUNCTION WINMAIN (BYVAL hCurInstance  AS LONG, _
                      BYVAL hPrevInstance AS LONG, _
                      BYVAL lpszCmdLine         AS ASCIIZ PTR, _
                      BYVAL nCmdShow      AS LONG) EXPORT AS LONG
    
       DIM ThisFile AS ASCIIZ * 128
       DIM Stat AS LONG
       Stat = GetModuleFileName (hCurInstance, ThisFile, SIZEOF(ThisFile) )
       PRINT "Hello World from Program " & ThisFile
    
       Stat = DDEClientCC
    
       PRINT "Any Key To Exit...."
       J$ = WAITKEY$
    
    END FUNCTION
    
    FUNCTION DDEClientCC () AS LONG
        LOCAL i AS LONG
        LOCAL lId AS LONG
        LOCAL hDDEConv AS LONG
        LOCAL hDDEService AS LONG
        LOCAL hDDETopic AS LONG
        LOCAL hDDEItem AS LONG
        LOCAL lResult AS LONG
        LOCAL tDdeConv AS CONVCONTEXT
    
        LOCAL  szServer AS ASCIIZ * %MAX_PATH          ' The executable name of the DDE server application
        LOCAL  szXls    AS ASCIIZ * %MAX_PATH     ' the full path of the spreadsheet file
        LOCAL  szTopic AS ASCIIZ * %MAX_PATH            ' the (string) topic name as expected by the server
        LOCAL  szItem  AS ASCIIZ * %MAX_PATH            ' the (string) item name for the DDE data request
        LOCAL  szResponse AS ASCIIZ * 4096
        LOCAL  DDELastError AS LONG
        LOCAL  hDDEInit AS LONG
        LOCAL  hInitCode AS LONG
        LOCAL  Execute_Timeout AS LONG
               Execute_TimeOut = 3000&            ' three seconds allowed for a response
    
        DIM J AS STRING
        LET szServer = "excel"                                                    ' the Excel DDE server name
        'LET szServer = "TPPC"
    
        LET szXls = "C:\Software_Development\Testdata\Excel XLS\claims.csv"     ' spreadsheet file name
        LET szTopic = "[claims.csv]claims"   ' Workbook /sheet . EXCEL DOES NOT WORK with paths in there!
    
        '  FOR TESTING 11.13.08
        LSET szXLS = "D:\Clients\Cloyes Gear\_System Processing\ASN Production\Portal\BPITABLES.xls"
    
        'LET szTopic = "[name_dob.xls]Sheet2"   ' Workbook /sheet . EXCEL DOES NOT WORK with paths in there!
                                               ' IF you do "Sheet Two that works, even if there had never been another sheet
                                               ' If sheet name does not exist, you get an invalid parameter error in WaitForInputIdle
        LET szTopic = "[bpitables.xls]dbo_ship_carton"
        ' should prompt for row, col to retrieve
    
    
    ' 7.29.01 Try "System" Topic?
    '    LET szTopic = "System"
        'since we are client only we decline to receive CALLBACKS
        ' I do not understand this, but Mr Heyworth included it.
        hInitCode = DdeInitialize  (lId, CODEPTR(Dde_CallbackFunc), %APPCMD_CLIENTONLY, 0 )
        IF hInitCode <> %DMLERR_NO_ERROR THEN
            PRINT "Failed to initialize DDE & DDEErrorText (hInitCode)
            EXIT FUNCTION
        END IF
    
    
        LOCAL hResult AS LONG, GetDataResult  AS LONG
        LOCAL sYN AS STRING
    
        ' =====================================================================
        '  Enter a prompt/accept loop to test data retrieval
        ' =====================================================================
    
         DO
              LINE INPUT  "server? <CR=quit> ", szServer
              IF lstrlen (szServer) = 0 THEN
                   EXIT DO
              ELSE
                   PRINT "USING$ (Server '&', OK Y/N?", szServer
                   sYN = UCASE$(WAITKEY$)
                   IF sYN = "Y" THEN
                       DO
                          LINE INPUT " Topic?" , szTopic
                          IF lStrLen(szTopic) = 0 THEN
                               EXIT DO
                          ELSE
                             '======================================================================
                             ' As coded, the Server and Topic must both be defined to connect
                             '======================================================================
    
                                'create a DDE string handle for the service
                                hDDEService = DdeCreateStringHandle( lId, szServer, %CP_WINANSI )
                                IF hDDEService = 0 THEN
                                    DDELastError = DDEGetLastError (lID)
                                    PRINT "Cannot create String Handle for service "  & szServer & ". " & DDEErrorText (DDELastError)
                                    GOTO Clean_Up
                                END IF
                                'create string handle for the topic
                                hDDETopic = DdeCreateStringHandle( lId, szTopic, %CP_WINANSI )
                                IF hDDETopic = 0 THEN
                                    DDELastError = DDEGetLastError (lID)
                                    PRINT "Cannot create String Handle for topic "  & szTopic & ". " & DDEErrorText (DDELastError)
                                    GOTO Clean_Up
                                END IF
    
                                'Connect (start conversation)
                                tDdeConv.cb = SIZEOF(tDdeConv)
                                tDdeConv.iCodePage = %CP_WINANSI
                                hDDEConv = DdeConnect( lId, hDDEService, hDDETopic, tDdeConv )
                               ' will not connect if server is not running. If Excel, does not automatically load the correct
                               ' speadsheet (connection fails); returns %DMLERR_NO_CONV_ESTABLISHED (&H400A) under these conditions.
    
                                 ' -------------------------------------------
                                 '  ITEM LOOP
                                 ' -------------------------------------------
    
                                 DO
                                      szResponse = ""
                                      PRINT "Server:" & SzServer & "   Topic:" & szTopic
                                      LINE INPUT "Enter the Item To Retrieve: (CR=quit) ", szItem
                                      ' see above: for Excel, "RnCn" retrieves single cell, "RnCn:RmCm" retrieves a range of cells
    
    
                                      ' IF item = "system"
    
                                      IF szItem = "" THEN      ' Cannot create a DDE string handle for null string
                                         EXIT DO
                                      END IF
                                      ' create the DDE string handle for the item
                                      hDDEItem = DdeCreateStringHandle( lId, szItem, %CP_WINANSI )
                                      IF hDDEItem = 0 THEN
                                         DDELastError = DDEGetLastError (lID)
                                         PRINT "Cannot Create String Handle for Item ==>" & szItem & ". " & DDEErrorText (DDELastError)
                                         GOTO Clean_Up
                                      END IF
                                      ' do the DDE transaction
                                      ' PB/CC 5 gave me a 426 variable expected error on the first zero... I changed to BYVAL NUll.
                                      ' and it compiled. ITs when data are being passed, not true here.
                                      RESET szResponse
                                      LOCAL sREsponse AS STRING
                                      sResponse =  STRING$(4096,$SPC)
                                      lresult = DDeClientTransaction (BYVAL 0&, 0&,hDDEConv,hDDEItem,%CF_TEXT, %XTYP_REQUEST, Execute_timeout, hResult)
                                      IF ISTRUE (lresult) THEN                        ' the return value is the handle of the return value
                                         GetDataResult = DDEGetData (lResult, BYVAL STRPTR(sResponse), LEN(sResponse)-1, 0)
                                         REPLACE $NUL WITH $SPC IN sResponse
                                         sResponse      = RTRIM$(sResponse)
                                         PRINT USING$ ("Success. Returned # bytes value '&'", LEN(sResponse), sResponse)
                                      ELSE
                                         DDELastError =DDEGetLastError(lID)
                                         PRINT "DDEClientTransaction Failed. " & DDEErrorText(DDELastError)
                                      END IF
                                      ' free the string handle (created anew for each request)
                                      IF hDDEItem THEN
                                         CALL DdeFreeStringHandle( lId, hDDEItem )
                                         hDDEItem = 0
                                      END IF
                                 LOOP   ' item level
    
                          END IF   ' if topic length was 0
    
                       LOOP        ' topic level
    
                   END IF    ' if Server "Y" or not
           END IF            ' if server len = 0 or not
         LOOP                ' MIAN
    
    
    Clean_Up:
        IF hDDEConv THEN
            CALL DdeDisconnect( hDDEConv )
        END IF
    
        IF hDDEItem THEN
            CALL DdeFreeStringHandle( lId, hDDEItem )
        END IF
    
        IF hDDETopic THEN
            CALL DdeFreeStringHandle( lId, hDDETopic )
        END IF
    
        IF hDDEService THEN
            CALL DdeFreeStringHandle( lId, hDDEService )
        END IF
    
        CALL DdeUninitialize( lId )
    
        PRINT "Finished with DDE Client"
    
    END FUNCTION
    
    FUNCTION DDEErrorText (BYVAL DMLERR AS LONG) AS STRING
    
       LOCAL W AS STRING
       SELECT CASE DMLERR
    
          CASE %DMLERR_ADVACKTIMEOUT
               W = "ADV_ACK_TIMEOUT"
          CASE  %DMLERR_BUSY
               W = "BUSY"
          CASE %DMLERR_DATAACKTIMEOUT
               W = "DATA_ACK_TIMEOUT"
          CASE %DMLERR_DLL_NOT_INITIALIZED
               W = "DLL_NOT_INTIALIZED"
          CASE %DMLERR_DLL_USAGE
               W = "DLL_USAGE"
          CASE %DMLERR_EXECACKTIMEOUT
               W = "EXEC_ACK_TIMEOUT"
          CASE  %DMLERR_INVALIDPARAMETER
               W= "INVALID_PARAMETER"
          CASE  %DMLERR_LOW_MEMORY
               W = "LOW_MEMORY"
          CASE %DMLERR_MEMORY_ERROR
               W = "MEMORY_ERROR"
          CASE %DMLERR_NOTPROCESSED
               W = "NOT_PROCESSED (not found)"
          CASE %DMLERR_NO_CONV_ESTABLISHED
               W = "NO_CONV_ESTABLISHED"
          CASE %DMLERR_POKEACKTIMEOUT
               W = "POKE_ACK_TIMEOUT"
          CASE  %DMLERR_POSTMSG_FAILED
               W= "POSTMSG_FAILED"
          CASE %DMLERR_REENTRANCY
               W = "REENTRANCY ERROR"
          CASE %DMLERR_SERVER_DIED
               W = "SERVER_DIED"
          CASE %DMLERR_SYS_ERROR
               W = "SYS_ERROR"
          CASE %DMLERR_UNADVACKTIMEOUT
               W = "UNADV_ACK_TIMEOUT"
          CASE %DMLERR_UNFOUND_QUEUE_ID
               W ="UNFOUND_QUEUE_ID"
          CASE ELSE
               W = "NO DESCRIPTION AVAIALABLE"
       END SELECT
    
       FUNCTION = "(x'" & HEX$(DMLERR, 4) & "') " & W
    END FUNCTION
    
    
    ' *** END OF FILE ***'
    Michael Mattias
    Tal Systems (retired)
    Port Washington WI USA
    [email protected]
    http://www.talsystems.com

    Comment


    • #3
      FWIW, are you sure that COM interface is supposed to be installed with Adobe Reader?

      That interface may only be available either as part of the entire Acrobat(r) package or as part of the seperately-licensed "API" product.

      (May also be similar limitations re access to the DDE interface).
      Michael Mattias
      Tal Systems (retired)
      Port Washington WI USA
      [email protected]
      http://www.talsystems.com

      Comment


      • #4
        Thanks for the example. I also got one using VB6 with Google 'DDE Tutorial' as a backup example.

        From reading several posts the DDE is really restricted and can be used without purchasing anything. I think you are right about the COM interface being only for the Acrobat product itself.

        I had help from Experts-Exchange finding the references to the available interfaces with just the reader.

        By the way, there is a DDE example in the Petzold PB conversions available elsewhere on the PB site but it would not compile. The DDEAck Type variable didn't match what was in the WIN32API.INC file. Chapter 17.

        Bob Mechler

        Comment


        • #5
          >The DDEAck Type variable didn't match what was in the WIN32API.INC file.

          PB's folks changing the Windows' header files is not exactly breaking news.

          You change one or the other so it does compile and execute.
          Michael Mattias
          Tal Systems (retired)
          Port Washington WI USA
          [email protected]
          http://www.talsystems.com

          Comment


          • #6
            It has not been changed. What it happens is that the translated examples use a modified win32api.inc file, included in PBINC.ZIP.

            As declared in PB's win32api.inc:

            Code:
            TYPE DDEACK
              bAppReturnCode AS BYTE
              bFlags AS BYTE         ' bit flags
            END TYPE
            As declared in the win32api.inc file included in PBINC.ZIP:

            Code:
            TYPE DDEACK
              bAppReturnCode AS INTEGER
              Reserved AS INTEGER
              fbusy AS INTEGER
              fack AS INTEGER
            END TYPE
            As it should be:

            Code:
            TYPE DDEACK
               bAppReturnCode AS BIT  * 8 IN WORD
               reserved       AS BIT  * 6
               fBusy          AS BIT  * 1
               fAck           AS BIT  * 1
            END TYPE
            Forum: http://www.jose.it-berater.org/smfforum/index.php

            Comment


            • #7
              Jumped to a conclusion falsely, thanks for setting it straight.

              Bob Mechler

              Comment


              • #8
                These type declares seem not to be what ddepop1.bas needs in Petzold's example.

                Code:
                type DDEADVISE
                  wFlags as word         ' bit flags
                  cfFormat as integer
                end type
                
                type DDEDATA
                  wFlags as word         ' bit flags
                  cfFormat as integer
                  bValue(0 to 0) as byte ' array length may vary (fake type)
                end type
                By temporarily remarking out references to the above two type definitions, it finally compiled but of course doesn't work. I can't tell what they should be and where does one find PBINC.ZIP. Sorry, I probably should know this by now.


                Bob Mechler

                Comment


                • #9
                  PBINC.ZIP is included in PETZOLD.ZIP, the file that contains the old translation of the Petzold examples: http://www.powerbasic.com/support/downloads/windows.htm

                  Code:
                  TYPE DDEADVISE
                    Reserved AS INTEGER
                    fDeferUpd AS INTEGER
                    fAckReq AS INTEGER
                    cfFormat AS INTEGER
                  END TYPE
                  
                  TYPE DDEDATA
                    unused AS INTEGER
                    fresponse AS INTEGER
                    fRelease AS INTEGER
                    Reserved AS INTEGER
                    fAckReq AS INTEGER
                    cfFormat AS INTEGER
                    Value(1) AS BYTE
                  END TYPE
                  However, be aware that are wrong. They should be:

                  Code:
                  TYPE DDEADVISE
                     reserved  AS BIT     * 14 IN WORD
                     fDeferUpd AS BIT     * 1
                     fAckReq   AS BIT     * 1
                     cfFormat  AS INTEGER
                  END TYPE
                  
                  TYPE DDEDATA
                     unused    AS BIT * 12 IN WORD
                     fResponse AS BIT * 1
                     fRelease  AS BIT * 1
                     reserved  AS BIT * 1
                     fAckReq   AS BIT * 1
                     cfFormat  AS INTEGER
                     bValue(0) AS BYTE             ' any size array
                  END TYPE
                  PB include files don't use bit fields because older versions of the compiler didn't support it. The translator of the examples has tried to solve it using integers, but this is plainly wrong.
                  Forum: http://www.jose.it-berater.org/smfforum/index.php

                  Comment


                  • #10
                    Since DDE is clearly a supported control method with Acrobat 9.0, I need to learn this stuff. It's a little problem that we are mostly stuck with 7.04 for now but I should be able to do this one job in PB 8.0 (to get BIT * 1 in my type declaration).

                    I should be able to proceed, thanks much.

                    Bob Mechler

                    Comment


                    • #11
                      Got ShowPop2.bas to work after changing replacing %NULL with pdata as long in the following code snippet. Don't know why it worked though.

                      Code:
                              call DdeClientTransaction (pdata, 0, hConv, hszItem, %CF_TEXT,_
                                                         %XTYP_ADVSTOP, %DDE_TIMEOUT, %NULL)
                      Bob Mechler

                      Comment


                      • #12
                        Another way to do it, I like better. No Acrobat Reader needed.

                        The answer is installing Ghostscript 8.63 and using the following through ShellExecute.

                        gswin32c -q -sDEVICE=mswinpr2 -dNOPAUSE -dBATCH culand2.pdf

                        Bob Mechler

                        Comment


                        • #13
                          What a typical American solution: No DDE. No COM. Just throw some money at it.

                          Where has that sense of adventure gone?

                          Mostly facetious of course, since I'm sure purchasing & installing the third-party product was likely the more expedient and economical solution.
                          Michael Mattias
                          Tal Systems (retired)
                          Port Washington WI USA
                          [email protected]
                          http://www.talsystems.com

                          Comment


                          • #14
                            What money? Using the GPL license of Ghostscript doesn't cost anything unless I'm misreading something.

                            Still haven't given up on DDE though, right now the -sOutputFile="%printer%HP5PLJ" parameter stills generates a printer dialog box when the doc says it shouldn't.

                            Bob Mechler

                            Comment


                            • #15
                              using Ghostscript to print pdf to local and network printers

                              The following program which you can copy, paste, compile and run on your computer to test will get the default printer and produce the parameter to successfully send a pdf to a local or a network printer if you have Ghostscript 8.63 installed.

                              Excluding the -sOutputFile parameter will bring up the printer dialog to send it to any other printer that is attached.

                              The following program based on one in Poffs by Semen will get the name of the default printer and then prepares the parameter for the Ghostscript command line call.

                              Code:
                                 #COMPILE EXE "C:\MYPDF\defp.exe"
                                 #REGISTER NONE
                                 #DIM ALL
                                 #INCLUDE "WIN32API.INC"
                              
                                 FUNCTION PBMAIN()
                                    DIM PrinterName AS ASCIIZ * 255
                                    DIM sPrinterName AS STRING
                                    GetProfileString "WINDOWS", "DEVICE", ",,,", PrinterName, SIZEOF(PrinterName)
                                    sPrinterName$ = PrinterName
                                    sPrinterName$ = PARSE$(sPrinterName$,1)
                                    MSGBOX("Element of Ghostscript batch file is: " + $DQ + "\\spool\" + sPrinterName$ + $DQ)
                                 END FUNCTION
                              Code:
                              gswin32c -q -sDEVICE=mswinpr2 -sOutputFile="\\spool\HPLJ5P" -dNOPAUSE -dBATCH %1
                              When run on my Windows Vista Business Laptop I get this.
                              Code:
                              gswin32c -q -sDEVICE=mswinpr2 -sOutputFile="\\spool\\\BOBM-HWA\HPLJ5P" 
                              -dNOPAUSE -dBATCH %1
                              The %1 is just a placeholder for the PDF file. It also works with PS files.

                              Kinda weird looking parameter but it works on both computers sending the same pdf to the same printer. One computer is connected locally and the other is connected through the network. No printer dialog or need for Acrobat Reader.


                              Bob Mechler
                              Last edited by BOB MECHLER; 25 Jan 2009, 12:11 PM. Reason: Editing needed

                              Comment

                              Working...
                              X