• Welcome to Jose's Read Only Forum 2023.
 

Embedding Microsoft Office Spreadsheet

Started by José Roca, October 11, 2008, 10:15:53 PM

Previous topic - Next topic

0 Members and 1 Guest are viewing this topic.

José Roca

 
The following little example, written to test the OWCxx include files, demonstrates how to embed an instance of the Microsoft Office Spreadsheet, using ATL.DLL as the OLE container, and fill some cells with values.

OWC11 version


' ########################################################################################
' This example demonstrates how to embed Microsoft Office Spreadsheet
' ########################################################################################

' SED_PBWIN - Use the PBWIN compiler
#COMPILE EXE
#DIM ALL
#INCLUDE ONCE "ATL.INC"        ' // ATL
#INCLUDE ONCE "EXDISP.INC"     ' // WebBrowser Control
#INCLUDE ONCE "OWC11.INC"      ' // Office Web Components

%IDC_SPREADSHEET = 101

' ========================================================================================
' 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

   ' Required: Initialize ATL
   AtlAxWinInit

   hFont = GetStockObject(%ANSI_VAR_FONT)

   ' Register the window class
   szClassName        = "OWC11"
   wcex.cbSize        = SIZEOF(wcex)
   wcex.style         = 0 '%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_WINDOW ' %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 = "Microsoft Office Spreadsheet"

   ' 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.72
   nHeight = (((rc.nBottom - rc.nTop)) + 2) * 0.70
   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 AtlForwardMessage(hWndMain, uMsg) THEN
         IF IsDialogMessage(hWndMain, uMsg) = 0 THEN
            TranslateMessage uMsg
            DispatchMessage uMsg
         END IF
      END IF
   WEND

   FUNCTION = uMsg.wParam

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

' ========================================================================================
' PROCEDURE: AtlForwardMessage
' PURPOSE:   Forwards messages to ATL
' RETURN:    TRUE if message was processed, FALSE if it was not.
' ========================================================================================

FUNCTION AtlForwardMessage ( _
   BYVAL hWnd  AS DWORD, _   ' handle of window
   BYREF uMsg  AS tagMSG _   ' message information
   ) AS LONG

   ' Default return value
   FUNCTION = %FALSE

   ' Retrieve the handle of the window that hosts the WebBrowser control
   LOCAL hCtrl AS DWORD
   hCtrl = GetDlgItem(hWnd, %IDC_SPREADSHEET)

   ' Retrieve the ancestor of the control that has the focus
   LOCAL hWndCtrl AS DWORD
   hWndCtrl = GetFocus
   DO
      IF ISFALSE GetParent(hWndCtrl) OR GetParent(hWndCtrl) = hWnd THEN EXIT DO
      hWndCtrl = GetParent(hWndCtrl)
   LOOP

   ' If the focus is in the WebBrowser, forward the message to it
   IF hCtrl = hWndCtrl THEN
      IF ISTRUE SendMessage(hCtrl, &H37F, 0, VARPTR(uMsg)) THEN FUNCTION = %TRUE
   END IF

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  hr AS LONG
   LOCAL  hCtl AS DWORD
   LOCAL  rc AS RECT
   LOCAL  pISpreadSheet AS OWC11_ISpreadsheet
   LOCAL  vUrl AS VARIANT

   SELECT CASE wMsg

      CASE %WM_CREATE
         GetClientRect hWnd, rc
         hCtl = CreateWindowEx(0, "AtlAxWin", "OWC11.Spreadsheet.11", %WS_CHILD OR %WS_VISIBLE OR %WS_TABSTOP, _
                0, 0, 0, 0, hWnd, %IDC_SPREADSHEET, GetModuleHandle(""), BYVAL %NULL)
         ' Get the IDispatch of the control
         pISpreadSheet = AtlAxGetDispatch(GetDlgItem(hWnd, %IDC_SPREADSHEET))
         IF ISOBJECT(pISpreadSheet) THEN
            pISpreadSheet.Range("A1").Formula = 1
            pISpreadSheet.Range("A2").Formula = 2
            pISpreadSheet.Range("A3").Formula = 3
            pISpreadSheet.Range("B1").Formula = 10
            pISpreadSheet.Range("B2").Formula = 15
            pISpreadSheet.Range("B3").Formula = 18
            ' Release the interface
            pISpreadSheet = NOTHING
         END IF
         SetFocus hCtl

      CASE %WM_SIZE
         ' Resizes the control
         IF wParam <> %SIZE_MINIMIZED THEN
            GetClientRect hWnd, rc
            MoveWindow GetDlgItem(hWnd, %IDC_SPREADSHEET), 0, 0, rc.nRight - rc.nLeft, rc.nBottom - rc.nTop, %TRUE
         END IF

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

      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_DESTROY
         ' Quit
         PostQuitMessage 0
         EXIT FUNCTION

   END SELECT

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

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


OWC10 version


' ########################################################################################
' This example demonstrates how to embed Microsoft Office Spreadsheet
' ########################################################################################

' SED_PBWIN - Use the PBWIN compiler
#COMPILE EXE
#DIM ALL
#INCLUDE ONCE "ATL.INC"        ' // ATL
#INCLUDE ONCE "EXDISP.INC"     ' // WebBrowser Control
#INCLUDE ONCE "OWC10.INC"      ' // Office Web Components

%IDC_SPREADSHEET = 101

' ========================================================================================
' 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

   ' Required: Initialize ATL
   AtlAxWinInit

   hFont = GetStockObject(%ANSI_VAR_FONT)

   ' Register the window class
   szClassName        = "OWC11"
   wcex.cbSize        = SIZEOF(wcex)
   wcex.style         = 0 '%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_WINDOW ' %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 = "Microsoft Office Spreadsheet"

   ' 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.72
   nHeight = (((rc.nBottom - rc.nTop)) + 2) * 0.70
   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 AtlForwardMessage(hWndMain, uMsg) THEN
         IF IsDialogMessage(hWndMain, uMsg) = 0 THEN
            TranslateMessage uMsg
            DispatchMessage uMsg
         END IF
      END IF
   WEND

   FUNCTION = uMsg.wParam

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

' ========================================================================================
' PROCEDURE: AtlForwardMessage
' PURPOSE:   Forwards messages to ATL
' RETURN:    TRUE if message was processed, FALSE if it was not.
' ========================================================================================

FUNCTION AtlForwardMessage ( _
   BYVAL hWnd  AS DWORD, _   ' handle of window
   BYREF uMsg  AS tagMSG _   ' message information
   ) AS LONG

   ' Default return value
   FUNCTION = %FALSE

   ' Retrieve the handle of the window that hosts the WebBrowser control
   LOCAL hCtrl AS DWORD
   hCtrl = GetDlgItem(hWnd, %IDC_SPREADSHEET)

   ' Retrieve the ancestor of the control that has the focus
   LOCAL hWndCtrl AS DWORD
   hWndCtrl = GetFocus
   DO
      IF ISFALSE GetParent(hWndCtrl) OR GetParent(hWndCtrl) = hWnd THEN EXIT DO
      hWndCtrl = GetParent(hWndCtrl)
   LOOP

   ' If the focus is in the WebBrowser, forward the message to it
   IF hCtrl = hWndCtrl THEN
      IF ISTRUE SendMessage(hCtrl, &H37F, 0, VARPTR(uMsg)) THEN FUNCTION = %TRUE
   END IF

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  hr AS LONG
   LOCAL  hCtl AS DWORD
   LOCAL  rc AS RECT
   LOCAL  pISpreadSheet AS OWC10_ISpreadsheet
   LOCAL  vUrl AS VARIANT

   SELECT CASE wMsg

      CASE %WM_CREATE
         GetClientRect hWnd, rc
         hCtl = CreateWindowEx(0, "AtlAxWin", "OWC10.Spreadsheet.10", %WS_CHILD OR %WS_VISIBLE OR %WS_TABSTOP, _
                0, 0, 0, 0, hWnd, %IDC_SPREADSHEET, GetModuleHandle(""), BYVAL %NULL)
         ' Get the IDispatch of the control
         pISpreadSheet = AtlAxGetDispatch(GetDlgItem(hWnd, %IDC_SPREADSHEET))
         IF ISOBJECT(pISpreadSheet) THEN
            pISpreadSheet.Range("A1").Formula = 1
            pISpreadSheet.Range("A2").Formula = 2
            pISpreadSheet.Range("A3").Formula = 3
            pISpreadSheet.Range("B1").Formula = 10
            pISpreadSheet.Range("B2").Formula = 15
            pISpreadSheet.Range("B3").Formula = 18
            ' Release the interface
            pISpreadSheet = NOTHING
         END IF
         SetFocus hCtl

      CASE %WM_SIZE
         ' Resizes the control
         IF wParam <> %SIZE_MINIMIZED THEN
            GetClientRect hWnd, rc
            MoveWindow GetDlgItem(hWnd, %IDC_SPREADSHEET), 0, 0, rc.nRight - rc.nLeft, rc.nBottom - rc.nTop, %TRUE
         END IF

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

      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_DESTROY
         ' Quit
         PostQuitMessage 0
         EXIT FUNCTION

   END SELECT

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

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


José Roca

#1
 
The following example demonstrates how to embed an instance of the Microsoft Office Spreadsheet using my Ole Container (OLECON.INC).

OWC11 Version


' ########################################################################################
' This example demonstrates how to embed Microsoft Office Spreadsheet
' ########################################################################################

' SED_PBWIN - Use the PBWIN compiler
#COMPILE EXE
#DIM ALL
#INCLUDE ONCE "OLECON.INC"     ' // OLE Container
#INCLUDE ONCE "OWC11.INC"      ' // Office Web Components

%IDC_SPREADSHEET = 101

' ========================================================================================
' 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

   ' Required: Initialize the OLE Container
   OC_WinInit

   hFont = GetStockObject(%ANSI_VAR_FONT)

   ' Register the window class
   szClassName        = "OWC11"
   wcex.cbSize        = SIZEOF(wcex)
   wcex.style         = 0 '%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_WINDOW ' %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 = "Microsoft Office Spreadsheet"

   ' 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.72
   nHeight = (((rc.nBottom - rc.nTop)) + 2) * 0.70
   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)
      ' This control doesn't require message forwarding
'      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 hr            AS LONG
   LOCAL hCtl          AS DWORD
   LOCAL rc            AS RECT
   LOCAL vUrl          AS VARIANT
   LOCAL pISpreadSheet AS OWC11_ISpreadsheet

   SELECT CASE wMsg

      CASE %WM_CREATE
         GetClientRect hWnd, rc
         hCtl = CreateWindowEx(0, $OC_CLASSNAME, "OWC11.Spreadsheet.11", %WS_CHILD OR %WS_VISIBLE OR %WS_TABSTOP, _
                0, 0, 0, 0, hWnd, %IDC_SPREADSHEET, GetModuleHandle(""), BYVAL %NULL)
         ' Get the IDispatch of the control
         pISpreadSheet = OC_GetDispatch(GetDlgItem(hWnd, %IDC_SPREADSHEET))
         IF ISOBJECT(pISpreadSheet) THEN
            pISpreadSheet.Range("A1").Formula = 1
            pISpreadSheet.Range("A2").Formula = 2
            pISpreadSheet.Range("A3").Formula = 3
            pISpreadSheet.Range("B1").Formula = 10
            pISpreadSheet.Range("B2").Formula = 15
            pISpreadSheet.Range("B3").Formula = 18
            ' Release the interface
            pISpreadSheet = NOTHING
         END IF
         SetFocus hCtl

      CASE %WM_SIZE
         ' Resizes the control
         IF wParam <> %SIZE_MINIMIZED THEN
            GetClientRect hWnd, rc
            MoveWindow GetDlgItem(hWnd, %IDC_SPREADSHEET), 0, 0, rc.nRight - rc.nLeft, rc.nBottom - rc.nTop, %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_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_DESTROY
         PostQuitMessage 0
         EXIT FUNCTION

   END SELECT

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

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


OWC10 Version


' ########################################################################################
' This example demonstrates how to embed Microsoft Office Spreadsheet
' ########################################################################################

' SED_PBWIN - Use the PBWIN compiler
#COMPILE EXE
#DIM ALL
#INCLUDE ONCE "OLECON.INC"     ' // OLE Container
#INCLUDE ONCE "OWC10.INC"      ' // Office Web Components

%IDC_SPREADSHEET = 101

' ========================================================================================
' 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

   ' Required: Initialize the OLE Container
   OC_WinInit

   hFont = GetStockObject(%ANSI_VAR_FONT)

   ' Register the window class
   szClassName        = "OWC10"
   wcex.cbSize        = SIZEOF(wcex)
   wcex.style         = 0 '%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_WINDOW ' %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 = "Microsoft Office Spreadsheet"

   ' 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.72
   nHeight = (((rc.nBottom - rc.nTop)) + 2) * 0.70
   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)
       ' This control doesn't require message forwarding
'      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 hr            AS LONG
   LOCAL hCtl          AS DWORD
   LOCAL rc            AS RECT
   LOCAL vUrl          AS VARIANT
   LOCAL pISpreadSheet AS OWC10_ISpreadsheet

   SELECT CASE wMsg

      CASE %WM_CREATE
         GetClientRect hWnd, rc
         hCtl = CreateWindowEx(0, $OC_CLASSNAME, "OWC10.Spreadsheet.10", %WS_CHILD OR %WS_VISIBLE OR %WS_TABSTOP, _
                0, 0, 0, 0, hWnd, %IDC_SPREADSHEET, GetModuleHandle(""), BYVAL %NULL)
         ' Get the IDispatch of the control
         pISpreadSheet = OC_GetDispatch(GetDlgItem(hWnd, %IDC_SPREADSHEET))
         IF ISOBJECT(pISpreadSheet) THEN
            pISpreadSheet.Range("A1").Formula = 1
            pISpreadSheet.Range("A2").Formula = 2
            pISpreadSheet.Range("A3").Formula = 3
            pISpreadSheet.Range("B1").Formula = 10
            pISpreadSheet.Range("B2").Formula = 15
            pISpreadSheet.Range("B3").Formula = 18
            ' Release the interface
            pISpreadSheet = NOTHING
         END IF
         SetFocus hCtl

      CASE %WM_SIZE
         ' Resizes the control
         IF wParam <> %SIZE_MINIMIZED THEN
            GetClientRect hWnd, rc
            MoveWindow GetDlgItem(hWnd, %IDC_SPREADSHEET), 0, 0, rc.nRight - rc.nLeft, rc.nBottom - rc.nTop, %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_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_DESTROY
         PostQuitMessage 0
         EXIT FUNCTION

   END SELECT

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

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