Skip to content
Draft
Changes from 1 commit
Commits
Show all changes
22 commits
Select commit Hold shift + click to select a range
933a367
resolved inserting 0 lengthed slist in list bug
aman-godara Oct 10, 2021
ea46f19
changed name
aman-godara Oct 10, 2021
c790494
added delete function for stringlist
aman-godara Sep 6, 2021
e446e7a
completed TODO by adding move subroutine
aman-godara Sep 6, 2021
bfad13d
renamed delete to pop, created subroutine drop
aman-godara Sep 12, 2021
00de2b7
fixed an error in documentation of stringlist
aman-godara Sep 12, 2021
92d5f0d
created a new subroutine pop_positions
aman-godara Sep 12, 2021
1468fb6
added range functions for pop and drop
aman-godara Sep 12, 2021
937fac2
corrected a typo
aman-godara Sep 12, 2021
f60dd9e
corrected errors in documentation
aman-godara Sep 13, 2021
88a1abb
added range feature for get, added shift function
aman-godara Sep 13, 2021
ccd6dff
made move subroutine of stdlib_string_type module pure
aman-godara Sep 13, 2021
2e216c8
some minor changes
aman-godara Sep 15, 2021
5d24c0c
rename capture_popped to popped_strings
aman-godara Sep 17, 2021
48c94dc
renamed to popped_strings all over the function
aman-godara Sep 17, 2021
980c18a
removing redundant naming convention
aman-godara Sep 26, 2021
e935ea1
improved append operator's performance
aman-godara Sep 26, 2021
e34cce2
changed naming convention throughout the module
aman-godara Sep 26, 2021
2b3a5ef
some minor improvements
aman-godara Oct 15, 2021
29f9880
Minor refactoring
aman-godara Dec 25, 2021
207c1fb
Add strides feature to get function
aman-godara Dec 26, 2021
e6b6143
Add get_impl interface in the middle
aman-godara Dec 28, 2021
File filter

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Prev Previous commit
Next Next commit
added range feature for get, added shift function
  • Loading branch information
aman-godara committed Oct 15, 2021
commit 88a1abbf56cbe3de4b2cb386714d99733c8106f8
170 changes: 114 additions & 56 deletions src/stdlib_stringlist_type.f90
Original file line number Diff line number Diff line change
Expand Up @@ -84,18 +84,20 @@ module stdlib_stringlist_type
insert_before_chararray_int, &
insert_before_stringarray_int

procedure :: get_string_idx => get_string_idx_impl
generic, public :: get => get_string_idx
procedure :: get_idx => get_idx_impl
procedure :: get_range_idx => get_range_idx_impl
generic, public :: get => get_idx, &
get_range_idx

procedure :: pop_idx => pop_idx_impl
procedure :: pop_range_idx => pop_range_idx_impl
generic, public :: pop => pop_idx, &
pop_range_idx
procedure :: pop_idx => pop_idx_impl
procedure :: pop_range_idx => pop_range_idx_impl
generic, public :: pop => pop_idx, &
pop_range_idx

procedure :: drop_idx => drop_idx_impl
procedure :: drop_range_idx => drop_range_idx_impl
generic, public :: drop => drop_idx, &
drop_range_idx
procedure :: drop_idx => drop_idx_impl
procedure :: drop_range_idx => drop_range_idx_impl
generic, public :: drop => drop_idx, &
drop_range_idx

end type stringlist_type

Expand Down Expand Up @@ -453,6 +455,21 @@ 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), intent(in) :: 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 @@ -588,7 +605,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_empty_positions( list, idxn, positions )
subroutine insert_before_engine( list, idxn, positions )
!> Not a part of public API
class(stringlist_type), intent(inout) :: list
integer, intent(inout) :: idxn
Expand Down Expand Up @@ -618,7 +635,7 @@ subroutine insert_before_empty_positions( list, idxn, positions )

end if

end subroutine insert_before_empty_positions
end subroutine insert_before_engine

!> Version: experimental
!>
Expand All @@ -633,7 +650,7 @@ subroutine insert_before_string_int_impl( list, idxn, string )
integer :: work_idxn

work_idxn = idxn
call insert_before_empty_positions( list, work_idxn, 1 )
call insert_before_engine( list, work_idxn, 1 )

list%stringarray(work_idxn) = string

Expand Down Expand Up @@ -688,7 +705,7 @@ subroutine insert_before_chararray_int_impl( list, idxn, carray )
integer :: work_idxn, idxnew

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

do i = 1, size( carray )
idxnew = work_idxn + i - 1
Expand All @@ -711,7 +728,7 @@ subroutine insert_before_stringarray_int_impl( list, idxn, sarray )
integer :: work_idxn, idxnew

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

do i = 1, size( sarray )
idxnew = work_idxn + i - 1
Expand All @@ -722,68 +739,113 @@ end subroutine insert_before_stringarray_int_impl

! get:

!> Version: experimental
!>
!> Returns strings present at stringlist_indexes in interval ['first', 'last']
!> Stores requested strings in array 'capture_strings'
!> No return
subroutine get_engine( list, first, last, capture_strings )
class(stringlist_type) :: list
type(stringlist_index_type), intent(in) :: first, last
type(string_type), allocatable, intent(out) :: capture_strings(:)

integer :: from, to
integer :: i, inew

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
if ( from <= to ) then
pos = to - from + 1
allocate( capture_strings(pos) )

inew = 1
do i = from, to
capture_strings(inew) = list%stringarray(i)
inew = inew + 1
end do

else
allocate( capture_strings(0) )
end if

end subroutine get_engine

!> Version: experimental
!>
!> Returns the string present at stringlist_index 'idx' in stringlist 'list'
!> Returns string_type instance
pure function get_string_idx_impl( list, idx )
class(stringlist_type), intent(in) :: list
type(stringlist_index_type), intent(in) :: idx
type(string_type) :: get_string_idx_impl

integer :: idxn
pure function get_idx_impl( list, idx )
class(stringlist_type), intent(in) :: list
type(stringlist_index_type), intent(in) :: idx
type(string_type) :: get_idx_impl

idxn = list%to_current_idxn( idx )
type(string_type), allocatable :: capture_strings(:)

! if the index is out of bounds, returns a string_type instance equivalent to empty string
if ( 1 <= idxn .and. idxn <= list%len() ) then
get_string_idx_impl = list%stringarray(idxn)
call get_engine( list, idx, idx, capture_strings )

! if index 'idx' is out of bounds, returns an empty string
if ( size(capture_strings) == 1 ) then
call move( capture_strings(1), get_idx_impl )
end if

end function get_string_idx_impl
end function get_idx_impl

!> Version: experimental
!>
!> Returns strings present at stringlist_indexes in interval ['first', 'last']
!> Returns array of string_type instances
pure function get_range_idx_impl( list, first, last )
class(stringlist_type), intent(in) :: list
type(stringlist_index_type), intent(in) :: first, last

type(string_type), allocatable :: get_range_idx_impl(:)

call get_engine( list, first, last, get_range_idx_impl )

end function get_range_idx_impl

! pop & drop:

!> Version: experimental
!>
!> Removes strings present at indexes in interval ['first', 'last']
!> Returns captured popped strings
subroutine pop_engine( list, first, last, capture_popped)
!> Stores captured popped strings in array 'capture_popped'
!> No return
subroutine pop_drop_engine( list, first, last, capture_popped )
class(stringlist_type) :: list
type(stringlist_index_type), intent(in) :: first, last
type(string_type), allocatable, intent(out), optional :: capture_popped(:)

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

old_len = list%len()

firstn = max( list%to_current_idxn( first ), 1 )
lastn = min( list%to_current_idxn( last ), old_len )
firstn = list%to_current_idxn( first )
lastn = list%to_current_idxn( last )
from = max( firstn , 1 )
to = min( lastn , old_len )

! out of bounds indexes won't modify stringlist
if ( firstn <= lastn ) then
pos = lastn - firstn + 1
if ( from <= to ) then
pos = to - from + 1
new_len = old_len - pos

allocate( new_stringarray(new_len) )
do i = 1, firstn - 1
do i = 1, from - 1
call move( list%stringarray(i), new_stringarray(i) )
end do

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

inew = firstn
do i = lastn + 1, old_len
inew = from
do i = to + 1, old_len
call move( list%stringarray(i), new_stringarray(inew) )
inew = inew + 1
end do
Expand All @@ -795,9 +857,7 @@ subroutine pop_engine( list, first, last, capture_popped)
end if
end if

end subroutine pop_engine

! pop:
end subroutine pop_drop_engine

!> Version: experimental
!>
Expand All @@ -810,10 +870,10 @@ function pop_idx_impl( list, idx )

type(string_type), dimension(:), allocatable :: popped_strings

call pop_engine( list, idx, idx, popped_strings )
call pop_drop_engine( list, idx, idx, popped_strings )

if ( size(popped_strings) == 1 ) then
pop_idx_impl = popped_strings(1)
call move( pop_idx_impl, popped_strings(1) )
end if

end function pop_idx_impl
Expand All @@ -829,12 +889,10 @@ function pop_range_idx_impl( list, first, last )

type(string_type), dimension(:), allocatable :: pop_range_idx_impl

call pop_engine( list, first, last, pop_range_idx_impl )
call pop_drop_engine( list, first, last, pop_range_idx_impl )

end function pop_range_idx_impl

! drop:

!> Version: experimental
!>
!> Removes the string present at stringlist_index 'idx' in stringlist 'list'
Expand All @@ -843,7 +901,7 @@ subroutine drop_idx_impl( list, idx )
class(stringlist_type) :: list
type(stringlist_index_type), intent(in) :: idx

call pop_engine( list, idx, idx )
call pop_drop_engine( list, idx, idx )

end subroutine drop_idx_impl

Expand All @@ -852,11 +910,11 @@ 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)
subroutine drop_range_idx_impl( list, first, last )
class(stringlist_type) :: list
type(stringlist_index_type), intent(in) :: first, last

call pop_engine( list, first, last )
call pop_drop_engine( list, first, last )

end subroutine drop_range_idx_impl

Expand Down