Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
Announcements
FPGA community forums and blogs on community.intel.com are migrating to the new Altera Community and are read-only. For urgent support needs during this transition, please visit the FPGA Design Resources page or contact an Altera Authorized Distributor.
29285 Discussions

Elemental user defined operator being naughty and hiding rank-specific procedure

IanH
Honored Contributor III
721 Views
With 11.1.065, when compiled with /check:all /warn:all /stand:f03 I get an error that a scalar valued expression is required in the if statement marked #C. But my understanding is that the expression is scalar, as the compiler should select the pure (not elemental) specific procedure ge_foos, which returns a scalar.

Bizarrely, if I swap the line commenting on the lines marked #B and #C around, this compiles with no error, though, despite going nearly cross-eyed from looking at it, I cannot see a relevant difference between the definitions of the interface blocks and the procedures.

Alternatively, if I comment out the statement that makes the unused > operator visible (the line marked #A), it all compiles too.

[fortran]MODULE Foos
  IMPLICIT NONE  
  
  PRIVATE  
  PUBLIC :: Construct
  PUBLIC :: OPERATOR(>)                 ! #A
  PUBLIC :: OPERATOR(>=)
  
  TYPE, PUBLIC :: Foo
    PRIVATE
    INTEGER :: comp
  END TYPE Foo

  INTERFACE Construct
    MODULE PROCEDURE Construct_
  END INTERFACE Construct
  
  INTERFACE OPERATOR(>)
    MODULE PROCEDURE gt_foo
    MODULE PROCEDURE gt_foos
  END INTERFACE OPERATOR(>)
  
  INTERFACE OPERATOR(>=)
    MODULE PROCEDURE ge_foo
    MODULE PROCEDURE ge_foos
  END INTERFACE OPERATOR(>=)
CONTAINS    
  FUNCTION Construct_ RESULT(obj)
    TYPE(Foo) :: obj
    !****
    obj%comp = 0
  END FUNCTION Construct_
  
  ELEMENTAL FUNCTION gt_foo(lhs, rhs) RESULT(res)
    TYPE(Foo), INTENT(IN) :: lhs
    INTEGER, INTENT(IN) :: rhs
    LOGICAL :: res
    !****
    res = .TRUE.
  END FUNCTION gt_foo
  
  ELEMENTAL FUNCTION ge_foo(lhs, rhs) RESULT(res)
    TYPE(Foo), INTENT(IN) :: lhs
    INTEGER, INTENT(IN) :: rhs
    LOGICAL :: res    
    !****
    res = .TRUE.
  END FUNCTION ge_foo  
  
  PURE FUNCTION gt_foos(lhs, rhs) RESULT(res)
    TYPE(Foo), INTENT(IN) :: lhs(:)
    INTEGER, INTENT(IN) :: rhs
    LOGICAL :: res
    !****
    res = .FALSE.
  END FUNCTION gt_foos
  
  PURE FUNCTION ge_foos(lhs, rhs) RESULT(res)
    TYPE(Foo), INTENT(IN) :: lhs(:)
    INTEGER, INTENT(IN) :: rhs
    LOGICAL :: res
    !****
    res = .FALSE.
  END FUNCTION ge_foos
END MODULE Foos

PROGRAM ItsSpecificallyNotElemental
  USE Foos
  IMPLICIT NONE    
  TYPE(Foo) :: foo_list(2)  
  INTEGER :: i  
  !****
  DO i = 1, SIZE(foo_list)
    foo_list(i) = Construct()
  END DO  
!  IF (foo_list > 0)  THEN        ! #B
  IF (foo_list >= 0)  THEN        ! #C 
    WRITE (*, *) 'Boing'
  END IF
END PROGRAM ItsSpecificallyNotElemental
[/fortran]
As an aside: when are we likely to see in IVF the F2003 ability to "override" structure constructors with a generic?

Thanks for any advice,

IanH
0 Kudos
5 Replies
jimdempseyatthecove
Honored Contributor III
721 Views
Ian,

The question relates to what is actually being called by

IF(foo_list>=0)

Is this interpreted as

IF(foo_list> (=0))

What happens with

IF(foo_list>=(0))

Also, as a diagnostic, define an operator ".ge." an then change the errant statement to use .ge. instead of >=, does this too report the same error?

Jim Dempsey

0 Kudos
Steven_L_Intel1
Employee
721 Views
Jim, >= is always parsed as an operator equivalent to .GE..

Ian, I'll take a look at this and see what is going on.
0 Kudos
jimdempseyatthecove
Honored Contributor III
721 Views
>>Jim, >= is always parsed as an operator equivalent to .GE..

Unless there is a compiler bug, which Ian seems to have an example thereof.

The substitution of .ge. for >= was explicity designed to expose if ">=" were not treated as a single token.
If .ge. works where >= fails, then this is a strong indicator that the token parser broke the ">=" into two tokens. And in which case, this information (works or fails in same manner) may be helpful to your compiler support staff in locating the errant code.

Jim Dempsey
0 Kudos
Steven_L_Intel1
Employee
721 Views
The use of > vs. .GE. has no effect on this problem. I can make it fail with either one.

Reported as issue DPD200155690. Thanks for the nice example.
0 Kudos
Steven_L_Intel1
Employee
721 Views
This has been fixed in our sources for the next major release.
0 Kudos
Reply