@@ -59,7 +59,7 @@ module stdlib_stringlist
59
59
private
60
60
procedure :: copy = > create_copy
61
61
62
- procedure , public :: destroy = > destroy_list
62
+ procedure , public :: clear = > clear_list
63
63
64
64
procedure , public :: len = > length_list
65
65
@@ -88,13 +88,23 @@ module stdlib_stringlist
88
88
insert_before_stringlist_int, &
89
89
insert_before_chararray_int, &
90
90
insert_before_stringarray_int
91
- ! procedure :: get_string_int => get_string_int_impl
91
+
92
92
procedure :: get_string_idx = > get_string_idx_wrap
93
93
generic, public :: get = > get_string_idx
94
- ! get_string_int
95
94
96
95
end type stringlist_type
97
96
97
+ ! > Version: experimental
98
+ ! >
99
+ ! > Constructor for stringlist
100
+ ! > Returns an instance of type stringlist_type
101
+ ! > [Specifications](../page/specs/stdlib_stringlist.html#stringlist_type)
102
+ interface stringlist_type
103
+ module procedure new_stringlist
104
+ module procedure new_stringlist_carray
105
+ module procedure new_stringlist_sarray
106
+ end interface
107
+
98
108
! > Version: experimental
99
109
! >
100
110
! > Concatenates stringlist with the input entity
@@ -140,8 +150,48 @@ module stdlib_stringlist
140
150
141
151
contains
142
152
153
+ ! constructor for stringlist_type:
154
+
155
+ ! > Constructor with no argument
156
+ ! > Returns a new instance of type stringlist
157
+ pure function new_stringlist ()
158
+ type (stringlist_type) :: new_stringlist
159
+ type (string_type), dimension (0 ) :: sarray
160
+
161
+ new_stringlist = stringlist_type( 0 , sarray )
162
+
163
+ end function new_stringlist
164
+
165
+ ! > Constructor to convert chararray to stringlist
166
+ ! > Returns a new instance of type stringlist
167
+ pure function new_stringlist_carray ( carray )
168
+ character (len=* ), dimension (:), intent (in ) :: carray
169
+ type (stringlist_type) :: new_stringlist_carray
170
+ type (string_type), dimension ( size (carray) ) :: sarray
171
+ integer :: i
172
+
173
+ do i = 1 , size (carray)
174
+ sarray(i) = string_type( carray(i) )
175
+ end do
176
+
177
+ new_stringlist_carray = stringlist_type( sarray )
178
+
179
+ end function new_stringlist_carray
180
+
181
+ ! > Constructor to convert stringarray to stringlist
182
+ ! > Returns a new instance of type stringlist
183
+ pure function new_stringlist_sarray ( sarray )
184
+ type (string_type), dimension (:), intent (in ) :: sarray
185
+ type (stringlist_type) :: new_stringlist_sarray
186
+
187
+ new_stringlist_sarray = stringlist_type( size (sarray), sarray )
188
+
189
+ end function new_stringlist_sarray
190
+
191
+ ! constructor for stringlist_index_type:
192
+
143
193
! > Returns an instance of type 'stringlist_index_type' representing forward index 'idx'
144
- pure function forward_index (idx )
194
+ pure function forward_index ( idx )
145
195
integer , intent (in ) :: idx
146
196
type (stringlist_index_type) :: forward_index
147
197
@@ -150,14 +200,16 @@ pure function forward_index(idx)
150
200
end function forward_index
151
201
152
202
! > Returns an instance of type 'stringlist_index_type' representing backward index 'idx'
153
- pure function backward_index (idx )
203
+ pure function backward_index ( idx )
154
204
integer , intent (in ) :: idx
155
205
type (stringlist_index_type) :: backward_index
156
206
157
207
backward_index = stringlist_index_type( .false. , idx )
158
208
159
209
end function backward_index
160
210
211
+ ! copy
212
+
161
213
! > Returns a deep copy of the stringlist 'original'
162
214
pure function create_copy ( original )
163
215
class(stringlist_type), intent (in ) :: original
@@ -167,6 +219,8 @@ pure function create_copy( original )
167
219
168
220
end function create_copy
169
221
222
+ ! concatenation operator:
223
+
170
224
! > Appends character scalar 'string' to the stringlist 'list'
171
225
! > Returns a new stringlist
172
226
function append_char ( list , string )
@@ -273,6 +327,8 @@ function prepend_sarray( sarray, list )
273
327
274
328
end function prepend_sarray
275
329
330
+ ! equality operator:
331
+
276
332
! > Compares stringlist 'list' for equality with stringlist 'slist'
277
333
! > Returns a logical
278
334
pure logical function eq_stringlist( list, slist )
@@ -353,6 +409,8 @@ pure logical function eq_sarray_stringlist( sarray, list )
353
409
354
410
end function eq_sarray_stringlist
355
411
412
+ ! inequality operator:
413
+
356
414
! > Compares stringlist 'list' for inequality with stringlist 'slist'
357
415
! > Returns a logical
358
416
pure logical function ineq_stringlist( list, slist )
@@ -403,22 +461,21 @@ pure logical function ineq_sarray_stringlist( sarray, list )
403
461
404
462
end function ineq_sarray_stringlist
405
463
406
- ! destroy :
464
+ ! clear :
407
465
408
466
! > Version: experimental
409
467
! >
410
468
! > Resets stringlist 'list' to an empy stringlist of len 0
411
469
! > Modifies the input stringlist 'list'
412
- subroutine destroy_list ( list )
413
- ! > TODO: needs a better name?? like clear_list or reset_list
414
- class(stringlist_type), intent (out ) :: list
470
+ subroutine clear_list ( list )
471
+ class(stringlist_type), intent (inout ) :: list
415
472
416
473
list% size = 0
417
474
if ( allocated ( list% stringarray ) ) then
418
475
deallocate ( list% stringarray )
419
476
end if
420
477
421
- end subroutine destroy_list
478
+ end subroutine clear_list
422
479
423
480
! len:
424
481
0 commit comments