Skip to content

Commit 82f35a5

Browse files
authored
Merge pull request #736 from jvdp1/fix_string_intrinsic
Fix the procedure `move` for string_type
2 parents df0b3f9 + b82b39a commit 82f35a5

File tree

3 files changed

+22
-5
lines changed

3 files changed

+22
-5
lines changed

doc/specs/stdlib_string_type.md

+3-1
Original file line numberDiff line numberDiff line change
@@ -1523,6 +1523,7 @@ Experimental
15231523
Moves the allocation from `from` to `to`, consequently deallocating `from` in this process.
15241524
If `from` is not allocated before execution, `to` gets deallocated by the process.
15251525
An unallocated `string_type` instance is equivalent to an empty string.
1526+
If `from` and `to` are the same variable, then `from` remains unchanged.
15261527

15271528
#### Syntax
15281529

@@ -1537,7 +1538,8 @@ Pure subroutine (Elemental subroutine, only when both `from` and `to` are `type(
15371538
- `from`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
15381539
This argument is `intent(inout)`.
15391540
- `to`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
1540-
This argument is `intent(out)`.
1541+
This argument is `intent(inout)` when both `from` and `to` are `type(string_type)`,
1542+
otherwise `intent(out)`.
15411543

15421544
#### Example
15431545

src/stdlib_string_type.fypp

+4-2
Original file line numberDiff line numberDiff line change
@@ -680,9 +680,11 @@ contains
680680
!> No output
681681
elemental subroutine move_string_string(from, to)
682682
type(string_type), intent(inout) :: from
683-
type(string_type), intent(out) :: to
683+
type(string_type), intent(inout) :: to
684+
character(:), allocatable :: tmp
684685

685-
call move_alloc(from%raw, to%raw)
686+
call move_alloc(from%raw, tmp)
687+
call move_alloc(tmp, to%raw)
686688

687689
end subroutine move_string_string
688690

test/string/test_string_intrinsic.f90

+15-2
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,20 +707,32 @@ 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
713714

714715
from_string = "moving to self"
715716
! string_type (allocated) --> string_type (allocated)
716717
call move(from_string, from_string)
717-
call check(error, from_string == "", "move: test_case 8")
718+
call check(error, from_string == "moving to self", "move: test_case 8")
718719
if (allocated(error)) return
719720

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)