Skip to content

Commit 2e216c8

Browse files
committed
some minor changes
1 parent ccd6dff commit 2e216c8

File tree

1 file changed

+26
-25
lines changed

1 file changed

+26
-25
lines changed

src/stdlib_stringlist_type.f90

Lines changed: 26 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -171,14 +171,16 @@ end function new_stringlist
171171
pure function new_stringlist_carray( array )
172172
character(len=*), dimension(:), intent(in) :: array
173173
type(stringlist_type) :: new_stringlist_carray
174-
type(string_type), dimension( size(array) ) :: sarray
174+
175+
type(string_type), allocatable :: sarray(:)
175176
integer :: i
176177

178+
allocate( sarray( size(array) ) )
177179
do i = 1, size(array)
178180
sarray(i) = string_type( array(i) )
179181
end do
180182

181-
new_stringlist_carray = stringlist_type( sarray )
183+
call move_alloc( sarray, new_stringlist_carray%stringarray )
182184

183185
end function new_stringlist_carray
184186

@@ -188,7 +190,6 @@ pure function new_stringlist_sarray( array )
188190
type(string_type), dimension(:), intent(in) :: array
189191
type(stringlist_type) :: new_stringlist_sarray
190192

191-
new_stringlist_sarray = stringlist_type()
192193
new_stringlist_sarray%stringarray = array
193194

194195
end function new_stringlist_sarray
@@ -476,7 +477,7 @@ end function shift
476477
!>
477478
!> Resets stringlist 'list' to an empy stringlist of len 0
478479
!> Modifies the input stringlist 'list'
479-
subroutine clear_list( list )
480+
pure subroutine clear_list( list )
480481
class(stringlist_type), intent(inout) :: list
481482

482483
if ( allocated( list%stringarray ) ) then
@@ -540,7 +541,7 @@ end function convert_to_current_idxn
540541
!>
541542
!> Inserts character scalar 'string' AT stringlist_index 'idx' in stringlist 'list'
542543
!> Modifies the input stringlist 'list'
543-
subroutine insert_at_char_idx_wrap( list, idx, string )
544+
pure subroutine insert_at_char_idx_wrap( list, idx, string )
544545
class(stringlist_type), intent(inout) :: list
545546
type(stringlist_index_type), intent(in) :: idx
546547
character(len=*), intent(in) :: string
@@ -553,7 +554,7 @@ end subroutine insert_at_char_idx_wrap
553554
!>
554555
!> Inserts string 'string' AT stringlist_index 'idx' in stringlist 'list'
555556
!> Modifies the input stringlist 'list'
556-
subroutine insert_at_string_idx_wrap( list, idx, string )
557+
pure subroutine insert_at_string_idx_wrap( list, idx, string )
557558
class(stringlist_type), intent(inout) :: list
558559
type(stringlist_index_type), intent(in) :: idx
559560
type(string_type), intent(in) :: string
@@ -566,7 +567,7 @@ end subroutine insert_at_string_idx_wrap
566567
!>
567568
!> Inserts stringlist 'slist' AT stringlist_index 'idx' in stringlist 'list'
568569
!> Modifies the input stringlist 'list'
569-
subroutine insert_at_stringlist_idx_wrap( list, idx, slist )
570+
pure subroutine insert_at_stringlist_idx_wrap( list, idx, slist )
570571
class(stringlist_type), intent(inout) :: list
571572
type(stringlist_index_type), intent(in) :: idx
572573
type(stringlist_type), intent(in) :: slist
@@ -579,7 +580,7 @@ end subroutine insert_at_stringlist_idx_wrap
579580
!>
580581
!> Inserts chararray 'carray' AT stringlist_index 'idx' in stringlist 'list'
581582
!> Modifies the input stringlist 'list'
582-
subroutine insert_at_chararray_idx_wrap( list, idx, carray )
583+
pure subroutine insert_at_chararray_idx_wrap( list, idx, carray )
583584
class(stringlist_type), intent(inout) :: list
584585
type(stringlist_index_type), intent(in) :: idx
585586
character(len=*), dimension(:), intent(in) :: carray
@@ -592,7 +593,7 @@ end subroutine insert_at_chararray_idx_wrap
592593
!>
593594
!> Inserts stringarray 'sarray' AT stringlist_index 'idx' in stringlist 'list'
594595
!> Modifies the input stringlist 'list'
595-
subroutine insert_at_stringarray_idx_wrap( list, idx, sarray )
596+
pure subroutine insert_at_stringarray_idx_wrap( list, idx, sarray )
596597
class(stringlist_type), intent(inout) :: list
597598
type(stringlist_index_type), intent(in) :: idx
598599
type(string_type), dimension(:), intent(in) :: sarray
@@ -605,7 +606,7 @@ end subroutine insert_at_stringarray_idx_wrap
605606
!>
606607
!> Inserts 'positions' number of empty positions BEFORE integer index 'idxn'
607608
!> Modifies the input stringlist 'list'
608-
subroutine insert_before_engine( list, idxn, positions )
609+
pure subroutine insert_before_engine( list, idxn, positions )
609610
!> Not a part of public API
610611
type(stringlist_type), intent(inout) :: list
611612
integer, intent(inout) :: idxn
@@ -641,7 +642,7 @@ end subroutine insert_before_engine
641642
!>
642643
!> Inserts string 'string' BEFORE integer index 'idxn' in the underlying stringarray
643644
!> Modifies the input stringlist 'list'
644-
subroutine insert_before_string_int_impl( list, idxn, string )
645+
pure subroutine insert_before_string_int_impl( list, idxn, string )
645646
!> Not a part of public API
646647
class(stringlist_type), intent(inout) :: list
647648
integer, intent(in) :: idxn
@@ -660,7 +661,7 @@ end subroutine insert_before_string_int_impl
660661
!>
661662
!> Inserts stringlist 'slist' BEFORE integer index 'idxn' in the underlying stringarray
662663
!> Modifies the input stringlist 'list'
663-
subroutine insert_before_stringlist_int_impl( list, idxn, slist )
664+
pure subroutine insert_before_stringlist_int_impl( list, idxn, slist )
664665
!> Not a part of public API
665666
class(stringlist_type), intent(inout) :: list
666667
integer, intent(in) :: idxn
@@ -695,7 +696,7 @@ end subroutine insert_before_stringlist_int_impl
695696
!>
696697
!> Inserts chararray 'carray' BEFORE integer index 'idxn' in the underlying stringarray
697698
!> Modifies the input stringlist 'list'
698-
subroutine insert_before_chararray_int_impl( list, idxn, carray )
699+
pure subroutine insert_before_chararray_int_impl( list, idxn, carray )
699700
!> Not a part of public API
700701
class(stringlist_type), intent(inout) :: list
701702
integer, intent(in) :: idxn
@@ -718,7 +719,7 @@ end subroutine insert_before_chararray_int_impl
718719
!>
719720
!> Inserts stringarray 'sarray' BEFORE integer index 'idxn' in the underlying stringarray
720721
!> Modifies the input stringlist 'list'
721-
subroutine insert_before_stringarray_int_impl( list, idxn, sarray )
722+
pure subroutine insert_before_stringarray_int_impl( list, idxn, sarray )
722723
!> Not a part of public API
723724
class(stringlist_type), intent(inout) :: list
724725
integer, intent(in) :: idxn
@@ -755,7 +756,7 @@ pure subroutine get_engine( list, first, last, capture_strings )
755756
from = max( list%to_current_idxn( first ), 1 )
756757
to = min( list%to_current_idxn( last ), list%len() )
757758

758-
! out of bounds indexes won't be captured in capture_strings
759+
! out of bounds indexes won't be captured in 'capture_strings'
759760
if ( from <= to ) then
760761
allocate( capture_strings( to - from + 1 ) )
761762

@@ -812,8 +813,8 @@ end function get_range_idx_impl
812813
!> Removes strings present at indexes in interval ['first', 'last']
813814
!> Stores captured popped strings in array 'capture_popped'
814815
!> No return
815-
subroutine pop_drop_engine( list, first, last, capture_popped )
816-
class(stringlist_type) :: list
816+
pure subroutine pop_drop_engine( list, first, last, capture_popped )
817+
class(stringlist_type), intent(inout) :: list
817818
type(stringlist_index_type), intent(in) :: first, last
818819
type(string_type), allocatable, intent(out), optional :: capture_popped(:)
819820

@@ -824,8 +825,8 @@ subroutine pop_drop_engine( list, first, last, capture_popped )
824825
old_len = list%len()
825826
firstn = list%to_current_idxn( first )
826827
lastn = list%to_current_idxn( last )
827-
from = max( firstn , 1 )
828-
to = min( lastn , old_len )
828+
from = max( firstn, 1 )
829+
to = min( lastn, old_len )
829830

830831
! out of bounds indexes won't modify stringlist
831832
if ( from <= to ) then
@@ -863,7 +864,7 @@ end subroutine pop_drop_engine
863864
!> Removes the string present at stringlist_index 'idx' in stringlist 'list'
864865
!> Returns the removed string
865866
function pop_idx_impl( list, idx )
866-
class(stringlist_type) :: list
867+
class(stringlist_type), intent(inout) :: list
867868
type(stringlist_index_type), intent(in) :: idx
868869
type(string_type) :: pop_idx_impl
869870

@@ -883,7 +884,7 @@ end function pop_idx_impl
883884
!> in stringlist 'list'
884885
!> Returns removed strings
885886
function pop_range_idx_impl( list, first, last )
886-
class(stringlist_type) :: list
887+
class(stringlist_type), intent(inout) :: list
887888
type(stringlist_index_type), intent(in) :: first, last
888889

889890
type(string_type), dimension(:), allocatable :: pop_range_idx_impl
@@ -896,8 +897,8 @@ end function pop_range_idx_impl
896897
!>
897898
!> Removes the string present at stringlist_index 'idx' in stringlist 'list'
898899
!> Doesn't return the removed string
899-
subroutine drop_idx_impl( list, idx )
900-
class(stringlist_type) :: list
900+
pure subroutine drop_idx_impl( list, idx )
901+
class(stringlist_type), intent(inout) :: list
901902
type(stringlist_index_type), intent(in) :: idx
902903

903904
call pop_drop_engine( list, idx, idx )
@@ -909,8 +910,8 @@ end subroutine drop_idx_impl
909910
!> Removes strings present at stringlist_indexes in interval ['first', 'last']
910911
!> in stringlist 'list'
911912
!> Doesn't return removed strings
912-
subroutine drop_range_idx_impl( list, first, last )
913-
class(stringlist_type) :: list
913+
pure subroutine drop_range_idx_impl( list, first, last )
914+
class(stringlist_type), intent(inout) :: list
914915
type(stringlist_index_type), intent(in) :: first, last
915916

916917
call pop_drop_engine( list, first, last )

0 commit comments

Comments
 (0)