Page 2 of 2 FirstFirst 12
Results 11 to 18 of 18

Thread: VBA Macro which create new lines by codes

  1. #11
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Alls well that ends well..

    There are no rules about how / when you reply to any help you get.
    From the side of us helpers, here at excelfox.com, it’s good to know that you have seen the reply. Even if you don’t have time to test anything you get too quickly, you can always give a short reply saying thanks.
    If you are able to give feedback about if it works then even better.

    It’s all voluntary.

    Important for you to note if you are new to forums: There is also a lot of forums. They are all a bit different.
    Places like mrexcel.com and excelforum.com have lots more traffic and you will get a lot more quicker answers there, and they can also be less personal because there are also “Excel addicts” there that rush in giving as many short answers in a day that they can. Sometimes the answers are useful, sometimes not, and all variations in between. Often you'll get the same answer a few times as the "addicts" rarely take the time to read the whole Thread, sometimes not even reading anything other than the Thread title, or first post at the most.!! Some of them are only intersted in getting their post count and merit stars or whatever up. But you can get lucky. Some of the best experts are there. The Moderators are mostly all totally insane. Try to avoid them!

    This place is smaller, and it will take longer typically to get a response. But the answers may be a bit more thorough here. We are slightly more Human, and are less interested in short answer and questions.

    stackoverflow.com is a forum specialising in very short quick questions and answers. You will get penalised and shat on if you try to be human and say Hello or Thank you there!!!

    Take your pick, the world is thankfully full of lots of different colors and creeds.

    Alan




    P.S. Out of interest. – Have you been getting regular Email notifications of replies to this Thread? I only ask because they seem not to be working for some people. So I am just trying to see how bad it is, or whether just some people are affected
    According to your profile, you are in Automatic Thread Subscription Mode - Instant email notification
    So you should get instant notification.
    I should too. But since a month it stopped working for me…..
    Last edited by DocAElstein; 05-07-2021 at 07:29 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  2. #12
    Junior Member
    Join Date
    Apr 2021
    Posts
    6
    Rep Power
    0
    Oh, that's a really useful piece of advice. Thank you for the info!

    As for the notifications, I failed to sort them properly and about 2 weeks later I found excelfox's e-mails in spam box. So, that was my mistake, but the notifications themselves have been working just the way they are to.

  3. #13
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Thx for the info about your EMail notifications

    Good luck
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  4. #14
    Member p45cal's Avatar
    Join Date
    Oct 2013
    Posts
    94
    Rep Power
    11
    Alan, no I'm not getting notifications of responses…

    This one tries to preserve the leading zeroes (even if there are more than one) being guided by the length of the string directly before the hyphen:
    Code:
    Sub blah()
    Dim Results(), Destn As Range, rngSce As Range, Sce, j, Count, SceRw, a, itm, b, Padding, i, Cde, k
    Set Destn = Sheets("New").Range("A1")    'top left cell of where the results will go.
    Set rngSce = Sheets("Old").Range("A1").CurrentRegion
    Sce = rngSce.Value
    For j = 1 To 2    '2 loops, first time to get a count of rows needed, second time to populate array
      Count = 1
      For SceRw = 2 To UBound(Sce)
        a = Split(Application.Trim(Sce(SceRw, 3)), ";")
        For Each itm In a
          b = Split(Application.Trim(itm), "-")
          If UBound(b) > 0 Then 'there's a hyphen:
            Padding = Len(Application.Trim(b(0)))
            For i = CLng(b(0)) To CLng(b(1))
              Count = Count + 1
              If j > 1 Then
                Cde = Format(i, Application.Rept(0, Padding))
                For k = 1 To UBound(Sce, 2)
                  Results(Count, k) = Sce(SceRw, k)
                Next k
                Results(Count, 3) = Cde
              End If
            Next i
          Else 'there's no hyphen:
            Count = Count + 1
            If j > 1 Then
              Cde = Application.Trim(b(0))
              For k = 1 To UBound(Sce, 2)
                Results(Count, k) = Sce(SceRw, k)
              Next k
              Results(Count, 3) = Cde
            End If
          End If
        Next itm
      Next SceRw
      If j = 1 Then    'create new array
        ReDim Results(1 To Count, 1 To UBound(Sce, 2))
        For k = 1 To UBound(Sce, 2)    'populate top row of headers:
          Results(1, k) = Sce(1, k)
        Next k
      End If
    Next j
    Destn.Resize(UBound(Results)).Offset(, 2).NumberFormat = "@"    'format 3rd column as Text
    Destn.Resize(UBound(Results), UBound(Results, 2)).Value = Results
    End Sub
    Attached Files Attached Files

  5. #15
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Quote Originally Posted by p45cal View Post
    Alan, no I'm not getting notifications of responses…
    Thx. Assuming your Settings, General Settings
    General Settings.jpg

    are the same default as mine, Instantly, using Email
    Instantly, using EMail.JPG


    then you should get Notifications.


    If that’s the case , then the problem is , as usual, a bit erratic and inconsistent.
    Alex, for one, seems to be getting notifications as he should. You and me aren't.

    It might sort itself out. If not, I will try to look at this later, or talk to the current owner about it. ( I don’t want to trouble him just now, with the bad Corona situation in India.. )
    Last edited by DocAElstein; 05-09-2021 at 07:28 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  6. #16
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Another Macro variation , - in a series of about a thousand different ways to do the same thing in VBA….

    I have done a minor modification to my original macro offering here: https://excelfox.com/forum/showthrea...ll=1#post15550
    It has a modification to overcome the problem of there are some codes that start with 0, for example, '060-062'.
    I have replaced the solution of Alex’s “….'If...Then...Else Statement' so that the macro would add '0' at the beginning of some codes if there was one initially……”
    Instead of using that idea of Alex, I am using the idea that P45cal has used to …. …..the leading zeroes (even if there are more than one) being guided by the length of the string before the -…..

    I had thoughts of doing something like that myself originally, but I was not quite sure how to do it.
    ( In particular I was not quite sure how this thing works..
    Format(__ , ___ )
    I also did not know we have a Application.Rept( __ , ___) thing available
    ( ' Rept: https://docs.microsoft.com/de-de/off...tfunction.rept ) )
    So I have learnt about those things thanks to P45cal's extra solution.

    Just for further reference, Here is what’s going on there: ( P45cal's way of doing it, which I have copied into my latest version, Sub AlexAlanPascal() )
    We use the first number in a set like 061-069 , so in that example 061, to determine the “length” of digits, which we put in variable Padding.
    It will be 3 in that case:
    Padding = Len(StrtN)
    Padding = Len("061") = 3 ' "061" is character Length of three

    Then, when we add the numbers to the string in the loop , we do it slightly differently to how I originally did it.
    Instead of this line
    = NRngMod & Cnt & "; "
    For the example considered, we will have had:-
    = NRngMod & 61 & "; "

    I have now this modified line
    NRngMod & Format(Cnt, Application.Rept(0, Padding)) & "; "
    For the same example here we will have:-
    NRngMod & Format(61, Application.Rept(0, 3)) & "; " ' Rept: https://docs.microsoft.com/de-de/off...tfunction.rept
    =NRngMod & Format(61, 000) & "; "
    =NRngMod & "061" & "; "
    ( actually, the last bit might be NRngMod & 061 & "; "
    I am not quite sure exactly what is returned by Format(61, 000) , but that's less important to the overal idea )
    _._________________

    One small extra point of interest , which demonstrates how VBA is often kind to us and takes what looks like a number to be a number.. In some ways it shows that the disadvantage we experienced in Excel taking a text as number, can , actually, in other situations be a useful feature.
    In my experience, at least in VBA, the advantages of this feature outweigh the disadvantages. But its not a clear cut thing. For me it’s a ratio of about 20%:80% in terms of Disadvantage:Advantage.
    Other people may come to other conclusions, depending on their actual applications.
    I use and rely on this feature a lot, because I like to use string manipulation and often like to keep numbers held as strings. For example using strings for numbers often avoids Excel’s annoying unpredictable changing of a number's format. In general, a string is taken by VBA as a string: What you give it = what you see = what you get. But, the useful thing I find is that I can use those strings in formulas and functions in VBA , and VBA will usually take them as the number they look like. We sometimes say VBA will “coerce it into a number if it can

    Example : In my coding, in the above example, I loop from
    StrtN To StpN
    Which comes out in the example as
    "061" To "069"
    In some programming languages that would crap out and error, due to something like a Type mismatch because we are putting texts where numbers are expected. But in VBA it conveniently decides its doing this
    61 To 69
    There will be no error, and I can continue to use those string variables in string manipulations and/ or most VBA mathamatical formulas and functions.
    Using P45cal's way of doing it , for example, I am able to get the correct length of characters in order to maintain the format.
    Padding = Len(StrtN)
    Padding = Len("061") = 3 ' "061" is character Length of three

    If I had been using number variables for things like StrtN , then that idea likely would not work in my macro, since VBA may have changd the format, removing any leading zeros...


    Alan
    Attached Files Attached Files
    Last edited by DocAElstein; 05-11-2021 at 12:03 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  7. #17
    Member p45cal's Avatar
    Join Date
    Oct 2013
    Posts
    94
    Rep Power
    11
    Alan,
    Quote Originally Posted by DocAElstein View Post
    then you should get Notifications.
    I confirm that those are, and have been, my settings

  8. #18
    Senior Member
    Join Date
    Jun 2012
    Posts
    337
    Rep Power
    12
    I'd use:

    Code:
    Sub M_snb()
       sn = Sheet1.Cells(1).CurrentRegion
       
       c01 = "1"
       For j = 2 To UBound(sn)
           sn(j, 3) = Replace(sn(j, 3), ",", ";")
           For Each it In Filter(Split(sn(j, 3), ";"), "-")
             sn(j, 3) = Replace(sn(j, 3), it, " " & Join(Evaluate("transpose(row(" & Split(it, "-")(0) & ":" & Split(it, "-")(1) & "))"), "; "))
           Next
           
           c01 = c01 & Replace(Space(UBound(Split(sn(j, 3), ";")) + 1), " ", "," & j)
           c02 = c02 & ";" & sn(j, 3)
       Next
       sp = Application.Transpose(Split(c01, ","))
       st = Split(c02, ";")
       
       sp = Application.Index(sn, sp, [transpose(row(1:8))])
       
       For j = 1 To UBound(st)
          sp(j + 1, 3) = st(j)
          sp(j + 1, 5) = CDate(sp(j + 1, 5))
       Next
       
       Cells(10, 1).Resize(UBound(sp), UBound(sp, 2)) = sp
    End Sub

Similar Threads

  1. Replies: 14
    Last Post: 09-07-2016, 01:24 AM
  2. Replies: 9
    Last Post: 08-05-2013, 11:28 PM
  3. Replies: 0
    Last Post: 07-24-2013, 11:20 PM
  4. Replies: 3
    Last Post: 06-01-2013, 11:31 AM
  5. VBA editor auto-deletes spaces at the ends of lines
    By LalitPandey87 in forum Excel Help
    Replies: 0
    Last Post: 06-26-2012, 07:53 PM

Posting Permissions

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