Skip to content

Commit ccd6dff

Browse files
committed
made move subroutine of stdlib_string_type module pure
1 parent 88a1abb commit ccd6dff

File tree

2 files changed

+10
-11
lines changed

2 files changed

+10
-11
lines changed

src/stdlib_string_type.fypp

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -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+
pure 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/stdlib_stringlist_type.f90

Lines changed: 6 additions & 7 deletions
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

@@ -744,8 +744,8 @@ end subroutine insert_before_stringarray_int_impl
744744
!> Returns strings present at stringlist_indexes in interval ['first', 'last']
745745
!> Stores requested strings in array 'capture_strings'
746746
!> No return
747-
subroutine get_engine( list, first, last, capture_strings )
748-
class(stringlist_type) :: list
747+
pure subroutine get_engine( list, first, last, capture_strings )
748+
type(stringlist_type), intent(in) :: list
749749
type(stringlist_index_type), intent(in) :: first, last
750750
type(string_type), allocatable, intent(out) :: capture_strings(:)
751751

@@ -757,8 +757,7 @@ subroutine get_engine( list, first, last, capture_strings )
757757

758758
! out of bounds indexes won't be captured in capture_strings
759759
if ( from <= to ) then
760-
pos = to - from + 1
761-
allocate( capture_strings(pos) )
760+
allocate( capture_strings( to - from + 1 ) )
762761

763762
inew = 1
764763
do i = from, to
@@ -779,8 +778,8 @@ end subroutine get_engine
779778
pure function get_idx_impl( list, idx )
780779
class(stringlist_type), intent(in) :: list
781780
type(stringlist_index_type), intent(in) :: idx
782-
type(string_type) :: get_idx_impl
783781

782+
type(string_type) :: get_idx_impl
784783
type(string_type), allocatable :: capture_strings(:)
785784

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

0 commit comments

Comments
 (0)