Consulting

Results 1 to 18 of 18

Thread: VBA code to quickly change dates and times in comments

  1. #1

    VBA code to quickly change dates and times in comments

    I have a query function that performs through a comment in excel. I never have to change any part of the query except the dates and times. This ends up being the largest portion of the errors in my queries and I am moving on to teaching others how to run them. I am looking for an easier way to change the dates and times in the comments that will not require the user to actually go into the comment and edit. I figured VBA would be my best bet, but I am having a difficult time finding the code that will work.

    The format for the date/time portion of the query is as follows:

    WHERE TimeStampUTC > #YYYY-MM-DD HH:MM:SS# And TimeStampUTC <= #YYYY-MM-DD HH:MM:SS#
    I just want to be able to change the dates and times, preferably using a push button some easy entry format. Does anyone out there know of a way that this can be done?

    Any help would be greatly appreciated.

  2. #2
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Do you need help with the query or with getting data from the cell comment to the query?

    I ask, because if you need help with the comment, the code for the query is not very useful.
    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
    I just need help changing the dates and times. Right now I change them manually in the comments and it is tedious and sometimes causes problems because of punching in a wrong date or time or accidentally deleting a colon.

  4. #4
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    At least post a typical comment text for us.

    Then post one more thing, anything really, just so you are allowed to upload a copy of the workbook to us by first using the "Go advanced" button, then using the "Manage Attachments" button below the Advanced Editor.
    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
    Redacted - High Spread ColorMap.xls

    Here is part of a copy of the workbook that I use. The only part of the comments on these pages that I change is the bottom where the dates and times are

    WHERE TimeStampUTC > #YYYY-MM-DD HH:MM:SS# And TimeStampUTC <= #YYYY-MM-DD HH:MM:SS#
    Everything else stays the same and is used to constantly pull the same data about rolls of material. These are start and stop times for the rolls and I further process the data with other VBA code that I already have working. At the moment, I manually go in and adjust the dates and times, but I would really like a way to do this with something easier like a popup calender/clock or anything that would basically eliminate going into the comment manually. Once I start training others on this process, I know this will be where things get messy.

  6. #6
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Phidelt,

    It is obvious that you are truly a beginner; all of your code was recorded in macros, then parts were copied several times with only some values changed.

    If you truly are running this code on Excel XP, it will fail because XP has a 3 condition limit on Conditional Formatting. It will fail because you have put all the encoded conditions in Index(1)

    Storing database queries in cell comments is probably the worst place to store them. They belong in a module, most especially when you must apply some cell values to them.



    As to your original question, it is possible to programmatically retrieve values from some cell and put them into a cell's comment.

    For what you need, it requires first creating the entire Query in VBA code, then pasting the entire ready-to-use query into the Cell's Comment. Then, in order to use the Query, you need code to pull it out of the comment to make it ready-to-use. Again.



    @ all, The query code posted above are the actual Comment contents. I think that the timestamp referred to in 2 of the 4 comments might be Cells(LastRow, Comment.Parent.Column)



    @ Pidelt, You are trying too hard to hide what you are doing from us that we will never have enough information to help you.
    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

  7. #7
    I'll start with replying to the last part first. The only thing missing from this spreadsheet is a page of proprietary information that isn't pertinent to this topic, and very possibly could get me fired for sending it outside the corporation. Second, excel is a very small piece of the equation for me, so I don't have the time or the desire to master all the intricacies of it and vba. After 15 years as a cellular engineer I find myself in a whole new field of process control and I just stumbled on tool to use for analysing data that is already being pumped around the system. It uses proprietary software that for some crazy reason uses an excel comment to pull queries. I open that sheet every morning and manual change those dates and times to match up to specific rolls of material that were run between those dates and times. It already works, and works very well for what I need. As I've said several times now, all I want to do is be able to adjust those dates and times without opening the comment and doing it manually. I'm not pulling the date from a cell. I'm not pulling anything from any cell and placing it in a comment. The proprietary software uses the comment to do the query from a database on another server and dumps the info on the spreadsheet. I take this info up to my office to a win 7 machine. Then I use my very limited knowledge to bang around on the keyboard to make my copy paste conditional formatting make pretty colors come up on the screen so the people I send the reports to can quickly see what is in or out of process. You are probably very good at what you do, but you seem to have blinders on in this situation. I've explained and repeated what I am trying to do and you seem to still think I am trying to do something completely different from what I have asked.

  8. #8
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Phidel,

    I am thinking about the problem of you.

    You should too.

    You should think about Dilbert and Pointy-Hair.

    You will be aware of my solution tomorrow evening.
    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

  9. #9
    VBAX Master
    Joined
    Jul 2006
    Location
    Belgium
    Posts
    1,286
    Location
    Select a cell that has a comment in the format that you need and you want to alter it.
    Run this coding with alt + F8 and select the name of this macro. It will process the active cell that has to have a comment in the way you want.
    When putting something into the inputboxes, you can't use cursor keys, for some reason excel changes from cell . So use mouse to position your cursor.
    Sub Get_Comment()
    'WHERE TimeStampUTC > #YYYY-MM-DD HH:MM:SS# And TimeStampUTC <= #YYYY-MM-DD HH:MM:SS#
    'comment of cell
    Dim mycomment As String
    'starting date, starting time
    Dim mydate1 As String, mytime1 As String
    'ending date, ending time
    Dim mydate2 As String, mytime2 As String
    'show current comment
    MsgBox ActiveCell.Comment.Text
    'clear variable that will hold comment
    mycomment = vbNullString
    'declare the comment of active cell to variable mycomment
    mycomment = ActiveCell.Comment.Text
    'some split stuff to get date1 into variable, also rest of
    'split ups that you want to do
    mydate1 = Split(Split(ActiveCell.Comment.Text, "#")(1), " ")(0)
    mytime1 = Split(Split(ActiveCell.Comment.Text, "#")(1), " ")(1)
    mydate2 = Split(Split(ActiveCell.Comment.Text, "#")(3), " ")(0)
    mytime2 = Split(Split(ActiveCell.Comment.Text, "#")(3), " ")(1)
    mydate1 = Application.InputBox("Give new start date" & vbCrLf & _
                "Use the format YYYY-MM-DD ...", "Start date", mydate1, Type:=2)
    mytime1 = Application.InputBox("Give new start time ..." & vbCrLf & _
                "Use the format HH:MM:SS ...", "Start time ...", mytime1, Type:=2)
    mydate2 = Application.InputBox("Give new ending date" & vbCrLf & _
                "Use the format YYYY-MM-DD ...", "Ending date", mydate2, Type:=2)
    mytime2 = Application.InputBox("Give new ending time" & vbCrLf & _
                "Use the format HH:MM:SS ...", "Ending time", mytime2, Type:=2)
    'build new query that you want to store in comment
    mycomment = "WHERE TimeStampUTC > #" & mydate1 & " " & mytime1 & _
                "# And TimeStampUTC <= #" & mydate2 & " " & mytime2 & "#"
    'show old comment one last time
    MsgBox activecell.comment.text
    'delete the old comment
    ActiveCell.Comment.Delete
    'put new comment in the place
    ActiveCell.AddComment mycomment
    'show new comment
    MsgBox activecell.comment.text
    End Sub
    Charlize

  10. #10
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,642
    @SamT

    If you truly are running this code on Excel XP,
    I am not familiar with Excel XP.
    I run Excel 2000, 2003, 2007 & 2010 all 'under' (or on top of) the Windows XP umbrella.
    Last edited by snb; 12-12-2014 at 03:33 AM.

  11. #11
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,642
    An illustration:

    Sub M_snb()
      With Sheets("Total Weight").Cells(1).Comment
        sn = Split(.Text, vbLf)
    
        st = Split(sn(UBound(sn)), "#")
        st(1) = "2014-12-12 08:45:04"
        st(3) = "2014-12-12 18:30:30"
    
        sn(UBound(sn)) = Join(st, "#")
    
        .Text = Join(sn, vbLf)
      End With
    End Sub

  12. #12
    Charlize,

    First of all, thank you so much for the help. I really do appreciate it very much. One thing that I do need to do, though, is keep the first part of the comments that are present before the "WHERE TimeStampUTC..." parts. Each of these holds the destinations and data that the program is actually mining. I am trying to learn how this actually works, and your commenting really helps. I understand the need to delete the entire old comment and enter a new one, so I am thinking the fix is in the re-entry of the comment?

    Again thank you for your help.

    Quote Originally Posted by Charlize View Post
    Select a cell that has a comment in the format that you need and you want to alter it.
    Run this coding with alt + F8 and select the name of this macro. It will process the active cell that has to have a comment in the way you want.
    When putting something into the inputboxes, you can't use cursor keys, for some reason excel changes from cell . So use mouse to position your cursor.
    Sub Get_Comment()
    'WHERE TimeStampUTC > #YYYY-MM-DD HH:MM:SS# And TimeStampUTC <= #YYYY-MM-DD HH:MM:SS#
    'comment of cell
    Dim mycomment As String
    'starting date, starting time
    Dim mydate1 As String, mytime1 As String
    'ending date, ending time
    Dim mydate2 As String, mytime2 As String
    'show current comment
    MsgBox ActiveCell.Comment.Text
    'clear variable that will hold comment
    mycomment = vbNullString
    'declare the comment of active cell to variable mycomment
    mycomment = ActiveCell.Comment.Text
    'some split stuff to get date1 into variable, also rest of
    'split ups that you want to do
    mydate1 = Split(Split(ActiveCell.Comment.Text, "#")(1), " ")(0)
    mytime1 = Split(Split(ActiveCell.Comment.Text, "#")(1), " ")(1)
    mydate2 = Split(Split(ActiveCell.Comment.Text, "#")(3), " ")(0)
    mytime2 = Split(Split(ActiveCell.Comment.Text, "#")(3), " ")(1)
    mydate1 = Application.InputBox("Give new start date" & vbCrLf & _
                "Use the format YYYY-MM-DD ...", "Start date", mydate1, Type:=2)
    mytime1 = Application.InputBox("Give new start time ..." & vbCrLf & _
                "Use the format HH:MM:SS ...", "Start time ...", mytime1, Type:=2)
    mydate2 = Application.InputBox("Give new ending date" & vbCrLf & _
                "Use the format YYYY-MM-DD ...", "Ending date", mydate2, Type:=2)
    mytime2 = Application.InputBox("Give new ending time" & vbCrLf & _
                "Use the format HH:MM:SS ...", "Ending time", mytime2, Type:=2)
    'build new query that you want to store in comment
    mycomment = "WHERE TimeStampUTC > #" & mydate1 & " " & mytime1 & _
                "# And TimeStampUTC <= #" & mydate2 & " " & mytime2 & "#"
    'show old comment one last time
    MsgBox activecell.comment.text
    'delete the old comment
    ActiveCell.Comment.Delete
    'put new comment in the place
    ActiveCell.AddComment mycomment
    'show new comment
    MsgBox activecell.comment.text
    End Sub
    Charlize

  13. #13
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Quote Originally Posted by snb View Post
    @SamT



    I am not familiar with Excel XP.
    I run Excel 2000, 2003, 2007 & 2010 all 'under' (or on top of) the Windows XP umbrella.
    That would be Excel 2002 from Office XP

    See: Excel XP
    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

  14. #14
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Phidelt and I are having personality conflicts, so this is as far as I go.

    The pressing requirement is ease of training and use by others and the elimination of Date/Time entry errors as much as possible. To that end I suggest a user form with Calendar Control and some kind of time selector, (which will require the OP to provide us with the required time granularity) for data entry.. Cut and paste might be possible. Ask the OP.

    Other than setting the Timestamps, this is the simplest algorithm I can imagine. I think that even a BioEngineer can maintain and modify it.

    I suggest that the OP complete the two Functions, because the multi-line Query Strings are most pronto errrors herien and because they are mere grunt work only requiring a strong attention to detail.

    Option Explicit
    Sub SamT()
    'This code provided by
    'http://www.vbaexpress.com/forum/showthread.php?51338-VBA-code-to-quickly-change-dates-and-times-in-comments
    
    Dim StartTime As String
    Dim StopTime As String
    
    'Assigning timestamps code here
    '******
    '******
    '******
    '******
    
    'User selects a cell, then runs macro
    'the parent of the selected Cell is the worksheet
    Select Case Selection.Parent.Name
      Case Is = "Speed and Length"
        'Adding a Comment in this manner, deletes any existing Comment Text.
        If Selection.Address = "A1" Or "C1" Then _
        Selection.AddComment.Text NewSpeedAndLength(StartTime, StopTime)
      Case Is = "Total Weight"
        'Note two line continuation characters after "Then"
        If Selection.Address = "A1" Then _
        Selection.AddComment.Text NewTotalWeight(StartTime, StopTime)
      Case Is = "MIS Data"
        If Selection.Address = "A1" Then _
        Selection.AddComment.Text NewSMISData(StartTime, StopTime)
        
      Case Else 'A cell selection error mesage follows. Adjust as desired.
        MsgBox "You selected a wrong cell. Try again."
        Exit Sub
    End Select
    
    End Sub
    
    
    Private Function NewSpeedAndLength(StartTime As String, StopTime As String) As String
    'Code is formatted for clarity of query
    NewSpeedAndLength = _
      "<EQCQuery FC01/MXProLine/ScalarTrenders/ScalarTrender,H=1,F=0,T=0,MX=5000,R=5001,C=256>" & Chr(13) & _
      "SELECT *" & Chr(13) & _
      "FROM [/vio/code length/data source/math/value]" & Chr(13) & _
      "WHERE TimeStampUTC > #" & StartTime & "# And TimeStampUTC <= #" & StopTime & "#"
    End Function
    
    Private Function NewTotalWeight(StartTime As String, StopTime As String) As String
    NewTotalWeight = _
      <EQCQuery FC01/MXProLine/ArrayTrenders/ArrayTrender,H=1,F=0,T=0,MX=5000,R=5001,C=256,A=SC2 Total Low Res Now>
      SELECT [SC2 Total Low Res Now]
      FROM [/scanner 2/measurements/total weight/last scan/low res now/array]
      WHERE TimeStampUTC > # & StartTime & # And TimeStampUTC <= # & StopTime & M#
    End Function
    
    Private Function NewSMISData(StartTime As String, StopTime As String) As String
    
    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

  15. #15
    VBAX Master
    Joined
    Jul 2006
    Location
    Belgium
    Posts
    1,286
    Location
    This little piece will take the rest of the querystring before the first # . Before using this, test it very well for errors in the newly created querystring.
    Sub Get_Comment()
    'WHERE TimeStampUTC > #YYYY-MM-DD HH:MM:SS# And TimeStampUTC <= #YYYY-MM-DD HH:MM:SS#
    'comment of cell
    Dim mycomment As String
    'starting date, starting time
    Dim mydate1 As String, mytime1 As String
    'ending date, ending time
    Dim mydate2 As String, mytime2 As String
    'show current comment
    MsgBox ActiveCell.Comment.Text
    'clear variable that will hold comment
    mycomment = vbNullString
    'declare the comment of active cell to variable mycomment
    mycomment = ActiveCell.Comment.Text
    'some split stuff to get date1 into variable, also rest of
    'split ups that you want to do
    mydate1 = Split(Split(ActiveCell.Comment.Text, "#")(1), " ")(0)
    mytime1 = Split(Split(ActiveCell.Comment.Text, "#")(1), " ")(1)
    mydate2 = Split(Split(ActiveCell.Comment.Text, "#")(3), " ")(0)
    mytime2 = Split(Split(ActiveCell.Comment.Text, "#")(3), " ")(1)
    mydate1 = Application.InputBox("Give new start date" & vbCrLf & _
                "Use the format YYYY-MM-DD ...", "Start date", mydate1, Type:=2)
    mytime1 = Application.InputBox("Give new start time ..." & vbCrLf & _
                "Use the format HH:MM:SS ...", "Start time ...", mytime1, Type:=2)
    mydate2 = Application.InputBox("Give new ending date" & vbCrLf & _
                "Use the format YYYY-MM-DD ...", "Ending date", mydate2, Type:=2)
    mytime2 = Application.InputBox("Give new ending time" & vbCrLf & _
                "Use the format HH:MM:SS ...", "Ending time", mytime2, Type:=2)
    'build new query that you want to store in comment
    '*** old part for query
    'mycomment = "WHERE TimeStampUTC > #" & mydate1 & " " & mytime1 & _
                "# And TimeStampUTC <= #" & mydate2 & " " & mytime2 & "#"
    'Split gives part before first # then add new dates and times and try
    'to put a correct query in the comment. Still not bulletproof but you don't
    'have to enter the comment manually
    '*** new part that takes part of query before first #
    mycomment = Split(ActiveCell.Comment.Text, "#")(0) & "#" & mydate1 & " " & mytime1 & _
                "# And TimeStampUTC <= #" & mydate2 & " " & mytime2 & "#"
    'show old comment one last time
    MsgBox ActiveCell.Comment.Text
    'delete the old comment
    ActiveCell.Comment.Delete
    'put new comment in the place
    ActiveCell.AddComment mycomment
    'show new comment
    MsgBox ActiveCell.Comment.Text
    End Sub
    Charlize

  16. #16
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,642
    Did you overlook the suggestion in #11 ?

  17. #17
    Charlize,

    Thank you for your help with this issue. You have definitely come up with, what I feel like, is the best solution for what I was asking. I have been able to test this in a few samples and have had no problems at all. Thank you again.

  18. #18
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    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
  •