OSDN Git Service

2010-11-13 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / char_eoshift_5.f90
1 ! { dg-do run }
2 ! { dg-options "-fdump-tree-original" }
3
4 ! PR fortran/36403
5 ! Check that the string length of BOUNDARY is added to the library-eoshift
6 ! call even if BOUNDARY is missing (as it is optional).
7 ! This is the original test from the PR.
8
9 ! Contributed by Kazumoto Kojima.
10
11   CHARACTER(LEN=3), DIMENSION(10) :: Z
12   call test_eoshift
13 contains
14   subroutine test_eoshift 
15     CHARACTER(LEN=1), DIMENSION(10) :: chk
16     chk(1:8) = "5"
17     chk(9:10) = " "
18     Z(:)="456"
19     if (any (EOSHIFT(Z(:)(2:2),2) .ne. chk)) call abort 
20   END subroutine
21 END
22
23 ! Check that _gfortran_eoshift* is called with 8 arguments:
24 ! { dg-final { scan-tree-dump "_gfortran_eoshift\[0-9_\]+char \\(\[&a-zA-Z0-9._\]*, \[&a-zA-Z0-9._\]*, \[&a-zA-Z0-9._\]*, \[&a-zA-Z0-9._\]*, \[&a-zA-Z0-9._\]*, \[&a-zA-Z0-9._\]*, \[&a-zA-Z0-9._\]*, \[&a-zA-Z0-9._\]*\\)" "original" } }
25 ! { dg-final { cleanup-tree-dump "original" } }