Skip to content

Commit 5eedf6b

Browse files
committed
made move subroutine of stdlib_string_type module pure
1 parent 0452b5f commit 5eedf6b

File tree

2 files changed

+10
-11
lines changed

2 files changed

+10
-11
lines changed

Diff for: src/stdlib_string_type.fypp

+4-4
Original file line numberDiff line numberDiff line change
@@ -713,7 +713,7 @@ contains
713713

714714
!> Moves the allocated character scalar from 'from' to 'to'
715715
!> No output
716-
subroutine move_string_string(from, to)
716+
pure subroutine move_string_string(from, to)
717717
type(string_type), intent(inout) :: from
718718
type(string_type), intent(out) :: to
719719

@@ -723,7 +723,7 @@ contains
723723

724724
!> Moves the allocated character scalar from 'from' to 'to'
725725
!> No output
726-
subroutine move_string_char(from, to)
726+
pure subroutine move_string_char(from, to)
727727
type(string_type), intent(inout) :: from
728728
character(len=:), intent(out), allocatable :: to
729729

@@ -733,7 +733,7 @@ contains
733733

734734
!> Moves the allocated character scalar from 'from' to 'to'
735735
!> No output
736-
subroutine move_char_string(from, to)
736+
pure subroutine move_char_string(from, to)
737737
character(len=:), intent(inout), allocatable :: from
738738
type(string_type), intent(out) :: to
739739

@@ -743,7 +743,7 @@ contains
743743

744744
!> Moves the allocated character scalar from 'from' to 'to'
745745
!> No output
746-
subroutine move_char_char(from, to)
746+
pure subroutine move_char_char(from, to)
747747
character(len=:), intent(inout), allocatable :: from
748748
character(len=:), intent(out), allocatable :: to
749749

Diff for: src/stdlib_stringlist_type.f90

+6-7
Original file line numberDiff line numberDiff line change
@@ -464,7 +464,7 @@ pure function shift( idx, shift_by )
464464
type(stringlist_index_type), intent(in) :: idx
465465
integer, intent(in) :: shift_by
466466

467-
type(stringlist_index_type), intent(in) :: shift
467+
type(stringlist_index_type) :: shift
468468

469469
shift = merge( fidx( idx%offset + shift_by ), bidx( idx%offset + shift_by ), idx%forward )
470470

@@ -607,7 +607,7 @@ end subroutine insert_at_stringarray_idx_wrap
607607
!> Modifies the input stringlist 'list'
608608
subroutine insert_before_engine( list, idxn, positions )
609609
!> Not a part of public API
610-
class(stringlist_type), intent(inout) :: list
610+
type(stringlist_type), intent(inout) :: list
611611
integer, intent(inout) :: idxn
612612
integer, intent(in) :: positions
613613

@@ -740,8 +740,8 @@ end subroutine insert_before_stringarray_int_impl
740740
!> Returns strings present at stringlist_indexes in interval ['first', 'last']
741741
!> Stores requested strings in array 'capture_strings'
742742
!> No return
743-
subroutine get_engine( list, first, last, capture_strings )
744-
class(stringlist_type) :: list
743+
pure subroutine get_engine( list, first, last, capture_strings )
744+
type(stringlist_type), intent(in) :: list
745745
type(stringlist_index_type), intent(in) :: first, last
746746
type(string_type), allocatable, intent(out) :: capture_strings(:)
747747

@@ -753,8 +753,7 @@ subroutine get_engine( list, first, last, capture_strings )
753753

754754
! out of bounds indexes won't be captured in capture_strings
755755
if ( from <= to ) then
756-
pos = to - from + 1
757-
allocate( capture_strings(pos) )
756+
allocate( capture_strings( to - from + 1 ) )
758757

759758
inew = 1
760759
do i = from, to
@@ -775,8 +774,8 @@ end subroutine get_engine
775774
pure function get_idx_impl( list, idx )
776775
class(stringlist_type), intent(in) :: list
777776
type(stringlist_index_type), intent(in) :: idx
778-
type(string_type) :: get_idx_impl
779777

778+
type(string_type) :: get_idx_impl
780779
type(string_type), allocatable :: capture_strings(:)
781780

782781
call get_engine( list, idx, idx, capture_strings )

0 commit comments

Comments
 (0)