- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I'm trying to use the API calls to get the bitness of Excel, and I'm using the following code, which fails on the GetBinaryType call.
Any ideas?
Thanks,
PROGRAM TEST
IMPLICIT NONE
LOGICAL :: Is64Bit
Is64Bit = Is64BitExcel()
Write(*,*) Is64Bit
CONTAINS
LOGICAL function Is64BitExcel
USE KERNEL32
USE IFWINTY
USE WINTERACTER
IMPLICIT NONE
INTEGER(BOOL) :: ret
CHARACTER(LEN=MAX_PATH) :: ExcelPath
Integer(DWORD) :: BinaryType
Integer :: iLen
is64BitExcel = .FALSE.
CALL IOsRegistryGet("HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Windows\CurrentVersion\App Paths\excel.exe", &
excelPath, "Path", Length=iLen)
if (iLen>0) THEN
excelPath(iLen+1:)="excel.exe"
ret=GetBinaryType(excelPath, binaryType) !ret always zero, so file not found or not executable!
IS64BITExcel = (binaryType == SCS_32BIT_BINARY)
end if
end function Is64BitExcel
end program TEST
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Do you need to add a trailing null for excelPath before that GetBinaryType API call?
excelPath(iLen+1:) = "excel.exe" // ACHAR(0)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
That gives an access violation on the GetBinaryType call.
D
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hmmm.
INTERFACE FUNCTION GetBinaryType( & lpApplicationName, & lpBinaryType) import integer(BOOL) :: GetBinaryType ! BOOL !DEC$ ATTRIBUTES DEFAULT, STDCALL, DECORATE, ALIAS:'GetBinaryTypeA' :: GetBinaryType !DEC$ ATTRIBUTES REFERENCE, ALLOW_NULL :: lpApplicationName character*(*) lpApplicationName ! LPCSTR lpApplicationName integer(LPDWORD) lpBinaryType ! LPDWORD lpBinaryType END FUNCTION END INTERFACE
This !DEC$ babble always sends my head into a spin, but I think if a procedure is marked STDCALL then the default calling convention for arguments unless specified otherwise is akin to ATTRIBUTES VALUE. But the msdn C prototype suggests that is basically a DWORD passed by reference (the binary type is an output).
Replace binaryType in the function reference to GetBinaryType with LOC(binaryType) and see what happens. Retain the null termination business mentioned previously.
That Fortran API declaration seems a bit ... unfortunate ... to me.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
David, I do not have Winteracter, so I modified your program to use IFWIN. It worked correctly with the 32- and 64-bit compilers. Please note the two integer variables that have to be INTEGER(8) for Windows-64 and INTEGER(8) for Windows-32.
PROGRAM TEST IMPLICIT NONE LOGICAL :: Is64Bit Is64Bit = Is64BitExcel() Write(*,*) Is64Bit CONTAINS LOGICAL function Is64BitExcel USE KERNEL32 USE IFWIN IMPLICIT NONE INTEGER(BOOL) :: ret CHARACTER(LEN=256) :: ExcelPath Integer(8) :: hkey ! use Integer(4) for 32-bit version of Test program Integer :: iLen,ist,itype,isize,BinaryType is64BitExcel = .FALSE. ist = RegOpenKeyEx(HKEY_LOCAL_MACHINE, & 'SOFTWARE\\Microsoft\\Windows\\CurrentVersion\\App Paths\\excel.exe'C, & 0, KEY_ALL_ACCESS, LOC(hkey)) isize=len(ExcelPath) ist = RegQueryValueEx(hkey,'Path'C,0,loc(itype),loc(excelPath),LOC(isize)) ret=GetBinaryType(excelPath(1:isize) // 'excel.exe'C, LOC(binaryType)) IS64BITExcel = (binaryType == SCS_64BIT_BINARY) end function Is64BitExcel end program TEST
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Magic!
I didn't read your post properly the first time ... LOC(binaryType) without the Null termination on the string returned the same values as without LOC.
Using both LOC and Null termination gives a return code of 1 and BinaryType = 0 (=> 32bit).
Thanks,
David
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I don't do Windows calls often, so I don't know if the glue code in IFWIN that maps Fortran calls to C calls requires LOC to be applied to INTENT(OUT) arguments.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
In this case, yes it does. Note the use of LPDWORD as the kind - this means "long pointer to doubleword". Most of the API definitions we got from Microsoft back in the early days of DVF were like that, with a naive translation of LPxxx to "address by value", requiring LOC. Over time we added the IGNORE_LOC attribute and then could in many cases create an alternate interface with the proper type, but we didn't go back to all of the declarations to do this.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Further to this discussion on testing bitness, I am trying to get my install script to test this. (I know this isn't a Fortran question anymore).
Does anyone have 64-bit MS Office who would test an install script for me?
I am using NSIS, and the script code is:
RequestExecutionLevel user
Var BITNESS
OutFile "C:\Open\testbitness.exe"
Section "-MainSection" SEC01
SectionEnd
Function .onInit
ReadRegStr $0 HKLM "SOFTWARE\Microsoft\Windows\CurrentVersion\App Paths\excel.exe" "Path"
StrCpy $0 "$0excel.exe"
System::Call "kernel32::GetBinaryType(t, *l) i(.r0, .r1) ?e"
StrCpy $BITNESS "32"
StrCmp "$1" "0" +2
StrCpy $BITNESS "64"
MessageBox MB_ICONEXCLAMATION|MB_OK "Excel version installed is $BITNESS-bit"
FunctionEnd
Thanks,
David

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page