• Welcome to Jose's Read Only Forum 2023.
 

Embedding Macromedia Flash Player v. 9

Started by José Roca, July 17, 2008, 06:05:17 AM

Previous topic - Next topic

0 Members and 1 Guest are viewing this topic.

José Roca

 
The Macromedia Flash Player is a multimedia and application player created and distributed by Macromedia. It runs SWF files which can be created by the Macromedia Flash authoring tool, Macromedia Flex or a number of other Macromedia and third party tools.

José Roca

#1
 
The following class template can be used to connect with the events fired by the Macromedia Flash Player control.


' ########################################################################################
' Class CIShockwaveFlashEvents
' Interface name = _IShockwaveFlashEvents
' IID = {D27CDB6D-AE6D-11CF-96B8-444553540000}
' Event interface for Shockwave Flash
' Attributes = 4112 [&H1010] [Hidden] [Dispatchable]
' ########################################################################################

CLASS CIShockwaveFlashEvents GUID$("{01D9B3C5-B666-4EEE-8EE1-D801DC617EE2}") AS EVENT

INTERFACE IShockwaveFlashEventsImpl GUID$("{D27CDB6D-AE6D-11CF-96B8-444553540000}") AS EVENT

  INHERIT IDispatch

   ' =====================================================================================
   METHOD OnReadyStateChange <-609> ( _
     BYVAL newState AS LONG _                           ' [0] newState /* VT_I4 <Long> */
   )                                                    ' VOID

     ' *** Insert your code here ***

   END METHOD
   ' =====================================================================================

   ' =====================================================================================
   METHOD OnProgress <1958> ( _
     BYVAL percentDone AS LONG _                        ' [0] percentDone /* VT_I4 <Long> */
   )                                                    ' VOID

     ' *** Insert your code here ***

   END METHOD
   ' =====================================================================================

   ' =====================================================================================
   METHOD FSCommand <150> ( _
     BYVAL command AS STRING _                          ' [0] [in] command /* VT_BSTR */
   , BYVAL args AS STRING _                             ' [0] [in] args /* VT_BSTR */
   )                                                    ' VOID

     ' *** Insert your code here ***

   END METHOD
   ' =====================================================================================

   ' =====================================================================================
   METHOD FlashCall <197> ( _
     BYVAL request AS STRING _                          ' [0] [in] request /* VT_BSTR */
   )                                                    ' VOID

     ' *** Insert your code here ***

   END METHOD
   ' =====================================================================================

END INTERFACE

END CLASS


José Roca

#2
 
The following example demonstrates how to create an instance of the ShockWaveFlash player in a SDK window, load and play a movie and setting properties.

Note: To use ATL71.DLL as the container, add $ATL_DLLNAME = "ATL71.DLL" before #INCLUDE "ATL.INC" and change "AtlAxWin" to "AtlAxWin71" in CreateWindowEx.


' ########################################################################################
' Demonstrates how to create an instance of the ShockWaveFlash player in a SDk window,
' load and play a movie and setting properties.
' Note: To use ATL71.DLL as the container, add $ATL_DLLNAME = "ATL71.DLL" before
' #INCLUDE "ATL.INC" and change "AtlAxWin" to "AtlAxWin71" in CreateWindowEx.
' ########################################################################################

' SED_PBWIN - Use the PBWIN compiler
#COMPILE EXE
#DIM ALL
#INCLUDE "FLASH9.INC"
#INCLUDE "ATL.INC"

%ID_FLASH = 1001

' ========================================================================================
' Main
' ========================================================================================
FUNCTION WINMAIN (BYVAL hInstance AS DWORD, BYVAL hPrevInstance AS DWORD, BYVAL lpszCmdLine AS ASCIIZ PTR, BYVAL nCmdShow AS LONG) AS LONG

   LOCAL hWndMain AS dword
   LOCAL hCtl AS DWORD
   LOCAL hFont AS DWORD
   LOCAL wcex AS WndClassEx
   LOCAL szClassName AS ASCIIZ * 80
   LOCAL rc AS RECT
   LOCAL szCaption AS asciiz * 255
   LOCAL nLeft AS LONG
   LOCAL nTop AS LONG
   LOCAL nWidth AS LONG
   LOCAL nHeight AS LONG

   AtlAxWinInit  ' // Initializes ATL - must be called before creating an AtlAxWin71 window

   hFont = GetStockObject(%ANSI_VAR_FONT)

   ' Register the window class
   szClassName        = "MyClassName"
   wcex.cbSize        = SIZEOF(wcex)
   wcex.style         = %CS_HREDRAW OR %CS_VREDRAW
   wcex.lpfnWndProc   = CODEPTR(WndProc)
   wcex.cbClsExtra    = 0
   wcex.cbWndExtra    = 0
   wcex.hInstance     = hInstance
   wcex.hCursor       = LoadCursor (%NULL, BYVAL %IDC_ARROW)
   wcex.hbrBackground = %COLOR_3DFACE + 1
   wcex.lpszMenuName  = %NULL
   wcex.lpszClassName = VARPTR(szClassName)
   wcex.hIcon         = LoadIcon (%NULL, BYVAL %IDI_APPLICATION) ' Sample, if resource icon: LoadIcon(hInst, "APPICON")
   wcex.hIconSm       = LoadIcon (%NULL, BYVAL %IDI_APPLICATION) ' Remember to set small icon too..
   RegisterClassEx wcex

   ' Window caption
   szCaption = "Macromedia Flash Player"

   ' Retrieve the size of the working area
   SystemParametersInfo %SPI_GETWORKAREA, 0, BYVAL VARPTR(rc), 0

   ' Calculate the position and size of the window
   nWidth  = (((rc.nRight - rc.nLeft)) + 2) * 0.75   ' 75% of the client screen width
   nHeight = (((rc.nBottom - rc.nTop)) + 2) * 0.70   ' 70% of the client screen height
   nLeft   = ((rc.nRight - rc.nLeft) \ 2) - nWidth \ 2
   nTop    = ((rc.nBottom - rc.nTop) \ 2) - (nHeight \ 2)

   ' Create a window using the registered class
   hWndMain = CreateWindowEx(%WS_EX_CONTROLPARENT, _           ' extended style
                             szClassName, _                    ' window class name
                             szCaption, _                      ' window caption
                             %WS_OVERLAPPEDWINDOW OR _
                             %WS_CLIPCHILDREN, _               ' window style
                             nLeft, _                          ' initial x position
                             nTop, _                           ' initial y position
                             nWidth, _                         ' initial x size
                             nHeight, _                        ' initial y size
                             %NULL, _                          ' parent window handle
                             0, _                              ' window menu handle
                             hInstance, _                      ' program instance handle
                             BYVAL %NULL)                      ' creation parameters


   ' Show the window
   ShowWindow hWndMain, nCmdShow
   UpdateWindow hWndMain

   ' Message handler loop
   LOCAL Msg AS tagMsg
   WHILE GetMessage(Msg, %NULL, 0, 0)
      IF ISFALSE IsDialogMessage(hWndMain, Msg) THEN
         TranslateMessage Msg
         DispatchMessage Msg
      END IF
   WEND

   FUNCTION = msg.wParam

END FUNCTION
' ========================================================================================

' ========================================================================================
' Main Window procedure
' ========================================================================================
FUNCTION WndProc (BYVAL hWnd AS DWORD, BYVAL wMsg AS DWORD, BYVAL wParam AS DWORD, BYVAL lParam AS LONG) AS LONG

   LOCAL rc AS RECT
   LOCAL hCtl AS DWORD
   LOCAL hr AS DWORD
   LOCAL pFlash AS IShockwaveFlash

   SELECT CASE wMsg

      CASE %WM_SYSCOMMAND
        ' Capture this message and send a %WM_CLOSE message
        IF (wParam AND &HFFF0) = %SC_CLOSE THEN
           SendMessage hWnd, %WM_CLOSE, wParam, lParam
           EXIT FUNCTION
        END IF

      CASE %WM_CREATE
         ' Create the ShockWaveFlash window container
         hCtl = CreateWindowEx(0, "AtlAxWin", "ShockwaveFlash.ShockwaveFlash", %WS_CHILD OR %WS_VISIBLE, _
                               0, 0, 0, 0, hWnd, %ID_FLASH, GetModuleHandle(""), BYVAL %NULL)
         ' Get the IDispatch of the control
         pFlash = AtlAxGetDispatch(hCtl)
         IF ISOBJECT(pFlash) THEN
            ' Load the flash video - a full qualified path must be used
            pFlash.Movie = UCODE$(EXE.Path$ & "choudanse7.swf")
            ' Play the video
            pFlash.Play
            ' ---------------------------------------------------------------------
            ' Example code to set properties
            ' ---------------------------------------------------------------------
            ' Rotate the video
'            pFlash.SetVariable(UCODE$("_rotation"), UCODE$("10"))
            ' Modify the video transparency
'            pFlash.SetVariable(UCODE$("_alpha"), UCODE$("50"))
            ' Modify the scale and position
            pFlash.SetVariable(UCODE$("_xscale"), UCODE$("50"))
            pFlash.SetVariable(UCODE$("_yscale"), UCODE$("50"))
            pFlash.SetVariable(UCODE$("_x"), UCODE$("80"))
            pFlash.SetVariable(UCODE$("_y"), UCODE$("40"))
            ' ---------------------------------------------------------------------
            ' Release the interface
            pFlash = NOTHING
         END IF

      CASE %WM_SIZE
         IF wParam <> %SIZE_MINIMIZED THEN
            GetClientRect hWnd, rc
            MoveWindow GetDlgItem(hWnd, %ID_FLASH), 10, 10, (rc.nRight - rc.nLeft) - 20, (rc.nBottom - rc.nTop) - 20, %TRUE
         END IF

      CASE %WM_COMMAND
         SELECT CASE LOWRD(wParam)
            CASE %IDOK
               IF HIWRD(wParam) = %BN_CLICKED THEN
               END IF
            CASE %IDCANCEL
               IF HIWRD(wParam) = %BN_CLICKED THEN
                  SendMessage hWnd, %WM_DESTROY, wParam, lParam
                  FUNCTION = 0
                  EXIT FUNCTION
               END IF
         END SELECT

      CASE %WM_DESTROY
         PostQuitMessage 0
         EXIT FUNCTION

   END SELECT

   FUNCTION = DefWindowProc(hWnd, wMsg, wParam, lParam)

END FUNCTION
' ========================================================================================


José Roca

#3
 
DDT version of the previous example. To use ATL71.DLL as the container, add $ATL_DLLNAME = "ATL71.DLL" before #INCLUDE "ATL.INC" and change "AtlAxWin" to "AtlAxWin71" in CONTROL ADD.


' ########################################################################################
' Demonstrates how to create an instance of the ShockWaveFlash player in a DDT dialog,
' load and play a movie and setting properties.
' Note: To use ATL71.DLL as the container, add $ATL_DLLNAME = "ATL71.DLL" before
' #INCLUDE "ATL.INC" and change "AtlAxWin" to "AtlAxWin71" in CONTROL ADD.
' ########################################################################################

' SED_PBWIN - Use the PBWIN compiler
#COMPILE EXE
#DIM ALL
#INCLUDE "FLASH9.INC"
#INCLUDE "ATL.INC"

%ID_FLASH = 1001

' ========================================================================================
' Main
' ========================================================================================
FUNCTION WINMAIN (BYVAL hInstance AS DWORD, BYVAL hPrevInstance AS DWORD, BYVAL lpszCmdLine AS ASCIIZ PTR, BYVAL nCmdShow AS LONG) AS LONG

   LOCAL hDlg AS LONG

   AtlAxWinInit  ' // Initializes ATL - must be called before creating an AtlAxWin71 window

   DIALOG NEW 0, "Flash Player Demo", , , 400, 240, %WS_OVERLAPPED OR %WS_THICKFRAME OR %WS_SYSMENU OR _
   %WS_MINIMIZEBOX OR %WS_MAXIMIZEBOX OR %WS_VISIBLE OR %DS_CENTER TO hDlg
   CONTROL ADD "AtlAxWin", hDlg, %ID_FLASH, "ShockwaveFlash.ShockwaveFlash", 0, 0, 0, 0, %WS_VISIBLE OR %WS_CHILD

   DIALOG SHOW MODAL hDlg, CALL DlgProc

END FUNCTION
' ========================================================================================

' ========================================================================================
' Main Dialog procedure
' ========================================================================================
CALLBACK FUNCTION DlgProc() AS LONG

   LOCAL rc AS RECT
   LOCAL hr AS DWORD
   LOCAL pFlash AS IShockwaveFlash

   SELECT CASE CBMSG

      CASE %WM_INITDIALOG
         ' Get the IDispatch of the control
         pFlash = AtlAxGetDispatch(GetDlgItem(CBHNDL, %ID_FLASH))
         IF ISOBJECT(pFlash) THEN
            ' Load the flash video - a full qualified path must be used
            pFlash.Movie = UCODE$(EXE.Path$ & "choudanse7.swf")
            ' Play the video
            pFlash.Play
            ' ---------------------------------------------------------------------
            ' Example code to set properties
            ' ---------------------------------------------------------------------
            ' Rotate the video
'            pFlash.SetVariable(UCODE$("_rotation"), UCODE$("10"))
            ' Modify the video transparency
'            pFlash.SetVariable(UCODE$("_alpha"), UCODE$("50"))
            ' Modify the scale and position
            pFlash.SetVariable(UCODE$("_xscale"), UCODE$("50"))
            pFlash.SetVariable(UCODE$("_yscale"), UCODE$("50"))
            pFlash.SetVariable(UCODE$("_x"), UCODE$("80"))
            pFlash.SetVariable(UCODE$("_y"), UCODE$("40"))
            ' ---------------------------------------------------------------------
            ' Release the interface
            pFlash = NOTHING
         END IF

      CASE %WM_SIZE
         ' Resize the two sample buttons of the dialog
         IF CBWPARAM <> %SIZE_MINIMIZED THEN
            GetClientRect CBHNDL, rc
            MoveWindow GetDlgItem(CBHNDL, %ID_FLASH), 10, 10, (rc.nRight - rc.nLeft) - 20, (rc.nBottom - rc.nTop) - 20, %TRUE
         END IF

      CASE %WM_COMMAND
         SELECT CASE CBCTL
            CASE %IDOK
               IF CBCTLMSG = %BN_CLICKED THEN
               END IF
            CASE %IDCANCEL
               IF CBCTLMSG = %BN_CLICKED THEN DIALOG END CBHNDL, 0
         END SELECT

   END SELECT

END FUNCTION
' ========================================================================================


José Roca

#4
 
The following example uses my OLE container (OLECON.INC) instead of ATL.


' ########################################################################################
' Demonstrates how to create an instance of the ShockWaveFlash player in a SDk window,
' load and play a movie and setting properties.
' ########################################################################################

' SED_PBWIN - Use the PBWIN compiler
#COMPILE EXE
#DIM ALL
%OC_DEBUG = 1
#INCLUDE "FLASH9.INC"
#INCLUDE "OLECON.INC"

%ID_FLASH = 1001

' ========================================================================================
' Main
' ========================================================================================
FUNCTION WINMAIN (BYVAL hInstance AS DWORD, BYVAL hPrevInstance AS DWORD, BYVAL lpszCmdLine AS ASCIIZ PTR, BYVAL nCmdShow AS LONG) AS LONG

   LOCAL hWndMain    AS DWORD
   LOCAL hFont       AS DWORD
   LOCAL wcex        AS WNDCLASSEX
   LOCAL szClassName AS ASCIIZ * 80
   LOCAL rc          AS RECT
   LOCAL szCaption   AS ASCIIZ * 255
   LOCAL nLeft       AS LONG
   LOCAL nTop        AS LONG
   LOCAL nWidth      AS LONG
   LOCAL nHeight     AS LONG

   ' Required: Initialize the Ole Container
   OC_WinInit

   hFont = GetStockObject(%ANSI_VAR_FONT)

   ' Register the window class
   szClassName        = "MyClassName"
   wcex.cbSize        = SIZEOF(wcex)
   wcex.style         = %CS_HREDRAW OR %CS_VREDRAW
   wcex.lpfnWndProc   = CODEPTR(WndProc)
   wcex.cbClsExtra    = 0
   wcex.cbWndExtra    = 0
   wcex.hInstance     = hInstance
   wcex.hCursor       = LoadCursor (%NULL, BYVAL %IDC_ARROW)
   wcex.hbrBackground = %COLOR_3DFACE + 1
   wcex.lpszMenuName  = %NULL
   wcex.lpszClassName = VARPTR(szClassName)
   wcex.hIcon         = LoadIcon (%NULL, BYVAL %IDI_APPLICATION) ' Sample, if resource icon: LoadIcon(hInst, "APPICON")
   wcex.hIconSm       = LoadIcon (%NULL, BYVAL %IDI_APPLICATION) ' Remember to set small icon too..
   RegisterClassEx wcex

   ' Window caption
   szCaption = "Macromedia Flash Player"

   ' Retrieve the size of the working area
   SystemParametersInfo %SPI_GETWORKAREA, 0, BYVAL VARPTR(rc), 0

   ' Calculate the position and size of the window
   nWidth  = (((rc.nRight - rc.nLeft)) + 2) * 0.75   ' 75% of the client screen width
   nHeight = (((rc.nBottom - rc.nTop)) + 2) * 0.70   ' 70% of the client screen height
   nLeft   = ((rc.nRight - rc.nLeft) \ 2) - nWidth \ 2
   nTop    = ((rc.nBottom - rc.nTop) \ 2) - (nHeight \ 2)

   ' Create a window using the registered class
   hWndMain = CreateWindowEx(%WS_EX_CONTROLPARENT, _           ' extended style
                             szClassName, _                    ' window class name
                             szCaption, _                      ' window caption
                             %WS_OVERLAPPEDWINDOW OR _
                             %WS_CLIPCHILDREN, _               ' window style
                             nLeft, _                          ' initial x position
                             nTop, _                           ' initial y position
                             nWidth, _                         ' initial x size
                             nHeight, _                        ' initial y size
                             %NULL, _                          ' parent window handle
                             0, _                              ' window menu handle
                             hInstance, _                      ' program instance handle
                             BYVAL %NULL)                      ' creation parameters


   ' Show the window
   ShowWindow hWndMain, nCmdShow
   UpdateWindow hWndMain

   ' Message handler loop
   LOCAL uMsg AS tagMsg
   WHILE GetMessage(uMsg, %NULL, 0, 0)
      IF ISFALSE OC_ForwardMessage(GetFocus, uMsg) THEN
         IF IsDialogMessage(hWndMain, uMsg) = 0 THEN
            TranslateMessage uMsg
            DispatchMessage uMsg
         END IF
      END IF
   WEND

   FUNCTION = uMsg.wParam

END FUNCTION
' ========================================================================================

' ========================================================================================
' Main Window procedure
' ========================================================================================
FUNCTION WndProc (BYVAL hWnd AS DWORD, BYVAL wMsg AS DWORD, BYVAL wParam AS DWORD, BYVAL lParam AS LONG) AS LONG

   LOCAL rc AS RECT
   LOCAL hCtl AS DWORD
   LOCAL hr AS DWORD
   LOCAL pFlash AS IShockwaveFlash

   SELECT CASE wMsg

      CASE %WM_SYSCOMMAND
        ' Capture this message and send a %WM_CLOSE message
        IF (wParam AND &HFFF0) = %SC_CLOSE THEN
           SendMessage hWnd, %WM_CLOSE, 0, 0
           EXIT FUNCTION
        END IF

      CASE %WM_CREATE
         ' Create the ShockWaveFlash window container
         hCtl = CreateWindowEx(0, $OC_CLASSNAME, "ShockwaveFlash.ShockwaveFlash", %WS_CHILD OR %WS_VISIBLE, _
                               0, 0, 0, 0, hWnd, %ID_FLASH, GetModuleHandle(""), BYVAL %NULL)
         ' Get the IDispatch of the control
         pFlash = OC_GetDispatch(hCtl)
         IF ISOBJECT(pFlash) THEN
            ' Load the flash video - a full qualified path must be used
            pFlash.Movie = UCODE$(EXE.Path$ & "choudanse7.swf")
            ' Play the video
            pFlash.Play
            ' ---------------------------------------------------------------------
            ' Example code to set properties
            ' ---------------------------------------------------------------------
            ' Rotate the video
'            pFlash.SetVariable(UCODE$("_rotation"), UCODE$("10"))
            ' Modify the video transparency
'            pFlash.SetVariable(UCODE$("_alpha"), UCODE$("50"))
            ' Modify the scale and position
            pFlash.SetVariable(UCODE$("_xscale"), UCODE$("50"))
            pFlash.SetVariable(UCODE$("_yscale"), UCODE$("50"))
            pFlash.SetVariable(UCODE$("_x"), UCODE$("80"))
            pFlash.SetVariable(UCODE$("_y"), UCODE$("40"))
            ' ---------------------------------------------------------------------
            ' Release the interface
            pFlash = NOTHING
         END IF

      CASE %WM_SIZE
         IF wParam <> %SIZE_MINIMIZED THEN
            GetClientRect hWnd, rc
            MoveWindow GetDlgItem(hWnd, %ID_FLASH), 10, 10, (rc.nRight - rc.nLeft) - 20, (rc.nBottom - rc.nTop) - 20, %TRUE
         END IF

      CASE %WM_COMMAND
         SELECT CASE LO(WORD, wParam)
            CASE %IDCANCEL
               IF HI(WORD, wParam) = %BN_CLICKED THEN
                  SendMessage hWnd, %WM_CLOSE, 0, 0
                  EXIT FUNCTION
               END IF
         END SELECT

      CASE %WM_DESTROY
         PostQuitMessage 0
         EXIT FUNCTION

   END SELECT

   FUNCTION = DefWindowProc(hWnd, wMsg, wParam, lParam)

END FUNCTION
' ========================================================================================