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

Internal compiler error (C0000005) with assumed-rank array

Daniel_Dopico
New Contributor I
844 Views

The following piece of code offers an "1>fortcom: Fatal: There has been an internal compiler error (C0000005)." when trying to compile with Intel Parallel Studio 2018 update 5.

    program assumed_rank
        implicit none
        REAL(8),DIMENSION(2)::r1=1.d0
        REAL(8),DIMENSION(2,2)::r2=2.d0
        INTERFACE
            SUBROUTINE assumed_dummy(rP)
            REAL(8),DIMENSION(..)::rP
            END SUBROUTINE assumed_dummy
        END INTERFACE
    
        CALL assumed_dummy(r1)
        CALL assumed_dummy(r2)
    end program assumed_rank
    
    SUBROUTINE assumed_dummy(rP)
        REAL(8),DIMENSION(..)::rP
        REAL(8) r
    
        SELECT CASE(rank(rP))
        CASE(1)
            r=rP(1)
            print *,r
        CASE(2)
           r=rp(1,2)  ! Commenting this line solves the compilation error.
           print *,r
        END SELECT
    END SUBROUTINE assumed_dummy
 

0 Kudos
1 Solution
Steve_Lionel
Honored Contributor III
844 Views

In the current version of the compiler, assumed-rank is primarily of use for calling into non-Fortran code so that you don't have to declare multiple routines, one for each rank. If you want to do something today, the following works:

    program assumed_rank
        implicit none
        REAL(8),DIMENSION(2)::r1=1.d0
        REAL(8),DIMENSION(2,2)::r2=2.d0
        INTERFACE
            SUBROUTINE assumed_dummy(rP)
            REAL(8),DIMENSION(..)::rP
            END SUBROUTINE assumed_dummy
        END INTERFACE
    
        CALL assumed_dummy(r1)
        CALL assumed_dummy(r2)
    end program assumed_rank
    
    SUBROUTINE assumed_dummy(rP)
        USE, INTRINSIC :: ISO_C_BINDING
        REAL(8),DIMENSION(..)::rP
        REAL(8) r
        TYPE(C_PTR) :: ptr_rP
        
        ptr_RP = C_LOC(rP)
    
        SELECT CASE(rank(rP))
        CASE(1)
            block
            real(8), dimension(:), pointer :: rPA
            call C_F_POINTER (ptr_rP, rPA, SHAPE(rP))
            r=rPA(1)
            print *,1,r
            end block
        CASE(2)
            block
            real(8), dimension(:,:), pointer :: rPA
            call C_F_POINTER (ptr_rP, rPA, SHAPE(rP))
            r=rPA(1,2)
            print *,2,r
            end block
        END SELECT
    END SUBROUTINE assumed_dummy
D:\Projects>ifort t.f90
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, 
Version 19.0.2.190 Build 20190117
Copyright (C) 1985-2019 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.16.27027.1
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:t.exe
-subsystem:console
t.obj

D:\Projects>t.exe
           1   1.00000000000000
           2   2.00000000000000

 

View solution in original post

0 Kudos
10 Replies
Lorri_M_Intel
Employee
844 Views

While that was a clever way to try and use an assumed rank object in a program, that's not legal Fortran.

There is a Fortran 2018 feature called "SELECT RANK" that will allow you to do this, but that feature is not supported in PSXE 2018.

I agree, however, that the compiler should have done something more clever than give an internal compiler error when it encountered this line.

Can you submit the test program through the online support website, please?

                     --Lorri

0 Kudos
Daniel_Dopico
New Contributor I
844 Views

Thank you Lorri. With variations of the code I was able to obtain also something as weird as "catastrophic error" (or something like that).

I haven't trIed yet with the 2019 compiler though.

Daniel.

 

0 Kudos
Daniel_Dopico
New Contributor I
844 Views

Lorri Menard (Intel) wrote:

Can you submit the test program through the online support website, please?

                     --Lorri

I have just submitted a ticket reporting the issue.

0 Kudos
Daniel_Dopico
New Contributor I
844 Views

Lorri Menard (Intel) wrote:

While that was a clever way to try and use an assumed rank object in a program, that's not legal Fortran.

There is a Fortran 2018 feature called "SELECT RANK" that will allow you to do this, but that feature is not supported in PSXE 2018.

I agree, however, that the compiler should have done something more clever than give an internal compiler error when it encountered this line.

Can you submit the test program through the online support website, please?

                     --Lorri

Dear Lorri.

If SELECT RANK is not available, which is the proper way of using it? The documentation is scant. Or should we better wait for future updates?

Thanks!

0 Kudos
Steve_Lionel
Honored Contributor III
845 Views

In the current version of the compiler, assumed-rank is primarily of use for calling into non-Fortran code so that you don't have to declare multiple routines, one for each rank. If you want to do something today, the following works:

    program assumed_rank
        implicit none
        REAL(8),DIMENSION(2)::r1=1.d0
        REAL(8),DIMENSION(2,2)::r2=2.d0
        INTERFACE
            SUBROUTINE assumed_dummy(rP)
            REAL(8),DIMENSION(..)::rP
            END SUBROUTINE assumed_dummy
        END INTERFACE
    
        CALL assumed_dummy(r1)
        CALL assumed_dummy(r2)
    end program assumed_rank
    
    SUBROUTINE assumed_dummy(rP)
        USE, INTRINSIC :: ISO_C_BINDING
        REAL(8),DIMENSION(..)::rP
        REAL(8) r
        TYPE(C_PTR) :: ptr_rP
        
        ptr_RP = C_LOC(rP)
    
        SELECT CASE(rank(rP))
        CASE(1)
            block
            real(8), dimension(:), pointer :: rPA
            call C_F_POINTER (ptr_rP, rPA, SHAPE(rP))
            r=rPA(1)
            print *,1,r
            end block
        CASE(2)
            block
            real(8), dimension(:,:), pointer :: rPA
            call C_F_POINTER (ptr_rP, rPA, SHAPE(rP))
            r=rPA(1,2)
            print *,2,r
            end block
        END SELECT
    END SUBROUTINE assumed_dummy
D:\Projects>ifort t.f90
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, 
Version 19.0.2.190 Build 20190117
Copyright (C) 1985-2019 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.16.27027.1
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:t.exe
-subsystem:console
t.obj

D:\Projects>t.exe
           1   1.00000000000000
           2   2.00000000000000

 

0 Kudos
Daniel_Dopico
New Contributor I
844 Views

Thank you very much Steve. Your solution is beautiful and enlightening, nevertheless I think I will wait for future updates before blending my functions working on arrays of different ranks.

Daniel.

0 Kudos
Steve_Lionel
Honored Contributor III
844 Views

What is your application for this? There may be a more elegant solution than SELECT RANK.

0 Kudos
Daniel_Dopico
New Contributor I
844 Views

My application is multibody dynamics. It happens sometimes that you need to apply for example one force: you call a subrutine or function with a vector dummy argument (Rank-1 array). Sometimes you need to apply a bunch of forces and the dummy argument is a collection of vectors (Rank-2 array). I have it solved with two different functions and MODULE PROCEDURE interfaces, or GENERIC statements if they are type-bound procedures. I think it is an aceptable solution, but when I saw this assumed-rank feature I wanted to give it a try.

(I post an example of two of these functions that I mention).

SUBROUTINE genForce_coord(cuerpo,rP,F)
    USE SOLIDOS,ONLY:CCLpt
    TYPE(BODY) cuerpo
    REAL(8),DIMENSION(3)::rP,F,Cp(0:3)
    INTENT(IN) cuerpo,rP,F

    Cp=CCLpt(cuerpo,rP)
    CALL genForce_Qgen(cuerpo,matmul_CpT_F(Cp,F))
END SUBROUTINE genForce_coord
 

SUBROUTINE genForce_coord2(cuerpo,rP,F)
    USE SOLIDOS,ONLY:CCLpt
    TYPE(BODY) cuerpo
    REAL(8),DIMENSION(:,:)::rP
    REAL(8),DIMENSION(3,size(rp,2))::F
    REAL(8),DIMENSION(0:3)::Cp
    REAL(8),DIMENSION(12)::fQQ
    INTEGER i
    INTENT(IN) cuerpo,rP,F

    fQQ=0.d0
    DO i=1,size(rP,2)
        Cp=CCLpt(cuerpo,rP(:,i))
        fQQ=fQQ+matmul_CpT_F(Cp,F(:,i))
    ENDDO

    CALL genForce_Qgen(cuerpo,fQQ)  !Ensamblaje de fuerzas generalizadas
END SUBROUTINE genForce_coord2
 

0 Kudos
Steve_Lionel
Honored Contributor III
844 Views

If it's just a choice between rank 1 and 2, and the computations are somewhat different, I think generics are a better fit here with lower overhead. With generics, the arrays are passed by reference and the compiler can resolve the call. But with assumed-rank, the array is passed by descriptor, which takes extra code setting up for the call and decoding in the called routine. (Not only that, but a generics solution is going to be far more portable in the near term.)

Assumed rank was added at the request of the MPI Forum which wanted to be able to declare a single Fortran interface for a routine (written in C) that could handle arrays of any rank. These would be passed by C descriptor and the C code would get the info from the descriptor. Given that the standard allows up to rank 15 (Intel allows 31), and if you have more than one array argument, the number of combinations of signatures explodes.

It's good that you're trying assumed rank, and especially that you discovered a compiler bug. Your question also gave me the opportunity to demonstrate what Fortran code can do today with that feature.

0 Kudos
Daniel_Dopico
New Contributor I
844 Views

Thank you very much Steve for this clarification because sometimes only having this information about why something is being implemented we can take smart decisions about incorporating it to our code or not.

Daniel.

0 Kudos
Reply