Consulting

Results 1 to 8 of 8

Thread: Sleeper: VBA hour calculation over 24h

  1. #1
    VBAX Newbie
    Joined
    Jul 2017
    Posts
    2
    Location

    Sleeper: VBA hour calculation over 24h

    Hello,

    I try to add some hour:minutes (string formated) values in vba, but I doesn't work when I use strings like "101:10" (here I get an "type intolerance" error).

    For example:
    E9: "0:30"
    E10: "15:45"
    E11: "101:10"

    With the local formula "=DATWERT(E9)+ZEITWERT(E9)+DATWERT(E11)+ZEITWERT(E11)+DATWERT(E12)+ZEITWERT (E12)" in H1 I get the right value "117:25" (format: [hh]:mm).

    But my vba test-code:
    Dim test As Range
    
    For Each test In mylistobject.AutoFilter.Range.Columns(5).SpecialCells(xlCellTypeVisible).Cells.Offset(1, 0)
      debug.print DateValue(test.Value2) + TimeValue(test.Value2)
    Next test
    throws an error when i access the E11 cell ("101:10"). It seems that DateValue/TimeValue works slighty different than the german functions.
    I tried also DateValue(CDate(test.value2)) - but it doesn't worked too.

    Any help is welcome

    Thank you,
    Thomas

  2. #2
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    The only thing I can think of right now is

    Format E9:E11 as "[h]:mm"
    Debug.Print Format(test.Value2, "dd:hh:ss") 
    'Or (2 variations)
    Debug.Print Format(test.Value, "[d]:hh:ss")
    :
    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

  3. #3
    Knowledge Base Approver VBAX Wizard p45cal's Avatar
    Joined
    Oct 2005
    Location
    Surrey UK
    Posts
    5,876
    vba functions are frequently different from worksheet functions with the same name.
    MOD is one example, I guess DateValue behave differently too.
    The worksheet function DateValue seems to be happy dealing with hours >24, the vba function DateValue doesn't.
    You could stick with the worksheet function by trying the likes of:
    Evaluate("DateValue(""" & test.Value2 & """)")
    or
    yy = Evaluate("DateValue(""" & test & """)")
    or longer:
    yy = Evaluate("DateValue(""" & test & """) + TimeValue(""" & test & """)")
    If the quotation marks are in the cell and show on the worksheet then perhaps:
    yy = Evaluate("DateValue(" & test & ") + TimeValue(" & test & ")")

    I'm not at all sure whether you'd have to:
    yy = Evaluate("DATWERT(""" & test & """)")
    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
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    WorksheetFunction.DateValue() ?
    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

  5. #5
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    This is one ugly macro, but it does get the right answer


    Option Explicit
    
    Sub test()
        Dim E9 As String, E10 As String, E11 As String
        Dim X As Long
    
        E9 = "0:30"
        E10 = "15:45"
        E11 = "101:10"
    
        X = 60 * (1 * Split(E9, ":")(0) + 1 * Split(E10, ":")(0) + 1 * Split(E11, ":")(0)) + (1 * Split(E9, ":")(1) + 1 * Split(E10, ":")(1) + 1 * Split(E11, ":")(1))
    
        MsgBox CLng(X / 60) & ":" & (X - 60 * CLng(X / 60))
    
    End Sub
    Maybe a function to take "mm:ss" or "mmm:ss" strings and convert to integer seconds to calculating, and then format as "mmm:ss" to display
    ---------------------------------------------------------------------------------------------------------------------

    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,876
    Quote Originally Posted by SamT View Post
    WorksheetFunction.DateValue() ?
    Not available, at least not in Excel 2010 here, which is why I suggested Evaluate.
    You can find if a worksheet function is available to vba by using the full Application.WorksheetFunction syntax when you'll get the intellisense.
    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
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    I try to add some hour:minutes (string formated) values in vba, but I doesn't work when I use strings like "101:10" (here I get an "type intolerance" error).
    Are the Cells considered as Dates or as Strings by Excel?

    How to Test:
    Strings. Select the Cell: If in the Formula Bar, the first character is an apostrophe ('), then it's definitely a String.
    Dates: Format the cell as a Number with 10 decimal digits. If it then displays a decimal number, it's a Date.

    Without that knowledge, You can't use code to manipulate them.

    Generally, the Date/Time difference between two Date/Time values can be found as easily as
    Date/Time1 - Date/Time2
    The result will, of course, be in Decimal Days, which can be formatted with any Date/Time Formatting String.

    MS Applications store and use Date/Time values as Double Type values, wherein the Date portion is the Integer pat of the value and the Time portion is the Decimal part.

    The Date part of the Date/Time Value is merely the number of days since Jan 0, 1900. (Jan 1 = Date/Time Value 1.)
    The Time part is stored as Decimal Days, ie 1/(24x60x60). 6 hours, 1/4 Day = .25/24 = 0.0104167 = 6AM

    Today's date is stored as 43035.0, or 43035 days since Jan 0, 1900
    At 7:24:59 AM here, Excel stores the time as 0.3090162037, or 0.3090162037 Days since midnight.
    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
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    I thinking that the data is stored as strings, and not doubles formatted as "hhh:mm" or something

    As SamT says, to do any calculations they have to numbers or something that Excel can convert to numbers

    As something to think on, here's a user defined function that takes a variety of types and number of inputs and returns a string

    Capture.JPG


    Option Explicit
     
    Function SumTimeStrings(ParamArray A()) As Variant
        Dim i As Long, j As Long
        Dim X As Long
        Dim v As Variant
        
        On Error GoTo NiceExit
        
        For i = LBound(A) To UBound(A)
            If IsObject(A(i)) Then
                If TypeName(A(i)) = "Range" Then
                    For j = 1 To A(i).Cells.Count
                        'note .Text and not value - make sure cell is not displayed as #########
                        ' although .Value might work -- not tested
                        v = Split(A(i).Cells(j).Text, ":")
                        If UBound(v) = 1 Then
                            X = X + 60 * v(0) + 1 * v(1)
                        End If
                    Next j
                End If
            
            ElseIf VarType(A(i)) = vbString Then
                v = Split(A(i), ":")
                If UBound(v) = 1 Then
                    X = X + 60 * v(0) + 1 * v(1)
                End If
                            
            End If
        Next i
        
        
        'note the \ for integer division
        SumTimeStrings = CLng(X \ 60) & ":" & (X - 60 * CLng(X \ 60))
        Exit Function
            
    NiceExit:
        SumTimeStrings = CVErr(xlErrNum)
    End Function
    Attached Files Attached Files
    ---------------------------------------------------------------------------------------------------------------------

    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

Posting Permissions

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