Consulting

Results 1 to 14 of 14

Thread: VBA: Get Range of found cell

  1. #1

    VBA: Get Range of found cell

    Hi everyone. I have this code that finds a value in the cells of a defined range. I need help on how to set a new range of the cell that is found. The new range should be everything below the found cell to the last row used.

    Also I am not sure if there is a better way, but with the current code, it will find "Test" in the entire range. In a realistic setting, Test should only be found once in the entire range.

    Here is my code so far:

    Sub test()
    Dim rng As Range, newRng As Range
    
    Set rng = Range("A2:ZZ2")
        
        For Each cell In rng.Cells
            If cell.Value = "Test" Then
              Set newRng = 'SOME CODE
            End If
        Next
        
    End Sub

  2. #2
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    If I understand correctly, I think this is all you need

    Set newRng = cell
    Exit For

    If you find "Test" then there's no need to continue inside the For loop
    ---------------------------------------------------------------------------------------------------------------------

    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
    Thanks for your reply.. let me try this. Not sure if cell is the exact range I was asking for.

  4. #4
    VBAX Guru Kenneth Hobs's Avatar
    Joined
    Nov 2005
    Location
    Tecumseh, OK
    Posts
    4,956
    Location
    Welcome to the forum!

    If cell was not what you wanted, please explain more.

    Have you considered Range's Find method?

    Option Explicit
    'Option Compare Binary 'Case sensitive comparisons.
    Option Compare Text   'Case insensitive comparisons.
    
    
    Sub paul()
      Dim rng As Range, newRng As Range
      Dim cell As Range
       
      Set rng = Range("A2:ZZ2")
       
      For Each cell In rng
        If cell.Value2 = "Test" Then
          Set newRng = cell 'SOME CODE
          Exit For
        End If
      Next
      
      If Not cell Is Nothing Then MsgBox "Test found in cell: " & cell.Address
    End Sub
    
    
    Sub ken()
      Dim newRng As Range, r As Range
      
      Set r = Range("A2:ZZ2")
       
      Set newRng = r.Find("Test", after:=r(r.Cells.Count), SearchOrder:=xlNext)
      If Not newRng Is Nothing Then _
        MsgBox "Found case insensitive ""Test"" in cell: " & newRng.Address
      
      Set newRng = r.Find("Test", after:=r(r.Cells.Count), _
        SearchOrder:=xlNext, MatchCase:=True)
      If Not newRng Is Nothing Then _
        MsgBox "Found case sensitive ""Test"" in cell: " & newRng.Address
    End Sub

  5. #5
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    Quote Originally Posted by thes4s View Post
    Thanks for your reply.. let me try this. Not sure if cell is the exact range I was asking for.
    That's always possible, but that's what the code was asking for

    As Ken says, more information might be helpful if it's not
    ---------------------------------------------------------------------------------------------------------------------

    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
    Joined
    Apr 2012
    Posts
    5,646
    Sub M_snb() 
      msgbox  Range("A2:ZZ2").find("Test").offset(1).resize(usedrange.rows.count-2).address
    End Sub

  7. #7
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Sub Test()
    'Sets NewRng = Used Range below first instance of "Test".
    'Does not include Row of "Test"
    'Does include entire last Column even if last rows of column are empty
    
    Dim Found As Range
    Dim NewRng As Range
    
    With Sheet1.UsedRange
    Set Found = .Find("Test")
    If Not Found Is Nothing Then _
      Set NewRng = Range(Cells(Found.Row + 1, 1), .Cells(.Cells.Count))
    End With
    End Sub
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

  8. #8
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,646
    @SamT


    Why ignoring the object variable you just created ?
    If Not Found Is Nothing Then Set NewRng = range(found.offset(1),found.end(xldown))

  9. #9
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    To make clear to beginner what is going on.

    In production I could replace all "Found" with "NewRng."

    It is not clear (to me) if the OP wants "NewRng" to be just the Column of "Test" or the entire Used Range below "Test."
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

  10. #10
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,646
    To me neither.

  11. #11
    Quote Originally Posted by SamT View Post
    Sub Test()
    'Sets NewRng = Used Range below first instance of "Test".
    'Does not include Row of "Test"
    'Does include entire last Column even if last rows of column are empty
    
    Dim Found As Range
    Dim NewRng As Range
    
    With Sheet1.UsedRange
    Set Found = .Find("Test")
    If Not Found Is Nothing Then _
      Set NewRng = Range(Cells(Found.Row + 1, 1), .Cells(.Cells.Count))
    End With
    End Sub
    Thx for this. I will try this and will keep you up to date. But from the looks of the code, from my limited knowledge of VBA. Once "test" is found, whenever it is at, it will be set as the range correct? The reason I ask, is the range set with the horizontal or vertical range?
    Last edited by thes4s; 11-18-2015 at 04:09 PM.

  12. #12
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    A worksheet's "UsedRange" is defined as a rectangle that contains every used cell on the sheet. A Used cell is defined as a cell the has a formula or value or is formatted.

    That sub sets "NewRng " = the entire UsedRange that is below the Row that has the first instance of "Test" in it.

    Paul's post # 2 And Kenneth's post 34 sets NewRng = the cell that has "Test" in it.

    You did not specify what you wanted NewRng set to. you just said the Range below Test.

    This part of my sub is using VBA shorthand
    Set NewRng = Range(Cells(Found.Row + 1, 1), .Cells(.Cells.Count))
    Set NewRng = Range(Range1,Range2) sets NewRng to all the Range between and including Range1 and Range2

    A Range can be addressed by Cells(Row, Column)
    Cells(Found.Row +1, 1)
    is the First Column in the Row below (Row + 1) Found (the "Test" cell)

    Since it is within the With ...End With block, the bare dots before ".Cells" is shorthand for
    Set NewRng = Range(Cells(Found.Row + 1, 1), Sheet1.UsedRange.Cells(Sheet1.UsedRange.Cells.Count))
    If the UsedRange has n Cells, then .Cells(n) is the last cell in the Used Range
    Last edited by SamT; 11-18-2015 at 04:52 PM.
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

  13. #13
    You did not specify what you wanted NewRng set to. you just said the Range below Test.
    SamT, I am sorry if I did not specify the new range. But let me specify, once "Test" is found for example if it is found on B2. The first cell below it to the last cell used in the column will be the new range. So newRng = Range("B3:B17"). Does your code you provided do this for me? Thanks again.

  14. #14
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    No it doesn't.

    Why don't you try it first and let us see what you come up with
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

Posting Permissions

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