Silverfrost Forums

Welcome to our forums

conveting REGQUERYVALUEEX to /64

7 Jun 2019 10:49 #23744

Dan's example of problems with SDBG ( or is it SDBG64 ? ) has provided a number of questions for me about how to convert to /64. It also shows some interesting problems accessing the registry. His example code is use mswin Integer, external :: processor_id jj= processor_id () end !--------------------------------

      integer function processor_id () 
! 
!       With thanks to John Horspool 2008-04-02 
! 
   use mswin 
   CHARACTER*400 LDATA 
   CHARACTER*80 getenv@, IDENTIFIER 
   CHARACTER*80 CPU_stepping, CPU_description 
   integer   n_processorsTotalGetEnv 
   character*256 ResultsToSave(10) 
   integer iVersionOfTesrResFile 

        LSTR=400 

        k = REGOPENKEYEX(HKEY_LOCAL_MACHINE, & 
         'HARDWARE\DESCRIPTION\System\CentralProcessor\0', 0,KEY_READ,MyKey) 

   CPU_description= ' N/A ' 
        if (MyKey.GT.0) then 
          k = REGQUERYVALUEEX(MyKey,'ProcessorNameString', & 
              CORE4(0),CORE4(0),LDATA,LSTR) 
!          WRITE(*,'(a,a)')' Processor : ', LDATA(1:LSTR) 
     CPU_description = LDATA(1:min(80,LSTR)) 
        endif 

   k = REGCLOSEKEY(MyKey) 

!   write(*,*) getenv@('PROCESSOR_IDENTIFIER')    
!   write(*,*) 'Number of cores=', getenv@('NUMBER_OF_PROCESSORS') 

       READ(getenv@('NUMBER_OF_PROCESSORS'),*)n_processorsTotalGetEnv 
       Write (*,*) ' Number of Processors/cores/threads= ', & 
       n_processorsTotalGetEnv, ' ', getenv@('PROCESSOR_IDENTIFIER') 
       Read (getenv@('PROCESSOR_IDENTIFIER'),'(a)') CPU_stepping 

   processor_id=2 
        end function  

I have a number of questions about this example:

  1. Is the use of a 'system' or intrinsic character function valid in an internal READ, eg 'READ(getenv@('NUMBER_OF_PROCESSORS'),)n_processorsTotalGetEnv ' I would use a character? variable first, as below, but is it necessary ? IDENTIFIER = getenv@('NUMBER_OF_PROCESSORS') READ(IDENTIFIER,*) n_processorsTotalGetEnv '

  2. When converting the following to /64, does 'CORE4(0)' need to be changed for 64-bit addressing ? It appears to work. ' k = REGQUERYVALUEEX(MyKey,'ProcessorNameString', & CORE4(0),CORE4(0),LDATA,LSTR) '

  3. The use of ' CHARACTER*80 getenv@, IDENTIFIER ' does not work well for me. What do we do for environment variables that are longer than 80 characters, eg PATH. Should getenv@ be declared as external, or not declared at all ?

  4. I included extra code to get the system MHz from the registry, as: integer4 LSTR, k, myKey, word_type, cpu_mhz INTEGER2 CPU_xx(2) integer1 kkkk(4) equivalence ( CPU_xx, kkkk ) ... word_type = 0 CPU_xx = 0 LSTR = 4 k = REGQUERYVALUEEX (MyKey, '~MHz', CORE4(0), word_type, CPU_xx, LSTR) write (,) 'word_type=',word_type, cpu_xx, lstr, k CPU_MHz = cpu_xx(1) WRITE (,'(i0,1x,i0,a,i8)') k, Lstr,' MHz : ', CPU_MHz, kkkk

~MHz is listed as a REG_DWORD In this call word_type indicates the result is a Dword (4-byte?), but the value returned is 2-byte then padded with 2 spaces. I can't explain this result either.

Any suggestions ?

Thanks and thinking of John Horspool

John

7 Jun 2019 11:13 #23745

For those interested in my expanded registry inquiry, my incomplete /64 code is: program test_processor_id use mswin Integer, external :: processor_id integer jj jj = processor_id () end program test_processor_id !--------------------------------

  integer function processor_id () 
! 
!       With thanks to John Horspool 2008-04-02 
! 
   use mswin 
   CHARACTER*400 LDATA 
   CHARACTER*80 getenv@, IDENTIFIER, num_process, ftn95_ver, ftn95_path
   CHARACTER*80 CPU_stepping, CPU_description, PC_Name, PC_Maker
   INTEGER*2    CPU_xx(2)
   integer      LSTR, k, myKey, word_type, cpu_mhz, n_process
!
! Get ProcessorNameString from Registry : HARDWARE\DESCRIPTION\System\CentralProcessor\0
!
        write (*,'(/a,a)') ' Reading Processor Name from Registry :','HARDWARE\DESCRIPTION\System\CentralProcessor\0'
        k = REGOPENKEYEX ( HKEY_LOCAL_MACHINE, 'HARDWARE\DESCRIPTION\System\CentralProcessor\0',   &
                           0, KEY_READ, MyKey ) 
        write (*,'(a,i0,a,i0)') ' REGOPENKEYEX = ',k, ' : MyKey = ',MyKey

        CPU_description = ' N/A ' 
        CPU_stepping    = ' N/A ' 
        if ( MyKey > 0 ) then 
          LSTR = 400 
          k = REGQUERYVALUEEX (MyKey, 'ProcessorNameString', CORE4(0),CORE4(0), LDATA, LSTR) 
          WRITE (*,'(i0,1x,i0,a,a)') k, Lstr,'  Processor : ', LDATA(1:LSTR) 
          CPU_description = LDATA(1:LSTR)
!
          LSTR = 400 
          k = REGQUERYVALUEEX (MyKey, 'Identifier', CORE4(0),CORE4(0), LDATA, LSTR) 
          WRITE (*,'(i0,1x,i0,a,a)') k, Lstr,'  Identifier : ', LDATA(1:LSTR) 
          CPU_stepping = LDATA(1:LSTR)
!
          word_type = 0
          CPU_xx    = 0
          LSTR      = 4
          k = REGQUERYVALUEEX (MyKey, '~MHz', CORE4(0), word_type, CPU_xx, LSTR)
          write (*,*) 'word_type=',word_type, cpu_xx, lstr, k
          call echo_bytes (CPU_xx)
          CPU_MHz = cpu_xx(1)
          WRITE (*,'(i0,1x,i0,a,i8)') k, Lstr,'  MHz : ', CPU_MHz
          write (*,*) 'CPU_MHz =',CPU_MHz
!
        end if 

       k = REGCLOSEKEY (MyKey) 
!
! Get PC name string from Registry : HARDWARE\DESCRIPTION\System\BIOS
!
        write (*,'(/a,a)') ' Reading PC Name from Registry :','HARDWARE\DESCRIPTION\System\BIOS'
        k = REGOPENKEYEX ( HKEY_LOCAL_MACHINE, 'HARDWARE\DESCRIPTION\System\BIOS',   &
                           0, KEY_READ, MyKey ) 
        write (*,'(a,i0,a,i0)') ' REGOPENKEYEX = ',k, ' : MyKey = ',MyKey

        PC_Maker = ' N/A ' 
        PC_Name  = ' N/A ' 
        if ( MyKey > 0 ) then 
          LSTR = 400 
          k = REGQUERYVALUEEX (MyKey, 'SystemManufacturer', CORE4(0),CORE4(0), LDATA, LSTR) 
          WRITE (*,'(i0,1x,i0,a,a)') k, Lstr,'  PC Maker : ', LDATA(1:LSTR) 
          PC_Maker = LDATA(1:LSTR)
!
          LSTR = 400 
          k = REGQUERYVALUEEX (MyKey, 'SystemProductName', CORE4(0),CORE4(0), LDATA, LSTR) 
          WRITE (*,'(i0,1x,i0,a,a)') k, Lstr,'  PC Name  : ', LDATA(1:LSTR) 
          PC_Name  = LDATA(1:LSTR)
!
        end if 

       k = REGCLOSEKEY (MyKey) 
!
! Get info from environment variables
!
       num_process = getenv@ ('NUMBER_OF_PROCESSORS')
       IDENTIFIER  = getenv@ ('PROCESSOR_IDENTIFIER')
       ftn95_ver   = getenv@ ('f95.ver')
       ftn95_path  = getenv@ ('ftn95_path')
!
7 Jun 2019 11:17 #23746

/ctd ! write (,) 'NUMBER_OF_PROCESSORS = ', trim(num_process), len_trim (num_process) write (,) 'PROCESSOR_IDENTIFIER = ', trim(IDENTIFIER), len_trim (IDENTIFIER) ! READ (num_process,) n_process Write (,'(a,i0,a,a)') ' Number of Processors/cores/threads = ', n_process Write (,'(a,a)') ' Processor Identifier = ', trim (IDENTIFIER) ! Read (IDENTIFIER,'(a)') CPU_stepping ! why ?? ! write (,) ' ' write (,'(a,a)') ' PC_Maker = ', trim (PC_Maker) write (,'(a,a)') ' PC_Name = ', trim (PC_Name) write (,'(a,a)') ' CPU_descriptor = ', trim (CPU_description) Write (,'(a,a)') ' CPU_stepping = ', trim (CPU_stepping) Write (,'(a,i0,a)') ' CPU MHz = ', CPU_MHz,' MHz' write (,'(a,i0)') ' Num Processors = ', n_process write (,'(a,a)') ' ftn95_ver = ', trim (ftn95_ver) write (*,'(a,a)') ' ftn95_path = ', trim (ftn95_path) ! processor_id = 2 ! end function processor_id

  subroutine echo_bytes (ii)
  integer*4 ii
  integer*4 jj
  integer*1 kk(4)
  equivalence (jj,kk)
  write (*,*) 'i4   =',ii
  jj = ii
  write (*,*) 'byte =',kk
  end subroutine echo_bytes

I am yet to read the PATH and parse it as for Win 10.

I should review the documentation for GET_ENVIRONMENT_VARIABLE and how it returns a variable length string .

9 Jun 2019 1:15 #23754

Here is some code that illustrates these issues...

 INTEGER,PARAMETER::LSTR=512,KEY_READ=Z'20019'
 INTEGER(7),PARAMETER::HKEY_LOCAL_MACHINE=Z'80000002'
 CHARACTER(LEN=LSTR) getenv@,LDATA
 STDCALL RegOpenKeyEx'RegOpenKeyExA'(VAL,STRING,VAL,VAL,REF):INTEGER*4
 STDCALL RegQueryValueEx'RegQueryValueExA'(VAL,STRING,REF,REF,STRING,REF):INTEGER*4
 STDCALL RegQueryValueEx1'RegQueryValueExA'(VAL,STRING,REF,REF,REF,REF):INTEGER*4
 STDCALL RegCloseKey'RegCloseKey'(VAL):INTEGER*4
 INTEGER(7) MyKey
 INTEGER n_processorsTotal,word_type,CPU_xx,sz
 READ(getenv@('NUMBER_OF_PROCESSORS'),*) n_processorsTotal
 PRINT*, n_processorsTotal
 k = RegOpenKeyEx(HKEY_LOCAL_MACHINE,'HARDWARE\DESCRIPTION\System\CentralProcessor\0',0,KEY_READ,MyKey)
 k = RegQueryValueEx(MyKey,'ProcessorNameString',CORE8(0),CORE8(0),LDATA,LSTR)
 PRINT*, k, '   ', TRIM(LDATA)
 sz = 4
 k = RegQueryValueEx1(MyKey,'~MHz',CORE8(0),word_type,CPU_xx,sz) 
 PRINT*, k, word_type, sz, CPU_xx
 k = RegCloseKey(MyKey)
 END
  1. This is OK.
  2. CORE4 might work but CORE8 is correct for 64 bits.
  3. The declaration for getenv@ should be large enough (here 512).
  4. A different interface is needed for REG_DWORD values.
9 Jun 2019 2:41 #23756

Paul,

Thanks for the answers. I shall review them further.

re 1) Although this is ok, I wonder if SDBG would struggle with this construct.

re 2) I am still not sure what is correct. For /64, shouldn't CORE4(0) or CORE8(0) have an integer(kind=7) :: zero = 0 as the argument, ie CORE4(zero) ? I think that in all cases the second 'CORE4(0)' can be replaced by word_type, without any problem.

re 3) The use of the new subroutine GET_ENVIRONMENT_VARIABLE should solve these problems.

re 4) I notice you have provided RegQueryValueEx1, although there is some of Dan's devilry at play here. I sent the post because I was getting a 2-byte integer value followed by 2 space bytes. I have since rebooted and the 2 space bytes are now replaced by zero. I suspect that your fix is what is needed.

Thanks again for your answers,

John

9 Jun 2019 9:09 #23757

John

  1. SDBG should have no problem with this.

  2. CORE8(0) is correct for 64 bits. CORE4(0) might also work but it is not the natural choice.

  3. getenv@ works but you must provide a large enough buffer via its declaration. You can increase from your 80 to my 512 or to whatever you like.

  4. There is no devilry here. The interface determines how values are passed and for REG_DWORD you need a REF and not a STRING.

Note also that the HKEY constants in the standard Silverfrost INCLUDE files should strictly be INTEGER(7) and not INTEGER*4. I will aim to change this for the next release.

Please login to reply.