Consulting

Results 1 to 20 of 20

Thread: VBA Function - Last Row

  1. #1
    VBAX Regular
    Joined
    Jan 2017
    Location
    Warsaw
    Posts
    70
    Location

    VBA Function - Last Row

    Hey Guys!

    I'm currently trying to implement/create a function (VBA based) for the last row in the respective column.
    I'm working a lot with dynamic tables, so it could rate high the performance and usibility.


    For Example:

    =SUM(C2:LastRow(3))

    I know there are some combined excel-funtions that defines the respective last row but I want it a bit more professional.

    Do anyone have a suggestion for this objective?
    Is there anything to consider about? Maybe some weak points with working with something like that?


    Best regards
    Joshua

  2. #2
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    Not 100% sure I'm understanding, but maybe something these as a starting point?

    The Yellow is the data, the Orange is RangeToEnd(), and the Green are LastRowAddr

    Capture.JPG





    Option Explicit
    
    Function LastRowAddr(C As Long, Optional RowAbsolute As Boolean = True, Optional ColumnAbsolute As Boolean = True) As String
        LastRowAddr = Cells(Rows.Count, C).End(xlUp).Address(RowAbsolute, ColumnAbsolute)
    End Function
    
    Function RangeToEnd(R As Range) As Range
        Set RangeToEnd = Range(R, Cells(Rows.Count, R.Column).End(xlUp))
    End Function
    ---------------------------------------------------------------------------------------------------------------------

    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
    Administrator
    VP-Knowledge Base
    VBAX Grand Master mdmackillop's Avatar
    Joined
    May 2004
    Location
    Scotland
    Posts
    14,489
    Location
    or maybe =SUMDOWN(C2)
    Function SUMDOWN(r As Range)
    SUMDOWN = WorksheetFunction.Sum(Range(r, Cells(Rows.Count, r.Column).End(xlUp)))
    End Function
    MVP (Excel 2008-2010)

    Post a workbook with sample data and layout if you want a quicker solution.


    To help indent your macros try Smart Indent

    Please remember to mark threads 'Solved'

  4. #4
    VBAX Regular
    Joined
    Jan 2017
    Location
    Warsaw
    Posts
    70
    Location
    Thanks guys for your posts.

    I'm sorry that I was to imprecise.

    The objectiv is to get the address of the last row for the respective column. That respective column would be defined with the index number, inside the brackets of the function.
    For example the function for colum C:
    =LastRow(3)
    > C15

    I'm working with a lot of functions, including different operations according to the scope of a respective column.


    Do you need a further or more detailed explanation?

    Are there any weak points for that?
    Maybe I'm on a wrong way.


    Best regards!

  5. #5
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    Quote Originally Posted by joshua1990 View Post
    Thanks guys for your posts.

    I'm sorry that I was to imprecise.

    The objectiv is to get the address of the last row for the respective column. That respective column would be defined with the index number, inside the brackets of the function.
    For example the function for colum C:
    =LastRow(3)
    > C15
    And LastRowAddr() in post #2 doesn't do that?
    ---------------------------------------------------------------------------------------------------------------------

    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
    VBAX Guru Kenneth Hobs's Avatar
    Joined
    Nov 2005
    Location
    Tecumseh, OK
    Posts
    4,956
    Location
    Depends on what you want I guess. Here is one way to get the string and range values. It is similar to what the other two guys showed you.

    Some of it is redundant but shows a concept.
    '=SUM(INDIRECT("C2:"&slastrow("C")))
    Function sLastRow(col As Variant, Optional os As Long) As String
        Application.Volatile
        If Not IsNumeric(col) Then col = Columns(col).Column()
        sLastRow = Cells(Cells.Rows.Count, col).End(xlUp).Offset(os).Address
    End Function
     
    '=SUM(C2:rlastrow("C"))
    Function rLastRow(col As Variant, Optional os As Long) As Range
        Application.Volatile
        If Not IsNumeric(col) Then col = Columns(col).Column()
        Set rLastRow = Cells(Cells.Rows.Count, col).End(xlUp).Offset(os)
    End Function

  7. #7
    VBAX Regular
    Joined
    Jan 2017
    Location
    Warsaw
    Posts
    70
    Location
    Hey Paul!

    I'm sorry, I have some problems with the buildung of the function in excel.

    Of cource, your function delivers a relative address of the respective last row.
    But how can I put or include this defined function into an regular function?
    Are there any symbols or operators necessary.

    I got a #Value with the following constructions
    =SUM(A2:LastRowAddr(1))
    =SUM(A2:(LastRowAddr(1)))
    =SUM(A2:"LastRowAddr(1)")
    =SUM(A2:&LastRowAddr(1)&)
    Thanks Kenneth!

    It works with the following formulation
    =SUM(INDIRECT("C2:"&LastRowAddr(1)))

  8. #8
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    Quote Originally Posted by joshua1990 View Post
    Hey Paul!

    I'm sorry, I have some problems with the buildung of the function in excel.

    Of cource, your function delivers a relative address of the respective last row.
    But how can I put or include this defined function into an regular function?
    Are there any symbols or operators necessary.

    I got a #Value with the following constructions
    =SUM(A2:LastRowAddr(1))
    =SUM(A2LastRowAddr(1)))
    =SUM(A2:"LastRowAddr(1)")
    =SUM(A2:&LastRowAddr(1)&)


    The objectiv is to get the address of the last row for the respective column. That respective column would be defined with the index number, inside the brackets of the function.
    For example the function for colum C:
    Sorry, when you said "address" I thought you mean the .Address as a String

    LastRowAddr returns a string, so =SUM("A2:"&LastRowAddr(1)) would work


    But if you want a Range (like C15) then

    Function LastRow(C As Long) As Range
        Set LastRow = Cells(Rows.Count, C).End(xlUp)
    End Function
    so =SUM(A2:LastRow(1)) would work

    Capture.JPG
    ---------------------------------------------------------------------------------------------------------------------

    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

  9. #9
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    standard module code
    Option Explicit
    
    Public Function LastRowAddress(ColNum As Long) As String
    Dim LastCell As Range
    Set LastCell = Application.Caller.Parent.Cells(Rows.Count, ColNum).End(xlUp)
    LastRowAddress = LastCell.Address(RowAbsolute:=False, ColumnAbsolute:=False)
    End Function
    Returns an address like A2 with no $ signs. works on all worksheets
    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
    Eine dynamische Tabelle.
    Spalte 1 : Spalte Name: "aa1"

    Letzte Zelle in Spalte1:
     =INDEX(A:A;ROWS(Table1[[#All];[aa1]]);1)
    Aber das braucht man nicht zum summieren von Spalte C; dann reicht

    =SUM(Table1[[#All];[aa3]])

  11. #11
    VBAX Regular
    Joined
    Jan 2017
    Location
    Warsaw
    Posts
    70
    Location
    Thanks guys for all your posts!

    We have now the following solutions:

    Function LastRowAddr(C As Long, Optional RowAbsolute As Boolean = True, Optional ColumnAbsolute As Boolean = True) As String 
        LastRowAddr = Cells(Rows.Count, C).End(xlUp).Address(RowAbsolute, ColumnAbsolute) 
    End Function
    This works great. It delivers a relative address of the last row.

    Function SUMDOWN(r As Range)     SUMDOWN = WorksheetFunction.Sum(Range(r, Cells(Rows.Count, r.Column).End(xlUp)))  End Function
    I dont think this will solve the problem. The objective is to create a function for the last row for a definite column.


    Function rLastRow(col As Variant, Optional os As Long) As Range     Application.Volatile 
        If Not IsNumeric(col) Then col = Columns(col).Column() 
        Set rLastRow = Cells(Cells.Rows.Count, col).End(xlUp).Offset(os)  End Function
    Is this working with the index of the column and the letter (A)?
    Or whats the big difference in this kind?

    Function LastRow(C As Long) As Range 
        Set LastRow = Cells(Rows.Count, C).End(xlUp) 
    End Function
    I'm sorry. I not have know, that I searched the range and not exactly the address.

    Option Explicit 
     
    Public Function LastRowAddress(ColNum As Long) As String 
        Dim LastCell As Range 
        Set LastCell = Application.Caller.Parent.Cells(Rows.Count, ColNum).End(xlUp) 
        LastRowAddress = LastCell.Address(RowAbsolute:=False, ColumnAbsolute:=False) 
    End Function
    Probably this is the best approach, isn't it?
    Are there some weak points?

    @snb:

    The objective was/ is a VBA function. I know, there are different ways with combined excel-functions to solve this problem.



    @all:
    Which approach would you choose and why?

  12. #12
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,646
    No, it isn't

    Function F_snb()
        F_snb = ActiveSheet.Cells(Rows.Count, ActiveCell.Column).End(xlUp).Address
    End Function
    or
    Function F_snb(y)   ' specify the column
        F_snb = ActiveSheet.Cells(Rows.Count, y).End(xlUp).Address
    End Function
    or
    Function F_snb(c00,y)   ' specify the sheet and the column
        F_snb = Sheets(c00).Cells(Rows.Count, y).End(xlUp).Address
    End Function

  13. #13
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    C is the column number, not Column "C"


    Function LastRow(C As Long) As Range 
        Set LastRow = Cells(Rows.Count, C).End(xlUp) 
    End Function

    Look at the screen shot in #8 and how it's used in the formula
    ---------------------------------------------------------------------------------------------------------------------

    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

  14. #14
    VBAX Regular
    Joined
    Jan 2017
    Location
    Warsaw
    Posts
    70
    Location
    Quote Originally Posted by Paul_Hossler View Post
    C is the column number, not Column "C"


    Function LastRow(C As Long) As Range 
        Set LastRow = Cells(Rows.Count, C).End(xlUp) 
    End Function

    Look at the screen shot in #8 and how it's used in the formula

    Yeah, I know (:

    The post referred to the following code:
    Function SUMDOWN(r As Range)     
    SUMDOWN = WorksheetFunction.Sum(Range(r, Cells(Rows.Count, r.Column).End(xlUp)))  
    End Function
    The variable r is declared as a range-object. So it doesn't work with numbers, but yours approach.

  15. #15
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Probably this is the best approach, isn't it?
    Are there some weak points?
    I don't like use numbers to refer to columns. By changing the name and Type of ColNum to Col and Variant, one can use either
    =LastRowAddress(3)
    or
    =LastRowAddress("C")

    Public Function LastRowAddress(Col) As String 
        Dim LastCell As Range 
        Set LastCell = Application.Caller.Parent.Cells(Rows.Count, Col).End(xlUp) 
        LastRowAddress = LastCell.Address(RowAbsolute:=False, ColumnAbsolute:=False) 
    End Function
    By adding a line, one can even use Ranges by simply clicking a cell when using fx to insert the function
    Public Function LastRowAddress(Col) As String
        Dim LastCell As Range
        If TypeName(Col) = "Range" Then Col = Col.Column
        Set LastCell = Application.Caller.Parent.Cells(Rows.Count, Col).End(xlUp)
        LastRowAddress = LastCell.Address(RowAbsolute:=False, ColumnAbsolute:=False)
    End Function
    With that, the formula options are:
    =LastRowAddress(3)
    or
    =LastRowAddress("C")
    Or
    =LastRowAddress (C2)
    OR
    =LastRowAddress(C:C)
    OR
    even other Functions that return a Range reference
    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

  16. #16
    Administrator
    VP-Knowledge Base VBAX Grand Master mdmackillop's Avatar
    Joined
    May 2004
    Location
    Scotland
    Posts
    14,489
    Location
    Are there some weak points?
    Ensure that the function is Volatile (mine is not). Changing a value within the range does not force a recalculation.
    MVP (Excel 2008-2010)

    Post a workbook with sample data and layout if you want a quicker solution.


    To help indent your macros try Smart Indent

    Please remember to mark threads 'Solved'

  17. #17
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    Expanding on SamT's and mac's ideas to increase flexibility ...



    =SUM($A$1:LastRow(1))
    =SUM($A$1:LastRow("a"))
    =SUM($A$1:LastRow($A$7))


    Option Explicit
    Public Function LastRow(Col As Variant) As Variant
        
        Application.Volatile
        
        With Application.Caller.Parent
            If TypeName(Col) = "Range" Then
                Set LastRow = .Cells(.Rows.Count, Col.Cells(1, 1).Column).End(xlUp)
                
            ElseIf IsNumeric(Col) Then
                Set LastRow = .Cells(.Rows.Count, Col).End(xlUp)
                
            ElseIf VarType(Col) = vbString Then
                Set LastRow = .Cells(.Rows.Count, Col).End(xlUp)
            
            Else
                LastRow = CVErr(xlErrNA)
            End If
        End With
    End Function
    ---------------------------------------------------------------------------------------------------------------------

    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
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Quote Originally Posted by mdmackillop View Post
    Ensure that the function is Volatile (mine is not). Changing a value within the range does not force a recalculation.
    Public Function LastRowAddress(Col) As String 
        Dim LastCell As Range 
       Application.Volatile
    
        If TypeName(Col) = "Range" Then Col = Col.Column 
    
        Set LastCell = Application.Caller.Parent.Cells(Rows.Count, Col).End(xlUp) 
        LastRowAddress = LastCell.Address(RowAbsolute:=False, ColumnAbsolute:=False) 
    End Function
    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

  19. #19
    VBAX Regular
    Joined
    Jan 2017
    Location
    Warsaw
    Posts
    70
    Location
    Thanks guys for the adjustments!

    Maybe there are a futher more point to figure out.
    A classic excel-function rearrange the respective column or/ and cell by pulling the formula along column or row, of course only if the address/ range is relative declared.
    Is this dynamic adoption also possible to include?

  20. #20
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    To learn Excel VBA: Record Macro...

    Open a new Excel.
    In Cell A1 place a 1 (ein )
    In Cell B1 place "=A1"
    Select A1:B5
    Excel Menu >> Tools >> Macro >> Record New Macro >> Store Macro in this workbook >> OK
    Press Ctrl+D
    Excel Menu >> Tools >> Macro >> Stop Recording


    In C1 place "=NOW()"
    Cell Format C1 >> Custom >> "MMM" (MMM)
    Record New Macro
    Select C1:C5
    Excel Menu >> Edit >> Fill >> Series >> Date Unit >> Month >> OK
    Stop Recording

    Open VBA Editor (VBIDE) >> Modules >> Module1

    Note difference when Selecting Cells before recording and after recording.

    Place Cursor in "FillDown" in one Macro >> Press F1 for Help. In addition, look at all topics in "See Also" in FillDown Help

    See "DataSeries" in Help




    Typical Recorded Macro:
    Sub Macro3()
    '
    ' Macro3 Macro
    ' Macro recorded 9/2/2017 by SamT
    '
    
    '
        Range("C1:C5").Select
        Selection.DataSeries Rowcol:=xlColumns, Type:=xlChronological, Date:= _
            xlMonth, Step:=1, Trend:=False
    End Sub
    Note in above macro,
    Range("C1:C5").Select
    Selection.

    Macros cannot read minds, you should delete all such ".Select>Selection.", Leaving only one dot after deletion.
    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
  •