Results 1 to 10 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,451
    Rep Power
    10
    This is post 112, Page 12 from this Thread we are in https://www.excelfox.com/forum/showt...-VBA-CSV-stuff
    https://www.excelfox.com/forum/showt...ll=1#post23981
    https://www.excelfox.com/forum/showthread.php/2559-Notes-tests-text-files-manipulation-of-text-files-in-Excel-and-with-Excel-VBA-CSV-stuff?p=23981&viewfull=1#post23981
    https://www.excelfox.com/forum/showt...ge12#post23981
    https://www.excelfox.com/forum/showthread.php/2559-Notes-tests-text-files-manipulation-of-text-files-in-Excel-and-with-Excel-VBA-CSV-stuff/page12#post23981





    More detailed look at information from an extended property
    This is the actual text copied room the text file,
    Code:
     //  Name:     System.Size -- PKEY_Size
    //  Type:     UInt64 -- VT_UI8
    //  FormatID: (FMTID_Storage) {B725F130-47EF-101A-A5F1-02608C9EEBAC}, 12 (PID_STG_SIZE)
    //
    //  
    DEFINE_PROPERTYKEY(PKEY_Size, 0xB725F130, 0x47EF, 0x101A, 0xA5, 0xF1, 0x02, 0x60, 0x8C, 0x9E, 0xEB, 0xAC, 12);
    #define INIT_PKEY_Size { { 0xB725F130, 0x47EF, 0x101A, 0xA5, 0xF1, 0x02, 0x60, 0x8C, 0x9E, 0xEB, 0xAC }, 12 }
    Here are those 7 ( 8 ) lines broken down into characters,
    Code:
     "Size " & "-" & "-" & " PKEY" & "_" & "Size" & vbCr & vbLf
    "/" & "/" & "  Type" & ":" & "     UInt64 " & "-" & "-" & " VT" & "_" & "UI8" & vbCr & vbLf
    "/" & "/" & "  FormatID" & ":" & " " & "(" & "FMTID" & "_" & "Storage" & ")" & " " & Chr(123) & "B725F130" & "-" & "47EF" & "-" & "101A" & "-" & "A5F1" & "-" & "02608C9EEBAC" & Chr(125) & "," & " 12 " & "(" & "PID" & "_" & "STG" & "_" & "SIZE" & ")" & vbCr & vbLf
    "/" & "/" & vbCr & vbLf
    "/" & "/" & "  " & vbCr & vbLf
    "DEFINE" & "_" & "PROPERTYKEY" & "(" & "PKEY" & "_" & "Size" & "," & " 0xB725F130" & "," & " 0x47EF" & "," & " 0x101A" & "," & " 0xA5" & "," & " 0xF1" & "," & " 0x02" & "," & " 0x60" & "," & " 0x8C" & "," & " 0x9E" & "," & " 0xEB" & "," & " 0xAC" & "," & " 12" & ")" & ";" & vbCr & vbLf
    "#" & "define INIT" & "_" & "PKEY" & "_" & "Size " & Chr(123) & " " & Chr(123) & " 0xB725F130" & "," & " 0x47EF" & "," & " 0x101A" & "," & " 0xA5" & "," & " 0xF1" & "," & " 0x02" & "," & " 0x60" & "," & " 0x8C" & "," & " 0x9E" & "," & " 0xEB" & "," & " 0xAC " & Chr(125) & "," & " 12 " & Chr(125) & vbCr & vbLf
    vbCr & vbLf
    I don't see any "hidden character" surprizes, or anything else of interest or concern at this stage. So…..

    How to move on to get a list of just the property name word that we need ( in the current example that word is Size )
    The last macro put the property name, ( after the System. Bit ), and all following details in a 1 dimensional array that was then conveniently pasted out into a list in a worksheet. I could forget about the worksheet list initially and then within VBA arrays efficiently get at the first word bits I wants. But text is cheap and Excel is all about ordering boxes of things into a convenient list. Furthermore I have efficient ways of manipulating lists using excel function evaluate range ways. So I think it will be convenient to keep the full text in the first column and get the name words initially efficiently in the another column
    See here https://www.excelfox.com/forum/showt...ll=1#post23983


    Simple text file of Propherties
    Using the final file obtained there ( https://www.excelfox.com/forum/showt...ll=1#post23983 ] ) , it is convenient to make a simple text file looking like this, ( just showing the first and last few lines, ( there are 1054 in total )
    Code:
    Address.Country
    Address.CountryCode
    Address.Region
    Address.RegionCode
    Address.Town
    Audio.ChannelCount
    Audio.Compression
    Audio.EncodingBitrate
    Audio.Format
    Audio.IsVariableBitRate
    Audio.PeakValue
    Audio.SampleRate
    Audio.SampleSize
    Audio.StreamName
    Audio.StreamNumber
    Calendar.Duration
    Calendar.IsOnline
    Calendar.IsRecurring
    Calendar.Location
    Calendar.OptionalAttendeeAddresses
    Calendar.OptionalAttendeeNames
    Calendar.OrganizerAddress
    Calendar.OrganizerName
    Calendar.ReminderTime
    Calendar.RequiredAttendeeAddresses
    Calendar.RequiredAttendeeNames
    Calendar.Resources
    Calendar.ResponseStatus
    Calendar.ShowTimeAs
    Calendar.ShowTimeAsText
    Communication.AccountName
    Communication.DateItemExpires
    Communication.Direction
    Communication.FollowupIconIndex
    Communication.HeaderItem
    Communication.PolicyTag
    Communication.SecurityFlags
    Communication.Suffix
    Communication.TaskStatus
    Communication.TaskStatusText
    Computer.DecoratedFreeSpace
    Contact.AccountPictureDynamicVideo
    Contact.AccountPictureLarge
    Contact.AccountPictureSmall
    Contact.Anniversary
    Contact.AssistantName
    Contact.AssistantTelephone
    Contact.Birthday
    Contact.BusinessAddress
    Contact.BusinessAddress1Country
    Contact.BusinessAddress1Locality
    Contact.BusinessAddress1PostalCode
    Contact.BusinessAddress1Region
    Contact.BusinessAddress1Street
    Contact.BusinessAddress2Country
    Contact.BusinessAddress2Locality
    Contact.BusinessAddress2PostalCode
    Contact.BusinessAddress2Region
    Contact.BusinessAddress2Street
    Contact.BusinessAddress3Country
    Contact.BusinessAddress3Locality
    Contact.BusinessAddress3PostalCode
    Contact.BusinessAddress3Region
    Contact.BusinessAddress3Street
    Contact.BusinessAddressCity
    Contact.BusinessAddressCountry
    Contact.BusinessAddressPostalCode
    Contact.BusinessAddressPostOfficeBox
    Contact.BusinessAddressState
    Contact.BusinessAddressStreet
    Contact.BusinessEmailAddresses
    Contact.BusinessFaxNumber
    Contact.BusinessHomePage
    Contact.BusinessTelephone
    Contact.CallbackTelephone
    Contact.CarTelephone
    Contact.Children
    Contact.CompanyMainTelephone
    Contact.ConnectedServiceDisplayName
    Contact.ConnectedServiceIdentities
    Contact.ConnectedServiceName
    Contact.ConnectedServiceSupportedActions
    Contact.DataSuppliers
    Contact.Department
    Contact.DisplayBusinessPhoneNumbers
    Contact.DisplayHomePhoneNumbers
    Contact.DisplayMobilePhoneNumbers
    Contact.DisplayOtherPhoneNumbers
    Contact.EmailAddress
    Contact.EmailAddress2
    Contact.EmailAddress3
    Contact.EmailAddresses
    Contact.EmailName
    Contact.FileAsName
    Contact.FirstName
    Contact.FullName
    Contact.Gender
    Contact.GenderValue
    Contact.Hobbies
    .
    .
    .
    .
    .
    
    Task.Owner
    Video.Compression
    Video.Director
    Video.EncodingBitrate
    Video.FourCC
    Video.FrameHeight
    Video.FrameRate
    Video.FrameWidth
    Video.HorizontalAspectRatio
    Video.IsSpherical
    Video.IsStereo
    Video.Orientation
    Video.SampleSize
    Video.StreamName
    Video.StreamNumber
    Video.TotalBitrate
    Video.TranscodedForSync
    Video.VerticalAspectRatio
    Volume.FileSystem
    Volume.IsMappedDrive
    ( Note in final use, we must include a leading System. )
    Using the final file obtained there ( https://www.excelfox.com/forum/showt...ll=1#post23983 ] ) , this code in the worksheet object tab name Ext(Hidden)proph


    Code:
    '       WSO_PropNamesExtended.xls          https://app.box.com/s/sv5rxxtwv1v18ir3xmi6gdti8pawx0jq
    Sub MakeExtProphsTextFile()  '   https://www.excelfox.com/forum/showthread.php/2559-Notes-tests-text-files-manipulation-of-text-files-in-Excel-and-with-Excel-VBA-CSV-stuff?p=23981&viewfull=1#post23981
    Rem 1  Copy to Clipboard
    Me.Range("E2:E1055").Copy  '                                                                  Selection.Copy  '  Or   Application.SendKeys "^c"
        With GetObject("New:{1C3B4210-F441-11CE-B9EA-00AA006B1A69}")  '    http://web.archive.org/web/20200124185244/http://excelmatters.com/2013/10/04/late-bound-msforms-dataobject/
        Dim StringBack As String ' This is for the entire text held for the range in the windows clipboard after a  .Copy
         .GetFromClipboard: Let StringBack = .GetText()
                '                                                                        .Clear
                '                                                                        .SetText StringBack
                '                                                                        .PutInClipboard
        End With
     Let StringBack = Left(StringBack, Len(StringBack) - 2) ' Get rid of the extra vbcr & vblf caused by  .copy
    Rem 2
    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 & "\ExtProphs.txt"  '   ' CHANGE TO SUIT  
     Open PathAndFileName2 For Output As #FileNum2   '  ' Will be made if not there
     Print #FileNum2, StringBack ' write out entire text file
     Close #FileNum2
    
    End Sub
    






    Excel File with coding in:
    WSO_PropNamesExtended.xls https://app.box.com/s/sv5rxxtwv1v18ir3xmi6gdti8pawx0jq

    Text file made from above coding
    ExtProphs.txt https://app.box.com/s/rcl6mubx42xgwh0r9rt3fxjv18i7vmxs


    ( Text file used previously, - the large one with all Propherty details, file obtained from the official Microsoft propkey.h, a header file in the Windows SDK stuff, https://www.eileenslounge.com/viewto...313961#p313961
    propkey h.txt https://app.box.com/s/r9jx8r8qhs1g0phvg20f5penmhfetbcg
    )
    Attached Files Attached Files
    Last edited by DocAElstein; 02-10-2024 at 02:48 AM.

  2. #2
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,451
    Rep Power
    10
    Reply to last post, (Reply to SpeakEasy), Uncensored Version

    Quote Originally Posted by SpeakEasy
    https://www.eileenslounge.com/viewto...314905#p314905
    These are SCIDs, an alternative method of using ExtendedProperty…..
    Thanks for all that. Interesting. I expect I will come back here often and ponder all that.
    I have come across the {weird number in curly bracket unique identifier GUID things}, - I am not so totally sure what they are about but have used them and messed with them in a thread I am still looking for. ( I also have used them as a way to Late bind, and never really got the point so good, and I think in the thread I am looking for, I was randomly finding them on the registry and messing with them trying to figure out what they are about or what they did. (Often they seemed to "initiate" things on my computer to always start, things I never knew I had)
    It’s all a bit confusing for me, all these new terms, but never the less very helpful to have it all here as I expect eventually it may all fall in to place, when I re read, discover things, and keep experimenting, etc.

    I had spent some time already looking in detail at the text like file you pointed me to. I examined it carefully to see exactly what characters are in it. ( https://www.excelfox.com/forum/showt...ge12#post23981 You do get what you see, - there are no strange "hidden" characters in it), so I made notes on it, isolated the names and went on to experiment using the name bits from it.
    ( https://www.excelfox.com/forum/showt...ge59#post23983
    https://www.excelfox.com/forum/showt...ge4#post239729

    I was going to reference all that in some concluding feedback here, but then got unexpectedly stuck on the XP issue.
    I had pulled out a list of all 1054 names to put in .ExtendedProperty("System.name")
    , so I the am going to go back to that now and pull out the SCIDs , ( I am first getting my masks, disinfectant, surgical gloves etc. ready, - googling tells me SCID is some weakness in immune system caused by playing chess on computers, - could be some early experiments of Bill Gates maybe, to distribute viruses in operating systems which finally led to the Coronavirus)

    I had not noticed yet that that the GUIDs in that forum post I found tied up with the ones in the propkey h text file thing. I see now they do, thanks for the heads up. (These GUID things seem to have their ugly head all over the place so my first reaction was to ignore the ones in the propkey h text file thing , Lol.? )
    ( It’s possibly falling into place now, I see now that the mysterious forum post I found was possibly planted in by a forth columnist working for Microsoft or Bill Gates. I expect getting rid of that post will be like trying to cut out Microsoft Edge. I may have to just try to quarantine/ isolate it somehow, or limit its resources to contain it a bit)

    Thanks for the enlightening reply,
    Alan

    P.S. A bit of Laymen lateral thinking… These GUIDs refer to other stuff, often I think some sort of sub programs, libraries of stuff, including perhaps functions / programs, ( dll and COM codswallops & co ) that may or may not be available. I wonder if when I look now at the relevant GUIDs , then me or someone smarter may be able to identify some "package/ download cabinet or kitchen sink" or whatever, that I am missing on my XP machines that is causing my XP problem ??
    Last edited by DocAElstein; 03-04-2024 at 02:39 PM.

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
  •