Consulting

Results 1 to 20 of 20

Thread: Runtime error: 13 mismatch in complicated VBA array

  1. #1
    VBAX Regular
    Joined
    Apr 2024
    Location
    UK
    Posts
    9
    Location

    Runtime error: 13 mismatch in complicated VBA array

    Windows 10
    Excel pro Plus 2019


    I am getting a Run-Time: error 13 - Data Mismatch when running my code below with excel VBA editor highlighting the two rows
    If arrData(i, 1) = arrData(i + 1, 1) And arrData(i, 2) = arrData(i + 1, 2) And _
        arrData(i, 9) = arrData(i + 1, 9) And arrData(i, 10) = arrData(i + 1, 10) Then
    I wanted to achieve the fastest possible method using VBA as using a formula (which I explain further down) takes excel over 6
    minutes to run on a spreadsheet with currently 91,000 rows and when live, this figure will only increase.

    What is it I am running the Sub on.
    On a worksheet called "DATA SORT" with a header row.
    There is data in Columns A to J.

    For the sake of this explination, a number of rows with matching data in specific columns are essentually a data set for one product.

    The defining Columns where matching data will occur are Columns A, B, I2 and J.
    The data in Columns C, D, E, F, and G, will not match and will vary.
    This is why I am using columns A, B, I2 and J to make the matches.

    What is it that I am trying to do.
    Where the data (or value) in Columns A, B, I2 and J match with the next row down, look at the row after that, if it also matches then
    continue until the next row does not match.

    *In essence that is defining the a set or group of rows that relate to each other because of the matches in Columns A, B, I2 and J.

    For that set or group of "matching" rows, look at the data or values in the rows of Column E.
    *Column E value will always be a number, either a 1 or 2 or a mix of 1's and 2's.

    If the data/values in all of the cells are all 1's then in column K, in the last row of the matching data set enter the text "YES"
    If the data/values in all of the cells are all 2's then in column K, in the last row of the matching data set enter the text "NO"
    If the data/values in all of the cells are a mix or 1's and 2' then in column K, in the last row of the matching data set enter the text "MAYBE"

    Then look at the row that did not match with the one above it, and where the data (or value) in Columns A, B, I2 and J match with the next row down, look at the row after that, if it also matches then continue down until the next row does not match.

    *This defines the next Data Set (product family) repeat the process described above.
    Then move on to the next, and then the next all of the way down the work sheet.

    I am mindful to not confuse my description but I was origianlly using a formula to do this which was entered by VBA and copied down column K
    until the last used row.

    This was fine when the number of rows was fairly small, say around 1000, maybe 2000, but now there are 91,000 and this will get bigger, when pasted in and copied down by VBA it takes over 6 minutes to run
    and the pages of the work sheet go dim - not good really.

    I include it here so you might be able to see what I am trying to replace but this VBA was my attempt to replace the formula below with something faster.
    My thinking was that loading as much of the data, that my knowledge alllows me to, in to an array and doing the calculations in memory *should* speed
    up quite a lot.

    =IF(AND(A2=A3,B2=B3,I2=I3,J2=J2),"",TEXTJOIN("+",,CHOOSE({1,2},IF(COUNTIFS( E$2:E2,1,B$2:B2,B2),"YES",""),IF(COUNTIFS(E$2:E2,2,B$2:B2,B2),"NO",""),2)))

    This is kind of a big ask but I have tried to explain what I am trying do and what I have done to get as best as I can.


    I am extremely grateful for any assistance.


    Sub SortAndWriteLettersClmK()
    'Turn off application settings
        Application.ScreenUpdating = False
        Application.Calculation = xlCalculationManual
    
    
        Dim ws As Worksheet
        Dim lastRow As Long, i As Long, startRow As Long
        Dim matchCountOne As Long, matchCountTwo As Long
        Dim arrData As Variant, results() As String
        
        Set ws = ThisWorkbook.Worksheets("DATA SORT")
        lastRow = ws.Cells(ws.Rows.Count, "A").End(xlUp).Row
        
        'Read data into an array for faster processing
        arrData = ws.Range("A2:J" & lastRow).value
        ReDim results(1 To UBound(arrData))
        
        'Initialize startRow
        startRow = 1
        
        For i = 1 To UBound(arrData) - 1
            If arrData(i, 1) = arrData(i + 1, 1) And arrData(i, 2) = arrData(i + 1, 2) And _
               arrData(i, 9) = arrData(i + 1, 9) And arrData(i, 10) = arrData(i + 1, 10) Then
                'Matching row found, increment counts based on value in column E (position 5 in array)
                If arrData(i, 5) = 1 Then
                    matchCountOne = matchCountOne + 1
                ElseIf arrData(i, 5) = 2 Then
                    matchCountTwo = matchCountTwo + 1
                End If
            Else
                'Non-matching or final match in a series - determine what to write in column K
                If matchCountOne > matchCountTwo Then
                    FillResults results, startRow, i, "YES"
                ElseIf matchCountTwo > matchCountOne Then
                    FillResults results, startRow, i, "NO"
                ElseIf matchCountOne = matchCountTwo And matchCountOne > 0 Then
                    FillResults results, startRow, i, "MAYBE"
                End If
                'Reset counters and set new start row
                matchCountOne = 0
                matchCountTwo = 0
                startRow = i + 1
            End If
        Next i
        
        'Write results to Column K
        ws.Range("K2:K" & lastRow).value = Application.Transpose(results)
    'Turn on application settings
        Application.ScreenUpdating = True
        Application.Calculation = xlCalculationAutomatic
    
    End Sub
    
    
    Sub FillResults(arr() As String, start As Long, endRow As Long, value As String)
        'Helper sub
        Dim i As Long
        For i = start To endRow
            arr(i) = value
        Next i
    End Sub

  2. #2
    VBAX Mentor
    Joined
    Nov 2022
    Location
    The Great Land
    Posts
    344
    Location
    Maybe time to migrate to a database app like Access.

    Could you provide sample workbook? Follow instructions at bottom of my post.
    How to attach file: Reading and Posting Messages (vbaexpress.com), click Go Advanced below post edit window. To provide db: copy, remove confidential data, run compact & repair, zip w/Windows Compression.

  3. #3
    Moderator VBAX Master georgiboy's Avatar
    Joined
    Mar 2008
    Location
    Kent, England
    Posts
    1,213
    Location
    Perhaps it will work better as below:

    Sub SortAndWriteLettersClmK()
        Dim ws As Worksheet
        Dim lastRow As Long, i As Long
        Dim matchCountOne As Long, matchCountTwo As Long
        Dim arrData As Variant, results() As String
        
        'Turn off application settings
        Application.ScreenUpdating = False
        Application.Calculation = xlCalculationManual
        
        Set ws = ThisWorkbook.Worksheets("DATA SORT")
        lastRow = ws.Cells(ws.Rows.Count, "A").End(xlUp).Row + 1
        
        'Read data into an array for faster processing
        arrData = ws.Range("A2:J" & lastRow).value
        ReDim results(1 To UBound(arrData))
        
        For i = 1 To UBound(arrData) - 1
            If arrData(i, 1) = arrData(i + 1, 1) And arrData(i, 2) = arrData(i + 1, 2) And _
               arrData(i, 9) = arrData(i + 1, 9) And arrData(i, 10) = arrData(i + 1, 10) Then
                'Matching row found, increment counts based on value in column E (position 5 in array)
                If arrData(i, 5) = 1 Then
                    matchCountOne = matchCountOne + 1
                ElseIf arrData(i, 5) = 2 Then
                    matchCountTwo = matchCountTwo + 1
                End If
            Else
                'Non-matching or final match in a series - determine what to write in column K
                If matchCountOne > 0 And matchCountTwo = 0 Then
                    results(i) = "YES"
                ElseIf matchCountTwo > 0 And matchCountOne = 0 Then
                    results(i) = "NO"
                Else
                    results(i) = "MAYBE"
                End If
                'Reset counters and set new start row
                matchCountOne = 0
                matchCountTwo = 0
            End If
        Next i
        
        'Write results to Column K
        ws.Range("K2:K" & lastRow).value = Application.Transpose(results)
        'Turn on application settings
        Application.ScreenUpdating = True
        Application.Calculation = xlCalculationAutomatic
    End Sub
    Click here for a guide on how to add code tags
    Click here for a guide on how to mark a thread as solved
    Click here for a guide on how to upload a file with your post

    Excel 365, Version 2404, Build 17531.20140

  4. #4
    When it stops, what are the values of each of the arrData items you're attempting to compare? Are they each the same data type?
    You can use these instructions Debugging in Excel VBA (In Easy Steps) (excel-easy.com) to view their contents at the time of the error, this should show you why the error is happening.

  5. #5
    VBAX Regular
    Joined
    Apr 2024
    Location
    UK
    Posts
    9
    Location
    Hello Everyone.

    First I would like to thank everyone who has either read this thread and/or replied but I wish to apoligise
    for not replying until now but since making this post I have been quite unwell.

    Before becoming ill I had made a start on a Example worksheet with my existing VBA in use but now
    I am on the mend I hope to get that completed and make replies to the posts here over the next few days.

    Once again, thank you for your replies and suggestions.

    Best

    Event2020

  6. #6
    Very glad to know you're on the mend. Sorry you've been unwell.

  7. #7
    I bet one or more cells in the original data contain an error result (like #REF!, #DIV/0!, #NAME?). You could convert the values to string before comparing:
     If CStr(arrData(i, 1)) = CStr(arrData(i + 1, 1)) And CStr(arrData(i, 2)) = CStr(arrData(i + 1, 2)) And _
               CStr(arrData(i, 9)) = CStr(arrData(i + 1, 9)) And CStr(arrData(i, 10)) = CStr(arrData(i + 1, 10)) Then
    Regards,

    Jan Karel Pieterse
    Excel MVP jkp-ads.com

  8. #8
    VBAX Regular
    Joined
    Apr 2024
    Location
    UK
    Posts
    9
    Location
    Quote Originally Posted by jdelano View Post
    Very glad to know you're on the mend. Sorry you've been unwell.
    Thank you, that is very kind.

    Tentatively back to full speed today.

  9. #9
    VBAX Regular
    Joined
    Apr 2024
    Location
    UK
    Posts
    9
    Location
    Quote Originally Posted by jdelano View Post
    When it stops, what are the values of each of the arrData items you're attempting to compare? Are they each the same data type?
    You can use these instructions Debugging in Excel VBA (In Easy Steps) (excel-easy.com) to view their contents at the time of the error, this should show you why the error is happening.

    Thank you.

  10. #10
    VBAX Regular
    Joined
    Apr 2024
    Location
    UK
    Posts
    9
    Location
    Hi everyone.


    The Runtime error: 13 seems to have, strangly, cured itself and I am unable to duplicate it.
    Ihave not changed the code or the dataset.


    I have attached a link to an example workbook to this post which uses dummy data, mostly fruit and various varieties, all obtained from various websites and the important colums that must match moving down the worksheet, A, B, I, J, are intact regardless of the dummy data.

    Its in a 3.4 mb zip file so I am unable to upload as a file here.

    https://drive.google.com/file/d/1yJd...ew?usp=sharing



    I have added two extra colums, L & M.
    In my original worksheet I only used Column K to host the value from my formula to VBA conversion.


    I wanted a side-by-side comparason while testing so it now works like this...
    Column K = original formula
    Column L = why georgiboy's Code
    Column M = My original code


    georgiboy's code works perfectly, and fast, except for when it gets to Row L21425 and it fills every cell going down with "#N/A" as my original does. The VBA itself does not give any error except from entering "#N/A" in the cells.


    I know in my original post I mentioned this error but in the example workbook I am using all new data so that rules out a data error. I am at a loss as to why georgiboy's Code and my own produces this error at the same row number.

    I am wondering is this might be a virtual memory limitation.


    If you are kind enough to take a look at the Example worksheet, you will see that I have left comments for myself in the VBA. I do this as I work to remind myself of issues and so on.

    Thanks

  11. #11
    Moderator VBAX Master georgiboy's Avatar
    Joined
    Mar 2008
    Location
    Kent, England
    Posts
    1,213
    Location
    I think this is due to the limitations of the TRANSPOSE function, try it as below where the need for this function has been removed.

    Sub FormulaInVBA_Col_L()
        Dim ws As Worksheet
        Dim lastRow As Long, i As Long
        Dim matchCountOne As Long, matchCountTwo As Long
        Dim arrData As Variant, results As Variant
    
        'Turn off application settings
        Application.ScreenUpdating = False
        Application.Calculation = xlCalculationManual
        
        Set ws = ThisWorkbook.Worksheets("Test Data")
        lastRow = ws.Cells(ws.Rows.Count, "A").End(xlUp).Row + 1
        
        'Read data into an array for faster processing
        arrData = ws.Range("A2:J" & lastRow).value
        ReDim results(1 To UBound(arrData), 1 To 1)
        
        For i = 1 To UBound(arrData) - 1
            If arrData(i, 1) = arrData(i + 1, 1) And arrData(i, 2) = arrData(i + 1, 2) And _
               arrData(i, 9) = arrData(i + 1, 9) And arrData(i, 10) = arrData(i + 1, 10) Then
                'Matching row found, increment counts based on value in column E (position 5 in array)
                If arrData(i, 5) = 1 Then
                    matchCountOne = matchCountOne + 1
                ElseIf arrData(i, 5) = 2 Then
                    matchCountTwo = matchCountTwo + 1
                End If
            Else
                'Non-matching or final match in a series - determine what to write in column K
                If matchCountOne > 0 And matchCountTwo = 0 Then
                    results(i, 1) = "YES"
                ElseIf matchCountTwo > 0 And matchCountOne = 0 Then
                    results(i, 1) = "NO"
                Else
                    results(i, 1) = "MAYBE"
                End If
                'Reset counters and set new start row
                matchCountOne = 0
                matchCountTwo = 0
            End If
        Next i
        
        'Write results to Column K
        ws.Range("L2:L" & lastRow - 1).value = results
        'Turn on application settings
        Application.ScreenUpdating = True
        Application.Calculation = xlCalculationAutomatic
    End Sub
    Click here for a guide on how to add code tags
    Click here for a guide on how to mark a thread as solved
    Click here for a guide on how to upload a file with your post

    Excel 365, Version 2404, Build 17531.20140

  12. #12
    VBAX Regular
    Joined
    Apr 2024
    Location
    UK
    Posts
    9
    Location
    Quote Originally Posted by georgiboy View Post
    I think this is due to the limitations of the TRANSPOSE function, try it as below where the need for this function has been removed.
    Hi georgiboy.

    I sat in front of my laptop for nearly five hours and I just could not see what was wrong.

    I would never have thought of the TRANSPOSE function being the issue as I was, wrongly, blinkered in the
    mindset of a literal conversion of the formula to VBA without considering the steps needed.


    This afternoon I have tested it in my example workbook, and in the final workbook.

    Thank you, it works perfectly and is almost instantaneous filling in data down 91,304 rows.

    I could not have asked for a better result.

    Thank you again for your kind help.

  13. #13
    Moderator VBAX Wizard Aussiebear's Avatar
    Joined
    Dec 2005
    Location
    Queensland
    Posts
    5,096
    Location
    Can the limitations be overcome by reducing the size of data being transposed at the time of action?
    Remember To Do the Following....
    Use [Code].... [/Code] tags when posting code to the thread.
    Mark your thread as Solved if satisfied by using the Thread Tools options.
    If posting the same issue to another forum please show the link

  14. #14
    Moderator VBAX Master georgiboy's Avatar
    Joined
    Mar 2008
    Location
    Kent, England
    Posts
    1,213
    Location
    Quote Originally Posted by Aussiebear View Post
    Can the limitations be overcome by reducing the size of data being transposed a the time of action?
    I suppose, but sometimes the data is the data and you just have to work with it. If I am honest the code is better without the use of TRANSPOSE.

    TRANSPOSE is limited to the same amount of rows as old excel I believe.
    Last edited by georgiboy; 05-07-2024 at 02:11 AM. Reason: typo
    Click here for a guide on how to add code tags
    Click here for a guide on how to mark a thread as solved
    Click here for a guide on how to upload a file with your post

    Excel 365, Version 2404, Build 17531.20140

  15. #15
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,738
    Location
    I try to find a MS article for things like this, but this is the best I found


    https://www.ablebits.com/office-addi...536%20elements.


    Note. Transposing with VBA, has a limitation of 65536 elements. In case your array exceeds this limit, the extra data will be silently cast away.
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  16. #16
    VBAX Master Aflatoon's Avatar
    Joined
    Sep 2009
    Location
    UK
    Posts
    1,728
    Location
    If I remember rightly, it varies with versions too. In my 365, this code:

       Dim u(1 To 2, 1 To 70000)
       Dim v
       v = Application.Transpose(u)
       MsgBox UBound(v, 1)
    rather worryingly shows 4464 as the upper bound of the first dimension of the transposed array. So it appears to have done some sort of Mod 65536 and resized using the remainder, keeping the data from the start of the original array.
    Be as you wish to seem

  17. #17
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,738
    Location
    I wonder if 32 bit or 64 bit Excel makes a difference?
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  18. #18
    Knowledge Base Approver VBAX Wizard p45cal's Avatar
    Joined
    Oct 2005
    Location
    Surrey UK
    Posts
    5,877
    Quote Originally Posted by Paul_Hossler View Post
    I wonder if 32 bit or 64 bit Excel makes a difference?
    With 64bit Windows and 64bit MS365 I get the same results as msg#16
    For me, I try always to avoid using TRANSPOSE in vba;
    • it's faster to loop and
    • transpose converts the data type Date to String, leaving it to Excel and whatever locale it's working in to re-interpret those date strings to dates proper.
    p45cal
    Everyone: If I've helped and you can't be bothered to acknowledge it, I can't be bothered to look at further posts from you.

  19. #19
    Moderator VBAX Master georgiboy's Avatar
    Joined
    Mar 2008
    Location
    Kent, England
    Posts
    1,213
    Location
    Mine is the same - 4464,

    I did note though that if the number of rows is 65536 then the ubound returns 65536. If you make it 65537 then the ubound is 2 I suppose for the same reason.

       Dim u(1 To 2, 1 To 65536)
       Dim v
       v = Application.Transpose(u)
       MsgBox UBound(v, 1)
       Dim u(1 To 2, 1 To 65537)
       Dim v
       v = Application.Transpose(u)
       MsgBox UBound(v, 1)
    I think I will be avoiding TRANSPOSE on larger ranges that have the potential to expand going forward, why on earth would Microsoft not have the transpose function updated to work with the new row size...

    Quote Originally Posted by Aflatoon View Post
    So it appears to have done some sort of Mod 65536 and resized using the remainder, keeping the data from the start of the original array.
    So strange
    Click here for a guide on how to add code tags
    Click here for a guide on how to mark a thread as solved
    Click here for a guide on how to upload a file with your post

    Excel 365, Version 2404, Build 17531.20140

  20. #20
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,738
    Location
    Guessing ---

    Older Excel worksheets were limited to 65536 rows, and since TRANSPOSE() is a ws fuction, someone took the easy way out and hardcoded something that was never made compatible with the 1M+ row versions of Excel??
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

Tags for this Thread

Posting Permissions

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