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

IFX 2024.2.0 Internal Compiler Error: Array Constructor Leads to Segmentation Violation

KP_14
Novice
753 Views

This is a greatly simplified version of a program that was causing an internal compiler error in IFX 2024.2.0. This issue is also reproducible in IFORT 2021.13.0 Build 20240602.

 

Command: "ifx ice003.F90 -o ice003.out"

Version: 2024.2.0 Build 20240602

Error: "error #5633: **Internal compiler error: segmentation violation signal raised**"


See line 66 in the program below. The use of the array constructor to concatenate an array and an object that contains a pointer and a type that contains an allocatable seems to generate the error.

ice003.F90

PROGRAM ice003
    IMPLICIT none
  !----------------------------------------------------------------------    
    TYPE :: C
        INTEGER, ALLOCATABLE :: Y
    END TYPE C
  !----------------------------------------------------------------------        
    TYPE :: B
        INTEGER :: X
    END TYPE B
  !----------------------------------------------------------------------        
    TYPE :: A
        CLASS (B), POINTER :: B_Pointer
        TYPE (C) :: C_Comp
    END TYPE A
  !----------------------------------------------------------------------    
    TYPE :: D
        TYPE (A), DIMENSION(:), ALLOCATABLE :: A_Array
    END TYPE D
  !----------------------------------------------------------------------    
  ! Main Program Start
  
    TYPE (D) :: My_D
    TYPE (A) :: My_A
  
    TYPE (B), TARGET :: My_B
  
    My_B%X = 4
  
    My_A%B_Pointer => My_B
    My_A%C_Comp%Y = 6
  
    ALLOCATE(My_D%A_Array(2))
  
    CALL Add(My_D, My_A)
  
    WRITE (*,*) "X: ", My_D%A_Array(3)%B_Pointer%X
    WRITE (*,*) "Y: ", My_D%A_Array(3)%C_Comp%Y
  
  ! Main Program End
  !----------------------------------------------------------------------
CONTAINS
  !----------------------------------------------------------------------
    SUBROUTINE Add(D_Arg, A_Arg)
        
        CLASS (D), INTENT (InOut) :: D_Arg
        TYPE (A), INTENT (In) :: A_Arg
        
        INTEGER (KIND = 4) :: Current_Size, New_Size
        
        TYPE (A), DIMENSION(:), ALLOCATABLE :: Temp_A_Array
        
        IF (ALLOCATED(D_Arg%A_Array)) THEN
            
            Current_Size = SIZE(D_Arg%A_Array, 1)
            New_Size = Current_Size + 1
            
            ALLOCATE(Temp_A_Array(Current_Size))
            
            Temp_A_Array = D_Arg%A_Array
            
            DEALLOCATE(D_Arg%A_Array)
            
            ALLOCATE(D_Arg%A_Array(New_Size))
            
            D_Arg%A_Array = (/ Temp_A_Array, A_Arg /)
            
            DEALLOCATE(Temp_A_Array)
            
        END IF
        
    END SUBROUTINE Add
  !----------------------------------------------------------------------
END PROGRAM ice003

 

3 Replies
P-W
Novice
561 Views

Any update on this issue?

0 Kudos
TobiasK
Moderator
521 Views

@P-W


sorry forgot to mention that I have escalated this last week to the developers. However, no updates yet.


0 Kudos
TobiasK
Moderator
294 Views

@P-W


we implemented a fix for this issue which will be included in the next release, 2025.1.


0 Kudos
Reply