- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Hello,
I am currently trying to convert our Powerstation 4.0 Fortran code to Intel Visual Fortran to achieve better debugging possibies. The application is a mix between C, C++ and Fortran 77. A lot of posts in this forum helped me a great deal to walk this path. But now I encountered an error, where I don't know how to solve it properly.
I recieve the following two errors, which both relate to the line CALL SPROT(LFL) in x.f:
error #6633: The type of the actual argument differs from the type of the dummy argument. [LFL]
error #6634: The shape matching rules of actual arguments and dummy arguments have been violated. [LFL]
They are obviously both closely related, but since I am a beginner in Fortran, I don't know how to declare LFL or modify the Interface declaration to have them work together without changing the way the COMMON block is adressed, because it is used in a lot of other places in the program.
cmodule.f90:
module cmodule !DllExport int WINAPI sprot(char* cBuf) Interface subroutine SPROT (cBuf) & BIND(C, name="SPROT") use, INTRINSIC :: ISO_C_BINDING IMPLICIT NONE !DEC$ ATTRIBUTES STDCALL :: SPROT character cBuf end subroutine SPROT end interface end module
x.f:
SUBROUTINE STDAUS use cmodule COMMON /CWRI 1 / NF,NF0,LFL(1058),LFT(128),LFS(16, 1 200 2 ) C ... CALL SPROT(LFL) C ... END SUBROUTINE
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
I am assuming from the error #6633 the LFL is implicitly typed as INTEGER, so that its usage is to provide a buffer for data from the C function that the Fortran code won't parse directly. Then I would change line 9 of x.f to
CALL SPROT(C_LOC(LFL))
You are going to have to ensure that SUBROUTINE STDAUS USEes ISO_C_BINDING. Now we have to fix the interface body to accommodate this:
module cmodule !DllExport int WINAPI sprot(char* cBuf) Interface function SPROT (cBuf) & BIND(C, name="SPROT") use, INTRINSIC :: ISO_C_BINDING IMPLICIT NONE !DEC$ ATTRIBUTES STDCALL :: SPROT integer(C_INT) sprot type(C_PTR), value :: cBuf end function SPROT end interface end module
Notice that I changed from a subroutine to a function because its C prototype says that it's a function returning an int. That char* cBuf argument could, depending on context, be type as CHARACTER :: cBuf, CHARACTER :: cBuf(*), or TYPE(C_PTR), VALUE :: cBuf, but since we intend to do type cheating we want to use the last alternative and pass the address of LFL. There may be a further error to get over, but this should get you close.
Link kopiert
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
I am assuming from the error #6633 the LFL is implicitly typed as INTEGER, so that its usage is to provide a buffer for data from the C function that the Fortran code won't parse directly. Then I would change line 9 of x.f to
CALL SPROT(C_LOC(LFL))
You are going to have to ensure that SUBROUTINE STDAUS USEes ISO_C_BINDING. Now we have to fix the interface body to accommodate this:
module cmodule !DllExport int WINAPI sprot(char* cBuf) Interface function SPROT (cBuf) & BIND(C, name="SPROT") use, INTRINSIC :: ISO_C_BINDING IMPLICIT NONE !DEC$ ATTRIBUTES STDCALL :: SPROT integer(C_INT) sprot type(C_PTR), value :: cBuf end function SPROT end interface end module
Notice that I changed from a subroutine to a function because its C prototype says that it's a function returning an int. That char* cBuf argument could, depending on context, be type as CHARACTER :: cBuf, CHARACTER :: cBuf(*), or TYPE(C_PTR), VALUE :: cBuf, but since we intend to do type cheating we want to use the last alternative and pass the address of LFL. There may be a further error to get over, but this should get you close.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Whoops, the next error will be for the CALL:
ires = SPROT(C_LOC(LFL))
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Thank you so far.
The first error I recieved was, that C_LOC cannot be found by the linker.
After adding use, INTRINSIC :: ISO_C_BINDING to the head of the SUBROUTINE I still recieve error 6633.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Sorry, the error appeared in different source files, where I did not yet add use, INTRINSIC :: ISO_C_BINDING.
For now it seems to work. Thank you.
I'll keep trying to fix the other errors and will report back.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Note that C_LOC requires an argument have the TARGET attribute. (It would be nice for ifort to be able to issue a warning about this.)
A note about the code in the original post, just for clarity and because occasionally a misconception arises - inside the interface block the intrinsic ISO_C_BINDING is referenced by a USE statement, but then none of the things that are provided by that module are actually used in that interface block. Therefore, for that intrinsic module, that USE statement in the original post was "pointless". Unlike some of the other intrinsic modules, that intrinsic module has no magic powers - just USE'ing it doesn't change the behaviour of the code. (It would also be nice if ifort could also warn about "no entities from this module were referenced", or perhaps that is better left for "lint" type tools.)
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Yes, I was worried about this, but wasn't sure how to declare the TARGET attribute. My line of reasoning was that a COMMON block is really like an instance of a user-defined type so the TARGET attribute was all or nothing. However, it seems you can't give a COMMON block the TARGET attribute, but you can do so for variables inside that block. If the O.P. doesn't want to modify his INCLUDE file, I suppose he could just put the TARGET statement in subroutine STDAUS. Here is the syntax, checkable with gfortran but not with ifort:
program P use ISO_C_BINDING common /c1/ I_integer(2,2), R_real(3) TARGET I_integer type(C_PTR) cp character(80) fmt cp = C_LOC(I_integer) write(fmt,'(*(g0))') '(z0.',2*C_SIZEOF(0_C_INTPTR_T),')' write(*,fmt) transfer(cp,0_C_INTPTR_T) end program P
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
What is the defined behaviour of C_LOC when called on somehting without the TARGET statement? I could not find anything regarding it in the documentation.
I suppose the TARGET statement is important for optimization and type checking.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
If I supply the mentioned TARGET statement I recieve an error (7725), because these variables are used in EQUIVALENCE statements.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Oog. I told you that I was worried. Well, both ifort and gfortran accept this:
program P use ISO_C_BINDING common /c1/ I_integer(2,2), R_real(3) type(C_PTR) cp character(80) fmt cp = transfer(LOC(I_integer(1,1)),C_NULL_PTR) write(fmt,'(*(g0))') '(z0.',2*C_SIZEOF(0_C_INTPTR_T),')' write(*,fmt) transfer(cp,0_C_INTPTR_T) end program P
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
I am begining to think, that it might be simpler to change the signature and cast the argument in C to a char*.
edit: Which doesn't solve the original problem. It seems I am getting tired. I'll read up tomorrow.
But I have full control over the C part and can change the signature if nescessary. Same for the Fortan Interfaces and implementation code just the COMMON blocks should not be touched.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Oh no, casting to char* does work. Of course we could fix everything by going to a generic name, but I don't like that approach because if a whole lot of arguments are multivalent, the number of specific procedures increases exponentially.
But back to how char* works. First we set up the interface appropriately:
module cmodule !DllExport int WINAPI sprot(char* cBuf) Interface function SPROT (cBuf) & BIND(C, name="SPROT") use, INTRINSIC :: ISO_C_BINDING IMPLICIT NONE !DEC$ ATTRIBUTES STDCALL :: SPROT integer(C_INT) sprot character(kind=C_CHAR) :: cBuf(*) end function SPROT end interface end module
Now in the specification-part of subroutine STDAUS we need:
CHARACTER(LEN=4) LFL_ARG EQUIVALENCE(LFL_ARG,LFL)
And the function call is:
ires = SPROT(LFL_ARG)
Mmf... I see that you can't EQUIVALENCE CHARACTER and numeric types. But both gfortran and ifort let you get away with this if standards checking isn't in force. If that isn't acceptable, you could cast cBuf as an assumed-shape array of INTEGER or whatever numeric type is EQUIVALENCED to LFL and pass LFL or one of its EQUIVALENCE set.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
The behaviour of C_LOC given an argument that does not have the TARGET attribute is not defined.
When an object has the TARGET attribute the Fortran processor knows that the object might be aliased - a different name may refer to the same object. The potential for aliasing prevents some optimisations that the Fortran processor might otherwise consider.
(As a distant aside, pondered while I was trying to think of a relevant example - the standard does not appear to explicitly state that the arguments to the functions in ISO_C_BINDING have INTENT(IN). I wonder if this ever actually matters (noting it is explicitly stated for other intrinsic modules), and whether this is an oversight in the standard.)
You can give an object the TARGET attribute "temporarily" using a procedure call. Such a wrapper may be handy for other reasons. Borrowing from RO's earlier response:
module cmodule implicit none contains function sprot(cBuf) USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_INT, C_LOC INTEGER, TARGET :: cBuf(*) INTEGER(C_INT) :: sprot Interface !DllExport int WINAPI sprot(char* cBuf) function sprot_c (cBuf) & BIND(C, name="SPROT") use, INTRINSIC :: ISO_C_BINDING, only: c_int, c_ptr IMPLICIT NONE !DEC$ ATTRIBUTES STDCALL :: SPROT integer(C_INT) :: sprot_c type(C_PTR), value :: cBuf end function sprot_c end interface sprot = sprot_c(C_LOC(cBuf)) end function sprot end module cmodule PROGRAM p USE cmodule !IMPLICIT NONE COMMON /CWRI/ NF,NF0,LFL(1058),LFS(16,200) EQUIVALENCE (LFL,L_Whatever) PRINT *, sprot(LFL) END PROGRAM p
Note that the pointer passed to the c variant of sprot only refers to the dummy argument of the Fortran variant of sprot - after the Fortran variant of sprot completes that C address is invalid. This is only problematic if the C variant of sprot stores the pointer (and even then, it is unlikely to be a problem in practice - from a implementation point of view, the compiler may choose to make a copy of the actual argument when calling the Fortran variant of sprot, but given other aspects, you may also win the jackpot in lotto).
Lots of older code plays this game, but just to be clear - fundamentally the code is pretending that the memory backing an object of one type is actually an object of another type. C allows that for unsigned char, bar some explicit exceptions around COMPLEX and REAL (and, implicitly, C interoperable types), Fortran formally does not.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Some of the procedures in ISO_C_BINDING have INTENT specified - for example, C_F_POINTER, but most do not. C_LOC doesn't reference nor define its argument, so no intent is probably correct.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Steve Lionel (Intel) wrote:The ISO_C_BINDING subroutines have intent specified, but not the functions. I wondered if this was because the same style of specification for the intrinsic subroutines (intent explicitly specified) and functions was being used - the omission being that there is a "all arguments intent(in) unless otherwise stated" blanket statement for the intrinsic procedures (F2008 13.2.1), but that blanket statement does not apply to non intrinsic functions, such as those in ISO_C_BINDING (assuming I haven't missed another blanket statement for ISO_C_BINDING provided procedure arguments - which is an assumption that needs testing!).
Some of the procedures in ISO_C_BINDING have INTENT specified - for example, C_F_POINTER, but most do not. C_LOC doesn't reference nor define its argument, so no intent is probably correct.
There are a number of intrinsic functions that have similar characteristics to C_LOC, in terms of not referencing or defining arguments.
But again - I can't think of a practical consequence of this, bar being one of the many things that would need to be resolved if those procedures were ever to be made pure.

- RSS-Feed abonnieren
- Thema als neu kennzeichnen
- Thema als gelesen kennzeichnen
- Diesen Thema für aktuellen Benutzer floaten
- Lesezeichen
- Abonnieren
- Drucker-Anzeigeseite