Skip to content

Commit ca8433b

Browse files
committed
Fortran configury: Ensure F08 real_kinds are actually valid kinds
Issue: #5090 Signed-off-by: Luke Robison <[email protected]>
1 parent 53f415d commit ca8433b

File tree

1 file changed

+15
-7
lines changed

1 file changed

+15
-7
lines changed

m4/aclocal_fc.f90

+15-7
Original file line numberDiff line numberDiff line change
@@ -183,8 +183,11 @@ END PROGRAM FC_AVAIL_KINDS
183183
PROGRAM FC08_AVAIL_KINDS
184184
USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : stdout=>OUTPUT_UNIT, integer_kinds, real_kinds, logical_kinds
185185
IMPLICIT NONE
186-
INTEGER :: ik, jk, k, max_decimal_prec
186+
INTEGER :: ik, jk, k, kk, max_decimal_prec
187187
INTEGER :: num_rkinds, num_ikinds, num_lkinds
188+
logical :: found_rkinds( 1:SIZE(real_kinds) )
189+
character(len=1) :: sep
190+
188191

189192
! Find integer KINDs
190193

@@ -203,24 +206,29 @@ PROGRAM FC08_AVAIL_KINDS
203206

204207
num_rkinds = SIZE(real_kinds)
205208

209+
! some compilers (ACfL 24) reported real=16 kind, but refused to
210+
! compile with it. Verify the kind can be selected in SELECTED_REAL_KIND.
211+
found_rkinds(:) = .false.
206212
max_decimal_prec = 1
207213

208214
prec: DO ik = 2, 36
209215
exp: DO jk = 1, 700
210216
k = SELECTED_REAL_KIND(ik,jk)
211217
IF(k.LT.0) EXIT exp
218+
do kk = 1,num_rkinds
219+
if (real_kinds(kk) == k) found_rkinds(kk) = .true.
220+
end do
212221
max_decimal_prec = ik
213222
ENDDO exp
214223
ENDDO prec
215224

225+
sep = ""
216226
DO k = 1, num_rkinds
217-
WRITE(stdout,'(I0)', ADVANCE='NO') real_kinds(k)
218-
IF(k.NE.num_rkinds)THEN
219-
WRITE(stdout,'(A)',ADVANCE='NO') ','
220-
ELSE
221-
WRITE(stdout,'()')
222-
ENDIF
227+
if (.not. found_rkinds(k)) cycle
228+
WRITE(stdout,'(A,I0)', ADVANCE='NO') trim(sep), real_kinds(k)
229+
sep = ","
223230
ENDDO
231+
WRITE(stdout,'()')
224232

225233
WRITE(stdout,'(I0)') max_decimal_prec
226234
WRITE(stdout,'(I0)') num_ikinds

0 commit comments

Comments
 (0)