annotate gcc/testsuite/gfortran.dg/pr63883.f90 @ 131:84e7813d76e9

gcc-8.2
author mir3636
date Thu, 25 Oct 2018 07:37:49 +0900
parents 04ced10e8804
children
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
rev   line source
111
kono
parents:
diff changeset
1 ! { dg-do compile }
kono
parents:
diff changeset
2 ! { dg-additional-options "-ffast-math" }
kono
parents:
diff changeset
3 SUBROUTINE influence_factor ( gftype, error )
kono
parents:
diff changeset
4 INTEGER, PARAMETER :: dp=8
kono
parents:
diff changeset
5 INTEGER :: k,n,lb(3),ub(3),dim,pt
kono
parents:
diff changeset
6 COMPLEX(KIND=dp) :: b_m, exp_m, sum_m
kono
parents:
diff changeset
7 DO k = 0, n-2
kono
parents:
diff changeset
8 DO pt = lb (dim), ub (dim)
kono
parents:
diff changeset
9 sum_m = CMPLX ( 0.0_dp, 0.0_dp,KIND=dp)
kono
parents:
diff changeset
10 b_m = exp_m ** ( n - 1 ) / sum_m
kono
parents:
diff changeset
11 END DO
kono
parents:
diff changeset
12 END DO
kono
parents:
diff changeset
13 END SUBROUTINE influence_factor