Skip to content

Commit eae0027

Browse files
authored
Merge pull request #467 from Aman-Godara/move
implemented move_alloc for string_type
2 parents 245926f + 8b19b35 commit eae0027

File tree

3 files changed

+151
-1
lines changed

3 files changed

+151
-1
lines changed

doc/specs/stdlib_string_type.md

Lines changed: 55 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1972,3 +1972,58 @@ program demo
19721972
close(io)
19731973
end program demo
19741974
```
1975+
1976+
1977+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
1978+
### move
1979+
1980+
#### Description
1981+
1982+
Moves the allocation from `from` to `to`, consequently deallocating `from` in this process.
1983+
If `from` is not allocated before execution, `to` gets deallocated by the process.
1984+
An unallocated `string_type` instance is equivalent to an empty string.
1985+
1986+
#### Syntax
1987+
1988+
`call [[stdlib_string_type(module):move(interface)]] (from, to)`
1989+
1990+
#### Status
1991+
1992+
Experimental
1993+
1994+
#### Class
1995+
1996+
Pure Subroutine.
1997+
1998+
#### Argument
1999+
2000+
- `from`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
2001+
This argument is `intent(inout)`.
2002+
- `to`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
2003+
This argument is `intent(out)`.
2004+
2005+
#### Example
2006+
2007+
```fortran
2008+
program demo_move
2009+
use stdlib_string_type, only : string_type, assignment(=), move
2010+
implicit none
2011+
type(string_type) :: from_string
2012+
character(len=:), allocatable :: from_char, to_char
2013+
2014+
from_string = "move this string"
2015+
from_char = "move this char"
2016+
! from_string <-- "move this string"
2017+
! from_char <-- "move this char"
2018+
! to_char <-- (unallocated)
2019+
2020+
call move(from_string, to_char)
2021+
! from_string <-- ""
2022+
! to_char <-- "move this string"
2023+
2024+
call move(from_char, to_char)
2025+
! from_char <-- (unallocated)
2026+
! to_string <-- "move this char"
2027+
2028+
end program demo_move
2029+
```

src/stdlib_string_type.fypp

Lines changed: 51 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ module stdlib_string_type
2222
public :: string_type
2323
public :: len, len_trim, trim, index, scan, verify, repeat, adjustr, adjustl
2424
public :: lgt, lge, llt, lle, char, ichar, iachar
25-
public :: to_lower, to_upper, to_title, to_sentence, reverse
25+
public :: to_lower, to_upper, to_title, to_sentence, reverse, move
2626
public :: assignment(=)
2727
public :: operator(>), operator(>=), operator(<), operator(<=)
2828
public :: operator(==), operator(/=), operator(//)
@@ -214,6 +214,17 @@ module stdlib_string_type
214214
module procedure :: verify_char_string
215215
end interface verify
216216

217+
!> Version: experimental
218+
!>
219+
!> Moves the allocated character scalar from 'from' to 'to'
220+
!> [Specifications](../page/specs/stdlib_string_type.html#move)
221+
interface move
222+
module procedure :: move_string_string
223+
module procedure :: move_string_char
224+
module procedure :: move_char_string
225+
module procedure :: move_char_char
226+
end interface move
227+
217228
!> Lexically compare the order of two character sequences being greater,
218229
!> The left-hand side, the right-hand side or both character sequences can
219230
!> be represented by a string.
@@ -700,6 +711,45 @@ contains
700711

701712
end function verify_char_string
702713

714+
!> Moves the allocated character scalar from 'from' to 'to'
715+
!> No output
716+
subroutine move_string_string(from, to)
717+
type(string_type), intent(inout) :: from
718+
type(string_type), intent(out) :: to
719+
720+
call move_alloc(from%raw, to%raw)
721+
722+
end subroutine move_string_string
723+
724+
!> Moves the allocated character scalar from 'from' to 'to'
725+
!> No output
726+
subroutine move_string_char(from, to)
727+
type(string_type), intent(inout) :: from
728+
character(len=:), intent(out), allocatable :: to
729+
730+
call move_alloc(from%raw, to)
731+
732+
end subroutine move_string_char
733+
734+
!> Moves the allocated character scalar from 'from' to 'to'
735+
!> No output
736+
subroutine move_char_string(from, to)
737+
character(len=:), intent(inout), allocatable :: from
738+
type(string_type), intent(out) :: to
739+
740+
call move_alloc(from, to%raw)
741+
742+
end subroutine move_char_string
743+
744+
!> Moves the allocated character scalar from 'from' to 'to'
745+
!> No output
746+
subroutine move_char_char(from, to)
747+
character(len=:), intent(inout), allocatable :: from
748+
character(len=:), intent(out), allocatable :: to
749+
750+
call move_alloc(from, to)
751+
752+
end subroutine move_char_char
703753

704754
!> Compare two character sequences for being greater.
705755
!> In this version both character sequences are by a string.

src/tests/string/test_string_intrinsic.f90

Lines changed: 45 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -463,6 +463,50 @@ subroutine test_iachar
463463
call check(code == iachar("F"))
464464
end subroutine test_iachar
465465

466+
subroutine test_move
467+
type(string_type) :: from_string, to_string
468+
character(len=:), allocatable :: from_char, to_char
469+
470+
from_string = "Move This String"
471+
from_char = "Move This Char"
472+
call check(from_string == "Move This String" .and. to_string == "" .and. &
473+
& from_char == "Move This Char" .and. .not. allocated(to_char), &
474+
& "move: test_case 1")
475+
476+
! string_type (allocated) --> string_type (not allocated)
477+
call move(from_string, to_string)
478+
call check(from_string == "" .and. to_string == "Move This String", "move: test_case 2")
479+
480+
! character (allocated) --> string_type (not allocated)
481+
call move(from_char, from_string)
482+
call check(.not. allocated(from_char) .and. from_string == "Move This Char", &
483+
& "move: test_case 3")
484+
485+
! string_type (allocated) --> character (not allocated)
486+
call move(to_string, to_char)
487+
call check(to_string == "" .and. to_char == "Move This String", "move: test_case 4")
488+
489+
! character (allocated) --> string_type (allocated)
490+
call move(to_char, from_string)
491+
call check(.not. allocated(to_char) .and. from_string == "Move This String", &
492+
& "move: test_case 5")
493+
494+
from_char = "new char"
495+
! character (allocated) --> string_type (allocated)
496+
call move(from_char, from_string)
497+
call check(.not. allocated(from_char) .and. from_string == "new char", "move: test_case 6")
498+
499+
! character (unallocated) --> string_type (allocated)
500+
call move(from_char, from_string)
501+
call check(from_string == "", "move: test_case 7")
502+
503+
from_string = "moving to self"
504+
! string_type (allocated) --> string_type (allocated)
505+
call move(from_string, from_string)
506+
call check(from_string == "", "move: test_case 8")
507+
508+
end subroutine test_move
509+
466510
end module test_string_intrinsic
467511

468512
program tester
@@ -485,5 +529,6 @@ program tester
485529
call test_char
486530
call test_ichar
487531
call test_iachar
532+
call test_move
488533

489534
end program tester

0 commit comments

Comments
 (0)