New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
m_strings.f90 in branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/EXTERNAL/XMLF90/src/strings – NEMO

source: branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/EXTERNAL/XMLF90/src/strings/m_strings.f90 @ 3861

Last change on this file since 3861 was 3861, checked in by cetlod, 11 years ago

2013/dev_r3411_CNRS4_IOCRS : minor modification in XMLF90/src/strings/m_strings.f90 routine ; needed if running with bounds checking

  • Property svn:keywords set to Id
File size: 163.1 KB
Line 
1!*******************************************************************************
2! module STRINGS
3! Mart Rentmeester, Mart.Rentmeester@sci.kun.nl
4! http://nn-online.sci.kun.nl/fortran
5! Version 1.0
6!*******************************************************************************
7
8      module m_strings
9
10      private
11
12      type string
13          private
14          integer                 :: len = 0
15          integer                 :: size = 0
16
17          character, pointer      :: chars(:) => null()
18
19      end type string
20
21      character, parameter :: blank = ' '
22
23!     GENERIC PROCEDURE INTERFACE DEFINITIONS
24
25!---- LEN interface
26      interface len
27          module procedure len_s
28      end interface
29
30!---- Conversion (to CHAR) procedure interfaces
31      interface char
32          module procedure s_to_c, &! string to character
33                           s_to_slc       ! string to specified length character
34      end interface
35
36!---- ASSIGNMENT interfaces
37      interface assignment(=)
38          module procedure assign_s_to_s, &! string = string
39                           assign_s_to_c, &! character = string
40                           assign_c_to_s        ! string = character
41      end interface
42
43!---- // operator interfaces
44      interface operator(//)
45          module procedure s_concat_s, &! string // string
46                           s_concat_c, &! string // character
47                           c_concat_s     ! character // string
48      end interface
49
50!---- INSERT_IN_STRING interface
51      interface insert_in_string
52          module procedure insert_in_string_c, insert_in_string_s
53      end interface
54
55!---- PREPEND_TO_STRING interface
56      interface prepend_to_string
57          module procedure prepend_to_string_c, prepend_to_string_s
58      end interface
59
60!---- APPEND_TO_STRING interface
61      interface append_to_string
62          module procedure append_to_string_c, append_to_string_s
63      end interface
64
65!---- REPLACE_IN_STRING interface
66      interface replace_in_string
67          module procedure replace_in_string_sc_s,   replace_in_string_ss_s,   &
68                           replace_in_string_sc_sf,  replace_in_string_ss_sf,  &
69                           replace_in_string_scc,    replace_in_string_ssc,    &
70                           replace_in_string_scs,    replace_in_string_sss,    &
71                           replace_in_string_scc_f,  replace_in_string_ssc_f,  &
72                           replace_in_string_scs_f,  replace_in_string_sss_f
73      end interface
74
75
76!---- REPEAT interface
77      interface repeat
78          module procedure repeat_s
79      end interface
80
81!---- ==  .eq. comparison operator interfaces
82      interface operator(==)
83          module procedure s_eq_s, &! string == string
84                           s_eq_c, &! string == character
85                           c_eq_s         ! character == string
86      end interface
87
88!---- /=  .ne. comparison operator interfaces
89      interface operator(/=)
90          module procedure s_ne_s, &! string /= string
91                           s_ne_c, &! string /= character
92                           c_ne_s         ! character /= string
93      end interface
94
95!---- <  .lt. comparison operator interfaces
96      interface operator(<)
97          module procedure s_lt_s, &! string < string
98                           s_lt_c, &! string < character
99                           c_lt_s         ! character < string
100      end interface
101
102!---- <=  .le. comparison operator interfaces
103      interface operator(<=)
104          module procedure s_le_s, &! string <= string
105                           s_le_c, &! string <= character
106                           c_le_s         ! character <= string
107      end interface
108
109!---- >=  .ge. comparison operator interfaces
110      interface operator(>=)
111          module procedure s_ge_s, &! string >= string
112                           s_ge_c, &! string >= character
113                           c_ge_s         ! character >= string
114      end interface
115
116!---- >  .gt. comparison operator interfaces
117      interface operator(>)
118          module procedure s_gt_s, &! string > string
119                           s_gt_c, &! string > character
120                           c_gt_s         ! character > string
121      end interface
122
123!---- .aeq. comparison operator interfaces
124      interface operator(.aeq.)
125          module procedure a_eq_a, &! array == array
126                           a_eq_c, &! array == character
127                           c_eq_a         ! character == array
128      end interface
129
130!---- .ane. comparison operator interfaces
131      interface operator(.ane.)
132          module procedure a_ne_a, &! array /= array
133                           a_ne_c, &! array /= character
134                           c_ne_a         ! character /= array
135      end interface
136
137!---- .alt. comparison operator interfaces
138      interface operator(.alt.)
139          module procedure a_lt_a, &! array < array
140                           a_lt_c, &! array < character
141                           c_lt_a         ! character < array
142      end interface
143
144!---- .ale. comparison operator interfaces
145      interface operator(.ale.)
146          module procedure a_le_a, &! array <= array
147                           a_le_c, &! array <= character
148                           c_le_a         ! character <= array
149      end interface
150
151!---- .age. comparison operator interfaces
152      interface operator(.age.)
153          module procedure a_ge_a, &! array >= array
154                           a_ge_c, &! array >= character
155                           c_ge_a         ! character >= array
156      end interface
157
158!---- .agt. comparison operator interfaces
159      interface operator(.agt.)
160          module procedure a_gt_a, &! array > array
161                           a_gt_c, &! array > character
162                           c_gt_a         ! character > array
163      end interface
164
165!---- LLT comparison function interfaces
166      interface llt
167          module procedure s_llt_s, &! llt(string,string)
168                           s_llt_c, &! llt(string,character)
169                           c_llt_s        ! llt(character,string)
170      end interface
171
172!---- LLE comparison function interfaces
173      interface lle
174          module procedure s_lle_s, &! lle(string,string)
175                           s_lle_c, &! lle(string,character)
176                           c_lle_s        ! lle(character,string)
177      end interface
178
179!---- LGE comparison function interfaces
180      interface lge
181          module procedure s_lge_s, &! lge(string,string)
182                           s_lge_c, &! lge(string,character)
183                           c_lge_s        ! lge(character,string)
184      end interface
185
186!---- LGT comparison function interfaces
187      interface lgt
188          module procedure s_lgt_s, &! lgt(string,string)
189                           s_lgt_c, &! lgt(string,character)
190                           c_lgt_s        ! lgt(character,string)
191      end interface
192
193!---- ALLT comparison function interfaces
194      interface allt
195          module procedure a_allt_a, &! allt(array,array)
196                           a_allt_c, &! allt(array,character)
197                           c_allt_a        ! allt(character,array)
198      end interface
199
200!---- ALLE comparison function interfaces
201      interface alle
202          module procedure a_alle_a, &! alle(array,array)
203                           a_alle_c, &! alle(array,character)
204                           c_alle_a        ! alle(character,array)
205      end interface
206
207!---- ALGE comparison function interfaces
208      interface alge
209          module procedure a_alge_a, &! alge(array,array)
210                           a_alge_c, &! alge(array,character)
211                           c_alge_a        ! alge(character,array)
212      end interface
213
214!---- ALGT comparison function interfaces
215      interface algt
216          module procedure a_algt_a, &! algt(array,array)
217                           a_algt_c, &! algt(array,character)
218                           c_algt_a        ! algt(character,array)
219      end interface
220
221!---- INDEX procedure
222      interface index
223          module procedure index_ss, index_sc, index_cs
224      end interface
225
226!---- AINDEX procedure
227      interface aindex
228          module procedure aindex_aa, aindex_ac, aindex_ca
229      end interface
230
231!---- SCAN procedure
232      interface scan
233          module procedure scan_ss, scan_sc, scan_cs
234      end interface
235
236!---- ASCAN procedure
237      interface ascan
238          module procedure ascan_aa, ascan_ac, ascan_ca
239      end interface
240
241!---- VERIFY procedure
242      interface verify
243          module procedure verify_ss, verify_sc, verify_cs
244      end interface
245
246!---- AVERIFY procedure
247      interface averify
248          module procedure averify_aa, averify_ac, averify_ca
249      end interface
250
251!---- TRIM interface
252      interface len_trim
253          module procedure len_trim_s
254      end interface
255
256!---- LEN_TRIM interface
257      interface trim
258          module procedure trim_s
259      end interface
260
261!---- IACHAR interface
262      interface iachar
263          module procedure iachar_s
264      end interface
265
266!---- ICHAR interface
267      interface ichar
268          module procedure ichar_s
269      end interface
270
271!---- ADJUSTL interface
272      interface adjustl
273          module procedure adjustl_s
274      end interface
275
276!---- ADJUSTR interface
277      interface adjustr
278          module procedure adjustr_s
279      end interface
280
281!---- LEN_STRIP interface
282      interface len_strip
283          module procedure len_strip_c, len_strip_s
284      end interface
285
286!---- STRIP interface
287      interface strip
288          module procedure strip_c, strip_s
289      end interface
290
291!---- UPPERCASE interface
292      interface uppercase
293          module procedure uppercase_s, uppercase_c
294      end interface
295
296!---- TO_UPPERCASE interface
297      interface to_uppercase
298          module procedure to_uppercase_s, to_uppercase_c
299      end interface
300
301!---- LOWERCASE interface
302      interface lowercase
303          module procedure lowercase_s, lowercase_c
304      end interface
305
306!---- TO_LOWERCASE interface
307      interface to_lowercase
308          module procedure to_lowercase_s, to_lowercase_c
309      end interface
310
311!---- EXTRACT interface
312      interface extract
313          module procedure extract_s, extract_c
314      end interface
315
316!---- SUBSTRING interface
317      interface substring
318          module procedure extract_s, extract_c
319      end interface
320
321!---- REMOVE interface
322      interface remove
323          module procedure remove_s, remove_c
324      end interface
325
326!---- INSERT interface
327      interface insert
328          module procedure insert_ss, insert_cs, insert_sc, insert_cc
329      end interface
330
331!---- REPLACE interface
332      interface replace
333          module procedure replace_cc_s,   replace_cs_s,   &
334                           replace_sc_s,   replace_ss_s,   &
335                           replace_cc_sf,  replace_cs_sf,  &
336                           replace_sc_sf,  replace_ss_sf,  &
337                           replace_ccc,    replace_csc,    &
338                           replace_ccs,    replace_css,    &
339                           replace_scc,    replace_ssc,    &
340                           replace_scs,    replace_sss,    &
341                           replace_ccc_f,  replace_csc_f,  &
342                           replace_ccs_f,  replace_css_f,  &
343                           replace_scc_f,  replace_ssc_f,  &
344                           replace_scs_f,  replace_sss_f
345      end interface
346
347!---- SORT interface
348      interface sort
349          module procedure sort_c, sort_s
350      end interface
351
352!---- LSORT interface
353      interface lsort
354          module procedure lsort_c, lsort_s
355      end interface
356
357!---- RANK interface
358      interface rank
359          module procedure rank_c, rank_s
360      end interface
361
362!---- LRANK interface
363      interface lrank
364          module procedure lrank_c, lrank_s
365      end interface
366
367
368
369!---- Publically accessible entities
370      public :: string
371      public :: assignment(=),unstring
372      public :: insert,replace,remove,extract,substring
373      public :: repeat,index,scan,verify
374      public :: operator(//)
375      public :: operator(==),operator(/=)
376      public :: operator(<),operator(<=)
377      public :: operator(>),operator(>=)
378      public :: llt,lle,lge,lgt
379      public :: char,len,len_trim,trim,iachar,ichar,adjustl,adjustr
380      public :: lowercase,to_lowercase,uppercase,to_uppercase
381      public :: strip,len_strip
382      public :: sort,rank,lsort,lrank
383
384      public :: resize_string,string_size,swap_strings
385      public :: trim_string,strip_string
386      public :: adjustl_string,adjustr_string
387      public :: insert_in_string,remove_from_string
388      public :: prepend_to_string,append_to_string
389      public :: replace_in_string
390
391
392
393
394      contains
395
396!*******************************************************************************
397!     LEN
398!*******************************************************************************
399
400      elemental function len_s(s)
401
402      implicit none
403      type(string), intent(in)  :: s
404      integer                   :: len_s
405
406
407      len_s = s%len
408
409      end function len_s
410
411!*******************************************************************************
412!     STRING_SIZE
413!*******************************************************************************
414
415      elemental function string_size(s)
416
417      implicit none
418      type(string), intent(in)  :: s
419      integer                   :: string_size
420
421
422      string_size = s%size
423
424      end function string_size
425
426!*******************************************************************************
427!     CHAR
428!*******************************************************************************
429!     Returns the characters of string as an automatically sized character
430
431      pure function s_to_c(s)
432
433      implicit none
434      type(string),intent(in)   :: s
435      character(len(s))         :: s_to_c
436
437
438      s_to_c = transfer(s%chars(1:len(s)),s_to_c)
439
440      end function s_to_c
441
442!*******************************************************************************
443!     Returns the character of fixed length, length, containing the characters
444!     of string either padded with blanks or truncated on the right to fit
445
446      pure function s_to_slc(s,length)
447
448      implicit none
449      type(string),intent(in)  :: s
450      integer, intent(in)      :: length
451      character(length)        :: s_to_slc
452      integer                  :: i,lc
453
454
455      lc = min(len(s),length)
456      s_to_slc(1:lc) = transfer(s%chars(1:lc),s_to_slc)
457
458!     Result longer than string: padding needed
459      if (lc < length) s_to_slc(lc+1:length) = blank
460
461      end function s_to_slc
462
463!*******************************************************************************
464! Assign a string value to a string variable overriding default assignement.
465! Reallocates string variable to size of string value and copies characters.
466
467      elemental subroutine assign_s_to_s(var,expr)
468
469      implicit none
470      type(string), intent(out)  :: var
471      type(string), intent(in)   :: expr
472
473
474
475      if (associated(var%chars,expr%chars)) then
476!         Identity assignment: nothing to be done
477          continue
478      else
479          if (associated(var%chars)) deallocate(var%chars)
480
481          var%size = expr%size
482          var%len = expr%len
483!AG
484          if (associated(expr%chars)) then
485             allocate(var%chars(1:var%size))
486             var%chars(1:var%len) = expr%chars(1:var%len)
487          endif
488      endif
489
490
491      end subroutine assign_s_to_s
492
493!*******************************************************************************
494! Assign a string value to a character variable.
495! If the string is longer than the character truncate the string on the right.
496! If the string is shorter the character is blank padded on the right.
497
498      elemental subroutine assign_s_to_c(var,expr)
499
500      implicit none
501      character(*), intent(out)  :: var
502      type(string), intent(in)   :: expr
503      integer                    :: i,lc,ls
504
505
506      lc = len(var);
507      ls = min(len(expr),lc)
508
509      var(1:ls) = transfer(expr%chars(1:ls),var(1:ls))
510
511      do i=ls+1,lc
512          var(i:i) = blank
513      enddo
514
515      end subroutine assign_s_to_c
516
517!*******************************************************************************
518!     Assign a character value to a string variable.
519!     Disassociates the string variable from its current value, allocates new
520!     space to hold the characters and copies them from the character value
521!     into this space.
522
523      elemental subroutine assign_c_to_s(var,expr)
524
525      implicit none
526      type(string), intent(out)  :: var
527      character(*), intent(in)   :: expr
528      integer                    :: i,lc
529
530
531
532      if (associated(var%chars)) deallocate(var%chars)
533
534
535      lc = len(expr)
536      var%len = lc
537      var%size = lc
538      allocate(var%chars(1:lc))
539!!AG: NAG compiler uses temporaries here:
540!      var%chars(:) = (/ (expr(i:i), i=1,lc) /)
541       do i=1,lc
542          var%chars(i) = expr(i:i)
543       enddo
544
545      end subroutine assign_c_to_s
546
547!*******************************************************************************
548!     RESIZE_STRING procedure
549!*******************************************************************************
550
551!*** return code
552!*** n < 0  --> deallocate?
553
554!     pure subroutine resize_string(s,newsize,status)
555      pure subroutine resize_string(s,newsize)
556
557      implicit none
558      type(string), intent(inout)     :: s
559      integer, intent(in)             :: newsize
560!     integer, intent(out), optional  :: status
561
562      character, pointer              :: c(:)
563
564      integer                         :: i
565
566
567      if (newsize <= 0) return
568
569
570      if (associated(s%chars)) then
571
572          i = min(newsize,s%len)
573          allocate(c(i))
574          c(:) = s%chars(1:i)
575          deallocate(s%chars)
576
577          s%chars => c
578
579          s%len = i
580          s%size = newsize
581      else
582          s%size = newsize
583          s%len = 0
584          allocate(s%chars(s%size))
585      endif
586
587      end subroutine resize_string
588
589!*******************************************************************************
590!     SWAP_STRINGS
591!*******************************************************************************
592      subroutine swap_strings(s1,s2)
593
594
595      implicit none
596      type(string), intent(inout)  :: s1,s2
597      integer                      :: l,s
598      character, pointer           :: c(:)
599
600
601      l = s1%len
602      s = s1%size
603      c => s1%chars
604      s1%len = s2%len
605      s1%size = s2%size
606      s1%chars => s2%chars
607      s2%len = l
608      s2%size = s
609      s2%chars => c
610
611      end subroutine swap_strings
612
613!*******************************************************************************
614!     TRIM_STRINGSIZE
615!*******************************************************************************
616
617      subroutine trim_stringsize(s)
618
619      implicit none
620      type(string), intent(inout)  :: s
621
622
623      call resize_string(s,len(s))
624
625      end subroutine trim_stringsize
626
627!*******************************************************************************
628!     TRIM_STRING
629!*******************************************************************************
630
631      subroutine trim_string(s)
632
633      implicit none
634      type(string), intent(inout)  :: s
635
636
637      s%len = len_trim(s)
638
639      end subroutine trim_string
640
641!*******************************************************************************
642!    STRIP
643!*******************************************************************************
644
645     pure subroutine strip_string(s)
646
647     implicit none
648     type(string), intent(inout)  :: s
649     integer                      :: i,i1,i2
650
651
652     do i1=1,len(s)
653         if (s%chars(i1) /= blank) exit
654     enddo
655     do i2=len(s),1,-1
656         if (s%chars(i2) /= blank) exit
657     enddo
658     do i=i1,i2
659         s%chars(i-i1+1) = s%chars(i)
660     enddo
661     s%len = i2 - i1 + 1
662
663     end subroutine strip_string
664
665!*******************************************************************************
666!     ADJUSTL_STRING
667!*******************************************************************************
668! Returns as a character variable the string adjusted to the left,
669! removing leading blanks and inserting trailing blanks.
670
671      pure subroutine adjustl_string(s)
672
673      implicit none
674      type(string), intent(inout)  :: s
675      integer                      :: i,j
676
677
678      do i=1,len(s)
679          if (s%chars(i) /= blank) exit
680      enddo
681      do j=i,len(s)
682          s%chars(j-i:j-i) = s%chars(j)
683      enddo
684      s%chars(j+1:) = blank
685
686      end subroutine adjustl_string
687
688!*******************************************************************************
689!     ADJUSTR_STRING
690!*******************************************************************************
691! Returns as a character variable the string adjusted to the right,
692! removing trailing blanks and inserting leading blanks.
693
694      pure subroutine adjustr_string(s)
695
696      implicit none
697      type(string), intent(inout)  :: s
698      integer                      :: i,j,l,lt
699
700
701      l = len(s)
702      lt = len_trim(s)
703
704      i = l - lt
705
706      do j=1,lt
707          s%chars(j+i:j+i) = s%chars(j)
708      enddo
709      s%chars(1:i) = blank
710
711
712      end subroutine adjustr_string
713
714!*******************************************************************************
715!     PREPEND_TO_STRING
716!*******************************************************************************
717
718      pure subroutine prepend_to_string_s(s1,s2)
719
720      implicit none
721      type(string), intent(inout)  :: s1
722      type(string), intent(in)     :: s2
723      integer                      :: i,ls1,ls2
724
725      character, pointer           :: ss(:)
726
727
728      ls1 = len(s1)
729      ls2 = len(s2)
730      if (ls2 == 0) return
731      if (ls1+ls2 > string_size(s1)) then
732          allocate(ss(ls1+ls2))
733          do i=1,ls2
734              ss(i) = s2%chars(i)
735          enddo
736          do i=1,ls1
737              ss(ls2+i) = s1%chars(i)
738          enddo
739          deallocate(s1%chars)
740
741          s1%chars => ss
742
743          s1%len = ls1 + ls2
744          s1%size = s1%len
745      else
746          do i=ls1,1,-1
747              s1%chars(ls2+i) = s1%chars(i)
748          enddo
749          do i=1,ls2
750              s1%chars(i) = s2%chars(i)
751          enddo
752          s1%len = ls1 + ls2
753      endif
754
755      end subroutine prepend_to_string_s
756
757!*******************************************************************************
758
759      pure subroutine prepend_to_string_c(s,c)
760
761      implicit none
762      type(string), intent(inout)  :: s
763      character(*), intent(in)     :: c
764      integer                      :: i,ls,lc
765
766      character, pointer           :: ss(:)
767
768
769
770      ls = len(s)
771      lc = len(c)
772      if (lc == 0) return
773      if (ls+lc > string_size(s)) then
774          allocate(ss(ls+lc))
775          do i=1,lc
776              ss(i) = c(i:i)
777          enddo
778          do i=1,ls
779              ss(lc+i) = s%chars(i)
780          enddo
781          deallocate(s%chars)
782
783          s%chars => ss
784
785          s%len = ls + lc
786          s%size = s%len
787      else
788          do i=ls,1,-1
789              s%chars(lc+i) = s%chars(i)
790          enddo
791          do i=1,lc
792              s%chars(i) = c(i:i)
793          enddo
794          s%len = ls + lc
795      endif
796
797      end subroutine prepend_to_string_c
798
799!*******************************************************************************
800!     APPEND_TO_STRING
801!*******************************************************************************
802
803      pure subroutine append_to_string_s(s1,s2)
804
805      implicit none
806      type(string), intent(inout)  :: s1
807      type(string), intent(in)     :: s2
808      integer                      :: i,ls1,ls2
809
810      character, pointer           :: ss(:)
811
812
813      ls1 = len(s1)
814      ls2 = len(s2)
815      if (ls2 == 0) return
816      if (ls1+ls2 > string_size(s1)) then
817          allocate(ss(ls1+ls2))
818          do i=1,ls1
819              ss(i) = s1%chars(i)
820          enddo
821          do i=ls1+1,ls1+ls2
822              ss(i) = s2%chars(i-ls1)
823          enddo
824          deallocate(s1%chars)
825
826          s1%chars => ss
827
828          s1%len = ls1 + ls2
829          s1%size = s1%len
830      else
831          do i=ls1+1,ls1+ls2
832              s1%chars(i) = s2%chars(i-ls1)
833          enddo
834          s1%len = ls1 + ls2
835      endif
836
837      end subroutine append_to_string_s
838
839!*******************************************************************************
840
841      pure subroutine append_to_string_c(s,c)
842
843      implicit none
844      type(string), intent(inout)  :: s
845      character(*), intent(in)     :: c
846      integer                      :: i,ls,lc
847
848      character, pointer           :: ss(:)
849
850
851
852      ls = len(s)
853      lc = len(c)
854      if (lc == 0) return
855      if (ls+lc > string_size(s)) then
856          allocate(ss(ls+lc))
857          do i=1,ls
858              ss(i) = s%chars(i)
859          enddo
860          do i=ls+1,ls+lc
861              ss(i) = c(i-ls:i-ls)
862          enddo
863          deallocate(s%chars)
864
865          s%chars => ss
866
867          s%len = ls + lc
868          s%size = s%len
869      else
870          do i=ls+1,ls+lc
871              s%chars(i) = c(i-ls:i-ls)
872          enddo
873          s%len = ls + lc
874      endif
875
876      end subroutine append_to_string_c
877
878!*******************************************************************************
879!     INSERT_IN_STRING
880!*******************************************************************************
881
882      pure subroutine insert_in_string_s(s1,start,s2)
883
884      implicit none
885      type(string), intent(inout)  :: s1
886      type(string), intent(in)     :: s2
887      integer, intent(in)          :: start
888      integer                      :: i,ip,is,ls1,ls2
889
890      character, pointer           :: ss(:)
891
892
893      ls1 = len(s1)
894      ls2 = len(s2)
895      if (ls2 == 0) return
896      if (ls1+ls2 > string_size(s1)) then
897          allocate(ss(ls1+ls2))
898          is = max(start,1)
899          ip = min(ls1+1,is)
900          do i=1,ip-1
901              ss(i) = s1%chars(i)
902          enddo
903          do i=ip,ip+ls2-1
904              ss(i) = s2%chars(i-ip+1)
905          enddo
906          do i=ip+ls2,ls1+ls2
907              ss(i) = s1%chars(i-ls2)
908          enddo
909          deallocate(s1%chars)
910
911          s1%chars => ss
912
913          s1%len = ls1 + ls2
914          s1%size = s1%len
915      else
916          is = max(start,1)
917          ip = min(ls1+1,is)
918          do i=ls1+ls2,ip+ls2,-1
919              s1%chars(i) = s1%chars(i-ls2)
920          enddo
921          do i=ip,ip+ls2-1
922              s1%chars(i) = s2%chars(i-ip+1)
923          enddo
924          s1%len = ls1 + ls2
925      endif
926
927      end subroutine insert_in_string_s
928
929!*******************************************************************************
930
931      pure subroutine insert_in_string_c(s,start,c)
932
933      implicit none
934      type(string), intent(inout)  :: s
935      character(*), intent(in)     :: c
936      integer, intent(in)          :: start
937      integer                      :: i,ip,is,ls,lc
938
939      character, pointer           :: ss(:)
940
941
942
943      ls = len(s)
944      lc = len(c)
945      if (lc == 0) return
946      if (ls+lc > string_size(s)) then
947          allocate(ss(ls+lc))
948          is = max(start,1)
949          ip = min(ls+1,is)
950          do i=1,ip-1
951              ss(i) = s%chars(i)
952          enddo
953          do i=ip,ip+lc-1
954              ss(i) = c(i-ip+1:i-ip+1)
955          enddo
956          do i=ip+lc,ls+lc
957              ss(i) = s%chars(i-lc)
958          enddo
959          deallocate(s%chars)
960
961          s%chars => ss
962
963          s%len = ls + lc
964          s%size = s%len
965      else
966          is = max(start,1)
967          ip = min(ls+1,is)
968          do i=ls+lc,ip+lc,-1
969              s%chars(i) = s%chars(i-lc)
970          enddo
971          do i=ip,ip+lc-1
972              s%chars(i) = c(i-ip+1:i-ip+1)
973          enddo
974          s%len = ls + lc
975      endif
976
977      end subroutine insert_in_string_c
978
979!*******************************************************************************
980!     REPLACE_IN_STRING
981!*******************************************************************************
982!     pure subroutine replace_in_string_ss_s(s,start,ss)
983!
984!     implicit none
985!     type(string), intent(inout)  :: s
986!     type(string), intent(in)     :: ss
987!     integer, intent(in)          :: start
988!
989!
990!     call replace_in_string_sc_s(s,start,char(ss))
991!
992!     end subroutine replace_in_string_ss_s
993!*******************************************************************************
994
995!*******************************************************************************
996
997      pure subroutine replace_in_string_ss_s(s,start,ss)
998
999      implicit none
1000      type(string), intent(inout)  :: s
1001      type(string), intent(in)     :: ss
1002      integer, intent(in)          :: start
1003      integer                      :: i,ip,is,lr,lss,ls
1004      character, pointer           :: rs(:)
1005      logical                      :: new
1006
1007
1008      lr = lr_ss_s(s,start,ss)
1009      lss = len(ss)
1010      ls = len(s)
1011      is = max(start,1)
1012      ip = min(ls+1,is)
1013
1014      new = lr > string_size(s)
1015
1016      if (new) then
1017          allocate(rs(lr))
1018      else
1019          rs => s%chars
1020      endif
1021
1022      do i=lr,ip+lss,-1
1023          rs(i) = s%chars(i)
1024      enddo
1025      do i=lss,1,-1
1026          rs(ip-1+i) = ss%chars(i)
1027      enddo
1028      if (new) then
1029          do i=1,ip-1
1030              rs(i) = s%chars(i)
1031          enddo
1032      endif
1033
1034      if (new) then
1035          deallocate(s%chars)
1036          s%chars => rs
1037          s%size = lr
1038      else
1039          nullify(rs)
1040      endif
1041      s%len = lr
1042
1043      end subroutine replace_in_string_ss_s
1044
1045!*******************************************************************************
1046!     pure subroutine replace_in_string_ss_sf(s,start,finish,ss)
1047!
1048!     implicit none
1049!     type(string), intent(inout)  :: s
1050!     type(string), intent(in)     :: ss
1051!     integer, intent(in)          :: start,finish
1052!
1053!
1054!     call replace_in_string_sc_sf(s,start,finish,char(ss))
1055!
1056!     end subroutine replace_in_string_ss_sf
1057!*******************************************************************************
1058
1059!*******************************************************************************
1060
1061      pure subroutine replace_in_string_ss_sf(s,start,finish,ss)
1062
1063      implicit none
1064      type(string), intent(inout)  :: s
1065      type(string), intent(in)     :: ss
1066      integer, intent(in)          :: start,finish
1067      integer                      :: i,if,ip,is,lr,ls,lss
1068      character, pointer           :: rs(:)
1069      logical                      :: new
1070
1071
1072      lr = lr_ss_sf(s,start,finish,ss)
1073      lss = len(ss)
1074      ls = len(s)
1075      is = max(start,1)
1076      ip = min(ls+1,is)
1077      if = max(ip-1,min(finish,ls))
1078
1079      new = lr > string_size(s)
1080
1081      if (new) then
1082          allocate(rs(lr))
1083      else
1084          rs => s%chars
1085      endif
1086
1087      do i=1,lr-ip-lss+1
1088          rs(i+ip+lss-1) = s%chars(if+i)
1089      enddo
1090      do i=lss,1,-1
1091          rs(i+ip-1) = ss%chars(i)
1092      enddo
1093      if (new) then
1094          do i=1,ip-1
1095              rs(i) = s%chars(i)
1096          enddo
1097      endif
1098
1099      if (new) then
1100          deallocate(s%chars)
1101          s%chars => rs
1102          s%size = lr
1103      else
1104          nullify(rs)
1105      endif
1106      s%len = lr
1107
1108      end subroutine replace_in_string_ss_sf
1109
1110!*******************************************************************************
1111
1112!*******************************************************************************
1113
1114      pure subroutine replace_in_string_sc_s(s,start,c)
1115
1116      implicit none
1117      type(string), intent(inout)  :: s
1118      character(*), intent(in)     :: c
1119      integer, intent(in)          :: start
1120      integer                      :: i,ip,is,lc,lr,ls
1121      character, pointer           :: rs(:)
1122      logical                      :: new
1123
1124
1125      lr = lr_sc_s(s,start,c)
1126      lc = len(c)
1127      ls = len(s)
1128      is = max(start,1)
1129      ip = min(ls+1,is)
1130
1131      new = lr > string_size(s)
1132
1133      if (new) then
1134          allocate(rs(lr))
1135      else
1136          rs => s%chars
1137      endif
1138
1139      do i=lr,ip+lc,-1
1140          rs(i) = s%chars(i)
1141      enddo
1142      do i=lc,1,-1
1143          rs(ip-1+i) = c(i:i)
1144      enddo
1145      if (new) then
1146          do i=1,ip-1
1147              rs(i) = s%chars(i)
1148          enddo
1149      endif
1150
1151      if (new) then
1152          deallocate(s%chars)
1153          s%chars => rs
1154          s%size = lr
1155      else
1156          nullify(rs)
1157      endif
1158      s%len = lr
1159
1160      end subroutine replace_in_string_sc_s
1161
1162!*******************************************************************************
1163
1164!*******************************************************************************
1165
1166      pure subroutine replace_in_string_sc_sf(s,start,finish,c)
1167
1168      implicit none
1169      type(string), intent(inout)  :: s
1170      character(*), intent(in)     :: c
1171      integer, intent(in)          :: start,finish
1172      integer                      :: i,if,ip,is,lc,lr,ls
1173      character, pointer           :: rs(:)
1174      logical                      :: new
1175
1176
1177      lr = lr_sc_sf(s,start,finish,c)
1178      lc = len(c)
1179      ls = len(s)
1180      is = max(start,1)
1181      ip = min(ls+1,is)
1182      if = max(ip-1,min(finish,ls))
1183
1184      new = lr > string_size(s)
1185
1186      if (new) then
1187          allocate(rs(lr))
1188      else
1189          rs => s%chars
1190      endif
1191
1192      do i=1,lr-ip-lc+1
1193          rs(i+ip+lc-1) = s%chars(if+i)
1194      enddo
1195      do i=lc,1,-1
1196          rs(i+ip-1) = c(i:i)
1197      enddo
1198      if (new) then
1199          do i=1,ip-1
1200              rs(i) = s%chars(i)
1201          enddo
1202      endif
1203
1204      if (new) then
1205          deallocate(s%chars)
1206          s%chars => rs
1207          s%size = lr
1208      else
1209          nullify(rs)
1210      endif
1211      s%len = lr
1212
1213      end subroutine replace_in_string_sc_sf
1214
1215!*******************************************************************************
1216!*******************************************************************************
1217!*******************************************************************************
1218
1219      pure subroutine replace_in_string_scc(s,target,ss)
1220
1221      implicit none
1222      type(string), intent(inout)  :: s
1223      character(*), intent(in)     :: target,ss
1224
1225
1226      call x_replace_in_string_scc(s,target,ss,'first')
1227
1228
1229      end subroutine replace_in_string_scc
1230
1231!*******************************************************************************
1232
1233      pure subroutine replace_in_string_scc_f(s,target,ss,action)
1234
1235      implicit none
1236      type(string), intent(inout)  :: s
1237      character(*), intent(in)     :: target,ss,action
1238
1239
1240      call x_replace_in_string_scc(s,target,ss,action)
1241
1242      end subroutine replace_in_string_scc_f
1243
1244!*******************************************************************************
1245
1246      pure subroutine x_replace_in_string_scc(s,target,ss,action)
1247
1248      implicit none
1249      type(string), intent(inout)  :: s
1250      character(*), intent(in)     :: target,ss,action
1251      logical                      :: every,back
1252      integer                      :: lr,ls,lt,lss
1253      integer                      :: i,i1,i2,k1,k2,m1,m2
1254
1255      character, pointer           :: rs(:)
1256
1257
1258
1259      lr = lr_scc(s,target,ss,action)
1260      ls = len(s)
1261      lt = len(target)
1262      lss = len(ss)
1263
1264      if (lt == 0) then
1265          if (ls == 0) then
1266              do i=1,lss
1267                  s%chars(i) = ss(i:i)
1268              enddo
1269              s%len = lss
1270          endif
1271          return
1272      endif
1273
1274      select case(uppercase(action))
1275      case('FIRST')
1276          back = .false.
1277          every = .false.
1278      case('LAST')
1279          back = .true.
1280          every = .false.
1281      case('ALL')
1282          back = .false.
1283          every = .true.
1284      case default
1285          back = .false.
1286          every = .false.
1287      end select
1288
1289      allocate(rs(lr))
1290
1291      if (back) then
1292!         Backwards search
1293
1294!         k2 points to the absolute position one before the target in string
1295          k2 = ls
1296          m2 = lr
1297          do
1298!             find the next occurrence of target
1299              i1 = aindex(s%chars(:k2),target,back)
1300              if (i1 == 0) then
1301!                 fill up to the end
1302                  rs(:m2) = s%chars(:k2)
1303                  exit
1304              endif
1305!             i1 points to the absolute position of the first
1306!             letter of target in string
1307!             i2 points to the absolute position of the last
1308!             letter of target in string
1309              i2 = i1 + lt - 1
1310
1311!             copy the unaffected text string chunk after it
1312!             k1 points to the absolute position one after target in string
1313              k1 = i2 + 1
1314              m1 = m2 + k1 - k2
1315              rs(m1:m2) = s%chars(k1:k2)
1316              m2 = m1 - 1
1317              m1 = m2 - lss + 1
1318!             copy the replacement substring for target
1319              do i=1,lss
1320                  rs(m1+i-1) = ss(i:i)
1321              enddo
1322
1323!             k2 points to the absolute position one before the target in string
1324              k2 = i1 - 1
1325              m2 = m1 - 1
1326              if (.not.every) then
1327                  rs(:m2) = s%chars(:k2)
1328                  exit
1329              endif
1330          enddo
1331      else
1332!         Forward search
1333
1334!         k1 points to the absolute position one after target in string
1335          k1 = 1
1336          m1 = 1
1337          do
1338!             find the next occurrence of target
1339              i1 = aindex(s%chars(k1:),target)
1340              if (i1 == 0) then
1341!                 fill up to the end
1342                  rs(m1:lr) = s%chars(k1:ls)
1343                  exit
1344              endif
1345!             i1 points to the absolute position of the first
1346!             letter of target in string
1347              i1 = k1 + (i1 - 1)
1348!             i2 points to the absolute position of the last
1349!             letter of target in string
1350              i2 = i1 + lt - 1
1351
1352!             copy the unaffected text string chunk before it
1353!             k2 points to the absolute position one before the target in string
1354              k2 = i1 - 1
1355              m2 = m1 + k2 - k1
1356              rs(m1:m2) = s%chars(k1:k2)
1357              m1 = m2 + 1
1358              m2 = m1 + lss - 1
1359!             copy the replacement substring for target
1360              do i=1,lss
1361                  rs(m1+i-1) = ss(i:i)
1362              enddo
1363
1364!             k1 points to the absolute position one after target in string
1365              k1 = i2 + 1
1366              m1 = m2 + 1
1367              if (.not.every) then
1368                  rs(m1:lr) = s%chars(k1:ls)
1369                  exit
1370              endif
1371          enddo
1372      endif
1373
1374
1375      if (associated(s%chars)) deallocate(s%chars)
1376      s%chars => rs
1377
1378      s%len = lr
1379      s%size = size(s%chars)
1380
1381      end subroutine x_replace_in_string_scc
1382
1383!*******************************************************************************
1384
1385      pure subroutine replace_in_string_ssc(s,target,ss)
1386
1387      implicit none
1388      type(string), intent(inout)  :: s
1389      type(string), intent(in)     :: target
1390      character(*), intent(in)     :: ss
1391
1392
1393      call x_replace_in_string_scc(s,char(target),ss,'first')
1394
1395      end subroutine replace_in_string_ssc
1396
1397!*******************************************************************************
1398
1399      pure subroutine replace_in_string_ssc_f(s,target,ss,action)
1400
1401      implicit none
1402      type(string), intent(inout)  :: s
1403      type(string), intent(in)     :: target
1404      character(*), intent(in)     :: ss,action
1405
1406
1407      call x_replace_in_string_scc(s,char(target),ss,action)
1408
1409      end subroutine replace_in_string_ssc_f
1410
1411!*******************************************************************************
1412
1413      pure subroutine replace_in_string_scs(s,target,ss)
1414
1415      implicit none
1416      type(string), intent(inout)  :: s
1417      type(string), intent(in)     :: ss
1418      character(*), intent(in)     :: target
1419
1420
1421      call x_replace_in_string_scc(s,target,char(ss),'first')
1422
1423      end subroutine replace_in_string_scs
1424
1425!*******************************************************************************
1426
1427      pure subroutine replace_in_string_scs_f(s,target,ss,action)
1428
1429      implicit none
1430      type(string), intent(inout)  :: s
1431      type(string), intent(in)     :: ss
1432      character(*), intent(in)     :: target,action
1433
1434
1435      call x_replace_in_string_scc(s,target,char(ss),action)
1436
1437      end subroutine replace_in_string_scs_f
1438
1439!*******************************************************************************
1440
1441      pure subroutine replace_in_string_sss(s,target,ss)
1442
1443      implicit none
1444      type(string), intent(inout)  :: s
1445      type(string), intent(in)     :: ss,target
1446
1447
1448      call x_replace_in_string_scc(s,char(target),char(ss),'first')
1449
1450      end subroutine replace_in_string_sss
1451
1452!*******************************************************************************
1453
1454      pure subroutine replace_in_string_sss_f(s,target,ss,action)
1455
1456      implicit none
1457      type(string), intent(inout)  :: s
1458      type(string), intent(in)     :: ss,target
1459      character(*), intent(in)     :: action
1460
1461
1462      call x_replace_in_string_scc(s,char(target),char(ss),action)
1463
1464      end subroutine replace_in_string_sss_f
1465
1466!*******************************************************************************
1467!     REMOVE_FROM_STRING
1468!*******************************************************************************
1469
1470      pure subroutine remove_from_string(s,start,finish)
1471
1472      implicit none
1473      type(string), intent(inout)                      :: s
1474      integer, intent(in)                              :: start,finish
1475      integer                                          :: i,if,is,le,ls
1476
1477
1478      is = max(1,start)
1479      ls = len(s)
1480      if = min(ls,finish)
1481      if (if < is) return
1482
1483      le = if - is + 1            ! = len_extract
1484      do i=if+1,ls
1485          s%chars(i-le) = s%chars(i)
1486      enddo
1487      s%len = s%len - le
1488
1489      end subroutine remove_from_string
1490
1491!*******************************************************************************
1492!     UNSTRING procedure
1493!*******************************************************************************
1494!     Deallocate the chars in the string to avoid leaking of memory
1495!     Use this in functions and subroutines on locally declared variables
1496!     of type string after their use. (I.e. garbage collecting).
1497
1498      elemental subroutine unstring(s)
1499
1500      implicit none
1501      type(string), intent(inout)  :: s
1502
1503
1504
1505      if (associated(s%chars)) deallocate(s%chars)
1506      nullify(s%chars)
1507
1508      s%size = 0
1509      s%len = 0
1510
1511      end subroutine unstring
1512
1513!*******************************************************************************
1514!     //
1515!*******************************************************************************
1516!     string // string
1517
1518      pure function s_concat_s(s1,s2)
1519
1520      implicit none
1521      type(string), intent(in)    :: s1,s2
1522      character(len(s1)+len(s2))  :: s_concat_s
1523      integer                     :: l1,l2
1524
1525
1526      l1 = len(s1)
1527      l2 = len(s2)
1528      s_concat_s(1:l1) = s1
1529      s_concat_s(1+l1:l1+l2) = s2
1530
1531      end function s_concat_s
1532
1533!*******************************************************************************
1534!     string // character
1535
1536      pure function s_concat_c(s,c)
1537
1538      implicit none
1539      type(string), intent(in)  :: s
1540      character(*), intent(in)  :: c
1541      character(len(s)+len(c))  :: s_concat_c
1542      integer                   :: ls,lc
1543
1544
1545      ls = len(s)
1546      lc = len(c)
1547      s_concat_c(1:ls) = s
1548      s_concat_c(1+ls:ls+lc) = c
1549
1550      end function s_concat_c
1551
1552!*******************************************************************************
1553!     character // string
1554
1555      pure function c_concat_s(c,s)
1556
1557      implicit none
1558      character(*), intent(in)  :: c
1559      type(string), intent(in)  :: s
1560      character(len(s)+len(c))  :: c_concat_s
1561      integer                   :: lc,ls
1562
1563
1564      lc = len(c)
1565      ls = len(s)
1566      c_concat_s(1:lc) = c
1567      c_concat_s(1+lc:lc+ls) = s
1568
1569      end function c_concat_s
1570
1571!*******************************************************************************
1572!     REPEAT
1573!*******************************************************************************
1574
1575      function repeat_s(s,ncopies)
1576
1577      implicit none
1578      type(string), intent(in)   :: s
1579      integer, intent(in)        :: ncopies
1580      character(ncopies*len(s))  :: repeat_s
1581
1582
1583      if (ncopies < 0) stop 'Negative ncopies requested in REPEAT'
1584      repeat_s = repeat(char(s),ncopies)
1585
1586      end function repeat_s
1587
1588!*******************************************************************************
1589!     LEN_TRIM
1590!*******************************************************************************
1591
1592      elemental function len_trim_s(s)
1593
1594      implicit none
1595      type(string), intent(in)  :: s
1596      integer                   :: len_trim_s
1597
1598      if (len(s) == 0) then
1599        len_trim_s = 0
1600        return
1601      endif
1602      do len_trim_s = len(s),1,-1
1603          if (s%chars(len_trim_s) /= blank) return
1604      end do
1605
1606      end function len_trim_s
1607
1608!*******************************************************************************
1609!     TRIM
1610!*******************************************************************************
1611
1612      pure function trim_s(s)
1613
1614      implicit none
1615      type(string), intent(in)  :: s
1616      character(len_trim(s))    :: trim_s
1617      integer                   :: i
1618
1619
1620      do i=1,len(trim_s)
1621          trim_s(i:i) = s%chars(i)
1622      enddo
1623
1624      end function trim_s
1625
1626!*******************************************************************************
1627!     IACHAR
1628!*******************************************************************************
1629! Returns the position of the character string in the ISO 646 collating
1630! sequence. String must be of length one, otherwise result is as for
1631! intrinsic iachar.
1632
1633      elemental function iachar_s(s)
1634
1635      implicit none
1636      type(string), intent(in) :: s
1637      integer                  :: iachar_s
1638
1639
1640      iachar_s = iachar(char(s))
1641
1642      end function iachar_s
1643
1644!*******************************************************************************
1645!     ICHAR
1646!*******************************************************************************
1647! Returns the position of character from string in the processor collating
1648! sequence. String must be of length one, otherwise it will behave as the
1649! intrinsic ichar with the equivalent character string.
1650
1651      elemental function ichar_s(s)
1652
1653      implicit none
1654      type(string), intent(in) ::  s
1655      integer                  ::  ichar_s
1656
1657
1658      ichar_s = ichar(char(s))
1659
1660      end function ichar_s
1661
1662!*******************************************************************************
1663!     ADJUSTL
1664!*******************************************************************************
1665! Returns as a character variable the string adjusted to the left,
1666! removing leading blanks and inserting trailing blanks.
1667
1668      pure function adjustl_s(s)
1669
1670      implicit none
1671      type(string), intent(in)  :: s
1672      character(len(s))         :: adjustl_s
1673
1674
1675      adjustl_s = adjustl(char(s))
1676
1677      end function adjustl_s
1678
1679!*******************************************************************************
1680!     ADJUSTR
1681!*******************************************************************************
1682! Returns as a character variable the string adjusted to the right,
1683! removing trailing blanks and inserting leading blanks.
1684
1685      pure function adjustr_s(s)
1686
1687      implicit none
1688      type(string), intent(in)  :: s
1689      character(len(s))         :: adjustr_s
1690
1691
1692      adjustr_s = adjustr(char(s))
1693
1694      end function adjustr_s
1695
1696!*******************************************************************************
1697!    LEN_STRIP
1698!*******************************************************************************
1699
1700     elemental function len_strip_s(s)
1701
1702     implicit none
1703     type(string), intent(in) :: s
1704     integer                  :: len_strip_s
1705     integer                  :: i1,i2
1706
1707
1708     do i1=1,len(s)
1709         if (s%chars(i1) /= blank) exit
1710     enddo
1711     do i2=len(s),1,-1
1712         if (s%chars(i2) /= blank) exit
1713     enddo
1714     len_strip_s = max(0,i2-i1+1)
1715
1716     end function len_strip_s
1717
1718!*******************************************************************************
1719!    STRIP
1720!*******************************************************************************
1721
1722     pure function strip_s(s)
1723
1724     implicit none
1725     type(string), intent(in)  :: s
1726     character(len_strip(s))   :: strip_s
1727     integer                   :: i,j
1728
1729
1730     do i=1,len(s)
1731         if (s%chars(i) /= blank) exit
1732     enddo
1733     do j=1,len(strip_s)
1734         strip_s(j:j) = s%chars(i+j-1)
1735     enddo
1736
1737     end function strip_s
1738
1739!*******************************************************************************
1740
1741     elemental function len_strip_c(c)
1742
1743     implicit none
1744     character(*), intent(in) :: c
1745     integer                  :: len_strip_c
1746     integer                  :: i1,i2
1747
1748
1749     do i1=1,len(c)
1750         if (c(i1:i1) /= blank) exit
1751     enddo
1752     i2 = len_trim(c)
1753     len_strip_c = max(0,i2-i1+1)
1754
1755     end function len_strip_c
1756
1757!*******************************************************************************
1758
1759     pure function strip_c(c)
1760
1761     implicit none
1762     character(*), intent(in)  :: c
1763     character(len_strip(c))   :: strip_c
1764     integer                   :: i
1765
1766
1767     do i=1,len(c)
1768         if (c(i:i) /= blank) exit
1769     enddo
1770     strip_c(1:) = c(i:)
1771
1772     end function strip_c
1773
1774!*******************************************************************************
1775!     EXTRACT
1776!*******************************************************************************
1777      elemental FUNCTION len_extract_s(s,start,finish)
1778
1779      implicit none
1780      type(string), intent(in)  :: s
1781      integer, intent(in)       :: start,finish
1782      integer                   :: len_extract_s
1783      integer                   :: is,if
1784
1785
1786      is = max(1,start)
1787      if = min(len(s),finish)
1788      if (if < is) then
1789          len_extract_s = 0
1790      else
1791          len_extract_s = max(0,if-is) + 1
1792      endif
1793
1794      end function len_extract_s
1795
1796!*****************************************************
1797      pure function extract_s(s,start,finish)
1798
1799      implicit none
1800      type(string), intent(in)                  :: s
1801      integer, intent(in)                       :: start,finish
1802      character(len_extract_s(s,start,finish))  :: extract_s
1803      integer                                   :: i,is,if
1804
1805
1806      is = max(1,start)
1807      if = min(len(s),finish)
1808      if (if < is) then
1809          extract_s = ''
1810      else
1811          do i=1,max(0,if-is+1)
1812              extract_s(i:i) = s%chars(is+i-1)
1813          enddo
1814      endif
1815
1816      end function extract_s
1817
1818!*******************************************************************************
1819
1820!      elemental FUNCTION len_extract_s(s,start,finish)
1821
1822!      implicit none
1823!      type(string), intent(in)  :: s
1824!      integer, intent(in)       :: start,finish
1825!      integer                   :: len_extract_s
1826!      integer                   :: is,if
1827
1828
1829!      is = max(1,start)
1830!      if = min(len(s),finish)
1831!      if (if < is) then
1832!          len_extract_s = 0
1833!      else
1834!          len_extract_s = max(0,if-is) + 1
1835!      endif
1836
1837!      end function len_extract_s
1838
1839!*******************************************************************************
1840
1841      elemental function len_extract_c(c,start,finish)
1842
1843      implicit none
1844      character(*), intent(in)  :: c
1845      integer, intent(in)       :: start,finish
1846      integer                   :: len_extract_c
1847      integer                   :: is,if
1848
1849
1850      is = max(1,start)
1851      if = min(len(c),finish)
1852      if (if < is) then
1853          len_extract_c = 0
1854      else
1855          len_extract_c = max(0,if-is) + 1
1856      endif
1857
1858      end function len_extract_c
1859
1860!*******************************************************************************
1861
1862      pure function extract_c(c,start,finish)
1863
1864      implicit none
1865      character(*), intent(in)                  :: c
1866      integer, intent(in)                       :: start,finish
1867      character(len_extract_c(c,start,finish))  :: extract_c
1868      integer                                   :: is,if
1869
1870
1871      is = max(1,start)
1872      if = min(len(c),finish)
1873      if (if < is) then
1874          extract_c = ''
1875      else
1876          extract_c(1:if-is+1) = c(is:if)
1877      endif
1878
1879      end function extract_c
1880
1881!*******************************************************************************
1882
1883!      elemental function len_extract_c(c,start,finish)
1884
1885!      implicit none
1886!      character(*), intent(in)  :: c
1887!      integer, intent(in)       :: start,finish
1888!      integer                   :: len_extract_c
1889!      integer                   :: is,if
1890
1891
1892!      is = max(1,start)
1893!      if = min(len(c),finish)
1894!      if (if < is) then
1895!          len_extract_c = 0
1896!      else
1897!          len_extract_c = max(0,if-is) + 1
1898!      endif
1899
1900!      end function len_extract_c
1901
1902!*******************************************************************************
1903!     INSERT
1904!*******************************************************************************
1905
1906      pure function insert_ss(s1,start,s2)
1907
1908      implicit none
1909      type(string), intent(in)    :: s1,s2
1910      integer, intent(in)         :: start
1911      character(len(s1)+len(s2))  :: insert_ss
1912      integer                     :: i,ip,is,ls1,ls2
1913
1914
1915      ls1 = len(s1)
1916      ls2 = len(s2)
1917      is = max(start,1)
1918      ip = min(ls1+1,is)
1919      do i=1,ip-1
1920          insert_ss(i:i) = s1%chars(i)
1921      enddo
1922      do i=ip,ip+ls2-1
1923          insert_ss(i:i) = s2%chars(i-ip+1)
1924      enddo
1925      do i=ip+ls2,ls1+ls2
1926          insert_ss(i:i) = s1%chars(i-ls2)
1927      enddo
1928
1929      end function insert_ss
1930
1931!*******************************************************************************
1932
1933      pure function insert_sc(s1,start,c2)
1934
1935      implicit none
1936      type(string), intent(in)    :: s1
1937      character(*), intent(in)    :: c2
1938      integer, intent(in)         :: start
1939      character(len(s1)+len(c2))  :: insert_sc
1940      integer                     :: i,ip,is,ls1,ls2
1941
1942
1943      ls1 = len(s1)
1944      ls2 = len(c2)
1945      is = max(start,1)
1946      ip = min(ls1+1,is)
1947      do i=1,ip-1
1948          insert_sc(i:i) = s1%chars(i)
1949      enddo
1950      insert_sc(ip:ip+ls2-1) = c2
1951      do i=ip+ls2,ls1+ls2
1952          insert_sc(i:i) = s1%chars(i-ls2)
1953      enddo
1954
1955      end function insert_sc
1956
1957!*******************************************************************************
1958
1959      pure function insert_cs(c1,start,s2)
1960
1961      implicit none
1962      character(*), intent(in)    :: c1
1963      type(string), intent(in)    :: s2
1964      integer, intent(in)         :: start
1965      character(len(c1)+len(s2))  :: insert_cs
1966      integer                     :: i,ip,is,ls1,ls2
1967
1968
1969      ls1 = len(c1)
1970      ls2 = len(s2)
1971      is = max(start,1)
1972      ip = min(ls1+1,is)
1973      insert_cs(1:ip-1) = c1(1:ip-1)
1974      do i=ip,ip+ls2-1
1975          insert_cs(i:i) = s2%chars(i-ip+1)
1976      enddo
1977      insert_cs(ip+ls2:ls1+ls2) = c1(ip:ls1)
1978
1979      end function insert_cs
1980
1981!*******************************************************************************
1982
1983      pure function insert_cc(c1,start,c2)
1984
1985      implicit none
1986      character(*), intent(in)    :: c1,c2
1987      integer, intent(in)         :: start
1988      character(len(c1)+len(c2))  :: insert_cc
1989      integer                     :: ip,is,ls1,ls2
1990
1991
1992      ls1 = len(c1)
1993      ls2 = len(c2)
1994      is = max(start,1)
1995      ip = min(ls1+1,is)
1996      insert_cc(1:ip-1) = c1(1:ip-1)
1997      insert_cc(ip:ip+ls2-1) = c2
1998      insert_cc(ip+ls2:ls1+ls2) = c1(ip:ls1)
1999
2000      end function insert_cc
2001
2002!*******************************************************************************
2003!     REMOVE
2004!*******************************************************************************
2005
2006      pure function remove_c(c,start,finish)
2007
2008      implicit none
2009      character(*), intent(in)                         :: c
2010      integer, intent(in)                              :: start,finish
2011      character(len(c)-len_extract_c(c,start,finish))  :: remove_c
2012      integer                                          :: if,is,ls
2013
2014
2015      is = max(1,start)
2016      ls = len(c)
2017      if = min(ls,finish)
2018      if (if < is) then
2019          remove_c = c
2020      else
2021          remove_c = c(1:is-1) // c(if+1:)
2022      endif
2023
2024      end function remove_c
2025
2026!*******************************************************************************
2027
2028      pure function remove_s(s,start,finish)
2029
2030      implicit none
2031      type(string), intent(in)                         :: s
2032      integer, intent(in)                              :: start,finish
2033      character(len(s)-len_extract_s(s,start,finish))  :: remove_s
2034      integer                                          :: i,if,is,le,ls
2035
2036
2037      is = max(1,start)
2038      ls = len(s)
2039      if = min(ls,finish)
2040      if (if < is) then
2041           remove_s = s
2042      else
2043          le = if - is + 1
2044          do i=1,is-1
2045              remove_s(i:i) = s%chars(i)
2046          enddo
2047          do i=if+1,ls
2048              remove_s(i-le:i-le) = s%chars(i)
2049          enddo
2050      endif
2051
2052      end function remove_s
2053
2054!*******************************************************************************
2055!     REPLACE
2056!*******************************************************************************
2057
2058      pure function lr_cc_s(s,start,ss) result(l)
2059
2060      implicit none
2061      character(*), intent(in)  :: s,ss
2062      integer, intent(in)       :: start
2063      integer                   :: l
2064      integer                   :: ip,is,ls,lss
2065
2066
2067      l = max(len(s),min(len(s)+1,max(start,1)+len(ss)-1))
2068
2069      end function lr_cc_s
2070
2071!*******************************************************************************
2072!  Calculate the result string by the following actions:
2073!  Insert the characters from substring SS into string STR beginning
2074!  at position START replacing the following LEN(SUBSTRING) characters of
2075!  the string and enlarging string if necessary. If START is greater than
2076!  LEN(STRING) substring is simply appended to string by concatenation.
2077!  If START is less than 1, substring replaces characters in string
2078!  starting at 1
2079
2080      function replace_cc_s(s,start,ss) result(r)
2081
2082      implicit none
2083      character(*), intent(in)        :: s,ss
2084      integer, intent(in)             :: start
2085      character(lr_cc_s(s,start,ss))  :: r
2086      integer                         :: ip,is,l,lss,ls
2087
2088
2089      lss = len(ss)
2090      ls = len(s)
2091      is = max(start,1)
2092      ip = min(ls+1,is)
2093      l = len(r)
2094
2095      r(1:ip-1) = s(1:ip-1)
2096      r(ip:ip+lss-1) = ss
2097      r(ip+lss:l) = s(ip+lss:ls)
2098
2099      end function replace_cc_s
2100
2101!*******************************************************************************
2102
2103      pure function lr_cc_sf(s,start,finish,ss) result(l)
2104
2105      implicit none
2106      character(*), intent(in)  :: s,ss
2107      integer, intent(in)       :: start,finish
2108      integer                   :: l
2109      integer                   :: if,ip,is,ls,lss
2110
2111
2112      lss = len(ss)
2113      ls = len(s)
2114      is = max(start,1)
2115      ip = min(ls+1,is)
2116      if = max(ip-1,min(finish,ls))
2117      l = lss + ls - if+ip-1
2118
2119      end function lr_cc_sf
2120
2121!*******************************************************************************
2122!  Calculates the result string by the following actions:
2123!  Insert the substring SS into string STR beginning at position
2124!  START replacing the following FINISH-START+1 characters of the string
2125!  and enlarging or shrinking the string if necessary.
2126!  If start is greater than LEN(STRING) substring is simply appended to
2127!  string by concatenation. If START is less than 1, START = 1 is used.
2128!  If FINISH is greater than LEN(STRING), FINISH = LEN(STRING) is used.
2129!  If FINISH is less than START, substring is inserted before START.
2130
2131      function replace_cc_sf(s,start,finish,ss) result(r)
2132
2133      implicit none
2134      character(*), intent(in)                :: s,ss
2135      integer, intent(in)                     :: start,finish
2136      character(lr_cc_sf(s,start,finish,ss))  :: r
2137      integer                                 :: i,if,ip,is,l,ls,lss
2138
2139
2140      lss = len(ss)
2141      ls = len(s)
2142      is = max(start,1)
2143      ip = min(ls+1,is)
2144      if = max(ip-1,min(finish,ls))
2145      l = len(r)
2146
2147      r(1:ip-1) = s(1:ip-1)
2148      do i=1,lss
2149          r(i+ip-1:i+ip-1) = ss(i:i)
2150      enddo
2151      do i=1,l-ip-lss+1
2152          r(i+ip+lss-1:i+ip+lss-1) = s(if+i:if+i)
2153      enddo
2154
2155      end function replace_cc_sf
2156
2157!*******************************************************************************
2158
2159      pure function lr_cs_s(s,start,ss) result(l)
2160
2161      implicit none
2162      character(*), intent(in)  :: s
2163      type(string), intent(in)  :: ss
2164      integer, intent(in)       :: start
2165      integer                   :: l
2166      integer                   :: ip,is,ls,lss
2167
2168
2169      l = max(len(s),min(len(s)+1,max(start,1)+len(ss)-1))
2170
2171      end function lr_cs_s
2172
2173!*******************************************************************************
2174!  Calculate the result string by the following actions:
2175!  Insert the characters from substring SS into string STR beginning
2176!  at position START replacing the following LEN(SUBSTRING) characters of
2177!  the string and enlarging string if necessary. If START is greater than
2178!  LEN(STRING) substring is simply appended to string by concatenation.
2179!  If START is less than 1, substring replaces characters in string
2180!  starting at 1
2181
2182      function replace_cs_s(s,start,ss) result(r)
2183
2184      implicit none
2185      character(*), intent(in)        :: s
2186      type(string), intent(in)        :: ss
2187      integer, intent(in)             :: start
2188      character(lr_cs_s(s,start,ss))  :: r
2189      integer                         :: i,ip,is,l,lss,ls
2190
2191
2192      lss = len(ss)
2193      ls = len(s)
2194      is = max(start,1)
2195      ip = min(ls+1,is)
2196      l = len(r)
2197
2198      r(1:ip-1) = s(1:ip-1)
2199      r(ip:ip+lss-1) = transfer(ss%chars(1:lss),r(1:lss))
2200      r(ip+lss:l) = s(ip+lss:ls)
2201
2202      end function replace_cs_s
2203
2204!*******************************************************************************
2205
2206      pure function lr_cs_sf(s,start,finish,ss) result(l)
2207
2208      implicit none
2209      character(*), intent(in)  :: s
2210      type(string), intent(in)  :: ss
2211      integer, intent(in)       :: start,finish
2212      integer                   :: l
2213      integer                   :: if,ip,is,ls,lss
2214
2215
2216      lss = len(ss)
2217      ls = len(s)
2218      is = max(start,1)
2219      ip = min(ls+1,is)
2220      if = max(ip-1,min(finish,ls))
2221      l = lss + ls - if+ip-1
2222
2223      end function lr_cs_sf
2224
2225!*******************************************************************************
2226!  Calculates the result string by the following actions:
2227!  Insert the substring SS into string STR beginning at position
2228!  START replacing the following FINISH-START+1 characters of the string
2229!  and enlarging or shrinking the string if necessary.
2230!  If start is greater than LEN(STRING) substring is simply appended to
2231!  string by concatenation. If START is less than 1, START = 1 is used.
2232!  If FINISH is greater than LEN(STRING), FINISH = LEN(STRING) is used.
2233!  If FINISH is less than START, substring is inserted before START.
2234
2235      function replace_cs_sf(s,start,finish,ss) result(r)
2236
2237      implicit none
2238      character(*), intent(in)                :: s
2239      type(string), intent(in)                :: ss
2240      integer, intent(in)                     :: start,finish
2241      character(lr_cs_sf(s,start,finish,ss))  :: r
2242      integer                                 :: i,if,ip,is,l,ls,lss
2243
2244
2245      lss = len(ss)
2246      ls = len(s)
2247      is = max(start,1)
2248      ip = min(ls+1,is)
2249      if = max(ip-1,min(finish,ls))
2250      l = len(r)
2251
2252      r(1:ip-1) = s(1:ip-1)
2253
2254      r(i+ip:i+ip+lss-1) = transfer(ss%chars(1:lss),r(1:lss))
2255
2256      do i=1,lss
2257          r(i+ip-1:i+ip-1) = ss%chars(i)
2258      enddo
2259
2260      do i=1,l-ip-lss+1
2261          r(i+ip+lss-1:i+ip+lss-1) = s(if+i:if+i)
2262      enddo
2263
2264      end function replace_cs_sf
2265
2266!*******************************************************************************
2267
2268      pure function lr_sc_s(s,start,ss) result(l)
2269
2270      implicit none
2271      type(string), intent(in)  :: s
2272      character(*), intent(in)  :: ss
2273      integer, intent(in)       :: start
2274      integer                   :: l
2275      integer                   :: ip,is,ls,lss
2276
2277
2278      l = max(len(s),min(len(s)+1,max(start,1)+len(ss)-1))
2279
2280      end function lr_sc_s
2281
2282!*******************************************************************************
2283!  Calculate the result string by the following actions:
2284!  Insert the characters from substring SS into string STR beginning
2285!  at position START replacing the following LEN(SUBSTRING) characters of
2286!  the string and enlarging string if necessary. If START is greater than
2287!  LEN(STRING) substring is simply appended to string by concatenation.
2288!  If START is less than 1, substring replaces characters in string
2289!  starting at 1
2290
2291      function replace_sc_s(s,start,ss) result(r)
2292
2293      implicit none
2294      type(string), intent(in)        :: s
2295      character(*), intent(in)        :: ss
2296      integer, intent(in)             :: start
2297      character(lr_sc_s(s,start,ss))  :: r
2298      integer                         :: i,ip,is,l,lss,ls
2299
2300
2301      lss = len(ss)
2302      ls = len(s)
2303      is = max(start,1)
2304      ip = min(ls+1,is)
2305      l = len(r)
2306
2307      do i=1,ip-1
2308          r(i:i) = s%chars(i)
2309      enddo
2310
2311      do i=1,lss
2312          r(i+ip-1:i+ip-1) = ss(i:i)
2313      enddo
2314
2315      do i=ip+lss,l
2316          r(i:i) = s%chars(i)
2317      enddo
2318
2319      end function replace_sc_s
2320
2321!*******************************************************************************
2322
2323      pure function lr_sc_sf(s,start,finish,ss) result(l)
2324
2325      implicit none
2326      type(string), intent(in)  :: s
2327      character(*), intent(in)  :: ss
2328      integer, intent(in)       :: start,finish
2329      integer                   :: l
2330      integer                   :: if,ip,is,ls,lss
2331
2332
2333      lss = len(ss)
2334      ls = len(s)
2335      is = max(start,1)
2336      ip = min(ls+1,is)
2337      if = max(ip-1,min(finish,ls))
2338      l = lss + ls - if+ip-1
2339
2340      end function lr_sc_sf
2341
2342!*******************************************************************************
2343!  Calculates the result string by the following actions:
2344!  Insert the substring SS into string STR beginning at position
2345!  START replacing the following FINISH-START+1 characters of the string
2346!  and enlarging or shrinking the string if necessary.
2347!  If start is greater than LEN(STRING) substring is simply appended to
2348!  string by concatenation. If START is less than 1, START = 1 is used.
2349!  If FINISH is greater than LEN(STRING), FINISH = LEN(STRING) is used.
2350!  If FINISH is less than START, substring is inserted before START.
2351
2352      function replace_sc_sf(s,start,finish,ss) result(r)
2353
2354      implicit none
2355      type(string), intent(in)                :: s
2356      character(*), intent(in)                :: ss
2357      integer, intent(in)                     :: start,finish
2358      character(lr_sc_sf(s,start,finish,ss))  :: r
2359      integer                                 :: i,if,ip,is,l,ls,lss
2360
2361
2362      lss = len(ss)
2363      ls = len(s)
2364      is = max(start,1)
2365      ip = min(ls+1,is)
2366      if = max(ip-1,min(finish,ls))
2367      l = len(r)
2368
2369      do i=1,ip-1
2370          r(i:i) = s%chars(i)
2371      enddo
2372
2373      r(ip:ip+lss-1) = ss
2374
2375      do i=1,l-ip-lss+1
2376          r(i+ip+lss-1:i+ip+lss-1) = s%chars(if+i)
2377      enddo
2378
2379      end function replace_sc_sf
2380
2381!*******************************************************************************
2382
2383      pure function lr_ss_s(s,start,ss) result(l)
2384
2385      implicit none
2386      type(string), intent(in)  :: s,ss
2387      integer, intent(in)       :: start
2388      integer                   :: l
2389      integer                   :: ip,is,ls,lss
2390
2391
2392      l = max(len(s),min(len(s)+1,max(start,1)+len(ss)-1))
2393
2394      end function lr_ss_s
2395
2396!*******************************************************************************
2397!  Calculate the result string by the following actions:
2398!  Insert the characters from substring SS into string STR beginning
2399!  at position START replacing the following LEN(SUBSTRING) characters of
2400!  the string and enlarging string if necessary. If START is greater than
2401!  LEN(STRING) substring is simply appended to string by concatenation.
2402!  If START is less than 1, substring replaces characters in string
2403!  starting at 1
2404
2405      function replace_ss_s(s,start,ss) result(r)
2406
2407      implicit none
2408      type(string), intent(in)        :: s,ss
2409      integer, intent(in)             :: start
2410      character(lr_ss_s(s,start,ss))  :: r
2411      integer                         :: i,ip,is,l,lss,ls
2412
2413
2414      lss = len(ss)
2415      ls = len(s)
2416      is = max(start,1)
2417      ip = min(ls+1,is)
2418      l = len(r)
2419
2420      do i=1,ip-1
2421          r(i:i) = s%chars(i)
2422      enddo
2423
2424      do i=1,lss
2425          r(ip-1+i:ip-1+i) = ss%chars(i)
2426      enddo
2427
2428      do i=ip+lss,l
2429          r(i:i) = s%chars(i)
2430      enddo
2431
2432      end function replace_ss_s
2433
2434!*******************************************************************************
2435
2436      pure function lr_ss_sf(s,start,finish,ss) result(l)
2437
2438      implicit none
2439      type(string), intent(in)  :: s,ss
2440      integer, intent(in)       :: start,finish
2441      integer                   :: l
2442      integer                   :: if,ip,is,ls,lss
2443
2444
2445      lss = len(ss)
2446      ls = len(s)
2447      is = max(start,1)
2448      ip = min(ls+1,is)
2449      if = max(ip-1,min(finish,ls))
2450      l = lss + ls - if+ip-1
2451
2452      end function lr_ss_sf
2453
2454!*******************************************************************************
2455!  Calculates the result string by the following actions:
2456!  Insert the substring SS into string STR beginning at position
2457!  START replacing the following FINISH-START+1 characters of the string
2458!  and enlarging or shrinking the string if necessary.
2459!  If start is greater than LEN(STRING) substring is simply appended to
2460!  string by concatenation. If START is less than 1, START = 1 is used.
2461!  If FINISH is greater than LEN(STRING), FINISH = LEN(STRING) is used.
2462!  If FINISH is less than START, substring is inserted before START.
2463
2464      function replace_ss_sf(s,start,finish,ss) result(r)
2465
2466      implicit none
2467      type(string), intent(in)                :: s,ss
2468      integer, intent(in)                     :: start,finish
2469      character(lr_ss_sf(s,start,finish,ss))  :: r
2470      integer                                 :: i,if,ip,is,l,ls,lss
2471
2472
2473      lss = len(ss)
2474      ls = len(s)
2475      is = max(start,1)
2476      ip = min(ls+1,is)
2477      if = max(ip-1,min(finish,ls))
2478      l = len(r)
2479
2480      do i=1,ip-1
2481          r(i:i) = s%chars(i)
2482      enddo
2483
2484      do i=1,lss
2485          r(i+ip-1:i+ip-1) = ss%chars(i)
2486      enddo
2487
2488      do i=1,l-ip-lss+1
2489          r(i+ip+lss-1:i+ip+lss-1) = s%chars(if+i)
2490      enddo
2491
2492      end function replace_ss_sf
2493
2494!*******************************************************************************
2495
2496      pure function lr_ccc(s,target,ss,action) result(l)
2497
2498      implicit none
2499      character(*), intent(in)       :: s,target,ss,action
2500      integer                        :: l
2501      logical                        :: every,back
2502      integer                        :: ls,lt,lss,ipos,nr
2503
2504
2505      ls = len(s)
2506      lt = len(target)
2507      lss = len(ss)
2508
2509      if (lt == 0) then
2510          if (ls == 0) then
2511              l = lss
2512          else
2513              l = ls
2514          endif
2515          return
2516      endif
2517
2518      if (lt == lss) then
2519          l = ls
2520          return
2521      endif
2522
2523      select case(uppercase(action))
2524      case('FIRST')
2525          back = .false.
2526          every = .false.
2527      case('LAST')
2528          back = .true.
2529          every = .false.
2530      case('ALL')
2531          back = .false.
2532          every = .true.
2533      case default
2534          back = .false.
2535          every = .false.
2536      end select
2537
2538      nr = 0
2539      if (back) then
2540          ipos = ls
2541          do while (ipos > 0)
2542              ipos = index(s(:ipos),target,back)
2543              if (ipos == 0) exit
2544              nr = nr + 1
2545              if (.not. every) exit
2546              ipos = ipos - 1
2547          enddo
2548      else
2549          ipos = 1
2550          do while (ipos <= ls-lt+1)
2551              l = index(s(ipos:),target)
2552              if (l == 0) exit
2553              nr = nr + 1
2554              if (.not. every) exit
2555              ipos = ipos + l + 1
2556              ipos = ipos + 1
2557          enddo
2558      endif
2559      l = ls + nr*(lss-lt)
2560
2561      end function lr_ccc
2562
2563!*******************************************************************************
2564
2565      function replace_ccc(s,target,ss) result(r)
2566
2567      implicit none
2568      character(*), intent(in)                :: s,target,ss
2569      character(lr_ccc(s,target,ss,'first'))  :: r
2570
2571
2572      call x_replace_ccc(s,target,ss,'first',r)
2573
2574      end function replace_ccc
2575
2576!*******************************************************************************
2577
2578      function replace_ccc_f(s,target,ss,action) result(r)
2579
2580      implicit none
2581      character(*), intent(in)               :: s,target,ss,action
2582      character(lr_ccc(s,target,ss,action))  :: r
2583
2584
2585      call x_replace_ccc(s,target,ss,action,r)
2586
2587      end function replace_ccc_f
2588
2589!*******************************************************************************
2590!  Calculate the result string by the following actions:
2591!  Search for occurences of TARGET in string S, and replaces these with
2592!  substring SS.  If BACK present with value true search is backward otherwise
2593!  search is done forward.  If EVERY present with value true all accurences
2594!  of TARGET in S are replaced, otherwise only the first found is
2595!  replaced.  If TARGET is not found the result is the same as S.
2596
2597      subroutine x_replace_ccc(s,target,ss,action,r)
2598
2599      implicit none
2600      character(*), intent(in)               :: s,target,ss,action
2601      character(*), intent(inout)            :: r
2602      logical                                :: every,back
2603      integer                                :: lr,ls,lt,lss
2604      integer                                :: i1,i2,k1,k2,m1,m2
2605
2606
2607      lr = len(r)
2608      ls = len(s)
2609      lt = len(target)
2610      lss = len(ss)
2611
2612      if (lt == 0) then
2613          if (ls == 0) then
2614              r = ss
2615          else
2616              r = s
2617          endif
2618          return
2619      endif
2620
2621      select case(uppercase(action))
2622      case('FIRST')
2623          back = .false.
2624          every = .false.
2625      case('LAST')
2626          back = .true.
2627          every = .false.
2628      case('ALL')
2629          back = .false.
2630          every = .true.
2631      case default
2632          back = .false.
2633          every = .false.
2634      end select
2635
2636      if (back) then
2637          k2 = ls
2638          m2 = lr
2639          do
2640              i1 = index(s(:k2),target,back)
2641              if (i1 == 0) then
2642                  r(:m2) = s(:k2)
2643                  return
2644              endif
2645              i2 = i1 + lt - 1
2646              k1 = i2 + 1
2647              m1 = m2 + k1 - k2
2648              r(m1:m2) = s(k1:k2)
2649              m2 = m1 - 1
2650              m1 = m2 - lss + 1
2651              r(m1:m2) = ss
2652              k2 = i1 - 1
2653              m2 = m1 - 1
2654              if (.not. every) then
2655                  r(:m2) = s(:k2)
2656                  return
2657              endif
2658          enddo
2659      else
2660          k1 = 1
2661          m1 = 1
2662          do
2663              i1 = index(s(k1:),target)
2664              if (i1 == 0) then
2665                  r(m1:) = s(k1:)
2666                  return
2667              endif
2668              i1 = k1 + (i1 - 1)
2669              i2 = i1 + lt - 1
2670              k2 = i1 - 1
2671              m2 = m1 + k2 - k1
2672              r(m1:m2) = s(k1:k2)
2673              m1 = m2 + 1
2674              m2 = m1 + lss - 1
2675              r(m1:m2) = ss
2676              k1 = i2 + 1
2677              m1 = m2 + 1
2678              if (.not. every) then
2679                  r(m1:) = s(k1:)
2680                  return
2681              endif
2682          enddo
2683      endif
2684
2685      end subroutine x_replace_ccc
2686
2687!*******************************************************************************
2688
2689      function replace_csc(s,target,ss) result(r)
2690
2691      implicit none
2692      character(*), intent(in)                      :: s,ss
2693      type(string), intent(in)                      :: target
2694      character(lr_ccc(s,char(target),ss,'first'))  :: r
2695
2696
2697      call x_replace_ccc(s,char(target),ss,'first',r)
2698
2699      end function replace_csc
2700
2701!*******************************************************************************
2702
2703      function replace_csc_f(s,target,ss,action) result(r)
2704
2705      implicit none
2706      character(*), intent(in)                     :: s,ss,action
2707      type(string), intent(in)                     :: target
2708      character(lr_ccc(s,char(target),ss,action))  :: r
2709
2710
2711      call x_replace_ccc(s,char(target),ss,action,r)
2712
2713      end function replace_csc_f
2714
2715!*******************************************************************************
2716!*******************************************************************************
2717
2718      function replace_ccs(s,target,ss) result(r)
2719
2720      implicit none
2721      character(*), intent(in)                      :: s,target
2722      type(string), intent(in)                      :: ss
2723      character(lr_ccc(s,target,char(ss),'first'))  :: r
2724
2725
2726      call x_replace_ccc(s,target,char(ss),'first',r)
2727
2728      end function replace_ccs
2729
2730!*******************************************************************************
2731
2732      function replace_ccs_f(s,target,ss,action) result(r)
2733
2734      implicit none
2735      character(*), intent(in)                     :: s,target,action
2736      type(string), intent(in)                     :: ss
2737      character(lr_ccc(s,target,char(ss),action))  :: r
2738
2739
2740      call x_replace_ccc(s,target,char(ss),action,r)
2741
2742      end function replace_ccs_f
2743
2744!*******************************************************************************
2745!*******************************************************************************
2746
2747      function replace_css(s,target,ss) result(r)
2748
2749      implicit none
2750      character(*), intent(in)                            :: s
2751      type(string), intent(in)                            :: ss,target
2752      character(lr_ccc(s,char(target),char(ss),'first'))  :: r
2753
2754
2755      call x_replace_ccc(s,char(target),char(ss),'first',r)
2756
2757      end function replace_css
2758
2759!*******************************************************************************
2760
2761      function replace_css_f(s,target,ss,action) result(r)
2762
2763      implicit none
2764      character(*), intent(in)                           :: s,action
2765      type(string), intent(in)                           :: ss,target
2766      character(lr_ccc(s,char(target),char(ss),action))  :: r
2767
2768
2769      call x_replace_ccc(s,char(target),char(ss),action,r)
2770
2771      end function replace_css_f
2772
2773!*******************************************************************************
2774!*******************************************************************************
2775      pure function lr_scc(s,target,ss,action) result(l)
2776
2777      implicit none
2778      type(string), intent(in)       :: s
2779      character(*), intent(in)       :: target,ss,action
2780      integer                        :: l
2781      logical                        :: every,back
2782      integer                        :: ls,lt,lss,ipos,nr
2783
2784
2785      ls = len(s)
2786      lt = len(target)
2787      lss = len(ss)
2788
2789      if (lt == 0) then
2790          if (ls == 0) then
2791              l = lss
2792          else
2793              l = ls
2794          endif
2795          return
2796      endif
2797      if (lt == lss) then
2798          l = ls
2799          return
2800      endif
2801
2802      select case(uppercase(action))
2803      case('FIRST')
2804          back = .false.
2805          every = .false.
2806      case('LAST')
2807          back = .true.
2808          every = .false.
2809      case('ALL')
2810          back = .false.
2811          every = .true.
2812      case default
2813          back = .false.
2814          every = .false.
2815      end select
2816
2817      nr = 0
2818      if (back) then
2819          ipos = ls
2820          do while (ipos > 0)
2821              ipos = aindex(s%chars(:ipos),target,back)
2822              if (ipos == 0) exit
2823              nr = nr + 1
2824              if (.not. every) exit
2825              ipos = ipos - 1
2826          enddo
2827
2828      else
2829          ipos = 1
2830          do while (ipos <= ls-lt+1)
2831              l = aindex(s%chars(ipos:),target)
2832              if (l == 0) exit
2833              nr = nr + 1
2834              if (.not. every) exit
2835              ipos = ipos + l + 1
2836          enddo
2837      endif
2838      l = ls + nr*(lss-lt)
2839
2840      end function lr_scc
2841
2842!*******************************************************************************
2843
2844      function replace_scc(s,target,ss) result(r)
2845
2846      implicit none
2847      type(string), intent(in)                :: s
2848      character(*), intent(in)                :: target,ss
2849      character(lr_scc(s,target,ss,'first'))  :: r
2850
2851
2852      call x_replace_scc(s,target,ss,'first',r)
2853
2854
2855      end function replace_scc
2856
2857!*******************************************************************************
2858
2859      function replace_scc_f(s,target,ss,action) result(r)
2860
2861      implicit none
2862      type(string), intent(in)               :: s
2863      character(*), intent(in)               :: target,ss,action
2864      character(lr_scc(s,target,ss,action))  :: r
2865
2866
2867      call x_replace_scc(s,target,ss,action,r)
2868
2869      end function replace_scc_f
2870
2871!*******************************************************************************
2872!  Calculate the result string by the following actions:
2873!  Search for occurences of TARGET in string S, and replaces these with
2874!  substring SS.  If BACK present with value true search is backward otherwise
2875!  search is done forward.  If EVERY present with value true all accurences
2876!  of TARGET in S are replaced, otherwise only the first found is
2877!  replaced.  If TARGET is not found the result is the same as S.
2878
2879      subroutine x_replace_scc(s,target,ss,action,r)
2880
2881      implicit none
2882      type(string), intent(in)               :: s
2883      character(*), intent(in)               :: target,ss,action
2884      character(*), intent(inout)            :: r
2885      logical                                :: every,back
2886      integer                                :: lr,ls,lt,lss
2887      integer                                :: i1,i2,k1,k2,m1,m2
2888
2889
2890      lr = len(r)
2891      ls = len(s)
2892      lt = len(target)
2893      lss = len(ss)
2894
2895      if (lt == 0) then
2896          if (ls == 0) then
2897              r = ss
2898          else
2899              r = s
2900          endif
2901          return
2902      endif
2903
2904      select case(uppercase(action))
2905      case('FIRST')
2906          back = .false.
2907          every = .false.
2908      case('LAST')
2909          back = .true.
2910          every = .false.
2911      case('ALL')
2912          back = .false.
2913          every = .true.
2914      case default
2915          back = .false.
2916          every = .false.
2917      end select
2918
2919      if (back) then
2920          k2 = ls
2921          m2 = lr
2922          do
2923              i1 = aindex(s%chars(:k2),target,back)
2924              if (i1 == 0) then
2925                  r(:m2) = transfer(s%chars(:k2),r(:m2))
2926                  return
2927              endif
2928              i2 = i1 + lt - 1
2929              k1 = i2 + 1
2930              m1 = m2 + k1 - k2
2931              r(m1:m2) = transfer(s%chars(k1:k2),r(m1:m2))
2932              m2 = m1 - 1
2933              m1 = m2 - lss + 1
2934              r(m1:m2) = ss
2935              k2 = i1 - 1
2936              m2 = m1 - 1
2937              if (.not.every) then
2938                  r(:m2) = transfer(s%chars(:k2),r(:m2))
2939                  return
2940              endif
2941          enddo
2942      else
2943          k1 = 1
2944          m1 = 1
2945          do
2946              i1 = aindex(s%chars(k1:),target)
2947              if (i1 == 0) then
2948                  r(m1:) = transfer(s%chars(k1:),r(m1:))
2949                  return
2950              endif
2951              i1 = k1 + (i1 - 1)
2952              i2 = i1 + lt - 1
2953              k2 = i1 - 1
2954              m2 = m1 + k2 - k1
2955              r(m1:m2) = transfer(s%chars(k1:k2),r(m1:m2))
2956              m1 = m2 + 1
2957              m2 = m1 + lss - 1
2958              r(m1:m2) = ss
2959              k1 = i2 + 1
2960              m1 = m2 + 1
2961              if (.not.every) then
2962                  r(m1:) = transfer(s%chars(k1:),r(m1:))
2963                  return
2964              endif
2965          enddo
2966      endif
2967
2968      end subroutine x_replace_scc
2969
2970!*******************************************************************************
2971
2972      function replace_ssc(s,target,ss) result(r)
2973
2974      implicit none
2975      type(string), intent(in)                      :: s,target
2976      character(*), intent(in)                      :: ss
2977      character(lr_scc(s,char(target),ss,'first'))  :: r
2978
2979
2980      call x_replace_scc(s,char(target),ss,'first',r)
2981
2982
2983      end function replace_ssc
2984
2985!*******************************************************************************
2986
2987      function replace_ssc_f(s,target,ss,action) result(r)
2988
2989      implicit none
2990      type(string), intent(in)                     :: s,target
2991      character(*), intent(in)                     :: ss,action
2992      character(lr_scc(s,char(target),ss,action))  :: r
2993
2994
2995      call x_replace_scc(s,char(target),ss,action,r)
2996
2997      end function replace_ssc_f
2998
2999!*******************************************************************************
3000
3001      function replace_scs(s,target,ss) result(r)
3002
3003      implicit none
3004      type(string), intent(in)                      :: s,ss
3005      character(*), intent(in)                      :: target
3006      character(lr_scc(s,target,char(ss),'first'))  :: r
3007
3008
3009      call x_replace_scc(s,target,char(ss),'first',r)
3010
3011      end function replace_scs
3012
3013!*******************************************************************************
3014
3015      function replace_scs_f(s,target,ss,action) result(r)
3016
3017      implicit none
3018      type(string), intent(in)                     :: s,ss
3019      character(*), intent(in)                     :: target,action
3020      character(lr_scc(s,target,char(ss),action))  :: r
3021
3022
3023      call x_replace_scc(s,target,char(ss),action,r)
3024
3025      end function replace_scs_f
3026
3027!*******************************************************************************
3028
3029      function replace_sss(s,target,ss) result(r)
3030
3031      implicit none
3032      type(string), intent(in)                            :: s,ss,target
3033      character(lr_scc(s,char(target),char(ss),'first'))  :: r
3034
3035
3036      call x_replace_scc(s,char(target),char(ss),'first',r)
3037
3038      end function replace_sss
3039
3040!*******************************************************************************
3041
3042      function replace_sss_f(s,target,ss,action) result(r)
3043
3044      implicit none
3045      type(string), intent(in)                           :: s,ss,target
3046      character(*), intent(in)                           :: action
3047      character(lr_scc(s,char(target),char(ss),action))  :: r
3048
3049
3050      call x_replace_scc(s,char(target),char(ss),action,r)
3051
3052      end function replace_sss_f
3053
3054!*******************************************************************************
3055!     SORT, LSORT
3056!*******************************************************************************
3057!*******************************************************************************
3058! Sorts A into ascending order, from A(1) to A(N).
3059! Reference: Richard C. Singleton, Algorithm 347, SORT.
3060! Comm. ACM 3, 321 (March 1969).
3061! Algorithm is Copyright 1969 Association of Computing Machinery,
3062!*******************************************************************************
3063
3064      subroutine sort_c(a)
3065
3066      implicit none
3067      character(*), intent(inout)  :: a(:)
3068      character(len(a))            :: t,s
3069      integer                      :: p,i,j,k,l,m
3070      integer                      :: is(0:63)
3071
3072
3073      m = 0
3074      i = 1
3075      j = size(a)
3076
3077    5 continue
3078      if (i >= j) goto 70
3079
3080   10 continue
3081      p = (i + j)/2
3082      t = a(p)
3083      if (a(i) > t) then
3084          a(p) = a(i)
3085          a(i) = t
3086          t = a(p)
3087      endif
3088      if (a(j) < t) then
3089          a(p) = a(j)
3090          a(j) = t
3091          t = a(p)
3092          if (a(i) > t) then
3093              a(p) = a(i)
3094              a(i) = t
3095              t = a(p)
3096          endif
3097      endif
3098
3099      k = i
3100      l = j
3101      do
3102          do
3103              l = l - 1
3104              if (a(l) <= t) exit
3105          enddo
3106          s = a(l)
3107          do
3108              k = k + 1
3109              if (a(k) >= t) exit
3110          enddo
3111          if (k > l) exit
3112          a(l) = a(k)
3113          a(k) = s
3114      enddo
3115
3116      if (l-i > j-k) then
3117          is(m) = i
3118          m = m + 1
3119          is(m) = l
3120          m = m + 1
3121          i = k
3122      else
3123          is(m) = k
3124          m = m + 1
3125          is(m) = j
3126          m = m + 1
3127          j = l
3128      endif
3129      goto 80
3130
3131   70 continue
3132      if (m == 0) return
3133      m = m - 1
3134      j = is(m)
3135      m = m - 1
3136      i = is(m)
3137
3138   80 continue
3139      if (j-i >= 11) goto 10
3140      if (i == 1) goto 5
3141      i = i - 1
3142
3143      do
3144          i = i + 1
3145          if (i == j) goto 70
3146          t = a(i+1)
3147          if (a(i) <= t) cycle
3148          k = i
3149          do
3150              a(k+1) = a(k)
3151              k = k - 1
3152              if (t >= a(k)) exit
3153          enddo
3154          a(k+1) = t
3155      enddo
3156
3157      end subroutine sort_c
3158
3159!*******************************************************************************
3160! Sorts A into ascending order, from A(1) to A(N).
3161! Reference: Richard C. Singleton, Algorithm 347, SORT.
3162! Comm. ACM 3, 321 (March 1969).
3163! Algorithm is Copyright 1969 Association of Computing Machinery,
3164!*******************************************************************************
3165
3166      subroutine sort_s(a)
3167
3168      implicit none
3169      type(string), intent(inout)  :: a(:)
3170      type(string)                 :: s,t
3171      integer                      :: p,i,j,k,l,m
3172      integer                      :: is(0:63)
3173
3174
3175      m = 0
3176      i = 1
3177      j = size(a)
3178
3179    5 continue
3180      if (i >= j) goto 70
3181
3182   10 continue
3183      p = (i + j)/2
3184      call pstring(t,a(p))
3185      if (a(i) > t) then
3186          call pstring(a(p),a(i))
3187          call pstring(a(i),t)
3188          call pstring(t,a(p))
3189      endif
3190      if (a(j) < t) then
3191          call pstring(a(p),a(j))
3192          call pstring(a(j),t)
3193          call pstring(t,a(p))
3194          if (a(i) > t) then
3195              call pstring(a(p),a(i))
3196              call pstring(a(i),t)
3197              call pstring(t,a(p))
3198          endif
3199      endif
3200
3201      k = i
3202      l = j
3203      do
3204          do
3205              l = l - 1
3206              if (a(l) <= t) exit
3207          enddo
3208          call pstring(s,a(l))
3209          do
3210              k = k + 1
3211              if (a(k) >= t) exit
3212          enddo
3213          if (k > l) exit
3214          call pstring(a(l),a(k))
3215          call pstring(a(k),s)
3216      enddo
3217
3218      if (l-i > j-k) then
3219          is(m) = i
3220          m = m + 1
3221          is(m) = l
3222          m = m + 1
3223          i = k
3224      else
3225          is(m) = k
3226          m = m + 1
3227          is(m) = j
3228          m = m + 1
3229          j = l
3230      endif
3231      goto 80
3232
3233   70 continue
3234      if (m == 0) return
3235      m = m - 1
3236      j = is(m)
3237      m = m - 1
3238      i = is(m)
3239
3240   80 continue
3241      if (j-i >= 11) goto 10
3242      if (i == 1) goto 5
3243      i = i - 1
3244
3245      do
3246          i = i + 1
3247          if (i == j) goto 70
3248          call pstring(t,a(i+1))
3249          if (a(i) <= t) cycle
3250          k = i
3251          do
3252              call pstring(a(k+1),a(k))
3253              k = k - 1
3254              if (t >= a(k)) exit
3255          enddo
3256          call pstring(a(k+1),t)
3257      enddo
3258
3259      contains
3260
3261!-------------------------------------------------------------------------------
3262      subroutine pstring(p,t)
3263
3264      implicit none
3265      type(string), intent(inout)  :: p
3266      type(string), intent(in)     :: t
3267
3268
3269      p%len = t%len
3270      p%size = t%size
3271      p%chars => t%chars
3272
3273
3274      end subroutine pstring
3275!-------------------------------------------------------------------------------
3276
3277      end subroutine sort_s
3278
3279!*******************************************************************************
3280! Sorts A into ascending order, from A(1) to A(N).
3281! Reference: Richard C. Singleton, Algorithm 347, SORT.
3282! Comm. ACM 3, 321 (March 1969).
3283! Algorithm is Copyright 1969 Association of Computing Machinery,
3284! reproduced with permission.
3285!*******************************************************************************
3286
3287      subroutine lsort_c(a)
3288
3289      implicit none
3290      character(*), intent(inout)  :: a(:)
3291      character(len(a))            :: t,s
3292      integer                      :: p,i,j,k,l,m
3293      integer                      :: is(0:63)
3294
3295
3296      m = 0
3297      i = 1
3298      j = size(a)
3299
3300    5 continue
3301      if (i >= j) goto 70
3302
3303   10 continue
3304      p = (i + j)/2
3305      t = a(p)
3306      if (lgt(a(i),t)) then
3307          a(p) = a(i)
3308          a(i) = t
3309          t = a(p)
3310      endif
3311      if (llt(a(j),t)) then
3312          a(p) = a(j)
3313          a(j) = t
3314          t = a(p)
3315          if (lgt(a(i),t)) then
3316              a(p) = a(i)
3317              a(i) = t
3318              t = a(p)
3319          endif
3320      endif
3321
3322      k = i
3323      l = j
3324      do
3325          do
3326              l = l - 1
3327              if (lle(a(l),t)) exit
3328          enddo
3329          s = a(l)
3330          do
3331              k = k + 1
3332              if (lge(a(k),t)) exit
3333          enddo
3334          if (k > l) exit
3335          a(l) = a(k)
3336          a(k) = s
3337      enddo
3338
3339      if (l-i > j-k) then
3340          is(m) = i
3341          m = m + 1
3342          is(m) = l
3343          m = m + 1
3344          i = k
3345      else
3346          is(m) = k
3347          m = m + 1
3348          is(m) = j
3349          m = m + 1
3350          j = l
3351      endif
3352      goto 80
3353
3354   70 continue
3355      if (m == 0) return
3356      m = m - 1
3357      j = is(m)
3358      m = m - 1
3359      i = is(m)
3360
3361   80 continue
3362      if (j-i >= 11) goto 10
3363      if (i == 1) goto 5
3364      i = i - 1
3365
3366      do
3367          i = i + 1
3368          if (i == j) goto 70
3369          t = a(i+1)
3370          if (lle(a(i),t)) cycle
3371          k = i
3372          do
3373              a(k+1) = a(k)
3374              k = k - 1
3375              if (lge(t,a(k))) exit
3376          enddo
3377          a(k+1) = t
3378      enddo
3379
3380      end subroutine lsort_c
3381
3382!*******************************************************************************
3383! Sorts A into ascending order, from A(1) to A(N).
3384! Reference: Richard C. Singleton, Algorithm 347, SORT.
3385! Comm. ACM 3, 321 (March 1969).
3386! Algorithm is Copyright 1969 Association of Computing Machinery,
3387!*******************************************************************************
3388
3389      subroutine lsort_s(a)
3390
3391      implicit none
3392      type(string), intent(inout)  :: a(:)
3393      type(string)                 :: s,t
3394      integer                      :: p,i,j,k,l,m
3395      integer                      :: is(0:63)
3396
3397
3398      m = 0
3399      i = 1
3400      j = size(a)
3401
3402    5 continue
3403      if (i >= j) goto 70
3404
3405   10 continue
3406      p = (i + j)/2
3407      call pstring(t,a(p))
3408      if (lgt(a(i),t)) then
3409          call pstring(a(p),a(i))
3410          call pstring(a(i),t)
3411          call pstring(t,a(p))
3412      endif
3413      if (llt(a(j),t)) then
3414          call pstring(a(p),a(j))
3415          call pstring(a(j),t)
3416          call pstring(t,a(p))
3417          if (lgt(a(i),t)) then
3418              call pstring(a(p),a(i))
3419              call pstring(a(i),t)
3420              call pstring(t,a(p))
3421          endif
3422      endif
3423
3424      k = i
3425      l = j
3426      do
3427          do
3428              l = l - 1
3429              if (lle(a(l),t)) exit
3430          enddo
3431          call pstring(s,a(l))
3432          do
3433              k = k + 1
3434              if (lge(a(k),t)) exit
3435          enddo
3436          if (k > l) exit
3437          call pstring(a(l),a(k))
3438          call pstring(a(k),s)
3439      enddo
3440
3441      if (l-i > j-k) then
3442          is(m) = i
3443          m = m + 1
3444          is(m) = l
3445          m = m + 1
3446          i = k
3447      else
3448          is(m) = k
3449          m = m + 1
3450          is(m) = j
3451          m = m + 1
3452          j = l
3453      endif
3454      goto 80
3455
3456   70 continue
3457      if (m == 0) return
3458      m = m - 1
3459      j = is(m)
3460      m = m - 1
3461      i = is(m)
3462
3463   80 continue
3464      if (j-i >= 11) goto 10
3465      if (i == 1) goto 5
3466      i = i - 1
3467
3468      do
3469          i = i + 1
3470          if (i == j) goto 70
3471          call pstring(t,a(i+1))
3472          if (lle(a(i),t)) cycle
3473          k = i
3474          do
3475              call pstring(a(k+1),a(k))
3476              k = k - 1
3477              if (lge(t,a(k))) exit
3478          enddo
3479          call pstring(a(k+1),t)
3480      enddo
3481
3482      contains
3483
3484!-------------------------------------------------------------------------------
3485      subroutine pstring(p,t)
3486
3487      implicit none
3488      type(string), intent(inout)  :: p
3489      type(string), intent(in)     :: t
3490
3491
3492      p%len = t%len
3493      p%size = t%size
3494      p%chars => t%chars
3495
3496
3497      end subroutine pstring
3498!-------------------------------------------------------------------------------
3499
3500      end subroutine lsort_s
3501
3502!*******************************************************************************
3503!     RANK, LRANK
3504!*******************************************************************************
3505!*******************************************************************************
3506! Sorts A into ascending order, from A(1) to A(N).
3507! Reference: Richard C. Singleton, Algorithm 347, SORT.
3508! Comm. ACM 3, 321 (March 1969).
3509! Algorithm is Copyright 1969 Association of Computing Machinery,
3510! reproduced with permission.
3511!*******************************************************************************
3512
3513      subroutine rank_c(a,r)
3514
3515      implicit none
3516      character(*), intent(in)  :: a(:)
3517      integer, intent(out)      :: r(size(a))
3518      character(len(a))         :: t
3519      integer                   :: i,j,k,l,m,n,p,rs,rt
3520      integer                   :: is(0:63)
3521
3522
3523      n = size(a)
3524      r(:) = (/ (i, i=1,n) /)
3525      m = 0
3526      i = 1
3527      j = n
3528
3529    5 continue
3530      if (i >= j) goto 70
3531
3532   10 continue
3533      p = (j+i)/2
3534      rt = r(p)
3535      t = a(rt)
3536      if (a(r(i)) > t) then
3537          r(p) = r(i)
3538          r(i) = rt
3539          rt = r(p)
3540          t = a(rt)
3541      endif
3542      if (a(r(j)) < t) then
3543          r(p) = r(j)
3544          r(j) = rt
3545          rt = r(p)
3546          t = a(rt)
3547          if (a(r(i)) > t) then
3548              r(p) = r(i)
3549              r(i) = rt
3550              rt = r(p)
3551              t = a(rt)
3552          endif
3553      endif
3554
3555      k = i
3556      l = j
3557      do
3558          do
3559              l = l - 1
3560              if (a(r(l)) <= t) exit
3561          enddo
3562          rs = r(l)
3563          do
3564              k = k + 1
3565              if (a(r(k)) >= t) exit
3566          enddo
3567          if (k > l) exit
3568          r(l) = r(k)
3569          r(k) = rs
3570      enddo
3571
3572      if (l-i > j-k) then
3573          is(m) = i
3574          m = m + 1
3575          is(m) = l
3576          m = m + 1
3577          i = k
3578      else
3579          is(m) = k
3580          m = m + 1
3581          is(m) = j
3582          m = m + 1
3583          j = l
3584      endif
3585      goto 80
3586
3587   70 continue
3588      if (m == 0) return
3589      m = m - 1
3590      j = is(m)
3591      m = m - 1
3592      i = is(m)
3593
3594   80 continue
3595      if (j-i >= 11) goto 10
3596      if (i == 1) goto 5
3597      i = i - 1
3598
3599      do
3600          i = i + 1
3601          if (i == j) goto 70
3602          rt = r(i+1)
3603          t = a(rt)
3604          if (a(r(i)) <= t) cycle
3605          k = i
3606          do
3607              r(k+1) = r(k)
3608              k = k - 1
3609              if (t >= a(r(k))) exit
3610          enddo
3611          r(k+1) = rt
3612      enddo
3613
3614      end subroutine rank_c
3615
3616!*******************************************************************************
3617! Sorts A into ascending order, from A(1) to A(N).
3618! Reference: Richard C. Singleton, Algorithm 347, SORT.
3619! Comm. ACM 3, 321 (March 1969).
3620! Algorithm is Copyright 1969 Association of Computing Machinery,
3621!*******************************************************************************
3622
3623      subroutine rank_s(a,r)
3624
3625      implicit none
3626      type(string), intent(in)  :: a(:)
3627      integer, intent(out)      :: r(size(a))
3628      type(string)              :: t
3629      integer                   :: i,j,k,l,m,n,p,rs,rt
3630      integer                   :: is(0:63)
3631
3632
3633      n = size(a)
3634      r(:) = (/ (i, i=1,n) /)
3635      m = 0
3636      i = 1
3637      j = n
3638
3639    5 continue
3640      if (i >= j) goto 70
3641
3642   10 continue
3643      p = (j+i)/2
3644      rt = r(p)
3645      call pstring(t,a(rt))
3646      if (a(r(i)) > t) then
3647          r(p) = r(i)
3648          r(i) = rt
3649          rt = r(p)
3650          call pstring(t,a(rt))
3651      endif
3652      if (a(r(j)) < t) then
3653          r(p) = r(j)
3654          r(j) = rt
3655          rt = r(p)
3656          call pstring(t,a(rt))
3657          if (a(r(i)) > t) then
3658              r(p) = r(i)
3659              r(i) = rt
3660              rt = r(p)
3661              call pstring(t,a(rt))
3662          endif
3663      endif
3664
3665      k = i
3666      l = j
3667      do
3668          do
3669              l = l - 1
3670              if (a(r(l)) <= t) exit
3671          enddo
3672          rs = r(l)
3673          do
3674              k = k + 1
3675              if (a(r(k)) >= t) exit
3676          enddo
3677          if (k > l) exit
3678          r(l) = r(k)
3679          r(k) = rs
3680      enddo
3681
3682      if (l-i > j-k) then
3683          is(m) = i
3684          m = m + 1
3685          is(m) = l
3686          m = m + 1
3687          i = k
3688      else
3689          is(m) = k
3690          m = m + 1
3691          is(m) = j
3692          m = m + 1
3693          j = l
3694      endif
3695      goto 80
3696
3697   70 continue
3698      if (m == 0) return
3699      m = m - 1
3700      j = is(m)
3701      m = m - 1
3702      i = is(m)
3703
3704   80 continue
3705      if (j-i >= 11) goto 10
3706      if (i == 1) goto 5
3707      i = i - 1
3708
3709      do
3710          i = i + 1
3711          if (i == j) goto 70
3712          rt = r(i+1)
3713          call pstring(t,a(rt))
3714          if (a(r(i)) <= t) cycle
3715          k = i
3716          do
3717              r(k+1) = r(k)
3718              k = k - 1
3719              if (t >= a(r(k))) exit
3720          enddo
3721          r(k+1) = rt
3722      enddo
3723
3724      contains
3725
3726!-------------------------------------------------------------------------------
3727      subroutine pstring(p,t)
3728
3729      implicit none
3730      type(string), intent(inout)  :: p
3731      type(string), intent(in)     :: t
3732
3733
3734      p%len = t%len
3735      p%size = t%size
3736      p%chars => t%chars
3737
3738
3739      end subroutine pstring
3740!-------------------------------------------------------------------------------
3741
3742      end subroutine rank_s
3743
3744!*******************************************************************************
3745! Sorts A into ascending order, from A(1) to A(N).
3746! Reference: Richard C. Singleton, Algorithm 347, SORT.
3747! Comm. ACM 3, 321 (March 1969).
3748! Algorithm is Copyright 1969 Association of Computing Machinery,
3749!*******************************************************************************
3750
3751      subroutine lrank_c(a,r)
3752
3753      implicit none
3754      character(*), intent(in)  :: a(:)
3755      integer, intent(out)      :: r(size(a))
3756      character(len(a))         :: t
3757      integer                   :: i,j,k,l,m,n,p,rs,rt
3758      integer                   :: is(0:63)
3759
3760
3761      n = size(a)
3762      r(:) = (/ (i, i=1,n) /)
3763      m = 0
3764      i = 1
3765      j = n
3766
3767    5 continue
3768      if (i >= j) goto 70
3769
3770   10 continue
3771      p = (j+i)/2
3772      rt = r(p)
3773      t = a(rt)
3774      if (lgt(a(r(i)),t)) then
3775          r(p) = r(i)
3776          r(i) = rt
3777          rt = r(p)
3778          t = a(rt)
3779      endif
3780      if (llt(a(r(j)),t)) then
3781          r(p) = r(j)
3782          r(j) = rt
3783          rt = r(p)
3784          t = a(rt)
3785          if (llt(a(r(i)),t)) then
3786              r(p) = r(i)
3787              r(i) = rt
3788              rt = r(p)
3789              t = a(rt)
3790          endif
3791      endif
3792
3793      k = i
3794      l = j
3795      do
3796          do
3797              l = l - 1
3798              if (lle(a(r(l)),t)) exit
3799          enddo
3800          rs = r(l)
3801          do
3802              k = k + 1
3803              if (lge(a(r(k)),t)) exit
3804          enddo
3805          if (k > l) exit
3806          r(l) = r(k)
3807          r(k) = rs
3808      enddo
3809
3810      if (l-i > j-k) then
3811          is(m) = i
3812          m = m + 1
3813          is(m) = l
3814          m = m + 1
3815          i = k
3816      else
3817          is(m) = k
3818          m = m + 1
3819          is(m) = j
3820          m = m + 1
3821          j = l
3822      endif
3823      goto 80
3824
3825   70 continue
3826      if (m == 0) return
3827      m = m - 1
3828      j = is(m)
3829      m = m - 1
3830      i = is(m)
3831
3832   80 continue
3833      if (j-i >= 11) goto 10
3834      if (i == 1) goto 5
3835      i = i - 1
3836
3837      do
3838          i = i + 1
3839          if (i == j) goto 70
3840          rt = r(i+1)
3841          t = a(rt)
3842          if (lle(a(r(i)),t)) cycle
3843          k = i
3844          do
3845              r(k+1) = r(k)
3846              k = k - 1
3847              if (lge(t,a(r(k)))) exit
3848          enddo
3849          r(k+1) = rt
3850      enddo
3851
3852      end subroutine lrank_c
3853
3854!*******************************************************************************
3855! Sorts A into ascending order, from A(1) to A(N).
3856! Reference: Richard C. Singleton, Algorithm 347, SORT.
3857! Comm. ACM 3, 321 (March 1969).
3858! Algorithm is Copyright 1969 Association of Computing Machinery,
3859!*******************************************************************************
3860
3861      subroutine lrank_s(a,r)
3862
3863      implicit none
3864      type(string), intent(in)  :: a(:)
3865      integer, intent(out)      :: r(size(a))
3866      type(string)              :: t
3867      integer                   :: i,j,k,l,m,n,p,rs,rt
3868      integer                   :: is(0:63)
3869
3870
3871      n = size(a)
3872      r(:) = (/ (i, i=1,n) /)
3873      m = 0
3874      i = 1
3875      j = n
3876
3877    5 continue
3878      if (i >= j) goto 70
3879
3880   10 continue
3881      p = (j+i)/2
3882      rt = r(p)
3883      call pstring(t,a(rt))
3884      if (lgt(a(r(i)),t)) then
3885          r(p) = r(i)
3886          r(i) = rt
3887          rt = r(p)
3888          call pstring(t,a(rt))
3889      endif
3890      if (llt(a(r(j)),t)) then
3891          r(p) = r(j)
3892          r(j) = rt
3893          rt = r(p)
3894          call pstring(t,a(rt))
3895          if (lgt(a(r(i)),t)) then
3896              r(p) = r(i)
3897              r(i) = rt
3898              rt = r(p)
3899              call pstring(t,a(rt))
3900          endif
3901      endif
3902
3903      k = i
3904      l = j
3905      do
3906          do
3907              l = l - 1
3908              if (lle(a(r(l)),t)) exit
3909          enddo
3910          rs = r(l)
3911          do
3912              k = k + 1
3913              if (lge(a(r(k)),t)) exit
3914          enddo
3915          if (k > l) exit
3916          r(l) = r(k)
3917          r(k) = rs
3918      enddo
3919
3920      if (l-i > j-k) then
3921          is(m) = i
3922          m = m + 1
3923          is(m) = l
3924          m = m + 1
3925          i = k
3926      else
3927          is(m) = k
3928          m = m + 1
3929          is(m) = j
3930          m = m + 1
3931          j = l
3932      endif
3933      goto 80
3934
3935   70 continue
3936      if (m == 0) return
3937      m = m - 1
3938      j = is(m)
3939      m = m - 1
3940      i = is(m)
3941
3942   80 continue
3943      if (j-i >= 11) goto 10
3944      if (i == 1) goto 5
3945      i = i - 1
3946
3947      do
3948          i = i + 1
3949          if (i == j) goto 70
3950          rt = r(i+1)
3951          call pstring(t,a(rt))
3952          if (lle(a(r(i)),t)) cycle
3953          k = i
3954          do
3955              r(k+1) = r(k)
3956              k = k - 1
3957              if (lge(t,a(r(k)))) exit
3958          enddo
3959          r(k+1) = rt
3960      enddo
3961
3962      contains
3963
3964!-------------------------------------------------------------------------------
3965      subroutine pstring(p,t)
3966
3967      implicit none
3968      type(string), intent(inout)  :: p
3969      type(string), intent(in)     :: t
3970
3971
3972      p%len = t%len
3973      p%size = t%size
3974      p%chars => t%chars
3975
3976
3977      end subroutine pstring
3978!-------------------------------------------------------------------------------
3979
3980      end subroutine lrank_s
3981
3982!*******************************************************************************
3983!     COMPARE, LCOMPARE, ACOMPARE, ALCOMPARE
3984!*******************************************************************************
3985!*******************************************************************************
3986
3987      elemental function compare_ss(s1,s2) result(css)
3988
3989      implicit none
3990      type(string), intent(in)  :: s1,s2
3991      character(2)              :: css
3992      integer                   :: i,l1,l2
3993
3994
3995      l1 = len(s1)
3996      l2 = len(s2)
3997      do i=1,min(l1,l2)
3998          if (s1%chars(i) < s2%chars(i)) then
3999              css = 'LT'
4000              return
4001          elseif (s1%chars(i) > s2%chars(i)) then
4002              css = 'GT'
4003              return
4004          endif
4005      enddo
4006      if (l1 < l2) then
4007          do i=l1+1,l2
4008              if (blank < s2%chars(i)) then
4009                  css = 'LT'
4010                  return
4011              elseif (blank > s2%chars(i)) then
4012                  css = 'GT'
4013                  return
4014              endif
4015          enddo
4016      elseif (l1 > l2) then
4017          do i=l2+1,l1
4018              if (s1%chars(i) < blank) then
4019                  css = 'LT'
4020                  return
4021              elseif (s1%chars(i) > blank) then
4022                  css = 'GT'
4023                  return
4024              endif
4025          enddo
4026      endif
4027      css = 'EQ'
4028
4029      end function compare_ss
4030
4031!*******************************************************************************
4032
4033      elemental function compare_cs(c,s) result(css)
4034
4035      implicit none
4036      character(*), intent(in)  :: c
4037      type(string), intent(in)  :: s
4038      character(2)              :: css
4039      integer                   :: i,lc,ls
4040
4041
4042      lc = len(c)
4043      ls = len(s)
4044      do i=1,min(lc,ls)
4045          if (c(i:i) < s%chars(i)) then
4046              css = 'LT'
4047              return
4048          elseif (c(i:i) > s%chars(i)) then
4049              css = 'GT'
4050              return
4051          endif
4052      enddo
4053      if (lc < ls) then
4054          do i=lc+1,ls
4055              if (blank < s%chars(i)) then
4056                  css = 'LT'
4057                  return
4058              elseif (blank > s%chars(i)) then
4059                  css = 'GT'
4060                  return
4061              endif
4062          enddo
4063      elseif (lc > ls) then
4064          do i=ls+1,lc
4065              if (c(i:i) < blank) then
4066                  css = 'LT'
4067                  return
4068              elseif (c(i:i) > blank) then
4069                  css = 'GT'
4070                  return
4071              endif
4072          enddo
4073      endif
4074      css = 'EQ'
4075
4076      end function compare_cs
4077
4078!*******************************************************************************
4079!     ==
4080!*******************************************************************************
4081! string == string
4082
4083      elemental function s_eq_s(s1,s2)
4084
4085      implicit none
4086      type(string), intent(in)  :: s1,s2
4087      logical                   :: s_eq_s
4088      integer                   :: l1,l2
4089
4090
4091      l1 = len(s1)
4092      l2 = len(s2)
4093      if (l1 > l2) then
4094          s_eq_s = all(s1%chars(1:l2) == s2%chars) .and.  &
4095                   all(s1%chars(l2+1:l1) == blank)
4096      elseif (l1 < l2) then
4097          s_eq_s = all(s1%chars == s2%chars(1:l1)) .and.  &
4098                   all(blank == s2%chars(l1+1:l2))
4099      else
4100          s_eq_s = all(s1%chars == s2%chars)
4101      endif
4102
4103      end function s_eq_s
4104
4105!*******************************************************************************
4106! string == character
4107
4108      elemental function s_eq_c(s,c)
4109
4110      implicit none
4111      type(string), intent(in)  :: s
4112      character(*), intent(in)  :: c
4113      logical                   :: s_eq_c
4114      integer                   :: i,ls,lc
4115
4116
4117      ls = len(s)
4118      lc = len(c)
4119      do i=1,min(ls,lc)
4120          if (s%chars(i) /= c(i:i)) then
4121              s_eq_c = .false.
4122              return
4123          endif
4124      enddo
4125      if ((ls > lc) .and. any(s%chars(lc+1:ls) /= blank)) then
4126          s_eq_c = .false.
4127      elseif ((ls < lc) .and. (blank /= c(ls+1:lc))) then
4128          s_eq_c = .false.
4129      else
4130          s_eq_c = .true.
4131      endif
4132
4133      end function s_eq_c
4134
4135!*******************************************************************************
4136! character == string
4137
4138      elemental function c_eq_s(c,s)
4139
4140      implicit none
4141      character(*), intent(in)  :: c
4142      type(string), intent(in)  :: s
4143      logical                   :: c_eq_s
4144      integer                   :: i,lc,ls
4145
4146
4147      lc = len(c)
4148      ls = len(s)
4149      do i=1,min(lc,ls)
4150          if (c(i:i) /= s%chars(i)) then
4151              c_eq_s = .false.
4152              return
4153          endif
4154      enddo
4155      if ((lc > ls) .and. (c(ls+1:lc) /= blank)) then
4156          c_eq_s = .false.
4157      elseif ((lc < ls) .and. any(blank /= s%chars(lc+1:ls) ) )then
4158          c_eq_s = .false.
4159      else
4160          c_eq_s = .true.
4161      endif
4162
4163      end function c_eq_s
4164
4165!*******************************************************************************
4166!     /=
4167!*******************************************************************************
4168! string /= string
4169
4170      elemental function s_ne_s(s1,s2)
4171
4172      implicit none
4173      type(string), intent(in)  :: s1,s2
4174      logical                   :: s_ne_s
4175      integer                   :: l1,l2
4176
4177
4178      l1 = len(s1)
4179      l2 = len(s2)
4180      if (l1 > l2) then
4181          s_ne_s = any(s1%chars(1:l2) /= s2%chars) .or.  &
4182                   any(s1%chars(l2+1:l1) /= blank)
4183      elseif (l1 < l2) then
4184          s_ne_s = any(s1%chars /= s2%chars(1:l1)) .or. &
4185                   any(blank /= s2%chars(l1+1:l2))
4186      else
4187          s_ne_s = any(s1%chars /= s2%chars)
4188      endif
4189
4190      end function s_ne_s
4191
4192!*******************************************************************************
4193! string /= character
4194
4195      elemental function s_ne_c(s,c)
4196
4197      implicit none
4198      type(string), intent(in)  :: s
4199      character(*), intent(in)  :: c
4200      logical                   :: s_ne_c
4201      integer                   :: i,ls,lc
4202
4203
4204      ls = len(s)
4205      lc = len(c)
4206      do i=1,min(ls,lc)
4207          if (s%chars(i) /= c(i:i) )then
4208              s_ne_c = .true.
4209              return
4210          endif
4211      enddo
4212      if ((ls > lc) .and. any(s%chars(ls+1:lc) /= blank)) then
4213          s_ne_c = .true.
4214      elseif ((ls < lc) .and. blank /= c(ls+1:lc)) then
4215          s_ne_c = .true.
4216      else
4217          s_ne_c = .false.
4218      endif
4219
4220      end function s_ne_c
4221
4222!*******************************************************************************
4223! character /= string
4224
4225      elemental function c_ne_s(c,s)
4226
4227      implicit none
4228      character(*), intent(in)  :: c
4229      type(string), intent(in)  :: s
4230      logical                   :: c_ne_s
4231      integer                   :: i,lc,ls
4232
4233
4234      lc = len(c)
4235      ls = len(s)
4236      do i=1,min(lc,ls)
4237          if (c(i:i) /= s%chars(i)) then
4238              c_ne_s = .true.
4239              return
4240          endif
4241      enddo
4242      if ((lc > ls) .and. c(ls+1:lc) /= blank) then
4243          c_ne_s = .true.
4244      elseif ((lc < ls) .and. any(blank /= s%chars(lc+1:ls))) then
4245          c_ne_s = .true.
4246      else
4247          c_ne_s = .false.
4248      endif
4249
4250      end function c_ne_s
4251
4252!*******************************************************************************
4253!     < operators
4254!*******************************************************************************
4255! string < string
4256
4257      elemental function s_lt_s(s1,s2)
4258
4259      implicit none
4260      type(string), intent(in)  :: s1,s2
4261      logical                   :: s_lt_s
4262
4263
4264      s_lt_s = compare_ss(s1,s2) == 'LT'
4265
4266      end function s_lt_s
4267
4268!*******************************************************************************
4269! string < character
4270
4271      elemental function s_lt_c(s,c)
4272
4273      implicit none
4274      type(string), intent(in)  :: s
4275      character(*), intent(in)  :: c
4276      logical                   :: s_lt_c
4277
4278
4279      s_lt_c = compare_cs(c,s) == 'GT'
4280
4281      end function s_lt_c
4282
4283!*******************************************************************************
4284! character < string
4285
4286      elemental function c_lt_s(c,s)
4287
4288      implicit none
4289      character(*), intent(in)  :: c
4290      type(string), intent(in)  :: s
4291      logical                   :: c_lt_s
4292
4293
4294      c_lt_s = compare_cs(c,s) == 'LT'
4295
4296      end function c_lt_s
4297
4298!*******************************************************************************
4299!     <=  operators
4300!*******************************************************************************
4301! string <= string
4302
4303      elemental function s_le_s(s1,s2)
4304
4305      implicit none
4306      type(string), intent(in)  :: s1,s2
4307      logical                   :: s_le_s
4308
4309
4310      s_le_s = compare_ss(s1,s2) /= 'GT'
4311
4312      end function s_le_s
4313
4314!*******************************************************************************
4315! string <= character
4316
4317      elemental function s_le_c(s,c)
4318
4319      implicit none
4320      type(string), intent(in)  :: s
4321      character(*), intent(in)  :: c
4322      logical                   :: s_le_c
4323
4324
4325      s_le_c = compare_cs(c,s) /= 'LT'
4326
4327      end function s_le_c
4328
4329!*******************************************************************************
4330! character <= string
4331
4332      elemental function c_le_s(c,s)
4333
4334      implicit none
4335      character(*), intent(in)  :: c
4336      type(string), intent(in)  :: s
4337      logical                   :: c_le_s
4338
4339
4340      c_le_s = compare_cs(c,s) /= 'GT'
4341
4342      end function c_le_s
4343
4344!*******************************************************************************
4345!     >=  operators
4346!*******************************************************************************
4347! string >= string
4348
4349      elemental function s_ge_s(s1,s2)
4350
4351      implicit none
4352      type(string), intent(in) :: s1,s2
4353      logical                  :: s_ge_s
4354
4355
4356      s_ge_s = compare_ss(s1,s2) /= 'LT'
4357
4358      end function s_ge_s
4359
4360!*******************************************************************************
4361! string >= character
4362
4363      elemental function s_ge_c(s,c)
4364
4365      implicit none
4366      type(string), intent(in)  :: s
4367      character(*), intent(in)  :: c
4368      logical                   :: s_ge_c
4369
4370
4371      s_ge_c = compare_cs(c,s) /= 'GT'
4372
4373      end function s_ge_c
4374
4375!*******************************************************************************
4376! character >= string
4377
4378      elemental function c_ge_s(c,s)
4379
4380      implicit none
4381      character(*), intent(in)  :: c
4382      type(string), intent(in)  :: s
4383      logical                   :: c_ge_s
4384
4385
4386      c_ge_s = compare_cs(c,s) /= 'LT'
4387
4388      end function c_ge_s
4389
4390!*******************************************************************************
4391!     >  operators
4392!*******************************************************************************
4393! string > string
4394
4395      elemental function s_gt_s(s1,s2)
4396
4397      implicit none
4398      type(string), intent(in) :: s1,s2
4399      logical                  :: s_gt_s
4400
4401
4402      s_gt_s = compare_ss(s1,s2) == 'GT'
4403
4404      end function s_gt_s
4405
4406!*******************************************************************************
4407! string > character
4408
4409      elemental function s_gt_c(s,c)
4410
4411      implicit none
4412      type(string), intent(in)  :: s
4413      character(*), intent(in)  :: c
4414      logical                   :: s_gt_c
4415
4416
4417      s_gt_c = compare_cs(c,s) == 'LT'
4418
4419      end function s_gt_c
4420
4421!*******************************************************************************
4422! character > string
4423
4424      elemental function c_gt_s(c,s)
4425
4426      implicit none
4427      character(*), intent(in)  :: c
4428      type(string), intent(in)  :: s
4429      logical                   :: c_gt_s
4430
4431
4432      c_gt_s = compare_cs(c,s) == 'GT'
4433
4434      end function c_gt_s
4435
4436!*******************************************************************************
4437
4438      elemental function lcompare_ss(s1,s2) result(css)
4439
4440      implicit none
4441      type(string), intent(in)  :: s1,s2
4442      character(2)              :: css
4443      integer                   :: i,l1,l2
4444
4445
4446      l1 = len(s1)
4447      l2 = len(s2)
4448      do i=1,min(l1,l2)
4449          if (llt(s1%chars(i),s2%chars(i))) then
4450              css = 'LT'
4451              return
4452          elseif (lgt(s1%chars(i),s2%chars(i))) then
4453              css = 'GT'
4454              return
4455          endif
4456      enddo
4457      if (l1 < l2) then
4458          do i=l1+1,l2
4459              if (llt(blank,s2%chars(i))) then
4460                  css = 'LT'
4461                  return
4462              elseif (lgt(blank,s2%chars(i))) then
4463                  css = 'GT'
4464                  return
4465              endif
4466          enddo
4467      elseif (l1 > l2) then
4468          do i=l2+1,l1
4469              if (llt(s1%chars(i),blank)) then
4470                  css = 'LT'
4471                  return
4472              elseif (lgt(s1%chars(i),blank)) then
4473                  css = 'GT'
4474                  return
4475              endif
4476          enddo
4477      endif
4478      css = 'EQ'
4479
4480      end function lcompare_ss
4481
4482!*******************************************************************************
4483
4484      elemental function lcompare_cs(c,s) result(css)
4485
4486      implicit none
4487      character(*), intent(in)  :: c
4488      type(string), intent(in)  :: s
4489      character(2)              :: css
4490      integer                   :: i,lc,ls
4491
4492
4493      lc = len(c)
4494      ls = len(s)
4495      do i=1,min(lc,ls)
4496          if (llt(c(i:i),s%chars(i))) then
4497              css = 'LT'
4498              return
4499          elseif (lgt(c(i:i),s%chars(i))) then
4500              css = 'GT'
4501              return
4502          endif
4503      enddo
4504      if (lc < ls) then
4505          do i=lc+1,ls
4506              if (llt(blank,s%chars(i))) then
4507                  css = 'LT'
4508                  return
4509              elseif (lgt(blank,s%chars(i))) then
4510                  css = 'GT'
4511                  return
4512              endif
4513          enddo
4514      elseif (lc > ls) then
4515          do i=ls+1,lc
4516              if (llt(c(i:i),blank)) then
4517                  css = 'LT'
4518                  return
4519              elseif (lgt(c(i:i),blank)) then
4520                  css = 'GT'
4521                  return
4522              endif
4523          enddo
4524      endif
4525      css = 'EQ'
4526
4527      end function lcompare_cs
4528
4529!*******************************************************************************
4530!     LLT function
4531!*******************************************************************************
4532!     llt(string,string)
4533
4534      elemental function s_llt_s(s1,s2)
4535
4536      implicit none
4537      type(string), intent(in)  :: s1,s2
4538      logical                   :: s_llt_s
4539
4540      s_llt_s = (lcompare_ss(s1,s2) == 'LT')
4541
4542      end function s_llt_s
4543
4544!*******************************************************************************
4545!     llt(string,character)
4546
4547      elemental function s_llt_c(s1,c2)
4548
4549      implicit none
4550      type(string), intent(in)  :: s1
4551      character(*), intent(in)  :: c2
4552      logical                   :: s_llt_c
4553
4554      s_llt_c = (lcompare_cs(c2,s1) == 'GT')
4555
4556      end function s_llt_c
4557
4558!*******************************************************************************
4559!     llt(character,string)
4560
4561      elemental function c_llt_s(c1,s2)
4562
4563      implicit none
4564      type(string), intent(in)  :: s2
4565      character(*), intent(in)  :: c1
4566      logical                   :: c_llt_s
4567
4568      c_llt_s = (lcompare_cs(c1,s2) == 'LT')
4569
4570      end function c_llt_s
4571
4572!*******************************************************************************
4573!     LGT function
4574!*******************************************************************************
4575!     lgt(string,string)
4576
4577      elemental function s_lgt_s(s1,s2)
4578
4579      implicit none
4580      type(string), intent(in)  :: s1,s2
4581      logical                   :: s_lgt_s
4582
4583      s_lgt_s = (lcompare_ss(s1,s2) == 'GT')
4584
4585      end function s_lgt_s
4586
4587!*******************************************************************************
4588!     lgt(string,character)
4589
4590      elemental function s_lgt_c(s1,c2)
4591
4592      implicit none
4593      type(string), intent(in)  :: s1
4594      character(*), intent(in)  :: c2
4595      logical                   :: s_lgt_c
4596
4597      s_lgt_c = (lcompare_cs(c2,s1) == 'LT')
4598
4599      end function s_lgt_c
4600
4601!*******************************************************************************
4602!     lgt(character,string)
4603
4604      elemental function c_lgt_s(c1,s2)
4605
4606      implicit none
4607      type(string), intent(in)  :: s2
4608      character(*), intent(in)  :: c1
4609      logical                   :: c_lgt_s
4610
4611      c_lgt_s = (lcompare_cs(c1,s2) == 'GT')
4612
4613      end function c_lgt_s
4614
4615!*******************************************************************************
4616!     LGE function
4617!*******************************************************************************
4618!     lge(string,string)
4619
4620      elemental function s_lge_s(s1,s2)
4621
4622      implicit none
4623      type(string), intent(in)  :: s1,s2
4624      logical                   :: s_lge_s
4625
4626      s_lge_s = (lcompare_ss(s1,s2) /= 'LT')
4627
4628      end function s_lge_s
4629
4630!*******************************************************************************
4631!     lge(string,character)
4632
4633      elemental function s_lge_c(s1,c2)
4634
4635      implicit none
4636      type(string), intent(in)  :: s1
4637      character(*), intent(in)  :: c2
4638      logical                   :: s_lge_c
4639
4640      s_lge_c = (lcompare_cs(c2,s1) /= 'GT')
4641
4642      end function s_lge_c
4643
4644!*******************************************************************************
4645!     lge(character,string)
4646
4647      elemental function c_lge_s(c1,s2)
4648
4649      implicit none
4650      type(string), intent(in)  :: s2
4651      character(*), intent(in)  :: c1
4652      logical                   :: c_lge_s
4653
4654      c_lge_s = (lcompare_cs(c1,s2) /= 'LT')
4655
4656      end function c_lge_s
4657
4658!*******************************************************************************
4659!     LLE function
4660!*******************************************************************************
4661!     lle(string,string)
4662
4663      elemental function s_lle_s(s1,s2)
4664
4665      implicit none
4666      type(string), intent(in)  :: s1,s2
4667      logical                   :: s_lle_s
4668
4669      s_lle_s = (lcompare_ss(s1,s2) /= 'GT')
4670
4671      end function s_lle_s
4672
4673!*******************************************************************************
4674!     lle(string,character)
4675
4676      elemental function s_lle_c(s1,c2)
4677
4678      implicit none
4679      type(string), intent(in)  :: s1
4680      character(*), intent(in)  :: c2
4681      logical                   :: s_lle_c
4682
4683      s_lle_c = (lcompare_cs(c2,s1) /= 'LT')
4684
4685      end function s_lle_c
4686
4687!*******************************************************************************
4688!     lle(character,string)
4689
4690      elemental function c_lle_s(c1,s2)
4691
4692      implicit none
4693      type(string), intent(in)  :: s2
4694      character(*), intent(in)  :: c1
4695      logical                   :: c_lle_s
4696
4697      c_lle_s = (lcompare_cs(c1,s2) /= 'GT')
4698
4699      end function c_lle_s
4700
4701!*******************************************************************************
4702
4703      pure function acompare_aa(a1,a2) result(caa)
4704
4705      implicit none
4706      character, intent(in)  :: a1(:),a2(:)
4707      character(2)           :: caa
4708      integer                :: i,l1,l2
4709
4710
4711      l1 = size(a1)
4712      l2 = size(a2)
4713      do i=1,min(l1,l2)
4714          if (a1(i) < a2(i)) then
4715              caa = 'LT'
4716              return
4717          elseif (a1(i) > a2(i)) then
4718              caa = 'GT'
4719              return
4720          endif
4721      enddo
4722      if (l1 < l2) then
4723          do i=l1+1,l2
4724              if (blank < a2(i)) then
4725                  caa = 'LT'
4726                  return
4727              elseif (blank > a2(i)) then
4728                  caa = 'GT'
4729                  return
4730              endif
4731          enddo
4732      elseif (l1 > l2) then
4733          do i=l2+1,l1
4734              if (a1(i) < blank) then
4735                  caa = 'LT'
4736                  return
4737              elseif (a1(i) > blank) then
4738                  caa = 'GT'
4739                  return
4740              endif
4741          enddo
4742      endif
4743      caa = 'EQ'
4744
4745      end function acompare_aa
4746
4747!*******************************************************************************
4748
4749      pure function acompare_ca(c,a) result(cca)
4750
4751      implicit none
4752      character(*), intent(in)  :: c
4753      character, intent(in)     :: a(:)
4754      character(2)              :: cca
4755      integer                   :: i,lc,la
4756
4757
4758      lc = len(c)
4759      la = size(a)
4760      do i=1,min(lc,la)
4761          if (c(i:i) < a(i)) then
4762              cca = 'LT'
4763              return
4764          elseif (c(i:i) > a(i)) then
4765              cca = 'GT'
4766              return
4767          endif
4768      enddo
4769      if (lc < la) then
4770          do i=lc+1,la
4771              if (blank < a(i)) then
4772                  cca = 'LT'
4773                  return
4774              elseif (blank > a(i)) then
4775                  cca = 'GT'
4776                  return
4777              endif
4778          enddo
4779      elseif (lc > la) then
4780          do i=la+1,lc
4781              if (c(i:i) < blank) then
4782                  cca = 'LT'
4783                  return
4784              elseif (c(i:i) > blank) then
4785                  cca = 'GT'
4786                  return
4787              endif
4788          enddo
4789      endif
4790      cca = 'EQ'
4791
4792      end function acompare_ca
4793
4794!*******************************************************************************
4795!     ==
4796!*******************************************************************************
4797! array == array
4798
4799      pure function a_eq_a(a1,a2)
4800
4801      implicit none
4802      character, intent(in)  :: a1(:),a2(:)
4803      logical                :: a_eq_a
4804      integer                :: l1,l2
4805
4806
4807      l1 = size(a1)
4808      l2 = size(a2)
4809      if (l1 > l2) then
4810          a_eq_a = all(a1(1:l2) == a2) .and.  &
4811                   all(a1(l2+1:l1) == blank)
4812      elseif (l1 < l2) then
4813          a_eq_a = all(a1 == a2(1:l1)) .and.  &
4814                   all(blank == a2(l1+1:l2))
4815      else
4816          a_eq_a = all(a1 == a2)
4817      endif
4818
4819      end function a_eq_a
4820
4821!*******************************************************************************
4822! array == character
4823
4824      pure function a_eq_c(a,c)
4825
4826      implicit none
4827      character, intent(in)     :: a(:)
4828      character(*), intent(in)  :: c
4829      logical                   :: a_eq_c
4830      integer                   :: i,la,lc
4831
4832
4833      la = len(a)
4834      lc = len(c)
4835      do i=1,min(la,lc)
4836          if (a(i) /= c(i:i)) then
4837              a_eq_c = .false.
4838              return
4839          endif
4840      enddo
4841      if ((la > lc) .and. any(a(lc+1:la) /= blank)) then
4842          a_eq_c = .false.
4843      elseif ((la < lc) .and. (blank /= c(la+1:lc))) then
4844          a_eq_c = .false.
4845      else
4846          a_eq_c = .true.
4847      endif
4848
4849      end function a_eq_c
4850
4851!*******************************************************************************
4852! character == array
4853
4854      pure function c_eq_a(c,a)
4855
4856      implicit none
4857      character(*), intent(in)  :: c
4858      character, intent(in)     :: a(:)
4859      logical                   :: c_eq_a
4860
4861
4862      c_eq_a = a_eq_c(a,c)
4863
4864      end function c_eq_a
4865
4866!*******************************************************************************
4867!     /=
4868!*******************************************************************************
4869! array /= array
4870
4871      pure function a_ne_a(a1,a2)
4872
4873      implicit none
4874      character, intent(in)  :: a1(:),a2(:)
4875      logical                :: a_ne_a
4876      integer                :: l1,l2
4877
4878
4879      l1 = size(a1)
4880      l2 = size(a2)
4881      if (l1 > l2) then
4882          a_ne_a = any(a1(1:l2) /= a2) .or.  &
4883                   any(a1(l2+1:l1) /= blank)
4884      elseif (l1 < l2) then
4885          a_ne_a = any(a1 /= a2(1:l1)) .or. &
4886                   any(blank /= a2(l1+1:l2))
4887      else
4888          a_ne_a = any(a1 /= a2)
4889      endif
4890
4891      end function a_ne_a
4892
4893!*******************************************************************************
4894! array /= character
4895
4896      pure function a_ne_c(a,c)
4897
4898      implicit none
4899      character, intent(in)     :: a(:)
4900      character(*), intent(in)  :: c
4901      logical                   :: a_ne_c
4902      integer                   :: i,la,lc
4903
4904
4905      la = size(a)
4906      lc = len(c)
4907      do i=1,min(la,lc)
4908          if (a(i) /= c(i:i) )then
4909              a_ne_c = .true.
4910              return
4911          endif
4912      enddo
4913      if ((la > lc) .and. any(a(la+1:lc) /= blank)) then
4914          a_ne_c = .true.
4915      elseif ((la < lc) .and. blank /= c(la+1:lc)) then
4916          a_ne_c = .true.
4917      else
4918          a_ne_c = .false.
4919      endif
4920
4921      end function a_ne_c
4922
4923!*******************************************************************************
4924! character /= array
4925
4926      pure function c_ne_a(c,a)
4927
4928      implicit none
4929      character(*), intent(in)  :: c
4930      character, intent(in)     :: a(:)
4931      logical                   :: c_ne_a
4932
4933
4934      c_ne_a = acompare_ca(c,a) /= 'EQ'
4935
4936      end function c_ne_a
4937
4938!*******************************************************************************
4939!     < operators
4940!*******************************************************************************
4941! array < array
4942
4943      pure function a_lt_a(a1,a2)
4944
4945      implicit none
4946      character, intent(in)  :: a1(:),a2(:)
4947      logical                :: a_lt_a
4948
4949
4950      a_lt_a = acompare_aa(a1,a2) == 'LT'
4951
4952      end function a_lt_a
4953
4954!*******************************************************************************
4955! array < character
4956
4957      pure function a_lt_c(a,c)
4958
4959      implicit none
4960      character, intent(in)     :: a(:)
4961      character(*), intent(in)  :: c
4962      logical                   :: a_lt_c
4963
4964
4965      a_lt_c = acompare_ca(c,a) == 'GT'
4966
4967      end function a_lt_c
4968
4969!*******************************************************************************
4970! character < array
4971
4972      pure function c_lt_a(c,a)
4973
4974      implicit none
4975      character(*), intent(in)  :: c
4976      character, intent(in)     :: a(:)
4977      logical                   :: c_lt_a
4978
4979
4980      c_lt_a = acompare_ca(c,a) == 'LT'
4981
4982      end function c_lt_a
4983
4984!*******************************************************************************
4985!     <=  operators
4986!*******************************************************************************
4987! array <= array
4988
4989      pure function a_le_a(a1,a2)
4990
4991      implicit none
4992      character, intent(in)  :: a1(:),a2(:)
4993      logical                :: a_le_a
4994
4995
4996      a_le_a = acompare_aa(a1,a2) /= 'GT'
4997
4998      end function a_le_a
4999
5000!*******************************************************************************
5001! array <= character
5002
5003      pure function a_le_c(a,c)
5004
5005      implicit none
5006      character, intent(in)     :: a(:)
5007      character(*), intent(in)  :: c
5008      logical                   :: a_le_c
5009
5010
5011      a_le_c = acompare_ca(c,a) /= 'LT'
5012
5013      end function a_le_c
5014
5015!*******************************************************************************
5016! character <= array
5017
5018      pure function c_le_a(c,a)
5019
5020      implicit none
5021      character(*), intent(in)  :: c
5022      character, intent(in)     :: a(:)
5023      logical                   :: c_le_a
5024
5025
5026      c_le_a = acompare_ca(c,a) /= 'GT'
5027
5028      end function c_le_a
5029
5030!*******************************************************************************
5031!     >=  operators
5032!*******************************************************************************
5033! array >= array
5034
5035      pure function a_ge_a(a1,a2)
5036
5037      implicit none
5038      character, intent(in)  :: a1(:),a2(:)
5039      logical                :: a_ge_a
5040
5041
5042      a_ge_a = acompare_aa(a1,a2) /= 'LT'
5043
5044      end function a_ge_a
5045
5046!*******************************************************************************
5047! array >= character
5048
5049      pure function a_ge_c(a,c)
5050
5051      implicit none
5052      character, intent(in)     :: a(:)
5053      character(*), intent(in)  :: c
5054      logical                   :: a_ge_c
5055
5056
5057      a_ge_c = acompare_ca(c,a) /= 'GT'
5058
5059      end function a_ge_c
5060
5061!*******************************************************************************
5062! character >= array
5063
5064      pure function c_ge_a(c,a)
5065
5066      implicit none
5067      character(*), intent(in)  :: c
5068      character, intent(in)     :: a(:)
5069      logical                   :: c_ge_a
5070
5071
5072      c_ge_a = acompare_ca(c,a) /= 'LT'
5073
5074      end function c_ge_a
5075
5076!*******************************************************************************
5077!     >  operators
5078!*******************************************************************************
5079! array > array
5080
5081      pure function a_gt_a(a1,a2)
5082
5083      implicit none
5084      character, intent(in)  :: a1(:),a2(:)
5085      logical                :: a_gt_a
5086
5087
5088      a_gt_a = acompare_aa(a1,a2) == 'GT'
5089
5090      end function a_gt_a
5091
5092!*******************************************************************************
5093! array > character
5094
5095      pure function a_gt_c(a,c)
5096
5097      implicit none
5098      character, intent(in)     :: a(:)
5099      character(*), intent(in)  :: c
5100      logical                   :: a_gt_c
5101
5102
5103      a_gt_c = acompare_ca(c,a) == 'LT'
5104
5105      end function a_gt_c
5106
5107!*******************************************************************************
5108! character > array
5109
5110      pure function c_gt_a(c,a)
5111
5112      implicit none
5113      character(*), intent(in)  :: c
5114      character, intent(in)     :: a(:)
5115      logical                   :: c_gt_a
5116
5117
5118      c_gt_a = acompare_ca(c,a) == 'GT'
5119
5120      end function c_gt_a
5121
5122!*******************************************************************************
5123
5124      pure function alcompare_aa(a1,a2) result(caa)
5125
5126      implicit none
5127      character, intent(in)  :: a1(:),a2(:)
5128      character(2)           :: caa
5129      integer                :: i,l1,l2
5130
5131
5132      l1 = size(a1)
5133      l2 = size(a2)
5134      do i=1,min(l1,l2)
5135          if (llt(a1(i),a2(i))) then
5136              caa = 'LT'
5137              return
5138          elseif (lgt(a1(i),a2(i))) then
5139              caa = 'GT'
5140              return
5141          endif
5142      enddo
5143      if (l1 < l2) then
5144          do i=l1+1,l2
5145              if (llt(blank,a2(i))) then
5146                  caa = 'LT'
5147                  return
5148              elseif (lgt(blank,a2(i))) then
5149                  caa = 'GT'
5150                  return
5151              endif
5152          enddo
5153      elseif (l1 > l2) then
5154          do i=l2+1,l1
5155              if (llt(a1(i),blank)) then
5156                  caa = 'LT'
5157                  return
5158              elseif (lgt(a1(i),blank)) then
5159                  caa = 'GT'
5160                  return
5161              endif
5162          enddo
5163      endif
5164      caa = 'EQ'
5165
5166      end function alcompare_aa
5167
5168!*******************************************************************************
5169
5170      pure function alcompare_ca(c,a) result(cca)
5171
5172      implicit none
5173      character(*), intent(in)  :: c
5174      character, intent(in)     :: a(:)
5175      character(2)              :: cca
5176      integer                   :: i,lc,la
5177
5178
5179      lc = len(c)
5180      la = size(a)
5181      do i=1,min(lc,la)
5182          if (llt(c(i:i),a(i))) then
5183              cca = 'LT'
5184              return
5185          elseif (lgt(c(i:i),a(i))) then
5186              cca = 'GT'
5187              return
5188          endif
5189      enddo
5190      if (lc < la) then
5191          do i=lc+1,la
5192              if (llt(blank,a(i))) then
5193                  cca = 'LT'
5194                  return
5195              elseif (lgt(blank,a(i))) then
5196                  cca = 'GT'
5197                  return
5198              endif
5199          enddo
5200      elseif (lc > la) then
5201          do i=la+1,lc
5202              if (llt(c(i:i),blank)) then
5203                  cca = 'LT'
5204                  return
5205              elseif (lgt(c(i:i),blank)) then
5206                  cca = 'GT'
5207                  return
5208              endif
5209          enddo
5210      endif
5211      cca = 'EQ'
5212
5213      end function alcompare_ca
5214
5215!*******************************************************************************
5216!     LLT operators
5217!*******************************************************************************
5218! array < array
5219
5220      pure function a_allt_a(a1,a2)
5221
5222      implicit none
5223      character, intent(in)  :: a1(:),a2(:)
5224      logical                :: a_allt_a
5225
5226
5227      a_allt_a = alcompare_aa(a1,a2) == 'LT'
5228
5229      end function a_allt_a
5230
5231!*******************************************************************************
5232! array < character
5233
5234      pure function a_allt_c(a1,c2)
5235
5236      implicit none
5237      character, intent(in)     :: a1(:)
5238      character(*), intent(in)  :: c2
5239      logical                   :: a_allt_c
5240
5241
5242      a_allt_c = alcompare_ca(c2,a1) == 'GT'
5243
5244      end function a_allt_c
5245
5246!*******************************************************************************
5247! character < array
5248
5249      pure function c_allt_a(c1,a2)
5250
5251      implicit none
5252      character(*), intent(in)  :: c1
5253      character, intent(in)     :: a2(:)
5254      logical                   :: c_allt_a
5255
5256
5257      c_allt_a = alcompare_ca(c1,a2) == 'LT'
5258
5259      end function c_allt_a
5260
5261!*******************************************************************************
5262!     LLE  operators
5263!*******************************************************************************
5264! array <= array
5265
5266      pure function a_alle_a(a1,a2)
5267
5268      implicit none
5269      character, intent(in)  :: a1(:),a2(:)
5270      logical                :: a_alle_a
5271
5272
5273      a_alle_a = alcompare_aa(a1,a2) /= 'GT'
5274
5275      end function a_alle_a
5276
5277!*******************************************************************************
5278! array <= character
5279
5280      pure function a_alle_c(a1,c2)
5281
5282      implicit none
5283      character, intent(in)     :: a1(:)
5284      character(*), intent(in)  :: c2
5285      logical                   :: a_alle_c
5286
5287
5288      a_alle_c = alcompare_ca(c2,a1) /= 'LT'
5289
5290      end function a_alle_c
5291
5292!*******************************************************************************
5293! character <= array
5294
5295      pure function c_alle_a(c1,a2)
5296
5297      implicit none
5298      character(*), intent(in)  :: c1
5299      character, intent(in)     :: a2(:)
5300      logical                   :: c_alle_a
5301
5302
5303      c_alle_a = alcompare_ca(c1,a2) /= 'GT'
5304
5305      end function c_alle_a
5306
5307!*******************************************************************************
5308!     LGE  operators
5309!*******************************************************************************
5310! array >= array
5311
5312      pure function a_alge_a(a1,a2)
5313
5314      implicit none
5315      character, intent(in)  :: a1(:),a2(:)
5316      logical                :: a_alge_a
5317
5318
5319      a_alge_a = alcompare_aa(a1,a2) /= 'LT'
5320
5321      end function a_alge_a
5322
5323!*******************************************************************************
5324! array >= character
5325
5326      pure function a_alge_c(a1,c2)
5327
5328      implicit none
5329      character, intent(in)     :: a1(:)
5330      character(*), intent(in)  :: c2
5331      logical                   :: a_alge_c
5332
5333
5334      a_alge_c = alcompare_ca(c2,a1) /= 'GT'
5335
5336      end function a_alge_c
5337
5338!*******************************************************************************
5339! character >= array
5340
5341      pure function c_alge_a(c1,a2)
5342
5343      implicit none
5344      character(*), intent(in)  :: c1
5345      character, intent(in)     :: a2(:)
5346      logical                   :: c_alge_a
5347
5348
5349      c_alge_a = alcompare_ca(c1,a2) /= 'LT'
5350
5351      end function c_alge_a
5352
5353!*******************************************************************************
5354!     LGT  operators
5355!*******************************************************************************
5356! array > array
5357
5358      pure function a_algt_a(a1,a2)
5359
5360      implicit none
5361      character, intent(in)  :: a1(:),a2(:)
5362      logical                :: a_algt_a
5363
5364
5365      a_algt_a = alcompare_aa(a1,a2) == 'GT'
5366
5367      end function a_algt_a
5368
5369!*******************************************************************************
5370! array > character
5371
5372      pure function a_algt_c(a1,c2)
5373
5374      implicit none
5375      character, intent(in)     :: a1(:)
5376      character(*), intent(in)  :: c2
5377      logical                   :: a_algt_c
5378
5379
5380      a_algt_c = alcompare_ca(c2,a1) == 'LT'
5381
5382      end function a_algt_c
5383
5384!*******************************************************************************
5385! character > array
5386
5387      pure function c_algt_a(c1,a2)
5388
5389      implicit none
5390      character(*), intent(in)  :: c1
5391      character, intent(in)     :: a2(:)
5392      logical                   :: c_algt_a
5393
5394
5395      c_algt_a = alcompare_ca(c1,a2) == 'GT'
5396
5397      end function c_algt_a
5398
5399!*******************************************************************************
5400!     INDEX
5401!*******************************************************************************
5402
5403      elemental function index_ss(s,sub,back)
5404
5405      implicit none
5406      type(string), intent(in)       :: s,sub
5407      logical, intent(in), optional  :: back
5408      integer                        :: index_ss
5409      logical                        :: dir_switch
5410      integer                        :: ls,lsub
5411
5412
5413      if (present(back)) then
5414          dir_switch = back
5415      else
5416          dir_switch = .false.
5417      endif
5418
5419      ls = len(s)
5420      lsub = len(sub)
5421      index_ss = aindex(s%chars(:ls),sub%chars(:lsub),dir_switch)
5422
5423      end function index_ss
5424
5425!*******************************************************************************
5426
5427      elemental function index_sc(s,sub,back)
5428
5429      implicit none
5430      type(string), intent(in)       :: s
5431      character(*), intent(in)       :: sub
5432      logical, intent(in), optional  :: back
5433      integer                        :: index_sc
5434      logical                        :: dir_switch
5435      integer                        :: ls
5436
5437
5438      if (present(back)) then
5439          dir_switch = back
5440      else
5441          dir_switch = .false.
5442      endif
5443
5444      ls = len(s)
5445      index_sc = aindex(s%chars(:ls),sub,dir_switch)
5446
5447      end function index_sc
5448
5449!*******************************************************************************
5450
5451      elemental function index_cs(s,sub,back)
5452
5453      implicit none
5454      character(*), intent(in)       :: s
5455      type(string), intent(in)       :: sub
5456      logical, intent(in), optional  :: back
5457      integer                        :: index_cs
5458      logical                        :: dir_switch
5459
5460
5461      if (present(back)) then
5462          dir_switch = back
5463      else
5464          dir_switch = .false.
5465      endif
5466
5467      index_cs = index(s,char(sub),dir_switch)
5468
5469      end function index_cs
5470
5471!*******************************************************************************
5472!     AINDEX
5473!*******************************************************************************
5474
5475      pure function aindex_aa(s,sub,back) result(index_aa)
5476
5477      implicit none
5478      character, intent(in)          :: s(:),sub(:)
5479      logical, intent(in), optional  :: back
5480      integer                        :: index_aa
5481      logical                        :: dir_switch
5482      integer                        :: i,ls,lss
5483
5484
5485      if (present(back)) then
5486          dir_switch = back
5487      else
5488          dir_switch = .false.
5489      endif
5490
5491      ls = size(s)
5492      lss = size(sub)
5493
5494      if (lss == 0) then
5495          if (dir_switch) then
5496              index_aa = ls + 1
5497          else
5498              index_aa = 1
5499          endif
5500          return
5501      endif
5502
5503      if (dir_switch) then
5504!         backwards search
5505          do i=ls-lss+1,1,-1
5506              if (all(s(i:i+lss-1) == sub(1:lss))) then
5507                  index_aa = i
5508                  return
5509              endif
5510          enddo
5511          index_aa = 0
5512      else
5513!         forward search
5514          do i=1,ls-lss+1
5515              if (all(s(i:i+lss-1) == sub(1:lss))) then
5516                  index_aa = i
5517                  return
5518              endif
5519          enddo
5520          index_aa = 0
5521      endif
5522
5523      end function aindex_aa
5524
5525!*******************************************************************************
5526
5527      pure function aindex_ac(s,sub,back) result(index_ac)
5528
5529      implicit none
5530      character, intent(in)          :: s(:)
5531      character(*), intent(in)       :: sub
5532      logical, intent(in), optional  :: back
5533      integer                        :: index_ac
5534      logical                        :: dir_switch,matched
5535      integer                        :: i,j,ls,lss
5536
5537
5538      if (present(back)) then
5539          dir_switch = back
5540      else
5541          dir_switch = .false.
5542      endif
5543
5544      ls = size(s)
5545      lss = len(sub)
5546
5547      if (lss == 0) then
5548          if (dir_switch) then
5549              index_ac = ls + 1
5550          else
5551              index_ac = 1
5552          endif
5553          return
5554      endif
5555
5556      if (dir_switch) then
5557          index_ac = 0
5558          do i=ls-lss+1,1,-1
5559              matched = all(s(i:i+lss-1) == (/ (sub(j:j), j=1,lss) /))
5560              if (matched) then
5561                  index_ac = i
5562                  return
5563              endif
5564          enddo
5565      else
5566          index_ac = 0
5567          do i=1,ls-lss+1
5568              matched = all(s(i:i+lss-1) == (/ (sub(j:j), j=1,lss) /))
5569              if (matched) then
5570                  index_ac = i
5571                  return
5572              endif
5573          enddo
5574      endif
5575
5576      end function aindex_ac
5577
5578!*******************************************************************************
5579
5580      pure function aindex_ca(s,sub,back) result(index_ca)
5581
5582      implicit none
5583      character(*), intent(in)       :: s
5584      character, intent(in)          :: sub(:)
5585      logical, intent(in), optional  :: back
5586      integer                        :: index_ca
5587      logical                        :: dir_switch,matched
5588      integer                        :: i,j,ls,lss
5589
5590
5591      if (present(back)) then
5592          dir_switch = back
5593      else
5594          dir_switch = .false.
5595      endif
5596
5597      ls = len(s)
5598      lss = size(sub)
5599
5600      if (lss == 0) then
5601          if (dir_switch) then
5602              index_ca = ls + 1
5603          else
5604              index_ca = 1
5605          endif
5606          return
5607      endif
5608
5609      if (dir_switch) then
5610          do i=ls-lss+1,1,-1
5611              matched = .true.
5612              do j=1,lss
5613                  if (s(i+j-1:i+j-1) /= sub(j)) then
5614                      matched = .false.
5615                      exit
5616                  endif
5617              enddo
5618              if (matched) then
5619                  index_ca = i
5620                  return
5621              endif
5622          enddo
5623          index_ca = 0
5624      else
5625          do i=1,ls-lss+1
5626              matched = .true.
5627              do j=1,lss
5628                  if (s(i+j-1:i+j-1) /= sub(j)) then
5629                      matched = .false.
5630                      exit
5631                  endif
5632              enddo
5633              if (matched) then
5634                  index_ca = i
5635                  return
5636              endif
5637          enddo
5638          index_ca = 0
5639      endif
5640
5641      end function aindex_ca
5642
5643!*******************************************************************************
5644!     SCAN
5645!*******************************************************************************
5646
5647      elemental function scan_ss(s,set,back)
5648
5649      implicit none
5650      type(string), intent(in)       :: s,set
5651      logical, intent(in), optional  :: back
5652      integer                        :: scan_ss
5653      logical                        :: dir_switch
5654      integer                        :: ls,lset
5655
5656
5657      if (present(back)) then
5658          dir_switch = back
5659      else
5660          dir_switch = .false.
5661      endif
5662
5663      ls = len(s)
5664      lset = len(set)
5665      scan_ss = ascan_aa(s%chars(1:ls),set%chars(1:lset),dir_switch)
5666
5667      end function scan_ss
5668
5669!*******************************************************************************
5670
5671      elemental function scan_sc(s,set,back)
5672
5673      implicit none
5674      type(string), intent(in)       :: s
5675      character(*), intent(in)       :: set
5676      logical, intent(in), optional  :: back
5677      integer                        :: scan_sc
5678      logical                        :: dir_switch
5679      integer                        :: ls
5680
5681
5682      if (present(back)) then
5683          dir_switch = back
5684      else
5685          dir_switch = .false.
5686      endif
5687
5688      ls = len(s)
5689      scan_sc = ascan_ac(s%chars(1:ls),set,dir_switch)
5690
5691      end function scan_sc
5692
5693!*******************************************************************************
5694
5695      elemental function scan_cs(s,set,back)
5696
5697      implicit none
5698      character(*), intent(in)       :: s
5699      type(string), intent(in)       :: set
5700      logical, intent(in), optional  :: back
5701      integer                        :: scan_cs
5702      logical                        :: dir_switch
5703      integer                        :: lset
5704
5705
5706      if (present(back)) then
5707          dir_switch = back
5708      else
5709          dir_switch = .false.
5710      endif
5711
5712      lset = len(set)
5713      scan_cs = ascan_ca(s,set%chars(1:lset),dir_switch)
5714
5715      end function scan_cs
5716!*******************************************************************************
5717!     ASCAN
5718!*******************************************************************************
5719
5720      pure function ascan_aa(s,set,back)
5721
5722      implicit none
5723      character, intent(in)          :: s(:),set(:)
5724      logical, intent(in), optional  :: back
5725      integer                        :: ascan_aa
5726      logical                        :: dir_switch
5727      integer                        :: i,ls,lset
5728
5729
5730      if (present(back)) then
5731          dir_switch = back
5732      else
5733          dir_switch = .false.
5734      endif
5735
5736      ls = size(s)
5737      lset = size(set)
5738      if (dir_switch) then
5739!         backwards search
5740          do i=ls,1,-1
5741              if (any(set(1:lset) == s(i))) then
5742                  ascan_aa = i
5743                  return
5744              endif
5745          enddo
5746          ascan_aa = 0
5747      else
5748!         forward search
5749          do i=1,ls
5750              if (any(set(1:lset) == s(i))) then
5751                  ascan_aa = i
5752                  return
5753              endif
5754          enddo
5755          ascan_aa = 0
5756      endif
5757
5758      end function ascan_aa
5759
5760!*******************************************************************************
5761
5762      pure function ascan_ac(s,set,back)
5763
5764      implicit none
5765      character, intent(in)          :: s(:)
5766      character(*), intent(in)       :: set
5767      logical, intent(in), optional  :: back
5768      integer                        :: ascan_ac
5769      logical                        :: dir_switch,matched
5770      integer                        :: i,j,ls,lset
5771
5772
5773      if (present(back)) then
5774          dir_switch = back
5775      else
5776          dir_switch = .false.
5777      endif
5778
5779      ls = size(s)
5780      lset = len(set)
5781      if (dir_switch) then
5782!         backwards search
5783          do i=ls,1,-1
5784              matched = .false.
5785              do j=1,lset
5786                  if (s(i) == set(j:j)) then
5787                      matched = .true.
5788                      exit
5789                  endif
5790              enddo
5791              if (matched) then
5792                  ascan_ac = i
5793                  return
5794              endif
5795          enddo
5796          ascan_ac = 0
5797      else
5798!         forward search
5799          do i=1,ls
5800              matched = .false.
5801              do j=1,lset
5802                  if (s(i) == set(j:j)) then
5803                      matched = .true.
5804                      exit
5805                  endif
5806              enddo
5807              if (matched) then
5808                  ascan_ac = i
5809                  return
5810              endif
5811          enddo
5812          ascan_ac = 0
5813      endif
5814
5815      end function ascan_ac
5816
5817!*******************************************************************************
5818
5819      pure function ascan_ca(s,set,back)
5820
5821      implicit none
5822      character(*), intent(in)       :: s
5823      character, intent(in)          :: set(:)
5824      logical, intent(in), optional  :: back
5825      integer                        :: ascan_ca
5826      logical                        :: dir_switch,matched
5827      integer                        :: i,j,ls,lset
5828
5829
5830      if (present(back)) then
5831          dir_switch = back
5832      else
5833          dir_switch = .false.
5834      endif
5835
5836      ls = len(s)
5837      lset = size(set)
5838      if (dir_switch) then
5839!         backwards search
5840          do i=ls,1,-1
5841              matched = .false.
5842              do j=1,lset
5843                  if (s(i:i) == set(j)) then
5844                      matched = .true.
5845                      exit
5846                  endif
5847              enddo
5848              if (matched) then
5849                  ascan_ca = i
5850                  return
5851              endif
5852          enddo
5853          ascan_ca = 0
5854      else
5855!         forward search
5856          do i=1,ls
5857              matched = .false.
5858              do j=1,lset
5859                  if (s(i:i) == set(j)) then
5860                      matched = .true.
5861                      exit
5862                  endif
5863              enddo
5864              if (matched) then
5865                  ascan_ca = i
5866                  return
5867              endif
5868          enddo
5869          ascan_ca = 0
5870      endif
5871
5872      end function ascan_ca
5873
5874!*******************************************************************************
5875!     VERIFY
5876!*******************************************************************************
5877
5878      elemental function verify_ss(s,set,back)
5879
5880      implicit none
5881      type(string), intent(in)       :: s,set
5882      logical, intent(in), optional  :: back
5883      integer                        :: verify_ss
5884      logical                        :: dir_switch
5885      integer                        :: ls,lset
5886
5887
5888      if (present(back)) then
5889          dir_switch = back
5890      else
5891          dir_switch = .false.
5892      endif
5893
5894      ls = len(s)
5895      lset = len(set)
5896      verify_ss = averify_aa(s%chars(1:ls),set%chars(1:lset),dir_switch)
5897
5898      end function verify_ss
5899
5900!*******************************************************************************
5901
5902      elemental function verify_sc(s,set,back)
5903
5904      implicit none
5905      type(string), intent(in)       :: s
5906      character(*), intent(in)       :: set
5907      logical, intent(in), optional  :: back
5908      integer                        :: verify_sc
5909      logical                        :: dir_switch
5910      integer                        :: ls
5911
5912
5913      if (present(back)) then
5914          dir_switch = back
5915      else
5916          dir_switch = .false.
5917      endif
5918
5919      ls = len(s)
5920      verify_sc = averify_ac(s%chars(1:ls),set,dir_switch)
5921
5922      end function verify_sc
5923
5924!*******************************************************************************
5925
5926      elemental function verify_cs(s,set,back)
5927
5928      implicit none
5929      character(*), intent(in)       :: s
5930      type(string), intent(in)       :: set
5931      logical, intent(in), optional  :: back
5932      integer                        :: verify_cs
5933      logical                        :: dir_switch
5934      integer                        :: lset
5935
5936
5937      if (present(back)) then
5938          dir_switch = back
5939      else
5940          dir_switch = .false.
5941      endif
5942
5943      lset = len(set)
5944      verify_cs = averify_ca(s,set%chars(1:lset),dir_switch)
5945
5946      end function verify_cs
5947
5948!*******************************************************************************
5949!     AVERIFY
5950!*******************************************************************************
5951
5952      pure function averify_aa(s,set,back)
5953
5954      implicit none
5955      character, intent(in)          :: s(:),set(:)
5956      logical, intent(in), optional  :: back
5957      integer                        :: averify_aa
5958      logical                        :: dir_switch
5959      integer                        :: i,ls,lset
5960
5961
5962      if (present(back)) then
5963          dir_switch = back
5964      else
5965          dir_switch = .false.
5966      endif
5967
5968      ls = size(s)
5969      lset = size(set)
5970      if (dir_switch) then
5971!         backwards search
5972          do i=ls,1,-1
5973              if (.not.(any(set(1:lset) == s(i)))) then
5974                  averify_aa = i
5975                  return
5976              endif
5977          enddo
5978          averify_aa = 0
5979      else
5980!         forward search
5981          do i=1,ls
5982              if (.not.(any(set(1:lset) == s(i)))) then
5983                  averify_aa = i
5984                  return
5985              endif
5986          enddo
5987          averify_aa = 0
5988      endif
5989
5990      end function averify_aa
5991
5992!*******************************************************************************
5993
5994      pure function averify_ac(s,set,back)
5995
5996      implicit none
5997      character, intent(in)          :: s(:)
5998      character(*), intent(in)       :: set
5999      logical, intent(in), optional  :: back
6000      integer                        :: averify_ac
6001      logical                        :: dir_switch
6002      integer                        :: i,j,ls,lset
6003
6004
6005      if (present(back)) then
6006          dir_switch = back
6007      else
6008          dir_switch = .false.
6009      endif
6010
6011      ls = size(s)
6012      lset = len(set)
6013      if (dir_switch) then
6014!         backwards search
6015b:        do i=ls,1,-1
6016              do j=1,lset
6017                  if (s(i) == set(j:j)) cycle b
6018              enddo
6019              averify_ac = i
6020              return
6021          enddo b
6022          averify_ac = 0
6023      else
6024!         forward search
6025f:        do i=1,ls
6026              do j=1,lset
6027                  if (s(i) == set(j:j)) cycle f
6028              enddo
6029              averify_ac = i
6030              return
6031          enddo f
6032          averify_ac = 0
6033      endif
6034
6035      end function averify_ac
6036
6037!*******************************************************************************
6038
6039      pure function averify_ca(s,set,back)
6040
6041      implicit none
6042      character(*), intent(in)       :: s
6043      character, intent(in)          :: set(:)
6044      logical, intent(in), optional  :: back
6045      integer                        :: averify_ca
6046      logical                        :: dir_switch
6047      integer                        :: i,j,ls,lset
6048
6049
6050      if (present(back)) then
6051          dir_switch = back
6052      else
6053          dir_switch = .false.
6054      endif
6055
6056      ls = len(s)
6057      lset = size(set)
6058      if (dir_switch) then
6059!         backwards search
6060b:        do i=ls,1,-1
6061              do j=1,lset
6062                  if (s(i:i) == set(j)) cycle b
6063              enddo
6064              averify_ca = i
6065              return
6066          enddo b
6067          averify_ca = 0
6068      else
6069!         forward search
6070f:        do i=1,ls
6071              do j=1,lset
6072                  if (s(i:i) == set(j)) cycle f
6073              enddo
6074              averify_ca = i
6075              return
6076          enddo f
6077          averify_ca = 0
6078      endif
6079
6080      end function averify_ca
6081
6082!*******************************************************************************
6083!     UPPERCASE
6084!*******************************************************************************
6085
6086      pure function uppercase_s(s,begin,end)
6087
6088      implicit none
6089      type(string), intent(in)       :: s
6090      integer, intent(in), optional  :: begin,end
6091      character(len(s))              :: uppercase_s
6092      integer                        :: i,i1,i2,j
6093
6094
6095      i1 = 1
6096      if (present(begin)) i1 = max(i1,begin)
6097      i2 = len(s)
6098      if (present(end)) i2 = min(i2,end)
6099
6100      do i=1,i1-1
6101          uppercase_s(i:i) = s%chars(i)
6102      enddo
6103      do i=i1,i2
6104          j = iachar(s%chars(i))
6105          select case(j)
6106          case(97:122)
6107              uppercase_s(i:i) = achar(j-32)
6108          case default
6109              uppercase_s(1:i) = s%chars(i)
6110          end select
6111      enddo
6112      do i=i2+1,len(s)
6113          uppercase_s(i:i) = s%chars(i)
6114      enddo
6115
6116      end function uppercase_s
6117
6118!*******************************************************************************
6119
6120      pure function uppercase_c(c,begin,end)
6121
6122      implicit none
6123      character(*), intent(in)       :: c
6124      integer, intent(in), optional  :: begin,end
6125      character(len(c))              :: uppercase_c
6126      integer                        :: i,i1,i2,j
6127
6128
6129      i1 = 1
6130      if (present(begin)) i1 = max(i1,begin)
6131      i2 = len(c)
6132      if (present(end)) i2 = min(i2,end)
6133
6134      uppercase_c(:i1-1) = c(:i1-1)
6135      do i=i1,i2
6136          j = iachar(c(i:i))
6137          select case(j)
6138          case(97:122)
6139              uppercase_c(i:i) = achar(j-32)
6140          case default
6141              uppercase_c(i:i) = c(i:i)
6142          end select
6143      enddo
6144      uppercase_c(i2+1:) = c(i2+1:)
6145
6146      end function uppercase_c
6147
6148!*******************************************************************************
6149
6150      elemental subroutine to_uppercase_s(s,begin,end)
6151
6152      implicit none
6153      type(string), intent(inout)    :: s
6154      integer, intent(in), optional  :: begin,end
6155      integer                        :: i,i1,i2,j
6156
6157
6158      i1 = 1
6159      if (present(begin)) i1 = max(i1,begin)
6160      i2 = len(s)
6161      if (present(end)) i2 = min(i2,end)
6162
6163      do i=i1,i2
6164          j = iachar(s%chars(i))
6165          select case(j)
6166          case(97:122)
6167              s%chars(i) = achar(j-32)
6168          case default
6169              continue
6170          end select
6171      enddo
6172
6173      end subroutine to_uppercase_s
6174
6175!*******************************************************************************
6176
6177      elemental subroutine to_uppercase_c(c,begin,end)
6178
6179      implicit none
6180      character(*), intent(inout)    :: c
6181      integer, intent(in), optional  :: begin,end
6182      integer                        :: i,i1,i2,j
6183
6184
6185      i1 = 1
6186      if (present(begin)) i1 = max(i1,begin)
6187      i2 = len(c)
6188      if (present(end)) i2 = min(i2,end)
6189
6190      do i=i1,i2
6191          j = iachar(c(i:i))
6192          select case(j)
6193          case(97:122)
6194              c(i:i) = achar(j-32)
6195          case default
6196              continue
6197          end select
6198      enddo
6199
6200      end subroutine to_uppercase_c
6201
6202!*******************************************************************************
6203!     LOWERCASE
6204!*******************************************************************************
6205
6206      pure function lowercase_s(s,begin,end)
6207
6208      implicit none
6209      type(string), intent(in)       :: s
6210      integer, intent(in), optional  :: begin,end
6211      character(len(s))              :: lowercase_s
6212      integer                        :: i,i1,i2,j
6213
6214
6215      i1 = 1
6216      if (present(begin)) i1 = max(i1,begin)
6217      i2 = len(s)
6218      if (present(end)) i2 = min(i2,end)
6219
6220      do i=1,i1-1
6221          lowercase_s(i:i) = s%chars(i)
6222      enddo
6223      do i=i1,i2
6224          j = iachar(s%chars(i))
6225          select case(j)
6226          case(65:90)
6227              lowercase_s(i:i) = achar(j+32)
6228          case default
6229              lowercase_s(i:i) = s%chars(i)
6230          end select
6231      enddo
6232      do i=i2+1,len(s)
6233          lowercase_s(i:i) = s%chars(i)
6234      enddo
6235
6236      end function lowercase_s
6237
6238!*******************************************************************************
6239
6240      pure function lowercase_c(c,begin,end)
6241
6242      implicit none
6243      character(*), intent(in)       :: c
6244      integer, intent(in), optional  :: begin,end
6245      character(len(c))              :: lowercase_c
6246      integer                        :: i,i1,i2,j
6247
6248
6249      i1 = 1
6250      if (present(begin)) i1 = max(i1,begin)
6251      i2 = len(c)
6252      if (present(end)) i2 = min(i2,end)
6253
6254      lowercase_c(:i1-1) = c(:i1-1)
6255      do i=i1,i2
6256          j = iachar(c(i:i))
6257          select case(j)
6258          case(65:90)
6259              lowercase_c(i:i) = achar(j+32)
6260          case default
6261              lowercase_c(i:i) = c(i:i)
6262          end select
6263      enddo
6264      lowercase_c(i2+1:) = c(i2+1:)
6265
6266      end function lowercase_c
6267
6268!*******************************************************************************
6269
6270      elemental subroutine to_lowercase_s(s,begin,end)
6271
6272      implicit none
6273      type(string), intent(inout)    :: s
6274      integer, intent(in), optional  :: begin,end
6275      integer                        :: i,i1,i2,j
6276
6277
6278      i1 = 1
6279      if (present(begin)) i1 = max(i1,begin)
6280      i2 = len(s)
6281      if (present(end)) i2 = min(i2,end)
6282
6283      do i=i1,i2
6284          j = iachar(s%chars(i))
6285          select case(j)
6286          case(65:90)
6287              s%chars(i) = achar(j+32)
6288          case default
6289              continue
6290          end select
6291      enddo
6292
6293      end subroutine to_lowercase_s
6294
6295!*******************************************************************************
6296
6297      elemental subroutine to_lowercase_c(c,begin,end)
6298
6299      implicit none
6300      character(*), intent(inout)    :: c
6301      integer, intent(in), optional  :: begin,end
6302      integer                        :: i,i1,i2,j
6303
6304
6305      i1 = 1
6306      if (present(begin)) i1 = max(i1,begin)
6307      i2 = len(c)
6308      if (present(end)) i2 = min(i2,end)
6309
6310      do i=i1,i2
6311          j = iachar(c(i:i))
6312          select case(j)
6313          case(65:90)
6314              c(i:i) = achar(j+32)
6315          case default
6316              continue
6317          end select
6318      enddo
6319
6320      end subroutine to_lowercase_c
6321
6322!*******************************************************************************
6323
6324!*******************************************************************************
6325
6326      end module m_strings
Note: See TracBrowser for help on using the repository browser.