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

ICE with ifort 14.0.0 and 14.0.1

valery_w_
Beginner
612 Views

Dear All

Is it the right forum to post ifort ICEs?

The following code is producing an ICE with 14.0.0 and 14.0.1. Would it be possible to fix it for the next release?

Valery


MODULE semi_empirical_atom_types
  TYPE se_atom_type
  END TYPE se_atom_type
END MODULE semi_empirical_atom_types

MODULE semi_empirical_taper_types
  TYPE taper_type
  END TYPE taper_type
  TYPE se_taper_type
   CONTAINS
     PROCEDURE, PASS :: init => se_taper_init
  END TYPE se_taper_type
CONTAINS
  SUBROUTINE se_taper_init(se_taper)
    CLASS(se_taper_type)                     :: se_taper
  END SUBROUTINE se_taper_init
END MODULE semi_empirical_taper_types


MODULE semi_empirical_integrals_types
  TYPE se_int_control_type
  END TYPE se_int_control_type
  TYPE se_int_screen_type
   CONTAINS
     PROCEDURE, PASS :: get  => se_int_screen_get
     PROCEDURE, PASS :: put  => se_int_screen_put
  END TYPE se_int_screen_type
CONTAINS
  SUBROUTINE se_int_screen_put(this, ft, dft)
    CLASS(se_int_screen_type), INTENT(INOUT) :: this
    REAL(KIND=8), INTENT(IN), OPTIONAL      :: ft, dft
  END SUBROUTINE se_int_screen_put
  SUBROUTINE se_int_screen_get(this, ft, dft)
    CLASS(se_int_screen_type), INTENT(IN)    :: this
    REAL(KIND=8), INTENT(OUT), OPTIONAL     :: ft, dft
  END SUBROUTINE se_int_screen_get
END MODULE semi_empirical_integrals_types


MODULE semi_empirical_integrals_numerical
  USE semi_empirical_integrals_types
  USE semi_empirical_taper_types,      ONLY: se_taper_type,&
                                             taper_type
  USE semi_empirical_atom_types,            ONLY: se_atom_type
CONTAINS
  SUBROUTINE rotint_num (sepi,sepj,rijv,w,se_int_control,se_taper)
    CLASS(se_atom_type), INTENT(IN)           :: sepi, sepj
    REAL(KIND=8), DIMENSION(3), INTENT(IN)  :: rijv
    REAL(KIND=8), DIMENSION(2025), &
      INTENT(OUT)                            :: w
    CLASS(se_int_control_type), INTENT(IN)    :: se_int_control
    CLASS(se_taper_type), INTENT(IN)          :: se_taper
  END SUBROUTINE rotint_num

END MODULE semi_empirical_integrals_numerical


MODULE semi_empirical_integrals_analytical
  USE semi_empirical_integrals_types,  ONLY: se_int_screen_type
INTERFACE check_rotint_ana
   SUBROUTINE check_rotint_ana()
     USE semi_empirical_integrals_numerical,    ONLY: rotint_num
     USE semi_empirical_taper_types,            ONLY: se_taper_type
   END SUBROUTINE check_rotint_ana
END INTERFACE check_rotint_ana
CONTAINS
  SUBROUTINE dssss_nucint_ana()
    TYPE(se_int_screen_type)                 :: se_int_screen
    CALL se_int_screen%put(ft=1.0_8, dft=0.0_8)
  END SUBROUTINE dssss_nucint_ana
END MODULE semi_empirical_integrals_analytical
ifort -V
Intel(R) Fortran Intel(R) 64 Compiler XE for applications running on Intel(R) 64, Version 14.0.1.106 Build 20131008
Copyright (C) 1985-2013 Intel Corporation.  All rights reserved.
FOR NON-COMMERCIAL USE ONLY

ifort -c ice.f90
ice.f90(39): warning #6843: A dummy argument with an explicit INTENT(OUT) declaration is not given an explicit value.   [FT]
  SUBROUTINE se_int_screen_get(this, ft, dft)
-------------------------------------^
ice.f90(39): warning #6843: A dummy argument with an explicit INTENT(OUT) declaration is not given an explicit value.   [DFT]
  SUBROUTINE se_int_screen_get(this, ft, dft)
-----------------------------------------^
ice.f90(52): warning #6843: A dummy argument with an explicit INTENT(OUT) declaration is not given an explicit value.  
  SUBROUTINE rotint_num (sepi,sepj,rijv,w,se_int_control,se_taper)
----------------------------------------^
ice.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 ice.f90 (code 1)

0 Kudos
2 Replies
mecej4
Honored Contributor III
612 Views

If you remove the interface block for check_rotint_ana, which is not needed in the code that you presented, the compiler does not run into an ICE.

0 Kudos
Steven_L_Intel1
Employee
612 Views

Yes, this is a fine place to post such issues. We'll check it out - thanks.

0 Kudos
Reply