Skip to content

Commit

Permalink
made move subroutine of stdlib_string_type module pure
Browse files Browse the repository at this point in the history
  • Loading branch information
aman-godara committed Sep 13, 2021
1 parent bd703fb commit 4391972
Show file tree
Hide file tree
Showing 2 changed files with 10 additions and 11 deletions.
8 changes: 4 additions & 4 deletions src/stdlib_string_type.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -713,7 +713,7 @@ contains

!> Moves the allocated character scalar from 'from' to 'to'
!> No output
subroutine move_string_string(from, to)
pure subroutine move_string_string(from, to)
type(string_type), intent(inout) :: from
type(string_type), intent(out) :: to

Expand All @@ -723,7 +723,7 @@ contains

!> Moves the allocated character scalar from 'from' to 'to'
!> No output
subroutine move_string_char(from, to)
pure subroutine move_string_char(from, to)
type(string_type), intent(inout) :: from
character(len=:), intent(out), allocatable :: to

Expand All @@ -733,7 +733,7 @@ contains

!> Moves the allocated character scalar from 'from' to 'to'
!> No output
subroutine move_char_string(from, to)
pure subroutine move_char_string(from, to)
character(len=:), intent(inout), allocatable :: from
type(string_type), intent(out) :: to

Expand All @@ -743,7 +743,7 @@ contains

!> Moves the allocated character scalar from 'from' to 'to'
!> No output
subroutine move_char_char(from, to)
pure subroutine move_char_char(from, to)
character(len=:), intent(inout), allocatable :: from
character(len=:), intent(out), allocatable :: to

Expand Down
13 changes: 6 additions & 7 deletions src/stdlib_stringlist_type.f90
Original file line number Diff line number Diff line change
Expand Up @@ -464,7 +464,7 @@ pure function shift( idx, shift_by )
type(stringlist_index_type), intent(in) :: idx
integer, intent(in) :: shift_by

type(stringlist_index_type), intent(in) :: shift
type(stringlist_index_type) :: shift

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

Expand Down Expand Up @@ -607,7 +607,7 @@ end subroutine insert_at_stringarray_idx_wrap
!> Modifies the input stringlist 'list'
subroutine insert_before_engine( list, idxn, positions )
!> Not a part of public API
class(stringlist_type), intent(inout) :: list
type(stringlist_type), intent(inout) :: list
integer, intent(inout) :: idxn
integer, intent(in) :: positions

Expand Down Expand Up @@ -740,8 +740,8 @@ end subroutine insert_before_stringarray_int_impl
!> 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
pure subroutine get_engine( list, first, last, capture_strings )
type(stringlist_type), intent(in) :: list
type(stringlist_index_type), intent(in) :: first, last
type(string_type), allocatable, intent(out) :: capture_strings(:)

Expand All @@ -753,8 +753,7 @@ subroutine get_engine( list, first, last, capture_strings )

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

inew = 1
do i = from, to
Expand All @@ -775,8 +774,8 @@ end subroutine get_engine
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

type(string_type) :: get_idx_impl
type(string_type), allocatable :: capture_strings(:)

call get_engine( list, idx, idx, capture_strings )
Expand Down

0 comments on commit 4391972

Please sign in to comment.