@@ -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
@@ -691,7 +692,7 @@ end subroutine insert_before_stringlist_int_impl
691692 ! >
692693 ! > Inserts chararray 'carray' BEFORE integer index 'idxn' in the underlying stringarray
693694 ! > Modifies the input stringlist 'list'
694- subroutine insert_before_chararray_int_impl ( list , idxn , carray )
695+ pure subroutine insert_before_chararray_int_impl ( list , idxn , carray )
695696 ! > Not a part of public API
696697 class(stringlist_type), intent (inout ) :: list
697698 integer , intent (in ) :: idxn
@@ -714,7 +715,7 @@ end subroutine insert_before_chararray_int_impl
714715 ! >
715716 ! > Inserts stringarray 'sarray' BEFORE integer index 'idxn' in the underlying stringarray
716717 ! > Modifies the input stringlist 'list'
717- subroutine insert_before_stringarray_int_impl ( list , idxn , sarray )
718+ pure subroutine insert_before_stringarray_int_impl ( list , idxn , sarray )
718719 ! > Not a part of public API
719720 class(stringlist_type), intent (inout ) :: list
720721 integer , intent (in ) :: idxn
@@ -751,7 +752,7 @@ pure subroutine get_engine( list, first, last, capture_strings )
751752 from = max ( list% to_current_idxn( first ), 1 )
752753 to = min ( list% to_current_idxn( last ), list% len () )
753754
754- ! out of bounds indexes won't be captured in capture_strings
755+ ! out of bounds indexes won't be captured in ' capture_strings'
755756 if ( from <= to ) then
756757 allocate ( capture_strings( to - from + 1 ) )
757758
@@ -808,8 +809,8 @@ end function get_range_idx_impl
808809 ! > Removes strings present at indexes in interval ['first', 'last']
809810 ! > Stores captured popped strings in array 'capture_popped'
810811 ! > No return
811- subroutine pop_drop_engine ( list , first , last , capture_popped )
812- class(stringlist_type) :: list
812+ pure subroutine pop_drop_engine ( list , first , last , capture_popped )
813+ class(stringlist_type), intent ( inout ) :: list
813814 type (stringlist_index_type), intent (in ) :: first, last
814815 type (string_type), allocatable , intent (out ), optional :: capture_popped(:)
815816
@@ -820,8 +821,8 @@ subroutine pop_drop_engine( list, first, last, capture_popped )
820821 old_len = list% len ()
821822 firstn = list% to_current_idxn( first )
822823 lastn = list% to_current_idxn( last )
823- from = max ( firstn , 1 )
824- to = min ( lastn , old_len )
824+ from = max ( firstn, 1 )
825+ to = min ( lastn, old_len )
825826
826827 ! out of bounds indexes won't modify stringlist
827828 if ( from <= to ) then
@@ -859,7 +860,7 @@ end subroutine pop_drop_engine
859860 ! > Removes the string present at stringlist_index 'idx' in stringlist 'list'
860861 ! > Returns the removed string
861862 function pop_idx_impl ( list , idx )
862- class(stringlist_type) :: list
863+ class(stringlist_type), intent ( inout ) :: list
863864 type (stringlist_index_type), intent (in ) :: idx
864865 type (string_type) :: pop_idx_impl
865866
@@ -879,7 +880,7 @@ end function pop_idx_impl
879880 ! > in stringlist 'list'
880881 ! > Returns removed strings
881882 function pop_range_idx_impl ( list , first , last )
882- class(stringlist_type) :: list
883+ class(stringlist_type), intent ( inout ) :: list
883884 type (stringlist_index_type), intent (in ) :: first, last
884885
885886 type (string_type), dimension (:), allocatable :: pop_range_idx_impl
@@ -892,8 +893,8 @@ end function pop_range_idx_impl
892893 ! >
893894 ! > Removes the string present at stringlist_index 'idx' in stringlist 'list'
894895 ! > Doesn't return the removed string
895- subroutine drop_idx_impl ( list , idx )
896- class(stringlist_type) :: list
896+ pure subroutine drop_idx_impl ( list , idx )
897+ class(stringlist_type), intent ( inout ) :: list
897898 type (stringlist_index_type), intent (in ) :: idx
898899
899900 call pop_drop_engine( list, idx, idx )
@@ -905,8 +906,8 @@ end subroutine drop_idx_impl
905906 ! > Removes strings present at stringlist_indexes in interval ['first', 'last']
906907 ! > in stringlist 'list'
907908 ! > Doesn't return removed strings
908- subroutine drop_range_idx_impl ( list , first , last )
909- class(stringlist_type) :: list
909+ pure subroutine drop_range_idx_impl ( list , first , last )
910+ class(stringlist_type), intent ( inout ) :: list
910911 type (stringlist_index_type), intent (in ) :: first, last
911912
912913 call pop_drop_engine( list, first, last )
0 commit comments