Page 3 of 12 FirstFirst 12345 ... LastLast
Results 21 to 30 of 115

Thread: Notes tests, text files, manipulation of text files in Excel and with Excel VBA CSV stuff

Hybrid View

Previous Post Previous Post   Next Post Next Post
  1. #1
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,323
    Rep Power
    10
    Dec 2020-11-29

    If I make text file with nothing in it and then after look at the text file with the following macro ..._
    Code:
    ' A virgin text file
    Sub AVirginTextFile()
    ' 1    Make a virgin text file
    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 & "\" & "NoText.txt"  ' CHANGE path TO SUIT
     Open PathAndFileName2 For Output As #FileNum2
    Dim NoText As String
     Print #FileNum2, NoText ' write out entire text file, the file is made if not there
     Close #FileNum2
    ' 2a)  Get the text file as a long single string
    Dim FileNum As Long: Let FileNum = FreeFile(1)                                    ' https://msdn.microsoft.com/en-us/vba/language-reference-vba/articles/freefile-function
    Dim PathAndFileName As String, TotalFile As String
     Let PathAndFileName = ThisWorkbook.Path & Application.PathSeparator & "NoText.txt"   '                                                               CHANGE TO SUIT                                                                                                         From vixer zyxw1234  : http://www.eileenslounge.com/viewtopic.php?f=30&t=34629     DF.txt https://app.box.com/s/gw941dh9v8sqhvzin3lo9rfc67fjsbic
    Open PathAndFileName For Binary As #FileNum 'Open Route to data. Binary is a fundamental type data input...
     Let TotalFile = Space(LOF(FileNum)) '....and wot receives it has to be a string of exactly the right length
    Get #FileNum, , TotalFile                                               'Debug.Print TotalFile
    Close #FileNum
     Call WtchaGot_Unic_NotMuchIfYaChoppedItOff(TotalFile)
    End Sub
    _... then I will see nothing at all in Notepad, and from my WotchaGot function it will tell me that I have
    vbCr & vbLf

    If I Let NoText = "x" , and repeat the experiment, I see in notepad .._
    Code:
    x
    _.. and my function tells me that I have
    "x" & vbCr & vbLf

    Here are some more experiments, and the results:
    Let NoText = "x" & vbCr & "x"
    "x" & vbCr & "x" & vbCr & vbLf
    Code:
    xx
    Let NoText = "x" & vbLf & "x"
    "x" & vbLf & "x" & vbCr & vbLf
    Code:
    xx
    Let NoText = "x" & vbCr & vbLf & "x"
    "x" & vbCr & vbLf & "x" & vbCr & vbLf
    Code:
    x
    x
    Let NoText = "x" & vbLf & vbCr & "x"
    "x" & vbLf & vbCr & "x" & vbCr & vbLf
    Code:
    xx
    If I repeat the experiment using extension .csv instead of .txt everywhere in my macro, then the results are identical.
    So it appears that notepad only recognises the pair vbCr & vbLf as a new line

    ( Note: if I open any of the files ( .txt or .csv ) in Excel , using any default settings, then for the case of the vbLf or the vbCr or the pair vbCr & vbLf then Excel always seems to add a line and I see
    _____ Workbook: NoText.txt ( Using Excel 2007 32 bit )
    Row\Col
    A
    1
    x
    2
    x
    Worksheet: NoText
    _____ Workbook: NoText.csv ( Using Excel 2007 32 bit )
    Row\Col
    A
    1
    x
    2
    x
    Worksheet: NoText

    For the case of using vbLf & vbCr, using the default settings opening in Excel the .txt file also gives the same result, but strangely for the .csv file we see an extra line
    _____ Workbook: NoText.csv ( Using Excel 2007 32 bit )
    Row\Col
    A
    1
    x
    2
    3
    x
    Worksheet: NoText
    Last edited by DocAElstein; 11-29-2020 at 01:15 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  2. #2
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,323
    Rep Power
    10
    Following on, and in support of, these Forum Posts:
    http://www.eileenslounge.com/viewtop...292266#p292266
    https://excelfox.com/forum/showthrea...ge51#post12776

    In one of those Posts we figured out how to get a text file 3 column list of the service´s Name , DisplayName and StartType, using a single PowerShell script commandlet.
    Here I want to automate that a bit.
    First I reduced the text file a bit to this
    Code:
     
    Name                                                   DisplayName                                                                                  StartType
    ----                                                   -----------                                                                                  ---------
    AarSvc_72b48                                           Agent Activation Runtime_72b48                                                                  Manual
    AJRouter                                               AllJoyn-Routerdienst                                                                            Manual
    ALG                                                    Gatewaydienst auf Anwendungsebene                                                               Manual
    ApHidMonitorService                                    AlpsAlpine SMBus Monitor Service                                                             Automatic
    The I took a look using this
    Code:
    Sub LookInFirstBitOfTextString()  '  https://excelfox.com/forum/showthread.php/2408-Windows-10-and-Office-Excel/page51#post12776
    ' Get the text file as a long single string
    Dim FileNum As Long: Let FileNum = FreeFile(1)                                    ' https://msdn.microsoft.com/en-us/vba/language-reference-vba/articles/freefile-function
    Dim PathAndFileName As String, TotalFile As String
     Let PathAndFileName = ThisWorkbook.Path & Application.PathSeparator & "test4lines.txt"   '                                                               CHANGE TO SUIT                                                                                                         From vixer zyxw1234  : http://www.eileenslounge.com/viewtopic.php?f=30&t=34629     DF.txt https://app.box.com/s/gw941dh9v8sqhvzin3lo9rfc67fjsbic
    Open PathAndFileName For Binary As #FileNum 'Open Route to data. Binary is a fundamental type data input...
     Let TotalFile = Space(LOF(FileNum)) '....and wot receives it has to be a string of exactly the right length
    Get #FileNum, , TotalFile                                               'Debug.Print TotalFile
    Close #FileNum
     Call WtchaGot_Unic_NotMuchIfYaChoppedItOff(TotalFile)
    End Sub
    That produced a total strong with rather a lot of CHR(0)s
    https://i.postimg.cc/t43HCQr9/Rather...of-Chr-0-s.jpg
    So I modified the code a bit to take them out, since I am not too interested in them, and I am not sure what they might do. This is a mod I would most likely want to do permanently, and initially now, I would like to do it as its obscuring the main stuff I want to see: That is easily done with TotalFile = Replace(TotalFile, Chr(0), "", 1, -1, vbBinaryCompare)
    After that it looks a bit better.
    I have 4 characters at the start, Chr(255) Chr(254) vbCr vbLf , which I can probably do away with as well, same again: TotalFile = Replace(TotalFile, Chr(255) & Chr(254) & vbCr & vbLf , "", 1, 1, vbBinaryCompare) ( Altertnativel we can just consider the Chr(255) & Chr(254) as the first line and disregard that later.)
    The title line I could probably do away with as well, as I know what it is, or rather I know the 3 header words that I am interested in, as well as the order that they come in, "Name DisplayName StartType"
    and
    I can forget about the second line as well, as it seems to be just some dashes used to underline the headers.
    So I will be disregarding the first 2 ( or 3 ) lines

    The line separator is as expected, vbCr & vbLf . ( There are few extra trailing ones. I can leave those, as I don’t think they will confuse much of my further plans for manipulating the total string

    My plan will be to split by the vbCr & vbLf to get 1 dimensional array or the rows.
    The separator just seems to be a lot of spaces. As I have three text things that I want on each row, and they appear to have no spaces in them, I can do a simple bit of text manipulation to get at those three words at each row.
    After that, putting each word in a “row” of a 2 D array of 3 “columns” will be convenient to then paste out in an Excel worksheet

    This does all that
    Code:
    ' make array for output
    Dim arrOut() As String: ReDim arrOut(1 To UBound(arrRws()) - 2, 1 To 3) ' we are ignoring the first 3 lines. The  UBound  of the 1 dimensional array is already 1 less then the lines we need because a 1 dimensional array starts at 0
    Dim Cnt As Long
        For Cnt = 1 To UBound(arrRws()) - 2
            If arrRws(Cnt + 2) = "" Then
            ' This should occur at the last empty rows, so we could consider jumping out of the loop here
            Else
            ' time to split the line string
            Dim Pos1 As Long: Let Pos1 = InStr(1, arrRws(Cnt + 2), "  ", vbBinaryCompare)
            Dim Nme As String: Let Nme = Left(arrRws(Cnt + 2), Pos1 - 1)
            Dim Pos3 As Long: Let Pos3 = Len(arrRws(Cnt + 2)) - InStrRev(arrRws(Cnt + 2), "  ", -1, vbBinaryCompare)
            Dim StrtTyp As String: Let StrtTyp = Right(arrRws(Cnt + 2), Pos3)
            Dim DispNme As String: Let DispNme = Replace(arrRws(Cnt + 2), Nme, "", 1, -1, vbBinaryCompare)
             Let DispNme = Replace(DispNme, StrtTyp, "", 1, -1, vbBinaryCompare)
             Let DispNme = Trim(DispNme)
            ' fill the array for output
             Let arrOut(Cnt, 1) = Nme: arrOut(Cnt, 2) = DispNme: arrOut(Cnt, 3) = StrtTyp
            End If
    
        Next Cnt

    The rest is just pasting that arrOut() directly in a spreadsheet
    Attached Files Attached Files
    Last edited by DocAElstein; 02-09-2022 at 06:33 PM.

  3. #3
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,323
    Rep Power
    10
    later...
    ….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. #4
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,323
    Rep Power
    10
    post for later use ... later
    ….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. #5
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,323
    Rep Power
    10
    post ti get URL
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  6. #6
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,323
    Rep Power
    10
    later ,,,.........
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  7. #7
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,323
    Rep Power
    10
    later -----------
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  8. #8
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,323
    Rep Power
    10
    post for later...
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  9. #9
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,323
    Rep Power
    10
    later ...
    ….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!!

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

    Convert Excel data range to XML type text file

    In support of this post
    https://excelfox.com/forum/showthrea...5355#post15355


    _____ Workbook: Sample excel file.xls ( Using Excel 2007 32 bit )
    Row\Col A B C D E F G H I
    1 Entity ID day month year time
    1
    <-- row number
    2
    700
    19
    2
    2021
    08:00
    2
    3
    700
    19
    2
    2021
    08:30
    3
    4
    700
    20
    2
    2021
    09:00
    4
    5
    701
    19
    2
    2021
    09:30
    5
    6
    6
    7
    2
    3
    4
    5
    <-- column number
    8
    9 Lr=5
    10 arrIn()=Range("A1:E5").Value 1 2
    3
    4
    5
    6
    11
    1
    Entity ID day month year time
    12
    2
    700
    19
    2
    2021
    08:00
    13
    3
    700
    19
    2
    2021
    08:30
    14
    4
    700
    20
    2
    2021
    09:00
    15
    5
    701
    19
    2
    2021
    09:30
    16
    6
    17 Example: arrIn(5, 1) = 701
    Worksheet: Sheet1

    text file output
    HTML Code:
    <forecast>
    <Entity>700</Entity>
    <data>
    <date>
    <day>19/<day>
    <month>2</month>
    <year>2021</year>
    </date>
    <time>08:00</time>
    <time>08:30</time>
    </data>
    <data>
    <date>
    <day>20/<day>
    <month>2</month>
    <year>2021</year>
    </date>
    <time>09:00</time>
    </data>
    </forcast>
    <forecast>
    <Entity>701</Entity>
    <data>
    <date>
    <day>19/<day>
    <month>2</month>
    <year>2021</year>
    </date>
    <time>09:30</time>
    </data>
    </forcast>
    Code:
    Option Explicit
    '
    Sub ExcelToXML()
    Rem 1 worksheets data info
    Dim Ws1 As Worksheet: Set Ws1 = ThisWorkbook.Worksheets.Item(1)
    Dim Lr As Long: Let Lr = Ws1.Range("A" & Rows.Count & "").End(xlUp).Row
    Dim arrRng() As Variant: Let arrRng() = Ws1.Range("A1:E" & Lr + 1 & "").Value '  +1 is a bodge to help me not get errors when checking 1 row above my data
    Rem 2  Do it
    Dim TotalFile As String
    Dim Rw As Long: Let Rw = 2 ' Main row count
    ' #STEP 1 Start
        Do While Rw <= Lr ' This keeps us going as long as data is there
         Let TotalFile = TotalFile & "<forecast>" & vbCr & vbLf & "<Entity>" & arrRng(Rw, 1) & "</Entity>" & vbCr & vbLf: Debug.Print TotalFile
        ' # STEP 2 start
         Let TotalFile = TotalFile & "<data>" & vbCr & vbLf & "<date>" & vbCr & vbLf & "<day>" & arrRng(Rw, 2) & "/<day>" & vbCr & vbLf & "<month>" & arrRng(Rw, 3) & "</month>" & vbCr & vbLf & "<year>" & arrRng(Rw, 4) & "</year>" & vbCr & vbLf & "</date>" & vbCr & vbLf & "<time>" & Format(arrRng(Rw, 5), "hh" & ":" & "mm") & "</time>" & vbCr & vbLf: Debug.Print TotalFile
            '  #STEP 3 START
            ' Check   if Entity ID in first row = Entity ID in 2nd row and date in first row = date in 2nd row then      repeat STEP 3 for 2nd row and so on
            Do While Rw + 1 <= Lr And arrRng(Rw, 1) = arrRng(Rw + 1, 1) And arrRng(Rw, 2) = arrRng(Rw + 1, 2)
             Let TotalFile = TotalFile & "<time>" & Format(arrRng(Rw + 1, 5), "hh" & ":" & "mm") & "</time>" & vbCr & vbLf: Debug.Print TotalFile
             Let Rw = Rw + 1 ' This brings us to the line we just filled in
            Loop
         Let TotalFile = TotalFile & "</data>" & vbCr & vbLf: Debug.Print TotalFile
            
            ' Chect  if Entity ID in first row = Entity ID in 2nd row and date in first row not equals to date in 2nd row then    repeat STEP 2 for 2nd row and so on
            Do While Rw + 1 <= Lr And arrRng(Rw, 1) = arrRng(Rw + 1, 1) '   And Not arrRng(Rw, 2) = arrRng(Rw + 1, 2)
             Let TotalFile = TotalFile & "<data>" & vbCr & vbLf & "<date>" & vbCr & vbLf & "<day>" & arrRng(Rw + 1, 2) & "/<day>" & vbCr & vbLf & "<month>" & arrRng(Rw + 1, 3) & "</month>" & vbCr & vbLf & "<year>" & arrRng(Rw + 1, 4) & "</year>" & vbCr & vbLf & "</date>" & vbCr & vbLf & "<time>" & Format(arrRng(Rw + 1, 5), "hh" & ":" & "mm") & "</time>" & vbCr & vbLf: Debug.Print TotalFile
             Let Rw = Rw + 1 ' This brings us to the line we just filled in
            Loop
         Let TotalFile = TotalFile & "</data>" & vbCr & vbLf: Debug.Print TotalFile
        
            '  #STEP 3 END
            '  STEP 2 END
         Let TotalFile = TotalFile & "</forcast>" & vbCr & vbLf: Debug.Print TotalFile
         Let Rw = Rw + 1 '  ' This brings us to the next line
        '    STEP 1 END
        Loop '  While Rw <= Lr
     
     Let TotalFile = Replace(TotalFile, "</data>" & vbCr & vbLf & "</data>" & vbCr & vbLf, "</data>" & vbCr & vbLf, 1, -1, vbBinaryCompare): Debug.Print TotalFile ' I end up with a double  "</data>" & vbCr & vbLf
    Rem 3   Make text file
    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 & "\" & "XML_Stuff.txt"  ' ' CHANGE TO SUIT  ' Will be made if not there
     Open PathAndFileName2 For Output As #FileNum2
     Print #FileNum2, TotalFile ' write out entire text file
     Close #FileNum2
    
    End Sub
    
    '    <forecast>             ' #STEP 1 Start     Print #intFile, "<Forecast>"
    '    <Entity>700</Entity>   ' #STEP 1 Start     Print #intFile, "<Entity>" & Entity ID & "</Entity>"
    '    <data>                 ' #STEP 2 Start     Print #intFile, "<Data>"
    '    <date>                 ' #STEP 2 Start     Print #intFile, "<date>"
    '    <day>19</day>          ' #STEP 2 Start     Print #intFile, "<day>" & day &
    '    <month>2</month>       ' #STEP 2 Start              "</day><month>" & month & "</month>
    '    <year>2021</year>      ' #STEP 2 Start              <year>" & yeear & "</year>"
    '    </date>                ' #STEP 2 Start                  </date>"
    '    <time>8:00</time>      ' #STEP 3 START     Print #intFile, "<time>" & time & "</time>"
    '          Check  if Entity ID in first row = Entity ID in 2nd row
                ' and date in first row = date in 2nd row then
        '    <time>8:30</time>      ' repeat STEP 3 for 2nd row and so on
        '    </data>           ' #STEP 3 END
        '          Check  if Entity ID in first row = Entity ID in 2nd row
                    ' and date in first row IS NOT =   date in 2nd row then'
            '    repeat STEP ??3??  2 for 2nd row and so on
            '    <data>
            '    <date>
            '    <day>20</day>
            '    <month>2</month>
            '    <year>2021</year>
            '    </date>
            '    <time> ??8:00??  9.00   </time>
            '    </data>
        '    </forecast>       ' STEP 2 END           Print #intFile, "</forecast>"
    
    
    '    If Entity ID is not same as in previous row repeat STEP 1
    '
    '    <forecast>
    '    <Entity>701</Entity>
    '    <data>
    '    <date>
    '    <day>19</day>
    '    <month>2</month>
    '    <year>2021</year>
    '    </date>
    '    <time>9:30</time>
    '    </data>
    '    </forecast>
    '    <forecast>
    
    
    
    Attached Files Attached Files
    Last edited by DocAElstein; 02-17-2021 at 08:39 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!!

Similar Threads

  1. Replies: 109
    Last Post: 03-29-2024, 07:01 PM
  2. Replies: 4
    Last Post: 01-30-2022, 04:05 PM
  3. Replies: 29
    Last Post: 06-09-2020, 06:00 PM
  4. Notes tests. Excel VBA Folder File Search
    By DocAElstein in forum Test Area
    Replies: 39
    Last Post: 03-20-2018, 04:09 PM
  5. Collate Data from csv files to excel sheet
    By dhiraj.ch185 in forum Excel Help
    Replies: 16
    Last Post: 03-06-2012, 07:37 PM

Posting Permissions

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