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

Internal error when using a derived type decleared as a parameter

Olsen__Oystein
Beginner
903 Views

The following example generates an internal error. The internal error happens when I use a derived type that is declared as a parameter and in contains a generic binding. The offending statement is on line 76, while line 27 describes a work around.

I am using intel fortran 14.0.1 on openSUSE 12.3

[fortran]

MODULE HS2Kinds
USE ISO_FORTRAN_ENV, ONLY: INT32
USE ISO_FORTRAN_ENV, ONLY: REAL32, REAL64, REAL128

INTEGER, PARAMETER :: I4B = INT32

INTEGER, PARAMETER :: SP = REAL32
INTEGER, PARAMETER :: DP = REAL64
INTEGER, PARAMETER :: QP = REAL128
END MODULE HS2Kinds

MODULE HS2Frame
USE HS2Kinds
IMPLICIT NONE
PRIVATE

PUBLIC :: HSFrame, ITRF, ICRF

TYPE HSFrame
INTEGER(I4B), PRIVATE :: val = -1
CONTAINS
GENERIC :: toFrame => toFrameq, toFramed, toFrames
PROCEDURE, PASS :: toFrameq
PROCEDURE, PASS :: toFramed
PROCEDURE, PASS :: toFrames
END TYPE HSFrame

TYPE(HSFrame), PARAMETER :: ITRF = HSFrame(3)
TYPE(HSFrame), PARAMETER :: ICRF = HSFrame(12)

!ICE: No ICE with these two statements instead of those above.
!TYPE(HSFrame) :: ITRF = HSFrame(3)
!TYPE(HSFrame) :: ICRF = HSFrame(12)

CONTAINS
SUBROUTINE toFrameq(this, frm, r)
USE HS2Kinds, ONLY: XP => QP
CLASS(HSFrame), INTENT(IN) :: this, frm
REAL(XP), INTENT(INOUT) :: r(3)

! Dummy code
IF (this%val == 12 .AND. frm%val == 12) THEN
r = -1.0_XP
ELSE
r = REAL(frm%val, XP)
END IF
RETURN
END SUBROUTINE toFrameq

SUBROUTINE toFramed(this, frm, r)
USE HS2Kinds, ONLY: XP => DP
CLASS(HSFrame), INTENT(IN) :: this, frm
REAL(XP), INTENT(INOUT) :: r(3)

! Dummy code
IF (this%val == 12 .AND. frm%val == 12) THEN
r = -1.0_XP
ELSE
r = REAL(frm%val, XP)
END IF
RETURN
END SUBROUTINE toFramed

SUBROUTINE toFrames(this, frm, r)
USE HS2Kinds, ONLY: XP => SP
CLASS(HSFrame), INTENT(IN) :: this, frm
REAL(XP), INTENT(INOUT) :: r(3)

! Dummy code
IF (this%val == 12 .AND. frm%val == 12) THEN
r = -1.0_XP
ELSE
r = REAL(frm%val, XP)
END IF
RETURN
END SUBROUTINE toFrames

END MODULE HS2Frame

PROGRAM test
USE HS2Kinds
USE HS2Frame, ONLY: ITRF, ICRF
REAL(DP) :: r(3)


CALL ICRF%toFramed(ITRF, r)

!ICE: Internal error
CALL ICRF%toFrame(ITRF, r)

END PROGRAM test

[/fortran]

0 Kudos
6 Replies
Kevin_D_Intel
Employee
903 Views

Thank you for reporting this and for the convenient reproducer. I reproduced this with our latest CXE 2013 SP1 Update 1 also.

(Updated 11/8/2013): Steve escalated to Development.

0 Kudos
Steven_L_Intel1
Employee
903 Views

Issue ID is DPD200249703.

0 Kudos
Steven_L_Intel1
Employee
903 Views

This has been fixed for a release later this year.

0 Kudos
FortranFan
Honored Contributor III
903 Views

Steve,

Will it be possible to provide a target release version info along with such notifications?  Something like, "The fix is targeted for release in compiler version X due later this year" where X can be compiler 14, Update 3 (if there is such a thing), or XE 2015 (aka compiler 15?), etc.

I understand this may be difficult, but it will be very useful for us users if we know the target version.  Otherwise, we have to loop back with future release and see if the fix has been made it in there.

Thanks,

 

0 Kudos
Steven_L_Intel1
Employee
903 Views

If I say "release", I mean a major version release with a number higher than the current one. I'm not supposed to talk about what that number is before the product is released, especially as version numbers are really marketing things, but there will be only one major release this year so whatever it is called later this year, that will be it. But you can probably guess. (It won't be a "SP")

If I say "update", I mean an update to the current version, and I can usually give a timeframe for that.
 

0 Kudos
FortranFan
Honored Contributor III
903 Views

Steve Lionel (Intel) wrote:

If I say "release", I mean a major version release with a number higher than the current one. I'm not supposed to talk about what that number is before the product is released, especially as version numbers are really marketing things, but there will be only one major release this year so whatever it is called later this year, that will be it. But you can probably guess. (It won't be a "SP")

If I say "update", I mean an update to the current version, and I can usually give a timeframe for that.
 

Subtle and cool!  Thanks much for the explanation, I understand better.

0 Kudos
Reply