Ignore:
Timestamp:
Jan 29, 2022, 7:22:11 PM (2 years ago)
Author:
dcugnet
Message:

FIx for last version: function version of strReduce crashes with gfortran (but not for ifort) => back to subroutine version.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/misc/strings_mod.F90

    r4067 r4068  
    55  PRIVATE
    66  PUBLIC :: maxlen, init_printout, msg, fmsg, get_in, lunout, prt_level
    7   PUBLIC :: strLower, strHead, strStack,  strReduce,  strClean, strFind,  strIdx, find
    8   PUBLIC :: strUpper, strTail, strStackm, strReducef, strParse, strCount, strReplace, cat
     7  PUBLIC :: strLower, strHead, strStack,  strCount, strReduce,  strClean, strIdx
     8  PUBLIC :: strUpper, strTail, strStackm, strParse, strReplace, strFind, find, cat
    99  PUBLIC :: dispTable, dispOutliers, dispNameList
    1010  PUBLIC :: is_numeric, bool2str, int2str, real2str, dble2str
     
    347347  INTEGER,          OPTIONAL,    INTENT(OUT)   :: nb
    348348  CHARACTER(LEN=maxlen), ALLOCATABLE :: s1(:)
    349   INTEGER :: n
    350   s1 = strReducef(str, n); CALL MOVE_ALLOC(FROM=s1, TO=str)
    351   IF(PRESENT(nb)) nb = n
     349  INTEGER :: k, n, n1
     350  IF(PRESENT(nb)) nb = 0
     351  CALL MOVE_ALLOC(FROM=str, TO=s1); CALL strClean(s1)
     352  n1 = SIZE(s1, DIM=1)                                     !--- Total nb. of elements in "s1"
     353  n  = COUNT( [( ALL(s1(1:k-1)/=s1(k)), k=1, n1 )] )       !--- Nb of unique elements in "s1"
     354  ALLOCATE(str(n))
     355  IF(n==0) RETURN
     356  str(1) = s1(1)
     357  n=1; DO k=1,n1; IF(ANY(s1(1:k-1)==s1(k))) CYCLE; n=n+1; str(n)=s1(k); END DO
     358  IF(PRESENT(nb)) nb=n
    352359END SUBROUTINE strReduce_1
    353360!==============================================================================================================================
     
    370377  END IF
    371378END SUBROUTINE strReduce_2
    372 !==============================================================================================================================
    373 FUNCTION strReducef(str_in, nb) RESULT(str_ou)
    374   CHARACTER(LEN=*),           INTENT(IN)  :: str_in(:)
    375   INTEGER,          OPTIONAL, INTENT(OUT) :: nb
    376   CHARACTER(LEN=LEN(str_in)), ALLOCATABLE :: str_ou(:)
    377   CHARACTER(LEN=LEN(str_in)), ALLOCATABLE :: s1(:)
    378   INTEGER :: k, n, n1
    379   IF(PRESENT(nb)) nb = 0
    380   s1 = str_in; CALL strClean(s1)
    381   n1 = SIZE(s1, DIM=1)                                     !--- Total nb of  elements in "s1"
    382   n  = COUNT( [( ALL(s1(1:k-1)/=s1(k)), k=1, n1 )] )       !--- Nb of unique elements in "s1"
    383   ALLOCATE(str_ou(n)); IF(n==0) RETURN; str_ou(1) = s1(1)
    384   n=1; DO k=2,n1; IF(ANY(s1(1:k-1)==s1(k))) CYCLE; n=n+1; str_ou(n)=s1(k); END DO
    385   IF(PRESENT(nb)) nb = n
    386 END FUNCTION strReducef
    387379!==============================================================================================================================
    388380
Note: See TracChangeset for help on using the changeset viewer.