@@ -383,113 +383,130 @@ subroutine resize_string(list, n)
383
383
384
384
end subroutine resize_string
385
385
386
- pure function join (str ,sep ,trm ,left ,right ) result (string)
387
-
388
- ! > M_strings::join(3f): append an array of character variables with specified separator into a single CHARACTER variable
389
- ! >
390
- ! >##NAME
391
- ! > join(3f) - [M_strings:EDITING] append CHARACTER variable array into
392
- ! > a single CHARACTER variable with specified separator
393
- ! > (LICENSE:PD)
394
- ! >
395
- ! >##SYNOPSIS
396
- ! >
397
- ! > pure function join(str,sep,trm,left,right) result (string)
398
- ! >
399
- ! > character(len=*),intent(in) :: str(:)
400
- ! > character(len=*),intent(in),optional :: sep
401
- ! > logical,intent(in),optional :: trm
402
- ! > character(len=*),intent(in),optional :: right
403
- ! > character(len=*),intent(in),optional :: left
404
- ! > character(len=:),allocatable :: string
405
- ! >
406
- ! >##DESCRIPTION
407
- ! > JOIN(3f) appends the elements of a CHARACTER array into a single
408
- ! > CHARACTER variable, with elements 1 to N joined from left to right.
409
- ! > By default each element is trimmed of trailing spaces and the
410
- ! > default separator is a null string.
411
- ! >
412
- ! >##OPTIONS
413
- ! > STR(:) array of CHARACTER variables to be joined
414
- ! > SEP separator string to place between each variable. defaults
415
- ! > to a null string.
416
- ! > LEFT string to place at left of each element
417
- ! > RIGHT string to place at right of each element
418
- ! > TRM option to trim each element of STR of trailing
419
- ! > spaces. Defaults to .TRUE.
420
- ! >
421
- ! >##RESULT
422
- ! > STRING CHARACTER variable composed of all of the elements of STR()
423
- ! > appended together with the optional separator SEP placed
424
- ! > between the elements and optional left and right elements.
425
- ! >
426
- ! >##EXAMPLE
386
+ pure function join (str ,sep ,trm ,left ,right ,start ,end ) result (string)
427
387
! >
428
- ! > Sample program:
429
- ! >
430
- ! > program demo_join
431
- ! > use M_strings, only: join
432
- ! > implicit none
433
- ! > character(len=:),allocatable :: s(:)
434
- ! > character(len=:),allocatable :: out
435
- ! > integer :: i
436
- ! > s=[character(len=10) :: 'United',' we',' stand,', &
437
- ! > & ' divided',' we fall.']
438
- ! > out=join(s)
439
- ! > write(*,'(a)') out
440
- ! > write(*,'(a)') join(s,trm=.false.)
441
- ! > write(*,'(a)') (join(s,trm=.false.,sep='|'),i=1,3)
442
- ! > write(*,'(a)') join(s,sep='<>')
443
- ! > write(*,'(a)') join(s,sep=';',left='[',right=']')
444
- ! > write(*,'(a)') join(s,left='[',right=']')
445
- ! > write(*,'(a)') join(s,left='>>')
446
- ! > end program demo_join
447
- ! >
448
- ! > Expected output:
449
- ! >
450
- ! > United we stand, divided we fall.
451
- ! > United we stand, divided we fall.
452
- ! > United | we | stand, | divided | we fall. |
453
- ! > United | we | stand, | divided | we fall. |
454
- ! > United | we | stand, | divided | we fall. |
455
- ! > United<> we<> stand,<> divided<> we fall.<>
456
- ! > [United];[ we];[ stand,];[ divided];[ we fall.];
457
- ! > [United][ we][ stand,][ divided][ we fall.]
458
- ! > >>United>> we>> stand,>> divided>> we fall.
459
- ! >
460
- ! >##AUTHOR
461
- ! > John S. Urban
462
- ! >
463
- ! >##LICENSE
464
- ! > Public Domain
465
-
466
- character (len=* ),intent (in ) :: str(:)
467
- character (len=* ),intent (in ),optional :: sep, right, left
468
- logical ,intent (in ),optional :: trm
469
- character (len= :),allocatable :: string
470
- integer :: i
471
- logical :: trm_local
472
- character (len= :),allocatable :: sep_local, left_local, right_local
388
+ ! !##NAME
389
+ ! ! join(3f) - [fpm_strings:EDITING] append CHARACTER variable array into
390
+ ! ! a single CHARACTER variable with specified separator
391
+ ! ! (LICENSE:PD)
392
+ ! !
393
+ ! !##SYNOPSIS
394
+ ! !
395
+ ! ! pure function join(str,sep,trm,left,right,start,end) result (string)
396
+ ! !
397
+ ! ! character(len=*),intent(in) :: str(:)
398
+ ! ! character(len=*),intent(in),optional :: sep
399
+ ! ! logical,intent(in),optional :: trm
400
+ ! ! character(len=*),intent(in),optional :: right
401
+ ! ! character(len=*),intent(in),optional :: left
402
+ ! ! character(len=*),intent(in),optional :: start
403
+ ! ! character(len=*),intent(in),optional :: end
404
+ ! ! character(len=:),allocatable :: string
405
+ ! !
406
+ ! !##DESCRIPTION
407
+ ! ! JOIN(3f) appends the elements of a CHARACTER array into a single
408
+ ! ! CHARACTER variable, with elements 1 to N joined from left to right.
409
+ ! ! By default each element is trimmed of trailing spaces and the
410
+ ! ! default separator is a null string.
411
+ ! !
412
+ ! !##OPTIONS
413
+ ! ! STR(:) array of CHARACTER variables to be joined
414
+ ! ! SEP separator string to place between each variable. defaults
415
+ ! ! to a null string.
416
+ ! ! LEFT string to place at left of each element
417
+ ! ! RIGHT string to place at right of each element
418
+ ! ! START prefix string
419
+ ! ! END suffix string
420
+ ! ! TRM option to trim each element of STR of trailing
421
+ ! ! spaces. Defaults to .TRUE.
422
+ ! !
423
+ ! !##RESULT
424
+ ! ! STRING CHARACTER variable composed of all of the elements of STR()
425
+ ! ! appended together with the optional separator SEP placed
426
+ ! ! between the elements.
427
+ ! !
428
+ ! !##EXAMPLE
429
+ ! !
430
+ ! ! Sample program:
431
+ ! !
432
+ ! ! program demo_join
433
+ ! ! use fpm_strings, only: join
434
+ ! ! implicit none
435
+ ! ! character(len=:),allocatable :: s(:)
436
+ ! ! character(len=:),allocatable :: out
437
+ ! ! integer :: i
438
+ ! ! s=[character(len=10) :: 'United',' we',' stand,', &
439
+ ! ! & ' divided',' we fall.']
440
+ ! ! out=join(s)
441
+ ! ! write(*,'(a)') out
442
+ ! ! write(*,'(a)') join(s,trm=.false.)
443
+ ! ! write(*,'(a)') (join(s,trm=.false.,sep='|'),i=1,3)
444
+ ! ! write(*,'(a)') join(s,sep='<>')
445
+ ! ! write(*,'(a)') join(s,sep=';',left='[',right=']')
446
+ ! ! write(*,'(a)') join(s,left='[',right=']')
447
+ ! ! write(*,'(a)') join(s,left='>>')
448
+ ! ! end program demo_join
449
+ ! !
450
+ ! ! Expected output:
451
+ ! !
452
+ ! ! United we stand, divided we fall.
453
+ ! ! United we stand, divided we fall.
454
+ ! ! United | we | stand, | divided | we fall.
455
+ ! ! United | we | stand, | divided | we fall.
456
+ ! ! United | we | stand, | divided | we fall.
457
+ ! ! United<> we<> stand,<> divided<> we fall.
458
+ ! ! [United];[ we];[ stand,];[ divided];[ we fall.]
459
+ ! ! [United][ we][ stand,][ divided][ we fall.]
460
+ ! ! >>United>> we>> stand,>> divided>> we fall.
461
+ ! !
462
+ ! !##AUTHOR
463
+ ! ! John S. Urban
464
+ ! !
465
+ ! !##LICENSE
466
+ ! ! Public Domain
467
+
468
+ ! @(#)join(3f): append an array of character variables with specified separator into a single CHARACTER variable
469
+
470
+ character (len=* ),intent (in ) :: str(:)
471
+ character (len=* ),intent (in ),optional :: sep
472
+ character (len=* ),intent (in ),optional :: right
473
+ character (len=* ),intent (in ),optional :: left
474
+ character (len=* ),intent (in ),optional :: start
475
+ character (len=* ),intent (in ),optional :: end
476
+ logical ,intent (in ),optional :: trm
477
+ character (len= :),allocatable :: string
478
+ integer :: i
479
+ logical :: trm_local
480
+ character (len= :),allocatable :: sep_local
481
+ character (len= :),allocatable :: left_local
482
+ character (len= :),allocatable :: right_local
473
483
474
484
if (present (sep))then ; sep_local= sep ; else ; sep_local= ' ' ; endif
475
485
if (present (trm))then ; trm_local= trm ; else ; trm_local= .true. ; endif
476
486
if (present (left))then ; left_local= left ; else ; left_local= ' ' ; endif
477
487
if (present (right))then ; right_local= right ; else ; right_local= ' ' ; endif
478
488
479
489
string= ' '
480
- do i = 1 ,size (str)
490
+ do i = 1 ,size (str)- 1
481
491
if (trm_local)then
482
492
string= string// left_local// trim (str(i))// right_local// sep_local
483
493
else
484
494
string= string// left_local// str(i)// right_local// sep_local
485
495
endif
486
496
enddo
497
+ if (trm_local)then
498
+ string= string// left_local// trim (str(i))// right_local
499
+ else
500
+ string= string// left_local// str(i)// right_local
501
+ endif
502
+ if (present (start))string= start// string
503
+ if (present (end))string= string// end
487
504
end function join
488
505
489
506
function glob (tame ,wild )
490
507
! >
491
508
! !##NAME
492
- ! ! glob(3f) - [M_strings :COMPARE] compare given string for match to
509
+ ! ! glob(3f) - [fpm_strings :COMPARE] compare given string for match to
493
510
! ! pattern which may contain wildcard characters
494
511
! ! (LICENSE:PD)
495
512
! !
@@ -687,7 +704,7 @@ function glob(tame,wild)
687
704
! ! ! matching routines.
688
705
! ! !
689
706
! ! function test(tame, wild, bExpectedResult) result(bpassed)
690
- ! ! use M_strings , only : glob
707
+ ! ! use fpm_strings , only : glob
691
708
! ! character(len=*) :: tame
692
709
! ! character(len=*) :: wild
693
710
! ! logical :: bExpectedResult
@@ -722,7 +739,7 @@ function glob(tame,wild)
722
739
! !##LICENSE
723
740
! ! Public Domain
724
741
725
- ! ident_6=" @(#)M_strings ::glob(3f): function compares text strings, one of which can have wildcards ('*' or '?')."
742
+ ! @(#)fpm_strings ::glob(3f): function compares text strings, one of which can have wildcards ('*' or '?').
726
743
727
744
logical :: glob
728
745
character (len=* ) :: tame ! A string without wildcards
0 commit comments