https://gcc.gnu.org/bugzilla/show_bug.cgi?id=71252

--- Comment #7 from Joost VandeVondele <Joost.VandeVondele at mat dot ethz.ch> 
---
The following testcase is slightly different in that it leads to a segfault:

> cat bug.f90
MODULE xc_pbe
  INTEGER, PARAMETER :: dp=8
CONTAINS
SUBROUTINE pbe_lsd_calc(rhoa, rhob, norm_drho, norm_drhoa, norm_drhob,&
     e_0, e_ra, e_rb, e_ra_ndra, e_rb_ndrb, e_ndr_ndr,&
     e_ndra, e_ndrb, e_ra_ra, e_ra_rb, e_rb_rb, e_ra_ndr, e_rb_ndr,&
     grad_deriv,npoints,epsilon_rho,epsilon_drho,param,scale_ec,scale_ex,error)
    REAL(kind=dp), DIMENSION(*), INTENT(inout) :: e_0, e_ra, e_rb, e_ra_ndra, &
      e_ra_ra, e_ra_rb, e_rb_rb, e_ra_ndr, e_rb_ndr
    INTEGER, INTENT(in)                      :: grad_deriv, npoints
    REAL(kind=dp) :: A, A1rhoa, A1rhob, A_1, A_2, A_3, alpha_1_1, alpha_1_2, &
      t789, t79, t795, t798, t8, t80, t801, t812, t82, t820, t821
  SELECT CASE(grad_deriv)
  CASE default
     DO ii=1,npoints
        IF (my_rho>epsilon_rho) THEN
           IF (grad_deriv>=2.OR.grad_deriv==-2) THEN
              k_s1rhoa = k_srhoa
              t801 = t96 * t798 * k_srhoa / 0.2e1_dp
              trhoarhoa = t775 * t776 * phi1rhoa + t779 * t776 * k_s1rhoa / &
                   0.2e1_dp + t785 - t269 * t98 * phirhoarhoa / 0.2e1_dp + t779
* t789 &
                   * phi1rhoa / 0.2e1_dp + t795 * t789 * k_s1rhoa + t801 - t96
* t274 *&
                   0.2e1_dp + t269 * t277 * phi1rhoa / 0.2e1_dp + t96 * t798 *
k_s1rhoa&
                   / 0.2e1_dp + t812
              t959 = t908 + t911 + t914 + t917 + t919 + 0.2e1_dp * A1rhoa *
t116&
                   * Arhoa + 0.8e1_dp * t944 * Arhoa * t1rhoa + 0.2e1_dp * t314
* &
                   trhoa * t1rhoa + 0.4e1_dp * t318 * trhoarhoa
              t962 = 0.2e1_dp * t101 * t1rhoa * t299 + 0.2e1_dp * t297 * t868 *
&
                   t321 + 0.2e1_dp * t310 * t936 * t321 * t876 - t310 * t313 *
t959
              e_ra_ra(ii) = e_ra_ra(ii)+&
                   scale_ex * (0.2e1_dp * ex_unif_a1rhoa * Fx_a + &
                   my_rho * (epsilon_c_unifrhoarhoa + 0.6e1_dp * t858 * t294 *
phi1rhoa +&
                   phirhoarhoa + 0.3e1_dp * t293 * t326 * phi1rhoa + t110 *
t962 * t325&
                   - t110 * t967 * t879))
              trhoarhob = t775 * t776 * phirhob + t779 * t776 * k_srhob / &
                   scale_ex * (0.2e1_dp * ex_unif_b * &
                   Fx_bnorm_drhob + 0.2e1_dp * t481 * Fx_bnorm_drhob + 0.2e1_dp
* t156 &
                   * (-0.8e1_dp * t1712 * t1713 * s_bnorm_drhob + 0.2e1_dp *
t477 * &
                   s_bnorm_drhob * s_brhob + 0.2e1_dp * t477 * s_b * (-t467 *
t148 * &
                   kf_brhob / 0.2e1_dp - t146 * t472 / 0.2e1_dp))) / 0.2e1_dp
           END IF
        END IF
     END DO
  END SELECT
END SUBROUTINE pbe_lsd_calc
END MODULE xc_pbe


> gfortran  -c -O2 -ffast-math bug.f90
bug.f90:4:0:

 SUBROUTINE pbe_lsd_calc(rhoa, rhob, norm_drho, norm_drhoa, norm_drhob,&

internal compiler error: Segmentation fault
0xba068f crash_signal
        ../../gcc/gcc/toplev.c:333
0x904906 bb_seq_addr
        ../../gcc/gcc/gimple.h:1655
0x904906 gsi_start_bb
        ../../gcc/gcc/gimple-iterator.h:129
0x904906 gsi_for_stmt(gimple*)
        ../../gcc/gcc/gimple-iterator.c:617
0xd57ff2 insert_stmt_after
        ../../gcc/gcc/tree-ssa-reassoc.c:1323
0xd59cd5 build_and_add_sum
        ../../gcc/gcc/tree-ssa-reassoc.c:1392
0xd5b37e rewrite_expr_tree_parallel
        ../../gcc/gcc/tree-ssa-reassoc.c:4128
0xd65296 reassociate_bb
        ../../gcc/gcc/tree-ssa-reassoc.c:5339
0xd649c7 reassociate_bb
        ../../gcc/gcc/tree-ssa-reassoc.c:5391

Reply via email to