Skip to content

Commit

Permalink
some minor improvements
Browse files Browse the repository at this point in the history
  • Loading branch information
aman-godara committed Oct 15, 2021
1 parent e34cce2 commit 2b3a5ef
Showing 1 changed file with 45 additions and 58 deletions.
103 changes: 45 additions & 58 deletions src/stdlib_stringlist_type.f90
Original file line number Diff line number Diff line change
Expand Up @@ -75,14 +75,14 @@ module stdlib_stringlist_type
insert_at_chararray_idx, &
insert_at_stringarray_idx

procedure :: insert_before_string_int
procedure :: insert_before_stringlist_int
procedure :: insert_before_chararray_int
procedure :: insert_before_stringarray_int
generic :: insert_before => insert_before_string_int, &
insert_before_stringlist_int, &
insert_before_chararray_int, &
insert_before_stringarray_int
procedure :: insert_before_string_idxn
procedure :: insert_before_stringlist_idxn
procedure :: insert_before_chararray_idxn
procedure :: insert_before_stringarray_idxn
generic :: insert_before => insert_before_string_idxn, &
insert_before_stringlist_idxn, &
insert_before_chararray_idxn, &
insert_before_stringarray_idxn

procedure :: get_idx
procedure :: get_range_idx
Expand Down Expand Up @@ -218,7 +218,7 @@ end function backward_index

!> Appends character scalar 'rhs' to the stringlist 'list'
!> Returns a new stringlist
function append_char( lhs, rhs )
pure function append_char( lhs, rhs )
type(stringlist_type), intent(in) :: lhs
character(len=*), intent(in) :: rhs
type(stringlist_type) :: append_char
Expand All @@ -230,7 +230,7 @@ end function append_char

!> Appends string 'rhs' to the stringlist 'list'
!> Returns a new stringlist
function append_string( lhs, rhs )
pure function append_string( lhs, rhs )
type(stringlist_type), intent(in) :: lhs
type(string_type), intent(in) :: rhs
type(stringlist_type) :: append_string
Expand All @@ -242,7 +242,7 @@ end function append_string

!> Prepends character scalar 'lhs' to the stringlist 'rhs'
!> Returns a new stringlist
function prepend_char( lhs, rhs )
pure function prepend_char( lhs, rhs )
character(len=*), intent(in) :: lhs
type(stringlist_type), intent(in) :: rhs
type(stringlist_type) :: prepend_char
Expand All @@ -254,7 +254,7 @@ end function prepend_char

!> Prepends string 'lhs' to the stringlist 'rhs'
!> Returns a new stringlist
function prepend_string( lhs, rhs )
pure function prepend_string( lhs, rhs )
type(string_type), intent(in) :: lhs
type(stringlist_type), intent(in) :: rhs
type(stringlist_type) :: prepend_string
Expand All @@ -266,7 +266,7 @@ end function prepend_string

!> Appends stringlist 'rhs' to the stringlist 'lhs'
!> Returns a new stringlist
function append_stringlist( lhs, rhs )
pure function append_stringlist( lhs, rhs )
type(stringlist_type), intent(in) :: lhs
type(stringlist_type), intent(in) :: rhs
type(stringlist_type) :: append_stringlist
Expand All @@ -278,7 +278,7 @@ end function append_stringlist

!> Appends chararray 'rhs' to the stringlist 'lhs'
!> Returns a new stringlist
function append_carray( lhs, rhs )
pure function append_carray( lhs, rhs )
type(stringlist_type), intent(in) :: lhs
character(len=*), dimension(:), intent(in) :: rhs
type(stringlist_type) :: append_carray
Expand All @@ -290,7 +290,7 @@ end function append_carray

!> Appends stringarray 'rhs' to the stringlist 'lhs'
!> Returns a new stringlist
function append_sarray( lhs, rhs )
pure function append_sarray( lhs, rhs )
type(stringlist_type), intent(in) :: lhs
type(string_type), dimension(:), intent(in) :: rhs
type(stringlist_type) :: append_sarray
Expand All @@ -302,7 +302,7 @@ end function append_sarray

!> Prepends chararray 'lhs' to the stringlist 'rhs'
!> Returns a new stringlist
function prepend_carray( lhs, rhs )
pure function prepend_carray( lhs, rhs )
character(len=*), dimension(:), intent(in) :: lhs
type(stringlist_type), intent(in) :: rhs
type(stringlist_type) :: prepend_carray
Expand All @@ -314,7 +314,7 @@ end function prepend_carray

!> Prepends stringarray 'lhs' to the stringlist 'rhs'
!> Returns a new stringlist
function prepend_sarray( lhs, rhs )
pure function prepend_sarray( lhs, rhs )
type(string_type), dimension(:), intent(in) :: lhs
type(stringlist_type), intent(in) :: rhs
type(stringlist_type) :: prepend_sarray
Expand Down Expand Up @@ -458,21 +458,6 @@ pure logical function ineq_sarray_stringlist( lhs, rhs )

end function ineq_sarray_stringlist

! Version: experimental
!>
!> Shifts a stringlist_index by integer 'shift_by'
!> Returns the shifted stringlist_index
pure function shift( idx, shift_by )
!> Not a part of public API
type(stringlist_index_type), intent(in) :: idx
integer, intent(in) :: shift_by

type(stringlist_index_type) :: shift

shift = merge( fidx( idx%offset + shift_by ), bidx( idx%offset + shift_by ), idx%forward )

end function shift

! clear:

!> Version: experimental
Expand Down Expand Up @@ -525,7 +510,7 @@ end function to_future_at_idxn

!> Version: experimental
!>
!> Converts a forward index OR backward index to its equivalent integer index idxn
!> Converts a forward index OR backward index to its equivalent integer index
!> Returns an integer
pure integer function to_current_idxn( list, idx )
!> Not a part of public API
Expand Down Expand Up @@ -644,7 +629,7 @@ end subroutine insert_before_engine
!>
!> Inserts string 'string' BEFORE integer index 'idxn' in the underlying stringarray
!> Modifies the input stringlist 'list'
pure subroutine insert_before_string_int( list, idxn, string )
pure subroutine insert_before_string_idxn( list, idxn, string )
!> Not a part of public API
class(stringlist_type), intent(inout) :: list
integer, intent(in) :: idxn
Expand All @@ -657,13 +642,13 @@ pure subroutine insert_before_string_int( list, idxn, string )

list%stringarray(work_idxn) = string

end subroutine insert_before_string_int
end subroutine insert_before_string_idxn

!> Version: experimental
!>
!> Inserts stringlist 'slist' BEFORE integer index 'idxn' in the underlying stringarray
!> Modifies the input stringlist 'list'
pure subroutine insert_before_stringlist_int( list, idxn, slist )
pure subroutine insert_before_stringlist_idxn( list, idxn, slist )
!> Not a part of public API
class(stringlist_type), intent(inout) :: list
integer, intent(in) :: idxn
Expand All @@ -675,9 +660,9 @@ pure subroutine insert_before_stringlist_int( list, idxn, slist )

pre_length = slist%len()
if (pre_length > 0) then
work_idxn = idxn
work_idxn = idxn

call insert_before_empty_positions( list, work_idxn, pre_length )
call insert_before_engine( list, work_idxn, pre_length )
post_length = slist%len()

inew = work_idxn
Expand All @@ -692,53 +677,53 @@ pure subroutine insert_before_stringlist_int( list, idxn, slist )
end do
end if

end subroutine insert_before_stringlist_int
end subroutine insert_before_stringlist_idxn

!> Version: experimental
!>
!> Inserts chararray 'carray' BEFORE integer index 'idxn' in the underlying stringarray
!> Modifies the input stringlist 'list'
pure subroutine insert_before_chararray_int( list, idxn, carray )
pure subroutine insert_before_chararray_idxn( list, idxn, carray )
!> Not a part of public API
class(stringlist_type), intent(inout) :: list
integer, intent(in) :: idxn
character(len=*), dimension(:), intent(in) :: carray

integer :: i
integer :: work_idxn, idxnew
integer :: i, inew
integer :: work_idxn

work_idxn = idxn
call insert_before_engine( list, work_idxn, size( carray ) )

do i = 1, size( carray )
idxnew = work_idxn + i - 1
list%stringarray(idxnew) = string_type( carray(i) )
inew = work_idxn + i - 1
list%stringarray(inew) = string_type( carray(i) )
end do

end subroutine insert_before_chararray_int
end subroutine insert_before_chararray_idxn

!> Version: experimental
!>
!> Inserts stringarray 'sarray' BEFORE integer index 'idxn' in the underlying stringarray
!> Modifies the input stringlist 'list'
pure subroutine insert_before_stringarray_int( list, idxn, sarray )
pure subroutine insert_before_stringarray_idxn( list, idxn, sarray )
!> Not a part of public API
class(stringlist_type), intent(inout) :: list
integer, intent(in) :: idxn
type(string_type), dimension(:), intent(in) :: sarray

integer :: i
integer :: work_idxn, idxnew
integer :: i, inew
integer :: work_idxn

work_idxn = idxn
call insert_before_engine( list, work_idxn, size( sarray ) )

do i = 1, size( sarray )
idxnew = work_idxn + i - 1
list%stringarray(idxnew) = sarray(i)
inew = work_idxn + i - 1
list%stringarray(inew) = sarray(i)
end do

end subroutine insert_before_stringarray_int
end subroutine insert_before_stringarray_idxn

! get:

Expand Down Expand Up @@ -820,15 +805,13 @@ pure subroutine pop_drop_engine( list, first, last, popped_strings )
type(stringlist_index_type), intent(in) :: first, last
type(string_type), allocatable, intent(out), optional :: popped_strings(:)

integer :: firstn, lastn, from, to
integer :: from, to
integer :: i, inew, pos, old_len, new_len
type(string_type), dimension(:), allocatable :: new_stringarray

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( list%to_current_idxn( first ), 1 )
to = min( list%to_current_idxn( last ), old_len )

! out of bounds indexes won't modify stringlist
if ( from <= to ) then
Expand All @@ -842,8 +825,12 @@ pure subroutine pop_drop_engine( list, first, last, popped_strings )

! capture popped strings
if ( present(popped_strings) ) then
call get_engine( list, shift( first, from - firstn ), &
& shift( last, lastn - to ), popped_strings )
allocate( popped_strings(pos) )
inew = 1
do i = from, to
call move( list%stringarray(i), popped_strings(inew) )
inew = inew + 1
end do
end if

inew = from
Expand Down

0 comments on commit 2b3a5ef

Please sign in to comment.