Results 1 to 4 of 4

Thread: Understanding VBA Range Object Properties and referring to ranges and spreadsheet cells

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

    Understanding VBA Range Object Properties and referring to ranges and spreadsheet cells

    What is a cell and a Range Object.
    As Jorge G says here, https://powerspreadsheets.com/excel-vba-range-object/ , cells is probably the first thing that springs to mind when thinking about Excel. Often, cells is used very generally and imprecisely ( and occasionally very wrongly *** ). Mostly one uses “cells” as a very general term to refer to the "boxes" as you see them in a spreadsheet. Usually what you see as such is an extremely small amount of what is associated with, and can be done with, the cells. The word sticks in the mind from most people's initial experience with looking at Excel as a spreadsheet full of square boxes or cells with possibly some values in it, or seeing coloured rectangular areas etc. I will use italics where I use that or similar words generally and imprecisely. I will use bold for a specific defined Excel or VBA Object

    More precisely Excel organises its cells into groups of one or more cells and stores all information about these grouped cells in what it calls a Range Object. In simple terms this is just something that stores all the information. ( There is no VBA Cell or Cells Object. There is a Cells Property, but this is badly misunderstood. I will attempt to add some clarity in the next post ***).
    It follows that the smallest Range Object is that associated with a single cell.
    Even for a single cell, the information associated with a Range Object is massive . It is worth taking a look at it, - see here for example: http://www.excelforum.com/showthread...11#post4551080
    The Range Object is arguably the most important, the most biggest , and the most incorrectly understood Excel thing. Microsoft recently corrected some of their literature after I bombarded their various feedback parts of web sites with Comments explaining to them their mistakes and telling them it how I saw it.

    What is this Post about ( points to note )
    There are several ways to refer to ( or in a Object Oriented Hierarchical Programming type language we often say “to return” ) a Range Object.
    This post concentrates on the 2 - 3 Main ways to refer to or "return” a Range Object in VBA by "applying" to some Object "Properties" of the type having a coordinate type argument. For a beginner, this will come across a bit vague and imprecise at this stage . A good way to think of what I am on about is to think about how you get to a point of, or an area within , a map. Alternatively think of it as similar to navigating the globe through a pair of axis at 90 Degrees to each other.
    The other very important point to note at an early stage is that a Range Object can be, and is typically, associated with a single cell or a single rectangular spreadsheet area full of cells. The latter here, of all the cells within it is often referred to as a group of contiguous cells. ( In layman's terms contiguous means all of them – no spaces – none missing.. etc.).
    However, more precisely defined , The Range Object is organised into one or more of such single cells or rectangular groups of contiguous cells. Each one of these is named an Area. Because of the definition of a Range Object, it follows that each Area is itself a Range Object. ( That could further be sub divided into further areas, but rarely is).
    One last point here to note, is that in many ( not all ) cases the use of a variable in VBA for a Range Object in a code in this sort of from_..
    Rng.
    _.. is actually defaulting to the first Area that the Range Object has in its Areas list. ( It must, by definition, have at least one area ). As such, VBA effectively would "see" this in many, ( not all ), cases as the implied default.
    Rng.Areas.Item(1).
    The properties discussed in this post all apply to a single area, defaulting to the first area if none is given.
    http://www.excelforum.com/showthread...11#post4551484 http://www.excelforum.com/showthread...11#post4551080
    http://www.excelforum.com/showthread...=9#post4521752
    http://www.excelforum.com/showthread...9#post4521753_


    Referring to ranges in VBA ( What is a range )
    As with the word cells, the word ranges is equally very loosely used. Approximately it is referring to all the cells in a Range Object, or more commonly just the first and only area thereof. So once again it is referring to the part of the Range Object which we typically "see".
    Almost everything about the Range Object seems to have been designed to confuse. I expect it is based on the deep down workings of Excel. Deep down Excel has pseudo only one of anything, and what we "see" as multiple things is based on a complex system based on increments and offsets stored as sets of coordinates. Where numbers or sets of numbers match or "intercept" based on some algorithm results in our imaginary grid, aka. The spreadsheet we see in front of us.
    So Excel thinking is about referring via offsets from some point.
    The spreadsheet convention in Excel is fairly consistent in that it starts at, (that is to say row 1 and column 1 ( or "A" ) is), "top left" . A further very common and widely used convention is to " go along from the top left for all columns, then down to the next row, go along all columns from the left, then down to .. etc.."
    In our Property discussions we are using either
    _the sequential Item or Index following that convention, or
    _ the row number and column number, or, mostly,
    _ the default row number and column letter coordinate convention system.
    By the Latter row number and column letter coordinate convention system here we are talking about the typical default Excel Address strings like "A1" for a single cell and , "B2:C3" for a cell area where "B2" is top left, and "C3" is bottom right. ( There are some other syntaxes which are "allowed" , but it is best not to use then in my opinion. As others also note, Excel is probably defaulting in such cases back to the row number and column letter or row number and column letter or Item number , and there is the risk that we may end up with inappropriately constructed references when relying on the implicit default, https://powerspreadsheets.com/excel-...ent-3096080590 ) .

    _1) Range( ) type Properties
    Although not defined as such, the statement Range( ) "works" generally something like a method returning the Range Object given by or referred to by the string reference argument in the ( ). As noted, we should strictly restrict ourselves with range Properties to simple Address strings in the row number and column letter notation. Other syntaxes are accepted but can lead to problems.
    This Property type allows us to return a single cell, a multiple cell single area, or any combination thereof to give us a multi Areas Range Object. We have a single and double argument option.
    The single argument option is the most common as we can use it to refer to all possible Range Object types. For example, we would have forms such as
    _ a single cell area like Range("A1") ,
    _ a single area of multiple contiguous cells like Range("B2:C3"), and
    _ a multi area Range Object like Range("B2,D5:F7,G1,J1:J10,Named_Range") etc.. etc...
    Range( ) type Properties are confined to "+ve directions", that is to say going to the right or down from top left
    The double argument option is less common and is an alternative for, and restricted to, a single range area of one or cells. It is a "top left, bottom right" notation. So from the examples above, Range("A1") would be written Range("A1", "A1") and Range("B2:C3") would be written Range("B2", "C3"). Once again syntaxes other than row number and column letter notation are accepted but can lead to problems. ***

    _1a) Worksheets Range Property
    A Worksheet Object has a Property called Range. This is the Range ( ) discussed above using the row number and column letter Address notation based on "A1" being the first cell ( top left ) in the worksheet.
    It is advisable to always specify explicitly the Worksheet with a code line such as_..
    Worksheets("Sheet1").Range ("B2:C3")
    _... rather than relying on the default worksheet taken by
    Range ("B2:C3") .
    Similarly using variables helps keep things well organised:
    Dim Ws1 As Worksheet
    Set Ws1 = ThisWorkbook.Worksheets("Sheet1")
    Dim Rng As Range
    Set Rng = Ws1.Range("B2:C3")

    _1b) Range Range Property
    That title above, Range Range, is not a typo!. ( Frequently Excel use the same word for different things which helps confuse us). Range is the Range Object and Range or Range Range is the Property explained in this section.
    Having established a Range Object, such as for example, the Rng in _1a) , then the Range( ) can be used in exactly the same way once again, but this time the top left is the top left of the Range Object to which it applies
    So, as example, Rng, above was the single area Range Object of the 2row x 2column cells area starting top left in the Worksheet at B2, ( and extending to bottom right of C3).
    Therefore Rng.Range("B2:C2") will return a Range Object of a 1row x 2 columns cells area in the Worksheet in which Rng is in. The range starts top left at coordinate B2 relative to Address "B2" in the Worksheet. So finally the Address in the Worksheet of this new Range Object will be "C3:D3"
    Once Again all types of single and multi area cells and range construction is possible, but as the referencing will again only be able to refer to cells to the right and down from the original Range Object top left, then one cannot reference any cells to the left of, or back up from top left, in this case, B2 of the original Range Object, Rng in the Worksheet.

    _2) Range Item Property of a single cells area
    This is currently less commonly known, mostly because it is incorrectly referred to as a cells Property.
    Microsoft have changed some of their documentation following my recommendations to clarify the situation.
    This is a simpler coordinate referencing convention limited to referring to a single cell.
    It is more restrictive to the type, that is to say multiple cells ranges cannot be referred to, but in some of the argument options that it has, it allows “-ve and +ve direction” referring, which actually, strangely, allows for all cells in the Worksheet to be referenced , regardless of the start top left cell. ( But not with all argument options )
    _2a) VBA Items and range items. ( Range Item Property single argument ( ) case )
    Generally in VBA, for Objects or ( Properties) which have ( or can refer to ) a collection of similar things, the individual things can be referenced through a consecutive number or index like 1, 2, 3 .. etc.. Typically the syntax is like .Item(x), where x is usually an integer from 1 to the total Count of the similar things. ( For such an Object, the Object may be referred to as a Collection Object ).
    For the case of a Range Object of a single rectangular area of spreadsheet contiguous cells , things are a bit different*. Amongst other things, this number relates to each cell in the Range Object and usually to a some outside it. The ordering follows the typical Excel Spreadsheet cells order convention of numbered from left to right and from top to bottom. *Strangely, for the case of a Range Object we may use this to reference cells outside the Range Object that lie within the Worksheet boundaries. So we are not restricted to the Items count. For the single argument option, these "Overshoot" Items follow further the typical row then column convention , so effectively we can refer to and return a single cell Range Object anywhere from top left of the original range, and extending down to the bottom of, (but not beyond), the Worksheet in a column of width equal to that of the original range
    _2 b) Range Item Property double ( , ) argument case
    *It is a further confusing aspect of the Range Object that for the Range Object Item Property we may also use two arguments in the ( , ) bracket representing the row, and column. If this option is chosen then we can use numbers for both, or , for the columns , the column letter (wrapped in quotations) may be used as an alternative. In the two argument case we may extend beyond the original Range Object from the top left in the Original Range Object in the usual row, column way, ( we are not restricted to a particular width as with the one argument option). Note further, that when using the two argument option for the Range Object Item Property, negative co ordinates are permitted also, and we are again not restricted to the original range . This allows us to refer to all cells in the Worksheet.... Note however:
    _ the Range Object will need to have its top left far enough away from the Worksheet Top left origin such that the negative co ordinate applied does not go “further back to the left” or “further back up” than the Spreadsheet boundaries ;
    _ zeros in such as this Property reference, ( 0, 0 ) , is also from the syntax valid. Such a reference will effectively go “back up, and back left” by 1 ;
    _ there are no “-ve Letters” . So –ve column referencing is restricted to using column number referencing
    _..
    _ Returning multi cell and multi area Range Objects which contain cells back to the left or back up from top left of a Range Object can obviously be achieved by applying initially –ve Range Item Properties, followed by the appropriate Range Range Property.
    The point to note here is that the range Properties return a Range Object to which one can further apply range properties

    _...

    The above is all, I think, that one needs to know in order to effectively refer to, and return, Range Objects using range Properties.
    In the next post I try to clarify a few things that can lead to confusion ***
    Last edited by DocAElstein; 02-04-2017 at 02:45 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,270
    Rep Power
    10
    The last post covers the basic information for using Referring to Ranges in VBA using the two main properties , Range( ) Properties and Range Item Property

    But there are a lot of pit falls to be aware of. This post summarises them and suggests solutions


    _3 ) Cells Property
    There is no Cells Object. As noted in the previous Post, cells is often used in a general imprecise way to talk about aspects of the "boxes" we see in a spreadsheet.
    There is , however, a specific VBA Cells Property.
    But it is actually a property with no arguments which simply returns a Range Object comprising of the entire cells ( or single cell Range Objects ) contained in the Object to which it is applied.
    It has very limited use. The only one I can think of is for returning a Range Object comprising of a single area all cells within a Worksheet. This allows you to do all with the entire Worksheet cells that you can do with a Range Object.
    A couple of situations arise which cause confusion and lead to a false discussion of a Cells property which is typically explained as having the same arguments as the Range Item Property. One will very commonly see something of this form_..
    Cells(row, column)
    _..explained as a Cells property available to refer to a range. ( I even did it myself for a long time, and apologise for confusing any OPs! )
    A couple of examples to clarify and explain how the confusion comes about
    _3a ) Cells Property and Range Objects
    It is perfectly acceptable to apply the Cells Property to a Range Object . Indeed it is frequently done. But it is totally redundant as far as I can see.
    The results of doing this however, are frequently to present and explain a cells(row, column) type property incorrectly. To understand this it is important to understand the Range Item Property. So make sure you understand that before going any further. OK?
    Now consider some arbitrary Range Object. Say that associated with the first cell Item of a worksheet , Set to a variable such:
    Dim Rng1 As Range
    _ Set Rng1 = ThisWorkbook.Worksheets("Sheet1").Range("A1") ' Using Range Property of a Worksheet to return a Range Object
    Using the Range Item Property to return from this Range Object a new Range Object, say that of the second worksheet Item cell could be done explicitly as follows.
    Code:
    Dim Rng2 As Range
     Set Rng2 = Rng1.Areas.Item(1).Item(2)
    ' or
     Set Rng2 = Rng1.Areas.Item(1).Item(1, 2)
    ' or
     Set Rng2 = Rng1.Areas.Item(1).Item(1, "B")
    In most cases the first and only Area is being considered, which is the default, so .Areas.Item(1) is usually omitted. As with most VBA Objects, for the Range Object the default Property is the Item. This allows then from the syntax the .Item part in the Range Item Property statement to be removed. One acceptable shortened form would then be such as this:
    _ Set Rng2 = Rng1(1, 2)
    As noted we may apply the Cells property to a Range Object ( even though it is totally redundant because it returns the same Range Object )
    So we could also write_..
    _ Set Rng2 = Rng1.Cells(1, 2)
    _.. Here the same Range Object is returned by Cells , and that returned Range Object is having the Range Item Property applied to it. - .Cells is redundant here and can be removed. http://stackoverflow.com/questions/2...91641#41491641

    _3b ) Cells Property and Worksheet Objects
    This comes a bit closer to getting it correct, but not quite.
    The Cells property can be used to return directly a Range Object ( containing all the cells ) of a Worksheet. Without using the Cells Property we cannot therefore apply the Range Item Property.
    So this is valid for our previous example
    _ Set Rng2 = Worksheets("Sheet1").Cells.Areas.Item(1).Item(1, 2)
    Once again .Areas.Item(1) can be omitted, and .Item(1, 2) simplified to (1, 2), resulting in
    _ Set Rng2 = Worksheets("Sheet1").Cells(1, 2)
    We could just as well do this
    _ Set Rng2 = Worksheets("Sheet1").Range("A1").Areas.Item(1).Ite m(1, 2)
    and again simplify this to
    _ Set Rng2 = Worksheets("Sheet1").Range("A1")(1, 2)
    One could argue that Cells(1, 2) looks a bit neater than Range("A1")(1, 2). I personally would probably use Range("A1")(1, 2) just to remind me that I am using the Range Item Property in end effect. It might also be that creating a Range Object initially of just the first cell rather than of the entire worksheet cells might have some different effect.

    _4) Workbooks and Worksheets referencing in range property arguments
    I mentioned a few times that in the Range( ) statement syntaxes other than simple Address strings are accepted.
    My experiments suggest that this could be not directly as a conscious design to aid in ease of flexibility of use in range property constructs, but rather a by product of making the Range( ) compatible in use for a more direct way of referencing a Range Object. Briefly:
    _4a) In the single argument Range( ) case, it is possible use a full reference, or part thereof , in the string, using a form such as this
    Range("='[MyFile.xlsm]Sheet1'!A1") or Range("='Sheet1'!A1")
    _4b) In the two argument case it is possible to do something similar in this form
    Range(Workbooks("MyFile.xlsm").Worksheets("Sheets1 ").Range("A1"), Workbooks("MyFile.xlsm").Worksheets("Sheets1").Ran ge("A1"))
    or
    Range(Worksheets("Sheets1").Range("A1"), Worksheets("Sheets1").Range("A1"))
    _4c)(i) Defaulting Address
    I am thinking that the Workbooks and Worksheets referencing discussed in _4a and _4b) allows some sort of pseudo direct Object referencing as opposed to referring through a Property. This effectively uses the Range( ) statement to return the Application Range and the Range( ) statement argument must full qualify the Range Object as there is no preceding Object from which to obtain the necessary Worksheets reference. ( A cell or rather Range Object is an Object under / in a Worksheet ). This is not needed in the property usage case. But as it is there in the Range( ) statement "workings" for the above reason then it will still be accepted by a call of Range( ) in a property code line.
    It is found that if the Workbooks and Worksheets referencing in range property arguments is not the same as the Workbook and the Worksheet to which the Property is applied, the Range( ) statement errors due to the "method of range object for that Worksheet failing". This is consistent with that the full referencing is not really appropriate in the Properties referring cases. It works only if the final addressed cell or cells are within the Worksheet to which the property is being , ( or to the worksheet in which the Range Object to which it is applied is in ).
    _4c)(ii) Defaulting Address and some named range
    Another reason for the acceptance of a string other than the Address can be seen when considering the use of a named range in the constructs for the property referring. A named range may be used in place of any Address reference. However a point to note is that if we give the name of a range in a Worksheet appropriate for the property reference , "some_named_range", this named range must not have scope, that is to say, must not be accessible, from that Worksheet. The way Excel handles this situation is that actually it adds to our name. For example, consider that our named range is in Worksheet "Sheet1", but has been scoped to Worksheets "Sheet2". Excel actually holds this name as "Sheet2!some_named_range". A construct as this is then acceptable, and indeed needed: Worksheets("Sheet1").Range("A1,Sheet2!some_named_r ange")
    We might write_..
    Worksheets("Sheet1").Range ("A1,some_named_range")
    _.. but Excel reads that as the former. ( We note that Excel has the sometimes unnerving effect of changing string references to suit appropriately https://powerspreadsheets.com/excel-...ent-3105025065 ) . So this is another reason for the "acceptance" of a string argument larger than the simple Address
    _4d) Set Rng=Ws.Range(ws.Cells(1, 1), Ws.Cells(2, 2))
    Last edited by DocAElstein; 09-06-2019 at 07:30 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,270
    Rep Power
    10

    My mate Bill is a bit of a Tw@ - I gave him a Range object and he used the Cells property on it.

    I wanted to fill my VBA variable , Ra, with the Range object associated with the single cell C3 in a Worksheet which has a VBA variable , Ws, filled with that Worksheet object thereof. I thought I would do it using one of the two main types of Range property which returns a Range object, the Range Item Property. I decided to use it in its two argument form .Item(3, 3) as that returns me the Range object 3 down and 3 across from the top left cell of the single spreadsheet cells area Range object to which the property is applied.

    I thought it would be convenient to have my top left at the top left of the worksheet Ws. I thought of a couple of ways of doing that.
    __ First I thought I would fill a variable with the Range object of a few cells starting at the top left of my worksheet as I could maybe think of that as an area to work in. So I used the other main Range property type for returning a Range object , the Range(" ") type. I used the one belonging to the Worksheet Object class. So I ended up with a code looking something like this
    Set Rng = Ws.Range("A1:E5")' My work area
    Then I used the Range Item Property to get the Range object of cell C3 like this
    Set Ra = Rng.Areas.Item(1).Item(3, 3)
    I simplified it a bit: - Rng defaults to the first area if I remove the .Areas.Item(1) bit, and the default property of a Range object is the Range Item Property, so .Item(3, 3) can be replaced by (3, 3)
    So I ended up with
    Set Ra = Rng(3, 3)
    or this
    Set Ra = Ws.Range("A1:E5")(3, 3)

    __ My mate Bill is a bit obsessed the Cells property. So I thought I would do it again in a way to please him. I basically did the same, but used .Cells to return me the Range object of the entire cells in the worksheet. ( Note we have no Cells or Cell Object in VBA ). Here I went:
    Set Rng = Ws.Cells ' My work area is now the whole worksheet area
    Then similar to as before
    Set Ra = Rng.Areas.Item(1).Item(3, 3)
    simlified
    Set Ra = Rng(3, 3)
    or this
    Set Ra = Ws.Cells(3, 3)

    _.....

    I was not too keen on using Cells, but Bill always insisted.
    One day I thought I would play a joke on my mate Bill. I gave him a variable filled with the Range Object associated with the third cell in the worksheet,
    Set Rng = Ws.Range( "A3")
    Then I said to him jokingly, "..... take Rng and apply the cells property on that, like going 1 across and 3 down, to get my Range object, Ra..."
    Bill had and a quick think, then gave me this
    Set Ra = Rng.cells(3, 1)
    Ha Ha ! -- laugh ..,- I nearly did ! _......

    So I had a go at explaining it to him ...like this:
    This is the full code line he has:
    Set Ra = Rng.Cells.Areas.Item(1).Item(3, 1)
    .Cells is returning the Range object associated with all the cells in Rng. So it is returning exactly the same Range object as the range Object to which it is applied. So it is totally unnecessary.
    I then explained to him about the default area and the default Range Item property.
    So his final code line should of been
    Set Ra = Rng(3, 1)
    He got most of it. But he still is obsessed with his cells property and left that unnecessary bit in . He even keeps telling people that he is using a property with row and coordinate arguments to give him Ra based on like Rng.cells(row3, column1) or r.Cells(n, 1) etc...
    I keep trying to explain it to him but he doesn’t seem to have got the point yet...
    https://msdn.microsoft.com/en-us/lib.../ff196273.aspx



    _.............

    Color convention broadly speaking:
    Black is to do with a Range Object. It is an indication of that object or a property returning that object
    Cyan is to do with properties in general in a code ( and may only appear in part of the code word which is a property)
    Purple is a particular property in this case the Range Item Property
    Last edited by DocAElstein; 02-04-2017 at 01:32 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!!

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

    Simple VBA Range Item Property Demo

    A quick graphic demo of Range Item Property arguments. ( Aka , as many people still think of as
    Cells( takes arguments rows, columns ) Property. ( Which does not exist )
    )

    The full code descriptions and arguments and explanations thereof are around here:
    http://www.excelforum.com/showthread...11#post4551080
    and here:
    http://www.excelforum.com/showthread...11#post4551509
    and here:
    http://www.excelforum.com/showthread...11#post4555023


    An arbitrary Range object, that associated with the spreadsheet cells in a single area top left:bottom right of B3:C4 is shown highlighted in Yellow.
    In each cell shown, some of the Range Item Property argument options are indicated.

    This Post is intended to indicate the required syntax required in the brackets in order to use the a to refer to any cell in the worksheet in which the Range object is in.

    To summarise:
    We may use the VBA Range Item Property ( https://msdn.microsoft.com/en-us/lib.../ff841096.aspx https://msdn.microsoft.com/en-us/lib...ffice.15).aspx ) applied to a single Area of Range object to refer to any single cell in a worksheet. That is to say we use the VBA Range Item Property applied to a Range object to return a new Range object associated with any single cell in a worksheet.

    For the Range Item Property we have different argument options available.
    The syntax is based on
    either
    a two argument row, column coordinate system , like (1, -2) or (3, “B”)
    or
    a single argument sequential Item number ( Index ), like (3)

    In both cases the origin is taken as top left of the Range object to which the Property is applied.
    So if our original Range object variable was declared and then “filled” such_..
    Dim Rng1 As Range
    _ Set Rng1=Ws.Range(“B2”)
    _..then we may obtain a new range object thus:
    Dim Rng2 As Range
    _ Set Rng2=Rng1.Item(1, 2) ’ Returns Range object associated with cell C2 in worksheet Ws ( same row, one ”to the right” )
    or this
    _ Set Rng2=Rng1.Item(1, “B”) ’ Returns Range object associated with cell C2 in worksheet Ws ( same row, one ”to the right” )
    or this
    _ Set Rng2=Rng1.Item(0, 0) ’ Returns Range object associated with cell A1 in worksheet Ws ( one “back up”, and one “back to the left” )
    or this
    _ Set Rng2=Rng1.Item(2) ’ Returns Range object associated with cell C2 in worksheet Ws ( one ”to the right” )

    ( In all the code lines the .Item can be removed as the Range Item Property is the default property for a range Object. So we could write like this:
    _ Set Rng2=Rng1(1, 2)
    ( Often the .Cells property is included in such a code line. That is completely redundant in such a case as the .Cells Property returns the Range object of all the cells in the Object to which it is applied. So in such a code line the .Cells Property applied to Rng1 returns Rng1, but it looks nice:
    _ Set Rng2=Rng1.Cells(1, 2)
    http://excelmacromastery.com/excel-v.../#comment-2891 ) )


    To explain how we return the Range object associated with a single cell, such as like C2 or A1
    ( __In the screenshots below, the ( ) brackets like (1, 2) are as we would use them in a code line like we had above: Rng2=Rng1(1, 2) __)

    For the two argument option, we can refer to rows and columns by numbers which can also be negative which allows this option to refer to any single cell anywhere in the spreadsheet. Every row number and column possibility is shown from code line 20. ( It is also possible to use a column letter enclosed in quotes as an alternative, but this is limited to “+ve” letters ).

    All 2 argument options ( row number, column number )
    Row\Col
    A
    B
    C
    D
    1
    Rng_Item( -1, 0 )
    Rng_Item( -1, 1 )
    Rng_Item( -1, 2 )
    Rng_Item( -1, 3 )
    2
    Rng_Item( 0, 0 )
    Rng_Item( 0, 1 )
    Rng_Item( 0, 2 )
    Rng_Item( 0, 3 )
    3
    Rng_Item( 1, 0 )
    Rng_Item( 1, 1 )
    Rng_Item( 1, 2 )
    Rng_Item( 1, 3 )
    4
    Rng_Item( 2, 0 )
    Rng_Item( 2, 1 )
    Rng_Item( 2, 2 )
    Rng_Item( 2, 3 )
    5
    Rng_Item( 3, 0 )
    Rng_Item( 3, 1 )
    Rng_Item( 3, 2 )
    Rng_Item( 3, 3 )
    _..............................

    For the single argument option, all Item number possibilities are shown from code line 30. We start at top left of the original Range object and follow the typical spreadsheet convention of along all columns then down to next row. We can refer to all cells in a column of width equal to that of the original Range object area, extending down to the bottom of the worksheet in this column then row convention. Effectively only positive Item numbers ( Indexes ) are possible, but strangely we have Items outside the original Range object. The alternative column letter option is also shown over the single argument ( Index) area, but note that the column letter option is also available to the right of the Index area: The complete “+ve” letter range is shown in red text

    All single argument ( Index ) options
    Some 2 argument ( row number, column number ) options
    Some 2 argumant ( row number, column number ) options
    (complete column letter option range is shown in red text
    Row\Col
    A
    B
    C
    D
    1
    Rng_Item( -1, 0 )
    Rng_Item( -1, 1 )
    Rng_Item( -1, 2 )
    Rng_Item( -1, 3 )
    2
    Rng_Item( 0, 0 )
    Rng_Item( 0, 1 )
    Rng_Item( 0, 2 )
    Rng_Item( 0, 3 )
    3
    Rng_Item( 1, 0 )
    RngItm(1, "A") and RngIem( 1 )
    RngItm(1, "B") and RngIem( 2 )
    Rng_Item( 1, 3 )
    4
    Rng_Item( 2, 0 )
    RngItm(2, "A") and RngIem( 3 )
    RngItm(2, "B") and RngIem( 4 )
    Rng_Item( 2, 3 )
    5
    Rng_Item( 3, 0 )
    RngItm(3, "A") and RngIem( 5 )
    RngItm(3, "B") and RngIem( 6 )
    Rng_Item( 3, 3 )


    _....

    Simplified code:
    Code:
    Sub Funky2Tests2() '  http://www.excelforum.com/showthread.php?t=1154829&page=13&p=4566077#post4566077
    Dim RngObj1Area As Range ' Arbritrary Test Range
     Set RngObj1Area = Range("B3:C4") '
     Range("A1:D5").ClearContents: RngObj1Area.Interior.Pattern = xlNone: Let Range("A1:D5").Font.ColorIndex = xlAutomatic 'Prepare demo range
     Call RangeItemsArgumants2SHimpfGlified2(RngObj1Area, Range("A1:D5"))
    End Sub
    Sub RangeItemsArgumants2SHimpfGlified2(RngOrg As Range, RngDemo As Range)
    10  Let RngOrg.Interior.Color = 65535  'mark original Range Object spreadsheet cell area
    20  Let RngDemo.Value = Evaluate("=" & """Rng_Item( """ & "&" & "(Row(" & RngDemo.Address & ")" & "-" & "Row(" & RngOrg.Item(1).Address & ")" & ")+1&" & """, """ & "&" & "(Column(" & RngDemo.Address & ")-Column(" & RngOrg.Item(1).Address & "))+1" & "&" & """ )""")
    30 Dim RngItmLtrRow As Range: Set RngItmLtrRow = RngOrg.Resize((((RngDemo.Row + RngDemo.Rows.Count) - 1) - RngOrg.Row) + 1, RngOrg.Columns.Count): Let RngItmLtrRow.Value = Evaluate("=" & """RngItm(""" & "&" & "(Row(" & RngItmLtrRow.Address & ")" & "-" & "Row(" & RngItmLtrRow.Item(1).Address & ")" & ")+1&" & """, """"""" & "&" & "MID(ADDRESS(1,COLUMN(" & RngItmLtrRow.Address & ")-COLUMN(" & RngItmLtrRow.Item(1).Address & ")+1),2,(FIND(""$"",ADDRESS(1,COLUMN(" & RngItmLtrRow.Address & ")-COLUMN(" & RngItmLtrRow.Item(1).Address & ")+1),2)-2))" & "&" & """"""") and RngIem( """ & "&" & "(Column(" & RngItmLtrRow.Address & ")-Column(" & RngItmLtrRow.Item(1).Address & "))+1+" & "(((Row(" & RngItmLtrRow.Address & ")" & "-" & "Row(" & RngItmLtrRow.Item(1).Address & ")" & ")+1-1)*" & RngOrg.Columns.Count & ")" & "&" & """ )""")
    40 Dim RngCL As Range: Set RngCL = RngItmLtrRow.Resize(, ((RngDemo.Column + RngDemo.Columns.Count) - 1) - RngItmLtrRow.Column + 1): Let RngCL.Font.Color = -16776961
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    ' Rem Ref
    ' http://excelmatters.com/referring-to-ranges-in-vba/
    ' https://powerspreadsheets.com/excel-vba-range-object/
    ' http://spreadsheetpage.com/index.php...your_vba_code/   
    ' http://stackoverflow.com/questions/2...91641#41491641
    ' http://www.excelfox.com/forum/showth...eadsheet-cells
    ' http://www.excelforum.com/tips-and-t...eet-cells.html
    
    End Sub



    Edit 27 October, 2021-10-28 2021-10-27 05:05:17 excelfroum.com links may have changed
    http://www.excelforum.com/showthread...11#post4551080 ---- https://www.excelforum.com/developme...ml#post4551080
    http://www.excelforum.com/showthread...11#post4551509 ---- https://www.excelforum.com/developme...ml#post4551509
    http://www.excelforum.com/showthread...11#post4555023 ---- https://www.excelforum.com/developme...ml#post4555023
    Last edited by DocAElstein; 10-28-2021 at 12:09 PM.

Similar Threads

  1. Understanding the Formula
    By excel_learner in forum Excel Help
    Replies: 4
    Last Post: 12-27-2013, 01:52 PM
  2. Replies: 1
    Last Post: 12-13-2013, 05:45 AM
  3. Replies: 13
    Last Post: 06-10-2013, 09:05 AM
  4. 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
  5. Excel VBA Dictionary Object
    By Rajan_Verma in forum Rajan Verma's Corner
    Replies: 1
    Last Post: 05-13-2012, 10:01 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
  •