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

Generic binding inheritance

IanH
Honored Contributor III
1,350 Views

The following source:

[fortran]MODULE MaterialStreamValues
  IMPLICIT NONE
  PRIVATE
 
  TYPE, ABSTRACT, PUBLIC :: MaterialStreamValue
  CONTAINS
    PROCEDURE(ms_wflow_op), DEFERRED :: wflow_op
    GENERIC :: OPERATOR(.WFlow.) => wflow_op
  END TYPE MaterialStreamValue
 
  ABSTRACT INTERFACE
    ELEMENTAL FUNCTION ms_wflow_op(str) RESULT(wflow)
      IMPORT :: MaterialStreamValue
      IMPLICIT NONE
      !-------------------------------------------------------------------------
      CLASS(MaterialStreamValue), INTENT(IN) :: str
      REAL :: wflow
    END FUNCTION ms_wflow_op
  END INTERFACE
END MODULE MaterialStreamValues

MODULE AqueousStreamValues
  USE MaterialStreamValues
  IMPLICIT NONE
  PRIVATE
 
  TYPE, EXTENDS(MaterialStreamValue), PUBLIC :: AqueousStreamValue
  CONTAINS
    PROCEDURE :: wflow_op => as_wflow_op
  END TYPE AqueousStreamValue
CONTAINS
  SUBROUTINE proc(str)
    CLASS(AqueousStreamValue), INTENT(IN) :: str
    REAL :: magnitude
    !***************************************************************************
    magnitude = .WFlow. str
  END SUBROUTINE proc
 
  ELEMENTAL FUNCTION as_wflow_op(str) RESULT(wflow)
    CLASS(AqueousStreamValue), INTENT(IN) :: str
    REAL :: wflow
    !***************************************************************************
    wflow = 2.0
  END FUNCTION as_wflow_op
END MODULE AqueousStreamValues

[/fortran]

when compiled with ifort 13.0.0 gives an error that I think is bogus:

[plain]>ifort /c /check:all /warn:all /standard-semantics Ifort13GoesAndRuinsMyBeautifulTypeHierarchy.f90
Intel(R) Visual Fortran Compiler XE for applications running on IA-32, Version 13.0.0.089 Build 20120731
Copyright (C) 1985-2012 Intel Corporation.  All rights reserved.

Ifort13GoesAndRuinsMyBeautifulTypeHierarchy.f90(36): error #6767: No matching user defined OPERATOR with the given type
and rank has been defined.   [WFLOW]
    magnitude = .WFlow. str
-----------------^
Ifort13GoesAndRuinsMyBeautifulTypeHierarchy.f90(39): remark #7712: This variable has not been used.   [STR]
  ELEMENTAL FUNCTION as_wflow_op(str) RESULT(wflow)
---------------------------------^
compilation aborted for Ifort13GoesAndRuinsMyBeautifulTypeHierarchy.f90 (code 1)[/plain]

This had me going cross-eyed trying to spot the spelling mistake/get a reproducer, until I realised that the order of the module procedures in the second module matters (put proc after as_wflow_op and the error goes away).

There be ice-bergs for the compiler not far away from this example too.

0 Kudos
14 Replies
jimdempseyatthecove
Honored Contributor III
1,350 Views
IanH, have you experimented to see if there is an issue between operator(.WFlow.) and result(wflow)? Fortran is case insensitive. The order of the module procedures may (will) alter the order of creation of the symbol table. Should the symbol table contain operators sans .'s then there may be a conflict. I do not have V13 of the compiler so I cannot test. Jim Dempsey
0 Kudos
IanH
Honored Contributor III
1,350 Views
The name of the result variable (or the name of the operator) doesn't seem to change things. This problem is also in 12.1.x, not sure how I've avoided it till now.
0 Kudos
IanH
Honored Contributor III
1,350 Views
Here's a similar block of code (main change is the addition of a structure constructor) that gives an ICE. [fortran] MODULE MaterialStreamValues IMPLICIT NONE PRIVATE TYPE, ABSTRACT, PUBLIC :: MaterialStreamValue CONTAINS PROCEDURE(ms_wflow_op), DEFERRED, PRIVATE :: wflow_op GENERIC :: OPERATOR(.WFlow.) => wflow_op END TYPE MaterialStreamValue ABSTRACT INTERFACE FUNCTION ms_wflow_op(str) RESULT(wflow) IMPORT :: MaterialStreamValue IMPLICIT NONE CLASS(MaterialStreamValue), INTENT(IN) :: str REAL :: wflow END FUNCTION ms_wflow_op END INTERFACE END MODULE MaterialStreamValues MODULE AqueousStreamValues USE MaterialStreamValues IMPLICIT NONE PRIVATE PUBLIC :: AqueousStreamValue TYPE, EXTENDS(MaterialStreamValue) :: AqueousStreamValue PRIVATE REAL :: WFlow REAL :: MVConc(10) CONTAINS PROCEDURE :: wflow_op => as_wflow_op END TYPE AqueousStreamValue INTERFACE AqueousStreamValue MODULE PROCEDURE AqueousStreamValue_ END INTERFACE AqueousStreamValue CONTAINS PURE FUNCTION AqueousStreamValue_(wflow, mvconc) RESULT(str) REAL, INTENT(IN) :: wflow REAL, INTENT(IN) :: mvconc(:) TYPE(AqueousStreamValue) :: str !*************************************************************************** str%WFlow = wflow str%MVConc = mvconc END FUNCTION AqueousStreamValue_ FUNCTION as_wflow_op(str) RESULT(wflow) CLASS(AqueousStreamValue), INTENT(IN) :: str REAL :: wflow !*************************************************************************** wflow = 2.0 END FUNCTION as_wflow_op FUNCTION proc(lhs, rhs) RESULT(res) CLASS(AqueousStreamValue), INTENT(IN) :: lhs REAL, INTENT(IN) :: rhs TYPE(AqueousStreamValue) :: res !*************************************************************************** ! Oops - passed scalar instead of an array. res = AqueousStreamValue(.WFlow. lhs * rhs, 1.0) END FUNCTION proc END MODULE AqueousStreamValues [/fortran] [plain] >ifort /c /check:all /warn:all /standard-semantics "2012-09-26 ice.f90" Intel(R) Visual Fortran Compiler XE for applications running on IA-32, Version 13.0.0.089 Build 20120731 Copyright (C) 1985-2012 Intel Corporation. All rights reserved. 2012-09-26 ice.f90(63): internal error: Please visit 'http://www.intel.com/software/products/support' for assistance. res = AqueousStreamValue(.WFlow. lhs * rhs, 1.0) ^ [ Aborting due to internal error. ] compilation aborted for 2012-09-26 ice.f90 (code 1)[/plain]
0 Kudos
Steven_L_Intel1
Employee
1,350 Views
Ian, thanks for the second example - I have reported this as issue DPD200236866. As you note, making the second argument of the "constructor" an array rather than a scalar allows it to compile. In the code as shown, the compiler ought to complain about the constructor not matching the type. I will look at the first example next - I think you also started a discussion in comp.lang.fortran on this one.
0 Kudos
Steven_L_Intel1
Employee
1,350 Views
First example escalated as DPD200236870.
0 Kudos
IanH
Honored Contributor III
1,350 Views
The c.l.f discussion was just about language rules. Hopefully what the ifort compiler does now is what is supposed to happen. In the first example, the ordering of procedures after the contains statement of the module changes whether things compile or not, That can't be a healthy sign.
0 Kudos
Steven_L_Intel1
Employee
1,350 Views
Right - I've seen another case where procedure order matters. This is not right and we'll fix it.
0 Kudos
IanH
Honored Contributor III
1,350 Views
The c.l.f. discussion comes back with information (F08/0052) that says what I think the ifort compiler does now (private bindings can be overridden in modules other than the module that defines the private binding) is broken. :(
0 Kudos
IanH
Honored Contributor III
1,350 Views
And here be an example of c.l.f discussed breakage. [fortran] MODULE ParentMod IMPLICIT NONE PRIVATE PUBLIC :: call_a PUBLIC :: call_b TYPE, ABSTRACT, PUBLIC :: Parent CONTAINS PROCEDURE(parent_a), DEFERRED, PRIVATE, NOPASS :: a PROCEDURE, PRIVATE, NOPASS :: b END TYPE Parent ABSTRACT INTERFACE SUBROUTINE parent_a END SUBROUTINE parent_a END INTERFACE CONTAINS SUBROUTINE call_a(arg) CLASS(Parent), INTENT(IN) :: arg CALL arg%a END SUBROUTINE call_a SUBROUTINE b PRINT "('parent b')" END SUBROUTINE b SUBROUTINE call_b(arg) CLASS(Parent), INTENT(IN) :: arg CALL arg%b END SUBROUTINE call_b END MODULE ParentMod MODULE ExtensionMod USE ParentMod IMPLICIT NONE PRIVATE ! This violates C429 - this type inherits a deferred type bound procedure but ! it is not abstract. No diagnostic from compiler. (Rest of example pretends ! this issue doesn't exist.) TYPE, EXTENDS(PARENT), PUBLIC :: Extension CONTAINS PROCEDURE, NOPASS :: a PROCEDURE, NOPASS :: b END TYPE Extension CONTAINS SUBROUTINE a PRINT "('extension a')" END SUBROUTINE a SUBROUTINE b PRINT "('extension b')" END SUBROUTINE b END MODULE ExtensionMod PROGRAM PrivatelyIThinkItWasTheWrongCall USE ParentMod USE ExtensionMod IMPLICIT NONE TYPE(Extension) :: te CLASS(Parent), ALLOCATABLE :: cp !***************************************************************************** ALLOCATE(Extension :: cp) CALL te%a CALL call_a(cp) ! Prints 'extension a', but really calling deferred . ! procedure without implementation. CALL te%b CALL call_b(cp) ! Prints 'extension b', but should be "parent b". END PROGRAM PrivatelyIThinkItWasTheWrongCall [/fortran]
0 Kudos
Steven_L_Intel1
Employee
1,350 Views
Thanks - we are aware of Corrigendum 1 (we did, after all, vote on it) and will be going through it.
0 Kudos
Steven_L_Intel1
Employee
1,350 Views
In the case of your last example, F08/0052 says that since no accessible type-bound procedures are inherited at line 062, C429 doesn't apply. At least that's my reading - do you agree?
0 Kudos
IanH
Honored Contributor III
1,350 Views
Not quite (if I follow, which is always an issue prior to the first coffee of the day) - the change that F08/0052 made was to qualify what you can override, not what is inherited - so the unaccessible bindings are inherited, but can't be overridden. As one of those bindings is deferred then the extension needs to be abstract (but as you can't override the binding, the Parent type is rendered useless). I think there was an example like this in the interp.
0 Kudos
IanH
Honored Contributor III
1,350 Views
And to clarify the structure constructor issue - any array expression that's not just a designator or constant (or something like that) associated with an actual argument in a "structure constructor overload" causes an ICE (the "oops" above is probably a distraction). [fortran] MODULE m20121004 IMPLICIT NONE PRIVATE PUBLIC :: MyType TYPE :: MyType END TYPE MyType INTERFACE MyType MODULE PROCEDURE MyType_ END INTERFACE MyType CONTAINS FUNCTION MyType_(arg) RESULT(r) INTEGER, INTENT(IN) :: arg(:) TYPE(MyType) :: r END FUNCTION MyType_ END MODULE m20121004 PROGRAM StructureConstructors USE m20121004 IMPLICIT NONE TYPE(MyType) :: t t = MyType([1,2] * 1) END PROGRAM StructureConstructors [/fortran] [plain] >ifort /check:all /warn:all /standard-semantics StructureConstructors.f90 Intel(R) Visual Fortran Compiler XE for applications running on IA-32, Version 13.0.0.089 Build 20120731 Copyright (C) 1985-2012 Intel Corporation. All rights reserved. StructureConstructors.f90(11): warning #6178: The return value of this FUNCTION has not been defined. FUNCTION MyType_(arg) RESULT(r) -------------------------------^ StructureConstructors.f90(11): remark #7712: This variable has not been used. [ARG] FUNCTION MyType_(arg) RESULT(r) -------------------^ StructureConstructors.f90(11): remark #7712: This variable has not been used. FUNCTION MyType_(arg) RESULT(r) -------------------------------^ StructureConstructors.f90(22): internal error: Please visit 'http://www.intel.com/software/products/support' for assistance. t = MyType([1,2] * 1) ^ [ Aborting due to internal error. ] compilation aborted for StructureConstructors.f90 (code 1) [/plain]
0 Kudos
Steven_L_Intel1
Employee
1,350 Views
I expect that the fix for both problems will appear in Update 2 (January, I think).
0 Kudos
Reply