Skip to content

Commit 05941b0

Browse files
committed
add additional tests for string_type move
1 parent 8660485 commit 05941b0

File tree

1 file changed

+14
-1
lines changed

1 file changed

+14
-1
lines changed

test/string/test_string_intrinsic.f90

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -667,6 +667,7 @@ subroutine test_move(error)
667667
!> Error handling
668668
type(error_type), allocatable, intent(out) :: error
669669
type(string_type) :: from_string, to_string
670+
type(string_type) :: from_string_not
670671
type(string_type) :: from_strings(2), to_strings(2)
671672
character(len=:), allocatable :: from_char, to_char
672673

@@ -706,7 +707,7 @@ subroutine test_move(error)
706707
call check(error, .not. allocated(from_char) .and. from_string == "new char", "move: test_case 6")
707708
if (allocated(error)) return
708709

709-
! character (unallocated) --> string_type (allocated)
710+
! character (not allocated) --> string_type (allocated)
710711
call move(from_char, from_string)
711712
call check(error, from_string == "", "move: test_case 7")
712713
if (allocated(error)) return
@@ -720,6 +721,18 @@ subroutine test_move(error)
720721
! elemental: string_type (allocated) --> string_type (not allocated)
721722
call move(from_strings, to_strings)
722723
call check(error, all(from_strings(:) == "") .and. all(to_strings(:) == "Move This String"), "move: test_case 9")
724+
725+
! string_type (not allocated) --> string_type (not allocated)
726+
call move(from_string_not, to_string)
727+
call check(error, from_string_not == "" .and. to_string == "", "move: test_case 10")
728+
if (allocated(error)) return
729+
730+
! string_type (not allocated) --> string_type (not allocated)
731+
to_string = "to be deallocated"
732+
call move(from_string_not, to_string)
733+
call check(error, from_string_not == "" .and. to_string == "", "move: test_case 11")
734+
if (allocated(error)) return
735+
723736
end subroutine test_move
724737

725738
end module test_string_intrinsic

0 commit comments

Comments
 (0)