Consulting

Results 1 to 8 of 8

Thread: Solved: VBA lookup to insert value into cell.

  1. #1

    Solved: VBA lookup to insert value into cell.

    Hello gurus.

    I have a question that requires a lookup function.

    There is column E. with the forumular from E6 Down [VBA]=IF(C6="","",IF(C6<=SUMIF(Sheet1!A:A,A6,Sheet1!D),"Yes","No"))[/VBA]
    This does the lookup to see it im trying to take out more items that i have in stock. If im trying to take out more that i have No is placed into the Cell.
    The problem that im having using this is. I want to keep the yes or no value that is placed into that cell even after the amounts are changed in "sheet1" so that prity much says that i cant use the formular and have to use VBa.
    Also have a condtional format that will highlight a row if cell E6 is no and date is between now and 10 days ago.
    [VBA]=AND($E6="No",TODAY()<$D6+10)[/VBA]
    This just shows that that item needs to go on a backorder asap.

    The reason that i want to keep the original yes or no and that cell to not change after updating data on "sheet1" is i can tell how many times a item had to go in backorder in a timeperiodl.

    I can upload a example workbook. There is alot of other interaction with these two sheets that may or maynot be problematic, so if you are intrested in looking at the original workbook shoot me a pm and i will email it.
    If what i havce wrote doesnt make sence. let me know and ill try to explain again.

    Thankyou.

  2. #2
    Moderator VBAX Guru Simon Lloyd's Avatar
    Joined
    Sep 2005
    Location
    UK
    Posts
    3,003
    Location
    Im not sure what you are after, or why you would want the value to remain static as thats the whole point of a formula to show different results, however if you want the cell to remain "No" when it finally reaches no then right click the sheet tab you are working with and paste this:[vba]Private Sub Worksheet_Change(ByVal Target As Range)
    If Not Intersect(Target, Range("A1:A100")) Is Nothing Then
    If Target.Value="No" Then
    Target=Target.value
    End If
    End If
    End Sub
    [/vba]
    EDIT: Dont forget to change the range that you are working with!
    Regards,
    Simon
    Please read this before cross posting!
    In the unlikely event you didn't get your answer here try Microsoft Office Discussion @ The Code Cage
    If I have seen further it is by standing on the shoulders of giants.
    Isaac Newton, Letter to Robert Hooke, February 5, 1675 English mathematician & physicist (1642 - 1727)

  3. #3
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    [vba]

    Private Sub Worksheet_Change(ByVal Target As Range)
    Const WS_RANGE As String = "C:C" '<== change to suit

    On Error GoTo ws_exit
    Application.EnableEvents = False

    If Not Intersect(Target, Me.Range(WS_RANGE)) Is Nothing Then

    With Target

    If .Value = "" Then

    .Offset(0, 2).Value = ""
    ElseIf .Value <= Application.SumIf(Worksheets("Sheet1").Columns("A"), .Offset(0, -2).Value, Worksheets("Sheet1").Columns("D")) Then

    .Offset(0, 2).Value = "Yes"
    Else

    .Offset(0, 2).Value = "No"
    End If
    End With
    End If

    ws_exit:
    Application.EnableEvents = True
    End Sub
    [/vba]

    This is worksheet event code, which means that it needs to be
    placed in the appropriate worksheet code module, not a standard
    code module. To do this, right-click on the sheet tab, select
    the View Code option from the menu, and paste the code in.
    ____________________________________________
    Nihil simul inventum est et perfectum

    Abusus non tollit usum

    Last night I dreamed of a small consolation enjoyed only by the blind: Nobody knows the trouble I've not seen!
    James Thurber

  4. #4
    Moderator VBAX Guru Simon Lloyd's Avatar
    Joined
    Sep 2005
    Location
    UK
    Posts
    3,003
    Location
    Lol, Bob, i guess you must have looked at the attachment, i didn't have time this morning!
    Regards,
    Simon
    Please read this before cross posting!
    In the unlikely event you didn't get your answer here try Microsoft Office Discussion @ The Code Cage
    If I have seen further it is by standing on the shoulders of giants.
    Isaac Newton, Letter to Robert Hooke, February 5, 1675 English mathematician & physicist (1642 - 1727)

  5. #5
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    I don't work on a Saturday!
    ____________________________________________
    Nihil simul inventum est et perfectum

    Abusus non tollit usum

    Last night I dreamed of a small consolation enjoyed only by the blind: Nobody knows the trouble I've not seen!
    James Thurber

  6. #6
    Thankyou both for the help.

    I done a little work on the file last night and think im going to change the whole approach to this.
    Ill try both approaches and see what i like the best.
    ill update soon
    If anyone want to work on sunday there is a issue about this project the has bugged me since day one. its not a easy fix and needs the orignal file, so if anyone wants to jump onboard and take a look let me know.

    if i explain it now everyone will jump overboard & close the thread.

    thanks again

  7. #7
    Moderator VBAX Guru Simon Lloyd's Avatar
    Joined
    Sep 2005
    Location
    UK
    Posts
    3,003
    Location
    Quote Originally Posted by D_Rennie
    Thankyou both for the help.

    I done a little work on the file last night and think im going to change the whole approach to this.
    Ill try both approaches and see what i like the best.
    ill update soon
    If anyone want to work on sunday there is a issue about this project the has bugged me since day one. its not a easy fix and needs the orignal file, so if anyone wants to jump onboard and take a look let me know.

    if i explain it now everyone will jump overboard & close the thread.

    thanks again
    Nothing ventured nothing gained!, anyway for a seperate issue please start a new thread.

    You should go with xld's code as he has taken the time to look at your example and provide a tailored answer
    Regards,
    Simon
    Please read this before cross posting!
    In the unlikely event you didn't get your answer here try Microsoft Office Discussion @ The Code Cage
    If I have seen further it is by standing on the shoulders of giants.
    Isaac Newton, Letter to Robert Hooke, February 5, 1675 English mathematician & physicist (1642 - 1727)

  8. #8
    VBAX Expert
    Joined
    Feb 2005
    Location
    Nanaimo, British Columbia, Cananda
    Posts
    568
    Location
    Well I work some Sunday's...Post the file or pm me about the new thread and I'll look at it
    Cheers,

    dr

    "Questions, help and advice for free, small projects by donation. large projects by quote"

    http:\\www.ExcelVBA.joellerabu.com

Posting Permissions

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