Page 2 of 3 FirstFirst 123 LastLast
Results 11 to 20 of 27

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

  1. #11
    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

    Coding for last post

    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   '                             "Pointer" to a "Blue Print" (or Form, Questionnaire not yet filled in, a template etc.)"Pigeon Hole" in Memory, sufficient in construction to house a piece of Paper with code text giving the relevant information for the particular Variable Type. VBA is sent to it when it passes it. In a Routine it may be given a particular "Value", or ("Values" for Objects). There instructions say then how to do that and handle(store) that(those). At Dim the created Paper is like a Blue Print that has some empty spaces not yet filled in. A String is a bit tricky. The Blue Print code line Paper in the Pigeon Hole will allow to note the string Length and an Initial start memory Location. This Location well have to change frequently as strings of different length are assigned. Instructions will tell how to do this. Theoretically a special value vbNullString is set to aid in quick checks.. But..http://www.mrexcel.com/forum/excel-questions/361246-vbnullstring-2.html#post44116
     Let strTest = Chr(1) & "High""er" & vbCrLf & vbTab & """u."""
     Call WtchaGot(strIn:=strTest)
    ' Call WtchaGot(Chr(1) & "Hi" & vbCrLf & vbTab & """u.""")
    End Sub
    Code:
    Sub WtchaGot(ByVal strIn As String)
    Rem 1  ' Output "sheet hardcopies"
    '1a) Worksheets     'Make a Temporary Sheet, if not already there, in Current Active Workbook, for a simple list of all characters
        If Not Evaluate("=ISREF(" & "'" & "WotchaGotInString" & "'!Z78)") Then '   ( the '  are not important here, but iin general allow for a space in the worksheet name like  "Wotcha Got In String"
        Dim Wb As Workbook '                                   ' ' Dim:  ' Preparing a "Pointer" to an Initial "Blue Print" in Memory of the Object ( Pigeon Hole with a bit of paper or code lines on that can be filled in to refer to a specific Objec of this type ) . This also us to get easily at the Methods and Properties throught the applying of a period ( .Dot) ( intellisense )                     '
         Set Wb = ActiveWorkbook '  '                            Set now (to Active Workbook - one being "looked at"), so that we carefull allways referrence this so as not to go astray through Excel Guessing inplicitly not the one we want...         Set: Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191                                '
         Wb.Worksheets.Add After:=Wb.Worksheets.Item(Worksheets.Count) 'A sheeet is added and will be Active
        Dim ws As Worksheet '
         Set ws = ActiveSheet 'Rather than rely on always going to the active sheet, we referr to it Explicitly so that we carefull allways referrence this so as not to go astray through Excel Guessing implicitly not the one we want...    Set: Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191            ' Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191
         ws.Activate: ws.Cells(1, 1).Activate ' ws.Activate and activating a cell sometimes seemed to overcome a strange error
         Let ws.Name = "WotchaGotInString"
        Else ' The worksheet is already there , so I just need to set my variable to point to it
         Set ws = ThisWorkbook.Worksheets("WotchaGotInString")
        End If
    '1b) Array
    Dim myLenf As Long: Let myLenf = Len(strIn)  '            ' Long is very simple to handle, - final memory "size" type is known (123.456 and 000.001 have same "size" computer memory ) , and so a Address suggestion can be given for the next line when the variable is filled in.  '( Long is a Big whole Number limit (-2,147,483,648 to 2,147,483,647) If you need some sort of validation the value should only be within the range of a Byte/Integer otherwise there's no point using anything but Long.--upon/after 32-bit, Integers (Short) need converted internally anyways, so a Long is actually faster. )       https://www.mrexcel.com/forum/excel-questions/803662-byte-backward-loop-4.html
    Dim arrWotchaGot() As String: ReDim arrWotchaGot(1 To myLenf + 1, 1 To 2) ' +1 for header  Array for the output 2 column list.  The type is known and the size,  but I must use this ReDim  method simply because the dim statement  Dim( , )  is complie time thing and will only take actual numbers
     Let arrWotchaGot(1, 1) = Format(Now, "DD MMM YYYY") & vbLf & "Lenf is   " & myLenf: Let arrWotchaGot(1, 2) = Left(strIn, 20)
    Rem 2  String anylaysis
    'Dim myLenf As Long: Let myLenf = Len(strIn)
    Dim Cnt As Long
        For Cnt = 1 To myLenf ' ===Main Loop========================================================================
        ' Character analysis: Get at each character
        Dim Caracter As Variant ' String is probably OK.
        Let Caracter = Mid(strIn, Cnt, 1) ' '    the character in strIn at position from the left of length 1
        '2a) The character added to a single  WotchaGot  long character string to look at and possibly use in coding
        Dim WotchaGot As String ' This will be used to make a string that I can easilly see and also is in a form that I can copy and paste in a code line  required to build the full string of the complete character string
            '2a)(i) Most common characters and numbers to be displayed as "seen normally" ' -------2a)(i)--
            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
             Select Case Caracter ' 2a)(ii)_1
              Case " "
               Let WotchaGot = WotchaGot & """" & " " & """" & " & "
              Case "!"
               Let WotchaGot = WotchaGot & """" & "!" & """" & " & "
              Case "$"
               Let WotchaGot = WotchaGot & """" & "$" & """" & " & "
              Case "%"
               Let WotchaGot = WotchaGot & """" & "%" & """" & " & "
              Case "~"
               Let WotchaGot = WotchaGot & """" & "~" & """" & " & "
              Case "&"
               Let WotchaGot = WotchaGot & """" & "&" & """" & " & "
              Case "("
               Let WotchaGot = WotchaGot & """" & "(" & """" & " & "
              Case ")"
               Let WotchaGot = WotchaGot & """" & ")" & """" & " & "
              Case "/"
               Let WotchaGot = WotchaGot & """" & "/" & """" & " & "
              Case "\"
               Let WotchaGot = WotchaGot & """" & "\" & """" & " & "
              Case "="
               Let WotchaGot = WotchaGot & """" & "=" & """" & " & "
              Case "?"
               Let WotchaGot = WotchaGot & """" & "?" & """" & " & "
              Case "'"
               Let WotchaGot = WotchaGot & """" & "'" & """" & " & "
              Case "+"
               Let WotchaGot = WotchaGot & """" & "+" & """" & " & "
              Case "-"
               Let WotchaGot = WotchaGot & """" & "-" & """" & " & "
              Case "_"
               Let WotchaGot = WotchaGot & """" & "_" & """" & " & "
              Case "."
               Let WotchaGot = WotchaGot & """" & "." & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '                   ' 2a)(ii)_2
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
              Case vbCr
               Let WotchaGot = WotchaGot & "vbCr & "  ' I actuall would write manually in this case like     vbCr &
              Case vbLf
               Let WotchaGot = WotchaGot & "vbLf & "
              Case vbCrLf
               Let WotchaGot = WotchaGot & "vbCrLf & "
              Case vbNewLine
               Let WotchaGot = WotchaGot & "NewLine & "
              Case """"   ' This is how to get a single   "    No one is quite sure how this works.  My theory that,  is as good as any other,  is that  syntaxly   """"    or  "  """  or    """    "   are accepted.   But  in that the  """  bit is somewhat strange for VBA.   It seems to match  the first and Third " together as a  valid pair   but  the other  " in the middle of the  3 "s is also syntax OK, and does not error as    """     would  because  of the final 4th " which it syntaxly sees as a valid pair matched simultaneously as it does some similar check on the  first  and Third    as a concluding  string pair.  All is well except that  the second  "  is captured   within a   accepted  enclosing pair made up of the first and third  "   At the same time the 4th  "  is accepted as a final concluding   "   paired with the   second which it is  using but at the same time now isolated from.
               Let WotchaGot = WotchaGot & """" & """" & """" & """" & " & "                                ' The reason why  ""  ""   would not work is that    at the end of the  "" the next empty  character signalises the end of a  string pair, and only if  it saw a " would it keep checking the syntax rules which  then lead in the previous case to  the situation described above.
              Case vbTab
               Let WotchaGot = WotchaGot & "vbTab & "
              ' 2a)(iii)
                Case Else
                 WotchaGot = WotchaGot & "Chr(" & Asc(Caracter) & ")" & " & "
                'Let CaseElse = Caracter
            End Select
            End If ' End of the "normal simple character" or not ' -------2a)------Ended-----------
        '2b)  A 2 column Array for convenience of a list
         Let arrWotchaGot(Cnt + 1, 1) = Cnt & "           " & Caracter: Let arrWotchaGot(Cnt + 1, 2) = Asc(Caracter) ' +1 for header
        Next Cnt ' ========Main Loop=================================================================================
        If WotchaGot <> "" Then
         Let WotchaGot = Left(WotchaGot, Len(WotchaGot) - 3) ' take off last " & "    ( 2 spaces one either side of a  & )
         Let WotchaGot = Replace(WotchaGot, """ & |LinkTwoNormals|""", "", 1, -1, vbBinaryCompare)
        Else
        End If
    Rem 3 Output
    '3a) String
    MsgBox prompt:=WotchaGot: Debug.Print WotchaGot ' Hit Ctrl+g from the VB Editor to get a copyable version of the entire string
    '3b) List
    Dim NxtClm As Long: Let NxtClm = 1 ' In conjunction with next  If  this prevents the first column beine taken as 0 for an empty worksheet
     If Not ws.Range("A1").Value = "" Then Let NxtClm = ws.Cells.Item(1, Columns.Count).End(xlToLeft).Column + 1
     Let ws.Cells.Item(1, NxtClm).Resize(UBound(arrWotchaGot(), 1), UBound(arrWotchaGot(), 2)).Value = arrWotchaGot()
     ws.Cells.Columns.AutoFit
    End Sub
    '
    Last edited by DocAElstein; 12-20-2019 at 09:44 PM. Reason: added vbNewLine

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

    Unics to you

    Unics to you


    The previous discussion considered " plain text " which usually means normal numbers and common letters along with some other common character things, and a limited amount of forein language letters and characters. Historically we often refer to those sort of things as ascii stuff.

    If you want to get a bit more global and all encompassing , to include for example, a lot more non English language letters and characters, then you need to look at " unic " stuff.

    Simplified, we just need to change things like Chr to ChrW , and Asc to AscW.

    Here is an extended character version:
    http://www.excelfox.com/forum/showth...ll=1#post11818
    https://tinyurl.com/vuftsgp




    Refs
    http://www.eileenslounge.com/viewtop...262344#p262344
    https://www.joelonsoftware.com/2003/...ts-no-excuses/

    http://www.excelfox.com/forum/showth...ts-of-a-string
    Last edited by DocAElstein; 04-16-2021 at 04:10 PM.

  3. #13
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    This slightly modified version also adds a worksheet in which to paste
    both
    the original string into the first cell
    and
    the string, WtchaGot , into the second cell

    Code:
    Sub WtchaGot_Unic_NotMuchIfYaChoppedItOff(ByVal strIn As String) '
    Rem 1  ' Output "sheet hardcopies"
    '1a) Worksheets     'Make Temporary Sheets, if not already there, in Current Active Workbook, for a simple list of all characters, and for pasting the string into worksheet cells
    '1a)(i) Full list of characters worksheet
        If Not Evaluate("=ISREF(" & "'" & "WotchaGotInString" & "'!Z78)") Then '   ( the '  are not important here, but iin general allow for a space in the worksheet name like  "Wotcha Got In String"
        Dim Wb As Workbook '                                   ' ' Dim:  ' Preparing a "Pointer" to an Initial "Blue Print" in Memory of the Object ( Pigeon Hole with a bit of paper or code lines on that can be filled in to refer to a specific Objec of this type ) . This also us to get easily at the Methods and Properties throught the applying of a period ( .Dot) ( intellisense )                     '
         Set Wb = ActiveWorkbook '  '                            Set now (to Active Workbook - one being "looked at"), so that we carefull allways referrence this so as not to go astray through Excel Guessing inplicitly not the one we want...         Set: Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191                                '
         Wb.Worksheets.Add After:=Wb.Worksheets.Item(Worksheets.Count) 'A sheeet is added and will be Active
        Dim Ws As Worksheet '
         Set Ws = ActiveSheet 'Rather than rely on always going to the active sheet, we referr to it Explicitly so that we carefull allways referrence this so as not to go astray through Excel Guessing implicitly not the one we want...    Set: Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191            ' Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191
         Ws.Activate: Ws.Cells(1, 1).Activate ' ws.Activate and activating a cell sometimes seemed to overcome a strange error
         Let Ws.Name = "WotchaGotInString"
        Else ' The worksheet is already there , so I just need to set my variable to point to it
         Set Ws = ThisWorkbook.Worksheets("WotchaGotInString")
        End If
    '1a(ii) Worksheet to paste out string into worksheet cells
        If Not Evaluate("=ISREF(" & "'" & "StrIn|WtchaGot" & "'!Z78)") Then
         Set Wb = ActiveWorkbook
         Wb.Worksheets.Add Before:=Wb.Worksheets.Item(1)
        Dim Ws1 As Worksheet
         Set Ws1 = ActiveSheet
         Ws1.Activate: Ws1.Cells(1, 1).Activate
         Let Ws1.Name = "StrIn|WtchaGot"
        Else
         Set Ws1 = ThisWorkbook.Worksheets("StrIn|WtchaGot")
        End If
    '1b) Array
    Dim myLenf As Long: Let myLenf = Len(strIn)  '            ' Long is very simple to handle, - final memory "size" type is known (123.456 and 000.001 have same "size" computer memory ) , and so a Address suggestion can be given for the next line when the variable is filled in.  '( Long is a Big whole Number limit (-2,147,483,648 to 2,147,483,647) If you need some sort of validation the value should only be within the range of a Byte/Integer otherwise there's no point using anything but Long.--upon/after 32-bit, Integers (Short) need converted internally anyways, so a Long is actually faster. )       https://www.mrexcel.com/forum/excel-questions/803662-byte-backward-loop-4.html
    Dim arrWotchaGot() As String: ReDim arrWotchaGot(1 To myLenf + 1, 1 To 2) ' +1 for header  Array for the output 2 column list.  The type is known and the size,  but I must use this ReDim  method simply because the dim statement  Dim( , )  is complie time thing and will only take actual numbers
     Let arrWotchaGot(1, 1) = Format(Now, "DD MMM YYYY") & vbLf & "Lenf is   " & myLenf: Let arrWotchaGot(1, 2) = Left(strIn, 40)
    Rem 2  String anylaysis
    'Dim myLenf As Long: Let myLenf = Len(strIn)
    Dim Cnt As Long
        For Cnt = 1 To myLenf ' ===Main Loop========================================================================
        ' Character analysis: Get at each character
        Dim Caracter As Variant ' String is probably OK.
        Let Caracter = Mid(strIn, Cnt, 1) ' '    the character in strIn at position from the left of length 1
        '2a) The character added to a single  WotchaGot  long character string to look at and possibly use in coding
        Dim WotchaGot As String ' This will be used to make a string that I can easilly see and also is in a form that I can copy and paste in a code line  required to build the full string of the complete character string
            '2a)(i) Most common characters and numbers to be displayed as "seen normally" ' -------2a)(i)--
            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
             Select Case Caracter ' 2a)(ii)_1
              Case " "
               Let WotchaGot = WotchaGot & """" & " " & """" & " & "
              Case "!"
               Let WotchaGot = WotchaGot & """" & "!" & """" & " & "
              Case "$"
               Let WotchaGot = WotchaGot & """" & "$" & """" & " & "
              Case "%"
               Let WotchaGot = WotchaGot & """" & "%" & """" & " & "
              Case "~"
               Let WotchaGot = WotchaGot & """" & "~" & """" & " & "
              Case "&"
               Let WotchaGot = WotchaGot & """" & "&" & """" & " & "
              Case "("
               Let WotchaGot = WotchaGot & """" & "(" & """" & " & "
              Case ")"
               Let WotchaGot = WotchaGot & """" & ")" & """" & " & "
              Case "/"
               Let WotchaGot = WotchaGot & """" & "/" & """" & " & "
              Case "\"
               Let WotchaGot = WotchaGot & """" & "\" & """" & " & "
              Case "="
               Let WotchaGot = WotchaGot & """" & "=" & """" & " & "
              Case "?"
               Let WotchaGot = WotchaGot & """" & "?" & """" & " & "
              Case "'"
               Let WotchaGot = WotchaGot & """" & "'" & """" & " & "
              Case "+"
               Let WotchaGot = WotchaGot & """" & "+" & """" & " & "
              Case "-"
               Let WotchaGot = WotchaGot & """" & "-" & """" & " & "
              Case "_"
               Let WotchaGot = WotchaGot & """" & "_" & """" & " & "
              Case "."
               Let WotchaGot = WotchaGot & """" & "." & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '                   ' 2a)(ii)_2
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
              Case vbCr
               Let WotchaGot = WotchaGot & "vbCr & "  ' I actuall would write manually in this case like     vbCr &
              Case vbLf
               Let WotchaGot = WotchaGot & "vbLf & "
              Case vbCrLf
               Let WotchaGot = WotchaGot & "vbCrLf & "
              Case vbNewLine
               Let WotchaGot = WotchaGot & "vbNewLine & "
              Case """"   ' This is how to get a single   "    No one is quite sure how this works.  My theory that,  is as good as any other,  is that  syntaxly   """"    or  "  """  or    """    "   are accepted.   But  in that the  """  bit is somewhat strange for VBA.   It seems to match  the first and Third " together as a  valid pair   but  the other  " in the middle of the  3 "s is also syntax OK, and does not error as    """     would  because  of the final 4th " which it syntaxly sees as a valid pair matched simultaneously as it does some similar check on the  first  and Third    as a concluding  string pair.  All is well except that  the second  "  is captured   within a   accepted  enclosing pair made up of the first and third  "   At the same time the 4th  "  is accepted as a final concluding   "   paired with the   second which it is  using but at the same time now isolated from.
               Let WotchaGot = WotchaGot & """" & """" & """" & """" & " & "                                ' The reason why  ""  ""   would not work is that    at the end of the  "" the next empty  character signalises the end of a  string pair, and only if  it saw a " would it keep checking the syntax rules which  then lead in the previous case to  the situation described above.
              Case vbTab
               Let WotchaGot = WotchaGot & "vbTab & "
              ' 2a)(iii)
                Case Else
                    If AscW(Caracter) < 256 Then
                     Let WotchaGot = WotchaGot & "Chr(" & AscW(Caracter) & ")" & " & "
                    Else
                     Let WotchaGot = WotchaGot & "ChrW(" & AscW(Caracter) & ")" & " & "
                    End If
                'Let CaseElse = Caracter
            End Select
            End If ' End of the "normal simple character" or not ' -------2a)------Ended-----------
        '2b)  A 2 column Array for convenience of a list
         Let arrWotchaGot(Cnt + 1, 1) = Cnt & "           " & Caracter: Let arrWotchaGot(Cnt + 1, 2) = AscW(Caracter) ' +1 for header
        Next Cnt ' ========Main Loop=================================================================================
        '2c) Some tidying up
        If WotchaGot <> "" Then
         Let WotchaGot = Left(WotchaGot, Len(WotchaGot) - 3) ' take off last " & "    ( 2 spaces one either side of a  & )
         Let WotchaGot = Replace(WotchaGot, """ & |LinkTwoNormals|""", "", 1, -1, vbBinaryCompare)
         ' The next bit changes like this  "Lapto" & "p"  to  "Laptop"   You might want to leave it out ti speed things up a bit
            If Len(WotchaGot) > 5 And (Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[a-z]") And (Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[a-z]") And Mid(WotchaGot, Len(WotchaGot) - 6, 5) = """" & " & " & """" Then
             Let WotchaGot = Left$(WotchaGot, Len(WotchaGot) - 7) & Mid(WotchaGot, Len(WotchaGot) - 1, 2) '  Changes like this  "Lapto" & "p"  to  "Laptop"
            Else
            End If
        Else
        End If
    Rem 3 Output
    '3a) String
    '3a)(i)
    MsgBox Prompt:=WotchaGot: Debug.Print WotchaGot ' Hit Ctrl+g from the VB Editor to get a copyable version of the entire string
    '3a)(ii)
    Ws1.Activate: Ws1.Cells.Item(1, 1).Activate
     Let Ws1.Range("A1").Value = strIn
     Let Ws1.Range("B1").Value = WotchaGot
    '3b) List
    Dim NxtClm As Long: Let NxtClm = 1 ' In conjunction with next  If  this prevents the first column beine taken as 0 for an empty worksheet
     Ws.Activate: Ws.Cells.Item(1, 1).Activate
     If Not Ws.Range("A1").Value = "" Then Let NxtClm = Ws.Cells.Item(1, Columns.Count).End(xlToLeft).Column + 1
     Let Ws.Cells.Item(1, NxtClm).Resize(UBound(arrWotchaGot(), 1), UBound(arrWotchaGot(), 2)).Value = arrWotchaGot()
     Ws.Cells.Columns.AutoFit
    End Sub
    '
    Last edited by DocAElstein; 04-16-2021 at 04:12 PM.

  4. #14
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Another one
    https://excelfox.com/forum/showthrea...ll=1#post15142

    Modified Sub WtchaGot_Unic_NotMuchIfYaChoppedItOff(
    to create a text file output of the WotchaGot string ( in the last post it was used to produce the text file
    WotchaGot_in_tt.txt )

    Code:
    ' https://excelfox.com/forum/showthread.php/2302-quot-What%E2%80%99s-in-a-String-quot-VBA-break-down-Loop-through-character-contents-of-a-string
    ' https://excelfox.com/forum/showthread.php/2302-quot-What%E2%80%99s-in-a-String-quot-VBA-break-down-Loop-through-character-contents-of-a-string?p=11015&viewfull=1#post11015
    Sub WtchaGot_Unic_NotMuchIfYaChoppedItOff(ByVal strIn As String, Optional ByVal FlNme As String) '
    Rem 1  ' Output "sheet hardcopies"
    '1a) Worksheets     'Make Temporary Sheets, if not already there, in Current Active Workbook, for a simple list of all characters, and for pasting the string into worksheet cells
    '1a)(i) Full list of characters worksheet
        If Not Evaluate("=ISREF(" & "'" & "WotchaGotInString" & "'!Z78)") Then '   ( the '  are not important here, but in general allow for a space in the worksheet name like  "Wotcha Got In String"
        Dim Wb As Workbook '                                   ' ' Dim:  ' Preparing a "Pointer" to an Initial "Blue Print" in Memory of the Object ( Pigeon Hole with a bit of paper or code lines on that can be filled in to refer to a specific Objec of this type ) . This also us to get easily at the Methods and Properties throught the applying of a period ( .Dot) ( intellisense )                     '
         Set Wb = ActiveWorkbook '  '                            Set now (to Active Workbook - one being "looked at"), so that we carefull allways referrence this so as not to go astray through Excel Guessing inplicitly not the one we want...         Set: Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191                                '
         Wb.Worksheets.Add After:=Wb.Worksheets.Item(Worksheets.Count) 'A sheeet is added and will be Active
        Dim Ws As Worksheet '
         Set Ws = ActiveSheet 'Rather than rely on always going to the active sheet, we referr to it Explicitly so that we carefull allways referrence this so as not to go astray through Excel Guessing implicitly not the one we want...    Set: Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191            ' Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191
         Ws.Activate: Ws.Cells(1, 1).Activate ' ws.Activate and activating a cell sometimes seemed to overcome a strange error
         Let Ws.Name = "WotchaGotInString"
        Else ' The worksheet is already there , so I just need to set my variable to point to it
         Set Ws = ThisWorkbook.Worksheets("WotchaGotInString")
        End If
    '1a(ii) Worksheet to paste out string into worksheet cells
        If Not Evaluate("=ISREF(" & "'" & "StrIn|WtchaGot" & "'!Z78)") Then
         Set Wb = ActiveWorkbook
         Wb.Worksheets.Add After:=Wb.Worksheets.Item(1)
        Dim Ws1 As Worksheet
         Set Ws1 = ActiveSheet
         Ws1.Activate: Ws1.Cells(1, 1).Activate
         Let Ws1.Name = "StrIn|WtchaGot"
        Else
         Set Ws1 = ThisWorkbook.Worksheets("StrIn|WtchaGot")
        End If
    '1b) Array
    Dim myLenf As Long: Let myLenf = Len(strIn)  '            ' Long is very simple to handle, - final memory "size" type is known (123.456 and 000.001 have same "size" computer memory ) , and so a Address suggestion can be given for the next line when the variable is filled in.  '( Long is a Big whole Number limit (-2,147,483,648 to 2,147,483,647) If you need some sort of validation the value should only be within the range of a Byte/Integer otherwise there's no point using anything but Long.--upon/after 32-bit, Integers (Short) need converted internally anyways, so a Long is actually faster. )       https://www.mrexcel.com/forum/excel-questions/803662-byte-backward-loop-4.html
    Dim arrWotchaGot() As String: ReDim arrWotchaGot(1 To myLenf + 1, 1 To 2) ' +1 for header  Array for the output 2 column list.  The type is known and the size,  but I must use this ReDim  method simply because the dim statement  Dim( , )  is complie time thing and will only take actual numbers
     Let arrWotchaGot(1, 1) = FlNme & vbLf & Format(Now, "DD MMM YYYY") & vbLf & "Lenf is   " & myLenf: Let arrWotchaGot(1, 2) = Left(strIn, 40)
    Rem 2  String anylaysis
    'Dim myLenf As Long: Let myLenf = Len(strIn)
    Dim Cnt As Long
        For Cnt = 1 To myLenf ' ===Main Loop========================================================================
        ' Character analysis: Get at each character
        Dim Caracter As Variant ' String is probably OK.
        Let Caracter = Mid(strIn, Cnt, 1) ' '    the character in strIn at position from the left of length 1
        '2a) The character added to a single  WotchaGot  long character string to look at and possibly use in coding
        Dim WotchaGot As String ' This will be used to make a string that I can easilly see and also is in a form that I can copy and paste in a code line  required to build the full string of the complete character string
            '2a)(i) Most common characters and numbers to be displayed as "seen normally" ' -------2a)(i)--
            If Caracter Like "[A-Z]" Or Caracter Like "[0-9]" Or Caracter Like "[a-z]" Or Caracter = " " 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]" Or Mid(strIn, Cnt - 1, 1) Like " ") 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
             Select Case Caracter ' 2a)(ii)_1
              Case " "
               Let WotchaGot = WotchaGot & """" & " " & """" & " & "
              Case "!"
               Let WotchaGot = WotchaGot & """" & "!" & """" & " & "
              Case "$"
               Let WotchaGot = WotchaGot & """" & "$" & """" & " & "
              Case "%"
               Let WotchaGot = WotchaGot & """" & "%" & """" & " & "
              Case "~"
               Let WotchaGot = WotchaGot & """" & "~" & """" & " & "
              Case "&"
               Let WotchaGot = WotchaGot & """" & "&" & """" & " & "
              Case "("
               Let WotchaGot = WotchaGot & """" & "(" & """" & " & "
              Case ")"
               Let WotchaGot = WotchaGot & """" & ")" & """" & " & "
              Case "/"
               Let WotchaGot = WotchaGot & """" & "/" & """" & " & "
              Case "\"
               Let WotchaGot = WotchaGot & """" & "\" & """" & " & "
              Case "="
               Let WotchaGot = WotchaGot & """" & "=" & """" & " & "
              Case "?"
               Let WotchaGot = WotchaGot & """" & "?" & """" & " & "
              Case "'"
               Let WotchaGot = WotchaGot & """" & "'" & """" & " & "
              Case "+"
               Let WotchaGot = WotchaGot & """" & "+" & """" & " & "
              Case "-"
               Let WotchaGot = WotchaGot & """" & "-" & """" & " & "
              Case "_"
               Let WotchaGot = WotchaGot & """" & "_" & """" & " & "
              Case "."
               Let WotchaGot = WotchaGot & """" & "." & """" & " & "
              Case ","
               Let WotchaGot = WotchaGot & """" & "," & """" & " & "
              Case ";"
               Let WotchaGot = WotchaGot & """" & ";" & """" & " & "
              Case ":"
               Let WotchaGot = WotchaGot & """" & ":" & """" & " & "
              Case "#"
               Let WotchaGot = WotchaGot & """" & "#" & """" & " & "
              Case "@"
               Let WotchaGot = WotchaGot & """" & "@" & """" & " & "
              Case vbCr
               Let WotchaGot = WotchaGot & "vbCr & "  ' I actuall would write manually in this case like     vbCr &
              Case vbLf
               Let WotchaGot = WotchaGot & "vbLf & "
              Case vbCrLf
               Let WotchaGot = WotchaGot & "vbCrLf & "
              Case vbNewLine
               Let WotchaGot = WotchaGot & "vbNewLine & "
              Case """"   ' This is how to get a single   "    No one is quite sure how this works.  My theory that,  is as good as any other,  is that  syntaxly   """"    or  "  """  or    """    "   are accepted.   But  in that the  """  bit is somewhat strange for VBA.   It seems to match  the first and Third " together as a  valid pair   but  the other  " in the middle of the  3 "s is also syntax OK, and does not error as    """     would  because  of the final 4th " which it syntaxly sees as a valid pair matched simultaneously as it does some similar check on the  first  and Third    as a concluding  string pair.  All is well except that  the second  "  is captured   within a   accepted  enclosing pair made up of the first and third  "   At the same time the 4th  "  is accepted as a final concluding   "   paired with the   second which it is  using but at the same time now isolated from.
               Let WotchaGot = WotchaGot & """" & """" & """" & """" & " & "                                ' The reason why  ""  ""   would not work is that    at the end of the  "" the next empty  character signalises the end of a  string pair, and only if  it saw a " would it keep checking the syntax rules which  then lead in the previous case to  the situation described above.
              Case vbTab
               Let WotchaGot = WotchaGot & "vbTab & "
              ' 2a)(iii)
                Case Else
                    If AscW(Caracter) < 256 Then
                     Let WotchaGot = WotchaGot & "Chr(" & AscW(Caracter) & ")" & " & "
                    Else
                     Let WotchaGot = WotchaGot & "ChrW(" & AscW(Caracter) & ")" & " & "
                    End If
                'Let CaseElse = Caracter
            End Select
            End If ' End of the "normal simple character" or not ' -------2a)------Ended-----------
        '2b)  A 2 column Array for convenience of a list
         Let arrWotchaGot(Cnt + 1, 1) = Cnt & "           " & Caracter: Let arrWotchaGot(Cnt + 1, 2) = AscW(Caracter) ' +1 for header
        Next Cnt ' ========Main Loop=================================================================================
        '2c) Some tidying up
        If WotchaGot <> "" Then
         Let WotchaGot = Left(WotchaGot, Len(WotchaGot) - 3) ' take off last " & "    ( 2 spaces one either side of a  & )
         Let WotchaGot = Replace(WotchaGot, """ & |LinkTwoNormals|""", "", 1, -1, vbBinaryCompare)
         ' The next bit changes like this  "Lapto" & "p"  to  "Laptop"   You might want to leave it out ti speed things up a bit
            If Len(WotchaGot) > 5 And (Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[a-z]") And (Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[a-z]") And Mid(WotchaGot, Len(WotchaGot) - 6, 5) = """" & " & " & """" Then
             Let WotchaGot = Left$(WotchaGot, Len(WotchaGot) - 7) & Mid(WotchaGot, Len(WotchaGot) - 1, 2) '  Changes like this  "Lapto" & "p"  to  "Laptop"
            Else
            End If
        Else
        End If
    Rem 3 Output
    '3a) String
    '3a)(i)
    MsgBox Prompt:=WotchaGot: Debug.Print WotchaGot ' Hit Ctrl+g from the VB Editor to get a copyable version of the entire string
    '3a)(ii)
    Ws1.Activate: Ws1.Cells.Item(1, 1).Activate
    Dim Lr1 As Long: Let Lr1 = Ws1.Range("A" & Ws1.Rows.Count).End(xlUp).Row     '   http://www.excelfox.com/forum/showthread.php/2345-Appendix-Thread-(-Codes-for-other-Threads-HTML-Tables-etc-)?p=11466&viewfull=1#post11466      Making Lr dynamic ( using rng.End(XlUp) for a single column. )
     Let Ws1.Range("A" & Lr1 + 1 & "").Value = FlNme
     Let Ws1.Range("B" & Lr1 + 1 & "").Value = strIn
     Let Ws1.Range("C" & Lr1 + 1 & "").Value = WotchaGot
     Ws1.Cells.Columns.AutoFit
    '3b) List
    Dim NxtClm As Long: Let NxtClm = 1 ' In conjunction with next  If  this prevents the first column beine taken as 0 for an empty worksheet
     Ws.Activate: Ws.Cells.Item(1, 1).Activate
     If Not Ws.Range("A1").Value = "" Then Let NxtClm = Ws.Cells.Item(1, Columns.Count).End(xlToLeft).Column + 1
     Let Ws.Cells.Item(1, NxtClm).Resize(UBound(arrWotchaGot(), 1), UBound(arrWotchaGot(), 2)).Value = arrWotchaGot()
     Ws.Cells.Columns.AutoFit
    '3c) Output  WotchaGot  string to a text
    Dim FileNum2 As Long: Let FileNum2 = FreeFile(0)                                  ' https://msdn.microsoft.com/en-us/vba/language-reference-vba/articles/freefile-function
    Dim PathAndFileName2 As String
     Let PathAndFileName2 = ThisWorkbook.Path & "\" & "WotchaGot_in_" & Replace(FlNme, ".txt", "", 1, 1, vbBinaryCompare) & ".txt" ' CHANGE path TO SUIT
     Open PathAndFileName2 For Output As #FileNum2 ' CHANGE TO SUIT  ' Will be made if not there
     Print #FileNum2, WotchaGot ' write out entire text file
     Close #FileNum2
    End Sub
    Last edited by DocAElstein; 04-16-2021 at 04:13 PM.

  5. #15
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    This slightly modified version also adds a worksheet in which to paste
    both
    the original string into the first cell
    and
    the string, WtchaGot , into the second cell

    Code:
    Sub WtchaGot_Unic_NotMuchIfYaChoppedItOff(ByVal strIn As String) '
    Rem 1  ' Output "sheet hardcopies"
    '1a) Worksheets     'Make Temporary Sheets, if not already there, in Current Active Workbook, for a simple list of all characters, and for pasting the string into worksheet cells
    '1a)(i) Full list of characters worksheet
        If Not Evaluate("=ISREF(" & "'" & "WotchaGotInString" & "'!Z78)") Then '   ( the '  are not important here, but iin general allow for a space in the worksheet name like  "Wotcha Got In String"
        Dim Wb As Workbook '                                   ' ' Dim:  ' Preparing a "Pointer" to an Initial "Blue Print" in Memory of the Object ( Pigeon Hole with a bit of paper or code lines on that can be filled in to refer to a specific Objec of this type ) . This also us to get easily at the Methods and Properties throught the applying of a period ( .Dot) ( intellisense )                     '
         Set Wb = ActiveWorkbook '  '                            Set now (to Active Workbook - one being "looked at"), so that we carefull allways referrence this so as not to go astray through Excel Guessing inplicitly not the one we want...         Set: Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191                                '
         Wb.Worksheets.Add After:=Wb.Worksheets.Item(Worksheets.Count) 'A sheeet is added and will be Active
        Dim Ws As Worksheet '
         Set Ws = ActiveSheet 'Rather than rely on always going to the active sheet, we referr to it Explicitly so that we carefull allways referrence this so as not to go astray through Excel Guessing implicitly not the one we want...    Set: Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191            ' Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191
         Ws.Activate: Ws.Cells(1, 1).Activate ' ws.Activate and activating a cell sometimes seemed to overcome a strange error
         Let Ws.Name = "WotchaGotInString"
        Else ' The worksheet is already there , so I just need to set my variable to point to it
         Set Ws = ThisWorkbook.Worksheets("WotchaGotInString")
        End If
    '1a(ii) Worksheet to paste out string into worksheet cells
        If Not Evaluate("=ISREF(" & "'" & "StrIn|WtchaGot" & "'!Z78)") Then
         Set Wb = ActiveWorkbook
         Wb.Worksheets.Add Before:=Wb.Worksheets.Item(1)
        Dim Ws1 As Worksheet
         Set Ws1 = ActiveSheet
         Ws1.Activate: Ws1.Cells(1, 1).Activate
         Let Ws1.Name = "StrIn|WtchaGot"
        Else
         Set Ws1 = ThisWorkbook.Worksheets("StrIn|WtchaGot")
        End If
    '1b) Array
    Dim myLenf As Long: Let myLenf = Len(strIn)  '            ' Long is very simple to handle, - final memory "size" type is known (123.456 and 000.001 have same "size" computer memory ) , and so a Address suggestion can be given for the next line when the variable is filled in.  '( Long is a Big whole Number limit (-2,147,483,648 to 2,147,483,647) If you need some sort of validation the value should only be within the range of a Byte/Integer otherwise there's no point using anything but Long.--upon/after 32-bit, Integers (Short) need converted internally anyways, so a Long is actually faster. )       https://www.mrexcel.com/forum/excel-questions/803662-byte-backward-loop-4.html
    Dim arrWotchaGot() As String: ReDim arrWotchaGot(1 To myLenf + 1, 1 To 2) ' +1 for header  Array for the output 2 column list.  The type is known and the size,  but I must use this ReDim  method simply because the dim statement  Dim( , )  is complie time thing and will only take actual numbers
     Let arrWotchaGot(1, 1) = Format(Now, "DD MMM YYYY") & vbLf & "Lenf is   " & myLenf: Let arrWotchaGot(1, 2) = Left(strIn, 40)
    Rem 2  String anylaysis
    'Dim myLenf As Long: Let myLenf = Len(strIn)
    Dim Cnt As Long
        For Cnt = 1 To myLenf ' ===Main Loop========================================================================
        ' Character analysis: Get at each character
        Dim Caracter As Variant ' String is probably OK.
        Let Caracter = Mid(strIn, Cnt, 1) ' '    the character in strIn at position from the left of length 1
        '2a) The character added to a single  WotchaGot  long character string to look at and possibly use in coding
        Dim WotchaGot As String ' This will be used to make a string that I can easilly see and also is in a form that I can copy and paste in a code line  required to build the full string of the complete character string
            '2a)(i) Most common characters and numbers to be displayed as "seen normally" ' -------2a)(i)--
            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
             Select Case Caracter ' 2a)(ii)_1
              Case " "
               Let WotchaGot = WotchaGot & """" & " " & """" & " & "
              Case "!"
               Let WotchaGot = WotchaGot & """" & "!" & """" & " & "
              Case "$"
               Let WotchaGot = WotchaGot & """" & "$" & """" & " & "
              Case "%"
               Let WotchaGot = WotchaGot & """" & "%" & """" & " & "
              Case "~"
               Let WotchaGot = WotchaGot & """" & "~" & """" & " & "
              Case "&"
               Let WotchaGot = WotchaGot & """" & "&" & """" & " & "
              Case "("
               Let WotchaGot = WotchaGot & """" & "(" & """" & " & "
              Case ")"
               Let WotchaGot = WotchaGot & """" & ")" & """" & " & "
              Case "/"
               Let WotchaGot = WotchaGot & """" & "/" & """" & " & "
              Case "\"
               Let WotchaGot = WotchaGot & """" & "\" & """" & " & "
              Case "="
               Let WotchaGot = WotchaGot & """" & "=" & """" & " & "
              Case "?"
               Let WotchaGot = WotchaGot & """" & "?" & """" & " & "
              Case "'"
               Let WotchaGot = WotchaGot & """" & "'" & """" & " & "
              Case "+"
               Let WotchaGot = WotchaGot & """" & "+" & """" & " & "
              Case "-"
               Let WotchaGot = WotchaGot & """" & "-" & """" & " & "
              Case "_"
               Let WotchaGot = WotchaGot & """" & "_" & """" & " & "
              Case "."
               Let WotchaGot = WotchaGot & """" & "." & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '                   ' 2a)(ii)_2
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
    '          Case " "
    '           Let WotchaGot = WotchaGot & """" & " " & """" & " & "
              Case vbCr
               Let WotchaGot = WotchaGot & "vbCr & "  ' I actuall would write manually in this case like     vbCr &
              Case vbLf
               Let WotchaGot = WotchaGot & "vbLf & "
              Case vbCrLf
               Let WotchaGot = WotchaGot & "vbCrLf & "
              Case vbNewLine
               Let WotchaGot = WotchaGot & "vbNewLine & "
              Case """"   ' This is how to get a single   "    No one is quite sure how this works.  My theory that,  is as good as any other,  is that  syntaxly   """"    or  "  """  or    """    "   are accepted.   But  in that the  """  bit is somewhat strange for VBA.   It seems to match  the first and Third " together as a  valid pair   but  the other  " in the middle of the  3 "s is also syntax OK, and does not error as    """     would  because  of the final 4th " which it syntaxly sees as a valid pair matched simultaneously as it does some similar check on the  first  and Third    as a concluding  string pair.  All is well except that  the second  "  is captured   within a   accepted  enclosing pair made up of the first and third  "   At the same time the 4th  "  is accepted as a final concluding   "   paired with the   second which it is  using but at the same time now isolated from.
               Let WotchaGot = WotchaGot & """" & """" & """" & """" & " & "                                ' The reason why  ""  ""   would not work is that    at the end of the  "" the next empty  character signalises the end of a  string pair, and only if  it saw a " would it keep checking the syntax rules which  then lead in the previous case to  the situation described above.
              Case vbTab
               Let WotchaGot = WotchaGot & "vbTab & "
              ' 2a)(iii)
                Case Else
                    If AscW(Caracter) < 256 Then
                     Let WotchaGot = WotchaGot & "Chr(" & AscW(Caracter) & ")" & " & "
                    Else
                     Let WotchaGot = WotchaGot & "ChrW(" & AscW(Caracter) & ")" & " & "
                    End If
                'Let CaseElse = Caracter
            End Select
            End If ' End of the "normal simple character" or not ' -------2a)------Ended-----------
        '2b)  A 2 column Array for convenience of a list
         Let arrWotchaGot(Cnt + 1, 1) = Cnt & "           " & Caracter: Let arrWotchaGot(Cnt + 1, 2) = AscW(Caracter) ' +1 for header
        Next Cnt ' ========Main Loop=================================================================================
        '2c) Some tidying up
        If WotchaGot <> "" Then
         Let WotchaGot = Left(WotchaGot, Len(WotchaGot) - 3) ' take off last " & "    ( 2 spaces one either side of a  & )
         Let WotchaGot = Replace(WotchaGot, """ & |LinkTwoNormals|""", "", 1, -1, vbBinaryCompare)
         ' The next bit changes like this  "Lapto" & "p"  to  "Laptop"   You might want to leave it out ti speed things up a bit
            If Len(WotchaGot) > 5 And (Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[a-z]") And (Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[a-z]") And Mid(WotchaGot, Len(WotchaGot) - 6, 5) = """" & " & " & """" Then
             Let WotchaGot = Left$(WotchaGot, Len(WotchaGot) - 7) & Mid(WotchaGot, Len(WotchaGot) - 1, 2) '  Changes like this  "Lapto" & "p"  to  "Laptop"
            Else
            End If
        Else
        End If
    Rem 3 Output
    '3a) String
    '3a)(i)
    MsgBox Prompt:=WotchaGot: Debug.Print WotchaGot ' Hit Ctrl+g from the VB Editor to get a copyable version of the entire string
    '3a)(ii)
    Ws1.Activate: Ws1.Cells.Item(1, 1).Activate
     Let Ws1.Range("A1").Value = strIn
     Let Ws1.Range("B1").Value = WotchaGot
    '3b) List
    Dim NxtClm As Long: Let NxtClm = 1 ' In conjunction with next  If  this prevents the first column beine taken as 0 for an empty worksheet
     Ws.Activate: Ws.Cells.Item(1, 1).Activate
     If Not Ws.Range("A1").Value = "" Then Let NxtClm = Ws.Cells.Item(1, Columns.Count).End(xlToLeft).Column + 1
     Let Ws.Cells.Item(1, NxtClm).Resize(UBound(arrWotchaGot(), 1), UBound(arrWotchaGot(), 2)).Value = arrWotchaGot()
     Ws.Cells.Columns.AutoFit
    End Sub
    '
    Last edited by DocAElstein; 01-15-2020 at 05:38 PM.

  6. #16
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Another one
    https://excelfox.com/forum/showthrea...ll=1#post15142

    Modified Sub WtchaGot_Unic_NotMuchIfYaChoppedItOff(
    to create a text file output of the WotchaGot string ( in the last post it was used to produce the text file
    WotchaGot_in_tt.txt )

    Code:
    ' https://excelfox.com/forum/showthread.php/2302-quot-What%E2%80%99s-in-a-String-quot-VBA-break-down-Loop-through-character-contents-of-a-string
    ' https://excelfox.com/forum/showthread.php/2302-quot-What%E2%80%99s-in-a-String-quot-VBA-break-down-Loop-through-character-contents-of-a-string?p=11015&viewfull=1#post11015
    Sub WtchaGot_Unic_NotMuchIfYaChoppedItOff(ByVal strIn As String, Optional ByVal FlNme As String) '
    Rem 1  ' Output "sheet hardcopies"
    '1a) Worksheets     'Make Temporary Sheets, if not already there, in Current Active Workbook, for a simple list of all characters, and for pasting the string into worksheet cells
    '1a)(i) Full list of characters worksheet
        If Not Evaluate("=ISREF(" & "'" & "WotchaGotInString" & "'!Z78)") Then '   ( the '  are not important here, but in general allow for a space in the worksheet name like  "Wotcha Got In String"
        Dim Wb As Workbook '                                   ' ' Dim:  ' Preparing a "Pointer" to an Initial "Blue Print" in Memory of the Object ( Pigeon Hole with a bit of paper or code lines on that can be filled in to refer to a specific Objec of this type ) . This also us to get easily at the Methods and Properties throught the applying of a period ( .Dot) ( intellisense )                     '
         Set Wb = ActiveWorkbook '  '                            Set now (to Active Workbook - one being "looked at"), so that we carefull allways referrence this so as not to go astray through Excel Guessing inplicitly not the one we want...         Set: Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191                                '
         Wb.Worksheets.Add After:=Wb.Worksheets.Item(Worksheets.Count) 'A sheeet is added and will be Active
        Dim Ws As Worksheet '
         Set Ws = ActiveSheet 'Rather than rely on always going to the active sheet, we referr to it Explicitly so that we carefull allways referrence this so as not to go astray through Excel Guessing implicitly not the one we want...    Set: Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191            ' Values are filled at the memory locations and the directions there are specified in the variable "Blue Print "Pointer". In this case a Filled in Blue Print is passed.      http://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-4.html#post4387191
         Ws.Activate: Ws.Cells(1, 1).Activate ' ws.Activate and activating a cell sometimes seemed to overcome a strange error
         Let Ws.Name = "WotchaGotInString"
        Else ' The worksheet is already there , so I just need to set my variable to point to it
         Set Ws = ThisWorkbook.Worksheets("WotchaGotInString")
        End If
    '1a(ii) Worksheet to paste out string into worksheet cells
        If Not Evaluate("=ISREF(" & "'" & "StrIn|WtchaGot" & "'!Z78)") Then
         Set Wb = ActiveWorkbook
         Wb.Worksheets.Add After:=Wb.Worksheets.Item(1)
        Dim Ws1 As Worksheet
         Set Ws1 = ActiveSheet
         Ws1.Activate: Ws1.Cells(1, 1).Activate
         Let Ws1.Name = "StrIn|WtchaGot"
        Else
         Set Ws1 = ThisWorkbook.Worksheets("StrIn|WtchaGot")
        End If
    '1b) Array
    Dim myLenf As Long: Let myLenf = Len(strIn)  '            ' Long is very simple to handle, - final memory "size" type is known (123.456 and 000.001 have same "size" computer memory ) , and so a Address suggestion can be given for the next line when the variable is filled in.  '( Long is a Big whole Number limit (-2,147,483,648 to 2,147,483,647) If you need some sort of validation the value should only be within the range of a Byte/Integer otherwise there's no point using anything but Long.--upon/after 32-bit, Integers (Short) need converted internally anyways, so a Long is actually faster. )       https://www.mrexcel.com/forum/excel-questions/803662-byte-backward-loop-4.html
    Dim arrWotchaGot() As String: ReDim arrWotchaGot(1 To myLenf + 1, 1 To 2) ' +1 for header  Array for the output 2 column list.  The type is known and the size,  but I must use this ReDim  method simply because the dim statement  Dim( , )  is complie time thing and will only take actual numbers
     Let arrWotchaGot(1, 1) = FlNme & vbLf & Format(Now, "DD MMM YYYY") & vbLf & "Lenf is   " & myLenf: Let arrWotchaGot(1, 2) = Left(strIn, 40)
    Rem 2  String anylaysis
    'Dim myLenf As Long: Let myLenf = Len(strIn)
    Dim Cnt As Long
        For Cnt = 1 To myLenf ' ===Main Loop========================================================================
        ' Character analysis: Get at each character
        Dim Caracter As Variant ' String is probably OK.
        Let Caracter = Mid(strIn, Cnt, 1) ' '    the character in strIn at position from the left of length 1
        '2a) The character added to a single  WotchaGot  long character string to look at and possibly use in coding
        Dim WotchaGot As String ' This will be used to make a string that I can easilly see and also is in a form that I can copy and paste in a code line  required to build the full string of the complete character string
            '2a)(i) Most common characters and numbers to be displayed as "seen normally" ' -------2a)(i)--
            If Caracter Like "[A-Z]" Or Caracter Like "[0-9]" Or Caracter Like "[a-z]" Or Caracter = " " 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]" Or Mid(strIn, Cnt - 1, 1) Like " ") 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
             Select Case Caracter ' 2a)(ii)_1
              Case " "
               Let WotchaGot = WotchaGot & """" & " " & """" & " & "
              Case "!"
               Let WotchaGot = WotchaGot & """" & "!" & """" & " & "
              Case "$"
               Let WotchaGot = WotchaGot & """" & "$" & """" & " & "
              Case "%"
               Let WotchaGot = WotchaGot & """" & "%" & """" & " & "
              Case "~"
               Let WotchaGot = WotchaGot & """" & "~" & """" & " & "
              Case "&"
               Let WotchaGot = WotchaGot & """" & "&" & """" & " & "
              Case "("
               Let WotchaGot = WotchaGot & """" & "(" & """" & " & "
              Case ")"
               Let WotchaGot = WotchaGot & """" & ")" & """" & " & "
              Case "/"
               Let WotchaGot = WotchaGot & """" & "/" & """" & " & "
              Case "\"
               Let WotchaGot = WotchaGot & """" & "\" & """" & " & "
              Case "="
               Let WotchaGot = WotchaGot & """" & "=" & """" & " & "
              Case "?"
               Let WotchaGot = WotchaGot & """" & "?" & """" & " & "
              Case "'"
               Let WotchaGot = WotchaGot & """" & "'" & """" & " & "
              Case "+"
               Let WotchaGot = WotchaGot & """" & "+" & """" & " & "
              Case "-"
               Let WotchaGot = WotchaGot & """" & "-" & """" & " & "
              Case "_"
               Let WotchaGot = WotchaGot & """" & "_" & """" & " & "
              Case "."
               Let WotchaGot = WotchaGot & """" & "." & """" & " & "
              Case ","
               Let WotchaGot = WotchaGot & """" & "," & """" & " & "
              Case ";"
               Let WotchaGot = WotchaGot & """" & ";" & """" & " & "
              Case ":"
               Let WotchaGot = WotchaGot & """" & ":" & """" & " & "
              Case "#"
               Let WotchaGot = WotchaGot & """" & "#" & """" & " & "
              Case "@"
               Let WotchaGot = WotchaGot & """" & "@" & """" & " & "
              Case vbCr
               Let WotchaGot = WotchaGot & "vbCr & "  ' I actuall would write manually in this case like     vbCr &
              Case vbLf
               Let WotchaGot = WotchaGot & "vbLf & "
              Case vbCrLf
               Let WotchaGot = WotchaGot & "vbCrLf & "
              Case vbNewLine
               Let WotchaGot = WotchaGot & "vbNewLine & "
              Case """"   ' This is how to get a single   "    No one is quite sure how this works.  My theory that,  is as good as any other,  is that  syntaxly   """"    or  "  """  or    """    "   are accepted.   But  in that the  """  bit is somewhat strange for VBA.   It seems to match  the first and Third " together as a  valid pair   but  the other  " in the middle of the  3 "s is also syntax OK, and does not error as    """     would  because  of the final 4th " which it syntaxly sees as a valid pair matched simultaneously as it does some similar check on the  first  and Third    as a concluding  string pair.  All is well except that  the second  "  is captured   within a   accepted  enclosing pair made up of the first and third  "   At the same time the 4th  "  is accepted as a final concluding   "   paired with the   second which it is  using but at the same time now isolated from.
               Let WotchaGot = WotchaGot & """" & """" & """" & """" & " & "                                ' The reason why  ""  ""   would not work is that    at the end of the  "" the next empty  character signalises the end of a  string pair, and only if  it saw a " would it keep checking the syntax rules which  then lead in the previous case to  the situation described above.
              Case vbTab
               Let WotchaGot = WotchaGot & "vbTab & "
              ' 2a)(iii)
                Case Else
                    If AscW(Caracter) < 256 Then
                     Let WotchaGot = WotchaGot & "Chr(" & AscW(Caracter) & ")" & " & "
                    Else
                     Let WotchaGot = WotchaGot & "ChrW(" & AscW(Caracter) & ")" & " & "
                    End If
                'Let CaseElse = Caracter
            End Select
            End If ' End of the "normal simple character" or not ' -------2a)------Ended-----------
        '2b)  A 2 column Array for convenience of a list
         Let arrWotchaGot(Cnt + 1, 1) = Cnt & "           " & Caracter: Let arrWotchaGot(Cnt + 1, 2) = AscW(Caracter) ' +1 for header
        Next Cnt ' ========Main Loop=================================================================================
        '2c) Some tidying up
        If WotchaGot <> "" Then
         Let WotchaGot = Left(WotchaGot, Len(WotchaGot) - 3) ' take off last " & "    ( 2 spaces one either side of a  & )
         Let WotchaGot = Replace(WotchaGot, """ & |LinkTwoNormals|""", "", 1, -1, vbBinaryCompare)
         ' The next bit changes like this  "Lapto" & "p"  to  "Laptop"   You might want to leave it out ti speed things up a bit
            If Len(WotchaGot) > 5 And (Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[a-z]") And (Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[a-z]") And Mid(WotchaGot, Len(WotchaGot) - 6, 5) = """" & " & " & """" Then
             Let WotchaGot = Left$(WotchaGot, Len(WotchaGot) - 7) & Mid(WotchaGot, Len(WotchaGot) - 1, 2) '  Changes like this  "Lapto" & "p"  to  "Laptop"
            Else
            End If
        Else
        End If
    Rem 3 Output
    '3a) String
    '3a)(i)
    MsgBox Prompt:=WotchaGot: Debug.Print WotchaGot ' Hit Ctrl+g from the VB Editor to get a copyable version of the entire string
    '3a)(ii)
    Ws1.Activate: Ws1.Cells.Item(1, 1).Activate
    Dim Lr1 As Long: Let Lr1 = Ws1.Range("A" & Ws1.Rows.Count).End(xlUp).Row     '   http://www.excelfox.com/forum/showthread.php/2345-Appendix-Thread-(-Codes-for-other-Threads-HTML-Tables-etc-)?p=11466&viewfull=1#post11466      Making Lr dynamic ( using rng.End(XlUp) for a single column. )
     Let Ws1.Range("A" & Lr1 + 1 & "").Value = FlNme
     Let Ws1.Range("B" & Lr1 + 1 & "").Value = strIn
     Let Ws1.Range("C" & Lr1 + 1 & "").Value = WotchaGot
     Ws1.Cells.Columns.AutoFit
    '3b) List
    Dim NxtClm As Long: Let NxtClm = 1 ' In conjunction with next  If  this prevents the first column beine taken as 0 for an empty worksheet
     Ws.Activate: Ws.Cells.Item(1, 1).Activate
     If Not Ws.Range("A1").Value = "" Then Let NxtClm = Ws.Cells.Item(1, Columns.Count).End(xlToLeft).Column + 1
     Let Ws.Cells.Item(1, NxtClm).Resize(UBound(arrWotchaGot(), 1), UBound(arrWotchaGot(), 2)).Value = arrWotchaGot()
     Ws.Cells.Columns.AutoFit
    '3c) Output  WotchaGot  string to a text
    Dim FileNum2 As Long: Let FileNum2 = FreeFile(0)                                  ' https://msdn.microsoft.com/en-us/vba/language-reference-vba/articles/freefile-function
    Dim PathAndFileName2 As String
     Let PathAndFileName2 = ThisWorkbook.Path & "\" & "WotchaGot_in_" & Replace(FlNme, ".txt", "", 1, 1, vbBinaryCompare) & ".txt" ' CHANGE path TO SUIT
     Open PathAndFileName2 For Output As #FileNum2 ' CHANGE TO SUIT  ' Will be made if not there
     Print #FileNum2, WotchaGot ' write out entire text file
     Close #FileNum2
    End Sub
    Last edited by DocAElstein; 01-10-2021 at 03:22 PM.

  7. #17
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    This has a small modification to offset a bug when you only have one character..

    -....later when I re find it



    Much later....... I never found it so did it again on a later version

    https://excelfox.com/forum/showthrea...ll=1#post15524
    https://excelfox.com/forum/showthread.php/2302-quot-What%e2%80%99s-in-a-String-quot-VBA-break-down-Loop-through-character-contents-of-a-string?p=15524&viewfull=1#post15524
    Last edited by DocAElstein; 09-14-2022 at 11:53 AM.

  8. #18
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    This makes a few text files

    https://pastebin.com/HatYwAAD

    I will come back and document, explain and tidy all this up sometime, when it snows a lot outside....
    Last edited by DocAElstein; 04-16-2021 at 04:29 PM.

  9. #19
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    fhalhflkshfhhfslhf
    Last edited by DocAElstein; 04-16-2021 at 04:20 PM.

  10. #20
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    This bit causes a bit of an error , if you only have one character
    Code:
         ' The next bit changes like this  "Lapto" & "p"  to  "Laptop"   You might want to leave it out ti speed things up a bit
            If Len(WotchaGot) > 5 And (Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[a-z]") And (Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[a-z]") And Mid(WotchaGot, Len(WotchaGot) - 6, 5) = """" & " & " & """" Then
             Let WotchaGot = Left$(WotchaGot, Len(WotchaGot) - 7) & Mid(WotchaGot, Len(WotchaGot) - 1, 2) '  Changes like this  "Lapto" & "p"  to  "Laptop"
            Else
            End If
        Else
    As far as i can remember that is only needed to concatenate simple letters and nubers in the final output, just because like

    "Alan"

    looks a bit better than

    "A" & "l" & "a" & "n"

    So simple fix, is don't do that if Len(strIn) is 1

    Code:
            If Len(strIn) = 1 Then
            
            Else
                ' The next bit changes like this  "Lapto" & "p"  to  "Laptop"   You might want to leave it out ti speed things up a bit
                   If Len(WotchaGot) > 5 And (Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 1, 1) Like "[a-z]") And (Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[A-Z]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[0-9]" Or Mid(WotchaGot, Len(WotchaGot) - 7, 1) Like "[a-z]") And Mid(WotchaGot, Len(WotchaGot) - 6, 5) = """" & " & " & """" Then
                    Let WotchaGot = Left$(WotchaGot, Len(WotchaGot) - 7) & Mid(WotchaGot, Len(WotchaGot) - 1, 2) '  Changes like this  "Lapto" & "p"  to  "Laptop"
                   Else
                   End If
            End If
        Else


    https://pastebin.com/eutzzxHv
    https://excelfox.com/forum/showthrea...ll=1#post15524
    https://excelfox.com/forum/showthread.php/2302-quot-What%e2%80%99s-in-a-String-quot-VBA-break-down-Loop-through-character-contents-of-a-string?p=15524&viewfull=1#post15524
    https://www.excelfox.com/forum/showt...age2#post15524
    https://www.excelfox.com/forum/showthread.php/2302-quot-What%E2%80%99s-in-a-String-quot-VBA-break-down-Loop-through-character-contents-of-a-string/page2#post15524
    Last edited by DocAElstein; 01-18-2024 at 06:26 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
  •