lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr66311.f90
blob2cefa95e6441083dcbabdae4965d384125f7044d
1 ! { dg-do run }
2 ! { dg-additional-options "-fno-range-check -w" }
4 ! Check that we can print large constants
6 ! "-fno-range-check -w" is used so the testcase compiles even with targets
7 ! that don't support large integer kinds.
9 program test
10 use iso_fortran_env, only : ikinds => integer_kinds
11 implicit none
13 ! Largest integer kind
14 integer, parameter :: k = ikinds(size(ikinds))
15 integer, parameter :: hk = k / 2
17 if (k <= 8) stop
19 call check(9000000000000000000_k, "9000000000000000000")
20 call check(90000000000000000000_k, "90000000000000000000")
21 call check(int(huge(1_hk), kind=k), "9223372036854775807")
22 call check(2_k**63, "9223372036854775808")
23 call check(10000000000000000000_k, "10000000000000000000")
24 call check(18446744065119617024_k, "18446744065119617024")
25 call check(2_k**64 - 1, "18446744073709551615")
26 call check(2_k**64, "18446744073709551616")
27 call check(20000000000000000000_k, "20000000000000000000")
28 call check(huge(0_k), "170141183460469231731687303715884105727")
29 call check(huge(0_k)-1, "170141183460469231731687303715884105726")
31 call check(-9000000000000000000_k, "-9000000000000000000")
32 call check(-90000000000000000000_k, "-90000000000000000000")
33 call check(-int(huge(1_hk), kind=k), "-9223372036854775807")
34 call check(-2_k**63, "-9223372036854775808")
35 call check(-10000000000000000000_k, "-10000000000000000000")
36 call check(-18446744065119617024_k, "-18446744065119617024")
37 call check(-(2_k**64 - 1), "-18446744073709551615")
38 call check(-2_k**64, "-18446744073709551616")
39 call check(-20000000000000000000_k, "-20000000000000000000")
40 call check(-huge(0_k), "-170141183460469231731687303715884105727")
41 call check(-(huge(0_k)-1), "-170141183460469231731687303715884105726")
42 call check(-huge(0_k)-1, "-170141183460469231731687303715884105728")
44 call check(2_k * huge(1_hk), "18446744073709551614")
45 call check((-2_k) * huge(1_hk), "-18446744073709551614")
47 contains
49 subroutine check (i, str)
50 implicit none
51 integer(kind=k), intent(in), value :: i
52 character(len=*), intent(in) :: str
54 character(len=100) :: buffer
55 write(buffer,*) i
56 if (adjustl(buffer) /= adjustl(str)) STOP 1
57 end subroutine
59 end