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

Inherited elemental generic operator used as elemental operator gives ice

IanH
Honored Contributor III
826 Views

Inherited type bound generic operators used in an "elemental context" cause an ICE with 13.0.0.0.0.089.

[fortran]

MODULE m20121015
  IMPLICIT NONE
 
  PRIVATE
 
  TYPE, ABSTRACT, PUBLIC :: parent
  CONTAINS
    PROCEDURE(parent_op), DEFERRED :: op
    GENERIC :: OPERATOR(.op.) => op
  END TYPE parent
 
  ABSTRACT INTERFACE
    ELEMENTAL FUNCTION parent_op(arg) RESULT(r)
      IMPORT :: parent
      IMPLICIT NONE
      CLASS(parent), INTENT(IN) :: arg
      REAL :: r
    END FUNCTION parent_op
  END INTERFACE
 
  TYPE, EXTENDS(parent), PUBLIC :: t
  CONTAINS
    PROCEDURE :: op => t_op
  END TYPE t
CONTAINS
  ELEMENTAL FUNCTION t_op(arg) RESULT(r)
    CLASS(t), INTENT(IN) :: arg
    REAL :: r    
    r = 1.0
  END FUNCTION t_op
END MODULE m20121015

PROGRAM TheWifeDrankAllMyWine
  USE m20121015
  IMPLICIT NONE
  TYPE(t) :: t_array(10)
  !****
  PRINT *, .op. t_array
END PROGRAM TheWifeDrankAllMyWine

[/fortran]

[plain]

>ifort /check:all /warn:all /standard-semantics ElementalOperator.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.

ElementalOperator.f90(26): remark #7712: This variable has not been used.   [ARG]
  ELEMENTAL FUNCTION t_op(arg) RESULT(r)
--------------------------^
ElementalOperator.f90(38): catastrophic error: **Internal compiler error: internal abort** Please report this error alon
g with the circumstances in which it occurred in a Software Problem Report.  Note: File and line given may not be explic
it cause of this error.
compilation aborted for ElementalOperator.f90 (code 1)

[/plain]

Unrelated, but 13.0.0 has developed a habit here of complaining "Fatal compilation error: Out of memory asking for 2097160." after sending my machine into a swapping frenzy,  Same number, different projects with basically unrelated source.  Remarkable.

0 Kudos
11 Replies
IanH
Honored Contributor III
826 Views
While we are mulling on the topic of things type bound and generic... procedure resolution has a glitch in the case where there is both a matching specific binding and an elemental binding. [fortran] MODULE m20121016 IMPLICIT NONE PRIVATE TYPE, PUBLIC :: t CONTAINS PROCEDURE :: elemental => elemental_proc PROCEDURE :: array => array_proc GENERIC :: binding => elemental, array END TYPE t CONTAINS ELEMENTAL SUBROUTINE elemental_proc(obj, arg) CLASS(t), INTENT(IN) :: obj INTEGER, INTENT(IN) :: arg END SUBROUTINE elemental_proc PURE SUBROUTINE array_proc(obj, arg) CLASS(t), INTENT(IN) :: obj INTEGER, INTENT(IN) :: arg(:) END SUBROUTINE array_proc END MODULE m20121016 PROGRAM ICanFeelAFourexComingOn USE m20121016 IMPLICIT NONE TYPE(t) :: obj CALL obj%binding([1,2,3]) END PROGRAM ICanFeelAFourexComingOn [/fortran] [plain] >ifort /check:all /warn:all /standard-semantics ElementalResolution.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. (...elided "not used" warnings...) ElementalResolution.f90(26): error #8443: This generic type bound procedure reference has two or more specific procedure s with the same type/rank/keyword signature. [BINDING] CALL obj%binding([1,2,3]) -----------^ compilation aborted for ElementalResolution.f90 (code 1) [/plain] I think the two bindings are distinguishable (different rank) and hence resolvable by F2008 12.5.6 p2.
0 Kudos
IanH
Honored Contributor III
826 Views
Bump, and while we are here + 1, I would have expected a compile time diagnostic for the following program (which is completely unrelated to the above, but this will be an opportunity for the Intel folk to try out the moderation tools that came with this new forum :) ): [fortran] PROGRAM ArrayElementsDoNotHaveTheAllocatableAttribute IMPLICIT NONE INTEGER, ALLOCATABLE :: a(:) !**** ALLOCATE(a(1)) ! The argument to the ALLOCATED intrinsic violates 13.7.11 p3. PRINT *, ALLOCATED(a(1)) END PROGRAM ArrayElementsDoNotHaveTheAllocatableAttribute [/fortran] (I'm pretty sure that the assertion in the program name is right, but if not, then ummm... ignore this post!) [plain] >ifort /check:all /warn:all /standard-semantics /stand:f03 "2012-10-18 allocated.f90" && "2012-10-18 allocated.exe" 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. Microsoft (R) Incremental Linker Version 10.00.40219.01 Copyright (C) Microsoft Corporation. All rights reserved. "-out:2012-10-18 allocated.exe" -subsystem:console "2012-10-18 allocated.obj" T[/plain] If you poke the name of a non-allocatable scalar variable into the allocated intrinsic the compiler does complain, so the machinery to check 13.7.11p3 is available somewhere.
0 Kudos
Steven_L_Intel1
Employee
826 Views
Thanks, we'll take a look at these.
0 Kudos
Steven_L_Intel1
Employee
826 Views
The error in the first post has been escalated as issue DPD200237594. The error in the second post has been escalated as issue DPD200237595. Third post's issue is escalated as DPD200237596. This looked familiar but I couldn't find a previous report of it.
0 Kudos
Steven_L_Intel1
Employee
826 Views
The third post's problem will be fixed in a future major release. The other two are still being worked on.
0 Kudos
Steven_L_Intel1
Employee
826 Views
Regarding the second post's issue: Changing the order of the GENERIC declation to list the array function prior to the elemental function is a workaround. GENERIC :: binding => array, elemental ! works As in the test: GENERIC :: binding => elemental, array ! fails
0 Kudos
Steven_L_Intel1
Employee
826 Views
The problems in the first and second posts will be fixed in Update 2.
0 Kudos
mecej4
Honored Contributor III
826 Views
Steve: This thread brings to the front a shortcoming of the forum software. Ian has wantonly weaved several topics into a single thread ("rope"?), and you have replied with references such as "the second post", etc. If I wish to look up, say, "the fourth post", I am faced with hindrances. Since there is no numbering for the posts, one has to scroll through the entire thread from the beginning, and keep an accurate mental record of the sequence number of the posts within the thread. Does Intel really want Forum readers to go through such harrowing mental exercises in 2013? Is there a reason not to number the posts within a thread and display those numbers, or am I blaming a shortcoming of my browser (Firefox) upon the Intel forum software? Thanks.
0 Kudos
Steven_L_Intel1
Employee
826 Views
I find this as irritating as you do. I have asked for post numbering and links - I will remind the developers of this request. At least I figured out how to construct links to individual posts. You take the thread URL and add #comment-nnnnnnnn . You can get the nnnnnnnn by hovering over the Quote link and noting the number in the URL after the thread number. For example, the second post in this thread is http://software.intel.com/en-us/forums/topic/329001#comment-1711056
0 Kudos
mecej4
Honored Contributor III
826 Views
Steve, You wrote: "You take the thread URL and add #comment-nnnnnnnn . You can get the nnnnnnnn by hovering over the Quote link and noting the number in the URL after the thread number." That's a useful tip. However, the comment numbers are not always consecutive within a thread. For example, my first post in this thread has comment number 1719445, whereas your one-liner immediately before that one is numbered 1719437. Thus, comment number arithmetic may not give the post number.
0 Kudos
Steven_L_Intel1
Employee
826 Views
I didn't say the numbers are consecutive. You have to look at the "Quote" URL for the specific comment you want to reference.
0 Kudos
Reply