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

Thread: VBA Range.Sort with arrays. Alternative for simple use.

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

    Taking SimpleArraySort7 to SimpleArraySort8

    Here are the key simplifications to take SimpleArraySort7 to SimpleArraySort8

    Array referencing
    Version Sub SimpleArraySort8(_ has as main distinguishing characteristic the removal of , or rather replacement of array , arsRef() , by that used in The Index method code line, arrIndx() . This array, arrIndx() , is moved from global variables: The array taken for By Referencing at the signature line will be arrIndx() in place of arsRef() . All references to arsRef() are replaced by arrIndx()
    This could have been left as a global variable, but by declaring it in the signature line of Sub SimpleArraySort8(_ makes it the “housing carrying” wrapper for the supplied variable to the recursion routine array , and we can then leave the global variable with that same name arrIndx() for further use in the previous Sub SimpleArraySort7(_
    The arrays for the index line in the recursion routine arrOrig() , Rs() , Cms() , remain as globals.
    We will use the arrTS() from the original range capture to pass to be referenced to ( housed effectively within arrIndx() ). So that will be our final sorted array. ( arrIndx() will also be our final sorted array up to the point of the finally Ending of the first copy of the recursion routine, at which point that will then die: It is effective isolated from the “outside code module world”, so does not influence the global variable with the same name which we still have and which is available still for the previous version Sub SimpleArraySort7(

    Column elements in a row swapping
    One of the main distinguishing characteristics of the Index idea way, is that we sort the row indices in to a new order, and then apply the code line, .._
    arrIndx() = App.Ind(arrOrig() , rowindicis, columnindicies
    _.. to get the new order in one go.
    However we must be careful. The immediate conclusion might possibly be that all the sections swapping all column elements in a row are now redundant and so can be removed. The is almost true, but not quite: The reordering of the row indicia is following directly the bubbling through sort of the column being used in the current sort. We must therefore continue to sort/ swap this column element for the rows in parallel to sorting/ swapping the row indicie.
    Thus sections such as this in the previous Sub SimpleArraySort7(_ were swapping all the column elements and row indicies for two rows determined by the row number variables rOuter and rInner, …_

    If IsNumeric(arsRef(rOuter, Clm)) And IsNumeric(arsRef(rInner, Clm)) Then
    __ If CDbl(arsRef(rOuter, Clm)) < CDbl(arsRef(rInner, Clm)) Then
    ____ For Clms = 1 To UBound(arsRef(), 2)
    _____ Let Temp = arsRef(rOuter, Clms): Let arsRef(rOuter, Clms) = arsRef(rInner, Clms): Let arsRef(rInner, Clms) = Temp
    ____ Next Clms '----------| for each column in the array at the two rows rOuter and rInner
    ___ Let TempRs = Rs(rOuter, 1): Let Rs(rOuter, 1) = Rs(rInner, 1): Let Rs(rInner, 1) = TempRs


    _....Those sections need to be modified now so that they just swap those two rows in the column currently used to base the sort on, ( as well as still doing the swap of the row indicia )
    We note that Clms was the variable for all columns in the loop for all columns in the swapping in the code snippet above , and Clm was the variable for the current column being used to determine the current sort order. So we no longer need that loop to swap all columns, - that can be removed. But if we do this removal, we must add a swap section for the Clm column …_

    If IsNumeric(arrIndx(rOuter, Clm)) And IsNumeric(arrIndx(rInner, Clm)) Then
    __ If CDbl(arrIndx(rOuter, Clm)) < CDbl(arrIndx(rInner, Clm)) Then
    ___ Let Temp = arrIndx(rOuter, Clm): Let arrIndx(rOuter, Clm) = arrIndx(rInner, Clm): Let arrIndx(rInner, Clm) = Temp
    ___ Let TempRs = Rs(rOuter, 1): Let Rs(rOuter, 1) = Rs(rInner, 1): Let Rs(rInner, 1) = TempRs


    Simplifying ' Captains Blog, Start Treck
    A number of additions were made for the previous version in order to compare the sort at various stages made by
    the previous way – that in arsRef()
    and
    the Index idea way – that in arrIndx()

    These are no longer needed and are removed to make the routine a better direct comparison with the latest routine version used in the previous l way , Sub SimpleArraySort6(_



    Calling routine Sub TestieSimpleArraySort8() ( and Global variables and a required Function )
    http://www.excelfox.com/forum/showth...ll=1#post11056

    recursion routine Sub SimpleArraySort8(
    http://www.excelfox.com/forum/showth...ll=1#post11058




    I have started doing some timing measurements for the Index way idea to complement those already done ( http://www.excelfox.com/forum/showth...ll=1#post11037 Example: A few thousand columns with a few dozen rows )
    The new measurements start from approximately here:
    http://www.excelfox.com/forum/showth...ll=1#post11055
    http://www.excelfox.com/forum/showth...ll=1#post11061


    The initial measurements do not look particularly good.

    In the next posts I will review and summarise this idea for a simple example as a pre stage in a slight re Write of coding Sub TestieSimpleArraySort8()
    The re write is to make better use of the row indices since I can use them in place of the string of row indices which I currently pass through routines ( strRws = “ 1 2 6 9 8 ……. “ )
    Last edited by DocAElstein; 03-17-2019 at 07:48 PM.

  2. #12
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10

    Index idea summary

    Index idea Summary


    This is intended to summarise the ideas from the last posts, using a simplified Example
    The previous coding was an attempt to make a similar coding to the previous routines for a good comparison.
    The purpose of this summary is to
    re introduce the idea from scratch both to help understanding the general idea,
    but also
    to be a first step in the development of a generally more efficient coding by virtue of it being developed from the outset as for the Index idea.

    Index Idea coding Complete
    We can split this into two main ideas
    Non Index idea bits
    We remain with the general array recursion idea already used. The bubble sort technique is used.
    The principle idea is to have an initial coding section, Rem 1. As previously this makes a sort of rows. Those are all the range data rows initially. They are always sorted based on the values in a specific column. ( Often the chosen column number or letter will be referred to as the ”Key:= _, _ )
    The idea behind the use of recursion, is that after every sort, a check is done for rows having the same value. A copy of the sort routine then is done for those based on another column . This process goes on for as many different columns as necessary to get an ordered list , ( assuming the user has supplied enough “Keys” )
    Index Idea bit
    Without the index idea but I do this: If sorting “rows” in an array, using the Bubble sort way, then I go along ( down ) comparing values in a column, and swap them based on a < or > comparison. This means once the criteria for a sort has been reached, then I have to swap not only the values in the column that I am using to compare values, but also I have to do that for all columns in any two rows that get swapped.
    For the Index idea way, firstly , I introduce an array, typically a 2 dimension 1 column, (“vertical”) array. It has all the indices of the rows in it. So at the start of any coding it looks like,

    Rws() = 1;
    ____¬___2;
    ____¬___3;
    ____¬___.
    ____¬___.
    ___¬___.….etc
    ..
    ( Often conventionally that is seen written as Rws() = {1; 2; 3…. …etc…} , whereby the ; typically indicates a new line for a “vertical” array )

    I then still do the bubble sort/ swap along ( down ) a column. But I only change the values in that column and ignore the other columns. However I also swap the relevant row indices.
    Just to clarify: Lets say after a bubble sort I ended up swapping the value in a column in the second and third rows. As I do that swap I also swap the same elements of my indicia array, Rws()
    So looking at those numbers above, they would change to

    Rws() = 1;
    ____¬___3;
    ____¬___2;
    ____¬___.
    ____¬___.
    ___¬___.….etc
    ...
    ( or Rws() = {1; 3; 2…. , … etc…} )

    Index idea way
    In its simplest explanation: Excel VBA Application.Index Method applies a {row, column} co ordinate to an array to give the element from the array at the given {row, column} co ordinate position.
    Less well documented is, that it allows us to reorder an array in this sort of way, pseudo code:

    A b c _________________ A b c
    G h I ___=___ App.Indx( D e f , {1; 3; 2} , {1, 2, 3} )
    D e f _________________ G h i


    A b c _________________ A b c __ { 1;
    G h I ___=___ App.Indx( D e f , __ 3; __ , {1, 2, 3} )
    D e f _________________ G h I ____ 2 }


    The exact theory to how that above process works need a few weeks of reading to understand,
    http://www.excelfox.com/forum/showth...on-and-VLookUp
    https://www.excelforum.com/excel-new...ml#post4571172

    A summary based on the discussions at those above links, applied to our situation, is that Excel tries to reference the array in the first argument of the Index line, 9 times. This is that second argument 3x3 array
    A b c
    D e f
    G h I

    The second and third argument “force” Excel to try and do a 3 row x 3 column set of nine calculations
    It needs for this referencing 9 sets of co ordinates to apply to that 3x3 array to return a similarly sized array.
    The important conclusion form the theory at those links, is that in our situation, the way that Excel “works” means that as a , ( probably accidental ) , by-product of how Excel “works”, we effectively get duplications to fill the “missing” co ordinates
    So Excel goes along all columns, then down a row, then along all columns, then down a row, then along all columns, using, in or example, these co ordinates, pseudo
    ___1 1 1 ___ 1 2 3
    ___3 3 3 _, _ 1 2 3
    ___2 2 2 ___ 1 2 3
    So it does pseudo this, using the second argument, to give the final left hand Side results :.._
    ___{1,1}=A {1,2}=b {1,3}=c ‘ all columns for first row
    ___{3,1}=G {3,2}=h {3,3}=I ‘ all columns for third row
    ___{2,1}=D {2,2}=e {2,3}=f ‘ all columns for second row
    _.. it does each reference at a proportionally “offset place” in its “memory” , and so the returned output is in dimensions reflecting the 9 calculations.
    _.__________

    So , the idea of the index way is that we just sort the values in a column and additionally change correspondingly the row indicie array , Rs().
    At the end of the sort we have a code line something like this, which will give the row re order along all columns
    __arrIndx() = Application.Index(arrOrig(), Rs(), Cms())
    The original data array, arrOrig() , and the sequential list of the columns , Cms() , remains constant throughout any recursion coding.
    The order of the indices in Rs() and subsequently the row order for the final array in arrIndx() , will typically change after each sort.


    Simplified Examples
    The purpose of this coding is simply to be able to easily follow and understand the entire bubble sort and bubble sort with Index idea way.
    Therefore we will restrict the examples to simple numbers. The coding will deliberately be hard coded in many places to show actual numbers , as this will make it easier to see what we are doing.
    We will use the same test data range.
    Row\Col
    B
    C
    D
    E
    10
    1
    2
    3
    4
    11
    1
    1
    5
    3
    a
    12
    2
    9
    9
    9
    b
    13
    3
    1
    4
    2
    c
    14
    4
    8
    8
    8
    d
    15
    5
    1
    3
    2
    e
    16
    6
    7
    7
    7
    f
    Worksheet: Sorting
    The red numbers are not part of the test data range: I have added them manually and are just shown for convenience and to help in the explanations: They represent the “horizontal column” and “vertical row” indicies.
    I will intend to do a sort based on three columns. I will do this in two routines, Sub Bubbles , and Sub BubblesIndexIdeaWay. Both use the bubble sort, and the second modifies slightly the routine to use the Index way idea
    I will go for a simple Ascending order sort, based on sorting first by the first column , then the third and finally the second. A manual inspection tells me that the first sort will end up with three rows it cannot order because of all values of 1 in that first column. The second sort by column 3 will not be able to sort two rows both containing a 2 in that third column. A final sort by the second column should be able to give a final order.
    I can also check this by applying a simple coding using the existing VBA Range Sort Method: In a simple single line use this allows me to have up to 3 Keys
    SortRng.Sort _ key1:=SortRng.Columns(1), order1:=xlAscending, Key2:= SortRng.Columns(3), order2:=xlAscending, Key3:= SortRng.Columns(2), order3:=xlAscending, MatchCase:=False
    Code:
    Sub RangeSort() '  https://docs.microsoft.com/de-de/office/vba/api/excel.range.sort
    ' data range info
    Dim WsS As Worksheet: Set WsS = ThisWorkbook.Worksheets("Sorting")
    Dim RngToSort As Range: Set RngToSort = WsS.Range("B11:E16")
    ' copy and sort range using VBA Range.Sort Method
     RngToSort.Copy
     WsS.Paste Destination:=WsS.Range("B31")
    Dim SortRng As Range: Set SortRng = WsS.Range("B31").Resize(RngToSort.Rows.Count, RngToSort.Columns.Count)
     SortRng.Sort key1:=SortRng.Columns(1), order1:=xlAscending, Key2:=SortRng.Columns(3), order2:=xlAscending, Key3:=SortRng.Columns(2), order3:=xlAscending, MatchCase:=False '   Note: SortRng.Columns(3) --  the columns property of the range object, SortRng , gives the third column from the range SortRng , not the third column from the spreadsheet third column
    End Sub
    Running the above routine gives us the following:
    Row\Col
    A
    B
    C
    D
    E
    30
    1
    2
    3
    4
    31
    5
    1
    3
    2
    e
    32
    3
    1
    4
    2
    c
    33
    1
    1
    5
    3
    a
    34
    6
    7
    7
    7
    f
    35
    4
    8
    8
    8
    d
    36
    2
    9
    9
    9
    b
    Worksheet: Sorting
    Once again I have added the red numbers manually for demonstration purposes

    In the next posts we will develop the Array routine alternatives Sub Bubbles , and Sub BubblesIndexIdeaWay
    Last edited by DocAElstein; 03-15-2019 at 11:11 PM.

  3. #13
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10

    Index idea Summary. Sub Bubbles , and Sub BubblesIndexIdeaWay

    Recursion routines: Sub Bubbles , and Sub BubblesIndexIdeaWay

    Sub Bubbles
    Because recursion routines , ( at least for me ) are always difficult to understand, we will initially do a recursion routine without the new Index idea way, but which will use hindsight from the previous posts to make it in a way that can be easily modified to become Sub BubblesIndexIdeaWay But it actually the modifications are very minor, and actually only in the Calling routine Sub Call_Sub_Bubbles()
    I suppose I am just to trying to consolidate the understanding of the recursion code, before introducing the new “Index way idea” form of it.
    In this routine, Sub Bubbles , I will already use a global variable, which I have more recently introduced specifically for the Index way idea, Rs()
    In previous coding I have passed a string of the row indices , strRws = “ 1 3 2 5 6 7 “ , between different copies of the recursion routines. Because I need to use Rs() in the next routine , Sub BubblesIndexIdeaWay , I will make use of it now to ease the transition to the Index way idea.
    But important : I later need Rs() in , Sub BubblesIndexIdeaWay to house all indices in a reordered way to allow use of the App.Index formula. So I can’t do away with my strRws, which is used to pass between recursion routine copies the sub set of rows to be sorted for when rows in the column currently last sorted had duplicate values.
    So I mention Rs() a bit, but don’t really use it much..
    Only in the case of the first copy of the recursion routine, the previous string , strRws , and R(s) , fulfil the same basic purpose of housing indices for the current row order in the current running copy of the recursion routine

    So for Sub Bubbles, or rather Sub Call_Sub_Bubbles() , we need ( only ) the global variable R(s).
    But it does no harm to include all the variable needed for this and Sub BubblesIndexIdeaWay, at the top of the code module,
    Code:
    Option Explicit
    Dim Cms() As Variant, Rs() As Variant      ' "Horizointal Column" Indicies  , "Virtical row" Indicies
     Dim arrOrig() As Variant                   ' This    arrIndx() = Application.Index(arrOrig(), Rs(), Cms())  applies the modified Rs() to the original unsorted data range. So we need an array to use constantly containing the original data range
    Calling routine Sub Call_Sub_Bubbles()
    Usually routines that take arguments at the signature line ( in the Sub( x As Long, …. start bit) ) , cannot be run directly , and must be set off by another “Calling” routine which passes the required arguments at the “Call” line. For a recursion routine this is also the case for the first copy of the routines. ( Further copies start as the existing copy pauses after itself Calling another independent copy of the recursion routine to start )
    So we need a calling routine…._
    Sub Call_Sub_Bubbles() Calls Sub Bubbles Copy1
    Sub Bubbles Copy1 Calls Sub Bubbles Copy2
    Sub Bubbles Copy2 Calls Sub Bubbles Copy3
    _...........
    .
    For convenience we can also, in this routine, for test purposes create the array from a worksheet range which we will pass as the array to be sorted by our test range.
    This array, arrTS() , is passed to the recursion routine as one of the main arguments. ( The signature line of the recursion routine will declare the variable that needs to be passed this array, as being ByRef . This will means that all changes on that array inside the recursion routine , ( and necessarily any single copy of the recursion routine running at any time ) are referred back to this array. Effectively this can be thought of as the array arrTS() as being “carried in” the recursion routine signature line defined variable, and similarly one can consider all done on the array as being done on this arrTS()
    The next characteristic of this Calling routine was in this Thread so far only used for when a recursion routine was called using the index way idea ( __Sort8 , __Sort7 codings )
    I can’t easily replace in all codings the string of row indices , “ 1 3 2 5 6 7 “ , with the array of row indices,
    Rs() = 1;
    ____¬___3;
    ____¬___2;
    ____¬___5
    ____¬___6
    ____¬___7 }

    For the first copy of the recursion routine , ( the only copy Called by this Calling routine ) , those will be the initial ordered rows, in our example,
    {1;
    2;
    3
    4
    5
    6}

    But subsequently, I will likely only need a subset of the rows to further sort. It would get very messy to be chopping and changing in particular, the dimensions, of such an array. Mostly this is because it is a 2 dimensional ( all be it 1 “width”/column) array, and they are not so easy to manipulate as are 1 dimensional array that lend themselves to easy manipulation with string functions. The Join and Split are in particular very useful, but these only work on 1 dimensional arrays

    So I restrict the use of the Rs() in this coding to an alternative for generating the first string values. But that is not particularly any better than the previous way..

    Sub Call_Sub_Bubbles()
    For convenience we use spreadsheet functions to give us sequential indices initially in Rs() , ( and later in next routines Cms() ) Evaluate(Row(1to15)).JPG : https://imgur.com/UVTQCYO ( Evaluate(Column(1to6)).JPG : https://imgur.com/jbaZdgJ )
    ( The, "Vertical row" Indicies, ( and the "Horizointal Column" Indicies ) , can be Long or String types, and out App.Index coode line would work, but because we use for convenience spreadsheet functions vial the VBA Evaluate(“ “) function to obtain these. As the Evaluate(“ “) returns all things housed in Variant type, we declared Rws() ( and Cms() ) , as Variant )
    The information we need for the column by which to be sorted is taken in a simple string, which we organise to have a similar form to that for the Range.Sort method. For our example it looks like this: " 1 Asc 3 Asc 2 Asc " . For our simplified example , the Asc has no effect, but is included to aid in comparison with previous / further developed routines which have / will allow the option to chose Ascending or Descending sort order
    For any recursion routine it is almost always useful to have a variable set at the start of any copy of the routine which tells us which copy number is running. This I typically call CpyNo, CopyNumber , CopyNo or similar.
    At the start of every copy of the recursion routine, the value passed at the signature line is put in a local copy variable which can be then used to give the copy number of the current running routine.
    So from the Calling routine I pass 1. At the code line in the recursion routine which Calls into life a new copy of the routine, we pass like CopyNumber + 1 . This ensures we then have the correct value place at the start of any newly starting copy of the recursion routine, since the first copy of the recursion routine pauses and starts the second copy of the recursion routine, the second copy of the recursion routine pauses and starts the third copy of the recursion routine ….. etc…

    Here is our final Calling routine, Sub Call_Sub_Bubbles()
    ( It gives the same demo range output as Sub RangeSort() , ( or should do once I have written the routine that it Calls ) )
    Code:
    '
    Sub Call_Sub_Bubbles() ' Partially hard coded for ease of explanation
    ' data range info
    Dim WsS As Worksheet: Set WsS = ThisWorkbook.Worksheets("Sorting")
    Dim RngToSort As Range: Set RngToSort = WsS.Range("B11:E16")
                                               ' Set RngToSort = Selection '                          ' Selection.JPG : https://imgur.com/HnCdBt8
    
    Dim arrTS() As Variant ' array to be referred to in all recursion routines, initially the original data range
     Let arrTS() = RngToSort.Value
    ' Initial row indicies
     Let Rs() = Evaluate("=Row(1:6)") '
    Dim strRows As String, Cnt As Long: Let strRows = " "
        For Cnt = 1 To 6
         Let strRows = strRows & Rs(Cnt, 1) & " "
        Next Cnt
    ' we should have now strRows = " 1 2 3 4 5 6 "
     Call Bubbles(1, arrTS(), strRows, " 1 Asc 3 Asc 2 Asc ")
    
    ' Demo output
     Let WsS.Range("B31").Resize(RngToSort.Rows.Count, RngToSort.Columns.Count).Value = arrTS()
    End Sub
    '
    The next post develops the Called routine,
    Sub Bubbles(ByVal CpyNo As Long, ByRef arsRef() As Variant, ByVal strKeys As String)
    Last edited by DocAElstein; 03-16-2019 at 07:27 PM.

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

    Sub Bubbles - Rem 1 Bubble sort of Sort

    Sub Bubbles( ByVal CpyNo As Long, ByRef arsRef() As Variant, ByVal strKeys As String )
    Here’s the first bit…
    Code:
    Sub Bubbles(ByVal CpyNo As Long, ByRef arsRef() As Variant, ByVal strKeys As String)
    Dim CopyNo As Long: Let CopyNo = CpyNo 
    
    Rem -1 from the supplied arguments, get all data needed in current bubble sort
    Dim Keys() As String: Let Keys() = Split(Replace(Trim(strKeys), " ", " ", 1, -1, vbBinaryCompare), " ", -1, vbBinaryCompare) 
    Dim Clm As Long: Let Clm = CLng(Keys((CopyNo * 2) - 2))
    CopyNo:
    On every recursion run , that is to say, the copy brought into life by a Call form the routine itself, this will be increased by the Recursion Call by 1.
    This will be a local variable indicating the level down in recursion - I increase it by 1 at every Recursion Call, that is to say each Recursion Call in this routine gets given CopyNo+1 as the first passed argument , CpyNo
    ___Call Bubbles(CopyNo + 1, arsRef(), ……
    During a long “tunnel down”, the number at this point will keep increasing to reflect how “far down” we are. This ensures we then have the correct value place at the start of any newly starting copy of the recursion routine, since the first copy of the recursion routine pauses and starts the second copy of the recursion routine, the second copy of the recursion routine pauses and starts the third copy of the recursion routine ….. etc…

    Rem -1
    Keys()
    It is convenient to split " 1 Asc 3 Asc 2 Asc " , which will give me 6 elements, which with a bit of maths, I can get the information I need regarding the column to be used in determining the sort order
    Clm
    For the simplified routine I just want the column number used for the sort. ( 1 or 3 or 2 )
    As we will see, each next copy of the recursion routine is intended to use the next column to be used in determining the sort. So a simple bit of maths determines the element, and hence the contained column number to be used :
    Clm = CLng(Keys((CopyNo * 2) - 2))
    So for example , at the initial Call, done by the Calling routine, CpyNo is passed 1 from the supplied CopyNo
    I will then have Key(0) which in a 1 dimensional array produced by the VBA Split function is the first array element, which has “1” in it in our example.
    When the routine itself sets off a new copy, the next copy, CopyNo will become 2. Our formula , CLng(Keys((CopyNo * 2) - 2)) will use Key(1) which in a 1 dimensional array produced by the VBA Split function is the third array element, which has “3” in it in our example.
    ( I want a number, so I use Clng , but that probably is not needed, as VBA has a habit of usually accepting a string which “looks” like a number as the number it looks like, ( i.e. it takes “8” as 8 ) , in any situation where it is excepting a number )

    Rem 1 Bubble Sort
    I must have explained this basic idea a thousand times to myself and others. But I find I need to re say it every time to remind myself.
    Consider initially the first copy run …
    I have rows of values ( numbers in this simple example) in a column, Clm in my main data array, arsRef(__ , Clm )
    Rs Clm= 1
    1 __1
    2 __9
    3 __1
    4 __8
    5 __1
    6 __7
    I have an =Outer Loop== in my coding, controlled by a variable, rOuter, that goes, in this example, the first time, from 1 To 5. Picking out the last but top and bottom number from strRws, in this case 1 and 5 from “ 1 2 3 4 5 6 “ can be got in lots of ways. In previous routines I made a 1 dimensional array from using th Split function , and looked at the first an last but one element of that array. For no special reason I use a bit of string manipulation this time. By the way, the Immediate window is very useful for fiddling around to get at the right thing in coding such as this – see ImmediteWindowToHelpGetAtStuff.JPG : https://imgur.com/yGqmYSu : http://www.eileenslounge.com/viewtop...247121#p247121
    Attachment 2205

    A handy way of thinking about the bubble sort:
    I think of the position of the outer loop at any time, as that as where my left hand. At any point in time, its position is determined by rOuter, and it is pseudo “holding” what is currently in that row number, rOuter = 1 2 3 4 or 5. ( Note I never “hold” the last row in my left hand )
    At every of the 5 rows, my left hand waits there for a while, why my right hand in an -Inner Loop-- goes from one row above where my left hand currently is, rOuter+1 To the last row, 6
    As I go “down” with my right hand holds temporarily each row value.
    So at any point in the combined outer and inner looping, I have a value “in” each hand. This is effectively the middle point of the loop Here

    Basic Bubble sort loops

    __For rOuter = 1 To 5 ‘ =====
    ___ For rInner = rOuter+1 To 6 ‘----

    _____Here
    ______ Compare,
    ________ Possibly swap

    ____Next rInner ‘ ------
    __Next rOuter ‘ =====


    At Here, I compare the values in my hands. If the left hand, arsRef(rOuter, Clm) is > then the right hand, arsRef(rInner, Clm), then I swap the values.
    If you consider what happens for one full inner loop, the first time, (rOuter = 1) , this process will mean that the smallest number anywhere ends up in my left hand.
    As I move my left hand to row 2, and do the same process of moving my right hand down the remaining rows and comparing and possibly swapping values in my hand, then the next smallest ends up at row 2 .
    As I move my left hand to row 3, and do the same process ……_
    _….etc..

    Doing the swap
    I cannot in VBA, or in computing software generally, throw 2 values up in the air and catch them in the opposite hands. That is a nice Human ability to do things exactly at the same time. Most software just give the impression of doing things at the same time because it works so fast that we do not see every separate sequential thing. Our program must do a logical sequential progression: So to do the swap , ……
    my left hand puts its value in a Temporary place:
    ____ then the left hand takes the value from the right hand:
    _________finally the right hand takes the original left hand value from the Temporary place.

    Swap all columns.
    The reason for me doing the sorting is to re arrange all the rows. But what I have just explained has re ordered just one column, and not the entire row.
    The main difference in this routine, Sub Bubbles , and Sub BubblesIndexIdeaWay is how I do this. For the current routine, Sub Bubbles , I do this in the usual way for an array type bubble sort.
    At the inner point, Possibly swap Then, I don’t do the swap for just the column, Clm. ( I only use the variable Clm within the comparison line , Compare, If – I do this for the next routine also )
    What I actually do is introduce another, third loop, which swaps all columns.

    Recursion code designed to sort different row range
    I cannot hard code the rOuter as 1 To 5 , and the rInner as rOuter+1 To 6 , not even for this simplified coding, as I want to use the same coding ( or rather further independent copies of it) , to sort sub row sections for the case of duplicate values in previously sorted columns.
    Instead I use my array of row indices, Rs(). The intention will then be in Rem 3 to run a new copy of the recursion routine, Sub Bubbles , with the subset of Rs() and resort , ( and if necessary do this again to resort a further time by another column )
    Each time I consider in total from the lower indicie to the upper indicie. ( rOuter from the lower, rInner to the upper ) The first time in the current example , this will be 1 To 6 , then it should be 1 To 3, and finally it should be 1 To 2 . ( It must not necessarily be, as in this example, that we always start at 1 )

    Here is the final bubble sort code section
    Code:
    Dim rOuter As Long ' ========"Left Hand"=====================Outer Loop=====================================
        For rOuter = Rs(LBound(Rs(), 1), 1) To Rs(UBound(Rs(), 1), 1) - 1 ' For first row indicie to last but one row indicie
        Dim rInner As Long ' -------Inner Loop-------------"Right Hand"--------------------------
            For rInner = rOuter + 1 To Rs(UBound(Rs(), 1), 1) ' from just above left hand through all the rest
             'Here
                If CDbl(arsRef(rOuter, Clm)) > CDbl(arsRef(rInner, Clm)) Then
                Dim Temp As Variant ' I want to Swap those 2 above - I cant easilly in any coding change two values simulataneosly. So one of them Element values will put in this temporary place. This Element Values will then be given the other. Finally the other Element will be given this temporary value
                Dim Clms As Long '-------| with the condition met  a loop is done for all columns in the array in which those two values used in the comparison are replaced at each column
                    For Clms = 1 To UBound(arsRef(), 2)
                     Let Temp = arsRef(rOuter, Clms): Let arsRef(rOuter, Clms) = arsRef(rInner, Clms): Let arsRef(rInner, Clms) = Temp
                    Next Clms '----------| for each column in the array at the two rows rOuter and rInner
                Else
                End If
            Next rInner ' -----------------------------------------------------------------------
        Next rOuter ' ==========================================================================================
    _.___
    As an intermediate step, lets end the routine for now at this stage, and run it via the Calling code
    Intermediate coding for this is here: http://www.excelfox.com/forum/showth...ll=1#post11065
    ( Note that …_
    For rOuter = Rs(LBound(Rs(), 1), 1) To Rs(UBound(Rs(), 1), 1) - 1
    _... is only valid for this first copy run, --- typically less rows are used and we get them from like the strRws = “1 2 3 “
    … )

    If we run that using our test range we get these results:
    1 5 3 a
    1 4 2 c
    1 3 2 e
    7 7 7 f
    8 8 8 d
    9 9 9 b
    If we compare that with the expected final output, we see we are not quite there yet..
    1 3 2 e
    1 4 2 c
    1 5 3 a
    7 7 7 f
    8 8 8 d
    9 9 9 b
    Last edited by DocAElstein; 03-16-2019 at 07:43 PM.

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

    Rem 3 - Preparation for possible recursion Call

    Rem 3 Preparation for possible recursion Call
    What we want to do
    At this point, in many real applications we will likely have most of the rows sorted but will have possibly some rows with similar values in the column used in the initial sort.
    We need some way to send arrange that the array as now sorted is resent again sorted by another running copy of the recursion routine over the duplicate rows.
    We do not want to over simplify this coding. We did a bit of simplifying: For the sake of explanation of the general coding strategy it was OK to choose just numbers and all Ascending order. But to give the coding some worth in showing typical recursion coding workings, we should allow for the case of multiple duplicate row sections. We will discus that this is the sort of thing, that is to say going “back and forth” or “up and down” in a semi automatic way is what a recursion code is often best at.
    There is no single way I know of, to write such a coding. It simply takes some careful thought to arrange that the Call of a new copy is such that on termination of that copy, the way the original copy resumes will allow for the possibility of things such as for “going back down” if, in this case, we need once again to resort multiple rows. Sometimes there are a couple of general characteristics which can help in the design of such a coding…

    Main outer loop, and multiple copies of Copys/ “Levels”
    Usually we will have a main outer loop, which in our case will be approximately across the entire range of current rows to be sorted. Often, but not always, towards the end, or last half, of the loop, will be the recursion Call, that is to say the code line which causes the current running routine to pause, whilst a new independent copy of the routine starts.
    Having this Call part in a loop is probably what usually gives this ability to go “back and forth” between different independent copies of the recursion routine: You see , when a Called recursion routine copy ends, then the previous which had paused restarts, and depending on what your loop is doing, it will possibly cause the Call to be done again, so “you go back down” a copy level, or up a copy level depending on how you like to visualise it. It should be noted that each start and End of a recursion is an independent routine. The variable CopyNumber that we use tells us at “what level” we are, or how “far down” the recursion change of events. In our case that translates in the practice to which column in our list of columns to use , 1 3 2
    CopyNo 1 : we are using column 1 to determine the sort order
    CopyNo 2 : we are using column 3 to determine the sort order
    CopyNo 3 : we are using column 2 to determine the sort order
    There will only ever be one copy number 1 started, but that will likely pause a number of times. For further copy number , several may start and End: There can only ever be one running at any one time, but several independent copies could be ran from start to completion. The copy number is an indication of the “level” or in our case the column being used to determine the sort order. ( With hindsight… probably CopyLevel would be a better name for the variable… )

    Ending
    A typical, but not essential, characteristic of recursion routines is that not much usually goes on after the loop and / or last Call code line area. Further, a typical characteristic is that Ends, especially the final few Ends tend to occur one after the other. It tends to go unnoticed , for example when using debug F8 step code progression mode , since there Are not many code lines there. I find it therefore very demonstrative to have a Message box or Debug.Print code line immediately before the code end, with a message like “Ending a copy number “ & CopyNo & “”

    Our specific case: What do we need to do
    We already have the array we need for a possible required further sort in the case of duplicated values in the column used in the last bubble sort.
    What we need to do is determine any rows with those duplicate values, and then pause the current routine whilst we run another copy of the routine after we have changed the indices in Rs() to just the sub set of rows to be sorted.
    I guess there are many ways to do this. I expect I will come back some time and try a few.
    The basic strategy to take advantage of recursion in this case will probably usually be the same

    Basic recursion using strategy
    This is not so difficult as the original sort will mean that rows for duplicated values in the current/ last sort column will be grouped together. So the basic strategy is to loop “down” and whilst we do this noting the indicies for these rows for duplicated values in the current/ last sort column. Once we have such a group use the Call Sub Bubbles(__ recursion starting code line to pause the current routine and start a new copy of the recursion routine to sort these rows which have duplicated values in the current/ last sort column.

    Actual working application of the Basic recursion using strategy
    I find it very convenient, as well as making debug easier , to “collect things” like row indices in a long string. This is because
    it makes it easier to print or message box out what I have, so lends itself nicely to user interfaces to see what is going on,
    and
    there are very many string manipulating function and methods available

    In fact, I already use the variable, strRws , for the range of rows, so it makes sense to use it to build my duplicated rows indicies in this sort of form like " 1 2 3 ". In other words similar I use it similar to how it was used in its first use , where, in this example, it was built like this in the Calling routine, " 1 2 3 4 5 6 ". For its first use it has all the indicies, and now , subsequently it will hold the indices corresponding to duplicate row values in the current/ last column used to define the sort order, in the latest version of arsRef() :
    Just to clarify as it is easy to get lost in recursion routines: At this Rem 3 stage, I have most likely , just re ordered the array, arsRef(). It may have some rows that could not be put in any specific order if there were identical values in those rows in the column used in the last/ current sort.
    One of the main workings of this section, Rem 3 , will be to obtain a string of the form " 1 2 3 " which represents duplicate row values in the current/ last column used to define the sort order.
    ( In a more realistic example , I might have several groups of such rows, so would have strRws = " 7 8 9 10 " , strRws = " 17 18 " , strRws = " 72 73 74 75 76 77 78 " , ..etc… Furthermore some of those rows might still need to be sorted using a different column / that is to say, using the next user given column, -- hence the reason for trying a recursion routine which “keeps going further and further” as needed

    _ Let strRws = ""
    I initialise my variable so that I can use it to build up my new duplicate variable rows list

    __For rOuter = Left(Trim(tempStr), InStr(1, Trim(tempStr), " ", vbBinaryCompare) - 1) To …………………………
    I begin a main **Outer Loop** for all but the last row, where the actual rows are determined by the upper and lower values in strRws
    ____ If strRws = "" Or InStr(1, Trim(strRws),…………….
    ____ I have a condition which should catch the situation of starting looking for a set of duplicates, so this will be at the start, strRws = "" , or if the last loop produced no addition to the string and so is left at a single indicia, meaning that no in between space is present, and consequently this will be 0 , InStr(1, Trim(strRws), " ", vbBinaryCompare). With these conditions met my string will become like " 1 " ( with more realistic data this could be any row number )

    ____ If Trim(UCase(CStr(arsRef(rOuter, Clm)))) = Trim(UCase(CStr(arsRef(rOuter + 1, Clm)))) ………………
    ____ This code line looks to see if we have a duplicate at the next row in last/ current sort column. ( This is why we loop in the main outer loop to 1 less than the last row, to prevent an error of array index out of range here )
    _____ with the last condition met we add the indicie to the current string, strRws
    _____ Let strRws = strRws & rOuter + 1 & " "
    ____ Else ' without the last condition met
    ____ without the last condition met, we might have the end of a group of duplicate rows, in which case it would be time to organise a recursion run so
    ____ If Not InStr(1, Trim(strRws), " ", vbBinaryCompare) = 0 Then
    ______we this we check for this situation needing a recursion run,
    ______with the condition met its time to organise recursion run
    ' Now its time to organise a recursion run
    Because of how we built our string, strRws , we have nothing to do other than Call a new copy of the routine, Sub Bubbles( __ , with the appropriate arguments,
    After that new copy of the recursion routine Ends, I will come back to just after the Call line and in a normal practical use I might still find another group of rows in this look at the first full row sorted array, so I set strRws=””
    ______ '+++*** this would be end of loop for most cases
    Oh Fuck
    In most cases I am finished after I am towards the end of the main Loop here.
    But we have one slight problem: there is one small imperfection with our logic: In our logic, the end of a group of duplicates is determined by the two conditions:
    _ firstly the next row is not a duplicate, and
    _ secondly the current strRws has at least two indicies in it.
    The problem comes if we have a group of duplicate rows that include the last row: In such an occurrence we will never reach a point where the next line being not a duplicate causes us to do the first then second check and subsequent Call of a new copy of the routine, Sub Bubbles( __.
    To overcome this problem we include a last check which covers such an occurrence an allows a last Call of a new copy of the routine
    I think for realistic real life data, this might be one of those situations whereby you ignore the last problem so as to either
    use it effectively later to cause some mischief and then demand a high ransom to get correct it, or
    or
    you might consider arranging your data, such that the problem scenario would not occur. This might be a more efficient solution than having the extra check in every looping



    In the next post is a summary of a run of the routines
    ( Final coding here:
    http://www.excelfox.com/forum/showth...ll=1#post11067 )
    Last edited by DocAElstein; 03-16-2019 at 10:13 PM.

  6. #16
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10
    Illustration of a full run of coding from last post

    If you run the coding discussed in the last post, then you will have available in the Immediate window ( http://www.eileenslounge.com/viewtop...247121#p247121 ) similar below.

    I have added some screen shots in between to help illustrate better

    So if you run routine Sub Call_Sub_Bubbles() on the following test data, then you will get the results below in the immediate window 8 without the extra screenshots which I have added here.
    Row\Col
    B
    C
    D
    E
    11
    1
    5
    3
    a
    12
    9
    9
    9
    b
    13
    1
    4
    2
    c
    14
    8
    8
    8
    d
    15
    1
    3
    2
    e
    16
    7
    7
    7
    f
    Worksheet: Sorting

    After running Sub Call_Sub_Bubbles():
    Code:
     First procedure Call
     Running Copy No. 1 of routine.
      Sorted rows  1 2 3 4 5 6  based on values in column 1
    Bubbles(1, arrTS(), strRows, " 1 Asc ") 
    1
    5
    3
    1
    4
    2
    1
    3
    2
    7
    7
    7
    8
    8
    8
    9
    9
    9
    Checking now for Dups in that last sorted list Found dups in last list column 1, 1 2 3 , so now main Rec Call Running Copy No. 2 of routine. Sorted rows 1 2 3 based on values in column 3 Bubbles(1, arrTS(), strRows, " 1 Asc 3 Asc ")
    1
    4
    2
    1
    3
    2
    1
    5
    3
    7
    7
    7
    8
    8
    8
    9
    9
    9
    Checking now for Dups in that last sorted list Found dups in last list column 3, 1 2 , so now main Rec Call Running Copy No. 3 of routine. Sorted rows 1 2 based on values in column 2 Checking now for Dups in that last sorted list Ending a copy, Copy level 3 Ending a copy, Copy level 2 Ending a copy, Copy level 1
    The extra intermediate screenshots above I produced by using these alternative Call code lines
    Call Bubbles(1, arrTS(), strRows, " 1 Asc ")
    Call Bubbles(1, arrTS(), strRows, " 1 Asc 3 Asc ")



    Finally in the spreadsheet you should see this
    Row\Col
    B
    C
    D
    31
    1
    3
    2
    32
    1
    4
    2
    33
    1
    5
    3
    34
    7
    7
    7
    35
    8
    8
    8
    36
    9
    9
    9
    Worksheet: Sorting
    Last edited by DocAElstein; 03-16-2019 at 10:50 PM.

  7. #17
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10

    Converting Sub Bubbles to Sub BubblesIndexIdeaWay

    Converting Sub Bubbles to Sub BubblesIndexIdeaWay


    This and the next posts will concentrate primarily on the changes required to convert the coding from the last posts, _...
    http://www.excelfox.com/forum/showth...ll=1#post11063
    http://www.excelfox.com/forum/showth...ll=1#post11064
    http://www.excelfox.com/forum/showth...ll=1#post11066
    http://www.excelfox.com/forum/showth...ll=1#post11068

    _... into similar coding using the Index idea way.
    http://www.excelfox.com/forum/showth...ll=1#post11062
    http://www.excelfox.com/forum/showth...-VLookUp/page2
    https://www.excelforum.com/excel-new...ml#post4571172


    Global variables
    I am not too keen generally on global variables , http://www.eileenslounge.com/viewtop...=29652#p229402 , but the alternative in our current coding would be to pass things in such a way as to arrange for By Referring to them throughout all passed routines. This makes things a bit messy due to a long signature line when we have a few variables, so I will use some global variables. But we note that it is not essential to the index way. It is done more for visual convenience and prettiness

    These are the full set of global variable that should be placed at the top of a cod module
    Code:
    Option Explicit
    Dim Cms() As Variant, Rs() As Variant      ' "Horizointal Column" Indicies  , "Vertica row" Indicies.   ( The, "Vertical row" Indicies, ( and the "Horizointal Column" Indicies ) , can be Long or String types, and out App.Index coode line would work, but we typically use for convenience spreadsheet functions vial the VBA Evaluate(“ “) function to obtain these. As the Evaluate(“ “) returns all things housed in Variant type, we typically declared Rws() and Cms(), as Variant )
     Dim arrOrig() As Variant                   ' This    arrIndx() = Application.Index(arrOrig(), Rs(), Cms())  applies the modified Rs() to the original unsorted data range. So we need an array to use constantly containing the original data range
    Dim arrIndx() As Variant                   ' For   Sub SimpleArraySort7()
    Sub Call_Sub_BubblesIndexIdeaWay()
    We introduced the row indicies array, Rs(), in the last , although they were not really essential to have. We now require to use the complete variable associated with the Index idea way.
    ______ arrIndx() = Application.Index(arrOrig(), Rs(), Cms())
    We need to add something to give us our column indicies , in this example for 4 columns , { 1 , 2, 3, 4 } , which we can conveniently get from a spreadsheet function, Column( ) , via Evaluate(“ “) in VBA
    We also need to fill our original range data array, arrOrig(). This will simply be filled with the original data range, but will remain static.
    We no longer need to pass any array: We will simply be able to reference the global variable , arrIndx() , for our final sorted output , after the routine, Sub BubblesIndexIdeaWay() has finally ended all copies of it ran after it being called by Sub Call_Sub_BubblesIndexIdeaWay()

    arsRef() , arrIndx() WTF array
    There is a lot of very similar arrays flying around at the moment.
    Some will likely be redundant , or missing , in some codings. Often I will keep them to aid in coding version comparison, and their use may not be necessary, or , as mentioned full or partly redundant.

    arrTS() : Up until now this was usually our array to be sorted and was taken from the spreadsheet capture, arrTS() = RngToSort.Value . As this was normally taken in as the array to be By Referred to , it was pseudo like the array carried in the array of the recursion function, arsRef() , and all changes were referred to this. It became finally the sorted array and would usually be then pasted out for demonstration purposes at some range offset from the original data. This pasting out ways usually the last line in the Calling routine, so became the last thing done typically.
    arrIndx() : This is intended to be a global variable array, the array updated continuously with the new index way idea, arrIndx() = Application.Index(arrOrig(), Rs(), Cms()) . So this becomes , or is a replacement for , both all uses of arsRef() , and for the final usage of arrTS().
    arsRef() : Mostly used as the pseudo “housing / carrying” array used throughout the recursion routines, passed between copies and continually being modified so that the “carried” array, usually arrTS() would finally have the final sorted data range array. For the index way idea, we have a couple of ways to use arrIndx():
    _ We can pass this to be held in arsRef(),
    _ We can simply change all references in the routine from arsRef() to arrIndx(). Because arrIndx() is a global variable, we will then always be referring to this.
    Using the second option is the most sensible and efficient as then we can completely do without arsRef() , and indeed could completely remove it from anywhere, including the signature line of the recursion routine.
    For the sake of consistency and comparison, I will use the first option. This will also be helpful in development of the next routine, Sub BubblesIndexIdeaWay(), as I will have an intermediate stage, with both arrays present, filled by the alternative ways, and can compare the results.
    As arrIndx() will be passed to the recursion routine by Sub Call_Sub_BubblesIndexIdeaWay() , it needs to be filled initially, arrIndx() = arrTS()
    All of these arrays are dynamic arrays of Variant type elements and so can be directly assigned to each other


    Here is the almost the final Calling routine:

    Code:
    Sub Call_Sub_BubblesIndexIdeaWay() ' Partially hard coded for ease of explanation
    ' data range info
    Dim WsS As Worksheet: Set WsS = ThisWorkbook.Worksheets("Sorting")
    Dim RngToSort As Range: Set RngToSort = WsS.Range("B11:E16")
                                               ' Set RngToSort = Selection '                          ' Selection.JPG : https://imgur.com/HnCdBt8
    Dim arrTS() As Variant ' This is somewhat redundant for this version and could be replaced by arrOrig()
     Let arrTS() = RngToSort.Value
    ' Index idea variables
     Let arrOrig() = arrTS()
     Let arrIndx() = arrTS()
     Let Cms() = Evaluate("=Column(A:F)") ' Convenient way to get
     Let Rs() = Evaluate("=Row(1:6)") ' Initial row indicies
    ' Initial row indicies from full original range´of rows
    Dim strRows As String, Cnt As Long: Let strRows = " "
        For Cnt = 1 To 6
         Let strRows = strRows & Rs(Cnt, 1) & " "
        Next Cnt
    ' we should have now strRows = " 1 2 3 4 5 6 "
     Call BubblesIndexIdeaWay(1, arrIndx(), strRows, " 1 Asc 3 Asc 2 Asc ")
    ' Call BubblesIndexIdeaWay(1, arrIndx(), strRows, " 1 Asc ")
    ' Call BubblesIndexIdeaWay(1, arrIndx(), strRows, " 1 Asc 3 Asc ")
    ' Demo output
     Let WsS.Range("B31").Resize(RngToSort.Rows.Count, RngToSort.Columns.Count).Value = arrIndx()
    End Sub
    _.____________________-

    In the over next post the routine Sub BubblesIndexIdeaWay( __) will be developed. This will basically involve minor modifications to Sub Bubbles(__)

    Before the final conversion , I will refresh and review the situation and add some extra lines to the above calling routine:
    Row and Column indicies, Rs() and Cms()
    For demonstration purposes, I will add a couple of extra final output lines to the calling routine, Sub Call_Sub_BubblesIndexIdeaWay()
    These lines will simply paste out the initial and final row and column indices.
    Last edited by DocAElstein; 03-17-2019 at 02:38 PM.

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

    Refresh: Current stand of things, Initial Sub BubblesIndexIdeaWay as Sub Bubbles

    Refresh: Current stand of things, Initial Sub BubblesIndexIdeaWay as Sub Bubbles

    Before the final conversion , I will refresh and review the situation and add some extra lines to the above calling routine:
    Row and Column indicies, Rs() and Cms()
    For demonstration purposes, I will add a couple of extra final output lines to the calling routine, Sub Call_Sub_BubblesIndexIdeaWay()
    These lines will simply paste out the initial and final row and column indices.

    Initially I will run an intermediate routine , (which is a version of the last recursion routine) , from the below Calling routine. That version of the last recursion routine is here: http://www.excelfox.com/forum/showth...ll=1#post11071
    That referenced routine is simply Sub Bubbles(), with the name changed to Sub BubblesIndexIdeaWay(), and the two recursion Calling code lines changed from
    Call Bubbles(CopyNo + 1, arsRef(), strRws, strKeys)
    to
    Call BubblesIndexIdeaWay(CopyNo + 1, arsRef(), strRws, strKeys)

    If I use this below calling routine, (Sub Call_Sub_BubblesIndexIdeaWay() ) , using our test data range ( http://www.excelfox.com/forum/showth...ll=1#post11073 ) , to Call the intermediate recursion routine ( http://www.excelfox.com/forum/showth...ll=1#post11071 ) , then I get the results shown.

    Calling routine,
    Sub Call_Sub_BubblesIndexIdeaWay()

    Here: http://www.excelfox.com/forum/showth...ll=1#post11074

    Original data range with added row and column indices
    Row\Col
    A
    B
    C
    D
    E
    10
    1
    2
    3
    4
    11
    1
    1
    5
    3
    a
    12
    2
    9
    9
    9
    b
    13
    3
    1
    4
    2
    c
    14
    4
    8
    8
    8
    d
    15
    5
    1
    3
    2
    e
    16
    6
    7
    7
    7
    f
    Worksheet: Sorting



    Intermediate Output : Note row indicies are incorrect: They are not yet reordered. This is one of the main issues in the next post.
    Row\Col
    A
    B
    C
    D
    E
    30
    1
    2
    3
    4
    31
    1
    1
    3
    2
    e
    32
    2
    1
    4
    2
    c
    33
    3
    1
    5
    3
    a
    34
    4
    7
    7
    7
    f
    35
    5
    8
    8
    8
    d
    36
    6
    9
    9
    9
    b
    Worksheet: Sorting
    Last edited by DocAElstein; 03-17-2019 at 03:31 PM.

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

    Final conversion of Sub Bubbles to Sub BubblesIndexIdeaWay

    Final conversion of Sub Bubbles to Sub BubblesIndexIdeaWay

    As we have the current stand of the routines, as discussed in the last post, we have the final Calling routine, ( Sub Call_Sub_BubblesIndexIdeaWay(), http://www.excelfox.com/forum/showth...ll=1#post11074 )
    But currently , Sub BubblesIndexIdeaWay , is basically, Sub Bubbles
    This Final conversion of Sub Bubbles to Sub BubblesIndexIdeaWay will be done in twp parts: Firstly we will get the same results in arrIndx() as we already have in arsRef(). Then we will remove the redundant bits

    Part 1 Additions to make arrIndx() give us final Output
    From the last post, we see that we do not yet have the reordered Rs() at the end of the routines running. Therefore this will give the wrong final results
    ____________arrIndx() = Application.Index(arrOrig(), Rs(), Cms())
    Getting the correct Rs() is the main requirement to get Sub Bubbles working

    We need to remind ourselves what goes on in basic the sort, after which it is fairly obvious how we get the reordered indices:
    In the bubble sort, we reach a point whereby rows need to be swapped. Lets consider as random example that rows 2 and 3 need to be swapped, so
    row 2 become row 3 , and row 3 becomes row 2.
    As discussed we cannot do that easily in computing. In computing we need to have a temporary variable, pseudo
    Temp = row 2
    row 2 = row 3
    row 3 = Temp

    Our variable Rs() , holds the indices we need to apply to the original array to get the new reordered array. The current coding swaps rows. Rs() holds the indices of our original array. If we want the indicies in that Rs() , when applied to the original array, to return the reordered array, then they need to be swapped at exactly as the rows currently in arsRef() are.
    Putting that again in just slightly different wording. The original rows have an original row indicie. As the rows are moved ( swapped) up and down in arsRef() , the corresponding row indicie needs to be moved excactly the same in Rs()
    I can’t put that any clearer. You need to take a bit of time to let that run through your head, and then it should make sense.

    Once we have understood that last bit, then the coding modification may be obvious: At the current swap section we need to swap the indicies in Rs()
    Currently we have this:
    Code:
                Dim Clms As Long '-------| with the condition met  a loop is done for all columns in the array in which those two values used in the comparison are replaced at each column
                    For Clms = 1 To UBound(arsRef(), 2)
                     Let Temp = arsRef(rOuter, Clms): Let arsRef(rOuter, Clms) = arsRef(rInner, Clms): Let arsRef(rInner, Clms) = Temp
                    Next Clms '----------| for each column in the array at the two rows rOuter and rInner
    We simply add there a swap for the idiocies
    Code:
                Dim Clms As Long '-------| with the condition met  a loop is done for all columns in the array in which those two values used in the comparison are replaced at each column
                    For Clms = 1 To UBound(arsRef(), 2)
                     Let Temp = arsRef(rOuter, Clms): Let arsRef(rOuter, Clms) = arsRef(rInner, Clms): Let arsRef(rInner, Clms) = Temp
                    Next Clms '----------| for each column in the array at the two rows rOuter and rInner
                Dim TempRs As Long
                 Let TempRs = Rs(rOuter, 1): Let Rs(rOuter, 1) = Rs(rInner, 1): Let Rs(rInner, 1) = TempRs
    If you make just that modification and run the complete coding, ( see here for example http://www.excelfox.com/forum/showth...ll=1#post11076 ) , then you will find that the final indicies are correct…. Compare the input:
    1 2 3 4
    1 1 5 3 a
    2 9 9 9 b
    3 1 4 2 c
    4 8 8 8 d
    5 1 3 2 e
    6 7 7 7 f

    Here the output
    1 2 3 4
    5 1 3 2 e
    3 1 4 2 c
    1 1 5 3 a
    6 7 7 7 f
    2 9 9 9 b
    4 8 8 8 d


    We have the required Rs() , and can add the code line to apply to the formula , arrIndx() = Application.Index(arrOrig(), Rs(), Cms())
    We could add this code line now anywhere, for example at the end of the calling routine
    Code:
     Let RngDemoOutput = arrIndx()
     Let RngDemoOutput.Offset(-1, 0).Resize(1, 4).Value = Cms(): RngToSort.Offset(-1, 0).Resize(1, 4).Font.Color = vbRed
     Let RngDemoOutput.Offset(0, -1).Resize(6, 1).Value = Rs(): RngToSort.Offset(0, -1).Resize(6, 1).Font.Color = vbRed
    '
     Let RngDemoOutput.Offset(RngDemoOutput.Rows.Count, 0) = Application.Index(arrOrig(), Rs(), Cms())
    End Sub
    The above coding modification would give us this output:
    Row\Col
    A
    B
    C
    D
    E
    30
    1 2 3 4
    31
    5 1 3 2 e
    32
    3 1 4 2 c
    33
    1 1 5 3 a
    34
    6 7 7 7 f
    35
    2 9 9 9 b
    36
    4 8 8 8 d
    37
    1 3 2 e
    38
    1 4 2 c
    39
    1 5 3 a
    40
    7 7 7 f
    41
    9 9 9 b
    42
    8 8 8 d


    The above use of the formula, Application.Index(arrOrig(), Rs(), Cms()) , is helpful to demo its use.
    However, before we can move on in the next post to removal of redundant things, that is to say, code actions, we must do some further modifications.

    _.___________________

    The next two modifications are not immediate obvious at this stage, but it should become clearer why we need to do this, once the removing of redundant parts and associated modifications are discussed in the next post.

    Rem 2
    The modification so far will not be enough once we remove the redundant parts, since we must pass the modified full arrays at the Call code lines within the recursion routine. We will therefore need to have available the modified array, as given by arrIndx() , after the sort , Rem 1, and before the recursion call section, Rem 3
    Code:
        Next rOuter ' =============End Rem 1=================================================================
    Rem 2
     Let arrIndx() = Application.Index(arrOrig(), Rs(), Cms())
    Rem 3 Preparation for possible recursion Call
    _._____________
    As final modification in preparation of the removal of redundant parts, we need to use and send the arrIndx() rather than arsRef()

    _._____________
    As mentioned, these last two modifications are not immediate obvious at this stage, but it should become clearer why we need to do this, once the removing of redundant parts and associated modifications are discussed in the next post.
    _.___________
    Here are the final modifications before removal of redundant parts….
    http://www.excelfox.com/forum/showth...ll=1#post11077

    The next post considers modifications to remove redundant code actions
    Last edited by DocAElstein; 03-17-2019 at 06:22 PM.

  10. #20
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10
    Final conversion of Sub Bubbles to Sub BubblesIndexIdeaWay

    Step 2 removal of redundant coding
    In the last post we modified indices values in main sort loop sorting
    to get the modified Rs() to use in this
    arrIndx() = Application.Index(arrIndx(), Rs(), Cms())

    What we did was, at this section _...
    __ For Clms = 1 To UBound(arsRef(), 2)
    ___ Let Temp = arsRef(rOuter, Clms): Let arsRef(rOuter, Clms) = arsRef(rInner, Clms): Let arsRef(rInner, Clms) = Temp
    __ Next

    _... we used the row information in the variables rOuter and rInner, to do same swap for row indices,
    Dim TempRs As Long
    _ TempRs = Rs(rOuter, 1): Let Rs(rOuter, 1) = Rs(rInner, 1): Let Rs(rInner, 1) = TempRs


    Column elements in a row swapping
    One of the main distinguishing characteristics of the Index idea way, is that we sort the row indices in to a new order, and then apply the code line, .._
    arrIndx() = App.Ind(arrOrig() , rowindicis, columnindicies
    _.. to get the new order in one go.
    However we must be careful. The immediate conclusion might possibly be that all the sections swapping all column elements in a row are now redundant and so can be removed. The is almost true, but not quite: The reordering of the row indicia is following directly the bubbling through sort of the column being used in the current sort. We must therefore continue to sort/ swap this column element e currently have this
    ____ For Clms = 1 To UBound(arsRef(), 2)
    _____ Let Temp = arsRef(rOuter, Clms): Let arsRef(rOuter, Clms) = arsRef(rInner, Clms): Let arsRef(rInner, Clms) = Temp
    ____ Next Clms
    ___ Let TempRs = Rs(rOuter, 1): Let Rs(rOuter, 1) = Rs(rInner, 1): Let Rs(rInner, 1) = TempRs


    That needs now to be modified now so that they just swap those two row values in the column currently used to base the sort on, ( as well as still doing the swap of the row indicia )
    We note that Clms was the variable for all columns in the loop for all columns in the swapping in the code snippet above , and Clm was the variable for the current column being used to determine the current sort order. So we no longer need that loop to swap all columns, - that can be removed. But if we do this removal, we must add a swap section for the Clm column …_


    ___ Let Temp = arrIndx(rOuter, Clm): Let arrIndx(rOuter, Clm) = arrIndx(rInner, Clm): Let arrIndx(rInner, Clm) = Temp
    ___ Let TempRs = Rs(rOuter, 1): Let Rs(rOuter, 1) = Rs(rInner, 1): Let Rs(rInner, 1) = TempRs


    The complete bubble loop section now looks like this
    Code:
    Rem 1 Bubble sort
    Dim rOuter As Long ' ========"Left Hand"=====================Outer Loop=====================================
        ' For rOuter = Rs(LBound(Rs(), 1), 1) To Rs(UBound(Rs(), 1), 1) - 1 ' THIS WOULD ONLY WORK FOR Copy No 1      For first row indicie to last but one row indicie - I could do this for copy 1
        For rOuter = Left(Trim(strRws), InStr(1, Trim(strRws), " ", vbBinaryCompare) - 1) To Right(Trim(strRws), Len(Trim(strRws)) - InStrRev(Trim(strRws), " ", -1, vbBinaryCompare)) - 1 '   ImmediteWindowToHelpGetAtStuff.JPG : https://imgur.com/yGqmYSu : http://www.eileenslounge.com/viewtopic.php?f=27&t=16407&p=247121#p247121
        'For rOuter = 1 To 5 ' For first run
        Dim rInner As Long ' -------Inner Loop-------------"Right Hand"--------------------------
            For rInner = rOuter + 1 To Rs(UBound(Rs(), 1), 1) ' from just above left hand through all the rest
                If CDbl(arsRef(rOuter, Clm)) > CDbl(arsRef(rInner, Clm)) Then
                Dim Temp As Variant ' I want to Swap those 2 above - I cant easilly in any coding change two values simulataneosly. So one of them Element values will put in this temporary place. This Element Values will then be given the other. Finally the other Element will be given this temporary value
                 Let Temp = arrIndx(rOuter, Clm): Let arrIndx(rOuter, Clm) = arrIndx(rInner, Clm): Let arrIndx(rInner, Clm) = Temp
                Dim TempRs As Long
                 Let TempRs = Rs(rOuter, 1): Let Rs(rOuter, 1) = Rs(rInner, 1): Let Rs(rInner, 1) = TempRs
                Else
                End If
            Next rInner ' -----------------------------------------------------------------------
        Next rOuter ' ==================End=Rem 1===============================================================
    Rem 2
     Let arrIndx() = Application.Index(arrOrig(), Rs(), Cms())
    Here is the full final coding for Sub Call_Sub_BubblesIndexIdeaWay() and Sub BubblesIndexIdeaWay(__
    http://www.excelfox.com/forum/showth...ll=1#post11074
    http://www.excelfox.com/forum/showth...ll=1#post11078



    _.__________________________-

    The next part of this Thread will be to extend the shortened demo coding from the last few posts to a full coding example.
    Effectively this will be a slightly more efficient version of Sub SimpleArraySort8(__
    http://www.excelfox.com/forum/showth...ll=1#post11054
    http://www.excelfox.com/forum/showth...ll=1#post11056
    http://www.excelfox.com/forum/showth...ll=1#post11058


    _...... I expect I will do that later as a bit of revision when it snows next winter , and I come back inside to sit more on my bum and do computer stuff… Until then I’m off to do more useful things outside…. See ya x







    https://excelfox.com/forum/showthrea...ll=1#post11079







    Ref
    https://excelribbon.tips.net/T009600...d_Numbers.html
    http://www.eileenslounge.com/viewtop...247043#p247043

    Last edited by DocAElstein; 08-22-2020 at 12:59 PM.

Similar Threads

  1. Replies: 18
    Last Post: 02-12-2014, 10:47 AM
  2. Conditional Formatting to Create Simple Gantt Chart for Project Plans
    By Transformer in forum Tips, Tricks & Downloads (No Questions)
    Replies: 0
    Last Post: 07-30-2013, 06:32 AM
  3. Alternative to MSCOMCTL.ocx
    By vlc in forum Excel Help
    Replies: 7
    Last Post: 07-19-2013, 10:41 PM
  4. Free And Simple Excel Based Gantt Chart
    By Excel Fox in forum Download Center
    Replies: 0
    Last Post: 05-02-2013, 03:16 PM
  5. Excel Macro to Sort Data if a value changes in defined range
    By Rajesh Kr Joshi in forum Excel Help
    Replies: 4
    Last Post: 09-05-2012, 10:31 AM

Posting Permissions

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