Page 1 of 2 12 LastLast
Results 1 to 10 of 11

Thread: VBA Macro To Create A New Column Of Unique Values From Another Column Of Duplicates

  1. #1
    Junior Member
    Join Date
    May 2013
    Posts
    6
    Rep Power
    0

    VBA Macro To Create A New Column Of Unique Values From Another Column Of Duplicates

    Hello,

    I would need your help on he following please.

    in tab : report- I'll choose the country.
    in tab : Extract ESr: data will be changed accordingly to the selection.

    and data will be cleaned in column T-U- V- W.

    I need kind of macro in Column w (or formula), to extract unique value from column V. Without duplicates,

    This will allow me to make a reference in Tab report to put this code into a table without duplicates.

    PS: Iforget to mentioned that i need the macro to run each time we change the selection of the country.



    Thank you for your help01-Manual Aspiration-Advance-test.xlsx

  2. #2
    Moderator
    Join Date
    Jul 2012
    Posts
    156
    Rep Power
    12
    Try this one
    Code:
    Sub NoDupes()
        Dim sq() As Variant
        With Sheets("Extract ESR")
            sn = .Range("V2:V" & .Cells(Rows.Count, 22).End(xlUp).Row)
        End With
        On Error Resume Next
        With New Collection
            For j = 1 To UBound(sn)
                .Add sn(j, 1), CStr(sn(j, 1))
            Next
            ReDim Preserve sq(.Count)
            For i = 1 To .Count
                sq(i - 1) = .Item(i)
            Next
        End With
        On Error GoTo 0
        Sheets("Extract ESR").Range("W2").Resize(UBound(sq)) = WorksheetFunction.Transpose(sq)
    End Sub

  3. #3
    Administrator Admin's Avatar
    Join Date
    Mar 2011
    Posts
    1,122
    Rep Power
    10
    Hi

    Another option,

    In Worksheet (Report) module. Right click on tab 'Report' > view code > paste the code there.

    Code:
    Option Explicit
    
    Private Sub Worksheet_Change(ByVal Target As Range)
        
        kTest
        
    End Sub
    in a standard module

    Code:
    Option Explicit
    
    Sub kTest()
        
        Dim d, k, w, x, i As Long, n As Long, Country As String
        Dim c As String, s As String, m As String
        
        Set d = CreateObject("scripting.dictionary")
        
        w = Worksheets("Extract ESR").Range("a1").CurrentRegion.Resize(, 11).Value2
        
        Country = Worksheets("Report").Range("c1")
        ReDim k(1 To UBound(w, 1), 1 To 1)
        
        For i = 2 To UBound(w, 1)
            c = Country & w(i, 4) & w(i, 11)
            If c = w(i, 1) Then
                If Not d.exists(c) Then
                    If InStr(1, m, w(i, 6)) = 0 Then
                        n = n + 1
                        k(n, 1) = w(i, 6)
                        m = m & "," & w(i, 6)
                    End If
                    d.Item(c) = w(i, 6)
                Else
                    If InStr(1, m, w(i, 6)) = 0 Then
                        n = n + 1
                        k(n, 1) = w(i, 6)
                        m = m & "," & w(i, 6)
                    End If
                End If
            End If
        Next
        If n Then
            With Worksheets("Extract ESR").Range("w2").Resize(UBound(w, 1))
                .ClearContents
                If Not .NumberFormat = "@" Then .NumberFormat = "@"
                .Value = k
            End With
        End If
        
    End Sub
    Now while you change the country, the ids will be updated automatically. You don't need those formulas in columns R,S,T,U and V.
    Cheers !

    Excel Range to BBCode Table
    Use Social Networking Tools If You Like the Answers !

    Message to Cross Posters

    @ Home - Office 2010/2013/2016 on Win 10 (64 bit); @ Work - Office 2016 on Win 10 (64 bit)

  4. #4
    Junior Member
    Join Date
    May 2013
    Posts
    6
    Rep Power
    0
    This looks perfect.

    but the problem, the macro is not running automatically.

    I need to select "run macro", each time the country change.
    And my problem is: this report will be used by others people, and for their analysis, data need to be automatically cleaned.
    Is there any way to make it automatic

  5. #5
    Junior Member
    Join Date
    May 2013
    Posts
    6
    Rep Power
    0
    No, It works

    I would like to thank you very much.

    Really it's helpful

  6. #6
    Junior Member
    Join Date
    May 2013
    Posts
    6
    Rep Power
    0
    Hello,

    I have a question: can you tell me on which column the macro refer for "region"?? because in my file Portugal & spain shoul appear under Iberia, and if i put Iberia in the selection : c1 (worksheet report). The marco stops working.
    If i need to modify the value of region, where can i do it??

    Thank you in advance for your help.

  7. #7
    Junior Member
    Join Date
    May 2013
    Posts
    6
    Rep Power
    0
    Hello,

    I'm trying to understand a little about macro.

    I tried your proposition, but i see that the macro is not running automatically. Do you have any explanation please?

    It should run every time data in column V change.

    Thank you for helping me.

  8. #8
    Administrator Excel Fox's Avatar
    Join Date
    Mar 2011
    Posts
    1,401
    Rep Power
    10
    The post by Admin is meant for the worksheet change event to be triggered, and then the kTest procedure to be run. If you want to limit the trigger to a change in column V only, you could use

    Code:
    Private Sub Worksheet_Change(ByVal Target As Range)
        
    if Not Application.Intersection(target, Me.Range("V:V")) Is Nothing Then
        kTest
    End If
        
    End Sub
    A dream is not something you see when you are asleep, but something you strive for when you are awake.

    It's usually a bad idea to say that something can't be done.

    The difference between dream and aim, is that one requires soundless sleep to see and the other requires sleepless efforts to achieve

    Join us at Facebook

  9. #9
    Junior Member
    Join Date
    May 2013
    Posts
    6
    Rep Power
    0
    Hello,

    I have a question: can you tell me on which column the macro refer for "region"?? because in my file Portugal & spain shoul appear under Iberia, and if i put Iberia in the selection : c1 (worksheet report). The marco stops working.
    If i need to modify the value of region, where can i do it??

    Thank you in advance for your help.

  10. #10
    Administrator Admin's Avatar
    Join Date
    Mar 2011
    Posts
    1,122
    Rep Power
    10
    Quote Originally Posted by ketats1 View Post
    Hello,
    ...
    I have a question: can you tell me on which column the macro refer for "region"??
    If i need to modify the value of region, where can i do it??....
    In the macro it only refers Col D and Col K which refers as w(i, 4) and w(i, 11) respectively.

    Also write the following line before kTest in the worksheet module code.

    Code:
    If Target.Address(0, 0) <> "C1" Then Exit Sub
    this restrcits the macro to fire when C1 changes.
    Cheers !

    Excel Range to BBCode Table
    Use Social Networking Tools If You Like the Answers !

    Message to Cross Posters

    @ Home - Office 2010/2013/2016 on Win 10 (64 bit); @ Work - Office 2016 on Win 10 (64 bit)

Similar Threads

  1. Replies: 17
    Last Post: 05-22-2013, 11:58 PM
  2. Replies: 6
    Last Post: 05-16-2013, 09:56 AM
  3. Replies: 3
    Last Post: 08-05-2012, 09:16 PM
  4. Macro to create files as per the contents in a column
    By Praveen Bj in forum Excel Help
    Replies: 1
    Last Post: 07-05-2012, 09:07 PM
  5. Lookup Multi-Column For Unique String Combination For Numeric Value Output
    By Excel Fox in forum Excel and VBA Tips and Tricks
    Replies: 0
    Last Post: 07-03-2011, 07:23 PM

Tags for this Thread

Posting Permissions

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