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

Erroneous run-time behavior with an ELEMENTAL function whose result characteristics make use of a specification expression

FortranFan
Honored Contributor II
179 Views

Here's a summary of an incident submitted at the Intel Online Service Center in case any readers of this forum are interested: consider the following code that involves a function with the ELEMENTAL attribute and whose result characteristics make use of a specification expression:

module m

   implicit none

contains

   elemental function elemf( n, s ) result( new_s )

      ! Argument list
      integer, intent(in)         :: n
      character(len=*),intent(in) :: s
      ! Function result
      character(len=n*len(s)) :: new_s

      new_s = repeat( string=s, ncopies=n )

      return

   end function elemf

end module m

Now consider a program that invokes the above function, in one case making use of the ELEMENTAL attribute but not with the other. 

program p

   use, intrinsic :: iso_fortran_env, only : compiler_version
   use string_m, only : string_t
   use m, only : elemf

   implicit none

   integer, allocatable :: n(:)
   character(len=2), allocatable :: s(:)

   print *, "Compiler Version: ", compiler_version()

   n = [ 2, 3 ]
   s = [ "??", "!@" ]

   blk1: block
      type(string_t), allocatable :: x(:)
      allocate( x(size(n)) )
      x = elemf( n, s )
      print *, "block 1:"
      print *, "len(x) = ", len( x(1)%s() ), "; expected = ", n(1)*len(s(1))
   end block blk1

   blk2: block
      type(string_t), allocatable :: x(:)
      integer :: i
      allocate( x(size(n)) )
      do i = 1, size(n)
         x(i) = elemf( n(i), s(i) )
      end do
      print *, "block 2:"
      print *, "len(x) = ", len( x(1)%s() ), "; expected = ", n(1)*len(s(1))
      print *, "x = ", x
   end block blk2

   stop

end program p

Note the above makes use of a 'string' utility 'class' as follows:

module string_m

   implicit none

   private

   type, public :: string_t
      private
      character(len=:), allocatable :: m_s
   contains
      private
      procedure, pass(this) :: assign_s
      procedure, pass(this) :: write_s
      procedure, pass(this), public :: s => get_s
      generic, public :: assignment(=) => assign_s
      generic, public :: write(formatted) => write_s
   end type string_t

contains

   elemental subroutine assign_s( this, rhs )

      class(string_t), intent(inout) :: this
      character(len=*), intent(in)   :: rhs

      this%m_s = rhs

      return

   end subroutine assign_s

   subroutine write_s(this, lun, iotype, vlist, istat, imsg)

      ! argument definitions
      class(string_t), intent(in)     :: this
      integer, intent(in)             :: lun
      character(len=*), intent(in)    :: iotype
      integer, intent(in)             :: vlist(:)
      integer, intent(out)            :: istat
      character(len=*), intent(inout) :: imsg

      ! local variable
      character(len=9) :: sfmt

      sfmt = "(A)"
      if ( (iotype == "DT").and.(size(vlist) >= 1) ) then

         ! vlist(1) to be used as the field width of the character component.
         write(sfmt,"(A,I2,A)", iostat=istat, iomsg=imsg ) "(A", vlist(1), ")"
         if (istat /= 0) return

      end if

      write(lun, fmt=sfmt, iostat=istat, iomsg=imsg) this%m_s

      return

   end subroutine write_s

   elemental function get_s( this ) result( s )

      class(string_t), intent(in) :: this
      ! Function result
      character(len=len(this%m_s)) :: s

      s = this%m_s

   end function get_s

end module string_m

Upon execution of output built using Intel Fortran,

 Compiler Version:
 Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(
 R) 64, Version 18.0.1.156 Build 20171018

 block 1:
 len(x) =  5544984 ; expected =  4
 block 2:
 len(x) =  4 ; expected =  4
 x = ????!@!@!@

Note the " len(x) = 4496920 ; expected = 4" output from block 1 above.

It's erroneous and output varies from run to run.

0 Kudos
0 Replies
Reply