Skip to content

Commit b577a54

Browse files
committed
added first test case
1 parent 3534150 commit b577a54

File tree

5 files changed

+41
-303
lines changed

5 files changed

+41
-303
lines changed

src/stdlib_stringlist.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@
1515
! throughout the PR
1616
!
1717
module stdlib_stringlist
18-
use stdlib_string_type, only: string_type, char, operator(/=) !, move
18+
use stdlib_string_type, only: string_type, operator(/=) !, move
1919
use stdlib_math, only: clip
2020
! use stdlib_optval, only: optval
2121
implicit none
@@ -304,7 +304,7 @@ pure logical function eq_stringlist_carray( list, carray )
304304
if ( list%len() == size( carray ) ) then
305305
eq_stringlist_carray = .true.
306306
do i = 1, list%len()
307-
if ( char( list%stringarray(i) ) /= carray(i) ) then
307+
if ( list%stringarray(i) /= carray(i) ) then
308308
eq_stringlist_carray = .false.
309309
exit
310310
end if

src/tests/stringlist/test_delete.f90

Lines changed: 0 additions & 57 deletions
This file was deleted.

src/tests/stringlist/test_find.f90

Lines changed: 0 additions & 72 deletions
This file was deleted.
Lines changed: 39 additions & 84 deletions
Original file line numberDiff line numberDiff line change
@@ -1,97 +1,52 @@
1-
! test_insert.f90 --
2-
! Test the insertion routine
3-
!
4-
program test_insertion
1+
! SPDX-Identifier: MIT
2+
module test_insert_at
3+
use stdlib_error, only: check
4+
use stdlib_string_type, only: string_type, char, operator(//), operator(==)
55
use stdlib_stringlist, only: stringlist_type, stringlist_index_type, fidx, bidx, list_head, &
6-
& list_tail, operator(//), operator(==)
7-
use stdlib_string_type, only: string_type, char
6+
& list_tail, operator(==), operator(/=)
7+
use stdlib_ascii, only: to_string
8+
implicit none
89

9-
type(stringlist_type) :: list, second_list
10-
character(len=10), dimension(3) :: sarray
11-
12-
13-
call list%insert_at( fidx(1), "C" )
14-
call list%insert_at( fidx(1), "B" )
15-
call list%insert_at( fidx(1), "A" )
16-
17-
write(*,*) 'Expected: A, B, C (3)'
18-
call print_list( list )
19-
20-
call list%insert_at( list_tail, "D" )
21-
22-
write(*,*) 'Expected: A, B, C, D (4)'
23-
call print_list( list )
24-
25-
call list%insert_at( fidx(1), "X" )
26-
27-
write(*,*) 'Expected: X, A, B, C, D (5)'
28-
call print_list( list )
29-
30-
call list%insert_at( bidx(2), "Y" )
31-
32-
write(*,*) 'Expected: X, A, B, C, Y, D (6)'
33-
call print_list( list )
34-
35-
call list%insert_at( list_tail, "Z" )
36-
37-
write(*,*) 'Expected: X, A, B, Y, C, D, Z (7)'
38-
call print_list( list )
39-
40-
!
41-
! Try inserting a second list
42-
!
43-
call renew_list( list )
44-
45-
call second_list%insert_at( fidx(1), "SecondA" )
46-
call second_list%insert_at( fidx(2), "SecondB" )
47-
48-
call list%insert_at( fidx(2), second_list )
49-
call print_list( list )
50-
51-
call renew_list( list )
52-
53-
call list%insert_at( list_tail, second_list )
54-
call print_list( list )
55-
56-
!
57-
! Try inserting an array
58-
!
59-
call renew_list( list )
10+
contains
6011

61-
sarray(1) = "ThirdA"
62-
sarray(2) = "ThirdB"
63-
sarray(3) = "ThirdC"
12+
subroutine test_insert_at_1
13+
type(stringlist_type) :: first_list
14+
integer :: i, current_length
15+
character(len=:), allocatable :: string
6416

65-
call list%insert_at( list_head, sarray )
66-
call print_list( list )
17+
call check( first_list%to_current_idxn( list_tail ) == 0, "test_insert_at_1: list_tail == 0")
18+
call check( first_list%to_current_idxn( list_head ) == 1, "test_insert_at_1: list_head == 1")
6719

68-
call renew_list( list )
20+
current_length = 0
21+
do i = -5, 1
22+
string = to_string( i )
23+
call first_list%insert_at( fidx(i), string )
24+
current_length = current_length + 1
6925

70-
call list%insert_at( fidx(2), sarray )
71-
call print_list( list )
26+
call check( first_list%get( fidx(1) ) == string, "test_insert_at_1: get check failed &
27+
& for forward index " // string )
28+
call check( first_list%get( list_head ) == string, "test_insert_at_1: get list_head check &
29+
& failed for " // string )
30+
call check( first_list%get( bidx(current_length) ) == string, "test_insert_at_1: get &
31+
& list_head check failed for backward index " // string )
32+
call check( first_list%get( list_tail ) == to_string(-5), "test_insert_at_1: get list_tail &
33+
& check failed for " // string )
34+
call check( first_list%to_current_idxn( list_head ) == 1, "")
35+
call check( first_list%to_current_idxn( list_tail ) == current_length, "" )
36+
call check( first_list%len() == current_length, "test_insert_at_1: length check &
37+
& failed for " // to_string( current_length ) )
7238

73-
contains
74-
subroutine renew_list( list )
75-
type(stringlist_type), intent(inout) :: list
39+
end do
7640

77-
call list%destroy()
78-
call list%insert_at( fidx(1), "A" )
79-
call list%insert_at( fidx(2), "B" )
80-
call list%insert_at( fidx(3), "C" )
81-
write(*,*) '===>', list == ["A", "B", "C"], '<==='
82-
write(*,*) '===>', ["A", "B", "C"] == list, '<==='
41+
end subroutine test_insert_at_1
8342

84-
end subroutine renew_list
43+
end module test_insert_at
8544

86-
subroutine print_list( list )
87-
type(stringlist_type), intent(in) :: list
88-
integer :: i
8945

90-
write(*,*) list%len()
46+
program tester
47+
use test_insert_at
48+
implicit none
9149

92-
do i = 1, list%len()
93-
write(*,*) '>', char( list%get( fidx(i) ) ), '<'
94-
enddo
95-
end subroutine print_list
50+
call test_insert_at_1
9651

97-
end program test_insertion
52+
end program tester

src/tests/stringlist/test_replace_append.f90

Lines changed: 0 additions & 88 deletions
This file was deleted.

0 commit comments

Comments
 (0)