Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Problem after XE 15.0.0.108 install

andrew_4619
Honored Contributor III
1,690 Views

After  the install some code I has gave a number of build errors most of which are now resolved but there are a few things I really do not understand. Consider the source below which is a  simple pared down to the bare bones example... 

program Console4
    use OpenGL_GLU
    implicit none
    real(8)    :: rad=1.0_8
    real(8)    :: fred=0.0_8
    integer(4) :: slices=16
    integer(4) :: loops=2 
    integer(4) :: quad=1234  
    call gludisk(quad, fred, rad, slices, loops) 
end program Console4


!DEC$ objcomment lib:"glu32.lib"
MODULE OpenGL_GLU
    PUBLIC :: gluDisk
    INTERFACE
        SUBROUTINE gluDisk(quad, inner, outer, slices, loops)                         
            !DEC$ ATTRIBUTES STDCALL, REFERENCE, DECORATE, ALIAS:"gluDisk" :: gluDisk
            IMPORT
            INTEGER(4) :: slices
            INTEGER(4) :: loops
            REAL(8)    :: inner
            REAL(8)    :: outer
            integer(4) :: quad
        END SUBROUTINE gluDisk
    END INTERFACE
END MODULE OpenGL_GLU

The above are two separate source files for a x32 build (I will post the build log to the thread).  I get the error:

Console4.obj : error LNK2019: unresolved external symbol _gluDisk@20 referenced in function _MAIN__

I set the link to verbose to check that glu32.lib was actually searched and where the lib used resided. If I do a dumpbin of that LIB the symbol  is   _gluDisk@28 which is what I would expect as we have 2*8 + 3*4  = 28bytes on the call. Where are things going wrong????

 

0 Kudos
30 Replies
andrew_4619
Honored Contributor III
1,361 Views

Build log attached I(I hope)

0 Kudos
IanH
Honored Contributor II
1,361 Views

REFERENCE ?


(as in querying the keyword on line 18...  that's not a request for a citation...)

0 Kudos
andrew_4619
Honored Contributor III
1,361 Views

All passed by value including the quad object 'pointer' I think their-in lies the problem though as I am looking at the thread for some compiler changes to passing by value.

0 Kudos
andrew_4619
Honored Contributor III
1,361 Views

Got It! The original code had:

SUBROUTINE gluDisk(quad, inner, outer, slices, loops)                         
    !DEC$ ATTRIBUTES STDCALL, REFERENCE, DECORATE, ALIAS:"gluDisk" :: gluDisk
    IMPORT
    INTEGER(GLint), VALUE       :: slices, loops
    REAL(GLdouble), VALUE       :: inner, outer
    !TYPE(C_PTR), VALUE         :: quad
    integer(C_INTPTR_T), VALUE  :: quad
END SUBROUTINE gluDisk

 

The pesky refererence does nothing as the value attribute is applied. This gives a correct interface on 13 but not on 15 and now I can fix it! Strange how you can look hard at things and be blind to what is in front of you! Thank for the pointer Mr H.

0 Kudos
IanH
Honored Contributor II
1,361 Views

ninja'd

0 Kudos
Steven_L_Intel1
Employee
1,361 Views

The change in meaning for VALUE when not used in conjunction with BIND(C) is discussed in the release notes. This was done to conform to the standard. 

0 Kudos
andrew_4619
Honored Contributor III
1,361 Views

Steve Lionel (Intel) wrote:

The change in meaning for VALUE when not used in conjunction with BIND(C) is discussed in the release notes. This was done to conform to the standard. 

I noted that thanks.

As BIND(C) and ATTRIBUTE STDCALL are now permitted, is there any change with the problem of passing the derived type C_PTR now?

0 Kudos
Steven_L_Intel1
Employee
1,361 Views

We fixed the C_PTR problem quite a while ago. Do note that adding STDCALL to BIND(C) changes only the calling convention (and name decoration) - it doesn't have any of the other effects of STDCALL used without BIND(C). The mixed-language programming section of the documentation was revised to reflect this.

0 Kudos
JVanB
Valued Contributor II
1,361 Views

So we are supposed to use !DEC$ ATTRIBUTES VALUE rather than standard Fortran VALUE attribute for arguments to !DEC$ ATTRIBUTES STDCALL procedures unless BIND(C) is also declared as an attribute in which case either usage would be fine, right?

If !DEC$ ATTRIBUTES STDCALL is declared along with BIND(C) and we don't want decoration, we then must add !DEC$ ATTRIBUTES NODECORATE, correct?

BTW Steve, how do you get 170 X 30 pixels when the most the rest of us can get is 100 pixels in either direction?  The way it should work is that clicking on the thumbnail in the forum post should take the user to the appropriate profile page (as it does now) but that clicking on the (possibly slightly higher resolution) thumbnail in the profile page should take the user to the beautiful high-resolution action picture that was actually uploaded rather than repeating the view of the thumbnail.

0 Kudos
Steven_L_Intel1
Employee
1,361 Views

If BIND(C) is not specified, then ATTRIBUTES STDCALL implies ATTRIBUTES VALUE - same as it always did. The only thing we changed was to allow you to now specify ATTRIBUTES STDCALL when BIND(C) was also specified - before that was an error.

The idea was that BIND(C) provides a standard-way of defining an interface, including pass-by-value, but we didn't allow that with STDCALL meaning that if you wanted to declare a Windows API routine you had to use a complex ATTRIBUTES directive. gfortran allowed their verson of ATTRIBUTES STDCALL with BIND(C) and, while initially we didn't think that was a good idea, we came around to it eventually.

If you don't want decoration, then don't use BIND(C), because that always decorates, as specified by the standard (in that it does exactly what the companion C processor would do.) You can change the spelling and case of the name using NAME= in BIND(C), but you can't change the decoration. We don't allow ALIAS, DECORATE or NODECORATE (is there such a thing? I didn't think so) with BIND(C).

You can see a picture of me? All I see is a broken image - a problem I keep having from time to time.

0 Kudos
JVanB
Valued Contributor II
1,361 Views

But isn't the Fortran standard VALUE attribute different from !DEC$ ATTRIBUTES VALUE in that the former is actually pass by reference to a temporary copy unless the callee is BIND(C) whereas the latter is true pass by value?  That was the issue in Post #5 as I understood it because the !DEC$ ATTRIBUTES REFERENCE part reset the default so it was no longer !DEC$ ATTRIBUTES VALUE and the specification-part of the procedure then declared the Fortran standard VALUE attribute for all dummy arguments so that they were passed by reference to temporary copies.  Had app4619 instead declared all dummy arguments individually to be !DEC$ ATTRIBUTES VALUE everything should have worked OK even though the default for the procedure was !DEC$ ATTRIBUTES REFERENCE, is that right?  Is it permitted to declare a variable to have the Fortran standard VALUE attribute and at the same time declare it with !DEC$ ATTRIBUTES VALUE, or does the compiler properly ICE at the thought of this? For a !DEC$ ATTRIBUTES STDCALL procedure without the !DEC$ ATTRIBUTES REFERENCE or BIND(C) attribute, can the programmer declare a dummy argument with the Fortran standard VALUE attribute, and if so will the actual argument be passed by reference to a temporary copy or truly by value?

I've never seen a STDCALL procedure without decoration, but if you needed it you would be out of luck in gfortran and there seems to be no documented !DEC$ ATTRIBUTES NODECORATE in ifort, either.

Your picture is blank to me as well, but right-clicking and selecting Properties I get 75 X 13 pixels in your posts and 170 X 30 pixels in your profile page.

0 Kudos
andrew_4619
Honored Contributor III
1,361 Views

For what it is worth I ended up with:

PUBLIC :: gluDisk
INTERFACE
SUBROUTINE gluDisk(quad, inner, outer, slices, loops) BIND(C,NAME="gluDisk")                        
    !DEC$ ATTRIBUTES STDCALL :: gluDisk
    IMPORT
    INTEGER(GLint), VALUE       :: slices, loops
    REAL(GLdouble), VALUE       :: inner, outer
    !TYPE(C_PTR), VALUE         :: quad
    integer(C_INTPTR_T), VALUE  :: quad
END SUBROUTINE gluDisk
END INTERFACE

On the ground that it seemed the least non-standard if that makes sense. That works but I have not tested x64 and I am still not 100% sure of the correctness!

0 Kudos
JVanB
Valued Contributor II
1,361 Views

@ app4619: yeah, that's what you would have gotten had you searched the web for gfortran interfaces such as in http://home.comcast.net/~kmbtib/Fortran_stuff/example3.zip and duplicated the !GCC$ lines as !DEC$ lines, so that now the code should work both in gfortran and ifort, 32- and 64-bit modes.

0 Kudos
andrew_4619
Honored Contributor III
1,361 Views

Repeat Offender wrote:

@ app4619: yeah, that's what you would have gotten had you searched the web for gfortran interfaces such as in http://home.comcast.net/~kmbtib/Fortran_stuff/example3.zip and duplicated the !GCC$ lines as !DEC$ lines, so that now the code should work both in gfortran and ifort, 32- and 64-bit modes.

 

Thanks for the link the OGL/GLU interfaces look more pukka and complete than my own (and I only fixed the routines I am currently using) and are more current/standard than the ifort supplied ones. I will look at that further at some point. I suspect replacing GCC with DEC and using IFWINTY and the job might be done! BIND(C), STDCALL is definitely a good way to get more standard. I have been winging about omission this for some time so chapeau Intel ! :-)

 

0 Kudos
Steven_L_Intel1
Employee
1,361 Views

RO, I'm having a bit of trouble understanding all the points of your post, but let me try anyway.

  • Yes, F03 VALUE is different from ATTRIBUTES VALUE when the procedure is not BIND(C). Our implementation didn't get this right for many years, but now it does. If BIND(C) is not used, tthen F03 VALUE means pass a temporary copy which is then discarded on return.
  • If you have ATTRIBUTES STDCALL, REFERENCE, the REFERENCE changes the default back to reference from value. You can still override it with an ATTRIBUTES VALUE on individual arguments
  • Regarding name decoration - Calls from .NET languages such as VB don't apply decoration, so being able to disable the decoration is important. This is what our ATTRIBUTES ALIAS does (when you don't also say DECORATE).
  • The compiler should properly complain if you say BIND(C) and also any of the ATTRIBUTES other than STDCALL. I would hope it never gives an ICE.

Did I miss anything?

0 Kudos
JVanB
Valued Contributor II
1,361 Views

Let me attempt to clarify with actual code. Start with a C subroutine that can read the value:

subroutine sub(dummy) bind(C,name='sub')
   use ISO_C_BINDING
   implicit none
   integer(C_INTPTR_T), value :: dummy
   character(20) fmt
   write(fmt,'(a,i0,a)') '(Z0.',2*C_SIZEOF(dummy),')'
   write(*,fmt) dummy
end subroutine sub

Now the examples:

program value
   call test1
   call test2
   call test3
   call test4
   call test5
end program value

subroutine test1
   use ISO_C_BINDING
   implicit none
   interface
      subroutine sub(dummy) bind(C,name='sub')
         use ISO_C_BINDING
         implicit none
         integer(C_INTPTR_T), value :: dummy
      end subroutine sub
   end interface
   integer(C_INTPTR_T) actual
   actual = 1
   call sub(actual)
end subroutine test1

subroutine test2
   use ISO_C_BINDING
   implicit none
   interface
      subroutine sub(dummy)
         use ISO_C_BINDING
         implicit none
!DEC$ ATTRIBUTES C, DECORATE, ALIAS:'sub' :: sub
!DEC$ ATTRIBUTES value :: dummy
         integer(C_INTPTR_T) dummy
      end subroutine sub
   end interface
   integer(C_INTPTR_T) actual
   actual = 2
   call sub(actual)
end subroutine test2

subroutine test3
   use ISO_C_BINDING
   implicit none
   interface
      subroutine sub(dummy)
         use ISO_C_BINDING
         implicit none
!DEC$ ATTRIBUTES C, DECORATE, ALIAS:'sub' :: sub
         integer(C_INTPTR_T) dummy
      end subroutine sub
   end interface
   integer(C_INTPTR_T) actual
   actual = 3
   call sub(actual)
end subroutine test3

subroutine test4
   use ISO_C_BINDING
   implicit none
   interface
      subroutine sub(dummy)
         use ISO_C_BINDING
         implicit none
!DEC$ ATTRIBUTES C, DECORATE, ALIAS:'sub' :: sub
         integer(C_INTPTR_T), value :: dummy
      end subroutine sub
   end interface
   integer(C_INTPTR_T) actual
   actual = 4
   call sub(actual)
end subroutine test4

subroutine test5
   use ISO_C_BINDING
   implicit none
   interface
      subroutine sub(dummy)
         use ISO_C_BINDING
         implicit none
!DEC$ ATTRIBUTES C, DECORATE, ALIAS:'sub' :: sub
!DEC$ ATTRIBUTES VALUE :: dummy
         integer(C_INTPTR_T), value :: dummy
      end subroutine sub
   end interface
   integer(C_INTPTR_T) actual
   actual = 5
   call sub(actual)
end subroutine test5

First I hope that subroutine test5 is invalid and should be detected as such by the compiler and then should be elided because of conflicting attributes for dummy variable dummy.

Then I hope we all agree that subroutine test1 should print out 1 because the interface is specified as BIND(C) and only true value is possible.

Also I think that subroutine test2 should print out 2 because we have only confirmed the default !DEC$ ATTRIBUTES VALUE attribute of dummy argument dummy.

I also think that subroutine test3 should print out 3 because we have !DEC$ ATTRIBUTES C implies !DEC$ATTRIBUTES VALUE, not the Fortran standard VALUE attribute although it's a little difficult to find this in the documentation.

But subroutine test4 should print out some random address in hex because we have overridden the default !DEC$ ATTRIBUTES VALUE attribute with the Fortran standard VALUE attribute, thus passing actual argument actual by reference to a temporary copy.

What is version 15's behavior for these tests?

0 Kudos
Steven_L_Intel1
Employee
1,361 Views

Version 15 displays:

00000001
00000002
00000003
00000004
00000005

I don't think this is wrong. The F03 VALUE attribute says pass a copy, but when you have ATTRIBUTES C or VALUE you have gone outside the standard. In this case, we pass the copy by value.

I modified the program to have sub change the value of dummy to 314 and then have test4 and test5 display the value of actual afterward. I got this:

00000001
00000002
00000003
00000004
 On return in test4, actual=           4
00000005
 On return in test5, actual=           5

which is exactly what I expected.

0 Kudos
JVanB
Valued Contributor II
1,361 Views

If those results are supposed to be OK, then I just don't get it. Going back to post #5, app4619 had

!DEC$ ATTRIBUTES STDCALL, REFERENCE :: gluDisk

real(GLdouble), value :: inner

Now, the first line above tells the compiler to pass all arguments by reference, unless overridden.

The second line above tells the compiler to override the first line for dummy argument inner, passing by value. He said this worked in version 13, but failed in version 15, and you said in post #7 that this was because the Fortran standard VALUE attribute was applied in this case, not the !DEC$ ATTRIBUTES VALUE attribute, so now what was getting passed was the address of a copy of the actual argument, not the value of the actual argument.

But now you say in post #18, that in subroutine test4 where we see

!DEC$ ATTRIBUTES C :: sub

integer(C_INTPTR_T), value :: dummy

The first line this time tells the compiler to pass all arguments using the !DEC$ ATTRIBUTES VALUE attribute, unless overridden.

The second line tells the compiler to override the first line for dummy argument dummy, passing by Fortran standard value, one might expect from the results of post #5, but you say this doesn't happen. It seems to me these results are completely inconsistent. Where is my reasoning flawing and where would I look in ifort documentation to be unambiguously able to predict both outcomes correctly?

0 Kudos
andrew_4619
Honored Contributor III
1,361 Views

@RO #19, bear in mind the #5 code fails in 15 because the stdcall decoration fails so it won't link. I don't know if that helps if I had forced the correct LIB name via alias instead I am not sure what would have happened....

 

0 Kudos
JVanB
Valued Contributor II
1,285 Views

Well, there's one way to check what happened. Please compile this with ifort v. 15 and post the results:

module glu
   use ISO_C_BINDING
   implicit none
   integer, parameter :: GLint = C_INT
   integer, parameter :: GLdouble = C_DOUBLE
   interface
      subroutine gluDisk5(quad,inner,outer,slices,loops)
         import
         implicit none
         !DEC$ ATTRIBUTES STDCALL, REFERENCE, DECORATE, ALIAS:"gluDisk" :: gluDisk5
         integer(GLint), value :: slices, loops
         real(GLdouble), value :: inner, outer
         type(C_PTR), value :: quad
      end subroutine gluDisk5
   end interface
   interface
      subroutine gluDisk13(quad,inner,outer,slices,loops) bind(C,name='gluDisk')
         import
         implicit none
         !DEC$ ATTRIBUTES STDCALL :: gluDisk13
         integer(GLint), value :: slices, loops
         real(GLdouble), value :: inner, outer
         type(C_PTR), value :: quad
      end subroutine gluDisk13
   end interface
   contains
      subroutine gluDisk20(quad,inner,outer,slices,loops) bind(C,name='gluDisk')
         !DEC$ ATTRIBUTES STDCALL :: gluDisk20
         type(C_PTR), value :: quad,inner,outer,slices,loops
         type(C_PTR) cptr
         integer(GLint), pointer :: iptr
         real(GLdouble), pointer :: dptr
         type(C_PTR), pointer :: aptr
         character(20) fmt
         write(*,'(a)') '_gluDisk@20 invoked'
         write(fmt,'(a,i0,a)') '(Z0.',2*C_SIZEOF(aptr),')'
         write(*,fmt) transfer(quad,0_C_INTPTR_T)
         call C_F_POINTER(quad,aptr)
         write(*,fmt) transfer(aptr,0_C_INTPTR_T)
         write(*,fmt) transfer(inner,0_C_INTPTR_T)
         call C_F_POINTER(inner,dptr)
         write(*,'(Z0.16)') transfer(dptr,0_C_INT64_T)
         write(*,fmt) transfer(outer,0_C_INTPTR_T)
         call C_F_POINTER(outer,dptr)
         write(*,'(Z0.16)') transfer(dptr,0_C_INT64_T)
         write(*,fmt) transfer(slices,0_C_INTPTR_T)
         call C_F_POINTER(slices,iptr)
         write(*,'(Z0.8)') iptr
         write(*,fmt) transfer(loops,0_C_INTPTR_T)
         call C_F_POINTER(loops,iptr)
         write(*,'(Z0.8)') iptr
      end subroutine gluDisk20
      subroutine gluDisk28(quad,inner,outer,slices,loops) bind(C,name='gluDisk')
         !DEC$ ATTRIBUTES STDCALL :: gluDisk28
         integer(GLint), value, target :: slices, loops
         real(GLdouble), value, target :: inner, outer
         type(C_PTR), value, target :: quad
         type(C_PTR) cptr
         character(20) fmt
         write(*,'(a)') '_gluDisk@28 invoked'
         write(fmt,'(a,i0,a)') '(Z0.',2*C_SIZEOF(cptr),')'
         cptr = C_LOC(quad)
         write(*,fmt) transfer(cptr,0_C_INTPTR_T)
         write(*,fmt) transfer(quad,0_C_INTPTR_T)
         cptr = C_LOC(inner)
         write(*,fmt) transfer(cptr,0_C_INTPTR_T)
         write(*,'(Z0.16)') transfer(inner,0_C_INT64_T)
         cptr = C_LOC(outer)
         write(*,fmt) transfer(cptr,0_C_INTPTR_T)
         write(*,'(Z0.16)') transfer(outer,0_C_INT64_T)
         cptr = C_LOC(slices)
         write(*,fmt) transfer(cptr,0_C_INTPTR_T)
         write(*,'(Z0.8)') slices
         cptr = C_LOC(loops)
         write(*,fmt) transfer(cptr,0_C_INTPTR_T)
         write(*,'(Z0.8)') loops
      end subroutine gluDisk28
end module glu

program value
   use glu
   implicit none
   type(C_PTR) quad
   integer(GLint) loops,slices
   real(GLdouble) inner, outer
   quad = transfer(int(Z'DEADBEEF',C_INTPTR_T),quad)
   inner = 1.0_GLdouble
   outer = 1.5_GLdouble
   slices = 4
   loops = 5
   call gluDisk5(quad,inner,outer,slices,loops)
   call gluDisk13(quad,inner,outer,slices,loops)
end program value

I'm hoping you get something like:

_gluDisk@20 invoked
0023FDD0
DEADBEEF
0023FDE8
3FF0000000000000
0023FDD8
3FF8000000000000
0023FDCC
00000004
0023FDE4
00000005
_gluDisk@28 invoked
0023FD80
DEADBEEF
0023FD88
3FF0000000000000
0023FD90
3FF8000000000000
0023FD98
00000004
0023FDA0
00000005

Where those 0023FDXX numbers are any random addresses, but the other values should be as given. But please post, don't just say yes or no :)

0 Kudos
Reply