@@ -280,8 +280,8 @@ pure integer function capacity( list )
280
280
type (stringlist_type), intent (in ) :: list
281
281
282
282
capacity = 0
283
- if ( allocated (list% stringarray) ) then
284
- capacity = size (list% stringarray)
283
+ if ( allocated ( list% stringarray ) ) then
284
+ capacity = size ( list% stringarray )
285
285
end if
286
286
287
287
end function capacity
@@ -304,38 +304,38 @@ end function to_idxn
304
304
! string The string in question
305
305
!
306
306
subroutine insert_char_idx_wrap ( list , idx , string )
307
- type (stringlist_type), intent (inout ) :: list
308
- type (stringlist_index_type), intent (in ) :: idx
309
- character (len=* ), intent (in ) :: string
307
+ type (stringlist_type), intent (inout ) :: list
308
+ type (stringlist_index_type), intent (in ) :: idx
309
+ character (len=* ), intent (in ) :: string
310
310
311
311
call list% insert( idx, string_type( string ) )
312
312
313
313
end subroutine insert_char_idx_wrap
314
314
315
315
subroutine insert_string_idx_wrap ( list , idx , string )
316
- type (stringlist_type), intent (inout ) :: list
317
- type (stringlist_index_type), intent (in ) :: idx
318
- type (type_string ), intent (in ) :: string
316
+ type (stringlist_type), intent (inout ) :: list
317
+ type (stringlist_index_type), intent (in ) :: idx
318
+ type (string_type ), intent (in ) :: string
319
319
320
- call list% insert( to_idxn(idx), string )
320
+ call list% insert( to_idxn( idx ), string )
321
321
322
322
end subroutine insert_string_idx_wrap
323
323
324
324
subroutine insert_stringlist_idx_wrap ( list , idx , slist )
325
- type (stringlist_type), intent (inout ) :: list
326
- type (stringlist_index_type), intent (in ) :: idx
327
- type (stringlist_type), intent (in ) :: slist
325
+ type (stringlist_type), intent (inout ) :: list
326
+ type (stringlist_index_type), intent (in ) :: idx
327
+ type (stringlist_type), intent (in ) :: slist
328
328
329
- call list% insert( to_idxn(idx), slist )
329
+ call list% insert( to_idxn( idx ), slist )
330
330
331
331
end subroutine insert_stringlist_idx_wrap
332
332
333
333
subroutine insert_stringarray_idx_wrap ( list , idx , sarray )
334
- type (stringlist_type), intent (inout ) :: list
335
- type (stringlist_index_type), intent (in ) :: idx
336
- character (len=* ), dimension (:), intent (in ) :: sarray
334
+ type (stringlist_type), intent (inout ) :: list
335
+ type (stringlist_index_type), intent (in ) :: idx
336
+ character (len=* ), dimension (:), intent (in ) :: sarray
337
337
338
- call list% insert( to_idxn(idx), sarray )
338
+ call list% insert( to_idxn( idx ), sarray )
339
339
340
340
end subroutine insert_stringarray_idx_wrap
341
341
@@ -348,13 +348,13 @@ end subroutine insert_stringarray_idx_wrap
348
348
! number Number of positions
349
349
!
350
350
subroutine insert_empty_positions ( list , idxn , number )
351
- type (stringlist_type), intent (inout ) :: list
352
- integer , intent (inout ) :: idxn
353
- integer , intent (inout ) :: number
351
+ type (stringlist_type), intent (inout ) :: list
352
+ integer , intent (inout ) :: idxn
353
+ integer , intent (inout ) :: number
354
354
355
- integer :: i, inew
356
- integer :: new_size, old_size
357
- type (string_type), dimension (:), allocatable :: new_stringarray
355
+ integer :: i, inew
356
+ integer :: new_size, old_size
357
+ type (string_type), dimension (:), allocatable :: new_stringarray
358
358
359
359
if (number > 0 ) then
360
360
@@ -395,23 +395,23 @@ end subroutine insert_empty_positions
395
395
! Insert a new string into the list - specific implementation
396
396
!
397
397
subroutine insert_char_int_impl ( list , idx , string )
398
- type (stringlist_type), intent (inout ) :: list
399
- integer , intent (in ) :: idx
400
- character (len=* ), intent (in ) :: string
398
+ type (stringlist_type), intent (inout ) :: list
399
+ integer , intent (in ) :: idx
400
+ character (len=* ), intent (in ) :: string
401
401
402
- call insert( list, idx, string_type(string) )
402
+ call insert( list, idx, string_type( string ) )
403
403
404
404
end subroutine insert_char_int_impl
405
405
406
406
! insert_string_int_impl --
407
407
! Insert a new string into the list - specific implementation
408
408
!
409
409
subroutine insert_string_int_impl ( list , idx , string )
410
- type (stringlist_type), intent (inout ) :: list
411
- integer , intent (in ) :: idx
412
- type (string_type), intent (in ) :: string
410
+ type (stringlist_type), intent (inout ) :: list
411
+ integer , intent (in ) :: idx
412
+ type (string_type), intent (in ) :: string
413
413
414
- integer :: idxn
414
+ integer :: idxn
415
415
416
416
idxn = idx
417
417
call insert_empty_positions( list, idxn, 1 )
@@ -424,17 +424,17 @@ end subroutine insert_string_int_impl
424
424
! Insert a list of strings into the list - specific implementation
425
425
!
426
426
subroutine insert_stringlist_int_impl ( list , idx , slist )
427
- type (stringlist_type), intent (inout ) :: list
428
- integer , intent (in ) :: idx
429
- type (stringlist_type), intent (in ) :: slist
427
+ type (stringlist_type), intent (inout ) :: list
428
+ integer , intent (in ) :: idx
429
+ type (stringlist_type), intent (in ) :: slist
430
430
431
- integer :: i
432
- integer :: idxn, idxnew
431
+ integer :: i
432
+ integer :: idxn, idxnew
433
433
434
434
idxn = idx
435
- call insert_empty_positions( list, idxn, len (list ) )
435
+ call insert_empty_positions( list, idxn, len ( slist ) )
436
436
437
- do i = 1 , len (list )
437
+ do i = 1 , len ( slist )
438
438
idxnew = idxn + i - 1
439
439
list% stringarray(idxnew) = slist% stringarray(i)
440
440
end do
@@ -453,11 +453,11 @@ subroutine insert_chararray_int_impl( list, idx, sarray )
453
453
integer :: idxn, idxnew
454
454
455
455
idxn = idx
456
- call insert_empty_positions( list, idxn, size (sarray) )
456
+ call insert_empty_positions( list, idxn, size ( sarray ) )
457
457
458
- do i = 1 , size (sarray)
458
+ do i = 1 , size ( sarray )
459
459
idxnew = idxn + i - 1
460
- list% stringarray(idxnew) = string_type(sarray(i))
460
+ list% stringarray(idxnew) = string_type( sarray(i) )
461
461
end do
462
462
463
463
end subroutine insert_chararray_int_impl
@@ -474,9 +474,9 @@ subroutine insert_stringarray_int_impl( list, idx, sarray )
474
474
integer :: idxn, idxnew
475
475
476
476
idxn = idx
477
- call insert_empty_positions( list, idxn, size (sarray) )
477
+ call insert_empty_positions( list, idxn, size ( sarray ) )
478
478
479
- do i = 1 , size (sarray)
479
+ do i = 1 , size ( sarray )
480
480
idxnew = idxn + i - 1
481
481
list% stringarray(idxnew) = sarray(i)
482
482
end do
@@ -499,9 +499,9 @@ pure function get_string_idx_wrap( list, idx )
499
499
500
500
end function get_string_idx_wrap
501
501
502
- pure function get_string_int_impl ( list , idx )
502
+ pure function get_string_int_impl ( list , idxn )
503
503
type (stringlist_type), intent (in ) :: list
504
- integer , intent (in ) :: idx
504
+ integer , intent (in ) :: idxn
505
505
type (string_type) :: get_string_int_impl
506
506
507
507
integer :: idxnew
@@ -510,7 +510,7 @@ pure function get_string_int_impl( list, idx )
510
510
! Examine the actual index:
511
511
! - if the index is out of bounds, return a string_type equivalent to empty string
512
512
!
513
- if ( 1 <= idx .or. idx <= len (list) ) then
513
+ if ( 1 <= idxn .and. idxn <= len ( list ) ) then
514
514
get_string_int_impl = list% stringarray(idx)
515
515
end if
516
516
0 commit comments