Page 12 of 12 FirstFirst ... 2101112
Results 111 to 115 of 115

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

  1. #111
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    This is post 111, 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#post23979
    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=23979&viewfull=1#post23979
    https://www.excelfox.com/forum/showt...V-stuff/page12
    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







    In support of these forum posts
    https://www.excelfox.com/forum/showt...ll=1#post23969
    https://eileenslounge.com/viewtopic....313975#p313975



    Now here’s a thing….
    Quote Originally Posted by SpeakEasy
    uising the (hidden) ExtendedProperty property ...
    .....need to get hold of [fx]propkey.h[/fx], a header file in the Windows SDK. That file currently lists over 1000 extended properties (although many are not related to files or folders)
    https://eileenslounge.com/viewtopic....313961#p313961

    After a bit of initial looking into this,

    https://www.excelfox.com/forum/showt...ll=1#post23971
    https://www.excelfox.com/forum/showt...ll=1#post23969
    https://eileenslounge.com/viewtopic....313971#p313971
    MMPropertyTest https://app.box.com/s/27u7dyjee3rez44pdjq52uu2e7tgzu8v
    https://eileenslounge.com/viewtopic....314037#p314037
    propkey h.txt https://app.box.com/s/q8klctlcfka8s1uecklbf15n75cxc3v2
    , the TLDR is that I got a text file, propkey h.txt , with useful things in it. I want to get a more simpler list of stuff from that. This Thread is the place to do that,

    propkey h.txt What does it look like
    It look nice and well ordered, - do a search for example on a size property, and we see it as part of an already quite well structured list
    https://i.postimg.cc/bvbCYCh1/propkey-h.jpg
    Attachment 5748

    This is that text, as seen on the picture above, in 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 }
    With a typical macro like this un, we can take a look at that. (We are basically splitting the text up using something that appears to be used once for every property ,
    // Name: System.
    )
    Code:
    Option Explicit
    '   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=23979&viewfull=1#post23979
    Sub ExtendedPropertiesList()
    ' Rem 1 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 & "propkey h.txt"   '
    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
    '  Or  http://www.eileenslounge.com/viewtopic.php?p=295782&sid=f6dcab07c4d24e00e697fe4343dc7392#p295782
     Let TotalFile = Input(LOF(FileNum), FileNum)
    Close #FileNum
    ' Rem 2 Split the Prophs
    Dim arrProphs() As String: Let arrProphs() = Split(TotalFile, "//  Name:     System.", -1, vbBinaryCompare)
    ' 2a) Quick look at list
    Dim LCnt As Long: Let LCnt = UBound(arrProphs())
    Dim Rws() As Variant, Clms() As Variant, VertList() As Variant
     Let Rws() = Evaluate("ROW(1:" & LCnt + 1 & ")/ROW(1:" & LCnt + 1 & ")")
     Let Clms() = Evaluate("ROW(1:" & LCnt + 1 & ")")
     Let VertList() = Application.Index(arrProphs(), Rws(), Clms())
     Let Me.Range("A1:A" & LCnt & "") = VertList()
    Me.Cells.WrapText = False
    ' 2b) Look at some example props   using function    WtchaGot_Unic_NotMuchIfYaChoppedItOff
    '     The next text is copied from cell A 350
    '       "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 }
    '
    '    "
    '    The next text is copied from watch window at  arrProphs()(349)
    '        : arrProphs()(349) : "Size -- PKEY_Size
    '    //  Type:     UInt64 -- VT_UI8
    '    //  FormatID: (FMTID_Storage) {B725F130-47EF-101A-A5F1-02608C9EEBAC}, 12 (PID_STG_SIZE)
    '    //
    '    //
    '    DEFINE_PROPERTYKEY(PKE"
     Call WtchaGot_Unic_NotMuchIfYaChoppedItOff(arrProphs()(349), "Size349")
    
    
    Stop
    End Sub
    That macro and the function , WtchaGot_Unic_NotMuchIfYaChoppedItOff( , in the uploaded file



    Some results and discussions in next post
    Attached Files Attached Files
    Last edited by DocAElstein; 02-07-2024 at 06:42 PM.

  2. #112
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    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.

  3. #113
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Some notes in support of this discovery,
    https://www.excelfox.com/forum/showt...ws-Based-Files -
    https://www.excelfox.com/forum/showt...ws-Based-Files


    For Eileen’s Lounge https://www.eileenslounge.com/viewto...314893#p314893
    Hi,
    Some weird co incidences have hit me in the past few years, (including some similar to those that happened to same bad people that convinced them they were the chosen one to take over the world) ….
    Maybe in my case I am imagining it, or it is just Microsoft and Google taking over my PC and my mind…
    So here is one, not so dramatic, but worth a follow up here , I thought:….. I wanted to take a break from my experiments with Folder item properties, (and some naughty things I had better not mention), so for some light relief I did some mundane stuff of tidying up a forum by looking at soft deleted or closed, marked as possible spam Threads from years ago, waiting for someone like me to delete them permanently or reinstate them...
    Fairly soon I coincidently hit this one, in a dead Outlook sub forum of all places!? (Further strangely its posted by a "guest" in 2017. As far as I know it’s only ever been possible to post there after registering, and certainly it was the case in 2017, so it’s something akin to a virgin birth as well)
    https://www.excelfox.com/forum/showt...ws-Based-Files


    Now here is the strange coincidence, it’s a list of the names of "All Extended Property Of Windows Based Files" , which is what is related to what has been uppermost in my mind just now, and the main subject of this Thread.
    They are given in that strange {B725F130-47EF-101A-A5F1-02608C9EEBAC}, 14 form.
    Now I remember a long time ago in a Thread at Eileen’s Lounge I did something like running them sort of things in PowerShell, (I can’t remember why now, but since then I get a lot of new applications starting when I restart the computer I did it on??)

    So I am spending the rest of the day, or days, trying to find that old Thread, because I am thinking that God maybe had suggested I do it, in his mysterious way of moving and doing things.

    In the meantime I thought I would share this information, in case anyone has any thoughts on:
    (_ if I am the chosen one )
    _ how I might be able to somehow do things with these to get a file property information.? Possibly this weird variation on a theme might give another interesting solution to this thread, or point me in some useful direction. Or could I do anything else with them? For example, could these or what they might refer to help me to put things, programs, dlls things or the such, somewhere that might help me solve my recent related XP problem ?

    I put those things in a text file, ( with and without the headings ). There are 154, which is less than both the main two ways discussed here so far,
    the few hundred WSO Properties ( like from objWSOFolder.GetDetailsOf(FldrItm, 1) )
    , and
    the 1054 WSO Propherkeys (correspondingly like objWSOPassName.ExtendedProperty("System." & "Size") )
    , so I am not sure which of those two, if any, they may be related to?

    Thanks
    Alan


    Reply from SpeakEasy, https://www.eileenslounge.com/viewto...314905#p314905
    >They are given in that strange form

    These are SCIDs, an alternative method of using ExtendedProperty.

    So, if you examine the propkey.h file I pointed you to previously, you will see these 'strange' numbers as well as the [fx]System. [/fx]name strings. They are an alternate method to access the property, and basically consist of GUID representing the Format ID (FMTID) defining a property set, and a PID that identifies a specific property within that set. Together these make up what Microsoft refer to as a SCID, and can be passed to ExtendedProperty as a string instead of the human-readable string

    Here for example is the propkey.h entry for System.Size, with the SCID highlighted

    [fx]// 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 }[/fx]

    And here is how we can use it

    Code:
        Dim objShell As New Shell
                
        With objShell.Namespace("D:\downloads\deletemesoon").ParseName("20220501_103054.jpg")  ' your path and filename go here
            Debug.Print "Accurate size: " & .ExtendedProperty("System.Size")
            Debug.Print "Accurate size: " & .ExtendedProperty("{B725F130-47EF-101A-A5F1-02608C9EEBAC}, 12")
        End With
    (I don't expect this will fix your XP problem)
    Last edited by DocAElstein; 03-04-2024 at 02:17 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  4. #114
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    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.

  5. #115
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    This is post
    https://www.excelfox.com/forum/showt...ll=1#post24047
    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=24047&viewfull=1#post24047
    https://www.excelfox.com/forum/showt...ge12#post24047
    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#post24047

    Following on from the last post
    Quote Originally Posted by DocAElstein View Post
    , 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)...
    Later, after getting me morning Buns



























    Code:
    Address.Country -- PKEY_Address_Country
    
    //  Type:     String -- VT_LPWSTR  (For variants: VT_BSTR)
    
    //  FormatID: {C07B4199-E1DF-4493-B1E1-DE5946FB58F8}, 100
    
    DEFINE_PROPERTYKEY(PKEY_Address_Country, 0xC07B4199, 0xE1DF, 0x4493, 0xB1, 0xE1, 0xDE, 0x59, 0x46, 0xFB, 0x58, 0xF8, 100);
    
    #define INIT_PKEY_Address_Country { { 0xC07B4199, 0xE1DF, 0x4493, 0xB1, 0xE1, 0xDE, 0x59, 0x46, 0xFB, 0x58, 0xF8 }, 100 }
    
    
    
    
    "Address.Country -- PKEY_Address_Country
    //  Type:     String -- VT_LPWSTR  (For variants: VT_BSTR)
    //  FormatID: {C07B4199-E1DF-4493-B1E1-DE5946FB58F8}, 100
    DEFINE_PROPERTYKEY(PKEY_Address_Country, 0xC07B4199, 0xE1DF, 0x4493, 0xB1, 0xE1, 0xDE, 0x59, 0x46, 0xFB, 0x58, 0xF8, 100);
    #define INIT_PKEY_Address_Country { { 0xC07B4199, 0xE1DF, 0x4493, 0xB1, 0xE1, 0xDE, 0x59, 0x46, 0xFB, 0x58, 0xF8 }, 100 }
    
    "
    
    
    
    
    
    "Audio.Compression -- PKEY_Audio_Compression
    //  Type:     String -- VT_LPWSTR  (For variants: VT_BSTR)
    //  FormatID: (FMTID_AudioSummaryInformation) {64440490-4C8B-11D1-8B70-080036B11A03}, 10 (PIDASI_COMPRESSION)
    //
    //  
    DEFINE_PROPERTYKEY(PKEY_Audio_Compression, 0x64440490, 0x4C8B, 0x11D1, 0x8B, 0x70, 0x08, 0x00, 0x36, 0xB1, 0x1A, 0x03, 10);
    #define INIT_PKEY_Audio_Compression { { 0x64440490, 0x4C8B, 0x11D1, 0x8B, 0x70, 0x08, 0x00, 0x36, 0xB1, 0x1A, 0x03 }, 10 }
    
    "








    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=314837#p314837
    https://www.eileenslounge.com/viewtopic.php?f=21&t=40701&p=314836#p314836
    https://www.eileenslounge.com/viewtopic.php?f=27&t=40621&p=314621#p314621
    https://www.eileenslounge.com/viewtopic.php?f=27&t=40621&p=314619#p314619
    https://www.eileenslounge.com/viewtopic.php?f=27&t=40621&p=314600#p314600
    https://www.eileenslounge.com/viewtopic.php?f=27&t=40621&p=314599#p314599
    https://www.eileenslounge.com/viewtopic.php?f=27&t=40621&p=314274#p314274
    https://www.eileenslounge.com/viewtopic.php?f=27&t=40621&p=314229#p314229
    https://www.eileenslounge.com/viewtopic.php?f=27&t=40621&p=314195#p314195
    https://www.eileenslounge.com/viewtopic.php?f=36&t=39706&p=314110#p314110
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40597&p=314081#p314081
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40597&p=314078#p314078
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=314062#p314062
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40597&p=314054#p314054
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313971#p313971
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313909#p313909
    https://www.eileenslounge.com/viewtopic.php?f=27&t=40574&p=313879#p313879
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313859#p313859
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313855#p313855
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313848#p313848
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313843#p313843
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313792#p313792
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40560&p=313771#p313771
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40560&p=313767#p313767
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40560&p=313746#p313746
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40560&p=313744#p313744
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40560&p=313741#p313741
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313622#p313622
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313575#p313575
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313573#p313573
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313563#p313563
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533&p=313555#p313555
    https://www.eileenslounge.com/viewtopic.php?f=30&t=40533
    https://www.eileenslounge.com/viewtopic.php?f=39&t=40265&p=313468#p313468
    https://www.eileenslounge.com/viewtopic.php?f=42&t=40505&p=313411#p313411
    https://www.eileenslounge.com/viewtopic.php?f=32&t=40473&p=313384#p313384
    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    Last edited by DocAElstein; 03-05-2024 at 01:17 AM.

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
  •