@@ -75,14 +75,14 @@ module stdlib_stringlist_type
7575 insert_at_chararray_idx, &
7676 insert_at_stringarray_idx
7777
78- procedure :: insert_before_string_int
79- procedure :: insert_before_stringlist_int
80- procedure :: insert_before_chararray_int
81- procedure :: insert_before_stringarray_int
82- generic :: insert_before = > insert_before_string_int, &
83- insert_before_stringlist_int, &
84- insert_before_chararray_int, &
85- insert_before_stringarray_int
78+ procedure :: insert_before_string_idxn
79+ procedure :: insert_before_stringlist_idxn
80+ procedure :: insert_before_chararray_idxn
81+ procedure :: insert_before_stringarray_idxn
82+ generic :: insert_before = > insert_before_string_idxn, &
83+ insert_before_stringlist_idxn, &
84+ insert_before_chararray_idxn, &
85+ insert_before_stringarray_idxn
8686
8787 procedure :: get_idx
8888 procedure :: get_range_idx
@@ -218,7 +218,7 @@ end function backward_index
218218
219219 ! > Appends character scalar 'rhs' to the stringlist 'list'
220220 ! > Returns a new stringlist
221- function append_char ( lhs , rhs )
221+ pure function append_char ( lhs , rhs )
222222 type (stringlist_type), intent (in ) :: lhs
223223 character (len=* ), intent (in ) :: rhs
224224 type (stringlist_type) :: append_char
@@ -230,7 +230,7 @@ end function append_char
230230
231231 ! > Appends string 'rhs' to the stringlist 'list'
232232 ! > Returns a new stringlist
233- function append_string ( lhs , rhs )
233+ pure function append_string ( lhs , rhs )
234234 type (stringlist_type), intent (in ) :: lhs
235235 type (string_type), intent (in ) :: rhs
236236 type (stringlist_type) :: append_string
@@ -242,7 +242,7 @@ end function append_string
242242
243243 ! > Prepends character scalar 'lhs' to the stringlist 'rhs'
244244 ! > Returns a new stringlist
245- function prepend_char ( lhs , rhs )
245+ pure function prepend_char ( lhs , rhs )
246246 character (len=* ), intent (in ) :: lhs
247247 type (stringlist_type), intent (in ) :: rhs
248248 type (stringlist_type) :: prepend_char
@@ -254,7 +254,7 @@ end function prepend_char
254254
255255 ! > Prepends string 'lhs' to the stringlist 'rhs'
256256 ! > Returns a new stringlist
257- function prepend_string ( lhs , rhs )
257+ pure function prepend_string ( lhs , rhs )
258258 type (string_type), intent (in ) :: lhs
259259 type (stringlist_type), intent (in ) :: rhs
260260 type (stringlist_type) :: prepend_string
@@ -266,7 +266,7 @@ end function prepend_string
266266
267267 ! > Appends stringlist 'rhs' to the stringlist 'lhs'
268268 ! > Returns a new stringlist
269- function append_stringlist ( lhs , rhs )
269+ pure function append_stringlist ( lhs , rhs )
270270 type (stringlist_type), intent (in ) :: lhs
271271 type (stringlist_type), intent (in ) :: rhs
272272 type (stringlist_type) :: append_stringlist
@@ -278,7 +278,7 @@ end function append_stringlist
278278
279279 ! > Appends chararray 'rhs' to the stringlist 'lhs'
280280 ! > Returns a new stringlist
281- function append_carray ( lhs , rhs )
281+ pure function append_carray ( lhs , rhs )
282282 type (stringlist_type), intent (in ) :: lhs
283283 character (len=* ), dimension (:), intent (in ) :: rhs
284284 type (stringlist_type) :: append_carray
@@ -290,7 +290,7 @@ end function append_carray
290290
291291 ! > Appends stringarray 'rhs' to the stringlist 'lhs'
292292 ! > Returns a new stringlist
293- function append_sarray ( lhs , rhs )
293+ pure function append_sarray ( lhs , rhs )
294294 type (stringlist_type), intent (in ) :: lhs
295295 type (string_type), dimension (:), intent (in ) :: rhs
296296 type (stringlist_type) :: append_sarray
@@ -302,7 +302,7 @@ end function append_sarray
302302
303303 ! > Prepends chararray 'lhs' to the stringlist 'rhs'
304304 ! > Returns a new stringlist
305- function prepend_carray ( lhs , rhs )
305+ pure function prepend_carray ( lhs , rhs )
306306 character (len=* ), dimension (:), intent (in ) :: lhs
307307 type (stringlist_type), intent (in ) :: rhs
308308 type (stringlist_type) :: prepend_carray
@@ -314,7 +314,7 @@ end function prepend_carray
314314
315315 ! > Prepends stringarray 'lhs' to the stringlist 'rhs'
316316 ! > Returns a new stringlist
317- function prepend_sarray ( lhs , rhs )
317+ pure function prepend_sarray ( lhs , rhs )
318318 type (string_type), dimension (:), intent (in ) :: lhs
319319 type (stringlist_type), intent (in ) :: rhs
320320 type (stringlist_type) :: prepend_sarray
@@ -458,21 +458,6 @@ pure logical function ineq_sarray_stringlist( lhs, rhs )
458458
459459 end function ineq_sarray_stringlist
460460
461- ! Version: experimental
462- ! >
463- ! > Shifts a stringlist_index by integer 'shift_by'
464- ! > Returns the shifted stringlist_index
465- pure function shift ( idx , shift_by )
466- ! > Not a part of public API
467- type (stringlist_index_type), intent (in ) :: idx
468- integer , intent (in ) :: shift_by
469-
470- type (stringlist_index_type) :: shift
471-
472- shift = merge ( fidx( idx% offset + shift_by ), bidx( idx% offset + shift_by ), idx% forward )
473-
474- end function shift
475-
476461 ! clear:
477462
478463 ! > Version: experimental
@@ -525,7 +510,7 @@ end function to_future_at_idxn
525510
526511 ! > Version: experimental
527512 ! >
528- ! > Converts a forward index OR backward index to its equivalent integer index idxn
513+ ! > Converts a forward index OR backward index to its equivalent integer index
529514 ! > Returns an integer
530515 pure integer function to_current_idxn( list, idx )
531516 ! > Not a part of public API
@@ -644,7 +629,7 @@ end subroutine insert_before_engine
644629 ! >
645630 ! > Inserts string 'string' BEFORE integer index 'idxn' in the underlying stringarray
646631 ! > Modifies the input stringlist 'list'
647- pure subroutine insert_before_string_int ( list , idxn , string )
632+ pure subroutine insert_before_string_idxn ( list , idxn , string )
648633 ! > Not a part of public API
649634 class(stringlist_type), intent (inout ) :: list
650635 integer , intent (in ) :: idxn
@@ -657,13 +642,13 @@ pure subroutine insert_before_string_int( list, idxn, string )
657642
658643 list% stringarray(work_idxn) = string
659644
660- end subroutine insert_before_string_int
645+ end subroutine insert_before_string_idxn
661646
662647 ! > Version: experimental
663648 ! >
664649 ! > Inserts stringlist 'slist' BEFORE integer index 'idxn' in the underlying stringarray
665650 ! > Modifies the input stringlist 'list'
666- pure subroutine insert_before_stringlist_int ( list , idxn , slist )
651+ pure subroutine insert_before_stringlist_idxn ( list , idxn , slist )
667652 ! > Not a part of public API
668653 class(stringlist_type), intent (inout ) :: list
669654 integer , intent (in ) :: idxn
@@ -675,9 +660,9 @@ pure subroutine insert_before_stringlist_int( list, idxn, slist )
675660
676661 pre_length = slist% len ()
677662 if (pre_length > 0 ) then
678- work_idxn = idxn
663+ work_idxn = idxn
679664
680- call insert_before_empty_positions ( list, work_idxn, pre_length )
665+ call insert_before_engine ( list, work_idxn, pre_length )
681666 post_length = slist% len ()
682667
683668 inew = work_idxn
@@ -692,53 +677,53 @@ pure subroutine insert_before_stringlist_int( list, idxn, slist )
692677 end do
693678 end if
694679
695- end subroutine insert_before_stringlist_int
680+ end subroutine insert_before_stringlist_idxn
696681
697682 ! > Version: experimental
698683 ! >
699684 ! > Inserts chararray 'carray' BEFORE integer index 'idxn' in the underlying stringarray
700685 ! > Modifies the input stringlist 'list'
701- pure subroutine insert_before_chararray_int ( list , idxn , carray )
686+ pure subroutine insert_before_chararray_idxn ( list , idxn , carray )
702687 ! > Not a part of public API
703688 class(stringlist_type), intent (inout ) :: list
704689 integer , intent (in ) :: idxn
705690 character (len=* ), dimension (:), intent (in ) :: carray
706691
707- integer :: i
708- integer :: work_idxn, idxnew
692+ integer :: i, inew
693+ integer :: work_idxn
709694
710695 work_idxn = idxn
711696 call insert_before_engine( list, work_idxn, size ( carray ) )
712697
713698 do i = 1 , size ( carray )
714- idxnew = work_idxn + i - 1
715- list% stringarray(idxnew ) = string_type( carray(i) )
699+ inew = work_idxn + i - 1
700+ list% stringarray(inew ) = string_type( carray(i) )
716701 end do
717702
718- end subroutine insert_before_chararray_int
703+ end subroutine insert_before_chararray_idxn
719704
720705 ! > Version: experimental
721706 ! >
722707 ! > Inserts stringarray 'sarray' BEFORE integer index 'idxn' in the underlying stringarray
723708 ! > Modifies the input stringlist 'list'
724- pure subroutine insert_before_stringarray_int ( list , idxn , sarray )
709+ pure subroutine insert_before_stringarray_idxn ( list , idxn , sarray )
725710 ! > Not a part of public API
726711 class(stringlist_type), intent (inout ) :: list
727712 integer , intent (in ) :: idxn
728713 type (string_type), dimension (:), intent (in ) :: sarray
729714
730- integer :: i
731- integer :: work_idxn, idxnew
715+ integer :: i, inew
716+ integer :: work_idxn
732717
733718 work_idxn = idxn
734719 call insert_before_engine( list, work_idxn, size ( sarray ) )
735720
736721 do i = 1 , size ( sarray )
737- idxnew = work_idxn + i - 1
738- list% stringarray(idxnew ) = sarray(i)
722+ inew = work_idxn + i - 1
723+ list% stringarray(inew ) = sarray(i)
739724 end do
740725
741- end subroutine insert_before_stringarray_int
726+ end subroutine insert_before_stringarray_idxn
742727
743728 ! get:
744729
@@ -820,15 +805,13 @@ pure subroutine pop_drop_engine( list, first, last, popped_strings )
820805 type (stringlist_index_type), intent (in ) :: first, last
821806 type (string_type), allocatable , intent (out ), optional :: popped_strings(:)
822807
823- integer :: firstn, lastn, from, to
808+ integer :: from, to
824809 integer :: i, inew, pos, old_len, new_len
825810 type (string_type), dimension (:), allocatable :: new_stringarray
826811
827812 old_len = list% len ()
828- firstn = list% to_current_idxn( first )
829- lastn = list% to_current_idxn( last )
830- from = max ( firstn, 1 )
831- to = min ( lastn, old_len )
813+ from = max ( list% to_current_idxn( first ), 1 )
814+ to = min ( list% to_current_idxn( last ), old_len )
832815
833816 ! out of bounds indexes won't modify stringlist
834817 if ( from <= to ) then
@@ -842,8 +825,12 @@ pure subroutine pop_drop_engine( list, first, last, popped_strings )
842825
843826 ! capture popped strings
844827 if ( present (popped_strings) ) then
845- call get_engine( list, shift( first, from - firstn ), &
846- & shift( last, lastn - to ), popped_strings )
828+ allocate ( popped_strings(pos) )
829+ inew = 1
830+ do i = from, to
831+ call move( list% stringarray(i), popped_strings(inew) )
832+ inew = inew + 1
833+ end do
847834 end if
848835
849836 inew = from
0 commit comments