Consulting

Results 1 to 7 of 7

Thread: VBA VLOOKUP ON Historic trades

  1. #1
    Banned VBAX Contributor
    Joined
    Aug 2017
    Posts
    144
    Location

    VBA VLOOKUP ON Historic trades

    Hi Team,

    I have workbook (1) which has trade id in different sheets in column A. and

    I have set of historic trade id in workbook 2 sheet1 Colulmn (A) .

    In office my daily activity is to find out how many new trades processed and historic trades Processed.

    So I apply a Vlookup in workbook 1 sheets, in column B, if the vlookup result shows N/A Then those are New trades.

    else historic trades.
    Below code is working for me and its currently giving me the result Either N/A , exact match.


    Please suggest me the extra syntax , for N/A Result it should display "New Trades" & For exact match " Historic Trades"


    Also suggest any suggestion in my below code. Thanks.

    Option Explicit
    
    Sub Deferentiate_Historic_and_NewTrades()
    Dim wbk1 As Workbook
    Dim wbk2 As Workbook
    Dim MyData As Range
    Dim lr As Long
    Dim ws As Worksheet
    
    Set wbk1 = Workbooks.Open(Sheet1.Range("B5").Value) 'E:\MIS\STVB004\Todays Report\Daily report August 15.xlsx
    Set wbk2 = Workbooks.Open("F:\Mallesh\Historic trades data file\Historic trades.xlsx")
    
    wbk2.Sheets("Sheet1").Range("A1:A25000").Name = "MyData"
    Set MyData = ThisWorkbook.Sheets("Sheet1").Range("A1:A25000")
    
    Application.ScreenUpdating False
    
    For Each ws In wbk1.Worksheets
      
        Select Case ws.Name
            Case "Sheet1", "Sheet2", "Sheet4", "Sheet6"
            ws.Range("B1").EntireColumn.Insert
    
            ws.Range("B1").Value = "Historic/New"
                lr = ws.Cells(Rows.Count, "A").End(xlUp).Row
                ws.Range("B2:B" & lr).Formula = "=VLOOKUP(A2,'[" & wbk2.Name & "]sheet1'!$A$1:$A$10000,1,false)"
        End Select
    Next ws
    Application.ScreenUpdating True
    
    End Sub
    Last edited by Paul_Hossler; 08-20-2017 at 08:20 AM. Reason: Added CODE Tags - please use the [#] icon

  2. #2
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Not sure, but I think this will work
    Formula = "=IF ISERROR(VLOOKUP(A2,'[" & wbk2.Name & "]sheet1'!$A$1:$A$10000,1,false),"New","Historic"")
    Watch those Quotes, I am easily confused
    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
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Quote Originally Posted by SamT View Post
    Not sure, but I think this will work
    Formula = "=IF ISERROR(VLOOKUP(A2,'[" & wbk2.Name & "]sheet1'!$A$1:$A$10000,1,false),"New","Historic"")
    Watch those Quotes, I am easily confused
    You mean

    .Formula = "=IF(ISERROR(VLOOKUP(A2,'[" & wbk2.Name & "]Sheet1'!$A$1:$A$10000,1,False)),""New"",""Historic"")"
    ____________________________________________
    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
    Banned VBAX Contributor
    Joined
    Aug 2017
    Posts
    144
    Location
    Hello Sir,

    Your code worked successfully, I am too glad now , Thanks both of you for your precious time on my question !!!

    Regards,
    Mallesh

  5. #5
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    xld, That was for you to know and OP to figger out.
    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

  6. #6
    Banned VBAX Contributor
    Joined
    Aug 2017
    Posts
    144
    Location
    Hi Team,

    ws.Range("B2:B" & lr).Formula = .Formula = "=IF(ISERROR(VLOOKUP(A2,'[" & wbk2.Name & "]Sheet1'!$A$1:$A$10000,1,False)),""New"",""Historic"")"

    The above formula works for me, however when I checked the result I see the formula also, what line I need to add in looping so that only values gest pasted.

    Thanks in advance !!!


    Regards,
    Mallesh

  7. #7
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    If you only want Values, why are you using a Formula?
    ws.Range("B2:B" & lr).Formula= ...........
    ws.Calculate
    ws.Range("B2:B" & lr).Copy
    ws.Range("B2:B" & lr).PasteSpecial xlPasteValues
    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
  •