- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi all
when running this code:
Module testmod
Private
Type, Public, abstract :: myroot(k)
Integer, kind :: k
End type myroot
Type, Public, extends(myroot), abstract :: myvec
Integer(kind=8) :: lb1=1,ub1
End type myvec
Type, Public, extends(myvec) :: myvec_int
Integer(k), allocatable :: val(:,:)
contains
Procedure, Pass :: suba
End type myvec_int
Interface
Module Subroutine suba(this)
class(myvec_int(8)), Intent(inout) :: this
end Subroutine suba
end Interface
End Module testmod
Program Test
use testmod
Implicit none
Type(myvec_int(8)), allocatable :: a
allocate(a)
write(*,*) a%lb1
End Program Test
the parameterized derviced type (lb1 in myvec) looses its default initialization. a%lb1 is written out with zero. This does not happen if no procedure is bound to myvec_int. From my understanding this is a bug in 17.07 and 18.03.
cheers
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I think the program is not standard compliant. Why do you try this as an interface for a module procedure? Besides this syntax in line 14/15 does not even look conform. If I change this to
contains
! Interface
!Module
Subroutine suba (this)
class(myvec_int(8)), Intent(inout) :: this
end Subroutine suba
!end Interface
then ifort gets the expected result 1. Only then nagfor compiles the code at all and delivers 1. gfortran chokes on this.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@may.ka,
It's a bug in Intel Fortran compiler and it is present in the compiler 19.0 Beta version as well. You may submit a support request at the Intel OSC.
By the way, the bug appears related to the use of the MODULE SUBROUTINE for the binding to the type myvec_int. And some may get confused by the missing implementation for it in your original post. Though it shouldn't and doesn't make a difference with Intel Fortran and its behavior, a clearer reproducer may help:
module testmod
private
type, public, abstract :: myroot(k)
integer, kind :: k
end type myroot
type, public, extends(myroot), abstract :: myvec
integer(kind=8) :: lb1=1, ub1
end type myvec
type, public, extends(myvec) :: myvec_int
integer(k), allocatable :: val(:,:)
contains
procedure, pass :: suba
end type myvec_int
interface
module subroutine suba(this)
class(myvec_int(8)), intent(inout) :: this
end subroutine suba
end interface
end module testmod
submodule(testmod) sm
contains
module subroutine suba(this)
class(myvec_int(8)), intent(inout) :: this
this%val = 0 ! an arbitrary instruction
end subroutine suba
end submodule
program Test
use testmod
implicit none
type(myvec_int(8)), allocatable :: a
allocate(a)
write(*,*) a%lb1
end program Test
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Ok, right, that is part of an implementation in terms of submodules. That explains why nagfor considers this to be a syntax error.
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page