Skip to content

Commit 6033397

Browse files
authored
Merge pull request #562 from zoziha/to-elemental
Minor update `pure/elemental` in `string_type` module
2 parents f58da3b + 9df95dc commit 6033397

File tree

3 files changed

+15
-9
lines changed

3 files changed

+15
-9
lines changed

doc/specs/stdlib_string_type.md

+1-1
Original file line numberDiff line numberDiff line change
@@ -1993,7 +1993,7 @@ An unallocated `string_type` instance is equivalent to an empty string.
19931993

19941994
#### Class
19951995

1996-
Pure Subroutine.
1996+
Pure subroutine (Elemental subroutine, only when both `from` and `to` are `type(string_type)`)
19971997

19981998
#### Argument
19991999

src/stdlib_string_type.fypp

+7-7
Original file line numberDiff line numberDiff line change
@@ -52,18 +52,18 @@ module stdlib_string_type
5252

5353
!> Constructor for new string instances
5454
interface string_type
55-
pure elemental module function new_string(string) result(new)
55+
elemental module function new_string(string) result(new)
5656
character(len=*), intent(in), optional :: string
5757
type(string_type) :: new
5858
end function new_string
5959
#:for kind in INT_KINDS
60-
pure elemental module function new_string_from_integer_${kind}$(val) result(new)
60+
elemental module function new_string_from_integer_${kind}$(val) result(new)
6161
integer(${kind}$), intent(in) :: val
6262
type(string_type) :: new
6363
end function new_string_from_integer_${kind}$
6464
#:endfor
6565
#:for kind in LOG_KINDS
66-
pure elemental module function new_string_from_logical_${kind}$(val) result(new)
66+
elemental module function new_string_from_logical_${kind}$(val) result(new)
6767
logical(${kind}$), intent(in) :: val
6868
type(string_type) :: new
6969
end function new_string_from_logical_${kind}$
@@ -678,7 +678,7 @@ contains
678678

679679
!> Moves the allocated character scalar from 'from' to 'to'
680680
!> No output
681-
subroutine move_string_string(from, to)
681+
elemental subroutine move_string_string(from, to)
682682
type(string_type), intent(inout) :: from
683683
type(string_type), intent(out) :: to
684684

@@ -688,7 +688,7 @@ contains
688688

689689
!> Moves the allocated character scalar from 'from' to 'to'
690690
!> No output
691-
subroutine move_string_char(from, to)
691+
pure subroutine move_string_char(from, to)
692692
type(string_type), intent(inout) :: from
693693
character(len=:), intent(out), allocatable :: to
694694

@@ -698,7 +698,7 @@ contains
698698

699699
!> Moves the allocated character scalar from 'from' to 'to'
700700
!> No output
701-
subroutine move_char_string(from, to)
701+
pure subroutine move_char_string(from, to)
702702
character(len=:), intent(inout), allocatable :: from
703703
type(string_type), intent(out) :: to
704704

@@ -708,7 +708,7 @@ contains
708708

709709
!> Moves the allocated character scalar from 'from' to 'to'
710710
!> No output
711-
subroutine move_char_char(from, to)
711+
pure subroutine move_char_char(from, to)
712712
character(len=:), intent(inout), allocatable :: from
713713
character(len=:), intent(out), allocatable :: to
714714

src/tests/string/test_string_intrinsic.f90

+7-1
Original file line numberDiff line numberDiff line change
@@ -667,9 +667,11 @@ 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_strings(2), to_strings(2)
670671
character(len=:), allocatable :: from_char, to_char
671672

672673
from_string = "Move This String"
674+
from_strings = "Move This String"
673675
from_char = "Move This Char"
674676
call check(error, from_string == "Move This String" .and. to_string == "" .and. &
675677
& from_char == "Move This Char" .and. .not. allocated(to_char), &
@@ -713,7 +715,11 @@ subroutine test_move(error)
713715
! string_type (allocated) --> string_type (allocated)
714716
call move(from_string, from_string)
715717
call check(error, from_string == "", "move: test_case 8")
716-
718+
if (allocated(error)) return
719+
720+
! elemental: string_type (allocated) --> string_type (not allocated)
721+
call move(from_strings, to_strings)
722+
call check(error, all(from_strings(:) == "") .and. all(to_strings(:) == "Move This String"), "move: test_case 9")
717723
end subroutine test_move
718724

719725
end module test_string_intrinsic

0 commit comments

Comments
 (0)