Consulting

Results 1 to 8 of 8

Thread: VBA Pasting values to different cells in the same named range

  1. #1
    VBAX Newbie
    Joined
    Feb 2020
    Posts
    4
    Location

    VBA Pasting values to different cells in the same named range

    Hi all,

    I don't have a ton of VBA experience, so I was hoping I could get some ideas from others. I have a text document resulting from print statements in the following format:

    Set CurrentRng = Range("NamedRange")
    Print #1, .Name & Chr(9) & "NamedRange" & Chr(9) & CurrentRng

    So the data might look like this in the text file:

    Sheet Name Named Rng Value
    Sheet 1 Name 1 2
    Sheet 1 Name 2 3
    Sheet 1 Name 2 4

    Notice that there are 2 values for the the cell range "Name 2" (Named range encompasses two cells).

    I am trying to take the values from the text document and paste them into the correct cells (i.e. if values "3" and "4" were in cells A4 and A5, respectively, in the original document, I want to be able to return them to those positions but using the named range so the results are unaffected by any edits to the excel document)

    Here's my code:

    Sub Test_Input()
    
    Dim InData As String
    Dim SheetName As String
    Dim NamedRng As String
    Dim NewVal As String
    Dim WS As Worksheet
    Dim Target As String
    
    Open "TESTFILE" For Input As #1
    
    Do Until EOF(1)
        Line Input #1, InData
        
        SheetName = GetSubString(InData, Chr(9), 1)
        NamedRng = GetSubString(InData, Chr(9), 2)
        NewVal = GetSubString(InData, Chr(9), 3)
    
        Set WS = ThisWorkbook.Sheets(SheetName)
        
        Target = NamedRng
        
        WS.Range(Target) = NewVal
        
    Loop
    
    Close #1
    End Sub
    Where the GetSubString function is just pulling the 3 fields in the text document.

    I'm running into a problem when two entries have the same named range, as in the example above. So all the cells in the range "Name 2" will populate as 4, instead of the first populating as 3 and the second populating as 4. I know my code currently does nothing to separate these out, I'm having difficulty thinking of a way to get my desired result. Any ideas?

    Thanks in advance!

  2. #2
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,711
    Location
    Code fragment to put data into named range's cells



    Option Explicit
    
    
    Sub demo()
    
    
        ActiveSheet.Range("A1:B1").Name = "MyName"
        
        Range("MyName").Cells(1, 1).Value = 123
        Range("MyName").Cells(1, 2).Value = 456
    
    
        'or
    
    
        [MyName].Cells(1, 1).Value = 321
        [MyName].Cells(1, 2).Value = 654
    
    
    End Sub
    ---------------------------------------------------------------------------------------------------------------------

    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

  3. #3
    Knowledge Base Approver VBAX Wizard p45cal's Avatar
    Joined
    Oct 2005
    Location
    Surrey UK
    Posts
    5,844
    I think you might be able to set up a dictionary object to hold the last used cell for every SheetName/NamedRange combination.
    If you set up a workbook with named ranges etc. in and attach it here along with a text file, I'll give it a go.
    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.

  4. #4
    VBAX Newbie
    Joined
    Feb 2020
    Posts
    4
    Location
    Paul - I think this is the right idea. I've edited my loop to include the following bolded If statement:

    Do Until EOF(1)
        Line Input #1, InData
        
        SheetName = GetSubString(InData, Chr(9), 1)
        NamedRng = GetSubString(InData, Chr(9), 2)
        NewVal = GetSubString(InData, Chr(9), 3)
    
    
        Set WS = ThisWorkbook.Sheets(SheetName)
        
        Target = NamedRng
        
        If WS.Range(NamedRng).Count > 1 Then
            WS.Range(NamedRng).Cells(0 + r, 0 + c) = NewVal
            c = c + 1
        Else
            WS.Range(Target) = NewVal
        End If
        
    Loop
    Where r and c are set to 1. This works correctly for the first row of the named range, but I need to find a way to set r = r + 1 once the last column of the row is written in. Any ideas?

  5. #5
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,711
    Location
    Not sure I completely understand, but maybe .....

    Edited:

    r =1              ' <<<<<<<<<<<<<<<<<<<<<<<<<
    c = 1
    
    
    Do Until EOF(1)
        Line Input #1, InData
    
    
        SheetName = GetSubString(InData, Chr(9), 1)
        NamedRng = GetSubString(InData, Chr(9), 2)
        NewVal = GetSubString(InData, Chr(9), 3)
    
    
        Set WS = ThisWorkbook.Sheets(SheetName)
        Target = NamedRng
    
    
          WS.Range(NamedRng).Cells(r, c) = NewVal
    
    
          If c  > WS.Range(NamedRng).Count Then   ' <<<<<<<<<<<<<<<<<<<<<<<<<<
              c = 1
              r = r + 1
         Else
              c = c + 1
         End IF
      
    Loop
    Last edited by Paul_Hossler; 02-18-2020 at 12:38 PM.
    ---------------------------------------------------------------------------------------------------------------------

    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

  6. #6
    Knowledge Base Approver VBAX Wizard p45cal's Avatar
    Joined
    Oct 2005
    Location
    Surrey UK
    Posts
    5,844
    If you're filling in the cells of a named range by first filling the top row, left to right, before moving on to the 2nd row etc. then instead of using .Cells(row,column) you can use .Cells(index) and just keep incrementing that index by 1 each time.
    But you're still going to have problems because you're not resetting r and c to 1 when a different named range or different sheet is encountered.
    Again, if you set up a workbook with named ranges etc. in and attach it here along with a text file, I'll give it a go. Of course if you can't be bothered, then neither can I.
    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.

  7. #7
    VBAX Newbie
    Joined
    Feb 2020
    Posts
    4
    Location
    Hi P45cal,

    I apologize, I thought Paul's solution was enough, but as you noted I overlooked the need to reset r & c when a new named range appears.

    I threw together a quick sample file, I believe this should have enough data but let me know if this is adequate or not. In the file, there are 4 named cells and 2 named ranges. For some reason I was unable to attach a text document, but if you just run the first sub (test), it should provide you with a text file using whatever info is currently in the named cells that you can use for the input sub.

    Thanks!
    Attached Files Attached Files

  8. #8
    Knowledge Base Approver VBAX Wizard p45cal's Avatar
    Joined
    Oct 2005
    Location
    Surrey UK
    Posts
    5,844
    Try:
    Sub Test_Input()
    Dim InData As String, SheetName As String, NamedRng As String, NewVal As String
    Dim dict, uniq
    
    Set dict = CreateObject("scripting.Dictionary")
    Open "TESTFILE3" For Input As #1
    
    Do Until EOF(1)
      Line Input #1, InData
      SheetName = GetSubString(InData, Chr(9), 1)
      NamedRng = GetSubString(InData, Chr(9), 2)
      NewVal = GetSubString(InData, Chr(9), 3)
      uniq = SheetName & "|" & NamedRng
      If dict.exists(uniq) Then dict(uniq) = dict(uniq) + 1 Else dict(uniq) = 1
      ThisWorkbook.Sheets(SheetName).Range(NamedRng).Cells(dict(uniq)).Value = NewVal
    Loop
    Close #1
    End Sub
    And this is a more streamlined version of your test macro that so far seems to produce the same output:
    Sub test2()
    Dim cell As Range, WS As Worksheet, myRanges, rng
    
    Set WS = ThisWorkbook.Sheets("sheet1")
    
    Open "TESTFILE3" For Output As #1    ' Open file for output.
    myRanges = Array("CellN1", "CellN2", "CellN3", "CellN4", "CellRng1", "CellRng2")
    For Each rng In myRanges
      For Each cell In Range(rng).Cells
        If Trim(cell) <> "" Then Print #1, WS.Name & vbTab & rng & vbTab & cell
      Next cell
    Next rng
    
    Close #1
    End Sub
    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.

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
  •