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.

Generic resolution inside structure constructor

IanH
Honored Contributor III
633 Views

Inside a structure constructor (at least), resolution of a generic with a name that is the same as that of an intrinsic procedure does not appear to consider the specific procedures provided by the program.

If I use a temporary for the expression, the generic name is resolved correctly in the expression that sets the value of the temporary.

MODULE Direct2D
  IMPLICIT NONE
  
  PRIVATE
  
  PUBLIC :: SomeAPI
  PUBLIC :: Scale
  
  INTEGER, PARAMETER :: FLOAT = KIND(1.0)
  
  
  TYPE, BIND(C), PUBLIC :: D2D1_POINT_2F
    REAL(FLOAT) :: x = 0.0_FLOAT
    REAL(FLOAT) :: y = 0.0_FLOAT
  END TYPE D2D1_POINT_2F
  
  TYPE, BIND(C), PUBLIC :: D2D1_MATRIX_3x2_F
    REAL(FLOAT) :: data(2,3)
  END TYPE D2D1_MATRIX_3x2_F
  
  TYPE, BIND(C), PUBLIC :: D2D1_BRUSH_PROPERTIES
    REAL(FLOAT) :: opacity = 1.0_FLOAT
    TYPE(D2D1_MATRIX_3x2_F) :: transform
  END TYPE D2D1_BRUSH_PROPERTIES
  
  INTERFACE Scale
    MODULE PROCEDURE :: Scale_point
  END INTERFACE Scale
CONTAINS
  SUBROUTINE SomeAPI(brush_properties)
    TYPE(D2D1_BRUSH_PROPERTIES), INTENT(IN) :: brush_properties
    !...
  END SUBROUTINE SomeAPI
  
  ELEMENTAL FUNCTION Scale_point(x, y, center) RESULT(matrix)
    REAL(FLOAT), INTENT(IN) :: x
    REAL(FLOAT), INTENT(IN) :: y
    TYPE(D2D1_POINT_2F), INTENT(IN) :: center
    TYPE(D2D1_MATRIX_3X2_F) :: matrix
    !***************************************************************************
    matrix%data = RESHAPE(  &
        [ x, 0.0_FLOAT, 0.0_FLOAT, y,  &
          center.x - x * center.x, center.y - y * center.y ],  &
        [2, 3 ] )
  END FUNCTION Scale_point
END MODULE Direct2D

PROGRAM scale_bug
  USE Direct2D
  IMPLICIT NONE
  TYPE(D2D1_MATRIX_3X2_F) :: txfrm
  ! We get errors with:
  CALL SomeAPI(  &
      D2D1_BRUSH_PROPERTIES(  &
        TRANSFORM=Scale(1.0, 2.0, D2D1_POINT_2F()) ) )
  ! But not with:
  txfrm = Scale(1.0, 2.0, D2D1_POINT_2F())
  CALL SomeAPI(  &
      D2D1_BRUSH_PROPERTIES(  &
        TRANSFORM=txfrm ) )
END PROGRAM scale_bug

 

>ifort /check:all /warn:all /standard-semantics "2016-05-03 ScaleBug.f90"
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, Version 16.0.2.180 Build 20160204
Copyright (C) 1985-2016 Intel Corporation.  All rights reserved.

2016-05-03 ScaleBug.f90(30): remark #7712: This variable has not been used.   [BRUSH_PROPERTIES]
  SUBROUTINE SomeAPI(brush_properties)
---------------------^
2016-05-03 ScaleBug.f90(55): error #6506: This intrinsic procedure reference contains too many arguments.   [SCALE]
        TRANSFORM=Scale(1.0, 2.0, D2D1_POINT_2F()) ) )
------------------^
2016-05-03 ScaleBug.f90(55): error #6303: The assignment operation or the binary expression operation is invalid for the data types of the two operands.
        TRANSFORM=Scale(1.0, 2.0, D2D1_POINT_2F()) ) )
------------------^
2016-05-03 ScaleBug.f90(55): error #8001: The type of the element in a structure-constructor differs from the type of the component in the derived-type-def.
        TRANSFORM=Scale(1.0, 2.0, D2D1_POINT_2F()) ) )
------------------^
compilation aborted for 2016-05-03 ScaleBug.f90 (code 1)

 

0 Kudos
1 Reply
Kevin_D_Intel
Employee
633 Views

Thank you for the report Ian and the convenient reproducer. I reported this to Development.

(Internal tracking id: DPD200410518)

0 Kudos
Reply