aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/array_assignment_5.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc-4.9/gcc/testsuite/gfortran.dg/array_assignment_5.f90')
-rw-r--r--gcc-4.9/gcc/testsuite/gfortran.dg/array_assignment_5.f9016
1 files changed, 16 insertions, 0 deletions
diff --git a/gcc-4.9/gcc/testsuite/gfortran.dg/array_assignment_5.f90 b/gcc-4.9/gcc/testsuite/gfortran.dg/array_assignment_5.f90
new file mode 100644
index 000000000..6d585270c
--- /dev/null
+++ b/gcc-4.9/gcc/testsuite/gfortran.dg/array_assignment_5.f90
@@ -0,0 +1,16 @@
+! { dg-do run }
+! { dg-options "-ffrontend-optimize" }
+! PR 62214 - this used to give the wrong result.
+! Original test case by Oliver Fuhrer
+PROGRAM test
+ IMPLICIT NONE
+ CHARACTER(LEN=20) :: fullNames(2)
+ CHARACTER(LEN=255) :: pathName
+ CHARACTER(LEN=5) :: fileNames(2)
+
+ pathName = "/dir1/dir2/"
+ fileNames = (/ "file1", "file2" /)
+ fullNames = SPREAD(TRIM(pathName),1,2) // fileNames
+ if (fullNames(1) /= '/dir1/dir2/file1' .or. &
+ & fullnames(2) /= '/dir1/dir2/file2') call abort
+END PROGRAM test