Skip to content

Commit 9df95dc

Browse files
committed
Keep pure: char_string, char_string_range, maybe.
Add test for `elemental` `move`.
1 parent df9edbd commit 9df95dc

File tree

3 files changed

+12
-6
lines changed

3 files changed

+12
-6
lines changed

doc/specs/stdlib_string_type.md

+2-2
Original file line numberDiff line numberDiff line change
@@ -528,7 +528,7 @@ Return the character sequence represented by the string.
528528

529529
#### Class
530530

531-
Elemental function.
531+
Pure function.
532532

533533
#### Argument
534534

@@ -618,7 +618,7 @@ Return a substring from the character sequence of the string.
618618

619619
#### Class
620620

621-
Elemental function.
621+
Pure function.
622622

623623
#### Argument
624624

src/stdlib_string_type.fypp

+3-3
Original file line numberDiff line numberDiff line change
@@ -438,7 +438,7 @@ contains
438438

439439

440440
!> Return the character sequence represented by the string.
441-
elemental function char_string(string) result(character_string)
441+
pure function char_string(string) result(character_string)
442442
type(string_type), intent(in) :: string
443443
character(len=len(string)) :: character_string
444444

@@ -457,7 +457,7 @@ contains
457457
end function char_string_pos
458458

459459
!> Return the character sequence represented by the string.
460-
elemental function char_string_range(string, start, last) result(character_string)
460+
pure function char_string_range(string, start, last) result(character_string)
461461
type(string_type), intent(in) :: string
462462
integer, intent(in) :: start
463463
integer, intent(in) :: last
@@ -1233,7 +1233,7 @@ contains
12331233

12341234

12351235
!> Safely return the character sequences represented by the string
1236-
elemental function maybe(string) result(maybe_string)
1236+
pure function maybe(string) result(maybe_string)
12371237
type(string_type), intent(in) :: string
12381238
character(len=len(string)) :: maybe_string
12391239
if (allocated(string%raw)) then

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)