- 新着としてマーク
- ブックマーク
- 購読
- ミュート
- RSS フィードを購読する
- ハイライト
- 印刷
- 不適切なコンテンツを報告
I get an ICE with 11.1.069 (20100203) when compiling the following code:
[fortran]module mod_image TYPE IMAGE !INTEGER, KIND :: VALUE_KIND !< Kind of REAL or COMPLEX array to use for memory storage INTEGER :: DIM(3) = (/1,1,1/) !< Logical (X,Y,Z) dimensions of the image. !! Note that this does not necessarily correspond to !! memory allocation dimensions. LOGICAL :: IN_MEMORY = .FALSE. !< Whether image values are in-memory. Default = .FALSE. CHARACTER(LEN=4) :: TYPE = 'REAL' !< Type of image: 'REAL','COMP','DBLE','DCMP'. Default = .REAL. LOGICAL :: ORIGIN_AT_CENTER = .TRUE. !< Whether the origin is at the center of the image. !! Assumed to always be true in real space, but set !! appropriately by FT routines for reciprocal space. REAL(KIND=4), ALLOCATABLE :: RVALUE(:,:,:) !< Real array to hold values for REAL images. COMPLEX(KIND=4), POINTER :: CVALUE(:,:,:) !< Complex array to hold values for COMPLEX images. ! not used - to be removed REAL(KIND=8), ALLOCATABLE :: DRVALUE(:,:,:) !< Double precision array to hold values for DBLE images COMPLEX(KIND=8), POINTER :: DCVALUE(:,:,:) !< Double complex array to hold values for DCMP images CONTAINS PROCEDURE :: ORIGIN_COO => ORIGIN_COO END TYPE IMAGE CONTAINS !> \brief Returns the integer coordinates of the origin !! \todo Ensure this is called in all relevant subroutines, which should help smooth behaviour with even/odd dimensions PURE FUNCTION ORIGIN_COO(SELF) IMPLICIT NONE ! Arguments CLASS(IMAGE), INTENT(IN) :: SELF ! Result INTEGER :: ORIGIN_COO(3) ! Private variables INTEGER :: I ! Start work IF (SELF%ORIGIN_AT_CENTER) THEN DO I=1,3 IF (MOD(SELF%DIM(I),2) .EQ. 0.0) THEN ! Dimension is even ORIGIN_COO(I) = SELF%DIM(I)/2+1 ELSE ! Dimension is odd ORIGIN_COO(I) = (SELF%DIM(I)-1)/2+1 ENDIF ENDDO ELSE ORIGIN_COO = [1,1,1] ENDIF END FUNCTION ORIGIN_COO end module mod_image program test use mod_image implicit none type(image) :: img print *, 'Hello world', img%origin_coo end program[/fortran]
The compile command & ice:
[bash][alr99@kiev build1]$ ifort -c ../main.f90 ../main.f90(61): catastrophic error: **Internal compiler error: internal abort** Please report this error along with the circumstances in which it occurred in a Software Problem Report. Note: File and line given may not be explicit cause of this error. print *, 'Hello world', img%origin_coo --------------------------------^ compilation aborted for ../main.f90 (code 3) [/bash]
コピーされたリンク
4 返答(返信)
- 新着としてマーク
- ブックマーク
- 購読
- ミュート
- RSS フィードを購読する
- ハイライト
- 印刷
- 不適切なコンテンツを報告
Interestingly, adding parentheses after the TBP call solves this issue. I.e. replacing line 61 above with:
[fortran]print *, 'Hello world', img%origin_coo()[/fortran]
- 新着としてマーク
- ブックマーク
- 購読
- ミュート
- RSS フィードを購読する
- ハイライト
- 印刷
- 不適切なコンテンツを報告
Thanks for the reporting this. I reported it to Development, noted the internal tracking id below, and will update the thread as I learn more.
(Internal tracking id: DPD200151137)
- 新着としてマーク
- ブックマーク
- 購読
- ミュート
- RSS フィードを購読する
- ハイライト
- 印刷
- 不適切なコンテンツを報告
The fix for this issue is expected in next 11.1 update 6 (tentatively in the April/May '10 time -frame).
- 新着としてマーク
- ブックマーク
- 購読
- ミュート
- RSS フィードを購読する
- ハイライト
- 印刷
- 不適切なコンテンツを報告
(Resolution Update on 04/26/2010): This defect is fixed in the Intel Fortran Compiler Professional Edition 11.1 Update 6 (11.1.072 - Linux).
[bash]ifort -V -c u72168.f90
Intel Fortran Intel 64 Compiler Professional for applications running on Intel 64, Version 11.1 Build 20100414 Package ID: l_cprof_p_11.1.072 Copyright (C) 1985-2010 Intel Corporation. All rights reserved. Intel Fortran 11.1-2739 u72168.f90(49): error #8319: An EXTERNAL procedure name must not appear in an input/output item list. [ORIGIN_COO] print *, 'Hello world', img%origin_coo -------------------------------^ compilation aborted for u72168.f90 (code 1) [/bash]
