comparison gcc/testsuite/gfortran.dg/string_compare_1.f90 @ 111:04ced10e8804

gcc 7
author kono
date Fri, 27 Oct 2017 22:46:09 +0900
parents
children 84e7813d76e9
comparison
equal deleted inserted replaced
68:561a7518be6b 111:04ced10e8804
1 ! { dg-do run }
2
3 ! PR fortran/37099
4 ! Check for correct results when comparing array-section-substrings.
5
6 PROGRAM main
7 IMPLICIT NONE
8
9 CHARACTER(*), PARAMETER :: exprs(1) = (/ 'aa' /)
10
11 CHARACTER(*), PARAMETER :: al1 = 'a';
12 CHARACTER(len=LEN (al1)) :: al2 = al1;
13
14 LOGICAL :: tmp(1), tmp2(1)
15
16 tmp = (exprs(1:1)(1:1) == al1)
17 tmp2 = (exprs(1:1)(1:1) == al2)
18
19 PRINT '(L1)', tmp
20 PRINT '(L1)', tmp2
21
22 IF (.NOT. tmp(1) .OR. .NOT. tmp2(1)) THEN
23 CALL abort ()
24 END IF
25 END PROGRAM main