public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/17612] New: ICE in gfortran
@ 2004-09-22 15:52 giannozz at nest dot sns dot it
  2004-09-22 15:58 ` [Bug fortran/17612] " tobi at gcc dot gnu dot org
                   ` (7 more replies)
  0 siblings, 8 replies; 9+ messages in thread
From: giannozz at nest dot sns dot it @ 2004-09-22 15:52 UTC (permalink / raw)
  To: gcc-bugs

Daily gfortran build downloaded on 22 sep. 2004 for 
Linux i686 
 
$ gfc --version 
GNU Fortran 95 (GCC 4.0.0 20040922 (experimental)) 
Copyright (C) 2003 Free Software Foundation, Inc. 
 
$ gfc -c bug.f90 
bug.f90: In function 'nullify_pseudo_upf': 
bug.f90:76: internal compiler error: Segmentation fault 
 
$ cat bug.f90 
      MODULE pseudo_types 
 
        IMPLICIT NONE 
        INTEGER, PARAMETER :: dbl = selected_real_kind(14,200) 
 
        SAVE 
 
        TYPE pseudo_upf 
          CHARACTER(LEN=80):: generated   !  
          CHARACTER(LEN=80):: date_author ! Misc info 
          CHARACTER(LEN=80):: comment     ! 
          CHARACTER(LEN=2) :: psd       ! Element label 
          CHARACTER(LEN=20) :: typ      ! Pseudo type ( NC or US ) 
          LOGICAL  :: tvanp             ! .true. if Ultrasoft 
          LOGICAL :: nlcc               ! Non linear core corrections 
          CHARACTER(LEN=20) :: dft      ! Exch-Corr type 
          REAL(dbl) :: zp               ! z valence 
          REAL(dbl) :: etotps           ! total energy 
          REAL(dbl) :: ecutwfc          ! suggested cut-off for wfc 
          REAL(dbl) :: ecutrho          ! suggested cut-off for rho 
          LOGICAL :: has_so             ! if .true. includes spin-orbit 
          REAL(dbl) :: xmin             ! the minimum x of the linear mesh 
          REAL(dbl) :: rmax             ! the maximum radius of the mesh 
          REAL(dbl) :: zmesh            ! the nuclear charge used for mesh 
          REAL(dbl) :: dx               ! the deltax of the linear mesh 
          INTEGER, POINTER :: nn(:)      ! nn(nwfc) 
          REAL(dbl), POINTER :: rcut(:)  ! cut-off radius(nwfc) 
          REAL(dbl), POINTER :: rcutus(:)! cut-off ultrasoft radius (nwfc) 
          REAL(dbl), POINTER :: epseu(:) ! energy (nwfc) 
          REAL(dbl), POINTER :: jchi(:)  ! jchi(nwfc) 
          REAL(dbl), POINTER :: jjj(:)   ! jjj(nbeta) 
 
          INTEGER :: nv                 ! UPF file version number 
          INTEGER :: lmax               ! maximum angular momentum component 
          INTEGER :: mesh               ! number of point in the radial mesh 
          INTEGER :: nwfc               ! number of wavefunctions 
          INTEGER :: nbeta              ! number of projectors 
          CHARACTER(LEN=2), POINTER :: els(:)  ! els(nwfc) 
          INTEGER, POINTER :: lchi(:)   ! lchi(nwfc) 
          REAL(dbl), POINTER :: oc(:)   ! oc(nwfc) 
          REAL(dbl), POINTER :: r(:)    ! r(mesh) 
          REAL(dbl), POINTER :: rab(:)  ! rab(mesh) 
          REAL(dbl), POINTER :: rho_atc(:) ! rho_atc(mesh) 
          REAL(dbl), POINTER :: vloc(:)    ! vloc(mesh) 
          INTEGER, POINTER :: lll(:)       ! lll(nbeta) 
          INTEGER, POINTER :: kkbeta(:)    ! kkbeta(nbeta) 
          REAL(dbl), POINTER :: beta(:,:)  ! beta(mesh,nbeta) 
          INTEGER :: nd 
          REAL(dbl), POINTER :: dion(:,:)  ! dion(nbeta,nbeta) 
          INTEGER :: nqf 
          INTEGER :: nqlc 
          REAL(dbl), POINTER :: rinner(:)  ! rinner(0:2*lmax) 
          REAL(dbl), POINTER :: qqq(:,:)   ! qqq(nbeta,nbeta) 
          REAL(dbl), POINTER :: qfunc(:,:,:) ! qfunc(mesh,nbeta,nbeta) 
          REAL(dbl), POINTER :: qfcoef(:,:,:,:) ! 
          REAL(dbl), POINTER :: chi(:,:) !  chi(mesh,nwfc) 
          REAL(dbl), POINTER :: rho_at(:) !  rho_at(mesh) 
        END TYPE 
 
      CONTAINS 
 
        SUBROUTINE nullify_pseudo_upf( upf ) 
          TYPE( pseudo_upf ), INTENT(INOUT) :: upf 
          NULLIFY( upf%els, upf%lchi, upf%jchi, upf%oc ) 
          NULLIFY( upf%r, upf%rab )   
          NULLIFY( upf%rho_atc, upf%vloc )   
          NULLIFY( upf%nn, upf%rcut) 
          NULLIFY( upf%rcutus, upf%epseu) 
          NULLIFY( upf%lll, upf%jjj, upf%kkbeta, upf%beta, upf%dion )   
          NULLIFY( upf%rinner, upf%qqq, upf%qfunc, upf%qfcoef )   
          NULLIFY( upf%chi )   
          NULLIFY( upf%rho_at )   
          RETURN 
        END SUBROUTINE 
 
      END MODULE pseudo_types

-- 
           Summary: ICE in gfortran
           Product: gcc
           Version: 4.0.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P2
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: giannozz at nest dot sns dot it
                CC: gcc-bugs at gcc dot gnu dot org
  GCC host triplet: i686 Linux


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=17612


^ permalink raw reply	[flat|nested] 9+ messages in thread

end of thread, other threads:[~2004-10-15 17:15 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2004-09-22 15:52 [Bug fortran/17612] New: ICE in gfortran giannozz at nest dot sns dot it
2004-09-22 15:58 ` [Bug fortran/17612] " tobi at gcc dot gnu dot org
2004-09-22 16:01 ` tobi at gcc dot gnu dot org
2004-09-22 16:14 ` tobi at gcc dot gnu dot org
2004-09-24 18:00 ` tobi at gcc dot gnu dot org
2004-09-25 14:25 ` tobi at gcc dot gnu dot org
2004-09-27 14:41 ` tobi at gcc dot gnu dot org
2004-10-04 13:12 ` pbrook at gcc dot gnu dot org
2004-10-15 17:15 ` pinskia at gcc dot gnu dot org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).