Page 1 of 3 123 LastLast
Results 1 to 10 of 27

Thread: "What’s in a String"- VBA break down Loop through character contents of a string

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

    "What’s in a String"- VBA break down Loop through character contents of a string

    "What's in a String"- VBA break down Loop through character contents of a string

    __Hello (or _ vbTab & "He" & "l" & "l" & "o" & vbCr & vbLf _ )
    The initial three posts, post #1 , post #2 and post # 3 , will take some time to read through as in these posts the technical background is explained in as much detail as possible. If you already are at a good competent level of VBA , and/or want to get simply to a way to "see" what is in a string of text" , you may wish to start at post #4

    In VBA coding and probably a lot of things to do with computers what is "actually" there is a long string of "characters" . These "characters" can be what we may recognise as every day characters, like H e l l o , as well as other things which technically still go be the name of characters. Some times these other characters may be referred to as hidden characters. In this usage of the word, hidden is not really an official term, but more of an everyday term used to mean some characters in the string that in many systems which we use to "view" strings, those characters are not obvious to see to us Humans

    Check what ya got in ya string
    I have found it can be interesting, informing and occasionally essential, to know what I have in a string. This can be done very easily in VBA with a simple loop. In the simplest form you need to use just two simple VBA functions , one, Len , to initially get the character length so that you know how many times to loop. In the Loop you use a second function, Mid , to get at each character as you loop.

    In most practical situations you will have to get the string that you want to actually look at by some means that may not be straight forward. Exactly how you do that may vary from time to time, so it is usually convenient to write a routine which will work on some string which you present it. That routine will be a Sub routine which is written to take in a string, or string variable with a string in it.

    So as example we will make a routine with first (signature) line of, say
    Sub LoopThroughString(ByVal MyString As String)
    So we have a routine like
    Code:
    Sub LoopThroughString(ByVal MyString As String)
     
     
     
    End Sub
    The first ( signature ) line means that that routine will work from within another routine as a sort of a method, which when you Call it in to use, will need to be given some string value at MyString. You are allowed to pass it a variable containing a string variable as well, if you prefer: The signature line specifies that it will take the Value of that. Within the sub routine, you refer to the passed value via MyString

    For the purposes of this demo we will first need to have a simple routine that Calls that main routine, Sub LoopThroughString( ByVal MyString [color=Blue]As String[/color] )
    Lets call that Calling sub routine, Sub MyTestString()
    It is that simple routine that we will run in our demos. You have to do it like this, because you cannot easily run a code such as Sub LoopThroughString( ByVal MyString [color=Blue]As String[/color] ) directly. VBA syntax simply does not allow you to do that easily. The simplest way to get it to run is to Call it from a simple routine which must at the Call line pass the string that I want to look at.
    Either of the 8 Calling lines in the next routine are syntaxly satisfactory . So running the routine Sub MyTestString() will result in the routine Sub LoopThroughString( ByVal MyString [color=Blue]As String[/color] ) running 8 times: You will get the pop up message box 8 times :
    StringInfoMsgBox.JPG : https://imgur.com/cWG7z5s
    WotChaGotSimpleMsgBox.jpg
    Code:
    Sub MyTestString()
     Call LoopThroughString(MyString:="Hello")
     LoopThroughString MyString:="Hello"
     Call LoopThroughString("Hello")
     LoopThroughString "Hello"
    ' In the practice we would likely have our string obtained from some method and would have it held in some string variable
    Dim varForMyString As String
     Let varForMyString = "Hello"
     Call LoopThroughString(MyString:=varForMyString)
     LoopThroughString MyString:=varForMyString
     Call LoopThroughString(varForMyString)
     LoopThroughString varForMyString
    End Sub
    Sub LoopThroughString(ByVal MyString As String)
     MsgBox prompt:="You did pass" & vbCr & vbLf & "  the following string: " & vbCr & vbLf & vbTab & """" & MyString & """", Buttons:=vbInformation, Title:="Info about the string you gave me"
    End Sub
    I personally prefer the syntax form which helps remind me what is going on, and so I would reduce the demo coding to Call the main routine, Sub LoopThroughString( ByVal MyString [color=Blue]As String[/color] ) , just once and supply it the string under investigation within a variable:
    Code:
    Sub MyTestString()
    ' In the practice we would likely have our string obtained from some method and would have it held in some string variable
    Dim varForMyString As String
     Let varForMyString = "Hello"
     Call LoopThroughString(MyString:=varForMyString)
    End Sub
     
    Sub LoopThroughString(ByVal MyString As String)
     MsgBox prompt:="You did pass" & vbCr & vbLf & "  the following string: " & vbCr & vbLf & vbTab & """" & MyString & """", Buttons:=vbInformation, Title:="Info about the string you gave me"
    End Sub
    In that coding the various & vbCr & vbLf & vbTab & """" stuff is just to pretty up the format a bit and to make us aware of some of the most common hidden characters.
    This shortened version might be more familiar to a complete beginner:
    Code:
    Sub MyTestString()
    Dim varForMyString As String
     Let varForMyString = "Hello"
     LoopThroughString varForMyString
    End Sub
     
    Sub LoopThroughString(ByVal MyString As String)
     MsgBox MyString
    End Sub
    vbTab vbCr vbLf """"
    I have not mentioned it yet, it may have been obvious, but just in case not.. The first three things there are the most common used "hidden characters" and so are really worth with getting familiar with if you are interested in looking at contents of a string. Also the way we handle quotes in a string is very awkward leading often to problems, so it is really worth getting a feel for that at an early stage.
    vbCr vbLf
    These come about the early days of computing. Back then strings and other things in strings passing around computers and the early days of the internet tended to find there way fed into a mechanical printer of mechanical typewriter which had paper fed into it.
    Cr means something along the lines of carriage return which in turn means go back to the start. Usually this start means the left side of a piece of paper . You would need to do that if you are typing out along a piece of paper as eventually you would get to the other side of the paper. Almost always when you did a Cr you would need to move the piece of paper by a bit more than the height of a line so that the next printing did not go on top of thee last line printed. Typically the word "LlineFeed" was used for this process of shifting the paper, hence the Lf abbreviation
    So those "hidden characters" would have been recognised by an old printer as telling it to move to a new line and go back to the start side of the paper before printing further. As coding and screens and word processing developed, those two hidden characters were the natural things to keep using to indicate a new line on what ever media we "look at" computer stuff. There are two characters there. Often in coding you can use something like vbCrLf instead. But that is still "seen" as 2 characters by most computer things: it will almost always be measured to have a Length of 2. Some computer systems will recognise it as vbCrLf. Others will "see" it as vbCr & vbLf
    vbTab
    This can be a bit inconsistent. Or rather, the results it gives can be very dependant on various computer settings, so that can make it tricky to use effectively. The simplest explanation is a space. More specifically it can be use to define a specific place where something may begin. In some situations an argument version is available vbTab( ) to define specifically "where something may be". Exactly how it works can be a bit variable.

    Important uses of vbTab vbCr vbLf
    In computing generally the use of vbCr & vbLf will signalise to a display window or text file or similar to separate a string into lines. For modern uses there often is not the requirement to have the two and it would appear that in most cases either of these 3 will result in a new line being displayed.
    vbCr & vbLf
    vbCr
    vbLf

    In some situations Excel will use vbCr & vbLf to separate rows. It appears that within a cell it usually just uses vbLf
    In some situations Excel will use the vbTab to separate the text in a line of cells: In other words it can be thought of as replacing the vertical "wall" between cells
    These uses of vbTab vbCr vbLf allow for some interesting alternative ways to manipulate ranges.
    ref to be added later shfkjashfkjhhkhkjfhkjashfkjhkjhkjsahhfkjashfkjh
    Last edited by DocAElstein; 02-27-2019 at 06:40 PM.

  2. #2
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10

    "What’s in a String"- VBA break down Loop through character contents of a string

    spare post for later extension ... possibly
    Attached Images Attached Images
    Last edited by DocAElstein; 04-16-2021 at 04:15 PM.

  3. #3
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Quotes in VBA


    """" : "Producing a Single quote"
    Quotes in VBA can be very tricky. Often in code lines within VBA we see a complicated mess of multiple quotes. Often they are there in order to "produce" a single quote.
    There does not seem to be any clear documentation on this theme. I have a theory that helps me get both a feeling of understanding and usually helps me get the correct combination of multiple quotes.
    A Theory
    In Excel generally a pair of "enclosing" quotes is required to indicate something that will be ignored at the compile stage and will be "read" at run time. This will be text required which can itself be the requirement, that is to say plain text to be put or read somewhere. It can get a further level complicated when we wish to deal with the quotes to be applied to a spreadsheet via VBA






    https://excelribbon.tips.net/T003917...s_Numbers.html


    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=Ugw3nF0C04AGt73H1BB4AaABAg.9h6VhNCM-DZ9h7EqbG23kg
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwGTEyefOX7msIh1wZ4AaABAg.9h4sd6Vs4qE9h7KvJXmK 8o
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=Ugw3nF0C04AGt73H1BB4AaABAg.9h6VhNCM-DZ9h7E1gwg4Aq
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgywFtBEpkHDuK55r214AaABAg
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwviLabd7r_3KpP6wh4AaABAg.9h5lFRmix1R9h79hNGvJ bu
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwviLabd7r_3KpP6wh4AaABAg.9h5lFRmix1R9h79YAfa2 4T
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwviLabd7r_3KpP6wh4AaABAg.9h5lFRmix1R9h79M1SYH 1E
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwviLabd7r_3KpP6wh4AaABAg.9h5lFRmix1R9h78SxhXT nR
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwviLabd7r_3KpP6wh4AaABAg.9h5lFRmix1R9h78GftO_ iE
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgyG714V_k7odQMrTz14AaABAg.9h740K6COOA9h77HSGDH 4A
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgyG714V_k7odQMrTz14AaABAg.9h740K6COOA9h76fafzc EJ
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgyG714V_k7odQMrTz14AaABAg.9h740K6COOA9h759YIjl aG
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgyG714V_k7odQMrTz14AaABAg.9h740K6COOA9h74pjGcb Eq
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgyG714V_k7odQMrTz14AaABAg
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgzJJUDVv2Mb6YGkPYh4AaABAg.9h5uPRbWIZl9h7165DZd jg
    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    Last edited by DocAElstein; 09-22-2023 at 05:04 PM.

  4. #4
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Last edited by DocAElstein; 09-22-2023 at 05:39 PM.

  5. #5
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10

    Quotes in VBA : Using Debug to help "see” what VBA "sees”

    Using Debug to help “see” what VBA “sees”

    One difficulty is that if you get such a code line as above wrong then VBA will simply error either at compile or run time. The following techniques will not catch a complied error, but will make it much less likely for you to produce a string which will either error at run time or give the wrong final formula
    The key to this is to look first at your constructed string in the Immediate window. (You can further tidy up the coding a bit by putting the string into a variable and looking at that).
    The reason why this is helpful is that the Immediate window displays the string as VBA “sees” it. We need to make our string look to VBA exactly as we would physically type it in to the cell. So in the Immediate Window we need to see exactly this in our example
    =A2&" "&B2&"s of"&C2
    If we have constructed our string correctly, and we supply that string to the Immediate window, then in the Immediate window should be displayed exactly that.

    Using the VBA Immediate Window
    If you are not familiar with the Immediate Window, then I would recommend this very clear Blog on it from Jon Acampora https://www.excelcampus.com/vba/vba-...-window-excel/
    You can get the Immediate Window up by Hitting the short cut key combination of Ctrl+g from the VB Editor Environment. ( The VB Editor Environment can got up from a spreadsheet using the short cut key combination of Alt+F11. If you drag the Immediate Window around then often it will reappear the next time you get it up in the same place.
    Here is the code once again, with a few extra lines and lines to display the Immediate window
    I have used the Immediate window to assist in the steps taken to simplify the code
    In the practice I would click somewhere in the code and then use key F8 to step through the code. Note also that if you hover over any occurrence of strTest when in Debug mode, then this will reveal the contents of the string shown almost the same as in the Immediate window – in this case an extra enclosing “” pair is included.
    DebugQuotesInVBA.JPG : https://imgur.com/JEjoFlQ
    DebugQuotesInVBA.jpg
    Code:
    Sub Write_in_formula_using_VBA()
    Dim WsQuotesInVBA As Worksheet: Set WsQuotesInVBA = ThisWorkbook.Worksheets("QuotesInVBA")
     WsQuotesInVBA.Range("D2").ClearContents
    ' Full formua "written" by VBA into cell
     Let WsQuotesInVBA.Range("D2").Value = "=A2" & "&" & """" & " " & """" & "&" & "B2" & "&" & """" & "s of" & """" & "&" & "C2"
    ' Use Immediate Window to check string form ( Ctrl+g from VB Editor to get Immediate Window up )
     Debug.Print "=A2" & "&" & """" & " " & """" & "&" & "B2" & "&" & """" & "s of" & """" & "&" & "C2"
    Dim strTest As String
     Let strTest = "=A2" & "&" & """" & " " & """" & "&" & "B2" & "&" & """" & "s of" & """" & "&" & "C2"
     Debug.Print strTest
     Let strTest = "=A2" & "&" & """ " & """" & "&" & "B2" & "&" & """" & "s of" & """" & "&" & "C2"
     Debug.Print strTest
     Let strTest = "=A2" & "&" & """ """ & "&" & "B2" & "&" & """" & "s of" & """" & "&" & "C2"
     Debug.Print strTest
     Let strTest = "=A2" & "&"" """ & "&" & "B2" & "&" & """" & "s of" & """" & "&" & "C2"
     Debug.Print strTest
     Let strTest = "=A2" & "&"" ""&" & "B2" & "&" & """" & "s of" & """" & "&" & "C2"
     Debug.Print strTest
     Let strTest = "=A2" & "&"" ""&" & "B2" & "&""" & "s of" & """&" & "C2"
     Debug.Print strTest
     Let strTest = "=A2" & "&"" ""&" & "B2" & "&""s of""&" & "C2"
     Debug.Print strTest
     Let strTest = "=A2&"" ""&B2&""s of""&" & "C2"
     Debug.Print strTest
     Let WsQuotesInVBA.Range("D2").Value = strTest
    End Sub
    After running the above routine, you should finally see similar lines in the Immediate window. It is worth noting that you can do a simple copy of any of those formulas and paste it directly in a cell. That manual action is basically what VBA does twice in that routine in these two line
    WsQuotesInVBA.Range("D2").Value = "=A2" & "&" & """" & " " & """" & "&" & "B2" & "&" & """" & "s of" & """" & "&" & "C2"
    WsQuotesInVBA.Range("D2").Value = strTest


    Immediate Window Output:
    ( To paste this info here, I copied it from that window ( by highlighting it then Hitting Ctrl+c : Highlight Ctrl c.JPG : https://imgur.com/A5U1muA Highlight Ctrl c.JPG , and pasted it in with Keys Ctrl+v

    =A2&" "&B2&"s of"&C2
    =A2&" "&B2&"s of"&C2
    =A2&" "&B2&"s of"&C2
    =A2&" "&B2&"s of"&C2
    =A2&" "&B2&"s of"&C2
    =A2&" "&B2&"s of"&C2
    =A2&" "&B2&"s of"&C2
    =A2&" "&B2&"s of"&C2
    =A2&" "&B2&"s of"&C2


    Formula with Two quotes in a cell via VBA”Hello”
    A good exercise in practicing Quotes in VBA is to consider trying to put
    “”
    in a cell.
    Excel works more or less as VBA does, as it is basically a sort of pre written VB coding.
    It follows the same arguments as already discussed for VBA that we need to give Excel 4 quotes to get a single quote. This will result in a single quote appearing in a cell – Try it
    =””””
    The following will give you a double quote
    =”””” & “”””
    or
    = “”””””
    Consider how to get that in VBA …
    We need the string of “=” and 4 quotes for each of those 6 quotes, thus
    "=" & """" & """" & """" & """" & """" & """"
    or simplified:
    "=” & """""""""""""""
    or
    "="""""""""""""
    14 quotes !!!
    For a single quote, we write in the cell
    =””””
    In VBA
    "=" & """" & """" & """" & """"
    or
    "=" & """"""""""
    or
    "="""""""""
    10 Quotes !!!

    If I want to use VBA to write in a simple
    “Hello”
    in a cell, I need this in VBA
    "=" & """""""""" & "&" & """" & "Hello" & """" & "&" & """"""""""
    or
    "=" & """""""""" & "&" & """Hello""" & "&" & """"""""""
    or
    "=" & """""""""&""Hello""&"""""""""
    or
    "=" & """""""Hello"""""""
    If I had not seen the explanation of this posts, I doubt that I would of believed that !!!!
    CellHelloWithQuotes.JPG : https://imgur.com/rUCaGsF
    CellHelloWithQuotes.jpg
    Code:
    Sub DoubleTestie()
    ' Double quote in a cell
     Range("D3").Value = "=" & """" & """" & """" & """" & """" & """"
     Range("D3").Value = "=" & """""""""""""" ' "=" and 14 qoutes!!!
     Range("D3").Value = "="""""""""""""
    ' single quote in a cell
     Range("D4").Value = "=" & """" & """" & """" & """"
     Range("D4").Value = "=" & """""""""" ' "=" and 10 qoutes!!!
     Range("D4").Value = "="""""""""
    ' "Hello" in a cell
     Range("D5").Value = "=" & """""""""" & "&" & """" & "Hello" & """" & "&" & """"""""""
     Range("D5").Value = "=" & """""""""" & "&" & """Hello""" & "&" & """"""""""
     Debug.Print "=" & """""""""" & "&" & """Hello""" & "&" & """"""""""
     Range("D5").Value = "=" & """""""""&""Hello""&"""""""""
     Debug.Print "=" & """""""""&""Hello""&"""""""""
    ' Because all is text in the cell we can simplify this further
     Range("D5").Value = "=" & """""""Hello"""""""
     Debug.Print "=" & """""""Hello"""""""
    End Sub
    The corresponding Immediate Window Output:

    =""""&"Hello"&""""
    =""""&"Hello"&""""
    ="""Hello"""

    _.________________________________________________ ______

    Ref
    http://www.eileenslounge.com/viewtop...248196#p248196
    http://www.eileenslounge.com/viewtop...=25298#p196259
    https://excelribbon.tips.net/T003917...s_Numbers.html (ESCAPE CHARACTER )
    Last edited by DocAElstein; 06-25-2021 at 03:56 PM.

  6. #6
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10

    Quotes in VBA : Using Debug to help "see” what VBA "sees”

    spare post for later possible extension
    Attached Images Attached Images
    Last edited by DocAElstein; 04-16-2021 at 04:16 PM.

  7. #7
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10

    "What’s in a String"- VBA break down Loop through character contents of a string

    "What’s in a String"- VBA break down Loop through character contents of a string

    Coding to Loop through character contents of a string
    Recap :
    In VBA coding and probably a lot of things to do with computers what is “actually” there is a long string of “characters” . These “characters” can be what we may recognise as every day characters, like H e l l o , as well as other things which technically still go be the name of characters. Some times these other characters may be referred to as hidden characters. In this usage of the word, hidden is not really an official term, but more of an everyday term used to mean some characters in the string that in many systems which we use to “view” strings, those characters are not obvious to see to us Humans

    Check what ya got in ya string
    I have found it can be interesting, informing and occasionally essential, to know what I have in a string. This can be done very easily in VBA with a simple loop. In the simplest form you need to use just two simple VBA functions , one, Len , to initially get the character length so that you know how many times to loop. In the Loop you use a second function, Mid , to get at each character as you loop.

    In most practical situations you will have to get the string that you want to actually look at by some means that may not be straight forward. Exactly how you do that may vary from time to time, so it is usually convenient to write a routine which will work on some string which you present it. That routine will be a Sub routine which is written to take in a string, or string variable with a string in it.

    In post #1 ( http://www.excelfox.com/forum/showth...ts-of-a-string ) , the merits of different basic procedure formats were discussed.
    In this post we will start from the coding below , with the aim to develop the second procedure to give us a clear indication of exactly what is in the string under investigation, MyString


    Code:
    Sub MyTestString()
    ' In the practice we would likely have our string obtained from some method and would have it held in some string variable
    Dim varForMyString As String
     Let varForMyString = "Hello"
     Call WtchaGot(strIn:=varForMyString)
    End Sub
    
    Sub WtchaGot(ByVal strIn As String)
     MsgBox prompt:="You did pass" & vbCr & vbLf & "  the following string: " & vbCr & vbLf & vbTab & """" & strIn & """", Buttons:=vbInformation, Title:="Info about the string you gave me"
    End Sub
    The coding , on running procedure, Sub MyTestString() currently simply gives a message.
    WotChaGotSimpleMsgBox.JPG : https://imgur.com/eYXDqSB

    String output of characters and character listing .
    Output: Long VBA code string representation
    The full un simplified long string , as discussed in the example at the start of this Thread, in the syntax that would be required to add the string via coding is both a nice visual representation when used for all characters in a string, as well as being convenient to then use in coding for further investigations. So one of the two main outputs of the full routine, Sub WtchaGot(ByVal strIn As String) , will be a form which will show characters
    _ that can be “seen” in their typical form,
    and
    _ “hidden” characters will be shown in either a form which can be used in VBA coding, which if does not have a specific VBA syntax constant will resort to the official listed ASCII ( http://www.asciitable.com/ ) number form: For example, the carriage return has the official number of 13, which can be used in VBA coding as Chr(13) , but as this character also has a VBA constant form , vbCr , this will be used in our string output.

    As example, say at the start of the following text , some “hidden” character was present

    Hi
    __”u”.


    This would be an example of the testing procedure used to test our main routine:
    Code:
    Sub TestWtchaGot()
    ' In the practice we would likely have our string obtained from some method and would have it held in some string variable
    Dim strTest As String
     Let strTest = Chr(1) & "Hi" & vbCrLf & vbTab & """u."""
     Call WtchaGot(strIn:=strTest)
    ' Call WtchaGot(Chr(1) & "Hi" & vbCrLf & vbTab & """u.""")
    End Sub
    Our long VBA syntaxly acceptable string, which our routine should give us would be of this form

    __ Chr(1) & "H" & "i" & vbCr & vbLf & vbTab & """" & "u" & "." & """"

    This will be output in a message box and also in the Immediate window, ( from the immediate window we could obtain a copy in which to paste into the VBA code pane window as part of a routine )

    Output: Character listing
    A second output will be given which will be a simple 2 column list. One column will be the “see able” version of the character, if excel manages to do that, and the other column will be its ASCII character.
    This is intended to act as a notepad type thing , and if columns are already filled, then the latest will be added to the right of any existing ones. A date is given as well as the string length, and the first part of the string for ease of identification. It would be intended that the user manually deletes columns from time to time is they are no linger needed. This would be the results after two consecutive runs for the above example
    Row\Col
    A
    B
    C
    D
    E
    1
    07 Feb 2019 Hi
    "u."
    07 Feb 2019 Hi
    "u."
    2
    1 1
    3
    H 72 H 72
    4
    i 105 i 105
    5
    13 13
    6
    10 10
    7
    9 9
    8
    " 34 " 34
    9
    u 117 u 117
    10
    . 46 . 46
    11
    " 34 " 34
    12
    13

    A convenient customization could be to add a list of all ASCII characters in the first few columns. The routine would autoamticaaly ignores thes as it will paste its results in the next free column

    Code Example
    Here is a code example: http://www.excelfox.com/forum/showth...0938#post10938
    http://www.excelfox.com/forum/showth...0939#post10939
    . A brief description:

    Rem 1 Worksheets info
    ‘1a) The routine is written to work in Excel mainly because of the convenience of the output possibilities. A worksheet is made "WotchaGotInString" if it does not already exist. Its existence is checked by If it is Not possible to refer to an arbitrary range in the worksheet "WotchaGotInString"
    An array is made
    ‘1b) An array is made for the 2 column list and the first “row filled with some information : Date , Length of string and fist part of string

    Rem 2)
    This is the main Loop is done for each character in the string, ( the length has already been determined as it was needed for “row” dimension the 2 “column” array ). At the start of each loop, the character at that position is determined by
    __ Mid(strIn, Cnt, 1) ' the character in strIn at position from the left of length 1
    ‘2a) Long VBA code string representation
    This section tries to build a string in a format both pictorially convenient and syntaxly acceptable to VBA. The string will be built up in a string variable , WotchaGot
    __ Chr(1) & "H" & "i" & vbCr & vbLf & vbTab & """" & "u" & "." & """"
    All the single characters are shown separate by " & "
    There are then three main processes in this section , ‘2a) , to determine the type of character.
    ‘2a)(i). This checks to see if the current character is one of the simple ones, like "A - Z" or like "0 - 9" or like "a - z"
    __1If this is the case Then then we simply add that to the string variable housing the characters so far, WotchaGot. 2a) is then Ended
    __Else two other main sections , ‘2a)(ii) and ‘2a)(iii) will be gone through sequentially if the character was not a simple one. All the remaining section uses a Select Case to look for some Case or other , after which if it is found , an appropriate addition is made to WotchaGot.
    ' 2a)(ii)_1 are for cases where I may wish to see a “see able” character in its normal see able form, like these ! ” § $ % & / ; : . etc….
    ' 2a)(ii)_2 is for hidden characters which VBA has a constant for , like these
    vbCr , vbLf , vTab , etc..
    At a final ' 2a)(iii) we have a Case Else which hopefully will catch anything we have not listed. This will then be added to WotchaGot in the form of its ASCII number , which we show as like Chr(3)
    At this stage we are finished with section 2a) for any particular loop

    ‘2b) Fill the two “columns” in output Array for this loop.
    The first “column” is filled with the loop number ( which corresponds to the character number counting from the left in the original string) and the actual character as a see able or hidden character. The second “column” is given its ASCII number which we can determine in VBA via the Asc-Function thus:
    __ Asc(Caracter)
    where in our case Caracter is the string variable of length 1 which we use in each loop to hold the next single character given by
    __ Caracter = Mid(strIn, Cnt, 1)

    At this point the coding has reached the last point of the Loop and the Loop restarts
    Note: we have some lines commented out of this form
    ' ___ Case " "
    ' ____ Let WotchaGot = WotchaGot & """" & " " & """" & " & "

    This is for convenience for later addition of any other specific characters that should not be left for section ' 2a)(iii) Case Else to catch
    Just after the end of the Loop section is a code line to take off a last 3 characters ___ & __ ( 2 spaces each side of a & )


    Rem 3Output
    '3a) The long string, WotchaGot , is displayed both in a message box and in the Immediate window. Note that for long strings, that viewable length of a string is limited both in the message box and to lesser extent in the Immediate window.
    '3b) Our output array, arrWotchaGot() , is a 2 dimension array of two columns, so we paste this out starting top left of the next free column in row 1 over a range resized to the size of the array.


    _.___________________________________



    Refs
    https://www.automateexcel.com/vba/loop-through-string/
    Codes from Lisa Green : http://www.eileenslounge.com/viewtop...243670#p243668
    Last edited by DocAElstein; 02-08-2019 at 11:21 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!!

  8. #8
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10

    "What’s in a String"- VBA break down Loop through character contents of a string

    spare post possibly for extending later
    Last edited by DocAElstein; 04-16-2021 at 04:17 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!!

  9. #9
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10

    VBA break down Loop through character contents of a string Code Modifications

    A simple modification can be done to link "normal" characters so that simple text can be shown together rather than every individual character. This will make it easier to look along a long text containing a lot of "normal" text, such as words and numbers

    A simple text string can be added if the current and last character was something "normal" at code section
    Code:
            If Caracter Like "[A-Z]" Or Caracter Like "[0-9]" Or Caracter Like "[a-z]" Then ' Check for normal characters
                'SirNirios
                If Not Cnt = 1 Then ' I am only intersted in next line comparing the character before, and if i did not do this the next line would error if first character was a  "normal"  character
                    If Not Cnt = myLenf And (Mid(strIn, Cnt - 1, 1) Like "[A-Z]" Or Mid(strIn, Cnt - 1, 1) Like "[0-9]" Or Mid(strIn, Cnt - 1, 1) Like "[a-z]") Then  ' And (Mid(strIn, Cnt + 1, 1) Like "[A-Z]" Or Mid(strIn, Cnt + 1, 1) Like "[0-9]" Or Mid(strIn, Cnt + 1, 1) Like "[a-z]") Then
                     Let WotchaGot = WotchaGot & "|LinkTwoNormals|"
                    Else
                    End If
                Else
                End If
            Let WotchaGot = WotchaGot & """" & Caracter & """" & " & " ' This will give the sort of output that I need to write in a code line, so for example if I have a123 , this code line will be used 4 times and give like a final string for me to copy of   "a" & "1" & "2" & "3" &      I would phsically need to write in code  like  strVar = "a" & "1" & "2" & "3"   -  i could of course also write  = "a123"   but the point of this routine is to help me pick out each individual element
            Else ' Some other things that I would like to "see" normally - not "normal simple character" - or by a VBA constant, like vbCr vbLf  vbTab
    Any text can be used, but it should be chosen to be something unlikely to occur as text in your original string, strIn
    For a test code of like this …_
    Code:
    Sub TestWtchaGot()
    ' In the practice we would likely have our string obtained from some method and would have it held in some string variable
    Dim strTest As [color=blue]String[/color
     Let strTest = Chr(1) & "High""er" & vbCrLf & vbTab & """u."""
     Call WtchaGot(strIn:=strTest)
    End Sub
    _.. the seen text in the message box or Immediate window would be
    Chr(1) & "H" & |LinkTwoNormals|"i" & |LinkTwoNormals|"g" & |LinkTwoNormals|"h" & """" & "e" & |LinkTwoNormals|"r" & vbCr & vbLf & vbTab & """" & "u" & "." & """"
    Further down in the coding, the occurrences of " & |LinkTwoNormals|" can be removed with a simple line like
    Code:
         Let WotchaGot = Replace(WotchaGot, """ & |LinkTwoNormals|""", "", 1, -1, vbBinaryCompare)
    The output will then be like
    Chr(1) & "High" & """" & "er" & vbCr & vbLf & vbTab & """" & "u" & "." & """"

    Full modified coding including Calling routine for testing in the next post
    Last edited by DocAElstein; 02-27-2019 at 06:41 PM.

  10. #10
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10

    VBA break down Loop through character contents of a string Code Modifications

    spare post possibly for later
    Last edited by DocAElstein; 04-16-2021 at 04:18 PM.

Similar Threads

  1. VBA Versions of my "Get Field" and "Get Reverse Field" formulas
    By Rick Rothstein in forum Rick Rothstein's Corner
    Replies: 4
    Last Post: 06-02-2017, 06:15 PM
  2. Get "Reversed" Field from Delimited Text String
    By Rick Rothstein in forum Rick Rothstein's Corner
    Replies: 3
    Last Post: 02-22-2015, 09:01 AM
  3. Replies: 1
    Last Post: 02-10-2015, 09:41 AM
  4. Replies: 4
    Last Post: 09-09-2013, 05:13 PM
  5. Ordinal Suffix (i.e., "st", "nd", "rd" and "th")
    By Rick Rothstein in forum Rick Rothstein's Corner
    Replies: 0
    Last Post: 03-20-2012, 03:46 AM

Posting Permissions

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