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

FINAL binding to an ELEMENTAL procedure does not work: causes "Program Exception - Access Violation"

FortranFan
Honored Contributor III
950 Views

Consider the simple program shown below:

MODULE m

   !..
   IMPLICIT NONE

   !.. Private by default
   PRIVATE

   TYPE, PUBLIC :: t

      !.. private by default
      PRIVATE

      !.. Private fields
      CHARACTER(LEN=:), ALLOCATABLE :: m_string

   CONTAINS

      !.. Private by default
      PRIVATE
      FINAL :: Clean

      !..
      PROCEDURE, PASS(This), PUBLIC :: Set => Set_String
      PROCEDURE, PASS(This), PUBLIC :: Get => Get_String

   END TYPE t

CONTAINS

   PURE ELEMENTAL SUBROUTINE Set_String(This, NewString)

      !.. Argument list
      CLASS(t), INTENT(INOUT)      :: This
      CHARACTER(LEN=*), INTENT(IN) :: NewString

      !..
      This%m_string = NewString

      RETURN

   END SUBROUTINE Set_String

   PURE ELEMENTAL FUNCTION Get_String(This) RESULT(RetVal)

      !.. Argument list
      CLASS(t), INTENT(IN) :: This
      !.. Function result
      CHARACTER(LEN=:), ALLOCATABLE :: RetVal

      !..
      RetVal = This%m_string

      RETURN

   END FUNCTION Get_String

   PURE ELEMENTAL SUBROUTINE Clean(This)

      !.. Argument list
      TYPE(t), INTENT(INOUT)      :: This

      !.. Local variables
      INTEGER :: Istat

      IF (ALLOCATED(This%m_string)) THEN
         DEALLOCATE(This%m_string, STAT=Istat)
      END IF

      RETURN

   END SUBROUTINE Clean

END MODULE m

PROGRAM p

   USE m, ONLY : t

   IMPLICIT NONE

   !.. Local variables
   TYPE(t), ALLOCATABLE :: foo(:)
   INTEGER :: Istat
   INTEGER, PARAMETER :: MaxElem = 5
   INTEGER :: I
   CHARACTER(LEN=2048) :: ErrDealloc

   !..
   PRINT *, " Test Elemental finalizer "

   ALLOCATE(foo(MaxElem), STAT=Istat)
   IF (Istat /= 0) THEN
      PRINT *, " Error allocating foo."
      STOP
   END IF

   DO I = 1, MaxElem
      CALL foo(I)%Set(" string " // ACHAR(34+I))
      PRINT *, " foo element ",I, " is ",foo(I)%Get()
   END DO

   DEALLOCATE(foo, STAT=Istat, ERRMSG=ErrDealloc)
   IF (Istat /= 0) THEN
      PRINT *, " Error deallocating foo: STAT = ",Istat,", ERRMSG = ", ErrDealloc(1:LEN_TRIM(ErrDealloc))
      STOP
   END IF

   PRINT *, " End Program "

   STOP

END PROGRAM p

 

Upon compilation and execution with Intel Fortran, either compiler version 14 or 2015 Beta, the program fails as follows:

  Test Elemental finalizer
  foo element  1  is  string #
  foo element  2  is  string $
  foo element  3  is  string %
  foo element  4  is  string &
  foo element  5  is  string '
forrtl: severe (157): Program Exception - access violation
Image              PC        Routine            Line        Source
TestFor32.exe      00DA1494  _M_mp_CLEAN@4              66  TestMod.f90
TestFor32.exe      00DB13DA  Unknown               Unknown  Unknown
TestFor32.exe      00DA2467  _MAIN__                    28  TestFor.f90
TestFor32.exe      00E148A2  Unknown               Unknown  Unknown
TestFor32.exe      00E157BA  Unknown               Unknown  Unknown
TestFor32.exe      00E1590D  Unknown               Unknown  Unknown
kernel32.dll       7576338A  Unknown               Unknown  Unknown
ntdll.dll          76F5BF32  Unknown               Unknown  Unknown
ntdll.dll          76F5BF05  Unknown               Unknown  Unknown

 

My understanding is the above is consistent with current Fortran standard and the access violation is due to some bug in the compiler.  Can someone from Intel please investigate and provide feedback?

Thanks,

0 Kudos
18 Replies
FortranFan
Honored Contributor III
950 Views

FWIW, the above program works with gfortran 4.9 - the code compiles without any errors and it runs with no errors or memory leaks.

0 Kudos
FortranFan
Honored Contributor III
950 Views

A correction and a clarification:

  • I said, "Upon compilation and execution with Intel Fortran, either compiler version 14 or 2015 Beta, the program fails" - it is actually compiler 13 (version Compiler XE 13.1.1.171 to be exact) and 2015 Beta that I used for my testing.  I don't know the response with compiler version 14 - my apologies for any confusion.
  • As Yolanda Chen at Intel pointed out, the problem occurs with IA-32 (32-bit) build; Intel 64 (i.e., 64-bit) version runs fine.
0 Kudos
Steven_L_Intel1
Employee
950 Views

Did you already report this through Intel Premier Support and got a response from Yolanda?

0 Kudos
FortranFan
Honored Contributor III
950 Views

Steve Lionel (Intel) wrote:

Did you already report this through Intel Premier Support and got a response from Yolanda?

Steve,

My hunch is the problem with the simple code in this topic is connected with the more complex code in Premier Support incident 6000058970 I'd submitted over the weekend, so I've added a comment to that Premier incident about this new forum topic in case your engineering/development team feels the same and wishes to look at the two issues together.

Yolanda had pointed out earlier on the Premier incident about the differences between IA-32 and Intel 64 builds, so I retried the program in this topic for the two builds and found Intel 64 version ran ok.

Thanks,

0 Kudos
Steven_L_Intel1
Employee
950 Views

It could just be a coincidence. Please add this information to the Premier Support issue so that Yolanda can track it properly.

0 Kudos
Steven_L_Intel1
Employee
950 Views

You sent me a PM but I can't read any PMs right now. Since you already started a Premier Support issue on this topic, please continue it there to avoid duplication of effort.

0 Kudos
FortranFan
Honored Contributor III
950 Views

Steve Lionel (Intel) wrote:

You sent me a PM but I can't read any PMs right now. Since you already started a Premier Support issue on this topic, please continue it there to avoid duplication of effort.

Steve,

Thanks, I fully appreciate your comment about duplication of effort and I'll always remain fully cognizant of that.

Re: the Premier Support issue, sorry I wasn't fully clear in my comment in Quote #5 above.  The incident #6000058970 does indeed refer to a separate issue I'd mentioned in this forum topic about object-oriented list example from the book by Metcalf et al. - https://software.intel.com/en-us/forums/topic/518263 - see Quote #9 in there where I talk my own implementation of a list class similar to the MFE example and which runs into "access violation" error just like the MFE example.

My thoughts now are:

  1. the "access violation" error in my "list" class is different from that encountered while running the example code from MFE book,
  2. the "access violation" error in my "list" class is related to the error in the simple example in this topic with a FINAL binding to an ELEMENTAL procedure.

I could well be wrong, so I'll leave it all in Intel's good hands.

But to make a long story short, I think it is worth keeping my Premier Support issue #6000058970 and the one in this topic as two separate incidents with an alert to your development staff of a possible connection between the two.  If development comes and says they are indeed one and the same, then one of them can be closed out.

 

0 Kudos
Lorri_M_Intel
Employee
950 Views

Is this the program that has /iface:cvf set in the project property?

           --Lorri

0 Kudos
FortranFan
Honored Contributor III
950 Views

Yes, is that a problem?  It doesn't need to have this setting - it is an unintended carry-over in my Visual Studio "template" for Fortran projects that was created from one that needed this setting for interfacing to another library that was built with CVF-style options. 

 

0 Kudos
Steven_L_Intel1
Employee
950 Views

Yes, it is a problem. We discussed this in our team meeting today. Turn /iface:cvf off if you don't need it. If you do need it, add !DEC$ ATTRIBUTES DEFAULT to any FINAL routines.

0 Kudos
Yuan_C_Intel
Employee
950 Views

Hi,

Yes, I verified this runs successfully without /iface:cvf.

The same to the project in IPS incident #6000058970.

 

0 Kudos
FortranFan
Honored Contributor III
950 Views

Thanks Yolanda and Steve.

Not that it might affect me, but out of curiosity, what is the forward plan for Intel re: this issue - users should not use /iface:cvf if they wish to implement final bindings for IA-32 systems or is this a temporary workaround until Intel has a fix?

 

0 Kudos
Steven_L_Intel1
Employee
950 Views

The forward plan is to give a compile-time error if /iface:cvf or stdcall or stdref is in effect and you declare a FINAL procedure. This is similar to what we do for USEROPEN. We discussed options of making it work but decided that as this affects IA-32 Windows only, and only those who migrated from CVF (which didn't have FINAL procedures) and most of whom don't need /iface:cvf, it wasn't worth pursuing.

If you need /iface:cvf for specific routines, we now have !DEC$ ATTRIBUTES CVF you can use for convenience on those routines only. I'd say that the majority of people who have /iface:cvf enabled for their projects don't need it and should disable it. This can also bite you if you use IFLOGM or IMSL callbacks, both of which require the compiler's default calling convention.

0 Kudos
Lorri_M_Intel
Employee
950 Views

If you need/want to use /iface:cvf  you can add an explicit "default" attribute to your FINAL subroutine declaration using
!DEC$ ATTRIBUTES DEFAULT :: myFinalSubroutineName

             --Lorri

 

0 Kudos
FortranFan
Honored Contributor III
950 Views

Thanks Steve and Lorri.

Would you consider adding this information to Intel Fortran documentation e.g., "User and Reference Guide for the Intel® Fortran Compiler"?  It'll be nice if in the Help Viewer for Visual Studio, when one looks up information for iface and looks at "/iface:cvf", there is a link perhaps to a section to all the caveats associated with this option including the one about FINAL and ELEMENTAL procedures.

0 Kudos
Steven_L_Intel1
Employee
950 Views

We already have this:

Caution

On systems using IA-32 architecture, there must be agreement between the calling program and the called procedure as to which calling mechanism (C or STDCALL) is used or unpredictable errors may occur. If you change the default mechanism to STDCALL, you must use the ATTRIBUTES DEFAULT directive to reset the calling conventions for routines specified with the USEROPEN keyword in an OPEN statement and for comparison routines passed to the QSORT library routine.

I will have FINAL procedures added to this paragraph. (Looks like it needs to also talk about IFLOGM callbacks too, as well as IMSL.)

0 Kudos
FortranFan
Honored Contributor III
950 Views

So Steve/Lorri,

Is the message here that coders should view FINAL bindings as an "external procedure"?  And that /iface settings are relevant even for all Fortran projects using Intel compiler that the coder may normally view as not calling any "external procedures"?

After all, the settings for /iface are lumped under the "External Procedures" section under Fortran for project properties in Visual Studio.  So I only worry about that section when I know I'll be calling procedures from another library (e.g., some DLL procedure) or when I'm doing mixed-language programming, etc. 

For all Fortran projects like the console application I setup to test the code in the original post above, there are no explicit link-time or run-time dependencies to any non-system library/DLL.  For such projects, I have not been paying attention to "External Procedures" section in Visual Studio  - I guess I've been mistaken?

Thanks,

0 Kudos
Steven_L_Intel1
Employee
950 Views

The option applies to any procedures that are compiled or called. It has nothing to do with run-time libraries.

0 Kudos
Reply