Subversion Repositories lagranto.ecmwf

Rev

Details | Last modification | View Log | RSS feed

Rev Author Line No. Line
3 michaesp 1
module strings
2
 
3
use precision
4
 
5
private :: value_dr,value_sr,value_di,value_si
6
private :: write_dr,write_sr,write_di,write_si
7
private :: writeq_dr,writeq_sr,writeq_di,writeq_si
8
 
9
interface value  ! Generic operator for converting a number string to a 
10
                 ! number. Calling syntax is 'call value(numstring,number,ios)' 
11
                 ! where 'numstring' is a number string and 'number' is a 
12
                 ! real number or an integer (single or double precision).         
13
   module procedure value_dr
14
   module procedure value_sr
15
   module procedure value_di
16
   module procedure value_si
17
end interface
18
 
19
interface writenum  ! Generic  interface for writing a number to a string. The 
20
                    ! number is left justified in the string. The calling syntax
21
                    ! is 'call writenum(number,string,format)' where 'number' is
22
                    ! a real number or an integer, 'string' is a character string
23
                    ! containing the result, and 'format' is the format desired, 
24
                    ! e.g., 'e15.6' or 'i5'.
25
   module procedure write_dr
26
   module procedure write_sr
27
   module procedure write_di
28
   module procedure write_si
29
end interface
30
 
31
interface writeq  ! Generic interface equating a name to a numerical value. The
32
                  ! calling syntax is 'call writeq(unit,name,value,format)' where
33
                  ! unit is the integer output unit number, 'name' is the variable
34
                  ! name, 'value' is the real or integer value of the variable, 
35
                  ! and 'format' is the format of the value. The result written to
36
                  ! the output unit has the form <name> = <value>.
37
   module procedure writeq_dr
38
   module procedure writeq_sr
39
   module procedure writeq_di
40
   module procedure writeq_si
41
end interface
42
 
43
 
44
!**********************************************************************
45
 
46
contains
47
 
48
!**********************************************************************
49
 
50
subroutine parse(str,delims,args,nargs)
51
 
52
! Parses the string 'str' into arguments args(1), ..., args(nargs) based on
53
! the delimiters contained in the string 'delims'. Preceding a delimiter in
54
! 'str' by a backslash (\) makes this particular instance not a delimiter.
55
! The integer output variable nargs contains the number of arguments found.
56
 
57
character(len=*) :: str,delims
58
character(len=len_trim(str)) :: strsav
59
character(len=*),dimension(:) :: args
60
 
61
strsav=str
62
call compact(str)
63
na=size(args)
64
do i=1,na
65
  args(i)=' '
66
end do  
67
nargs=0
68
lenstr=len_trim(str)
69
if(lenstr==0) return
70
k=0
71
 
72
do
73
   if(len_trim(str) == 0) exit
74
   nargs=nargs+1
75
   call split(str,delims,args(nargs))
76
   call removebksl(args(nargs))
77
end do   
78
str=strsav
79
 
80
end subroutine parse
81
 
82
!**********************************************************************
83
 
84
subroutine compact(str)
85
 
86
! Converts multiple spaces and tabs to single spaces; deletes control characters;
87
! removes initial spaces.
88
 
89
character(len=*):: str
90
character(len=1):: ch
91
character(len=len_trim(str)):: outstr
92
 
93
str=adjustl(str)
94
lenstr=len_trim(str)
95
outstr=' '
96
isp=0
97
k=0
98
 
99
do i=1,lenstr
100
  ch=str(i:i)
101
  ich=iachar(ch)
102
 
103
  select case(ich)
104
 
105
    case(9,32)     ! space or tab character
106
      if(isp==0) then
107
        k=k+1
108
        outstr(k:k)=' '
109
      end if
110
      isp=1
111
 
112
    case(33:)      ! not a space, quote, or control character
113
      k=k+1
114
      outstr(k:k)=ch
115
      isp=0
116
 
117
  end select
118
 
119
end do
120
 
121
str=adjustl(outstr)
122
 
123
end subroutine compact
124
 
125
!**********************************************************************
126
 
127
subroutine removesp(str)
128
 
129
! Removes spaces, tabs, and control characters in string str
130
 
131
character(len=*):: str
132
character(len=1):: ch
133
character(len=len_trim(str))::outstr
134
 
135
str=adjustl(str)
136
lenstr=len_trim(str)
137
outstr=' '
138
k=0
139
 
140
do i=1,lenstr
141
  ch=str(i:i)
142
  ich=iachar(ch)
143
  select case(ich)    
144
    case(0:32)  ! space, tab, or control character
145
         cycle       
146
    case(33:)  
147
      k=k+1
148
      outstr(k:k)=ch
149
  end select
150
end do
151
 
152
str=adjustl(outstr)
153
 
154
end subroutine removesp
155
 
156
!**********************************************************************
157
 
158
subroutine value_dr(str,rnum,ios)
159
 
160
! Converts number string to a double precision real number
161
 
162
character(len=*)::str
163
real(kr8)::rnum
164
integer :: ios
165
 
166
ilen=len_trim(str)
167
ipos=scan(str,'Ee')
168
if(.not.is_digit(str(ilen:ilen)) .and. ipos/=0) then
169
   ios=3
170
   return
171
end if
172
read(str,*,iostat=ios) rnum
173
 
174
end subroutine value_dr
175
 
176
!**********************************************************************
177
 
178
subroutine value_sr(str,rnum,ios)
179
 
180
! Converts number string to a single precision real number
181
 
182
character(len=*)::str
183
real(kr4) :: rnum
184
real(kr8) :: rnumd 
185
 
186
call value_dr(str,rnumd,ios)
187
if( abs(rnumd) > huge(rnum) ) then
188
  ios=15
189
  return
190
end if
191
if( abs(rnumd) < tiny(rnum) ) rnum=0.0_kr4
192
rnum=rnumd
193
 
194
end subroutine value_sr
195
 
196
!**********************************************************************
197
 
198
subroutine value_di(str,inum,ios)
199
 
200
! Converts number string to a double precision integer value
201
 
202
character(len=*)::str
203
integer(ki8) :: inum
204
real(kr8) :: rnum
205
 
206
call value_dr(str,rnum,ios)
207
if(abs(rnum)>huge(inum)) then
208
  ios=15
209
  return
210
end if
211
inum=nint(rnum,ki8)
212
 
213
end subroutine value_di
214
 
215
!**********************************************************************
216
 
217
subroutine value_si(str,inum,ios)
218
 
219
! Converts number string to a single precision integer value
220
 
221
character(len=*)::str
222
integer(ki4) :: inum
223
real(kr8) :: rnum
224
 
225
call value_dr(str,rnum,ios)
226
if(abs(rnum)>huge(inum)) then
227
  ios=15
228
  return
229
end if
230
inum=nint(rnum,ki4)
231
 
232
end subroutine value_si
233
 
234
!**********************************************************************
235
 
236
subroutine shiftstr(str,n)
237
 
238
! Shifts characters in in the string 'str' n positions (positive values
239
! denote a right shift and negative values denote a left shift). Characters
240
! that are shifted off the end are lost. Positions opened up by the shift 
241
! are replaced by spaces.
242
 
243
character(len=*):: str
244
 
245
lenstr=len(str)
246
nabs=iabs(n)
247
if(nabs>=lenstr) then
248
  str=repeat(' ',lenstr)
249
  return
250
end if
251
if(n<0) str=str(nabs+1:)//repeat(' ',nabs)  ! shift left
252
if(n>0) str=repeat(' ',nabs)//str(:lenstr-nabs)  ! shift right 
253
return
254
 
255
end subroutine shiftstr
256
 
257
!**********************************************************************
258
 
259
subroutine insertstr(str,strins,loc)
260
 
261
! Inserts the string 'strins' into the string 'str' at position 'loc'. 
262
! Characters in 'str' starting at position 'loc' are shifted right to
263
! make room for the inserted string. Trailing spaces of 'strins' are 
264
! removed prior to insertion
265
 
266
character(len=*):: str,strins
267
character(len=len(str))::tempstr
268
 
269
lenstrins=len_trim(strins)
270
tempstr=str(loc:)
271
call shiftstr(tempstr,lenstrins)
272
tempstr(1:lenstrins)=strins(1:lenstrins)
273
str(loc:)=tempstr
274
return
275
 
276
end subroutine insertstr
277
 
278
!**********************************************************************
279
 
280
subroutine delsubstr(str,substr)
281
 
282
! Deletes first occurrence of substring 'substr' from string 'str' and
283
! shifts characters left to fill hole. Trailing spaces or blanks are
284
! not considered part of 'substr'.
285
 
286
character(len=*):: str,substr
287
 
288
lensubstr=len_trim(substr)
289
ipos=index(str,substr)
290
if(ipos==0) return
291
if(ipos == 1) then
292
   str=str(lensubstr+1:)
293
else
294
   str=str(:ipos-1)//str(ipos+lensubstr:)
295
end if   
296
return
297
 
298
end subroutine delsubstr
299
 
300
!**********************************************************************
301
 
302
subroutine delall(str,substr)
303
 
304
! Deletes all occurrences of substring 'substr' from string 'str' and
305
! shifts characters left to fill holes.
306
 
307
character(len=*):: str,substr
308
 
309
lensubstr=len_trim(substr)
310
do
311
   ipos=index(str,substr)
312
   if(ipos == 0) exit
313
   if(ipos == 1) then
314
      str=str(lensubstr+1:)
315
   else
316
      str=str(:ipos-1)//str(ipos+lensubstr:)
317
   end if
318
end do   
319
return
320
 
321
end subroutine delall
322
 
323
!**********************************************************************
324
 
325
function uppercase(str) result(ucstr)
326
 
327
! convert string to upper case
328
 
329
character (len=*):: str
330
character (len=len_trim(str)):: ucstr
331
 
332
ilen=len_trim(str)
333
ioffset=iachar('A')-iachar('a')     
334
iquote=0
335
ucstr=str
336
do i=1,ilen
337
  iav=iachar(str(i:i))
338
  if(iquote==0 .and. (iav==34 .or.iav==39)) then
339
    iquote=1
340
    iqc=iav
341
    cycle
342
  end if
343
  if(iquote==1 .and. iav==iqc) then
344
    iquote=0
345
    cycle
346
  end if
347
  if (iquote==1) cycle
348
  if(iav >= iachar('a') .and. iav <= iachar('z')) then
349
    ucstr(i:i)=achar(iav+ioffset)
350
  else
351
    ucstr(i:i)=str(i:i)
352
  end if
353
end do
354
return
355
 
356
end function uppercase
357
 
358
!**********************************************************************
359
 
360
function lowercase(str) result(lcstr)
361
 
362
! convert string to lower case
363
 
364
character (len=*):: str
365
character (len=len_trim(str)):: lcstr
366
 
367
ilen=len_trim(str)
368
ioffset=iachar('A')-iachar('a')
369
iquote=0
370
lcstr=str
371
do i=1,ilen
372
  iav=iachar(str(i:i))
373
  if(iquote==0 .and. (iav==34 .or.iav==39)) then
374
    iquote=1
375
    iqc=iav
376
    cycle
377
  end if
378
  if(iquote==1 .and. iav==iqc) then
379
    iquote=0
380
    cycle
381
  end if
382
  if (iquote==1) cycle
383
  if(iav >= iachar('A') .and. iav <= iachar('Z')) then
384
    lcstr(i:i)=achar(iav-ioffset)
385
  else
386
    lcstr(i:i)=str(i:i)
387
  end if
388
end do
389
return
390
 
391
end function lowercase
392
 
393
!**********************************************************************
394
 
395
subroutine readline(nunitr,line,ios)
396
 
397
! Reads line from unit=nunitr, ignoring blank lines
398
! and deleting comments beginning with an exclamation point(!)
399
 
400
character (len=*):: line
401
 
402
do  
403
  read(nunitr,'(a)', iostat=ios) line      ! read input line
404
  if(ios /= 0) return
405
  line=adjustl(line)
406
  ipos=index(line,'!')
407
  if(ipos == 1) cycle
408
  if(ipos /= 0) line=line(:ipos-1)
409
  if(len_trim(line) /= 0) exit
410
end do
411
return
412
 
413
end subroutine readline
414
 
415
!**********************************************************************
416
 
417
subroutine match(str,ipos,imatch)
418
 
419
! Sets imatch to the position in string of the delimiter matching the delimiter
420
! in position ipos. Allowable delimiters are (), [], {}, <>.
421
 
422
character(len=*) :: str
423
character :: delim1,delim2,ch
424
 
425
lenstr=len_trim(str)
426
delim1=str(ipos:ipos)
427
select case(delim1)
428
   case('(')
429
      idelim2=iachar(delim1)+1
430
      istart=ipos+1
431
      iend=lenstr
432
      inc=1
433
   case(')')
434
      idelim2=iachar(delim1)-1
435
      istart=ipos-1
436
      iend=1
437
      inc=-1
438
   case('[','{','<')
439
      idelim2=iachar(delim1)+2
440
      istart=ipos+1
441
      iend=lenstr
442
      inc=1
443
   case(']','}','>')
444
      idelim2=iachar(delim1)-2
445
      istart=ipos-1
446
      iend=1
447
      inc=-1
448
   case default
449
      write(*,*) delim1,' is not a valid delimiter'
450
      return
451
end select
452
if(istart < 1 .or. istart > lenstr) then
453
   write(*,*) delim1,' has no matching delimiter'
454
   return
455
end if
456
delim2=achar(idelim2) ! matching delimiter
457
 
458
isum=1
459
do i=istart,iend,inc
460
   ch=str(i:i)
461
   if(ch /= delim1 .and. ch /= delim2) cycle
462
   if(ch == delim1) isum=isum+1
463
   if(ch == delim2) isum=isum-1
464
   if(isum == 0) exit
465
end do
466
if(isum /= 0) then
467
   write(*,*) delim1,' has no matching delimiter'
468
   return
469
end if   
470
imatch=i
471
 
472
return
473
 
474
end subroutine match
475
 
476
!**********************************************************************
477
 
478
subroutine write_dr(rnum,str,fmt)
479
 
480
! Writes double precision real number rnum to string str using format fmt
481
 
482
real(kr8) :: rnum
483
character(len=*) :: str,fmt
484
character(len=80) :: formt
485
 
486
formt='('//trim(fmt)//')'
487
write(str,formt) rnum
488
str=adjustl(str)
489
 
490
end subroutine write_dr
491
 
492
!***********************************************************************
493
 
494
subroutine write_sr(rnum,str,fmt)
495
 
496
! Writes single precision real number rnum to string str using format fmt
497
 
498
real(kr4) :: rnum
499
character(len=*) :: str,fmt
500
character(len=80) :: formt
501
 
502
formt='('//trim(fmt)//')'
503
write(str,formt) rnum
504
str=adjustl(str)
505
 
506
end subroutine write_sr
507
 
508
!***********************************************************************
509
 
510
subroutine write_di(inum,str,fmt)
511
 
512
! Writes double precision integer inum to string str using format fmt
513
 
514
integer(ki8) :: inum
515
character(len=*) :: str,fmt
516
character(len=80) :: formt
517
 
518
formt='('//trim(fmt)//')'
519
write(str,formt) inum
520
str=adjustl(str)
521
 
522
end subroutine write_di
523
 
524
!***********************************************************************
525
 
526
subroutine write_si(inum,str,fmt)
527
 
528
! Writes single precision integer inum to string str using format fmt
529
 
530
integer(ki4) :: inum
531
character(len=*) :: str,fmt
532
character(len=80) :: formt
533
 
534
formt='('//trim(fmt)//')'
535
write(str,formt) inum
536
str=adjustl(str)
537
 
538
end subroutine write_si
539
 
540
!***********************************************************************
541
 
542
subroutine trimzero(str)
543
 
544
! Deletes nonsignificant trailing zeroes from number string str. If number
545
! string ends in a decimal point, one trailing zero is added.
546
 
547
character(len=*) :: str
548
character :: ch
549
character(len=10) :: exp
550
 
551
ipos=scan(str,'eE')
552
if(ipos>0) then
553
   exp=str(ipos:)
554
   str=str(1:ipos-1)
555
endif
556
lstr=len_trim(str)
557
do i=lstr,1,-1
558
   ch=str(i:i)
559
   if(ch=='0') cycle          
560
   if(ch=='.') then
561
      str=str(1:i)//'0'
562
      if(ipos>0) str=trim(str)//trim(exp)
563
      exit
564
   endif
565
   str=str(1:i)
566
   exit
567
end do
568
if(ipos>0) str=trim(str)//trim(exp)
569
 
570
end subroutine trimzero
571
 
572
!**********************************************************************
573
 
574
subroutine writeq_dr(unit,namestr,value,fmt)
575
 
576
! Writes a string of the form <name> = value to unit
577
 
578
real(kr8) :: value
579
integer :: unit
580
character(len=*) :: namestr,fmt
581
character(len=32) :: tempstr
582
 
583
call writenum(value,tempstr,fmt)
584
call trimzero(tempstr)
585
write(unit,*) trim(namestr)//' = '//trim(tempstr)
586
 
587
end subroutine writeq_dr
588
 
589
!**********************************************************************
590
 
591
subroutine writeq_sr(unit,namestr,value,fmt)
592
 
593
! Writes a string of the form <name> = value to unit
594
 
595
real(kr4) :: value
596
integer :: unit
597
character(len=*) :: namestr,fmt
598
character(len=32) :: tempstr
599
 
600
call writenum(value,tempstr,fmt)
601
call trimzero(tempstr)
602
write(unit,*) trim(namestr)//' = '//trim(tempstr)
603
 
604
end subroutine writeq_sr
605
 
606
!**********************************************************************
607
 
608
subroutine writeq_di(unit,namestr,ivalue,fmt)
609
 
610
! Writes a string of the form <name> = ivalue to unit
611
 
612
integer(ki8) :: ivalue
613
integer :: unit
614
character(len=*) :: namestr,fmt
615
character(len=32) :: tempstr
616
call writenum(ivalue,tempstr,fmt)
617
call trimzero(tempstr)
618
write(unit,*) trim(namestr)//' = '//trim(tempstr)
619
 
620
end subroutine writeq_di
621
 
622
!**********************************************************************
623
 
624
subroutine writeq_si(unit,namestr,ivalue,fmt)
625
 
626
! Writes a string of the form <name> = ivalue to unit
627
 
628
integer(ki4) :: ivalue
629
integer :: unit
630
character(len=*) :: namestr,fmt
631
character(len=32) :: tempstr
632
call writenum(ivalue,tempstr,fmt)
633
call trimzero(tempstr)
634
write(unit,*) trim(namestr)//' = '//trim(tempstr)
635
 
636
end subroutine writeq_si
637
 
638
!**********************************************************************
639
 
640
function is_letter(ch) result(res)
641
 
642
! Returns .true. if ch is a letter and .false. otherwise
643
 
644
character :: ch
645
logical :: res
646
 
647
select case(ch)
648
case('A':'Z','a':'z')
649
  res=.true.
650
case default
651
  res=.false.
652
end select
653
return
654
 
655
end function is_letter
656
 
657
!**********************************************************************
658
 
659
function is_digit(ch) result(res)
660
 
661
! Returns .true. if ch is a digit (0,1,...,9) and .false. otherwise
662
 
663
character :: ch
664
logical :: res
665
 
666
select case(ch)
667
case('0':'9')
668
  res=.true.
669
case default
670
  res=.false.
671
end select
672
return
673
 
674
end function is_digit
675
 
676
!**********************************************************************
677
 
678
subroutine split(str,delims,before,sep)
679
 
680
! Routine finds the first instance of a character from 'delims' in the
681
! the string 'str'. The characters before the found delimiter are
682
! output in 'before'. The characters after the found delimiter are
683
! output in 'str'. The optional output character 'sep' contains the 
684
! found delimiter. A delimiter in 'str' is treated like an ordinary 
685
! character if it is preceded by a backslash (\). If the backslash 
686
! character is desired in 'str', then precede it with another backslash.
687
 
688
character(len=*) :: str,delims,before
689
character,optional :: sep
690
logical :: pres
691
character :: ch,cha
692
 
693
pres=present(sep)
694
str=adjustl(str)
695
call compact(str)
696
lenstr=len_trim(str)
697
if(lenstr == 0) return        ! string str is empty
698
k=0
699
ibsl=0                        ! backslash initially inactive
700
before=' '
701
do i=1,lenstr
702
   ch=str(i:i)
703
   if(ibsl == 1) then          ! backslash active
704
      k=k+1
705
      before(k:k)=ch
706
      ibsl=0
707
      cycle
708
   end if
709
   if(ch == '\\') then          ! backslash with backslash inactive
710
      k=k+1
711
      before(k:k)=ch
712
      ibsl=1
713
      cycle
714
   end if
715
   ipos=index(delims,ch)         
716
   if(ipos == 0) then          ! character is not a delimiter
717
      k=k+1
718
      before(k:k)=ch
719
      cycle
720
   end if
721
   if(ch /= ' ') then          ! character is a delimiter that is not a space
722
      str=str(i+1:)
723
      if(pres) sep=ch
724
      exit
725
   end if
726
   cha=str(i+1:i+1)            ! character is a space delimiter
727
   iposa=index(delims,cha)
728
   if(iposa > 0) then          ! next character is a delimiter
729
      str=str(i+2:)
730
      if(pres) sep=cha
731
      exit
732
   else
733
      str=str(i+1:)
734
      if(pres) sep=ch
735
      exit
736
   end if
737
end do
738
if(i >= lenstr) str=''
739
str=adjustl(str)              ! remove initial spaces
740
return
741
 
742
end subroutine split
743
 
744
!**********************************************************************
745
 
746
subroutine removebksl(str)
747
 
748
! Removes backslash (\) characters. Double backslashes (\\) are replaced
749
! by a single backslash.
750
 
751
character(len=*):: str
752
character(len=1):: ch
753
character(len=len_trim(str))::outstr
754
 
755
str=adjustl(str)
756
lenstr=len_trim(str)
757
outstr=' '
758
k=0
759
ibsl=0                        ! backslash initially inactive
760
 
761
do i=1,lenstr
762
  ch=str(i:i)
763
  if(ibsl == 1) then          ! backslash active
764
   k=k+1
765
   outstr(k:k)=ch
766
   ibsl=0
767
   cycle
768
  end if
769
  if(ch == '\\') then          ! backslash with backslash inactive
770
   ibsl=1
771
   cycle
772
  end if
773
  k=k+1
774
  outstr(k:k)=ch              ! non-backslash with backslash inactive
775
end do
776
 
777
str=adjustl(outstr)
778
 
779
end subroutine removebksl
780
 
781
!**********************************************************************
782
 
783
end module strings  
784
 
785