Skip to content

Commit e4e10b9

Browse files
committed
Deploying to stdlib-fpm from @ 6033397 🚀
1 parent cc641dd commit e4e10b9

File tree

2 files changed

+18
-12
lines changed

2 files changed

+18
-12
lines changed

src/stdlib_string_type.f90

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -51,31 +51,31 @@ module stdlib_string_type
5151

5252
!> Constructor for new string instances
5353
interface string_type
54-
pure elemental module function new_string(string) result(new)
54+
elemental module function new_string(string) result(new)
5555
character(len=*), intent(in), optional :: string
5656
type(string_type) :: new
5757
end function new_string
58-
pure elemental module function new_string_from_integer_int8(val) result(new)
58+
elemental module function new_string_from_integer_int8(val) result(new)
5959
integer(int8), intent(in) :: val
6060
type(string_type) :: new
6161
end function new_string_from_integer_int8
62-
pure elemental module function new_string_from_integer_int16(val) result(new)
62+
elemental module function new_string_from_integer_int16(val) result(new)
6363
integer(int16), intent(in) :: val
6464
type(string_type) :: new
6565
end function new_string_from_integer_int16
66-
pure elemental module function new_string_from_integer_int32(val) result(new)
66+
elemental module function new_string_from_integer_int32(val) result(new)
6767
integer(int32), intent(in) :: val
6868
type(string_type) :: new
6969
end function new_string_from_integer_int32
70-
pure elemental module function new_string_from_integer_int64(val) result(new)
70+
elemental module function new_string_from_integer_int64(val) result(new)
7171
integer(int64), intent(in) :: val
7272
type(string_type) :: new
7373
end function new_string_from_integer_int64
74-
pure elemental module function new_string_from_logical_lk(val) result(new)
74+
elemental module function new_string_from_logical_lk(val) result(new)
7575
logical(lk), intent(in) :: val
7676
type(string_type) :: new
7777
end function new_string_from_logical_lk
78-
pure elemental module function new_string_from_logical_c_bool(val) result(new)
78+
elemental module function new_string_from_logical_c_bool(val) result(new)
7979
logical(c_bool), intent(in) :: val
8080
type(string_type) :: new
8181
end function new_string_from_logical_c_bool
@@ -689,7 +689,7 @@ end function verify_char_string
689689

690690
!> Moves the allocated character scalar from 'from' to 'to'
691691
!> No output
692-
subroutine move_string_string(from, to)
692+
elemental subroutine move_string_string(from, to)
693693
type(string_type), intent(inout) :: from
694694
type(string_type), intent(out) :: to
695695

@@ -699,7 +699,7 @@ end subroutine move_string_string
699699

700700
!> Moves the allocated character scalar from 'from' to 'to'
701701
!> No output
702-
subroutine move_string_char(from, to)
702+
pure subroutine move_string_char(from, to)
703703
type(string_type), intent(inout) :: from
704704
character(len=:), intent(out), allocatable :: to
705705

@@ -709,7 +709,7 @@ end subroutine move_string_char
709709

710710
!> Moves the allocated character scalar from 'from' to 'to'
711711
!> No output
712-
subroutine move_char_string(from, to)
712+
pure subroutine move_char_string(from, to)
713713
character(len=:), intent(inout), allocatable :: from
714714
type(string_type), intent(out) :: to
715715

@@ -719,7 +719,7 @@ end subroutine move_char_string
719719

720720
!> Moves the allocated character scalar from 'from' to 'to'
721721
!> No output
722-
subroutine move_char_char(from, to)
722+
pure subroutine move_char_char(from, to)
723723
character(len=:), intent(inout), allocatable :: from
724724
character(len=:), intent(out), allocatable :: to
725725

test/test_string_intrinsic.f90

Lines changed: 7 additions & 1 deletion
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)