Page 2 of 3 FirstFirst 123 LastLast
Results 11 to 20 of 30

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

Hybrid View

Previous Post Previous Post   Next Post Next Post
  1. #1
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,402
    Rep Power
    10

    Summary in words, existing Class objects that we already see, and what we don’t see, in the VB Editor

    Short summary in words, existing Class objects that we already see, and what we don’t see, in the VB Editor

    We can call almost anything an object. The concept of an object is very vague.
    The Objects tend to be organised hierarchically starting with the big ones at the top of the hierarchy, and going down through smaller ones. But once again its not always strictly held to.
    Something running parallel to this hierarchical structure which loosely fits into it all, is that we define a Class as a blueprint or Template from which to build one or more objects of that type , or model, or Class. Class is also a vague concept and means like a template, blueprint , or set of instructions or procedures to define how objects built from the Class will look like.
    Class things will tend to be further up the hierarchical structure, but once again, that is a general idea or concept. There is no point in wasting time arguing the toss about being accurate about some think that is a vague concept left to an individuals interpretation, but based on certain concepts which I have outlined

    There are “Class level”, Class objects that we don’t have any access to. They are probably extremely complex and define a lot of what an instance of Excel will be. At this level , or approximately we may view it as such, we can have a custom Class. We will see in the following posts that in effect that means we can insert and view a code module, used to define the object made from the “blue print” that the coding in a class module is.

    For the case of the “Class level”, Class objects that we don’t have any access to, we can see the objects: We can argue that Excel itself and the Worksheets are those, but also the object code modules are parts of those: For example, you can look inside a worksheet object code module. ( For example, double click on it in the VB Editor to open it : http://i.imgur.com/9iTEib0.jpg : ) - That is a “real” object code module . Its made by Microsoft using a Class module that we can’t see and one we cant get direct access to it.

    With our home made Class module it’s the other way around. We can see the class module. But the “real one” or “real ones” that gets made, we can’t see. ( I am not sure why that is. Maybe Microsoft just wanted it that way )
    I think a lot of the documentation and Blog sites don’t have it quite correct. They often refer to the ThisWorkbook and the worksheet code modules as class modules. I don’t think they are. They are object modules made form class modules we don’t have direct access to.


    We can argue the toss about why things are so organised. But no one knows for sure, and experts usually get upset when you talk about it**., since they prefer to know what they are talking about , which they don’t , half the time.
    The class modules we can’t see are likely massive with a lot proprietary information. We will see that we are limited to a small number of coding types in our custom Class module.
    The access to the object code modules is possibly primarily to allow us to fill in coding within the available event codings.
    This event coding consideration is not directly relevant to our Custom Class situation: We don’t have a simple way to make custom events. ( This Theme is handled in a more complex way ( https://excelfox.com/forum/showthrea...ication-Events ) )




    Ref
    ** https://www.myonlinetraininghub.com/...-module#p19192





    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=Ugxq4JHRza_zx3sz0fx4AaABAg
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=UgzMCQUIQgrbec400jl4AaABAg
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=UgwhVTFaD469mW9wO194AaABAg.9gJzxwFcnPU9gORqKw5t W_
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=Ugyb8nmKKoXvcdM58gV4AaABAg
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=UgwvvXcl1oa79xS7BAV4AaABAg
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=UgxvIFArksPprylHXYZ4AaABAg
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=Ugxq4JHRza_zx3sz0fx4AaABAg
    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA




    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    https://eileenslounge.com/viewtopic.php?f=27&t=35521&p=276185#p276185
    https://eileenslounge.com/viewtopic.php?p=276185#p276185
    https://eileenslounge.com/viewtopic.php?p=276185#p276185
    https://eileenslounge.com/viewtopic.php?p=276673#p276673
    https://eileenslounge.com/viewtopic.php?p=276751#p276751
    https://eileenslounge.com/viewtopic.php?p=276754#p276754
    https://eileenslounge.com/viewtopic.php?f=30&t=35100&p=274367#p274367
    https://eileenslounge.com/viewtopic.php?p=274368#p274368
    https://eileenslounge.com/viewtopic.php?p=274370#p274370
    https://eileenslounge.com/viewtopic.php?p=274578#p274578
    https://eileenslounge.com/viewtopic.php?p=274577#p274577
    https://eileenslounge.com/viewtopic.php?p=274474#p274474
    https://eileenslounge.com/viewtopic.php?p=274579#p274579
    https://www.excelfox.com/forum/showthread.php/261-Scrolling-Marquee-text-on-Userform?p=864&viewfull=1#post864
    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    Last edited by DocAElstein; 04-07-2024 at 11:57 AM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  2. #2
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,402
    Rep Power
    10
    For later use

    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    https://eileenslounge.com/viewtopic.php?p=318868#p318868
    https://eileenslounge.com/viewtopic.php?p=318311#p318311
    https://eileenslounge.com/viewtopic.php?p=318302#p318302
    https://eileenslounge.com/viewtopic.php?p=317704#p317704
    https://eileenslounge.com/viewtopic.php?p=317704#p317704
    https://eileenslounge.com/viewtopic.php?p=317857#p317857
    https://eileenslounge.com/viewtopic.php?p=317541#p317541
    https://eileenslounge.com/viewtopic.php?p=317520#p317520
    https://eileenslounge.com/viewtopic.php?p=317510#p317510
    https://eileenslounge.com/viewtopic.php?p=317547#p317547
    https://eileenslounge.com/viewtopic.php?p=317573#p317573
    https://eileenslounge.com/viewtopic.php?p=317574#p317574
    https://eileenslounge.com/viewtopic.php?p=317582#p317582
    https://eileenslounge.com/viewtopic.php?p=317583#p317583
    https://eileenslounge.com/viewtopic.php?p=317605#p317605
    https://eileenslounge.com/viewtopic.php?p=316935#p316935
    https://eileenslounge.com/viewtopic.php?p=317030#p317030
    https://eileenslounge.com/viewtopic.php?p=317030#p317030
    https://eileenslounge.com/viewtopic.php?p=317014#p317014
    https://eileenslounge.com/viewtopic.php?p=316940#p316940
    https://eileenslounge.com/viewtopic.php?p=316927#p316927
    https://eileenslounge.com/viewtopic.php?p=316875#p316875
    https://eileenslounge.com/viewtopic.php?p=316704#p316704
    https://eileenslounge.com/viewtopic.php?p=316412#p316412
    https://eileenslounge.com/viewtopic.php?p=316412#p316412
    https://eileenslounge.com/viewtopic.php?p=316254#p316254
    https://eileenslounge.com/viewtopic.php?p=316046#p316046
    https://eileenslounge.com/viewtopic.php?p=317050&sid=d7e077e50e904a138c794e1f2115da95#p317050
    https://www.youtube.com/@alanelston2330
    https://www.youtube.com/watch?v=yXaYszT11CA&lc=UgxEjo0Di9-9cnl8UnZ4AaABAg.9XYLEH1OwDIA35HNIei0z-
    https://eileenslounge.com/viewtopic.php?p=316154#p316154
    https://www.youtube.com/watch?v=TW3l7PkSPD4&lc=UgwAL_Jrv7yg7WWC8x14AaABAg
    https://teylyn.com/2017/03/21/dollarsigns/#comment-191
    https://eileenslounge.com/viewtopic.php?p=317050#p317050
    https://eileenslounge.com/viewtopic.php?f=27&t=40953&p=316854#p316854
    https://www.eileenslounge.com/viewtopic.php?v=27&t=40953&p=316875#p316875
    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    Last edited by DocAElstein; 07-25-2024 at 01:49 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  3. #3
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,402
    Rep Power
    10
    Not part of this blog - blog on class stuff to be finished next winter
    Alan. April 2020



    ( Post 7 )
    Part #5B Using " application events way " in the typical "class / application way"
    Brief description:
    As seen in the previous posts, it is very easy to get lost, so it is good to summarise in simple terms what we are going to do:
    We use two "standard available event routines" and one "application events routine"
    And we build two objects, or rather, we build one new object, and just assign a new variable to an existing object for the second one.
    We do a somewhat round about way, more complicated than necessary, as there seems to be some good programming reason for organising things like this in that way.
    The standard available event routine which kicks in when the workbook is opened is used. This "builds" the first of two object, in this case, a non standard object from a type (Class). The "blue print" of that type we prepare earlier. This "blue print" information is determined ( written ) inside a Class module which we add. That Class thing has a standard available event routine in it, which is the second standard available event routine thing which we use. That second standard available event routine kicks in when the first object, an object from that type/class is built. We add coding within that event routine to assign an object variable to a second object. That second object is the main object we need. So effectively, the first object being built causes that second object to be built, or rather in this case of the second object, the variable is assigned to an existing object: The variable for that object is declared to the type which is the Excel application itself. In other words, the variable we use for that object is Dimed to the Excel thing we have in front of us. But it is Dimed in a special way, like "Dim WithEvents" . This means that we then have some extra non standard available event coding available to us, which will be the event routines of the type of object ( class) to which we Dim/declare. In this case we Dim/declare to the Excel application itself, and so our new variable has access to the event routines of our Excel application itself.
    We choose to use the event routine that "monitors" workbooks being closed. The coding for that we write in the class module. So that becomes part of the second object. So once that object is built/ assigned it has that coding in it. We add in that routine the coding to determine what is done when a workbook is closed.

    Full Description and process
    Open the VB development window, for example using keys Alt+F8 when you have an Excel Application up and running in front of you.
    We insert a new Class module thing: Right click anywhere in the VBA Project window and select to insert a Class module. As we want to declare ( Dim ) to this type, it would be useful to give it a different name.
    Right Click in VBA Project window Insert Class module Rename.JPG : https://imgur.com/ZUJGnS4
    For example, in line with the reference I am using ( https://stackoverflow.com/questions/...ng-of-workbook ) I choose the name CloseHelper
    In this class code module we need the main ( second ) object which we want , which refers to the open Excel application in front of us. Lets use the variable , ClsLisWb , for this object. It is intended that this object "monitors closing of workbooks.
    From the first post of this thread ( jgzggtjgjhgjgjg ) we know that we do not want to instantiate using Set ClsLisWb = New Excel.Application , as we want to use the existing Excel open in front of us, so we add the single code line , Set ClsLisWb = Excel.Application , to the Initialize routine, which is typically the first event routine which is offered to us from the drop down list in a newly added Class module, Class Initialize Event.JPG : https://imgur.com/CC5XZOB
    The object, ClsLisWb , made by the Class initialize code is that which we want to "monitor" closing of workbooks. In the current way of doing things, the Class module effectively has written in it the blue print instructions for the object and sub objects of it, ( in this case ClsLisWb is an under object / sub object "belonging" to the parent object . ( I will arbitrarily name the first object , LisExcelLike ).
    I will add here in the Class module an event routine which is now available to ClsLisWb . We look for one which monitors workbook closing and find this one: , Private Sub ClsLisWb_WorkbookBeforeClose(ByVal Wb As Workbook, Cancel As Boolean) , WorkbookBeforeClose.JPG : https://imgur.com/xVFWMmL
    After the object ClsLisWb is "built/assigned", then this routine will effectively be a method of ClsLisWb which automatically starts on a Workbook close event taking place.
    So complete coding such as the following , within the Class module , will partially fulfil our requirements:
    CloseHelper.JPG : https://imgur.com/kt46yRn
    Class module CloseHelper
    Code:
    Option Explicit
    Private WithEvents ClsLisWb As Excel.Application
    Private Sub Class_Initialize() ' ' Routine to Instantiate ClsLisWb
     Set ClsLisWb = Excel.Application '
    End Sub
    Private Sub ClsLisWb_WorkbookBeforeClose(ByVal Wb As Workbook, Cancel As Boolean)
     Let Cancel = Not CunCls  '  With CanClose = True,  Cancel will be set to Not True = False
        If Not Wb Is ThisWorkbook Then Let Cancel = False 'To allow normal closing for other workbooks
    ' Secret code section not visible to us
        If Cancel = True Then
         'Do nothing and Exit this sub
        ElseIf Cancel = False Then
         'Close the workbook, Wb
        End If
    End Sub
    The small additional added coding from us above is similar to that from the last post, except that it includes an extra line so as to restrict the control of the closing to a particular workbook. ( To keep the example similar to the previous post, the closing control is restricted to the workbook in which the code is. ( we did not need that in the previous post ,as the corresponding event routine used , a standard one in that case, only applied to the workbook in which the routine was in. ) ).

    So we have the class module part of our solution.
    We would typically for convenience include the code to build the object LisExcelLike in the standard available event routine in the ThisWorkbook code module:
    ThisWorkbook code module
    Code:
    Private LisExcelLike As CloseHelper
    Private Sub Workbook_Open()
     Set LisExcelLike = New CloseHelper
    End Sub
    That code will kick off automatically when the workbook is opened.
    Just to remind ourselves again of what goes on: The instantiating of LisExcelLike happens then automatically when the workbook is opened, which in turn results in the instantiating, or rather assignnng, of the main object of interest to us, the second object, ClsLisWb

    Finally, as in the previous post example, we have a simple code in a normal code module to allow us to overwrite the close workbook prevention.
    Normal Code module
    Code:
    Option Explicit
    Public CunCls As Boolean
    Sub CloseMe()
     Let CunCls = True
     ThisWorkbook.Close
     Let CunCls = False ' I don't know why this is here? I don't think it will ever be done!!! ???
    End Sub






    Rem Ref
    ' ' http://www.eileenslounge.com/viewtopic.php?f=27&t=31331
    ' https://stackoverflow.com/questions/...ng-of-workbook
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  4. #4
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,402
    Rep Power
    10

    Disable Excel Close Button/ Control closing

    Not part of this blog - blog on class stuff to be finished next winter
    Alan. April 2020





    Further working examples

    Disable Excel Close Button/ Control closing
    ( Post 6 )
    Part #5 Disable Excel Close Button/ Control closing Cancel option Event code example
    We can do another example as a solution to a question to “Disable Excel Close Button”. This is a good example of using an Event routine which has the Cancel option available

    Part #5A Using “normal event routines” or “standard available event routines
    Event routines of the kind required for controlling Workbook events can typically be “found” from a group which we can find in the ThisWorkbook code module
    So
    Double-click ThisWorkbook to open its code module: then you can write in manually, or better still, evoke from the drop down lists a “Workbook procedure” with the name: Private Sub Workbook_BeforeClose(Cancel As Boolean )
    Evoke a Private Sub Workbook_BeforeClose(Cancel As Boolean).JPG : https://imgur.com/T7w6FJN , https://imgur.com/J22uX3g
    Code:
    Private Sub Workbook_BeforeClose(Cancel As Boolean)
      ' here we can add code to this “already available to us” event coding. Effectively the workbook was Dimed WithEvents somehow to the hidden class or similar of the Workbook object which is effectively also already effectively instantiated as we "open" the Workbook
    End Sub
    I am thinking that in such a code ….. the code has a secret hidden coding at the end which you can’t see. It really looks, pseudo, like this:
    Code:
    Private Sub Workbook_BeforeClose(Cancel As Boolean)
    
    ' here we can add code to this “already available to us” event coding. Effectively the workbook was Dimed WithEvents somehow to the hidden class or similar of the Workbook object which is effectively also already effectively instantiated as we "open" the Workbook
    
    ' Secret code section not visible to us
        If Cancel = True Then
         'Do nothing and Exit this sub
        ElseIf Cancel = False Then
         'Close this workbook
        End If
    End Sub
    So a solution , such as here http://www.eileenslounge.com/viewtopic.php?f=27&t=31331 , is to give you a way to have the default value of Cancel set to True within that code Private Sub Workbook_BeforeClose(Cancel As Boolean ) . ( I assume that the usual default value of Cancel will be False ).
    So, as in that post, we add coding in that event procedure which will make Cancel True by default. This will result in the , Private Sub Workbook_BeforeClose(Cancel As Boolean ) preventing a close of the workbook.
    For example, assume we have some global Boolean variable, CanClose , which by default will be False , (False is the default state for a Boolean Variable )
    Then we add a code line to the event routine:
    Code:
    Private Sub Workbook_BeforeClose(Cancel As Boolean)
     Let Cancel = Not CanClose '  With CanClose = True,  Cancel will be set to Not True = False
    
    ' Secret code section not visible to us
        If Cancel = True Then
         'Do nothing and Exit this sub
        ElseIf Cancel = False Then
         'Close this workbook
        End If
    End Sub
    The above coding will mean that if we do nothing else, Cancel will be set to True. So in normal use, such as by the user hitting the close button top right , Excel Close Button.JPG: https://imgur.com/ZvQCF2q , that procedure will prevent/cancel the closing.
    Then we could make a procedure, Sub CloseMe() , to be put in a normal module , _..
    Code:
    Public CanClose As Boolean ' This will be False by default
    
    
    Sub CloseMe()
     Let CanClose = True
     ThisWorkbook.Close
     Let CanClose = False ' I don't know why this is here? I don't think it will ever be done!!! ???
    End Sub
    _... This will allow you to change the value of Cancel to True: It works as follows: If that procedure, Sub CloseMe(), is run, then it changes the global variable, CanClose , to True, and then the next line, _..
    ThisWorkbook.Close
    _.. cause the code, Private Sub Workbook_BeforeClose(Cancel As Boolean) to start, and with CanClose equal to True, Cancel being set to Not CanClose , will be set to its usual value of False, and the workbook will close as usual.


    That all makes sense, I think.
    _._________________________________


    In the next post, I will do the equivalent with “application events way” in the typical “class / application way” that is typically done. As was discussed in previous posts, this is a slightly less direct way then necessary, but which is preferred for reasons of good programming practice.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  5. #5
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,402
    Rep Power
    10

    Disable Excel Close Button/ Control closing

    Not part of this blog - blog on class stuff to be finished next winter
    Alan. April 2020





    Further working examples

    Disable Excel Close Button/ Control closing
    ( Post 6 )
    Part #5 Disable Excel Close Button/ Control closing Cancel option Event code example
    We can do another example as a solution to a question to “Disable Excel Close Button”. This is a good example of using an Event routine which has the Cancel option available

    Part #5A Using “normal event routines” or “standard available event routines
    Event routines of the kind required for controlling Workbook events can typically be “found” from a group which we can find in the ThisWorkbook code module
    So
    Double-click ThisWorkbook to open its code module: then you can write in manually, or better still, evoke from the drop down lists a “Workbook procedure” with the name: Private Sub Workbook_BeforeClose(Cancel As Boolean )
    Evoke a Private Sub Workbook_BeforeClose(Cancel As Boolean).JPG : https://imgur.com/T7w6FJN , https://imgur.com/J22uX3g
    Code:
    Private Sub Workbook_BeforeClose(Cancel As Boolean)
      ' here we can add code to this “already available to us” event coding. Effectively the workbook was Dimed WithEvents somehow to the hidden class or similar of the Workbook object which is effectively also already effectively instantiated as we "open" the Workbook
    End Sub
    I am thinking that in such a code ….. the code has a secret hidden coding at the end which you can’t see. It really looks, pseudo, like this:
    Code:
    Private Sub Workbook_BeforeClose(Cancel As Boolean)
    
    ' here we can add code to this “already available to us” event coding. Effectively the workbook was Dimed WithEvents somehow to the hidden class or similar of the Workbook object which is effectively also already effectively instantiated as we "open" the Workbook
    
    ' Secret code section not visible to us
        If Cancel = True Then
         'Do nothing and Exit this sub
        ElseIf Cancel = False Then
         'Close this workbook
        End If
    End Sub
    So a solution , such as here http://www.eileenslounge.com/viewtopic.php?f=27&t=31331 , is to give you a way to have the default value of Cancel set to True within that code Private Sub Workbook_BeforeClose(Cancel As Boolean ) . ( I assume that the usual default value of Cancel will be False ).
    So, as in that post, we add coding in that event procedure which will make Cancel True by default. This will result in the , Private Sub Workbook_BeforeClose(Cancel As Boolean ) preventing a close of the workbook.
    For example, assume we have some global Boolean variable, CanClose , which by default will be False , (False is the default state for a Boolean Variable )
    Then we add a code line to the event routine:
    Code:
    Private Sub Workbook_BeforeClose(Cancel As Boolean)
     Let Cancel = Not CanClose '  With CanClose = True,  Cancel will be set to Not True = False
    
    ' Secret code section not visible to us
        If Cancel = True Then
         'Do nothing and Exit this sub
        ElseIf Cancel = False Then
         'Close this workbook
        End If
    End Sub
    The above coding will mean that if we do nothing else, Cancel will be set to True. So in normal use, such as by the user hitting the close button top right , Excel Close Button.JPG: https://imgur.com/ZvQCF2q , that procedure will prevent/cancel the closing.
    Then we could make a procedure, Sub CloseMe() , to be put in a normal module , _..
    Code:
    Public CanClose As Boolean ' This will be False by default
    
    
    Sub CloseMe()
     Let CanClose = True
     ThisWorkbook.Close
     Let CanClose = False ' I don't know why this is here? I don't think it will ever be done!!! ???
    End Sub
    _... This will allow you to change the value of Cancel to True: It works as follows: If that procedure, Sub CloseMe(), is run, then it changes the global variable, CanClose , to True, and then the next line, _..
    ThisWorkbook.Close
    _.. cause the code, Private Sub Workbook_BeforeClose(Cancel As Boolean) to start, and with CanClose equal to True, Cancel being set to Not CanClose , will be set to its usual value of False, and the workbook will close as usual.


    That all makes sense, I think.
    _._________________________________


    In the next post, I will do the equivalent with “application events way” in the typical “class / application way” that is typically done. As was discussed in previous posts, this is a slightly less direct way then necessary, but which is preferred for reasons of good programming practice.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  6. #6
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,402
    Rep Power
    10
    Not part of this blog - blog on class stuff to be finished next winter
    Alan. April 2020



    ( Post 7 )
    Part #5B Using " application events way " in the typical "class / application way"
    Brief description:
    As seen in the previous posts, it is very easy to get lost, so it is good to summarise in simple terms what we are going to do:
    We use two "standard available event routines" and one "application events routine"
    And we build two objects, or rather, we build one new object, and just assign a new variable to an existing object for the second one.
    We do a somewhat round about way, more complicated than necessary, as there seems to be some good programming reason for organising things like this in that way.
    The standard available event routine which kicks in when the workbook is opened is used. This "builds" the first of two object, in this case, a non standard object from a type (Class). The "blue print" of that type we prepare earlier. This "blue print" information is determined ( written ) inside a Class module which we add. That Class thing has a standard available event routine in it, which is the second standard available event routine thing which we use. That second standard available event routine kicks in when the first object, an object from that type/class is built. We add coding within that event routine to assign an object variable to a second object. That second object is the main object we need. So effectively, the first object being built causes that second object to be built, or rather in this case of the second object, the variable is assigned to an existing object: The variable for that object is declared to the type which is the Excel application itself. In other words, the variable we use for that object is Dimed to the Excel thing we have in front of us. But it is Dimed in a special way, like "Dim WithEvents" . This means that we then have some extra non standard available event coding available to us, which will be the event routines of the type of object ( class) to which we Dim/declare. In this case we Dim/declare to the Excel application itself, and so our new variable has access to the event routines of our Excel application itself.
    We choose to use the event routine that "monitors" workbooks being closed. The coding for that we write in the class module. So that becomes part of the second object. So once that object is built/ assigned it has that coding in it. We add in that routine the coding to determine what is done when a workbook is closed.

    Full Description and process
    Open the VB development window, for example using keys Alt+F8 when you have an Excel Application up and running in front of you.
    We insert a new Class module thing: Right click anywhere in the VBA Project window and select to insert a Class module. As we want to declare ( Dim ) to this type, it would be useful to give it a different name.
    Right Click in VBA Project window Insert Class module Rename.JPG : https://imgur.com/ZUJGnS4
    For example, in line with the reference I am using ( https://stackoverflow.com/questions/...ng-of-workbook ) I choose the name CloseHelper
    In this class code module we need the main ( second ) object which we want , which refers to the open Excel application in front of us. Lets use the variable , ClsLisWb , for this object. It is intended that this object "monitors closing of workbooks.
    From the first post of this thread ( jgzggtjgjhgjgjg ) we know that we do not want to instantiate using Set ClsLisWb = New Excel.Application , as we want to use the existing Excel open in front of us, so we add the single code line , Set ClsLisWb = Excel.Application , to the Initialize routine, which is typically the first event routine which is offered to us from the drop down list in a newly added Class module, Class Initialize Event.JPG : https://imgur.com/CC5XZOB
    The object, ClsLisWb , made by the Class initialize code is that which we want to "monitor" closing of workbooks. In the current way of doing things, the Class module effectively has written in it the blue print instructions for the object and sub objects of it, ( in this case ClsLisWb is an under object / sub object "belonging" to the parent object . ( I will arbitrarily name the first object , LisExcelLike ).
    I will add here in the Class module an event routine which is now available to ClsLisWb . We look for one which monitors workbook closing and find this one: , Private Sub ClsLisWb_WorkbookBeforeClose(ByVal Wb As Workbook, Cancel As Boolean) , WorkbookBeforeClose.JPG : https://imgur.com/xVFWMmL
    After the object ClsLisWb is "built/assigned", then this routine will effectively be a method of ClsLisWb which automatically starts on a Workbook close event taking place.
    So complete coding such as the following , within the Class module , will partially fulfil our requirements:
    CloseHelper.JPG : https://imgur.com/kt46yRn
    Class module CloseHelper
    Code:
    Option Explicit
    Private WithEvents ClsLisWb As Excel.Application
    Private Sub Class_Initialize() ' ' Routine to Instantiate ClsLisWb
     Set ClsLisWb = Excel.Application '
    End Sub
    Private Sub ClsLisWb_WorkbookBeforeClose(ByVal Wb As Workbook, Cancel As Boolean)
     Let Cancel = Not CunCls  '  With CanClose = True,  Cancel will be set to Not True = False
        If Not Wb Is ThisWorkbook Then Let Cancel = False 'To allow normal closing for other workbooks
    ' Secret code section not visible to us
        If Cancel = True Then
         'Do nothing and Exit this sub
        ElseIf Cancel = False Then
         'Close the workbook, Wb
        End If
    End Sub
    The small additional added coding from us above is similar to that from the last post, except that it includes an extra line so as to restrict the control of the closing to a particular workbook. ( To keep the example similar to the previous post, the closing control is restricted to the workbook in which the code is. ( we did not need that in the previous post ,as the corresponding event routine used , a standard one in that case, only applied to the workbook in which the routine was in. ) ).

    So we have the class module part of our solution.
    We would typically for convenience include the code to build the object LisExcelLike in the standard available event routine in the ThisWorkbook code module:
    ThisWorkbook code module
    Code:
    Private LisExcelLike As CloseHelper
    Private Sub Workbook_Open()
     Set LisExcelLike = New CloseHelper
    End Sub
    That code will kick off automatically when the workbook is opened.
    Just to remind ourselves again of what goes on: The instantiating of LisExcelLike happens then automatically when the workbook is opened, which in turn results in the instantiating, or rather assignnng, of the main object of interest to us, the second object, ClsLisWb

    Finally, as in the previous post example, we have a simple code in a normal code module to allow us to overwrite the close workbook prevention.
    Normal Code module
    Code:
    Option Explicit
    Public CunCls As Boolean
    Sub CloseMe()
     Let CunCls = True
     ThisWorkbook.Close
     Let CunCls = False ' I don't know why this is here? I don't think it will ever be done!!! ???
    End Sub






    Rem Ref
    ' ' http://www.eileenslounge.com/viewtopic.php?f=27&t=31331
    ' https://stackoverflow.com/questions/...ng-of-workbook
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  7. #7
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,402
    Rep Power
    10
    Not part of this blog - blog on class stuff to be finished next winter
    Alan. April 2020



    ( Post 7 )
    Part #5B Using " application events way " in the typical "class / application way"
    Brief description:
    As seen in the previous posts, it is very easy to get lost, so it is good to summarise in simple terms what we are going to do:
    We use two "standard available event routines" and one "application events routine"
    And we build two objects, or rather, we build one new object, and just assign a new variable to an existing object for the second one.
    We do a somewhat round about way, more complicated than necessary, as there seems to be some good programming reason for organising things like this in that way.
    The standard available event routine which kicks in when the workbook is opened is used. This "builds" the first of two object, in this case, a non standard object from a type (Class). The "blue print" of that type we prepare earlier. This "blue print" information is determined ( written ) inside a Class module which we add. That Class thing has a standard available event routine in it, which is the second standard available event routine thing which we use. That second standard available event routine kicks in when the first object, an object from that type/class is built. We add coding within that event routine to assign an object variable to a second object. That second object is the main object we need. So effectively, the first object being built causes that second object to be built, or rather in this case of the second object, the variable is assigned to an existing object: The variable for that object is declared to the type which is the Excel application itself. In other words, the variable we use for that object is Dimed to the Excel thing we have in front of us. But it is Dimed in a special way, like "Dim WithEvents" . This means that we then have some extra non standard available event coding available to us, which will be the event routines of the type of object ( class) to which we Dim/declare. In this case we Dim/declare to the Excel application itself, and so our new variable has access to the event routines of our Excel application itself.
    We choose to use the event routine that "monitors" workbooks being closed. The coding for that we write in the class module. So that becomes part of the second object. So once that object is built/ assigned it has that coding in it. We add in that routine the coding to determine what is done when a workbook is closed.

    Full Description and process
    Open the VB development window, for example using keys Alt+F8 when you have an Excel Application up and running in front of you.
    We insert a new Class module thing: Right click anywhere in the VBA Project window and select to insert a Class module. As we want to declare ( Dim ) to this type, it would be useful to give it a different name.
    Right Click in VBA Project window Insert Class module Rename.JPG : https://imgur.com/ZUJGnS4
    For example, in line with the reference I am using ( https://stackoverflow.com/questions/...ng-of-workbook ) I choose the name CloseHelper
    In this class code module we need the main ( second ) object which we want , which refers to the open Excel application in front of us. Lets use the variable , ClsLisWb , for this object. It is intended that this object "monitors closing of workbooks.
    From the first post of this thread ( jgzggtjgjhgjgjg ) we know that we do not want to instantiate using Set ClsLisWb = New Excel.Application , as we want to use the existing Excel open in front of us, so we add the single code line , Set ClsLisWb = Excel.Application , to the Initialize routine, which is typically the first event routine which is offered to us from the drop down list in a newly added Class module, Class Initialize Event.JPG : https://imgur.com/CC5XZOB
    The object, ClsLisWb , made by the Class initialize code is that which we want to "monitor" closing of workbooks. In the current way of doing things, the Class module effectively has written in it the blue print instructions for the object and sub objects of it, ( in this case ClsLisWb is an under object / sub object "belonging" to the parent object . ( I will arbitrarily name the first object , LisExcelLike ).
    I will add here in the Class module an event routine which is now available to ClsLisWb . We look for one which monitors workbook closing and find this one: , Private Sub ClsLisWb_WorkbookBeforeClose(ByVal Wb As Workbook, Cancel As Boolean) , WorkbookBeforeClose.JPG : https://imgur.com/xVFWMmL
    After the object ClsLisWb is "built/assigned", then this routine will effectively be a method of ClsLisWb which automatically starts on a Workbook close event taking place.
    So complete coding such as the following , within the Class module , will partially fulfil our requirements:
    CloseHelper.JPG : https://imgur.com/kt46yRn
    Class module CloseHelper
    Code:
    Option Explicit
    Private WithEvents ClsLisWb As Excel.Application
    Private Sub Class_Initialize() ' ' Routine to Instantiate ClsLisWb
     Set ClsLisWb = Excel.Application '
    End Sub
    Private Sub ClsLisWb_WorkbookBeforeClose(ByVal Wb As Workbook, Cancel As Boolean)
     Let Cancel = Not CunCls  '  With CanClose = True,  Cancel will be set to Not True = False
        If Not Wb Is ThisWorkbook Then Let Cancel = False 'To allow normal closing for other workbooks
    ' Secret code section not visible to us
        If Cancel = True Then
         'Do nothing and Exit this sub
        ElseIf Cancel = False Then
         'Close the workbook, Wb
        End If
    End Sub
    The small additional added coding from us above is similar to that from the last post, except that it includes an extra line so as to restrict the control of the closing to a particular workbook. ( To keep the example similar to the previous post, the closing control is restricted to the workbook in which the code is. ( we did not need that in the previous post ,as the corresponding event routine used , a standard one in that case, only applied to the workbook in which the routine was in. ) ).

    So we have the class module part of our solution.
    We would typically for convenience include the code to build the object LisExcelLike in the standard available event routine in the ThisWorkbook code module:
    ThisWorkbook code module
    Code:
    Private LisExcelLike As CloseHelper
    Private Sub Workbook_Open()
     Set LisExcelLike = New CloseHelper
    End Sub
    That code will kick off automatically when the workbook is opened.
    Just to remind ourselves again of what goes on: The instantiating of LisExcelLike happens then automatically when the workbook is opened, which in turn results in the instantiating, or rather assignnng, of the main object of interest to us, the second object, ClsLisWb

    Finally, as in the previous post example, we have a simple code in a normal code module to allow us to overwrite the close workbook prevention.
    Normal Code module
    Code:
    Option Explicit
    Public CunCls As Boolean
    Sub CloseMe()
     Let CunCls = True
     ThisWorkbook.Close
     Let CunCls = False ' I don't know why this is here? I don't think it will ever be done!!! ???
    End Sub






    Rem Ref
    ' ' http://www.eileenslounge.com/viewtopic.php?f=27&t=31331
    ' https://stackoverflow.com/questions/...ng-of-workbook
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  8. #8
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,402
    Rep Power
    10
    later again

  9. #9
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,402
    Rep Power
    10
    This is post https://www.excelfox.com/forum/showt...ll=1#post24163 https://www.excelfox.com/forum/showt...age3#post24163




    Some Extra notes to go with this main forum post
    https://eileenslounge.com/viewtopic....ffd8b7#p317533

    That forum post is one of those increasing occurrences recently of a one off post answering a question. There relevance to the Thread and their quality varies a lot. This one was fairly relevant but more of a quick example files perhaps picked up from somewhere, and I doubt we will ever see the OP again and I doubt he knows much about what he posted.
    But it gave me a chance to try and get some Class ideas of mine a bit better understood


    It is probably helpful to download the uploaded file, and have it open it in Excel, whilst working through the next few posts





    First what is it all about
    This appears to be an example of my suggested second of two main areas that class things may be used …_ 2 The area where I have mostly seen …… This usually involves tackling the area of WithEvents ….


    I started with a new virgin simple .xls file, and put a Class Module in it
    Add a Class Module.JPG

    I went through copying across your ( OP SamPi ) coding and changing it a bit and adding some 'comments to help me explain what was going on.
    (By the way, What actually happens (should happen) is that …
    Provided you first open the main file with all the class stuff in it, ( that was your (OP SamPi) OpenExcelFile.xlsm , and it is now my WatchMyFileOpenings.xls), then after that , if you open a file with the name test.csv , then, a message box should pop up and tell you about it )


    First the Class module stuff.
    This is my slightly modified version of your (OP SamPi) coding put inside the Class module.
    I gave the class module the name FileOpenWatcher , but that does not mean much. Initially, before we put text of coding into it, its just like a blank sheet of paper.
    Finally as below, it’s not much more. It is just like text on a bit of paper. Whilst not completely incorrect, it might be dangerous to envisage this as a template. This might cause one to think of it as a thing to be copied and used over and over again. Later with hindsight, this conception can be misleading. It is better to think of it as some notes in your pocket on a piece of paper, that you work from to make something over and over again. Think of there being other text notes and information, which we personally do not concern ourselves with, and when we use all the information, the text of the coding is just one thing we use. Generally it is a bad idea to consider copying of a class or coding in a class module. It can be misleading to the actual underlying concepts.
    The class module is generally designed to be used over and over again, in the similar way that a function is. In this example we only use it once. Here is the full text. Perhaps that text could be thought better conceptually as like that on a Stamp


    Class module, FileOpenWatcher: ( https://i.postimg.cc/TPPmLX2K/File-O...ode-module.jpg ) of WatchMyFileOpenings.xls
    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, 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 coding is not actual coding that will ever be done. It is like a blue print, or a Stamp , from which an actual object module will be made with that coding in it, (by an instanciate later in coding in another code module –
    In other words, something looking just like that, could be considered to appear, Stamped out as it were, by executing the following code lines
    Dim MeWatcher As FileOpenWatcher
    Private Sub Workbook_Open() ' This is done when this file opens
    Set MeWatcher = New
    We must image this appearing, as we do not see it)
    The full coding(text) window shown above is in a true Class module, as I tried to explain in my previous post , so its just like text on a piece of paper, and on its own pretty useless.

    Lets explain the build up of that text (which will later be coding):
    The very first line, Public WithEvents ExApp As Excel.Application , does something along the lines of making the variable, ExApp ,somehow be of a type like the Excel you are using, but not specifically the actual one you are using.
    The extra WithEvents means it gets all the usual Excel event codings so we can tap into them, ( and for convenience, after you make this line we get them extra things listed in the drop down list of the Class module
    WithEvents of the Excel application.JPG

    We have chosen the event coding that kicks in when a workbook is opened, as that is what we need for our particular example
    As generally with event coding, it can be considered that it is always there and runs when the event occurs ( the event of opening of a workbook in this example ), but we can add coding into it, so that this added coding also kicks in when the event occurs ( the event of opening of a workbook in this example )

    In this case the coding is fairly simple, to do a message box pop up, when a file opens with the name test.csv
    Code:
    ' 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
    

    So that’s it for the class module. It’s only half the full story. The second half is in the next post

    A last important thing again to remember: This is just like a piece of paper with a text of coding on it that will never run itself.
    We may "copy" that text and put it somewhere so as to use as "real" coding to be run.
    The "copy", is effectively done by these 2 sort of code lines later,
    Dim MeWatcher As FileOpenWatcher
    Private Sub Workbook_Open() ' This is done when this file opens
    Set MeWatcher = New

    The use of "copy" is perhaps a bit unwise, better is to imagine it stamped out

    With that we are finally doing is instantiating: A class describes the variables, properties, procedures, and events of an object (but a class is not an object itself; an object comes into existence when a class is instantiated)
    Attached Images Attached Images
    Attached Files Attached Files
    Last edited by DocAElstein; 06-16-2024 at 01:19 AM.

  10. #10
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,402
    Rep Power
    10
    Special procedures in Class text module

    Public Variable Properties 2


    Extended use of the special Class module text Procedures.
    The previous example was a simplified use to show the direct comparison with how they might typically be used to achieve the same as the simple Public variable as property. But we have much more flexibility due to these extra special procedures. Here are just a few notes and examples of some of the extra possibilities

    Extra coding text within the procedures
    Most normal VBA coding text is accepted inside the procedures. A simple example could be coding inside the Public Property Let to check the data given, and take action, such as a message box with a warning, followed by Exiting if the supplied data is unacceptable ..._
    ___If Len(Clr) > 20 Then MsgBox prompt:="That is too long for a color word": Exit Property
    _... … etc.. etc… etc… The possibilities are almost endless.

    Extra arguments
    In addition, the syntax allows us to bring in any other variables, which are added before the main variable in the Public Property Let signature line
    For example,
    Public Property Let CrColor(Optional CrsNme As String, Clr As String)
    for syntax reasons we must duplicate the extra information exactly in the paired Public Property Get
    Public Property Get CrColor(Optional CrsNme As String) As String
    ( I am not restricted to Optional argument. The coding works ijn the conventional way regarding the argument definitions: If I did not choose Optional , then I would have to give them in any usage or I would get an error )
    These extra arguments appear to be held internally somewhere as a form of pseudo global variable.


    Demo example
    To demonstrate this: Lets say we want to optionally provide a Car name, when giving the car color.
    This would be the slight modification necessary in the class module test:
    In class module Car
    Code:
    Private PrvteCrColor As String
    Public Property Let CrColor(Optional CrsNme As String, Clr As String)
     Let PrvteCrColor = CrsNme & " is " & Clr
    End Property
    Public Property Get CrColor(Optional CrsNme As String) As String ' this property returns the value, As String
     Let CrColor = PrvteCrColor
    End Property
    We can now add some code lines to our macro in a normal code module to demonstrate the use of the extra lines thus:
    In any normal code module
    Code:
    Sub My_CarColor()
    Dim objCr As Car: Set objCr = New Car ' This is the normal codelines used to typically make an object variable of a particular  Class
     Let objCr.CrColor = "Yellow"                               '  "write"  to the  CrColor  variable in objCr
     MsgBox Prompt:="I have colored my Car  " & objCr.CrColor   '  "read" (Get) from the  CrColor  variable in objCr
     
     Let objCr.CrColor("Mustang") = "Yellow"
     MsgBox Prompt:=objCr.CrColor    '
    End Sub
    The initial code lines work similarly to previously. The extra two lines at the end make use of the new argument possibility.

    The first message box gives _ I have colored my Car _ is Yellow
    The second message box gives _ Mustang is Yellow

    Notes:
    _1 ) Argument types
    We have chosen arbitrarily in the last example, the extra argument to be Optional in this example, but the general rules associated with procedures and Functions apply , such that , for example , if we had not included the Optional statement in the signature line, then we would have had to give a value for this in both of the Let code lines in the above normal code module macro. Because we used Optional , we were able to use the previous code lines in addition to the new one which makes uses of any supplied argument value

    _2) Review of paired nature and syntax structure
    _2)(i) We do not have to have a pair, since the absence of one of the other gives us the possibility to restrict the property on the instantiated object to be just either read or write. ( *I personally would usually keep the things in pairs and then ‘comment out as/ if necessary the procedure not required. I would do this as the syntax is a bit tricky/ complicated and easy to mix up the slight differences in the matched pairs )
    _2)(ii) *Assuming we use a pair , we can summarise the syntax as follows:
    There must be at least one argument, say, Nme , ( the last one ), in the Let …_
    _ Public Property Let Xyz ( ___ , ___ , Nme As Vrtyp ) ‘ takes in Nme via code line in normal macro like Let Onj.Xyz = “Myname”
    _ … The corresponding Get , below , returns a value in a similar way to how a normal VBA Function does. In the simplest case it returns the value brought in by the Let, ( Nme in this example ). Or it may have some relation to the value taken in by the Let. Or it can be something totally different. Or it can do something else and return no value, just as we sometimes do with a normal VBA Function. In this latter case there is no advantage over a simple procedure text in the class module, which also acts as a method of an object instantiated from the class.
    _ Public Property Get Xyz ( ___ , ___ , _ ) As Vrtyp ‘ This works similar to a standard VBA Function.

    In simple general terms, to relate to standard VBA things, we might refer to the .Xyz property, as we would, for example to the standard VBA .Value property
    _.____



    !!! Public Property Set
    In line with normal VBA declaration conventions and syntaxes, the word Set is used in place of Let if we are using an object variable type, ( in the above shown here : Vrtyp ) which is a an object
    _ Public Property Set Xyz ( ___ , ___ , Obj As VrObject )
    There is nothing new , special, or seemingly particular useful with the Public Property Set.
    In the next post, I will do a simple example and possibly add later any example I ever find useful.
    Last edited by DocAElstein; 03-03-2021 at 11:24 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

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
  •