Skip to content

Commit 3534150

Browse files
committed
added equality and inequality operators, added support for chararray in append oeprator
1 parent e0e0a96 commit 3534150

File tree

2 files changed

+207
-22
lines changed

2 files changed

+207
-22
lines changed

src/stdlib_stringlist.f90

Lines changed: 199 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -15,13 +15,13 @@
1515
! throughout the PR
1616
!
1717
module stdlib_stringlist
18-
use stdlib_string_type, only: string_type !, move
18+
use stdlib_string_type, only: string_type, char, operator(/=) !, move
1919
use stdlib_math, only: clip
2020
! use stdlib_optval, only: optval
2121
implicit none
2222
private
2323

24-
public :: stringlist_type, operator(//)
24+
public :: stringlist_type, operator(//), operator(==), operator(/=)
2525
public :: list_head, list_tail, fidx, bidx, stringlist_index_type
2626

2727
type stringlist_index_type
@@ -106,8 +106,36 @@ module stdlib_stringlist
106106
module procedure prepend_char
107107
module procedure prepend_string
108108
module procedure append_stringlist
109-
module procedure append_stringarray
110-
module procedure prepend_stringarray
109+
module procedure append_carray
110+
module procedure append_sarray
111+
module procedure prepend_carray
112+
module procedure prepend_sarray
113+
end interface
114+
115+
!> Version: experimental
116+
!>
117+
!> Compares stringlist for equality with the input entity
118+
!> Returns a logical
119+
!> [Specifications](../page/specs/stdlib_stringlist.html#equality-operator)
120+
interface operator(==)
121+
module procedure eq_stringlist
122+
module procedure eq_stringlist_carray
123+
module procedure eq_stringlist_sarray
124+
module procedure eq_carray_stringlist
125+
module procedure eq_sarray_stringlist
126+
end interface
127+
128+
!> Version: experimental
129+
!>
130+
!> Compares stringlist for inequality with the input entity
131+
!> Returns a logical
132+
!> [Specifications](../page/specs/stdlib_stringlist.html#inequality-operator)
133+
interface operator(/=)
134+
module procedure ineq_stringlist
135+
module procedure ineq_stringlist_carray
136+
module procedure ineq_stringlist_sarray
137+
module procedure ineq_carray_stringlist
138+
module procedure ineq_sarray_stringlist
111139
end interface
112140

113141
contains
@@ -197,29 +225,183 @@ function append_stringlist( list, slist )
197225

198226
end function append_stringlist
199227

228+
!> Appends chararray 'carray' to the stringlist 'list'
229+
!> Returns a new stringlist
230+
function append_carray( list, carray )
231+
type(stringlist_type), intent(in) :: list
232+
character(len=*), dimension(:), intent(in) :: carray
233+
type(stringlist_type) :: append_carray
234+
235+
append_carray = list%copy()
236+
call append_carray%insert_at( list_tail, carray )
237+
238+
end function append_carray
239+
200240
!> Appends stringarray 'sarray' to the stringlist 'list'
201241
!> Returns a new stringlist
202-
function append_stringarray( list, sarray )
242+
function append_sarray( list, sarray )
243+
type(stringlist_type), intent(in) :: list
244+
type(string_type), dimension(:), intent(in) :: sarray
245+
type(stringlist_type) :: append_sarray
246+
247+
append_sarray = list%copy()
248+
call append_sarray%insert_at( list_tail, sarray )
249+
250+
end function append_sarray
251+
252+
!> Prepends chararray 'carray' to the stringlist 'list'
253+
!> Returns a new stringlist
254+
function prepend_carray( carray, list )
255+
character(len=*), dimension(:), intent(in) :: carray
203256
type(stringlist_type), intent(in) :: list
204-
character(len=*), dimension(:), intent(in) :: sarray
205-
type(stringlist_type) :: append_stringarray
257+
type(stringlist_type) :: prepend_carray
206258

207-
append_stringarray = list%copy()
208-
call append_stringarray%insert_at( list_tail, sarray )
259+
prepend_carray = list%copy()
260+
call prepend_carray%insert_at( list_head, carray )
209261

210-
end function append_stringarray
262+
end function prepend_carray
211263

212264
!> Prepends stringarray 'sarray' to the stringlist 'list'
213265
!> Returns a new stringlist
214-
function prepend_stringarray( sarray, list )
215-
character(len=*), dimension(:), intent(in) :: sarray
216-
type(stringlist_type), intent(in) :: list
217-
type(stringlist_type) :: prepend_stringarray
266+
function prepend_sarray( sarray, list )
267+
type(string_type), dimension(:), intent(in) :: sarray
268+
type(stringlist_type), intent(in) :: list
269+
type(stringlist_type) :: prepend_sarray
270+
271+
prepend_sarray = list%copy()
272+
call prepend_sarray%insert_at( list_head, sarray )
273+
274+
end function prepend_sarray
275+
276+
!> Compares stringlist 'list' for equality with stringlist 'slist'
277+
!> Returns a logical
278+
pure logical function eq_stringlist( list, slist )
279+
type(stringlist_type), intent(in) :: list
280+
type(stringlist_type), intent(in) :: slist
281+
integer :: i
282+
283+
eq_stringlist = .false.
284+
if ( list%len() == slist%len() ) then
285+
eq_stringlist = .true.
286+
do i = 1, list%len()
287+
if ( list%stringarray(i) /= slist%stringarray(i) ) then
288+
eq_stringlist = .false.
289+
exit
290+
end if
291+
end do
292+
end if
293+
294+
end function eq_stringlist
295+
296+
!> Compares stringlist 'list' for equality with chararray 'carray'
297+
!> Returns a logical
298+
pure logical function eq_stringlist_carray( list, carray )
299+
type(stringlist_type), intent(in) :: list
300+
character(len=*), dimension(:), intent(in) :: carray
301+
integer :: i
302+
303+
eq_stringlist_carray = .false.
304+
if ( list%len() == size( carray ) ) then
305+
eq_stringlist_carray = .true.
306+
do i = 1, list%len()
307+
if ( char( list%stringarray(i) ) /= carray(i) ) then
308+
eq_stringlist_carray = .false.
309+
exit
310+
end if
311+
end do
312+
end if
313+
314+
end function eq_stringlist_carray
315+
316+
!> Compares stringlist 'list' for equality with stringarray 'sarray'
317+
!> Returns a logical
318+
pure logical function eq_stringlist_sarray( list, sarray )
319+
type(stringlist_type), intent(in) :: list
320+
type(string_type), dimension(:), intent(in) :: sarray
321+
integer :: i
322+
323+
eq_stringlist_sarray = .false.
324+
if ( list%len() == size( sarray ) ) then
325+
eq_stringlist_sarray = .true.
326+
do i = 1, list%len()
327+
if ( list%stringarray(i) /= sarray(i) ) then
328+
eq_stringlist_sarray = .false.
329+
exit
330+
end if
331+
end do
332+
end if
333+
334+
end function eq_stringlist_sarray
335+
336+
!> Compares stringlist 'list' for equality with chararray 'carray'
337+
!> Returns a logical
338+
pure logical function eq_carray_stringlist( carray, list )
339+
character(len=*), dimension(:), intent(in) :: carray
340+
type(stringlist_type), intent(in) :: list
341+
342+
eq_carray_stringlist = ( list == carray )
343+
344+
end function eq_carray_stringlist
345+
346+
!> Compares stringlist 'list' for equality with stringarray 'sarray'
347+
!> Returns a logical
348+
pure logical function eq_sarray_stringlist( sarray, list )
349+
type(string_type), dimension(:), intent(in) :: sarray
350+
type(stringlist_type), intent(in) :: list
351+
352+
eq_sarray_stringlist = ( list == sarray )
353+
354+
end function eq_sarray_stringlist
355+
356+
!> Compares stringlist 'list' for inequality with stringlist 'slist'
357+
!> Returns a logical
358+
pure logical function ineq_stringlist( list, slist )
359+
type(stringlist_type), intent(in) :: list
360+
type(stringlist_type), intent(in) :: slist
361+
362+
ineq_stringlist = .not.( list == slist )
363+
364+
end function ineq_stringlist
365+
366+
!> Compares stringlist 'list' for inequality with chararray 'carray'
367+
!> Returns a logical
368+
pure logical function ineq_stringlist_carray( list, carray )
369+
type(stringlist_type), intent(in) :: list
370+
character(len=*), dimension(:), intent(in) :: carray
371+
372+
ineq_stringlist_carray = .not.( list == carray )
373+
374+
end function ineq_stringlist_carray
375+
376+
!> Compares stringlist 'list' for inequality with stringarray 'sarray'
377+
!> Returns a logical
378+
pure logical function ineq_stringlist_sarray( list, sarray )
379+
type(stringlist_type), intent(in) :: list
380+
type(string_type), dimension(:), intent(in) :: sarray
381+
382+
ineq_stringlist_sarray = .not.( list == sarray )
383+
384+
end function ineq_stringlist_sarray
385+
386+
!> Compares stringlist 'list' for inequality with chararray 'carray'
387+
!> Returns a logical
388+
pure logical function ineq_carray_stringlist( carray, list )
389+
character(len=*), dimension(:), intent(in) :: carray
390+
type(stringlist_type), intent(in) :: list
391+
392+
ineq_carray_stringlist = .not.( carray == list)
393+
394+
end function ineq_carray_stringlist
395+
396+
!> Compares stringlist 'list' for inequality with stringarray 'sarray'
397+
!> Returns a logical
398+
pure logical function ineq_sarray_stringlist( sarray, list )
399+
type(string_type), dimension(:), intent(in) :: sarray
400+
type(stringlist_type), intent(in) :: list
218401

219-
prepend_stringarray = list%copy()
220-
call prepend_stringarray%insert_at( list_head, sarray )
402+
ineq_sarray_stringlist = .not.( sarray == list )
221403

222-
end function prepend_stringarray
404+
end function ineq_sarray_stringlist
223405

224406
! destroy:
225407

src/tests/stringlist/test_insert_at.f90

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -2,8 +2,8 @@
22
! Test the insertion routine
33
!
44
program test_insertion
5-
use stdlib_stringlist, only: stringlist_type, fidx, bidx, stringlist_index_type, &
6-
& list_head, list_tail
5+
use stdlib_stringlist, only: stringlist_type, stringlist_index_type, fidx, bidx, list_head, &
6+
& list_tail, operator(//), operator(==)
77
use stdlib_string_type, only: string_type, char
88

99
type(stringlist_type) :: list, second_list
@@ -17,19 +17,19 @@ program test_insertion
1717
write(*,*) 'Expected: A, B, C (3)'
1818
call print_list( list )
1919

20-
call list%insert_at( fidx(1), "D" )
20+
call list%insert_at( list_tail, "D" )
2121

2222
write(*,*) 'Expected: A, B, C, D (4)'
2323
call print_list( list )
2424

25-
call list%insert_at( bidx(1), "X" )
25+
call list%insert_at( fidx(1), "X" )
2626

2727
write(*,*) 'Expected: X, A, B, C, D (5)'
2828
call print_list( list )
2929

3030
call list%insert_at( bidx(2), "Y" )
3131

32-
write(*,*) 'Expected: X, A, B, Y, C, D (6)'
32+
write(*,*) 'Expected: X, A, B, C, Y, D (6)'
3333
call print_list( list )
3434

3535
call list%insert_at( list_tail, "Z" )
@@ -78,6 +78,9 @@ subroutine renew_list( list )
7878
call list%insert_at( fidx(1), "A" )
7979
call list%insert_at( fidx(2), "B" )
8080
call list%insert_at( fidx(3), "C" )
81+
write(*,*) '===>', list == ["A", "B", "C"], '<==='
82+
write(*,*) '===>', ["A", "B", "C"] == list, '<==='
83+
8184
end subroutine renew_list
8285

8386
subroutine print_list( list )

0 commit comments

Comments
 (0)