Page 3 of 3 FirstFirst 123
Results 21 to 27 of 27

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

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

    Examples of wots in a computer string

    Examples of wots in a computer string


    In the following posts I will look at some examples of examining the contents off a computer string of characters.
    Initially this will be a bit random. After I have a few I will probably sort them somehow and add an Index in this please

    If anyone would like to contribute an example, or make any comments then please do so via a reply to this Thread.
    Last edited by DocAElstein; 01-15-2020 at 05:20 PM.

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

    Examples of wots in a computer string

    Examples of wots in a computer string


    In the following posts I will look at some examples of examining the contents off a computer string of characters.
    Initially this will be a bit random. After I have a few I will probably sort them somehow and add an Index in this please

    If anyone would like to contribute an example, or make any comments then please do so via a reply to this Thread.

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

    Code breaks and___horizontal borders in code modules

    Code breaks and___horizontal borders in code modules

    This post is in support of these Threads
    http://www.excelfox.com/forum/showth...1001#post11001
    http://www.eileenslounge.com/viewtopic.php?f=30&t=31756


    We can observe some behaviour, the reason for which is not immediately obvious concerning the position taken for the light grey dividing line between. This appears to be influenced by the presence of a trailing isolated single underscore __

    The purpose of this post is to see if there might be anything "there" around the three _ _ _ other than the expected combination of like, for the coding example below, of
    __ " " & "_" & vbcR & vbLf & " "
    Code:
    Option Explicit
    Public LudwigII As Legend  _
    ________________________________________________________________________________________________________________________________________________________________________________
    
    
    Sub Sub1()
    Dim Lr As _
            Long
    End Sub ' ___ Some comments
    
    '  _  
    __________________________________________________________________________________________________________________________________________________________________________________
    
    
    Sub Sub2()
    ' code
    End Sub
    The code above I have in a code module, Modul1 , ( Modul1.JPG : https://imgur.com/Pa8TR6P ) I can examine contents of a code module with a few lines of coding as below.
    I have also included some code lines to check that the position of the grey border line____ as well as other lines correspond to as I might expect, that is to say, according to what we see in the above screenshot…

    Count Of Declaration lines is _ 3 ( Up to and including the line with the first border_______ )
    For Sub Sub1()
    ___ Procedure Stat Line will be 4 ( first line afte the first _______ )
    ___ Procedure Body line will be 6 ( line for Sub Sub1() )
    ___ Proc Count of Lines will be 9
    For Sub Sub2()
    ___ Procedure Stat Line will be 13
    ___ Procedure Body line will be 15
    ___ Proc Count of Lines will be 5

    The count of lines used in the module will be 17
    Code:
    1 1 Option Explicit
    2 2 Public LudwigII As Legend  _
    3 3 ________________________________________________________________________________________________________________________________________________________________________________
    4 1 
    5  2 
    6 3 Sub Sub1()
    7  4  Dim Lr As _
    8  5         Long
    9  6 End Sub ' ___ Some comments
    10 7
    11 8 '  _  
    12 9 __________________________________________________________________________________________________________________________________________________________________________________
    13 1
    14  2
    15 3 Sub Sub2()
    16  4  ' code
    17 5 End Sub
    The following code, placed in an other code module, will get is that information as well as a string which we can feed to our string analysis code
    Code:
    Sub BreakLineString()  '  http://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?p=11016&viewfull=1#post11016
    Dim StrTest As String
    Dim objMod As Object ' VBIDE.CodeModule  ' for intellisense  '  http://www.eileenslounge.com/viewtopic.php?f=30&t=31547&p=246604#p246602   
     Set objMod = ThisWorkbook.VBProject.VBComponents("Modul1").CodeModule
     Debug.Print
    ' Coding line number infomation
     Debug.Print objMod.CountOfDeclarationLines
     Debug.Print
     Debug.Print objMod.ProcStartLine(ProcName:="Sub1", procKind:=0)
     Debug.Print objMod.ProcBodyLine(ProcName:="Sub1", procKind:=0)
     Debug.Print objMod.ProcCountLines(ProcName:="Sub1", procKind:=0)
     Debug.Print
     Debug.Print objMod.ProcStartLine(ProcName:="Sub2", procKind:=0)
     Debug.Print objMod.ProcBodyLine(ProcName:="Sub2", procKind:=0)
     Debug.Print objMod.ProcCountLines(ProcName:="Sub2", procKind:=0)
     Debug.Print
     Debug.Print objMod.CountOfLines
     Debug.Print
    ' String analysis for module coding
     Let StrTest = objMod.Lines(Startline:=1, Count:=objMod.CountOfLines + 345)
     Call WtchaGot(strIn:=StrTest)
    End Sub
    Here again is the code which should be placed in full in a code module with name Module1, ( or if in any other module is used, then change the code references appropriately)
    Code:
     Option Explicit
    Public LudwigII As Legend _
    
    
    
    Sub Sub1()
    Dim Lr As _
            Long
    End Sub ' ___ Some comments
    
    ' _
    
    
    
    Sub Sub2()
    ' code
    End Sub
    When copying the above code, be careful not to inadvertently add any extra lines: To be sure of this, click anywhere in the coding and hit the key DownArrrow a few times until you are sure that you are at the end of the lines. Now hit the back key until the cursor is at the end of the last
    End Sub|
    Now run routine Sub BreakLineString()
    In the Immediate Window, ( http://www.eileenslounge.com/viewtop...247121#p247121 ) you will see initially a confirmation of the line numbers…
    3 CountOfDeclarationLines

    4 ProcStartLine(ProcName:="Sub1", procKind:=0)
    6 ProcBodyLine(ProcName:="Sub1", procKind:=0)
    9 ProcCountLines(ProcName:="Sub1", procKind:=0)

    13 ProcStartLine(ProcName:="Sub2", procKind:=0)
    15 ProcBodyLine(ProcName:="Sub2", procKind:=0)
    5 ProcCountLines(ProcName:="Sub2", procKind:=0)

    17 CountOfLines

    _.________________________________________________ ____________________-

    In the rest of the Immediate window, the section produced by WtchaGot(strIn:=StrTest) appears to show no indications of either.._
    _.. the light grey border line
    or
    _.. any irregularities around any trailing isolated single underscore _ _
    Code:
     "Option" & " " & "Explicit"
    & vbCr & vbLf & "Public" & " " & "LudwigII" & " " & "As" & " " & "Legend" & " " & "_"
    & vbCr & vbLf___________________________________________________________________________________________________________________________________________________________________________________
    & vbCr & vbLf
    & vbCr & vbLf
    & vbCr & vbLf & "Sub" & " " & "Sub1" & "(" & ")"
    & vbCr & vbLf & "Dim" & " " & "Lr" & " " & "As" & " " & "_"
    & vbCr & vbLf & " " & " " & " " & " " & " " & " " & " " & " " & "Long"
    & vbCr & vbLf & "End" & " " & "Sub" & " " & "'" & " " & "_" & "_" & "_" & " " & "Some" & " " & "comments"
    & vbCr & vbLf
    & vbCr & vbLf & "'" & " " & "_"
    & vbCr & vbLf_____________________________________________________________________________________________________________________________________________________________
    & vbCr & vbLf
    & vbCr & vbLf
    & vbCr & vbLf & "Sub" & " " & "Sub2" & "(" & ")"
    & vbCr & vbLf & "'" & " " & "code"
    & vbCr & vbLf & "End" & " " & "Sub"
    & vbCr & vbLf
    Note:
    _ I Have added the color to highlight the normal string combinations around the trailing isolated underscores,
    " " & "_" & vbCr & vbLf
    _ I have indicated what I consider to be the grey border lines_________ & vbCr & vbLf

    _ I have indicated in brown to give example of what I consider the procedure lines, as example for procedure Sub Sub2()
    ( I would consider the first line there as _ "" & vbCr & vbLf _ and the last line as _ "End" & " " & "Sub" & vbCr & vbLf _ )

    _ the actual string looks like a long single string like:
    Code:
     "Option" & " " & "Explicit" & vbCr & vbLf & "Public" & " " & "LudwigII" & " " & "As" & " " & "Legend" & " " & "_" & vbCr & vbLf & vbCr & vbLf & vbCr & vbLf & vbCr & vbLf & "Sub" & " " & "Sub1" & "(" & ")" & vbCr & vbLf & "Dim" & " " & "Lr" & " " & "As" & " " & "_" & vbCr & vbLf & " " & " " & " " & " " & " " & " " & " " & " " & "Long" & vbCr & vbLf & "End" & " " & "Sub" & " " & "'" & " " & "_" & "_" & "_" & " " & "Some" & " " & "comments" & vbCr & vbLf & vbCr & vbLf & "'" & " " & "_" & vbCr & vbLf & vbCr & vbLf & vbCr & vbLf & vbCr & vbLf & "Sub" & " " & "Sub2" & "(" & ")" & vbCr & vbLf & "'" & " " & "code" & vbCr & vbLf & "End" & " " & "Sub" & vbCr & vbLf
    _.___________________________

    Modul1 Wotcha Got.JPG : https://imgur.com/GVIHSqV
    Attachment 2573
    _.__________________________


    The conclusion is that whatever is going on to produce the grey line border behaviour is based on some detailed analysis of the code string and there are no extra "hidden" characters used to identify these areas







    Ref :
    VBA for the VBE : thinkz1.com
    Info / files private from Lisa Green
    https://excel.tips.net/T003219_Getti...haracters.html
    https://www.eileenslounge.com/viewto...p?f=30&t=36683

    Last edited by DocAElstein; 06-05-2021 at 08:44 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!!

  4. #24
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Last edited by DocAElstein; 08-10-2021 at 01:40 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!!

  5. #25
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    spare post to help organise and compose better later

  6. #26
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    .... spare post to help organise and compose better later

  7. #27
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Here a quick modified coding to look at the string seen in a highlighted word text (I had to chop a lot out to get it in the post size limit, the uploaded file has a fuller version)


    Code:
    '        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?p=21221&viewfull=1#post21221           https://www.excelfox.com/forum/showthread.php/2348-String-text-in-Word-html-Passing-info-between-Word-and-Excel?p=21222#post21222                                                              
    
    
    '  Modified a bit from here  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?p=15524&viewfull=1#post15524
    '  Modified to remove Excel Output bits and change  ThisWorkbook.Path   to   ThisDocument.Path   for the generated text files
    
    
    Sub WatchaGotWord(ByVal strIn As String, Optional ByVal FlNme As String) '
    'Rem 1  ' Output "sheet hardcopies"
    
    
    
    
    '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 " "
    '           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)
            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
        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
    
    
    
    
    '3c) Output  WotchaGot  string to a text file
    '3c)(i) Simple string
    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
     Let PathAndFileName2 = ThisDocument.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
    '3c)(ii) Introduce an  "invisible"  vbCr & vbLf  pair after each  seen pair within  the string. this will give actual lines in the text file
     Let WotchaGot = Replace(WotchaGot, "vbCr & vbLf & ", "vbCr & vbLf" & vbCr & vbLf, 1, -1, vbBinaryCompare)
    ' Let PathAndFileName2 = ThisWorkbook.Path & "\" & "WotchaGot_in_" & Replace(FlNme, ".txt", "", 1, 1, vbBinaryCompare) & "_inLines.txt" ' CHANGE path TO SUIT
     Let PathAndFileName2 = ThisDocument.Path & "\" & "WotchaGot_in_" & Replace(FlNme, ".txt", "", 1, 1, vbBinaryCompare) & "_inLines.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
     '3c(iii) Number the new introduced actual Liners in the text file
    Dim arrIt() As String: Let arrIt() = Split(WotchaGot, vbCr & vbLf, -1, vbBinaryCompare)
     Let WotchaGot = ""
        For Cnt = 0 To UBound(arrIt())
         Let WotchaGot = WotchaGot & Cnt & " " & arrIt(Cnt) & vbCr & vbLf
        Next Cnt
    ' Let PathAndFileName2 = ThisWorkbook.Path & "\" & "WotchaGot_in_" & Replace(FlNme, ".txt", "", 1, 1, vbBinaryCompare) & "_inNumberedLines.txt" ' CHANGE path TO SUIT
     Let PathAndFileName2 = ThisDocument.Path & "\" & "WotchaGot_in_" & Replace(FlNme, ".txt", "", 1, 1, vbBinaryCompare) & "_inNumberedLines.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
    Attached Files Attached Files
    Last edited by DocAElstein; 07-09-2023 at 05: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
  •