Consulting

Results 1 to 11 of 11

Thread: Writing array to sheet

  1. #1
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location

    Writing array to sheet

    Hi.

    I've just spent more time trying to write an array to a sheet than writing the code to make the array, and then still couldn't do it!

    This was in responce to this thread:

    Sub SplitList()
        Dim arr1, arr2, arr3(), arr4, lr As Long, i As Long, j As Long, k As Long, x As Long
        Dim str As String
        lr = Cells(Rows.Count, 1).End(xlUp).Row
        arr1 = Range("A2:E" & lr)
        x = 0
        For i = 1 To UBound(arr1)
            arr2 = Split(arr1(i, 3), ",")
            For j = 0 To UBound(arr2)
                For k = 1 To 5
                    If k = 3 Then
                        str = str & Trim(arr2(j)) & ","
                    Else
                        str = str & Trim(arr1(i, k)) & ","
                    End If
                Next
                ReDim Preserve arr3(x)
                arr3(x) = Split(Left(str, Len(str) - 1), ",")
                x = x + 1
                str = ""
            Next
        Next
        arr4 = Application.Transpose(arr3)
        Range("G2:K" & x + 1).Value = Application.Transpose(arr4)
    End Sub
    But I was trying to write arr3 direct like this:

        Range("G2:K" & x + 1).Value = arr3
    but it wouldn't write and have no idea why. Any answer please?
    Semper in excretia sumus; solum profundum variat.

  2. #2
    You can only pass either a single value or a two-dimensional array to Excel. arr3 is a one-dimensional array. The transpose function converts that to a two-dimensional one.
    Regards,

    Jan Karel Pieterse
    Excel MVP jkp-ads.com

  3. #3
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    please post a sample file.

    arr3 is a 1-dimensional array that can't be redimmed with redim preserve.

  4. #4
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    From earlier thread.
    Attached Files Attached Files
    Semper in excretia sumus; solum profundum variat.

  5. #5
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    Thanks guys, it's sinking in... slowly!

    So is the best way to do it the way I did? (I realise I could have used the same array name instead of introducing arr4)
    Semper in excretia sumus; solum profundum variat.

  6. #6
    Site Admin
    Urban Myth
    VBAX Guru
    Joined
    May 2004
    Location
    Oregon, United States
    Posts
    4,940
    Location
    There's a few things to note here in addition to what's already been said. VBA is kind of letting you get away with murder in most of this - which is a double-edged sword to be sure. For example, using UBound(), you don't have to specify the column as it will use the first dimension. I recommend always setting it on multi-dimensional arrays. So instead of using Ubound(arr1) you would use UBound(arr1, 1). You're also assuming your arrays are a base of 1, which they are when set to a range of cells, but this shouldn't be assumed. Instead of saying ' For i = 1 to...' you should use 'For i = LBound(arr, 1) to...'. Same with your j loop, it assumes a base of 0, like a normal array would behave, but using LBound takes out the guess work.

  7. #7
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    Thanks Zack, I'm still struggling with some of the ways to fill arrays, but I'm trying. I appreciate your comments on UBound, but I didn't assume them to be base 0 or 1, hence the change in start for the loops, I'm just a lazy typer!
    Semper in excretia sumus; solum profundum variat.

  8. #8
    Knowledge Base Approver VBAX Wizard p45cal's Avatar
    Joined
    Oct 2005
    Location
    Surrey UK
    Posts
    5,876
    You could also create arr3 in the correct orientation from the start, but to do that we have to know how big it will need to be because we can't ReDim Preserve as we go along because we'd have to ReDim the first member/dimension of the array which is verboten. So a line to calculate the needed size near the start tries to do that. Then your original code, with a tweak or two, handles the rest.
    Added bonus, if there were real dates in there, they wouldn't be mangled (converted to strings) by the Transpose operation(s) (but paulked and I have had that discussion recently).

    Sub SplitList()
    Dim lr As Long, arr1, zz As Long, x As Long, i As Long, arr2, j As Long, k As Long, arr3
    lr = Cells(Rows.Count, 1).End(xlUp).Row
    arr1 = Range("A2:E" & lr)
    'Find size of final array:
    zz = UBound(Split(WorksheetFunction.TextJoin(",", True, Range("C2:C" & lr).Value), ",")) + 1
    ReDim arr3(1 To zz, 1 To 5)
    x = 0
    For i = 1 To UBound(arr1)
      arr2 = Split(arr1(i, 3), ",")
      For j = 0 To UBound(arr2)
        x = x + 1
        For k = 1 To 5
          If k = 3 Then arr3(x, k) = Trim(arr2(j)) Else arr3(x, k) = arr1(i, k)
        Next
      Next
    Next
    Range("G2:K2").Resize(x).Value = arr3
    End Sub
    Last edited by p45cal; 04-28-2020 at 12:55 PM.
    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.

  9. #9
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    Brilliant, just what I needed to know. Thank you
    Semper in excretia sumus; solum profundum variat.

  10. #10
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    Sub M_snb()
      sn = sheet1.Cells(1).CurrentRegion
      ReDim st(UBound(Split(Join(Application.Transpose(Application.Index(sn, 0, 3)), ","), ",")), 4)
    
      For j = 2 To UBound(sn)
        sq = Split(sn(j, 3), ",")
        For jj = 0 To UBound(sq)
          st(n, 0) = sn(j, 1)
          st(n, 1) = sn(j, 2)
          st(n, 2) = Trim(sq(jj))
          st(n, 3) = sn(j, 4)
          st(n, 4) = sn(j, 5)
          n = n + 1
        Next
      Next
       
      sheet1.Cells(2, 7).Resize(UBound(st) + 1, UBound(st, 2) + 1) = st
    End Sub

  11. #11
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    One read, one write... brilliant too
    Semper in excretia sumus; solum profundum variat.

Posting Permissions

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