summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/coarray/send_char_array_1.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/coarray/send_char_array_1.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/coarray/send_char_array_1.f9054
1 files changed, 54 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/coarray/send_char_array_1.f90 b/gcc/testsuite/gfortran.dg/coarray/send_char_array_1.f90
new file mode 100644
index 00000000000..800a8acc34c
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/coarray/send_char_array_1.f90
@@ -0,0 +1,54 @@
+!{ dg-do run }
+
+program send_convert_char_array
+
+ implicit none
+
+ character(kind=1, len=:), allocatable, codimension[:] :: co_str_k1_scal
+ character(kind=1, len=:), allocatable :: str_k1_scal
+ character(kind=4, len=:), allocatable, codimension[:] :: co_str_k4_scal
+ character(kind=4, len=:), allocatable :: str_k4_scal
+
+ character(kind=1, len=:), allocatable, codimension[:] :: co_str_k1_arr(:)
+ character(kind=1, len=:), allocatable :: str_k1_arr(:)
+ character(kind=4, len=:), allocatable, codimension[:] :: co_str_k4_arr(:)
+ character(kind=4, len=:), allocatable :: str_k4_arr(:)
+
+ allocate(str_k1_scal, SOURCE='abcdefghij')
+ allocate(str_k4_scal, SOURCE=4_'abcdefghij')
+ allocate(character(len=20)::co_str_k1_scal[*]) ! allocate syncs here
+ allocate(character(kind=4, len=20)::co_str_k4_scal[*]) ! allocate syncs here
+
+ allocate(str_k1_arr, SOURCE=['abc', 'EFG', 'klm', 'NOP'])
+ allocate(str_k4_arr, SOURCE=[4_'abc', 4_'EFG', 4_'klm', 4_'NOP'])
+ allocate(character(len=5)::co_str_k1_arr(4)[*])
+ allocate(character(kind=4, len=5)::co_str_k4_arr(4)[*])
+
+ ! First check send/copy to self
+ co_str_k1_scal[1] = str_k1_scal
+ if (co_str_k1_scal /= str_k1_scal // ' ') call abort()
+
+ co_str_k4_scal[1] = str_k4_scal
+ if (co_str_k4_scal /= str_k4_scal // 4_' ') call abort()
+
+ co_str_k4_scal[1] = str_k1_scal
+ if (co_str_k4_scal /= str_k4_scal // 4_' ') call abort()
+
+ co_str_k1_scal[1] = str_k4_scal
+ if (co_str_k1_scal /= str_k1_scal // ' ') call abort()
+
+ co_str_k1_arr(:)[1] = str_k1_arr
+ if (any(co_str_k1_arr /= ['abc ', 'EFG ', 'klm ', 'NOP '])) call abort()
+
+ co_str_k4_arr(:)[1] = [4_'abc', 4_'EFG', 4_'klm', 4_'NOP']! str_k4_arr
+ if (any(co_str_k4_arr /= [4_'abc ', 4_'EFG ', 4_'klm ', 4_'NOP '])) call abort()
+
+ co_str_k4_arr(:)[1] = str_k1_arr
+ if (any(co_str_k4_arr /= [ 4_'abc ', 4_'EFG ', 4_'klm ', 4_'NOP '])) call abort()
+
+ co_str_k1_arr(:)[1] = str_k4_arr
+ if (any(co_str_k1_arr /= ['abc ', 'EFG ', 'klm ', 'NOP '])) call abort()
+
+end program send_convert_char_array
+
+! vim:ts=2:sts=2:sw=2: