Skip to content

Commit

Permalink
some minor changes
Browse files Browse the repository at this point in the history
  • Loading branch information
aman-godara committed Sep 15, 2021
1 parent 5eedf6b commit a02c5ed
Showing 1 changed file with 26 additions and 25 deletions.
51 changes: 26 additions & 25 deletions src/stdlib_stringlist_type.f90
Original file line number Diff line number Diff line change
Expand Up @@ -171,14 +171,16 @@ end function new_stringlist
pure function new_stringlist_carray( array )
character(len=*), dimension(:), intent(in) :: array
type(stringlist_type) :: new_stringlist_carray
type(string_type), dimension( size(array) ) :: sarray

type(string_type), allocatable :: sarray(:)
integer :: i

allocate( sarray( size(array) ) )
do i = 1, size(array)
sarray(i) = string_type( array(i) )
end do

new_stringlist_carray = stringlist_type( sarray )
call move_alloc( sarray, new_stringlist_carray%stringarray )

end function new_stringlist_carray

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

new_stringlist_sarray = stringlist_type()
new_stringlist_sarray%stringarray = array

end function new_stringlist_sarray
Expand Down Expand Up @@ -476,7 +477,7 @@ end function shift
!>
!> Resets stringlist 'list' to an empy stringlist of len 0
!> Modifies the input stringlist 'list'
subroutine clear_list( list )
pure subroutine clear_list( list )
class(stringlist_type), intent(inout) :: list

if ( allocated( list%stringarray ) ) then
Expand Down Expand Up @@ -540,7 +541,7 @@ end function convert_to_current_idxn
!>
!> Inserts character scalar 'string' AT stringlist_index 'idx' in stringlist 'list'
!> Modifies the input stringlist 'list'
subroutine insert_at_char_idx_wrap( list, idx, string )
pure subroutine insert_at_char_idx_wrap( list, idx, string )
class(stringlist_type), intent(inout) :: list
type(stringlist_index_type), intent(in) :: idx
character(len=*), intent(in) :: string
Expand All @@ -553,7 +554,7 @@ end subroutine insert_at_char_idx_wrap
!>
!> Inserts string 'string' AT stringlist_index 'idx' in stringlist 'list'
!> Modifies the input stringlist 'list'
subroutine insert_at_string_idx_wrap( list, idx, string )
pure subroutine insert_at_string_idx_wrap( list, idx, string )
class(stringlist_type), intent(inout) :: list
type(stringlist_index_type), intent(in) :: idx
type(string_type), intent(in) :: string
Expand All @@ -566,7 +567,7 @@ end subroutine insert_at_string_idx_wrap
!>
!> Inserts stringlist 'slist' AT stringlist_index 'idx' in stringlist 'list'
!> Modifies the input stringlist 'list'
subroutine insert_at_stringlist_idx_wrap( list, idx, slist )
pure subroutine insert_at_stringlist_idx_wrap( list, idx, slist )
class(stringlist_type), intent(inout) :: list
type(stringlist_index_type), intent(in) :: idx
type(stringlist_type), intent(in) :: slist
Expand All @@ -579,7 +580,7 @@ end subroutine insert_at_stringlist_idx_wrap
!>
!> Inserts chararray 'carray' AT stringlist_index 'idx' in stringlist 'list'
!> Modifies the input stringlist 'list'
subroutine insert_at_chararray_idx_wrap( list, idx, carray )
pure subroutine insert_at_chararray_idx_wrap( list, idx, carray )
class(stringlist_type), intent(inout) :: list
type(stringlist_index_type), intent(in) :: idx
character(len=*), dimension(:), intent(in) :: carray
Expand All @@ -592,7 +593,7 @@ end subroutine insert_at_chararray_idx_wrap
!>
!> Inserts stringarray 'sarray' AT stringlist_index 'idx' in stringlist 'list'
!> Modifies the input stringlist 'list'
subroutine insert_at_stringarray_idx_wrap( list, idx, sarray )
pure subroutine insert_at_stringarray_idx_wrap( list, idx, sarray )
class(stringlist_type), intent(inout) :: list
type(stringlist_index_type), intent(in) :: idx
type(string_type), dimension(:), intent(in) :: sarray
Expand All @@ -605,7 +606,7 @@ end subroutine insert_at_stringarray_idx_wrap
!>
!> Inserts 'positions' number of empty positions BEFORE integer index 'idxn'
!> Modifies the input stringlist 'list'
subroutine insert_before_engine( list, idxn, positions )
pure subroutine insert_before_engine( list, idxn, positions )
!> Not a part of public API
type(stringlist_type), intent(inout) :: list
integer, intent(inout) :: idxn
Expand Down Expand Up @@ -641,7 +642,7 @@ end subroutine insert_before_engine
!>
!> Inserts string 'string' BEFORE integer index 'idxn' in the underlying stringarray
!> Modifies the input stringlist 'list'
subroutine insert_before_string_int_impl( list, idxn, string )
pure subroutine insert_before_string_int_impl( list, idxn, string )
!> Not a part of public API
class(stringlist_type), intent(inout) :: list
integer, intent(in) :: idxn
Expand All @@ -660,7 +661,7 @@ end subroutine insert_before_string_int_impl
!>
!> Inserts stringlist 'slist' BEFORE integer index 'idxn' in the underlying stringarray
!> Modifies the input stringlist 'list'
subroutine insert_before_stringlist_int_impl( list, idxn, slist )
pure subroutine insert_before_stringlist_int_impl( list, idxn, slist )
!> Not a part of public API
class(stringlist_type), intent(inout) :: list
integer, intent(in) :: idxn
Expand Down Expand Up @@ -691,7 +692,7 @@ end subroutine insert_before_stringlist_int_impl
!>
!> Inserts chararray 'carray' BEFORE integer index 'idxn' in the underlying stringarray
!> Modifies the input stringlist 'list'
subroutine insert_before_chararray_int_impl( list, idxn, carray )
pure subroutine insert_before_chararray_int_impl( list, idxn, carray )
!> Not a part of public API
class(stringlist_type), intent(inout) :: list
integer, intent(in) :: idxn
Expand All @@ -714,7 +715,7 @@ end subroutine insert_before_chararray_int_impl
!>
!> Inserts stringarray 'sarray' BEFORE integer index 'idxn' in the underlying stringarray
!> Modifies the input stringlist 'list'
subroutine insert_before_stringarray_int_impl( list, idxn, sarray )
pure subroutine insert_before_stringarray_int_impl( list, idxn, sarray )
!> Not a part of public API
class(stringlist_type), intent(inout) :: list
integer, intent(in) :: idxn
Expand Down Expand Up @@ -751,7 +752,7 @@ pure subroutine get_engine( list, first, last, capture_strings )
from = max( list%to_current_idxn( first ), 1 )
to = min( list%to_current_idxn( last ), list%len() )

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

Expand Down Expand Up @@ -808,8 +809,8 @@ end function get_range_idx_impl
!> Removes strings present at indexes in interval ['first', 'last']
!> Stores captured popped strings in array 'capture_popped'
!> No return
subroutine pop_drop_engine( list, first, last, capture_popped )
class(stringlist_type) :: list
pure subroutine pop_drop_engine( list, first, last, capture_popped )
class(stringlist_type), intent(inout) :: list
type(stringlist_index_type), intent(in) :: first, last
type(string_type), allocatable, intent(out), optional :: capture_popped(:)

Expand All @@ -820,8 +821,8 @@ subroutine pop_drop_engine( list, first, last, capture_popped )
old_len = list%len()
firstn = list%to_current_idxn( first )
lastn = list%to_current_idxn( last )
from = max( firstn , 1 )
to = min( lastn , old_len )
from = max( firstn, 1 )
to = min( lastn, old_len )

! out of bounds indexes won't modify stringlist
if ( from <= to ) then
Expand Down Expand Up @@ -859,7 +860,7 @@ end subroutine pop_drop_engine
!> Removes the string present at stringlist_index 'idx' in stringlist 'list'
!> Returns the removed string
function pop_idx_impl( list, idx )
class(stringlist_type) :: list
class(stringlist_type), intent(inout) :: list
type(stringlist_index_type), intent(in) :: idx
type(string_type) :: pop_idx_impl

Expand All @@ -879,7 +880,7 @@ end function pop_idx_impl
!> in stringlist 'list'
!> Returns removed strings
function pop_range_idx_impl( list, first, last )
class(stringlist_type) :: list
class(stringlist_type), intent(inout) :: list
type(stringlist_index_type), intent(in) :: first, last

type(string_type), dimension(:), allocatable :: pop_range_idx_impl
Expand All @@ -892,8 +893,8 @@ end function pop_range_idx_impl
!>
!> Removes the string present at stringlist_index 'idx' in stringlist 'list'
!> Doesn't return the removed string
subroutine drop_idx_impl( list, idx )
class(stringlist_type) :: list
pure subroutine drop_idx_impl( list, idx )
class(stringlist_type), intent(inout) :: list
type(stringlist_index_type), intent(in) :: idx

call pop_drop_engine( list, idx, idx )
Expand All @@ -905,8 +906,8 @@ end subroutine drop_idx_impl
!> Removes strings present at stringlist_indexes in interval ['first', 'last']
!> in stringlist 'list'
!> Doesn't return removed strings
subroutine drop_range_idx_impl( list, first, last )
class(stringlist_type) :: list
pure subroutine drop_range_idx_impl( list, first, last )
class(stringlist_type), intent(inout) :: list
type(stringlist_index_type), intent(in) :: first, last

call pop_drop_engine( list, first, last )
Expand Down

0 comments on commit a02c5ed

Please sign in to comment.