diff --git a/doc/specs/stdlib_string_type.md b/doc/specs/stdlib_string_type.md index a0444b442..b1d34684e 100644 --- a/doc/specs/stdlib_string_type.md +++ b/doc/specs/stdlib_string_type.md @@ -1523,6 +1523,7 @@ Experimental Moves the allocation from `from` to `to`, consequently deallocating `from` in this process. If `from` is not allocated before execution, `to` gets deallocated by the process. An unallocated `string_type` instance is equivalent to an empty string. +If `from` and `to` are the same variable, then `from` remains unchanged. #### Syntax @@ -1537,7 +1538,8 @@ Pure subroutine (Elemental subroutine, only when both `from` and `to` are `type( - `from`: Character scalar or [[stdlib_string_type(module):string_type(type)]]. This argument is `intent(inout)`. - `to`: Character scalar or [[stdlib_string_type(module):string_type(type)]]. - This argument is `intent(out)`. + This argument is `intent(inout)` when both `from` and `to` are `type(string_type)`, + otherwise `intent(out)`. #### Example diff --git a/src/stdlib_string_type.fypp b/src/stdlib_string_type.fypp index 0bb5ff8a2..6ca4e1363 100644 --- a/src/stdlib_string_type.fypp +++ b/src/stdlib_string_type.fypp @@ -680,9 +680,11 @@ contains !> No output elemental subroutine move_string_string(from, to) type(string_type), intent(inout) :: from - type(string_type), intent(out) :: to + type(string_type), intent(inout) :: to + character(:), allocatable :: tmp - call move_alloc(from%raw, to%raw) + call move_alloc(from%raw, tmp) + call move_alloc(tmp, to%raw) end subroutine move_string_string diff --git a/test/string/test_string_intrinsic.f90 b/test/string/test_string_intrinsic.f90 index 582541d63..c84fbbd48 100644 --- a/test/string/test_string_intrinsic.f90 +++ b/test/string/test_string_intrinsic.f90 @@ -667,6 +667,7 @@ subroutine test_move(error) !> Error handling type(error_type), allocatable, intent(out) :: error type(string_type) :: from_string, to_string + type(string_type) :: from_string_not type(string_type) :: from_strings(2), to_strings(2) character(len=:), allocatable :: from_char, to_char @@ -706,7 +707,7 @@ subroutine test_move(error) call check(error, .not. allocated(from_char) .and. from_string == "new char", "move: test_case 6") if (allocated(error)) return - ! character (unallocated) --> string_type (allocated) + ! character (not allocated) --> string_type (allocated) call move(from_char, from_string) call check(error, from_string == "", "move: test_case 7") if (allocated(error)) return @@ -714,12 +715,24 @@ subroutine test_move(error) from_string = "moving to self" ! string_type (allocated) --> string_type (allocated) call move(from_string, from_string) - call check(error, from_string == "", "move: test_case 8") + call check(error, from_string == "moving to self", "move: test_case 8") if (allocated(error)) return ! elemental: string_type (allocated) --> string_type (not allocated) call move(from_strings, to_strings) call check(error, all(from_strings(:) == "") .and. all(to_strings(:) == "Move This String"), "move: test_case 9") + + ! string_type (not allocated) --> string_type (not allocated) + call move(from_string_not, to_string) + call check(error, from_string_not == "" .and. to_string == "", "move: test_case 10") + if (allocated(error)) return + + ! string_type (not allocated) --> string_type (not allocated) + to_string = "to be deallocated" + call move(from_string_not, to_string) + call check(error, from_string_not == "" .and. to_string == "", "move: test_case 11") + if (allocated(error)) return + end subroutine test_move end module test_string_intrinsic