Consulting

Results 1 to 6 of 6

Thread: VBA to remove a comma if it's the cells first characters

  1. #1
    VBAX Tutor
    Joined
    Jan 2005
    Location
    Greenville, SC
    Posts
    220
    Location

    VBA to remove a comma if it's the cells first characters

    I need a looping code that will remove a comma at the beginning of a cell all the way down column T

    Something like this:
    ,aurtd
    ,breed ,sdvs ,dvsv
    ,aolikj ,zdv ,zdc
    adca ,dddv ,dvvgg
    bgfd ,tgd ,dfge
    , adfs ,rks ,tyyo

    Would become this:
    aurtd
    breed ,sdvs ,dvsv
    aolikj ,zdv ,zdc
    adca ,dddv ,dvvgg
    bgfd ,tgd ,dfge
    adfs ,rks ,tyyo



    Thank You in advance!
    Michael

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

    Public Sub ProcessData()
    Dim Lastrow As Long
    Dim i As Long

    Application.ScreenUpdating = False

    With ActiveSheet

    Lastrow = .Cells(.Rows.Count, "A").End(xlUp).Row
    For i = 1 To Lastrow

    Do

    If Left$(.Cells(i, "A").Value2, 1) = "," Then

    .Cells(i, "A").Value2 = Right$(.Cells(i, "A").Value2, Len(.Cells(i, "A").Value2) - 1)
    End If
    Loop While Left$(.Cells(i, "A").Value2, 1) = ","

    .Cells(i, "A").Value2 = LTrim(.Cells(i, "A").Value2)
    Next i
    End With

    Application.ScreenUpdating = True
    End Sub
    [/vba]
    ____________________________________________
    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

  3. #3
    VBAX Tutor
    Joined
    Jan 2005
    Location
    Greenville, SC
    Posts
    220
    Location
    xld,
    It seems you are always the one to help me!
    I appreciate this greatly.
    That worked perfect, same as the last macro you helped with.

    OK,
    How about this. I am finding that I need to put a space after each comma within the cells but if it has a space, then ignore it.
    Like this:
    aurtd
    breed,sdvs,dvsv
    aolikj,zdv, zdc
    adca,dddv,dvvgg
    bgfd,tgd,dfge
    adfs, rks,tyyo
    To this:
    aurtd
    breed, sdvs, dvsv
    aolikj, zdv , zdc
    adca, dddv, dvvgg
    bgfd, tgd, dfge
    adfs , rks, tyyo

    Is this possible?

    Michael

  4. #4
    VBAX Tutor
    Joined
    Jan 2005
    Location
    Greenville, SC
    Posts
    220
    Location
    xld,
    Nevermind, I can use find and replace to do this. I know it is not VBA , but I can do that one thing this time.

    Thank You again,
    Michael

  5. #5
    VBAX Expert shrivallabha's Avatar
    Joined
    Jan 2010
    Location
    Mumbai
    Posts
    750
    Location
    I tried a variation. Here it is:
    [VBA]Sub SplitData()
    Dim vData As Variant
    Dim sData As String
    Dim lLastRow As Long
    lLastRow = Range("A" & Rows.Count).End(xlUp).Row
    For i = 1 To lLastRow
    vData = Split(Range("A" & i).Value, ",")
    sData = ""
    For j = LBound(vData) To UBound(vData)
    If vData(j) <> vbNullString Then
    If j <> UBound(vData) Then
    sData = sData & Trim(vData(j)) & ", "
    Else
    sData = sData & Trim(vData(j))
    End If
    End If
    Next j
    Range("A" & i).Value = sData
    Next i
    End Sub
    [/VBA]
    Regards,
    --------------------------------------------------------------------------------------------------------
    Shrivallabha
    --------------------------------------------------------------------------------------------------------
    Using Excel 2016 in Home / 2010 in Office
    --------------------------------------------------------------------------------------------------------

  6. #6
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    I thoought I had replied with the VBA to do that last step, but it isn't here so I will post it anyway

    [vba]

    Public Sub ProcessData()
    Dim Lastrow As Long
    Dim i As Long

    Application.ScreenUpdating = False

    With ActiveSheet

    Lastrow = .Cells(.Rows.Count, "A").End(xlUp).Row
    For i = 1 To Lastrow

    Do

    If Left$(.Cells(i, "A").Value2, 1) = "," Then

    .Cells(i, "A").Value2 = Right$(.Cells(i, "A").Value2, Len(.Cells(i, "A").Value2) - 1)
    End If
    Loop While Left$(.Cells(i, "A").Value2, 1) = ","

    .Cells(i, "A").Value2 = LTrim(Replace(.Cells(i, "A").Value2, ",", ", "))
    Next i
    End With

    Application.ScreenUpdating = True
    End Sub [/vba]
    ____________________________________________
    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

Posting Permissions

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