PR 78534 Change character length from int to size_t
[official-gcc.git] / gcc / testsuite / gfortran.dg / repeat_4.f90
blob99e7aee4670fa36261409153cb58b5c89132c0e5
1 ! REPEAT intrinsic -- various checks should be enforced
3 ! { dg-do compile }
4 program test
5 use iso_c_binding, only: k => c_size_t
6 implicit none
7 character(len=0), parameter :: s0 = ""
8 character(len=1), parameter :: s1 = "a"
9 character(len=2), parameter :: s2 = "ab"
10 character(len=0) :: t0
11 character(len=1) :: t1
12 character(len=2) :: t2
14 t0 = "" ; t1 = "a" ; t2 = "ab"
16 ! Check for negative NCOPIES argument
17 print *, repeat(s0, -1) ! { dg-error "Argument NCOPIES of REPEAT intrinsic is negative" }
18 print *, repeat(s1, -1) ! { dg-error "Argument NCOPIES of REPEAT intrinsic is negative" }
19 print *, repeat(s2, -1) ! { dg-error "Argument NCOPIES of REPEAT intrinsic is negative" }
20 print *, repeat(t0, -1) ! { dg-error "Argument NCOPIES of REPEAT intrinsic is negative" }
21 print *, repeat(t1, -1) ! { dg-error "Argument NCOPIES of REPEAT intrinsic is negative" }
22 print *, repeat(t2, -1) ! { dg-error "Argument NCOPIES of REPEAT intrinsic is negative" }
24 ! Check for too large NCOPIES argument and limit cases
25 print *, repeat(t0, huge(0_k))
26 print *, repeat(t1, huge(0_k))
27 print *, repeat(t2, huge(0_k)) ! { dg-error "Argument NCOPIES of REPEAT intrinsic is too large " }
28 print *, repeat(s2, huge(0_k)) ! { dg-error "Argument NCOPIES of REPEAT intrinsic is too large " }
30 print *, repeat(t0, huge(0_k)/2)
31 print *, repeat(t1, huge(0_k)/2)
32 print *, repeat(t2, huge(0_k)/2)
34 print *, repeat(t0, huge(0_k)/2+1)
35 print *, repeat(t1, huge(0_k)/2+1)
36 print *, repeat(t2, huge(0_k)/2+1) ! { dg-error "Argument NCOPIES of REPEAT intrinsic is too large " }
37 print *, repeat(s2, huge(0_k)/2+1) ! { dg-error "Argument NCOPIES of REPEAT intrinsic is too large " }
39 end program test