diff --git a/doc/specs/stdlib_string_type.md b/doc/specs/stdlib_string_type.md index 3a809171e..4c6d84194 100644 --- a/doc/specs/stdlib_string_type.md +++ b/doc/specs/stdlib_string_type.md @@ -1972,3 +1972,58 @@ program demo close(io) end program demo ``` + + + +### move + +#### Description + +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. + +#### Syntax + +`call [[stdlib_string_type(module):move(interface)]] (from, to)` + +#### Status + +Experimental + +#### Class + +Pure Subroutine. + +#### Argument + +- `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)`. + +#### Example + +```fortran +program demo_move + use stdlib_string_type, only : string_type, assignment(=), move + implicit none + type(string_type) :: from_string + character(len=:), allocatable :: from_char, to_char + + from_string = "move this string" + from_char = "move this char" + ! from_string <-- "move this string" + ! from_char <-- "move this char" + ! to_char <-- (unallocated) + + call move(from_string, to_char) + ! from_string <-- "" + ! to_char <-- "move this string" + + call move(from_char, to_char) + ! from_char <-- (unallocated) + ! to_string <-- "move this char" + +end program demo_move +``` diff --git a/src/stdlib_string_type.fypp b/src/stdlib_string_type.fypp index a802830b2..9e85c34a9 100644 --- a/src/stdlib_string_type.fypp +++ b/src/stdlib_string_type.fypp @@ -22,7 +22,7 @@ module stdlib_string_type public :: string_type public :: len, len_trim, trim, index, scan, verify, repeat, adjustr, adjustl public :: lgt, lge, llt, lle, char, ichar, iachar - public :: to_lower, to_upper, to_title, to_sentence, reverse + public :: to_lower, to_upper, to_title, to_sentence, reverse, move public :: assignment(=) public :: operator(>), operator(>=), operator(<), operator(<=) public :: operator(==), operator(/=), operator(//) @@ -206,6 +206,17 @@ module stdlib_string_type module procedure :: verify_char_string end interface verify + !> Version: experimental + !> + !> Moves the allocated character scalar from 'from' to 'to' + !> [Specifications](../page/specs/stdlib_string_type.html#move) + interface move + module procedure :: move_string_string + module procedure :: move_string_char + module procedure :: move_char_string + module procedure :: move_char_char + end interface move + !> Lexically compare the order of two character sequences being greater, !> The left-hand side, the right-hand side or both character sequences can !> be represented by a string. @@ -721,6 +732,45 @@ contains end function verify_char_string + !> Moves the allocated character scalar from 'from' to 'to' + !> No output + subroutine move_string_string(from, to) + type(string_type), intent(inout) :: from + type(string_type), intent(out) :: to + + call move_alloc(from%raw, to%raw) + + end subroutine move_string_string + + !> Moves the allocated character scalar from 'from' to 'to' + !> No output + subroutine move_string_char(from, to) + type(string_type), intent(inout) :: from + character(len=:), intent(out), allocatable :: to + + call move_alloc(from%raw, to) + + end subroutine move_string_char + + !> Moves the allocated character scalar from 'from' to 'to' + !> No output + subroutine move_char_string(from, to) + character(len=:), intent(inout), allocatable :: from + type(string_type), intent(out) :: to + + call move_alloc(from, to%raw) + + end subroutine move_char_string + + !> Moves the allocated character scalar from 'from' to 'to' + !> No output + subroutine move_char_char(from, to) + character(len=:), intent(inout), allocatable :: from + character(len=:), intent(out), allocatable :: to + + call move_alloc(from, to) + + end subroutine move_char_char !> Compare two character sequences for being greater. !> In this version both character sequences are by a string. diff --git a/src/tests/string/test_string_intrinsic.f90 b/src/tests/string/test_string_intrinsic.f90 index e546a73ff..47427eab2 100644 --- a/src/tests/string/test_string_intrinsic.f90 +++ b/src/tests/string/test_string_intrinsic.f90 @@ -463,6 +463,50 @@ subroutine test_iachar call check(code == iachar("F")) end subroutine test_iachar + subroutine test_move + type(string_type) :: from_string, to_string + character(len=:), allocatable :: from_char, to_char + + from_string = "Move This String" + from_char = "Move This Char" + call check(from_string == "Move This String" .and. to_string == "" .and. & + & from_char == "Move This Char" .and. .not. allocated(to_char), & + & "move: test_case 1") + + ! string_type (allocated) --> string_type (not allocated) + call move(from_string, to_string) + call check(from_string == "" .and. to_string == "Move This String", "move: test_case 2") + + ! character (allocated) --> string_type (not allocated) + call move(from_char, from_string) + call check(.not. allocated(from_char) .and. from_string == "Move This Char", & + & "move: test_case 3") + + ! string_type (allocated) --> character (not allocated) + call move(to_string, to_char) + call check(to_string == "" .and. to_char == "Move This String", "move: test_case 4") + + ! character (allocated) --> string_type (allocated) + call move(to_char, from_string) + call check(.not. allocated(to_char) .and. from_string == "Move This String", & + & "move: test_case 5") + + from_char = "new char" + ! character (allocated) --> string_type (allocated) + call move(from_char, from_string) + call check(.not. allocated(from_char) .and. from_string == "new char", "move: test_case 6") + + ! character (unallocated) --> string_type (allocated) + call move(from_char, from_string) + call check(from_string == "", "move: test_case 7") + + from_string = "moving to self" + ! string_type (allocated) --> string_type (allocated) + call move(from_string, from_string) + call check(from_string == "", "move: test_case 8") + + end subroutine test_move + end module test_string_intrinsic program tester @@ -485,5 +529,6 @@ program tester call test_char call test_ichar call test_iachar + call test_move end program tester