diff --git a/doc/specs/stdlib_string_type.md b/doc/specs/stdlib_string_type.md index 17cdce920..27cabe383 100644 --- a/doc/specs/stdlib_string_type.md +++ b/doc/specs/stdlib_string_type.md @@ -1993,7 +1993,7 @@ An unallocated `string_type` instance is equivalent to an empty string. #### Class -Pure Subroutine. +Pure subroutine (Elemental subroutine, only when both `from` and `to` are `type(string_type)`) #### Argument diff --git a/src/stdlib_string_type.fypp b/src/stdlib_string_type.fypp index a47ee6fc0..0bb5ff8a2 100644 --- a/src/stdlib_string_type.fypp +++ b/src/stdlib_string_type.fypp @@ -52,18 +52,18 @@ module stdlib_string_type !> Constructor for new string instances interface string_type - pure elemental module function new_string(string) result(new) + elemental module function new_string(string) result(new) character(len=*), intent(in), optional :: string type(string_type) :: new end function new_string #:for kind in INT_KINDS - pure elemental module function new_string_from_integer_${kind}$(val) result(new) + elemental module function new_string_from_integer_${kind}$(val) result(new) integer(${kind}$), intent(in) :: val type(string_type) :: new end function new_string_from_integer_${kind}$ #:endfor #:for kind in LOG_KINDS - pure elemental module function new_string_from_logical_${kind}$(val) result(new) + elemental module function new_string_from_logical_${kind}$(val) result(new) logical(${kind}$), intent(in) :: val type(string_type) :: new end function new_string_from_logical_${kind}$ @@ -678,7 +678,7 @@ contains !> Moves the allocated character scalar from 'from' to 'to' !> No output - subroutine move_string_string(from, to) + elemental subroutine move_string_string(from, to) type(string_type), intent(inout) :: from type(string_type), intent(out) :: to @@ -688,7 +688,7 @@ contains !> Moves the allocated character scalar from 'from' to 'to' !> No output - subroutine move_string_char(from, to) + pure subroutine move_string_char(from, to) type(string_type), intent(inout) :: from character(len=:), intent(out), allocatable :: to @@ -698,7 +698,7 @@ contains !> Moves the allocated character scalar from 'from' to 'to' !> No output - subroutine move_char_string(from, to) + pure subroutine move_char_string(from, to) character(len=:), intent(inout), allocatable :: from type(string_type), intent(out) :: to @@ -708,7 +708,7 @@ contains !> Moves the allocated character scalar from 'from' to 'to' !> No output - subroutine move_char_char(from, to) + pure subroutine move_char_char(from, to) character(len=:), intent(inout), allocatable :: from character(len=:), intent(out), allocatable :: to diff --git a/src/tests/string/test_string_intrinsic.f90 b/src/tests/string/test_string_intrinsic.f90 index 3d4e3f145..582541d63 100644 --- a/src/tests/string/test_string_intrinsic.f90 +++ b/src/tests/string/test_string_intrinsic.f90 @@ -667,9 +667,11 @@ subroutine test_move(error) !> Error handling type(error_type), allocatable, intent(out) :: error type(string_type) :: from_string, to_string + type(string_type) :: from_strings(2), to_strings(2) character(len=:), allocatable :: from_char, to_char from_string = "Move This String" + from_strings = "Move This String" from_char = "Move This Char" call check(error, from_string == "Move This String" .and. to_string == "" .and. & & from_char == "Move This Char" .and. .not. allocated(to_char), & @@ -713,7 +715,11 @@ subroutine test_move(error) ! string_type (allocated) --> string_type (allocated) call move(from_string, from_string) call check(error, from_string == "", "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") end subroutine test_move end module test_string_intrinsic