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

Intel 11.1/12.0 internal compiler error

jr_reuter
Beginner
380 Views
The Intel (even in the latest version Intel Fortran Compiler XE for applications running on IA-32, Version 12.0.1.107 Build 20101116) crashes on the code below (perfectly well compiled by gfortran, NAG, g95, Portland) with an internal compiler error:

ifort -c iso_varying_string.f90
ifort -c variables.f90
variables.f90: catastrophic error: **Internal compiler error: segmentation violation signal raised** 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.
compilation aborted for variables.f90 (code 1)

(iso_varying_string.f90 is the standard file from the web http://www.fortran.com/iso_varying_string.f95)

Here is the code:

module kinds
implicit none
private

public :: single, double
public :: default

integer, parameter :: single = &
& selected_real_kind (precision(1.), range(1.))
integer, parameter :: double = &
& selected_real_kind (precision(1._single) + 1, range(1._single) + 1)
integer, parameter :: default = double

end module kinds

!!!!!

module diagnostics

use kinds, only: default !NODEP!
use iso_varying_string, string_t => varying_string !NODEP!

implicit none
private

public :: real2string
public :: real2char
public :: cmplx2string
public :: cmplx2char

integer, parameter :: &
& TERMINATE=-2, BUG=-1, &
& FATAL=1, ERROR=2, WARNING=3, MESSAGE=4, RESULT=5, DEBUG=6
integer, parameter :: TERM_STOP = 0, TERM_EXIT = 1, TERM_CRASH = 2

type :: string_list
character(len=1000) :: string
type(string_list), pointer :: next
end type string_list
type :: string_list_pointer
type(string_list), pointer :: first, last
end type string_list_pointer

integer, save :: msg_level = RESULT
integer, save :: handle_fatal_errors = TERM_EXIT
type(string_list_pointer), dimension(TERMINATE:WARNING), save :: &
& msg_list = string_list_pointer (null(), null())
interface real2string
module procedure real2string_list, real2string_fmt
end interface
interface real2char
module procedure real2char_list, real2char_fmt
end interface

contains

pure function real2fixed (x, fmt) result (c)
real(default), intent(in) :: x
character(*), intent(in), optional :: fmt
character(200) :: c
c = ""
write (c, *) x
c = adjustl (c)
end function real2fixed

pure function real2fixed_fmt (x, fmt) result (c)
real(default), intent(in) :: x
character(*), intent(in) :: fmt
character(200) :: c
c = ""
write (c, fmt) x
c = adjustl (c)
end function real2fixed_fmt

pure function real2string_list (x) result (s)
real(default), intent(in) :: x
type(string_t) :: s
s = trim (real2fixed (x))
end function real2string_list

pure function real2string_fmt (x, fmt) result (s)
real(default), intent(in) :: x
character(*), intent(in) :: fmt
type(string_t) :: s
s = trim (real2fixed_fmt (x, fmt))
end function real2string_fmt

pure function real2char_list (x) result (c)
real(default), intent(in) :: x
character(len_trim (real2fixed (x))) :: c
c = real2fixed (x)
end function real2char_list
pure function real2char_fmt (x, fmt) result (c)
real(default), intent(in) :: x
character(*), intent(in) :: fmt
character(len_trim (real2fixed_fmt (x, fmt))) :: c
c = real2fixed_fmt (x, fmt)
end function real2char_fmt

pure function cmplx2string (x) result (s)
complex(default), intent(in) :: x
type(string_t) :: s
s = real2string (real (x, default))
if (aimag (x) /= 0) s = s // " + "
end function cmplx2string

pure function cmplx2char (x) result (c)
complex(default), intent(in) :: x
character(len (char (cmplx2string (x)))) :: c
c = "a"
end function cmplx2char

end module diagnostics

!!!!!

module variables

use kinds, only: default !NODEP!
use diagnostics !NODEP!

implicit none
private

type :: var_entry_t
private
integer :: type = 0
complex(default), pointer :: cval => null ()
type(var_entry_t), pointer :: next => null ()
end type var_entry_t

contains

recursive subroutine var_entry_write (var, show_ptr, &
intrinsic)
type(var_entry_t), intent(in) :: var
logical, intent(in), optional :: show_ptr
logical, intent(in), optional :: intrinsic
write (*, *) cmplx2char (var%cval)
end subroutine var_entry_write

end module variables





0 Kudos
2 Replies
Kevin_D_Intel
Employee
380 Views
Thank you for notifying us about the internal error. I reproduced the error with both 11.1 and XE 2011 (12.0) and forwarded to Development (internal tracking id noted below).

(Internal tracking id: DPD200165433)

(Resolution Update on 10/27/2011): This defect is fixed in the Intel Fortran Composer XE 2011 Update6 (2011.1.1.233 - Linux)
0 Kudos
Kevin_D_Intel
Employee
380 Views
This defect is fixed in the Intel Fortran Composer XE 2011 Update6 (2011.1.1.233 - Linux)
0 Kudos
Reply