aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/spread_scalar_source.f90
diff options
context:
space:
mode:
authorBen Cheng <bccheng@google.com>2014-03-25 22:37:19 -0700
committerBen Cheng <bccheng@google.com>2014-03-25 22:37:19 -0700
commit1bc5aee63eb72b341f506ad058502cd0361f0d10 (patch)
treec607e8252f3405424ff15bc2d00aa38dadbb2518 /gcc-4.9/gcc/testsuite/gfortran.dg/spread_scalar_source.f90
parent283a0bf58fcf333c58a2a92c3ebbc41fb9eb1fdb (diff)
downloadtoolchain_gcc-1bc5aee63eb72b341f506ad058502cd0361f0d10.tar.gz
toolchain_gcc-1bc5aee63eb72b341f506ad058502cd0361f0d10.tar.bz2
toolchain_gcc-1bc5aee63eb72b341f506ad058502cd0361f0d10.zip
Initial checkin of GCC 4.9.0 from trunk (r208799).
Change-Id: I48a3c08bb98542aa215912a75f03c0890e497dba
Diffstat (limited to 'gcc-4.9/gcc/testsuite/gfortran.dg/spread_scalar_source.f90')
-rw-r--r--gcc-4.9/gcc/testsuite/gfortran.dg/spread_scalar_source.f9052
1 files changed, 52 insertions, 0 deletions
diff --git a/gcc-4.9/gcc/testsuite/gfortran.dg/spread_scalar_source.f90 b/gcc-4.9/gcc/testsuite/gfortran.dg/spread_scalar_source.f90
new file mode 100644
index 000000000..118a2de6e
--- /dev/null
+++ b/gcc-4.9/gcc/testsuite/gfortran.dg/spread_scalar_source.f90
@@ -0,0 +1,52 @@
+! { dg-do run }
+! { dg-options "-O0" }
+
+ character*1 :: i, j(10)
+ character*8 :: buffer
+ integer(kind=1) :: ii, jj(10)
+ type :: mytype
+ real(kind=8) :: x
+ integer(kind=1) :: i
+ character*15 :: ch
+ end type mytype
+ type(mytype) :: iii, jjj(10)
+
+ i = "w"
+ ii = 42
+ iii = mytype (41.9999_8, 77, "test_of_spread_")
+
+! Test constant sources.
+
+ j = spread ("z", 1 , 10)
+ if (any (j /= "z")) call abort ()
+ jj = spread (19, 1 , 10)
+ if (any (jj /= 19)) call abort ()
+
+! Test variable sources.
+
+ j = spread (i, 1 , 10)
+ if (any (j /= "w")) call abort ()
+ jj = spread (ii, 1 , 10)
+ if (any (jj /= 42)) call abort ()
+ jjj = spread (iii, 1 , 10)
+ if (any (jjj%x /= 41.9999_8)) call abort ()
+ if (any (jjj%i /= 77)) call abort ()
+ if (any (jjj%ch /= "test_of_spread_")) call abort ()
+
+! Check that spread != 1 is OK.
+
+ jj(2:10:2) = spread (1, 1, 5)
+ if (any (jj(1:9:2) /= 42) .or. any (jj(2:10:2) /= 1)) call abort ()
+
+! Finally, check that temporaries and trans-io.c work correctly.
+
+ write (buffer, '(4a1)') spread (i, 1 , 4)
+ if (trim(buffer) /= "wwww") call abort ()
+ write (buffer, '(4a1)') spread ("r", 1 , 4)
+ if (trim(buffer) /= "rrrr") call abort ()
+ write (buffer, '(4i2)') spread (ii, 1 , 4)
+ if (trim(buffer) /= "42424242") call abort ()
+ write (buffer, '(4i2)') spread (31, 1 , 4)
+ if (trim(buffer) /= "31313131") call abort ()
+
+ end