@@ -69,10 +69,10 @@ module stdlib_stringlist_type
6969 procedure :: insert_at_stringlist_idx = > insert_at_stringlist_idx_wrap
7070 procedure :: insert_at_chararray_idx = > insert_at_chararray_idx_wrap
7171 procedure :: insert_at_stringarray_idx = > insert_at_stringarray_idx_wrap
72- generic, public :: insert_at = > insert_at_char_idx, &
73- insert_at_string_idx, &
74- insert_at_stringlist_idx, &
75- insert_at_chararray_idx, &
72+ generic, public :: insert_at = > insert_at_char_idx, &
73+ insert_at_string_idx, &
74+ insert_at_stringlist_idx, &
75+ insert_at_chararray_idx, &
7676 insert_at_stringarray_idx
7777
7878 procedure :: insert_before_string_int = > insert_before_string_int_impl
@@ -87,11 +87,15 @@ module stdlib_stringlist_type
8787 procedure :: get_string_idx = > get_string_idx_impl
8888 generic, public :: get = > get_string_idx
8989
90- procedure :: pop_string_idx = > pop_string_idx_impl
91- generic, public :: pop = > pop_string_idx
90+ procedure :: pop_idx = > pop_idx_impl
91+ procedure :: pop_range_idx = > pop_range_idx_impl
92+ generic, public :: pop = > pop_idx, &
93+ pop_range_idx
9294
93- procedure :: drop_string_idx = > drop_string_idx_impl
94- generic, public :: drop = > drop_string_idx
95+ procedure :: drop_idx = > drop_idx_impl
96+ procedure :: drop_range_idx = > drop_range_idx_impl
97+ generic, public :: drop = > drop_idx, &
98+ drop_range_idx
9599
96100 end type stringlist_type
97101
@@ -739,7 +743,7 @@ end function get_string_idx_impl
739743 ! >
740744 ! > Removes strings present at indexes in interval ['first', 'last']
741745 ! > Returns captured popped strings
742- subroutine pop_positions ( list , first , last , capture_popped )
746+ subroutine pop_engine ( list , first , last , capture_popped )
743747 class(stringlist_type) :: list
744748 type (stringlist_index_type), intent (in ) :: first, last
745749 type (string_type), allocatable , intent (out ), optional :: capture_popped(:)
@@ -781,44 +785,75 @@ subroutine pop_positions( list, first, last, capture_popped)
781785 end do
782786
783787 call move_alloc( new_stringarray, list% stringarray )
784-
788+ else
789+ if ( present (capture_popped) ) then
790+ allocate ( capture_popped(0 ) )
791+ end if
785792 end if
786793
787- end subroutine pop_positions
794+ end subroutine pop_engine
788795
789796 ! pop:
790797
791798 ! > Version: experimental
792799 ! >
793800 ! > Removes the string present at stringlist_index 'idx' in stringlist 'list'
794801 ! > Returns the removed string
795- function pop_string_idx_impl ( list , idx )
802+ function pop_idx_impl ( list , idx )
796803 class(stringlist_type) :: list
797804 type (stringlist_index_type), intent (in ) :: idx
798- type (string_type) :: pop_string_idx_impl
805+ type (string_type) :: pop_idx_impl
799806
800- type (string_type), dimension (:), allocatable :: capture_popped
807+ type (string_type), dimension (:), allocatable :: popped_strings
801808
802- call pop_positions ( list, idx, idx, capture_popped )
809+ call pop_engine ( list, idx, idx, popped_strings )
803810
804- if ( allocated (capture_popped) ) then
805- pop_string_idx_impl = capture_popped (1 )
811+ if ( size (popped_strings) > 0 ) then
812+ pop_idx_impl = popped_strings (1 )
806813 end if
807814
808- end function pop_string_idx_impl
815+ end function pop_idx_impl
816+
817+ ! > Version: experimental
818+ ! >
819+ ! > Removes strings present at stringlist_indexes in interval ['first', 'last']
820+ ! > in stringlist 'list'
821+ ! > Returns removed strings
822+ function pop_range_idx_impl ( list , first , last )
823+ class(stringlist_type) :: list
824+ type (stringlist_index_type), intent (in ) :: first, last
825+
826+ type (string_type), dimension (:), allocatable :: pop_range_idx_impl
827+
828+ call pop_engine( list, first, last, pop_range_idx_impl )
829+
830+ end function pop_range_idx_impl
809831
810832 ! drop:
811833
812834 ! > Version: experimental
813835 ! >
814836 ! > Removes the string present at stringlist_index 'idx' in stringlist 'list'
815837 ! > Doesn't return the removed string
816- subroutine drop_string_idx_impl ( list , idx )
838+ subroutine drop_idx_impl ( list , idx )
817839 class(stringlist_type) :: list
818840 type (stringlist_index_type), intent (in ) :: idx
819841
820- call pop_positions( list, idx, idx )
842+ call pop_engine( list, idx, idx )
843+
844+ end subroutine drop_idx_impl
845+
846+ ! > Version: experimental
847+ ! >
848+ ! > Removes strings present at stringlist_indexes in interval ['first', 'last']
849+ ! > in stringlist 'list'
850+ ! > Doesn't return removed strings
851+ subroutine drop_idx_impl ( list , first , last )
852+ class(stringlist_type) :: list
853+ type (stringlist_index_type), intent (in ) :: first, last
854+
855+ call pop_engine( list, first, last )
821856
822- end subroutine drop_string_idx_impl
857+ end subroutine drop_idx_impl
823858
824859end module stdlib_stringlist_type
0 commit comments