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

Another coarray bug with 17U4

OP1
New Contributor II
204 Views

When the code below is run with the coarray option toggled on, different behaviors are observed depending on which line (20 or 21) is commented out.

  • Commenting out line 20 yields the expected result
  • Commenting out line 21 yields an access violation error on line 37.

Since the variable on line 37 is not coindexed, I am surprised by this result. Does this work with version 18 of the compiler?

MODULE M

    IMPLICIT NONE
    TYPE,ABSTRACT :: T_SHAPE_CONTAINER
        CHARACTER(LEN=:),ALLOCATABLE :: NAME
    END TYPE T_SHAPE_CONTAINER
    TYPE,EXTENDS(T_SHAPE_CONTAINER) :: T_POINT_CONTAINER
        REAL,ALLOCATABLE :: COORDINATES(:,:)
    END TYPE T_POINT_CONTAINER
    TYPE,EXTENDS(T_SHAPE_CONTAINER) :: T_LINE_CONTAINER
        REAL,ALLOCATABLE :: COORDINATES(:,:,:)
    END TYPE T_LINE_CONTAINER
    TYPE :: T_CONTAINER
        CLASS(T_SHAPE_CONTAINER),ALLOCATABLE :: SHAPE_CONTAINER
    END TYPE T_CONTAINER
    TYPE :: T_SHAPE_DATA
        TYPE(T_CONTAINER),ALLOCATABLE :: SHAPES(:)
    END TYPE T_SHAPE_DATA

    TYPE(T_SHAPE_DATA) :: SHAPE_DATA_1
  • ,SHAPE_DATA_2
  •     !TYPE(T_SHAPE_DATA) :: SHAPE_DATA_1,SHAPE_DATA_2 END MODULE M PROGRAM P     USE M     IMPLICIT NONE     INTEGER :: I         ALLOCATE(SHAPE_DATA_1%SHAPES(2))         ALLOCATE(T_POINT_CONTAINER :: SHAPE_DATA_1%SHAPES(1)%SHAPE_CONTAINER)         ALLOCATE(T_LINE_CONTAINER  :: SHAPE_DATA_1%SHAPES(2)%SHAPE_CONTAINER)         DO I=1,2             SELECT TYPE (A => SHAPE_DATA_1%SHAPES(I)%SHAPE_CONTAINER)                 TYPE IS (T_POINT_CONTAINER)                     A%NAME = 'Points'                     ALLOCATE(A%COORDINATES(3,2))                     A%COORDINATES(:,1) = [1.,2.,3.]                     A%COORDINATES(:,2) = [4.,5.,6.]                 TYPE IS (T_LINE_CONTAINER)                     ALLOCATE(A%COORDINATES(3,2,2))                     A%NAME = 'Lines'                     A%COORDINATES(:,1,1) = [7.,8.,9.]                     A%COORDINATES(:,2,1) = [10.,11.,12.]                     A%COORDINATES(:,1,2) = [13.,14.,15.]                     A%COORDINATES(:,2,2) = [16.,17.,18.]             END SELECT         END DO         SHAPE_DATA_2 = SHAPE_DATA_1         DO I=1,2             SELECT TYPE (A => SHAPE_DATA_2%SHAPES(I)%SHAPE_CONTAINER)                 TYPE IS (T_POINT_CONTAINER)                     WRITE(*,* )A%NAME                     WRITE(*,*) A%COORDINATES                 TYPE IS (T_LINE_CONTAINER)                     WRITE(*,* )A%NAME                     WRITE(*,*) A%COORDINATES             END SELECT         END DO END PROGRAM P
  •  

    0 Kudos
    1 Solution
    Lorri_M_Intel
    Employee
    204 Views

    No, this does not work with 18.0 Update 1.

    Could you please report it via the support site?  that's the best way to get the bug into our internal problem reporting data base, therefore getting it on our work list, etc.

                Thank you for your help -

                              --Lorri

     

     

    View solution in original post

    0 Kudos
    1 Reply
    Lorri_M_Intel
    Employee
    205 Views

    No, this does not work with 18.0 Update 1.

    Could you please report it via the support site?  that's the best way to get the bug into our internal problem reporting data base, therefore getting it on our work list, etc.

                Thank you for your help -

                              --Lorri

     

     

    0 Kudos
    Reply