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

The `select type` of the `logical` type reports an error

zoziha
Novice
910 Views

The following is part of the code I wrote. It runs normally on Windows-gfortran-12, but an error occurs on Windows-ifort-2021.6.0. From my experience, the code Fortran syntax seems to be fine, which may be a bug in ifort?

module disp_m

    use, intrinsic :: iso_fortran_env, only: output_unit, sp => real32, dp => real64
    implicit none
    private

    public :: disp

contains

    !> Displays dataset x
    subroutine disp(x, header, fmt, unit)
        class(*), intent(in) :: x(..)                       !! Dataset to be displayed
        character(len=*), intent(in), optional :: header    !! Header of the dataset
        character(len=*), intent(in), optional :: fmt       !! Format of the dataset
        integer, intent(in), optional :: unit               !! File unit to outputted
        character(:), allocatable :: fmt_
        integer :: unit_, i

        if (present(fmt)) then
            fmt_ = '(*('//fmt//',:,", "))'
        else
            fmt_ = '(*(g0.4,:,", "))'
        end if

        if (present(unit)) then
            unit_ = unit
        else
            unit_ = output_unit
        end if

        if (present(header)) write (unit_, '(a)') header

        select rank (x)
        rank (0)
            select type (x)  ! <-- This line
            type is (real(sp)); write (unit_, fmt_) x
            type is (real(dp)); write (unit_, fmt_) x
            type is (integer); write (unit_, fmt_) x
            type is (logical); write (unit_, fmt_) x
            end select

        rank (1)
            select type (x)
            type is (real(sp)); write (unit_, fmt_) x(:)
            type is (real(dp)); write (unit_, fmt_) x(:)
            type is (integer); write (unit_, fmt_) x(:)
            type is (logical); write (unit_, fmt_) x(:)
            end select

        rank (2)
            do i = 1, size(x, 2)
                select type (x)
                type is (real(sp)); write (unit_, fmt_) x(:, i)
                type is (real(dp)); write (unit_, fmt_) x(:, i)
                type is (integer); write (unit_, fmt_) x(:, i)
                type is (logical); write (unit_, fmt_) x(:, i)
                end select
            end do
        end select

    end subroutine disp

end module disp_m

program main

    use disp_m, only: disp
    
    integer :: i(5) = [110, 2, 45678910, 10, 45]
    logical :: l = .true.
    call disp(i, "i = ", "i10")
    call disp(spread(i+10, dim=1, ncopies=3), "spread(i, dim=1, ncopies=3) = ", "i0")
    call disp(real(spread(i-11, dim=1, ncopies=3)), "real(spread(i, dim=1, ncopies=3)) = ", "g11.4")
    call disp(l, ".true. = ")  ! <-- This line

end program main

 The error message is as follows:

$ ifort /warn:all /check:all /error-limit:1 /Od /Z7 /assume:byterecl /traceback demo.f90
$ demo.exe
i = 
       110,          2,   45678910,         10,         45
spread(i, dim=1, ncopies=3) =
120, 120, 120
12, 12, 12
45678920, 45678920, 45678920
20, 20, 20
55, 55, 55
real(spread(i, dim=1, ncopies=3)) =
  99.00    ,   99.00    ,   99.00
 -9.000    ,  -9.000    ,  -9.000
 0.4568E+08,  0.4568E+08,  0.4568E+08
 -1.000    ,  -1.000    ,  -1.000
  34.00    ,   34.00    ,   34.00
.true. =
forrtl: severe (157): Program Exception - access violation
Image              PC                Routine            Line        Source
demo_disp.exe      00007FF6A6321E52  DISP_M_mp_DISP             36  demo_disp.f90
demo_disp.exe      00007FF6A6328C0D  MAIN__                     75  demo_disp.f90
demo_disp.exe      00007FF6A63C55FE  Unknown               Unknown  Unknown
demo_disp.exe      00007FF6A63C6164  Unknown               Unknown  Unknown
KERNEL32.DLL       00007FFEEC2F7034  Unknown               Unknown  Unknown
ntdll.dll          00007FFEEDCA2651  Unknown               Unknown  Unknown

 

0 Kudos
9 Replies
Barbara_P_Intel
Moderator
901 Views

I am investigating your issue to see if it's a compiler bug. Can you please supply the complete output that you expect? Thank you.



0 Kudos
zoziha
Novice
892 Views

The expected result should be:

 

$ ifort /warn:all /check:all /error-limit:1 /Od /Z7 /assume:byterecl /traceback demo.f90
$ demo.exe
i = 
       110,          2,   45678910,         10,         45
spread(i, dim=1, ncopies=3) =
120, 120, 120
12, 12, 12
45678920, 45678920, 45678920
20, 20, 20
55, 55, 55
real(spread(i, dim=1, ncopies=3)) =
  99.00    ,   99.00    ,   99.00
 -9.000    ,  -9.000    ,  -9.000
 0.4568E+08,  0.4568E+08,  0.4568E+08
 -1.000    ,  -1.000    ,  -1.000
  34.00    ,   34.00    ,   34.00
.true. =
T

 

 The code can be reduced to the following example:

 

module disp_m

    use, intrinsic :: iso_fortran_env, only: output_unit, sp => real32, dp => real64
    implicit none
    private

    public :: disp

contains

    !> Displays dataset x
    subroutine disp(x)
        class(*), intent(in) :: x(..)                       !! Dataset to be displayed

        select rank (x)
        rank (0)
            select type (x)  ! <-- This line
            type is (real(sp)); write (*, '(g0.4)') x
            type is (real(dp)); write (*, '(g0.4)') x
            type is (integer); write (*, '(g0.4)') x
            type is (logical); write (*, '(g0.4)') x
            end select
        end select

    end subroutine disp

end module disp_m

program main

    use disp_m, only: disp

    logical :: l = .true.
    call disp(l)  ! <-- This line
    call disp(1)
    call disp(1.0)
    call disp(1.0d0)

end program main

 

 which gives the following results on gfortran:

 

>> gfortran demo.f90 && ./a.exe
T
1
1.000
1.000

 

 But ifort gives the following error:

 

>> ifort demo.f90 /warn:all /check:all /error-limit:1 /Od /Z7 /assume:byterecl /traceback
>> demo.exe
forrtl: severe (157): Program Exception - access violation
Image              PC                Routine            Line        Source
main.exe           00007FF7D62412D2  DISP_M_mp_DISP             17  main.f90
main.exe           00007FF7D6242B2D  MAIN__                     34  main.f90
main.exe           00007FF7D62DE27E  Unknown               Unknown  Unknown
main.exe           00007FF7D62DEDE4  Unknown               Unknown  Unknown
KERNEL32.DLL       00007FF9BCD97034  Unknown               Unknown  Unknown
ntdll.dll          00007FF9BD9A2651  Unknown               Unknown  Unknown

 

 The `class(*)` and `rank(..)` syntaxes are used here, which may be the key reason for the error. (As long as rank(0) reports an error, rank(1)/rank(2) does not report an error)

0 Kudos
Barbara_P_Intel
Moderator
870 Views

Thank you for the reduced reproducer.

I checked several different sources. The use of an assumed-rank array in a SELECT TYPE is illegal Fortran.

From the Fortran standard document:

Constraint 838 in section 8.5.8.7 Assumed-rank entity states:

C838     An assumed-rank variable name shall not appear in a designator or expression except as an actual argument

               that corresponds to a dummy argument that is assumed-rank, the argument of the function C_LOC or C_SIZEOF

               from the intrinsic module ISO_C_BINDING, the first dummy argument of an intrinsic inquiry function, or the selector

               of a SELECT RANK statement. 


The Forum regulars who know the standard inside and out and frequent this forum are at the J3 US Fortran Standards meeting this week. I'm sure one of them would have noticed.

I filed a bug report. The Intel compiler should have caught this illegal use. The bug report is CMPLRLLVM-39084.

Thank you for bringing this to our attention!



0 Kudos
Steve_Lionel
Honored Contributor III
859 Views

I hate to disagree with Barbara, but I must. The X inside the SELECT RANK block is not assumed-rank - the whole idea of SELECT RANK is that the associating entity has the specified rank. The words from 11.1.10.3 are:

Within the block following a RANK ( scalar-int-constant-expr ) statement, the associating entity has the specified rank; the lower bound of each dimension is the result of the intrinsic function LBOUND (16.9.109) applied to the corresponding dimension of the selector, and the upper bound of each dimension is the result of the intrinsic function UBOUND (16.9.196) applied to the corresponding dimension of the selector.

0 Kudos
FortranFan
Honored Contributor II
851 Views

@Barbara_P_Intel ,

Sorry the fix by Intel will need to look further at the issue in the original post with Intel Fortran, the standard ostensibly supports it!

Intel Fortran team can see it as follows with the "associate-name => selector" notation in the SELECT RANK construct.  Note in blocks other than RANK DEFAULT within the SELECT RANK construct, the entity corresponding to the associate-name i.e., the associating entity per the standard is not assumed-rank:

    subroutine disp(arg)
        class(*), intent(in) :: arg(..)

        select rank (x => arg)
        rank (0)
           select type (x)  ! <-- Here 'x' is rank-1 and thus can be used in SELECT TYPE construct
           type is (real(sp)); write (*, '(g0.4)') x

 

0 Kudos
zoziha
Novice
824 Views

From the user's point of view, it seems unreasonable that `select rank` and `select type` cannot be used together normally.

There are two basic combinations of `select rank` and `select type`:

  1. The `select rank` is in the `select type` structure;
  2. The `select type` is in the `select rank` structure.

And indeed, Fortran may have some ways of doing it through the `associate`(=>) syntax.

0 Kudos
Barbara_P_Intel
Moderator
806 Views

I stand corrected. We had a communication breakdown when I asked for a sanity check before posting my reply.

This is legal Fortran. I'll be filing new bug reports for the runtime issue.



Barbara_P_Intel
Moderator
784 Views

New bug filed: CMPLRLLVM-39141.



0 Kudos
Barbara_P_Intel
Moderator
166 Views

This runtime failure is fixed with both ifx and ifort that are available in version 2024.1. These compilers were released last week.

Please try them out!



0 Kudos
Reply