@@ -304,23 +304,48 @@ contains
304304
305305 subroutine test_swap_str(error)
306306 type(error_type), allocatable, intent(out) :: error
307- character(5) :: x(2), y(2)
308-
309- x = ['abcde','fghij']
310- y = ['fghij','abcde']
307+ block
308+ character(5) :: x(2), y(2)
309+
310+ x = ['abcde','fghij']
311+ y = ['fghij','abcde']
311312
312- call swap(x,y)
313-
314- call check(error, all( x == ['fghij','abcde'] ) )
315- if (allocated(error)) return
316- call check(error, all( y == ['abcde','fghij'] ) )
317- if (allocated(error)) return
313+ call swap(x,y)
314+
315+ call check(error, all( x == ['fghij','abcde'] ) )
316+ if (allocated(error)) return
317+ call check(error, all( y == ['abcde','fghij'] ) )
318+ if (allocated(error)) return
318319
319- ! check self swap
320- call swap(x,x)
321-
322- call check(error, all( x == ['fghij','abcde'] ) )
323- if (allocated(error)) return
320+ ! check self swap
321+ call swap(x,x)
322+
323+ call check(error, all( x == ['fghij','abcde'] ) )
324+ if (allocated(error)) return
325+ end block
326+
327+ block
328+ character(4) :: x
329+ character(6) :: y
330+
331+ x = 'abcd'
332+ y = 'efghij'
333+ call swap(x,y)
334+
335+ call check(error, x == 'efgh' )
336+ if (allocated(error)) return
337+ call check(error, y(1:6) == 'abcd ' )
338+ if (allocated(error)) return
339+
340+ x = 'abcd'
341+ y = 'efghij'
342+ call swap(x,y(1:4))
343+
344+ call check(error, x == 'efgh' )
345+ if (allocated(error)) return
346+ call check(error, y == 'abcdij' )
347+ if (allocated(error)) return
348+ end block
324349 end subroutine test_swap_str
325350
326351 subroutine test_swap_stt(error)
0 commit comments