Results 1 to 10 of 30

Thread: Class Stuff: VBA Custom Classes & Objects, Class Modules

Threaded View

Previous Post Previous Post   Next Post Next Post
  1. #23
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,458
    Rep Power
    10
    https://www.excelfox.com/forum/showt...ll=1#post24189



    Background to getting a solution without a class module
    ( Background to getting non class module solution to this solution
    https://eileenslounge.com/viewtopic....317547#p317547
    https://www.excelfox.com/forum/showt...age3#post24163
    https://www.excelfox.com/forum/showt...age3#post24165
    )

    Lets review what we did in the two posts using the Class module


    We inserted a Class module. We put text, in coding form, into/ onto it. Think of that code module and text now as text on a stamp The first main line of that text,
    __| Public WithEvents ExApp As Excel.Application
    , is of the form of coding which declares a variable of the type to point to a memory location capable of dealing the Excel Application. In Layman terms it can be thought of as somehow organising something to "be" like the Excel we are using. The WithEvents makes available to that "thing", or would if it was actual coding, the event coding associated with Excel.
    From those event codings, we are interested finally in the event of when a file is opened. So the next text below is that of coding that organises that a message box pops up if a file by the name of test.csv is opened
    Code:
    ' This and the next macro is the text of coding we need to tell us if we open the file "test.csv"
    Public Sub ExApp_WorkbookOpen(ByVal Wb As Workbook) ' This will become a property in a final Instanciated object, and I intend to use it
    Dim s As String
     Let s = Wb.Name
        If s = "test.csv" Then Call MyMacro
    End Sub
    Sub MyMacro() ' This is available also in intellisense to a final instanciated object, although in this example I will not use it, - its calls from the routine above. Splitting the two is not done for any particular reason
    MsgBox Prompt:="You just opened  test.csv"
    End Sub
    



    Here below is the final complete text of the Class module "Stamp"

    Class module, FileOpenWatcher
    Code:
    ' This is not coding that will ever be done. It is like a stamp from which we effectively make the coding to put in an actual class object module:  This is a Class module. Not an actual class object module
    Option Explicit
    Public WithEvents ExApp As Excel.Application  ' This makes ExApp a variable/ object that some how is like a running Excel, and also the   WithEvents  means it has access to all those  codings that it has that kick off when something happens
    
    ' This and the next macro is the text of coding we need to tell us if we open the file "test.csv"
    Private Sub ExApp_WorkbookOpen(ByVal Wb As Workbook) ' This will become a property in a final Instanciated object, and I intend to use it
    Dim s As String
     Let s = Wb.Name
        If s = "test.csv" Then Call MyMacro
    End Sub
    Sub MyMacro() ' This is available also in intellisense to a final instanciated object, although in this example I will not use it, - its calles from the routine above. Splitting the two is not done for any particular reason
    MsgBox Prompt:="You just opened  test.csv"
    End Sub
    
    One advantage of this class way of doing it is that this stamp of text can be used over and over again, along similar lines to why we use functions. Using the idea of the Stamp, this stamp is effectively used by these instanciating code lines:
    Dim MeWatcher As FileOpenWatcher
    Private Sub Workbook_Open()
    Set MeWatcher = New FileOpenWatcher


    In other words an instanciation is done, then , as a result of doing that instanciation , MeWatcher becomes a variable pointing to a thing/ object capable of doing something when a file is opened. I would argue that we have something, which we cannot see, but which could be regarded as associated with the object pointed to by MeWatcher. Another Layman perception idea would be that we have this invisible object code module with the name MeWatcher, looking like this https://i.postimg.cc/wM2Wn8zT/Object...suggestion.jpg

    Our task in the next posts is to do the same without a use of a class module.
    So let’s think about this
    …..
    According to the Alan theory of class modules and object modules, after the instanciation, we are left with an object module, which can be thought of as identical looking to the text of the class module and it looks like that perception suggestion, although we cant see it, not like what as we can see similar things like the instanciated ThisWorkbook object code module and the worksheets object code modules.
    Here below is that perception suggestion again.


    Object module, MeWatcher ( perception suggestion )
    Code:
    ' This is , or can reasonably be perceived to be, the "real" coding that is done
    Option Explicit
    Public WithEvents ExApp As Excel.Application ' This makes ExApp a variable/ object that some how is like a running Excel, and also the   WithEvents  means it has access to all those  codings that it has that kick off when something happens
    
    ' This and the next macro is the sort of coding we need to tell us if we open the file "test.csv"
    Private Sub ExApp_WorkbookOpen(ByVal Wb As Workbook) ' This will become a property in a final Instanciated object, amnd I intend to use it
    Dim s As String
     Let s = Wb.Name
        If s = "test.csv" Then Call MyMacro
    End Sub
    Sub MyMacro() ' This is available also in intellisense to a final instanciated object, although in this example I will not use it, - its calles from the routine above. Splitting the two is not done for any particular reason
    MsgBox Prompt:="You just opened  test.csv"
    End Sub
    
    That is , or can reasonably be perceived to be, the "real" coding that is done, (or perhaps more accurately the VBA source coding used finally in the compiled coding which actually runs). And by virtue of the code line somewhere else of , Set MeWatcher.ExApp = Excel.Application , the variable , or object, MeWatcher , is effectively my running Excel


    Now here is the key to getting the task done
    As I just said, …
    Quote Originally Posted by DocAElstein View Post
    According to the Alan theory of class modules and object modules, after the instanciation, we are left with an object module, which can be thought of as identical looking to the text of the class module and it looks like ….. although we cant see it, as we can see things like the instanciated ThisWorkbook object code module and the worksheets object code modules
    Assuming, as my theory does, that the perceived object module from an instantiation from a custom class and the ThisWorkbook object code module and the worksheets object code modules are very similar things, possibly even from some object module class then their syntax, and OLE Automation entry protocols will be consistent without conflicts in any dependency chains allowing assynchronous gateways to the event codings. In layman terms this means
    _ wot works when written in our class modules after instanciation
    _ does as well in the worksheets and ThisWorkbook code modules

    If we do a quick experiment with a ThisWorkbook module we see perhaps that we may be on to something…
    Here is the default event coding available
    https://i.postimg.cc/wvydVYRq/Defaul...ook-coding.jpg
    Default ThisWorkbook Workbook coding.jpg

    Now if we add one of this WithEvents declarations, it looks promising
    https://i.postimg.cc/k5hmKg4Y/Added-...ion-coding.jpg https://i.postimg.cc/Jzxm7qWL/Added-...kbook-Open.jpg
    Added WithEvents ThisWorkbook Excel Application coding.JPG Added WithEvents ThisWorkbook Excel Application coding including Workbook_Open.JPG

    What I am saying here is that the WithEvents declaration seems to result in the same extra options in the dropdowns of the ThisWorkbook module as we have seen appearing in the class module dropdowns after the same WithEvents declaration.

    We see the same in any worksheet module….
    Before, as default
    https://i.postimg.cc/hvC2b0JT/Worksh...nt-codings.jpg
    Worksheets default event codings.jpg

    , after adding an WithEvents declaration
    https://i.postimg.cc/j54gCTt8/Worksh...ith-Events.jpg
    Worksheets module Event codings after adding a WithEvents.jpg


    So , based on my theories, the main thing to think about to get a solution without a class module, is two things:-
    _1) Given that we have already have modules which I suggest cone from the same or similar strain/ origin/ class as my perception suggestion , then we can simply put the coding of the perception suggestion in any of the object modules.
    _2) We can forget the instantiation: The object variable used will not be the MeWatcher of my perception suggestion object, but the name of the object module used.


    So, we will do that in the next two posts.
    Last edited by DocAElstein; 06-19-2024 at 03:04 PM.

Similar Threads

  1. PQ - IP C class generator
    By sandy666 in forum ETL PQ Tips and Tricks
    Replies: 0
    Last Post: 10-22-2020, 05:16 AM
  2. Backup all modules, class modules and userforms to a selectable folder
    By MrBlackd in forum Excel and VBA Tips and Tricks
    Replies: 1
    Last Post: 04-06-2014, 08:33 AM
  3. Manipulate VBA Array Object Using Class Module
    By Rajan_Verma in forum Rajan Verma's Corner
    Replies: 0
    Last Post: 06-06-2013, 07:53 PM
  4. Array Class Module
    By Rajan_Verma in forum Rajan Verma's Corner
    Replies: 3
    Last Post: 12-20-2012, 11:22 AM
  5. Class Objects Created Using the CreateObject Method That Employs Late Binding
    By Excel Fox in forum Excel and VBA Tips and Tricks
    Replies: 0
    Last Post: 08-16-2011, 12:38 PM

Posting Permissions

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