MODULE strings_mod IMPLICIT NONE PRIVATE PUBLIC :: maxlen, init_printout, msg, fmsg, get_in, lunout, prt_level PUBLIC :: strLower, strHead, strStack, strCount, strReduce, strClean, strIdx PUBLIC :: strUpper, strTail, strStackm, strParse, strReplace, strFind, find, cat PUBLIC :: dispTable, dispOutliers, dispNameList PUBLIC :: is_numeric, bool2str, int2str, real2str, dble2str PUBLIC :: reduceExpr, str2bool, str2int, str2real, str2dble PUBLIC :: addQuotes, testFile, checkList, removeComment, test INTERFACE get_in; MODULE PROCEDURE getin_s, getin_i, getin_r, getin_l; END INTERFACE get_in INTERFACE msg; MODULE PROCEDURE msg_1, msg_m; END INTERFACE msg INTERFACE fmsg; MODULE PROCEDURE fmsg_1, fmsg_m; END INTERFACE fmsg INTERFACE strHead; MODULE PROCEDURE strHead_1, strHead_m; END INTERFACE strHead INTERFACE strTail; MODULE PROCEDURE strTail_1, strTail_m; END INTERFACE strTail INTERFACE strClean; MODULE PROCEDURE strClean_1, strClean_m; END INTERFACE strClean INTERFACE strReduce; MODULE PROCEDURE strReduce_1, strReduce_2; END INTERFACE strReduce INTERFACE strIdx; MODULE PROCEDURE strIdx_1, strIdx_m; END INTERFACE strIdx INTERFACE strCount; MODULE PROCEDURE strCount_m1, strCount_11, strCount_1m; END INTERFACE strCount INTERFACE strReplace; MODULE PROCEDURE strReplace_1, strReplace_m; END INTERFACE strReplace INTERFACE cat; MODULE PROCEDURE horzcat_s1, horzcat_i1, horzcat_r1, & ! horzcat_d1, horzcat_dm, horzcat_sm, horzcat_im, horzcat_rm; END INTERFACE cat INTERFACE find; MODULE PROCEDURE strFind, find_int, find_boo; END INTERFACE find INTERFACE dispOutliers; MODULE PROCEDURE dispOutliers_1, dispOutliers_2; END INTERFACE dispOutliers INTERFACE reduceExpr; MODULE PROCEDURE reduceExpr_1, reduceExpr_m; END INTERFACE reduceExpr INTERFACE addQuotes; MODULE PROCEDURE addQuotes_1, addQuotes_m; END INTERFACE addQuotes INTERFACE testFile; MODULE PROCEDURE testFile_1, testFile_m; END INTERFACE testFile INTEGER, PARAMETER :: maxlen = 256 !--- Standard maximum length for strings INTEGER, SAVE :: lunout = 6 !--- Printing unit (default: 6, ie. on screen) INTEGER, SAVE :: prt_level = 1 !--- Printing level (default: 1, ie. print all) CONTAINS !============================================================================================================================== LOGICAL FUNCTION test(lcond, lout) RESULT(lerr) LOGICAL, INTENT(IN) :: lcond LOGICAL, INTENT(OUT) :: lout lerr = lcond; lout = lcond END FUNCTION test !============================================================================================================================== !============================================================================================================================== SUBROUTINE init_printout(lunout_, prt_level_) INTEGER, INTENT(IN) :: lunout_, prt_level_ lunout = lunout_ prt_level = prt_level_ END SUBROUTINE init_printout !============================================================================================================================== !============================================================================================================================== !=== Same as getin ; additional last argument: the default value. !============================================================================================================================== SUBROUTINE getin_s(nam, val, def) USE ioipsl_getincom, ONLY: getin CHARACTER(LEN=*), INTENT(IN) :: nam CHARACTER(LEN=*), INTENT(INOUT) :: val CHARACTER(LEN=*), INTENT(IN) :: def val = def; CALL getin(nam, val) IF(val/=def) WRITE(lunout,*)TRIM(nam)//' = '//TRIM(val) END SUBROUTINE getin_s !============================================================================================================================== SUBROUTINE getin_i(nam, val, def) USE ioipsl_getincom, ONLY: getin CHARACTER(LEN=*), INTENT(IN) :: nam INTEGER, INTENT(INOUT) :: val INTEGER, INTENT(IN) :: def val = def; CALL getin(nam, val) IF(val/=def) WRITE(lunout,*)TRIM(nam)//' = '//TRIM(int2str(val)) END SUBROUTINE getin_i !============================================================================================================================== SUBROUTINE getin_r(nam, val, def) USE ioipsl_getincom, ONLY: getin CHARACTER(LEN=*), INTENT(IN) :: nam REAL, INTENT(INOUT) :: val REAL, INTENT(IN) :: def val = def; CALL getin(nam, val) IF(val/=def) WRITE(lunout,*)TRIM(nam)//' = '//TRIM(real2str(val)) END SUBROUTINE getin_r !============================================================================================================================== SUBROUTINE getin_l(nam, val, def) USE ioipsl_getincom, ONLY: getin CHARACTER(LEN=*), INTENT(IN) :: nam LOGICAL, INTENT(INOUT) :: val LOGICAL, INTENT(IN) :: def val = def; CALL getin(nam, val) IF(val.NEQV.def) WRITE(lunout,*)TRIM(nam)//' = '//TRIM(bool2str(val)) END SUBROUTINE getin_l !============================================================================================================================== !============================================================================================================================== !=== Display one or several messages, one each line, starting with the current routine name "modname". !============================================================================================================================== SUBROUTINE msg_1(str, modname, ll, unit) !--- Display a simple message "str". Optional parameters: ! * "modname": module name, displayed in front of the message (with ": " separator) if present. ! * "ll": message trigger ; message is displayed only if ll==.TRUE. ! * "unit": write unit (by default: "lunout") CHARACTER(LEN=*), INTENT(IN) :: str CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: modname LOGICAL, OPTIONAL, INTENT(IN) :: ll INTEGER, OPTIONAL, INTENT(IN) :: unit !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen) :: subn INTEGER :: unt subn = ''; IF(PRESENT(modname)) subn = modname IF(PRESENT(ll)) THEN; IF(.NOT.ll) RETURN; END IF unt = lunout; IF(PRESENT(unit)) unt = unit IF(subn == '') WRITE(unt,'(a)') str !--- Simple message IF(subn /= '') WRITE(unt,'(a)') TRIM(subn)//': '//str !--- Routine name provided END SUBROUTINE msg_1 !============================================================================================================================== SUBROUTINE msg_m(str, modname, ll, unit, nmax) !--- Same as msg_1 with multiple strings that are stacked (separator: coma) on up to "nmax" full lines. CHARACTER(LEN=*), INTENT(IN) :: str(:) CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: modname LOGICAL, OPTIONAL, INTENT(IN) :: ll INTEGER, OPTIONAL, INTENT(IN) :: unit INTEGER, OPTIONAL, INTENT(IN) :: nmax !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen), ALLOCATABLE :: s(:) CHARACTER(LEN=maxlen) :: subn INTEGER :: unt, nmx, k LOGICAL :: l subn = ''; IF(PRESENT(modname)) subn = modname l = .TRUE.; IF(PRESENT(ll)) l = ll unt = lunout; IF(PRESENT(unit)) unt = unit nmx = 128; IF(PRESENT(nmax)) nmx = nmax s = strStackm(str, ', ', nmx) DO k=1,SIZE(s); CALL msg_1(s(k), subn, l, unt); END DO END SUBROUTINE msg_m !============================================================================================================================== LOGICAL FUNCTION fmsg_1(str, modname, ll, unit) RESULT(l) CHARACTER(LEN=*), INTENT(IN) :: str CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: modname LOGICAL, OPTIONAL, INTENT(IN) :: ll INTEGER, OPTIONAL, INTENT(IN) :: unit !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen) :: subn INTEGER :: unt subn = ''; IF(PRESENT(modname)) subn = modname l = .TRUE.; IF(PRESENT(ll)) l = ll unt = lunout; IF(PRESENT(unit)) unt = unit CALL msg_1(str, subn, l, unt) END FUNCTION fmsg_1 !============================================================================================================================== LOGICAL FUNCTION fmsg_m(str, modname, ll, unit, nmax) RESULT(l) CHARACTER(LEN=*), INTENT(IN) :: str(:) CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: modname LOGICAL, OPTIONAL, INTENT(IN) :: ll INTEGER, OPTIONAL, INTENT(IN) :: unit INTEGER, OPTIONAL, INTENT(IN) :: nmax !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen) :: subn INTEGER :: unt, nmx subn = ''; IF(PRESENT(modname)) subn = modname l = .TRUE.; IF(PRESENT(ll)) l = ll unt = lunout; IF(PRESENT(unit)) unt = unit nmx = 128; IF(PRESENT(nmax)) nmx = nmax CALL msg_m(str, subn, l, unt, nmx) END FUNCTION fmsg_m !============================================================================================================================== !============================================================================================================================== !=== Lower/upper case conversion function. ==================================================================================== !============================================================================================================================== ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION strLower(str) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str INTEGER :: k out = str DO k=1,LEN_TRIM(str) IF(str(k:k)>='A' .AND. str(k:k)<='Z') out(k:k)=ACHAR(IACHAR(str(k:k))+32) END DO END FUNCTION strLower !============================================================================================================================== ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION strUpper(str) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str INTEGER :: k out = str DO k=1,LEN_TRIM(str) IF(str(k:k)>='a' .AND. str(k:k)<='z') out(k:k)=ACHAR(IACHAR(str(k:k))-32) END DO END FUNCTION strUpper !============================================================================================================================== !============================================================================================================================== !=== Extract the substring in front of the last (first if lFirst==TRUE) occurrence of separator "sep" in "str" ================ !=== Examples for str='a_b_c' and sep='_' and the bash command with the same effect: ================ !=== * strHead(..,.FALSE.) = 'a' ${str%%$sep*} ================ !=== * strHead(..,.TRUE.) = 'a_b' ${str%$sep*} ================ !============================================================================================================================== CHARACTER(LEN=maxlen) FUNCTION strHead_1(str,sep,lFirst) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: sep LOGICAL, OPTIONAL, INTENT(IN) :: lFirst !------------------------------------------------------------------------------------------------------------------------------ LOGICAL :: lf lf = .FALSE.; IF(PRESENT(lFirst)) lf=lFirst IF(PRESENT(sep)) THEN out = str(1:INDEX(str,sep,.NOT.lf)-1) ELSE out = str(1:INDEX(str,'/',.NOT.lf)-1) END IF IF(out == '') out = str END FUNCTION strHead_1 !============================================================================================================================== FUNCTION strHead_m(str,sep,lFirst) RESULT(out) CHARACTER(LEN=maxlen), ALLOCATABLE :: out(:) CHARACTER(LEN=*), INTENT(IN) :: str(:) CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: sep LOGICAL, OPTIONAL, INTENT(IN) :: lFirst !------------------------------------------------------------------------------------------------------------------------------ LOGICAL :: lf INTEGER :: k lf = .FALSE.; IF(PRESENT(lFirst)) lf=lFirst IF(PRESENT(sep)) THEN out = [(strHead_1(str(k), sep, lf), k=1, SIZE(str))] ELSE out = [(strHead_1(str(k), lFirst=lf), k=1, SIZE(str))] END IF END FUNCTION strHead_m !============================================================================================================================== !=== Extract the substring following the last (first if lFirst==TRUE) occurrence of separator "sep" in "str" ================ !=== Examples for str='a_b_c' and sep='_' and the bash command with the same effect: ================ !=== * strTail(..,.FALSE.) = 'c' ${str#*$sep} ================ !=== * strTail(..,.TRUE.) = 'b_c' ${str##*$sep} ================ !============================================================================================================================== CHARACTER(LEN=maxlen) FUNCTION strTail_1(str,sep,lFirst) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: sep LOGICAL, OPTIONAL, INTENT(IN) :: lFirst !------------------------------------------------------------------------------------------------------------------------------ LOGICAL :: lf lf = .FALSE.; IF(PRESENT(lFirst)) lf=lFirst IF(PRESENT(sep)) THEN out = str(INDEX(str,sep,.NOT.lf)+LEN(sep):LEN_TRIM(str)) ELSE out = str(INDEX(str,'/',.NOT.lf)+1:LEN_TRIM(str)) END IF IF(out == '') out = str END FUNCTION strTail_1 !============================================================================================================================== FUNCTION strTail_m(str,sep,lFirst) RESULT(out) CHARACTER(LEN=maxlen), ALLOCATABLE :: out(:) CHARACTER(LEN=*), INTENT(IN) :: str(:) CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: sep LOGICAL, OPTIONAL, INTENT(IN) :: lFirst !------------------------------------------------------------------------------------------------------------------------------ LOGICAL :: lf INTEGER :: k lf = .FALSE.; IF(PRESENT(lFirst)) lf=lFirst IF(PRESENT(sep)) THEN out = [(strTail_1(str(k), sep, lf), k=1, SIZE(str))] ELSE out = [(strTail_1(str(k), lFirst=lf), k=1, SIZE(str))] END IF END FUNCTION strTail_m !============================================================================================================================== !============================================================================================================================== !=== Concatenates the strings "str(:)" with separator "sep" into a single string using a separator (',' by default). ========== !============================================================================================================================== FUNCTION strStack(str, sep, mask) RESULT(out) CHARACTER(LEN=:), ALLOCATABLE :: out CHARACTER(LEN=*), INTENT(IN) :: str(:) CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: sep LOGICAL, OPTIONAL, INTENT(IN) :: mask(:) !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=:), ALLOCATABLE :: s INTEGER :: is, i0 IF(SIZE(str) == 0) THEN; out = ''; RETURN; END IF ALLOCATE(s, SOURCE=', '); IF(PRESENT(sep)) s=sep IF(PRESENT(mask)) THEN IF(ALL(.NOT.mask)) THEN; out = ''; RETURN; END IF i0 = 0; DO WHILE(.NOT.mask(i0+1)); i0 = i0+1; END DO out = str(i0); DO is=i0+1,SIZE(str, DIM=1); IF(.NOT.mask(is)) CYCLE; out = TRIM(out)//s//TRIM(str(is)); END DO ELSE out = str(1); DO is=2,SIZE(str, DIM=1); out = TRIM(out)//s//TRIM(str(is)); END DO END IF END FUNCTION strStack !============================================================================================================================== !=== Concatenate the strings "str(:)" with separator "sep" into one or several lines of "nmax" characters max (for display) === !============================================================================================================================== FUNCTION strStackm(str, sep, nmax) RESULT(out) CHARACTER(LEN=maxlen), ALLOCATABLE :: out(:) CHARACTER(LEN=*), INTENT(IN) :: str(:) CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: sep INTEGER, OPTIONAL, INTENT(IN) :: nmax !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen), ALLOCATABLE :: t(:) CHARACTER(LEN=maxlen) :: sp INTEGER :: is, ns, no, mx, n IF(SIZE(str) == 0) THEN; out = ['']; RETURN; END IF sp =', '; IF(PRESENT(sep )) sp = sep ns = 2 ; IF(PRESENT(sep )) ns = LEN(sep) mx = 256; IF(PRESENT(nmax)) mx = nmax no = 1; out = [''] DO is = 1, SIZE(str) n = LEN_TRIM(str(is)); IF(out(no)/='') n = n+ns+LEN_TRIM(out(no)) !--- Line length after "str(is)" inclusion IF(out(no) == '') THEN out(no) = str(is) !--- Empty new line: set to "str(is)" ELSE IF(n <= mx) THEN out(no) = TRIM(out(no))//sp(1:ns)//TRIM(str(is)) !--- Append "str(is)" to the current line ELSE ALLOCATE(t(no+1)); t(1:no) = out; no=no+1; t(no) = str(is) !--- Full line: "str(si)" put in next line CALL MOVE_ALLOC(FROM=t, TO=out) END IF END DO END FUNCTION strStackm !============================================================================================================================== !============================================================================================================================== !=== String cleaning: replace tabulation by spaces, remove NULL characters and comments. ====================================== !============================================================================================================================== SUBROUTINE strClean_1(str) CHARACTER(LEN=*), INTENT(INOUT) :: str INTEGER :: k, n, m n = LEN(str) DO k = n, 1, -1 m = IACHAR(str(k:k)) IF(m==9) str(k:k) = ' ' !--- Replace the tabulations with spaces IF(m==0) str(k:n) = str(k+1:n)//' ' !--- Remove the NULL characters END DO m = INDEX(str,'!')-1; IF(m==-1) m = LEN_TRIM(str) !--- Remove end of line comment str = ADJUSTL(str(1:m)) END SUBROUTINE strClean_1 !============================================================================================================================== SUBROUTINE strClean_m(str) CHARACTER(LEN=*), INTENT(INOUT) :: str(:) INTEGER :: k DO k = 1, SIZE(str); CALL strClean_1(str(k)); END DO END SUBROUTINE strClean_m !============================================================================================================================== !============================================================================================================================== !=== strReduce_1(str1) : Remove duplicated elements of str1. =========================================================== !=== strReduce_2(str1,str2): Append str1 with new elements of str2. =========================================================== !============================================================================================================================== SUBROUTINE strReduce_1(str, nb) CHARACTER(LEN=*), ALLOCATABLE, INTENT(INOUT) :: str(:) INTEGER, OPTIONAL, INTENT(OUT) :: nb !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen), ALLOCATABLE :: s1(:) INTEGER :: k, n, n1 IF(PRESENT(nb)) nb = 0 CALL MOVE_ALLOC(FROM=str, TO=s1); CALL strClean(s1) n1 = SIZE(s1, DIM=1) !--- Total nb. of elements in "s1" n = COUNT( [( ALL(s1(1:k-1)/=s1(k)), k=1, n1 )] ) !--- Nb of unique elements in "s1" ALLOCATE(str(n)) IF(n==0) RETURN str(1) = s1(1) n=1; DO k=2,n1; IF(ANY(s1(1:k-1)==s1(k))) CYCLE; n=n+1; str(n)=s1(k); END DO IF(PRESENT(nb)) nb=n END SUBROUTINE strReduce_1 !============================================================================================================================== SUBROUTINE strReduce_2(str1, str2) CHARACTER(LEN=*), ALLOCATABLE, INTENT(INOUT) :: str1(:) CHARACTER(LEN=*), INTENT(IN) :: str2(:) !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen), ALLOCATABLE :: s1(:), s2(:) INTEGER :: k IF(SIZE(str2)==0) RETURN s2 = str2; CALL strClean(s2) IF(.NOT.ALLOCATED(s2)) RETURN IF(SIZE(s2) == 0) THEN; DEALLOCATE(s2); RETURN; END IF IF(.NOT.ALLOCATED(str1)) THEN str1 = s2 ELSE IF(SIZE(str1)==0) THEN str1 = s2 ELSE s1 = str1; CALL strClean(s1) str1 = [s1, PACK(s2, MASK= [( ALL(s1(:) /= s2(k)), k=1, SIZE(s2) )] ) ] END IF END SUBROUTINE strReduce_2 !============================================================================================================================== !============================================================================================================================== !=== GET THE INDEX OF THE FIRST APPEARANCE IN THE STRING VECTOR "str(:)" OF THE STRING(s) "s[(:)]" ============================ !=== OPTIONALY: GET THE NUMBER OF FOUND ELEMENTS "n". NB: UNFOUND => INDEX=0 ============================ !============================================================================================================================== INTEGER FUNCTION strIdx_1(str, s) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str(:), s DO out = 1, SIZE(str); IF(str(out) == s) EXIT; END DO IF(out == 1+SIZE(str) .OR. SIZE(str)==0) out = 0 END FUNCTION strIdx_1 !============================================================================================================================== FUNCTION strIdx_m(str, s, n) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str(:), s(:) INTEGER, OPTIONAL, INTENT(OUT) :: n INTEGER, ALLOCATABLE :: out(:) !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: k out = [(strIdx_1(str(:), s(k)), k=1, SIZE(s))] IF(PRESENT(n)) n = COUNT(out(:)/=0) END FUNCTION strIdx_m !============================================================================================================================== !============================================================================================================================== !=== GET THE INDEX LIST OF THE ELEMENTS OF "str(:)" EQUAL TO "s" AND OPTIONALY, ITS LENGTH "n" ================================ !============================================================================================================================== FUNCTION strFind(str, s, n) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str(:), s INTEGER, OPTIONAL, INTENT(OUT) :: n INTEGER, ALLOCATABLE :: out(:) !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: k out = PACK( [(k, k=1, SIZE(str(:), DIM=1))], MASK = str(:) == s ) IF(PRESENT(n)) n = SIZE(out(:), DIM=1) END FUNCTION strFind !============================================================================================================================== FUNCTION find_int(i,j,n) RESULT(out) INTEGER, INTENT(IN) :: i(:), j INTEGER, OPTIONAL, INTENT(OUT) :: n INTEGER, ALLOCATABLE :: out(:) !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: k out = PACK( [(k, k=1, SIZE(i(:), DIM=1))], MASK = i(:) == j ) IF(PRESENT(n)) n = SIZE(out(:), DIM=1) END FUNCTION find_int !============================================================================================================================== FUNCTION find_boo(l,n) RESULT(out) LOGICAL, INTENT(IN) :: l(:) INTEGER, OPTIONAL, INTENT(OUT) :: n INTEGER, ALLOCATABLE :: out(:) !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: k out = PACK( [(k, k=1, SIZE(l(:), DIM=1))], MASK = l(:) ) IF(PRESENT(n)) n = SIZE(out(:), DIM=1) END FUNCTION find_boo !============================================================================================================================== !============================================================================================================================== !=== GET THE INDEX IN "rawList" OF THE 1ST APPEARANCE OF ONE OF THE "del(:)" SEPARATORS (0 IF NONE OF THEM ARE PRESENT) !=== IF lSc == .TRUE.: * SKIP HEAD SIGNS OR EXPONENTS SIGNS THAT SHOULD NOT BE CONFUSED WITH SEPARATORS !=== * THEN TEST WHETHER THE STRING FROM START TO THE FOUND SEPARATOR IS A CORRECTLY FORMATTED NUMBER !============================================================================================================================== LOGICAL FUNCTION strIdx_prv(rawList, del, ibeg, idx, idel, lSc) RESULT(lerr) CHARACTER(LEN=*), INTENT(IN) :: rawList !--- String in which delimiters have to be identified CHARACTER(LEN=*), INTENT(IN) :: del(:) !--- List of delimiters INTEGER, INTENT(IN) :: ibeg !--- Start index INTEGER, INTENT(OUT) :: idx !--- Index of the first identified delimiter in "rawList" INTEGER, INTENT(OUT) :: idel !--- Index of the identified delimiter (0 if idx==0) LOGICAL, OPTIONAL, INTENT(IN) :: lSc !--- Care about nbs with front sign or in scient. notation !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: idx0 !--- Used to display an identified non-numeric string lerr = .FALSE. idx = strIdx1(rawList, del, ibeg, idel) !--- idx/=0: del(idel) is at position "idx" in "rawList" IF(.NOT.PRESENT(lSc)) RETURN !--- No need to check exceptions for numbers => finished IF(.NOT. lSc ) RETURN !--- No need to check exceptions for numbers => finished !=== No delimiter found: the whole string must be a valid number IF(idx == 0) THEN !--- No element of "del" in "rawList" lerr = .NOT.is_numeric(rawList(ibeg:LEN_TRIM(rawList))) !--- String must be a number IF(lerr) idx = LEN_TRIM(rawList); RETURN !--- Set idx so that rawList(ibeg:idx-1) = whole string END IF IF(test(idx == 1 .AND. INDEX('+-',del(idel)) /= 0, lerr)) RETURN !--- The front delimiter is different from +/-: error IF( idx /= 1 .AND. is_numeric(rawList(ibeg:idx-1))) RETURN !--- The input string head is a valid number !=== The string part in front of the 1st delimiter is not a valid number: search for next delimiter index "idx" idx0 = idx ; idx = strIdx1(rawList, del, idx+1, idel) !--- Keep start index because idx is recycled IF(idx == 0) THEN lerr = .NOT.is_numeric(rawList(ibeg:LEN_TRIM(rawList))) !--- No other delimiter: whole string must be a valid numb IF(lerr) idx = idx0; RETURN END IF lerr = .NOT.is_numeric(rawList(ibeg:idx-1)) CONTAINS !------------------------------------------------------------------------------------------------------------------------------ INTEGER FUNCTION strIdx1(str, del, ib, id) RESULT(i) !--- Get the index of the first appereance of one of the delimiters "del(:)" in "str" starting from position "ib". !--- "id" is the index in "del(:)" of the first delimiter found. IMPLICIT NONE CHARACTER(LEN=*), INTENT(IN) :: str, del(:) INTEGER, INTENT(IN) :: ib INTEGER, INTENT(OUT) :: id !------------------------------------------------------------------------------------------------------------------------------ DO i = ib, LEN_TRIM(str); id = strIdx(del, str(i:i)); IF(id /= 0) EXIT; END DO IF(i > LEN_TRIM(str)) THEN; i = 0; id = 0; END IF END FUNCTION strIdx1 END FUNCTION strIdx_prv !============================================================================================================================== !============================================================================================================================== !=== Count the number of elements separated by "delimiter" in list "rawList". ================================================= !============================================================================================================================== LOGICAL FUNCTION strCount_11(rawList, delimiter, nb, lSc) RESULT(lerr) CHARACTER(LEN=*), INTENT(IN) :: rawList CHARACTER(LEN=*), INTENT(IN) :: delimiter INTEGER, INTENT(OUT) :: nb LOGICAL, OPTIONAL, INTENT(IN) :: lSc !------------------------------------------------------------------------------------------------------------------------------ LOGICAL :: ll ll = .FALSE.; IF(PRESENT(lSc)) ll = lSc lerr = strCount_1m(rawList, [delimiter], nb, ll) END FUNCTION strCount_11 !============================================================================================================================== LOGICAL FUNCTION strCount_m1(rawList, delimiter, nb, lSc) RESULT(lerr) CHARACTER(LEN=*), INTENT(IN) :: rawList(:) CHARACTER(LEN=*), INTENT(IN) :: delimiter INTEGER, ALLOCATABLE, INTENT(OUT) :: nb(:) LOGICAL, OPTIONAL, INTENT(IN) :: lSc !------------------------------------------------------------------------------------------------------------------------------ LOGICAL :: ll INTEGER :: id ll = .FALSE.; IF(PRESENT(lSc)) ll = lSc .AND. INDEX('+-', delimiter) /= 0 lerr = .TRUE. ALLOCATE(nb(SIZE(rawList))) DO id = 1, SIZE(rawList) lerr = lerr .AND. strCount_1m(rawList(id), [delimiter], nb(id), ll) END DO END FUNCTION strCount_m1 !============================================================================================================================== LOGICAL FUNCTION strCount_1m(rawList, delimiter, nb, lSc) RESULT(lerr) CHARACTER(LEN=*), INTENT(IN) :: rawList CHARACTER(LEN=*), INTENT(IN) :: delimiter(:) INTEGER, INTENT(OUT) :: nb LOGICAL, OPTIONAL, INTENT(IN) :: lSc !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: ib, ie, jd, nr LOGICAL :: ll CHARACTER(LEN=1024) :: r lerr = .FALSE. ll = .FALSE.; IF(PRESENT(lSc)) ll = lSc r = TRIM(ADJUSTL(rawList)) nr = LEN_TRIM(r); IF(nr == 0) RETURN nb = 1; ib = 1 DO lerr = strIdx_prv(r, delimiter, ib, ie, jd, ll) IF(fmsg('"'//TRIM(r(ib:ie-1))//'" is not numeric', ll=lerr)) RETURN IF(ie == 0 .OR. jd == 0) EXIT ib = ie + LEN(delimiter(jd)) DO WHILE(r(ib:ib) == ' ' .AND. ib < nr); ib = ib + 1; END DO !--- Skip spaces before next chain nb = nb + 1 END DO END FUNCTION strCount_1m !============================================================================================================================== !============================================================================================================================== !=== Purpose: Parse "delimiter"-separated list "rawList" into the pair keys(:), vals(:). ==================================== !=== Corresponding "vals" remains empty if the element does not contain "=" sign. ==================================== !============================================================================================================================== LOGICAL FUNCTION strParse(rawList, delimiter, keys, n, vals) RESULT(lerr) CHARACTER(LEN=*), INTENT(IN) :: rawList, delimiter CHARACTER(LEN=maxlen), ALLOCATABLE, INTENT(OUT) :: keys(:) INTEGER, OPTIONAL, INTENT(OUT) :: n CHARACTER(LEN=maxlen), ALLOCATABLE, OPTIONAL, INTENT(OUT) :: vals(:) !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=1024) :: r INTEGER :: nr, nk lerr = .FALSE. r = TRIM(ADJUSTL(rawList)) nr = LEN_TRIM(r); IF(nr == 0) THEN; keys = ['']; RETURN; END IF CALL strParse_prv(nk) !--- COUNT THE ELEMENTS ALLOCATE(keys(nk)) IF(PRESENT(vals)) THEN ALLOCATE(vals(nk)); CALL strParse_prv(nk, keys, vals) !--- PARSE THE KEYS ELSE CALL strParse_prv(nk, keys) !--- PARSE THE KEYS END IF IF(PRESENT(n)) n = nk CONTAINS !------------------------------------------------------------------------------------------------------------------------------ SUBROUTINE strParse_prv(nkeys, keys, vals) !--- * Get the number of elements after parsing ("nkeys" only is present) !--- * Parse the = pairs and store result in "keys" and "vals" (already allocated) IMPLICIT NONE INTEGER, INTENT(OUT) :: nkeys CHARACTER(LEN=maxlen), OPTIONAL, INTENT(OUT) :: keys(:) CHARACTER(LEN=maxlen), OPTIONAL, INTENT(OUT) :: vals(:) !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: ib, ie nkeys = 1; ib = 1 DO ie = INDEX(rawList(ib:nr), delimiter)+ib-1 !--- Determine the next separator start index IF(ie == ib-1) EXIT IF(PRESENT(keys)) keys(nkeys) = r(ib:ie-1) !--- Get the ikth key IF(PRESENT(vals)) CALL parseKeys(keys(nkeys), vals(nkeys)) !--- Parse the ikth = pair ib = ie + LEN(delimiter) DO WHILE(r(ib:ib) == ' ' .AND. ib < nr); ib = ib + 1; END DO !--- Skip spaces before next chain nkeys = nkeys+1 END DO IF(PRESENT(keys)) keys(nkeys) = r(ib:nr) !--- Get the last key IF(PRESENT(vals)) CALL parseKeys(keys(nkeys), vals(nkeys)) !--- Parse the last = pair END SUBROUTINE strParse_prv !------------------------------------------------------------------------------------------------------------------------------ SUBROUTINE parseKeys(key, val) CHARACTER(LEN=*), INTENT(INOUT) :: key CHARACTER(LEN=*), INTENT(OUT) :: val !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: ix ix = INDEX(key, '='); IF(ix == 0) RETURN !--- First "=" index in "key" val = ADJUSTL(key(ix+1:LEN_TRIM(key))) key = ADJUSTL(key(1:ix-1)) END SUBROUTINE parseKeys END FUNCTION strParse !============================================================================================================================== LOGICAL FUNCTION strParse_m(rawList, delimiter, keys, n, vals, lSc, id) RESULT(lerr) CHARACTER(LEN=*), INTENT(IN) :: rawList, delimiter(:) CHARACTER(LEN=maxlen), ALLOCATABLE, INTENT(OUT) :: keys(:) !--- Parsed keys vector INTEGER, OPTIONAL, INTENT(OUT) :: n !--- Length of the parsed vector CHARACTER(LEN=maxlen), OPTIONAL, ALLOCATABLE, INTENT(OUT) :: vals(:) !--- Values for = keys LOGICAL, OPTIONAL, INTENT(IN) :: lSc !--- Take care about numbers in scientific notation INTEGER, OPTIONAL, ALLOCATABLE, INTENT(OUT) :: id(:) !--- Indexes of the separators in "delimiter(:)" vector !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=1024) :: r INTEGER :: nr, ik, nk, ib, ie, jd LOGICAL :: ll ll = .FALSE.; IF(PRESENT(lSc)) ll = lSc IF(test(fmsg("Couldn't parse list: non-numerical strings were found", ll=strCount_1m(rawList, delimiter, nk, ll)),lerr)) RETURN !--- FEW ALLOCATIONS ALLOCATE(keys(nk)) IF(PRESENT(vals)) ALLOCATE(vals(nk)) IF(PRESENT(id)) ALLOCATE(id(nk-1)) IF(PRESENT(n)) n = nk !--- PARSING r = TRIM(ADJUSTL(rawList)) nr = LEN_TRIM(r); IF(nr == 0) RETURN ib = 1 DO ik = 1, nk-1 IF(test(fmsg('Non-numeric values found', ll=strIdx_prv(r, delimiter, ib, ie, jd, ll)),lerr)) RETURN keys(ik) = r(ib:ie-1) IF(PRESENT(vals)) CALL parseKeys(keys(ik), vals(ik)) !--- Parse a = pair IF(PRESENT(id )) id(ik) = jd !--- Index in "delimiter(:)" of the "ik"th delimiter ib = ie + LEN_TRIM( delimiter(jd) ) !--- Length of the current delimiter DO WHILE(r(ib:ib) == ' ' .AND. ib < nr); ib = ib + 1; END DO !--- Skip spaces before next chain END DO keys(nk) = r(ib:nr) IF(PRESENT(vals)) CALL parseKeys(keys(nk), vals(nk)) !--- Parse a = pair CONTAINS !------------------------------------------------------------------------------------------------------------------------------ SUBROUTINE parseKeys(key, val) CHARACTER(LEN=*), INTENT(INOUT) :: key CHARACTER(LEN=*), INTENT(OUT) :: val !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: ix ix = INDEX(key, '='); IF(ix == 0) RETURN !--- First "=" index in "key" val = ADJUSTL(key(ix+1:LEN_TRIM(key))) key = ADJUSTL(key(1:ix-1)) END SUBROUTINE parseKeys END FUNCTION strParse_m !============================================================================================================================== !============================================================================================================================== !=== String substitution: replace "key" by "val" each time it appears in "str". !============================================================================================================================== SUBROUTINE strReplace_1(str, key, val, lsurr) CHARACTER(LEN=*), INTENT(INOUT) :: str !--- Main string CHARACTER(LEN=*), INTENT(IN) :: key, val !--- "key" will be replaced by "val" LOGICAL, OPTIONAL, INTENT(IN) :: lsurr !--- TRUE => key must be surrounded by special characters to be substituted !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: i0, ix, nk, ns LOGICAL :: lsur, lb, le lsur = .FALSE.; IF(PRESENT(lsurr)) lsur = lsurr nk = LEN_TRIM(key) i0 = 1 DO ns = LEN_TRIM(str) ix = INDEX(str(i0:ns), TRIM(key)) !--- First appearance index of "key" in "s", starting from index "i0" IF(ix == 0) EXIT ix = ix + i0 -1 IF(lsur) THEN !--- Key must be surrounded by special characters !--- lb=.TRUE.: key is at the very beginning of "str" or located after a special character lb = ix ==1; IF(.NOT.lb) lb = INDEX('+-*/()^', str(ix-1 :ix-1 ))/=0 !--- le=.TRUE.: key is at the very end of "str" or located before a special character le = ix+nk-1==ns; IF(.NOT.le) le = INDEX('+-*/()^', str(ix+nk:ix+nk))/=0 IF(.NOT.(lb.AND.le)) THEN; i0 = i0 + nk; CYCLE; END IF END IF str = str(1:ix-1)//TRIM(val)//str(ix+nk:ns) END DO END SUBROUTINE strReplace_1 !============================================================================================================================== SUBROUTINE strReplace_m(str, key, val, lsurr) CHARACTER(LEN=*), INTENT(INOUT) :: str(:) !--- Main strings vector CHARACTER(LEN=*), INTENT(IN) :: key, val !--- "key" will be replaced by "val" LOGICAL, OPTIONAL, INTENT(IN) :: lsurr !--- TRUE => key must be surrounded by special characters to be substituted INTEGER :: k LOGICAL :: ll ll=.FALSE.; IF(PRESENT(lsurr)) ll=lsurr DO k=1, SIZE(str); CALL strReplace_1(str(k),key,val,ll); END DO END SUBROUTINE strReplace_m !============================================================================================================================== !============================================================================================================================== !=== Contatenate horizontally scalars/vectors of strings/integers/reals into a vector/array =================================== !============================================================================================================================== FUNCTION horzcat_s1(s0, s1, s2, s3, s4, s5, s6, s7, s8, s9) RESULT(out) CHARACTER(LEN=*), TARGET, INTENT(IN) :: s0 CHARACTER(LEN=*), OPTIONAL, TARGET, INTENT(IN) :: s1, s2, s3, s4, s5, s6, s7, s8, s9 CHARACTER(LEN=maxlen), ALLOCATABLE :: out(:) !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen), POINTER :: s LOGICAL :: lv(10) INTEGER :: iv lv = [ .TRUE. , PRESENT(s1), PRESENT(s2), PRESENT(s3), PRESENT(s4) , & PRESENT(s5), PRESENT(s6), PRESENT(s7), PRESENT(s8), PRESENT(s9) ] ALLOCATE(out(COUNT(lv))) DO iv=1, COUNT(lv) SELECT CASE(iv) CASE(1); s=> s0; CASE(2); s=> s1; CASE(3); s=> s2; CASE(4); s=> s3; CASE(5); s=> s4 CASE(6); s=> s5; CASE(7); s=> s6; CASE(8); s=> s7; CASE(9); s=> s8; CASE(10);s=> s9 END SELECT out(iv) = s END DO END FUNCTION horzcat_s1 !============================================================================================================================== FUNCTION horzcat_sm(s0, s1, s2, s3, s4, s5, s6, s7, s8, s9) RESULT(out) CHARACTER(LEN=*), TARGET, DIMENSION(:), INTENT(IN) :: s0 CHARACTER(LEN=*), OPTIONAL, TARGET, DIMENSION(:), INTENT(IN) :: s1, s2, s3, s4, s5, s6, s7, s8, s9 CHARACTER(LEN=maxlen), ALLOCATABLE :: out(:,:) !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen), POINTER :: s(:) LOGICAL :: lv(10) INTEGER :: nrow, ncol, iv, n lv = [ .TRUE. , PRESENT(s1), PRESENT(s2), PRESENT(s3), PRESENT(s4) , & PRESENT(s5), PRESENT(s6), PRESENT(s7), PRESENT(s8), PRESENT(s9) ] nrow = SIZE(s0); ncol=COUNT(lv) ALLOCATE(out(nrow, ncol)) DO iv=1, ncol SELECT CASE(iv) CASE(1); s=> s0; CASE(2); s=> s1; CASE(3); s=> s2; CASE(4); s=> s3; CASE(5); s=> s4 CASE(6); s=> s5; CASE(7); s=> s6; CASE(8); s=> s7; CASE(9); s=> s8; CASE(10);s=> s9 END SELECT n = SIZE(s, DIM=1) IF(n/=nrow) THEN; CALL msg("Can't concatenate vectors of differing lengths"); STOP; END IF out(:,iv) = s(:) END DO END FUNCTION horzcat_sm !============================================================================================================================== FUNCTION horzcat_i1(i0, i1, i2, i3, i4, i5, i6, i7, i8, i9) RESULT(out) INTEGER, TARGET, INTENT(IN) :: i0 INTEGER, OPTIONAL, TARGET, INTENT(IN) :: i1, i2, i3, i4, i5, i6, i7, i8, i9 INTEGER, ALLOCATABLE :: out(:) !------------------------------------------------------------------------------------------------------------------------------ INTEGER, POINTER :: i LOGICAL :: lv(10) INTEGER :: iv lv = [ .TRUE. , PRESENT(i1), PRESENT(i2), PRESENT(i3), PRESENT(i4) , & PRESENT(i5), PRESENT(i6), PRESENT(i7), PRESENT(i8), PRESENT(i9) ] ALLOCATE(out(COUNT(lv))) DO iv=1, COUNT(lv) SELECT CASE(iv) CASE(1); i=> i0; CASE(2); i=> i1; CASE(3); i=> i2; CASE(4); i=> i3; CASE(5); i=> i4 CASE(6); i=> i5; CASE(7); i=> i6; CASE(8); i=> i7; CASE(9); i=> i8; CASE(10);i=> i9 END SELECT out(iv) = i END DO END FUNCTION horzcat_i1 !============================================================================================================================== FUNCTION horzcat_im(i0, i1, i2, i3, i4, i5, i6, i7, i8, i9) RESULT(out) INTEGER, TARGET, DIMENSION(:), INTENT(IN) :: i0 INTEGER, OPTIONAL, TARGET, DIMENSION(:), INTENT(IN) :: i1, i2, i3, i4, i5, i6, i7, i8, i9 INTEGER, ALLOCATABLE :: out(:,:) !------------------------------------------------------------------------------------------------------------------------------ INTEGER, POINTER :: i(:) LOGICAL :: lv(10) INTEGER :: nrow, ncol, iv, n lv = [ .TRUE. , PRESENT(i1), PRESENT(i2), PRESENT(i3), PRESENT(i4) , & PRESENT(i5), PRESENT(i6), PRESENT(i7), PRESENT(i8), PRESENT(i9) ] nrow = SIZE(i0); ncol=COUNT(lv) ALLOCATE(out(nrow, ncol)) DO iv=1, ncol SELECT CASE(iv) CASE(1); i=> i0; CASE(2); i=> i1; CASE(3); i=> i2; CASE(4); i=> i3; CASE(5); i=> i4 CASE(6); i=> i5; CASE(7); i=> i6; CASE(8); i=> i7; CASE(9); i=> i8; CASE(10);i=> i9 END SELECT n = SIZE(i, DIM=1) IF(n/=nrow) THEN; CALL msg("Can't concatenate vectors of differing lengths"); STOP; END IF out(:,iv) = i(:) END DO END FUNCTION horzcat_im !============================================================================================================================== FUNCTION horzcat_r1(r0, r1, r2, r3, r4, r5, r6, r7, r8, r9) RESULT(out) REAL, TARGET, INTENT(IN) :: r0 REAL, OPTIONAL, TARGET, INTENT(IN) :: r1, r2, r3, r4, r5, r6, r7, r8, r9 REAL, ALLOCATABLE :: out(:) !------------------------------------------------------------------------------------------------------------------------------ REAL, POINTER :: r LOGICAL :: lv(10) INTEGER :: iv lv = [ .TRUE. , PRESENT(r1), PRESENT(r2), PRESENT(r3), PRESENT(r4) , & PRESENT(r5), PRESENT(r6), PRESENT(r7), PRESENT(r8), PRESENT(r9) ] ALLOCATE(out(COUNT(lv))) DO iv=1, COUNT(lv) SELECT CASE(iv) CASE(1); r=> r0; CASE(2); r=> r1; CASE(3); r=> r2; CASE(4); r=> r3; CASE(5); r=> r4 CASE(6); r=> r5; CASE(7); r=> r6; CASE(8); r=> r7; CASE(9); r=> r8; CASE(10);r=> r9 END SELECT out(iv) = r END DO END FUNCTION horzcat_r1 !============================================================================================================================== FUNCTION horzcat_rm(r0, r1, r2, r3, r4, r5, r6, r7, r8, r9) RESULT(out) REAL, TARGET, DIMENSION(:), INTENT(IN) :: r0 REAL, OPTIONAL, TARGET, DIMENSION(:), INTENT(IN) :: r1, r2, r3, r4, r5, r6, r7, r8, r9 REAL, ALLOCATABLE :: out(:,:) !------------------------------------------------------------------------------------------------------------------------------ REAL, POINTER :: r(:) LOGICAL :: lv(10) INTEGER :: nrow, ncol, iv, n lv = [ .TRUE. , PRESENT(r1), PRESENT(r2), PRESENT(r3), PRESENT(r4) , & PRESENT(r5), PRESENT(r6), PRESENT(r7), PRESENT(r8), PRESENT(r9) ] nrow = SIZE(r0); ncol=COUNT(lv) ALLOCATE(out(nrow, ncol)) DO iv=1, ncol SELECT CASE(iv) CASE(1); r=> r0; CASE(2); r=> r1; CASE(3); r=> r2; CASE(4); r=> r3; CASE(5); r=> r4 CASE(6); r=> r5; CASE(7); r=> r6; CASE(8); r=> r7; CASE(9); r=> r8; CASE(10);r=> r9 END SELECT n = SIZE(r, DIM=1) IF(n/=nrow) THEN; CALL msg("Can't concatenate vectors of differing lengths"); STOP; END IF out(:,iv) = r(:) END DO END FUNCTION horzcat_rm !============================================================================================================================== FUNCTION horzcat_d1(d0, d1, d2, d3, d4, d5, d6, d7, d8, d9) RESULT(out) DOUBLE PRECISION, TARGET, INTENT(IN) :: d0 DOUBLE PRECISION, OPTIONAL, TARGET, INTENT(IN) :: d1, d2, d3, d4, d5, d6, d7, d8, d9 DOUBLE PRECISION, ALLOCATABLE :: out(:) !------------------------------------------------------------------------------------------------------------------------------ DOUBLE PRECISION, POINTER :: d LOGICAL :: lv(10) INTEGER :: iv lv = [ .TRUE. , PRESENT(d1), PRESENT(d2), PRESENT(d3), PRESENT(d4) , & PRESENT(d5), PRESENT(d6), PRESENT(d7), PRESENT(d8), PRESENT(d9) ] ALLOCATE(out(COUNT(lv))) DO iv=1, COUNT(lv) SELECT CASE(iv) CASE(1); d=> d0; CASE(2); d=> d1; CASE(3); d=> d2; CASE(4); d=> d3; CASE(5); d=> d4 CASE(6); d=> d5; CASE(7); d=> d6; CASE(8); d=> d7; CASE(9); d=> d8; CASE(10);d=> d9 END SELECT out(iv) = d END DO END FUNCTION horzcat_d1 !============================================================================================================================== FUNCTION horzcat_dm(d0, d1, d2, d3, d4, d5, d6, d7, d8, d9) RESULT(out) DOUBLE PRECISION, TARGET, DIMENSION(:), INTENT(IN) :: d0 DOUBLE PRECISION, OPTIONAL, TARGET, DIMENSION(:), INTENT(IN) :: d1, d2, d3, d4, d5, d6, d7, d8, d9 DOUBLE PRECISION, ALLOCATABLE :: out(:,:) !------------------------------------------------------------------------------------------------------------------------------ DOUBLE PRECISION, POINTER :: d(:) LOGICAL :: lv(10) INTEGER :: nrow, ncol, iv, n lv = [ .TRUE. , PRESENT(d1), PRESENT(d2), PRESENT(d3), PRESENT(d4) , & PRESENT(d5), PRESENT(d6), PRESENT(d7), PRESENT(d8), PRESENT(d9) ] nrow = SIZE(d0); ncol=COUNT(lv) ALLOCATE(out(nrow, ncol)) DO iv=1, ncol SELECT CASE(iv) CASE(1); d=> d0; CASE(2); d=> d1; CASE(3); d=> d2; CASE(4); d=> d3; CASE(5); d=> d4 CASE(6); d=> d5; CASE(7); d=> d6; CASE(8); d=> d7; CASE(9); d=> d8; CASE(10);d=> d9 END SELECT n = SIZE(d, DIM=1) IF(n/=nrow) THEN; CALL msg("Can't concatenate vectors of differing lengths"); STOP; END IF out(:,iv) = d(:) END DO END FUNCTION horzcat_dm !============================================================================================================================== !============================================================================================================================== !--- Display a clean table composed of successive vectors of same length. !=== The profile "p" describe in which order to pick up the columns from "s", "i" and "r" for display. !=== * nRowMax lines are displayed (default: all lines) !=== * nColMax characters (default: as long as needed) are displayed at most on a line. If the effective total length is !=== higher, several partial tables are displayed ; the nHead (default: 1) first columns are included in each sub-table. !============================================================================================================================== LOGICAL FUNCTION dispTable(p, titles, s, i, r, rFmt, nRowMax, nColMax, nHead, unit, sub) RESULT(lerr) CHARACTER(LEN=*), INTENT(IN) :: p !--- DISPLAY MAP: s/i/r CHARACTER(LEN=*), INTENT(IN) :: titles(:) !--- TITLES (ONE EACH COLUMN) CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: s(:,:) !--- STRINGS INTEGER, OPTIONAL, INTENT(IN) :: i(:,:) !--- INTEGERS REAL, OPTIONAL, INTENT(IN) :: r(:,:) !--- REALS CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: rFmt !--- Format for reals INTEGER, OPTIONAL, INTENT(IN) :: nRowMax !--- Display at most "nRowMax" rows INTEGER, OPTIONAL, INTENT(IN) :: nColMax !--- Display at most "nColMax" characters each line INTEGER, OPTIONAL, INTENT(IN) :: nHead !--- Head columns repeated for multiple tables display INTEGER, OPTIONAL, INTENT(IN) :: unit !--- Output unit (default: screen) CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: sub !--- Subroutine name !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=2048) :: row CHARACTER(LEN=maxlen) :: rFm, el, subn CHARACTER(LEN=maxlen), ALLOCATABLE :: d(:,:) CHARACTER(LEN=1) :: s1, sp INTEGER :: is, ii, ir, it, k, nmx, unt, ic, np INTEGER :: ns, ni, nr, nt, l, ncol, nHd, ib, l0 INTEGER, ALLOCATABLE :: n(:), ncmx(:) INTEGER, PARAMETER :: nm=1 !--- Space between values & columns LOGICAL :: ls, li, lr subn = ''; IF(PRESENT(sub)) subn = sub rFm = '*'; IF(PRESENT(rFmt)) rFm = rFmt !--- Specified format for reals unt = lunout; IF(PRESENT(unit)) unt = unit !--- Specified output unit np = LEN_TRIM(p); ns = 0; ni = 0; nr = 0; ncol = 0 ls = PRESENT(s); li = PRESENT(i); lr = PRESENT(r) lerr = .FALSE.; IF(.NOT.ANY([ls,li,lr])) RETURN !--- Nothing to do sp = '|' !--- Separator !--- CHECK ARGUMENTS COHERENCE lerr = np /= SIZE(titles); IF(fmsg('display map "p" length and titles list mismatch', subn, lerr)) RETURN IF(ls) THEN ns = SIZE(s, 1); ncol = ncol + SIZE(s, 2); lerr = COUNT([(p(ic:ic)=='s', ic=1, np)]) /= SIZE(s, 2) END IF IF(li) THEN ni = SIZE(i, 1); ncol = ncol + SIZE(i, 2); lerr = COUNT([(p(ic:ic)=='i', ic=1, np)]) /= SIZE(i, 2) END IF IF(lr) THEN nr = SIZE(r, 1); ncol = ncol + SIZE(r, 2); lerr = COUNT([(p(ic:ic)=='r', ic=1, np)]) /= SIZE(r, 2) END IF IF(fmsg('display map "p" length and arguments number mismatch', subn, lerr)) RETURN lerr = ncol /= SIZE(titles); IF(fmsg('"titles" length and arguments number mismatch', subn, lerr)) RETURN lerr = ls.AND.li.AND.ns/=ni; IF(fmsg('string and integer arguments lengths mismatch', subn, lerr)) RETURN lerr = ls.AND.lr.AND.ns/=nr; IF(fmsg( 'string and real arguments lengths mismatch', subn, lerr)) RETURN lerr = li.AND.lr.AND.ni/=nr; IF(fmsg( 'integer and real arguments lengths mismatch', subn, lerr)) RETURN nmx = MAX(ns,ni,nr)+1; IF(PRESENT(nRowMax)) nmx = MIN(nmx,nRowMax+1) !--- Allocate the assembled quantities array ALLOCATE(d(nmx,ncol), n(ncol)) !--- Assemble the vectors into a strings array in the order indicated by "pattern" is = 1; ii = 1; ir = 1 DO ic = 1, ncol d(1,ic) = TRIM(titles(ic)) SELECT CASE(p(ic:ic)) CASE('s'); d(2:nmx,ic) = s(:,is) ; is = is + 1 CASE('i'); d(2:nmx,ic) = int2str(i(:,ii) ); ii = ii + 1 CASE('r'); d(2:nmx,ic) = real2str(r(:,ir),rFm); ir = ir + 1 END SELECT END DO CALL cleanZeros(d) DO ic = 1, ncol n(ic)=0; DO ir=1, nmx; n(ic)=MAX(n(ic), LEN_TRIM(d(ir,ic))); END DO END DO n(:) = n(:) + 2*nm !--- Build the vector of max column index in case the rows are too long (table must be displayed in multiple parts) nHd = 1; IF(PRESENT(nHead)) nHd = nHead IF(.NOT.PRESENT(nColMax)) THEN nt = 1; ncmx = [ncol] ELSE nt = 1; l0 = SUM(n(1:nHd)+1)+1 IF(PRESENT(sub)) l0=l0+LEN_TRIM(subn)+1 !--- Count the number of table parts l = l0; DO ic = nHd+1, ncol; l = l+n(ic)+1; IF(l>=nColMax) THEN; nt = nt+1; l = l0+n(ic)+1; END IF; END DO !--- Get the index of the last column for each table part ALLOCATE(ncmx(nt)); k = 1 l = l0; DO ic = nHd+1, ncol; l = l+n(ic)+1; IF(l>=nColMax) THEN; ncmx(k) = ic-1; l = l0+n(ic)+1; k = k+1; END IF; END DO ncmx(nt) = ncol END IF !--- Display the strings array as a table DO it = 1, nt DO ir = 1, nmx; row = '' DO ic = 1, nHd; el = d(ir,ic) s1 = sp row = TRIM(row)//REPEAT(' ',nm)//TRIM(el)//REPEAT(' ',n(ic)-LEN_TRIM(el)-nm)//s1 END DO ib = nHd+1; IF(it>1) ib = ncmx(it-1)+1 DO ic = ib, ncmx(it); el = d(ir,ic) s1 = sp row = TRIM(row)//REPEAT(' ',nm)//TRIM(el)//REPEAT(' ',n(ic)-LEN_TRIM(el)-nm)//s1 END DO nr = LEN_TRIM(row)-1 !--- Final separator removed CALL msg(row(1:nr), subn, unit=unt) IF(ir /= 1) CYCLE !--- Titles only are underlined row=''; DO ic=1,nHd; row=TRIM(row)//REPEAT('-',n(ic))//'+'; END DO DO ic = ib,ncmx(it); row=TRIM(row)//REPEAT('-',n(ic))//'+'; END DO CALL msg(row(1:LEN_TRIM(row)-1), subn, unit=unt) END DO CALL msg('', subn, unit=unt) END DO END FUNCTION dispTable !============================================================================================================================== !============================================================================================================================== LOGICAL FUNCTION dispNamelist(unt, p, titles, s, i, r, rFmt, llast) RESULT(lerr) INTEGER, INTENT(IN) :: unt !--- Output unit CHARACTER(LEN=*), INTENT(IN) :: p !--- DISPLAY MAP: s/i/r CHARACTER(LEN=*), INTENT(IN) :: titles(:) !--- TITLES (ONE EACH COLUMN) CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: s(:,:) !--- STRINGS INTEGER, OPTIONAL, INTENT(IN) :: i(:,:) !--- INTEGERS REAL, OPTIONAL, INTENT(IN) :: r(:,:) !--- REALS CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: rFmt !--- Format for reals LOGICAL, OPTIONAL, INTENT(IN) :: llast !--- Last variable: no final ',' !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen) :: rFm, el CHARACTER(LEN=maxlen), ALLOCATABLE :: d(:,:) CHARACTER(LEN=:), ALLOCATABLE :: sp, row INTEGER :: is, ii, ir, nrow, ic INTEGER :: ns, ni, nr, ncol, np INTEGER, ALLOCATABLE :: n(:) LOGICAL :: ls, li, lr, la rFm = '*'; IF(PRESENT(rFmt)) rFm = rFmt !--- Specified format for reals ls = PRESENT(s); li = PRESENT(i); lr = PRESENT(r) lerr = .FALSE.; IF(.NOT.ANY([ls,li,lr])) RETURN !--- Nothing to do la = .FALSE.; IF(PRESENT(llast)) la = llast !--- CHECK ARGUMENTS COHERENCE ns = 0; ni = 0; nr = 0; np = LEN_TRIM(p); ncol = 0 IF(ls) THEN; ns = SIZE(s, DIM=1); ncol = ncol + SIZE(s, DIM=2) lerr = COUNT([(p(ic:ic)=='s', ic=1, np)]) /= SIZE(s, DIM=2) END IF IF(li) THEN; ni = SIZE(i, DIM=1); ncol = ncol + SIZE(i, DIM=2) lerr = COUNT([(p(ic:ic)=='i', ic=1, np)]) /= SIZE(i, DIM=2) END IF IF(lr) THEN; nr = SIZE(r, DIM=1); ncol = ncol + SIZE(r, DIM=2) lerr = COUNT([(p(ic:ic)=='r', ic=1, np)]) /= SIZE(r, DIM=2) END IF IF(fmsg('display map "p" length and arguments number mismatch', ll=lerr)) RETURN lerr = ncol /= SIZE(titles); IF(fmsg('"titles" length and arguments number mismatch', ll=lerr)) RETURN lerr = ls.AND.li.AND.ns/=ni; IF(fmsg('string and integer arguments lengths mismatch', ll=lerr)) RETURN lerr = ls.AND.lr.AND.ns/=nr; IF(fmsg( 'string and real arguments lengths mismatch', ll=lerr)) RETURN lerr = li.AND.lr.AND.ni/=nr; IF(fmsg( 'integer and real arguments lengths mismatch', ll=lerr)) RETURN !--- Allocate the assembled quantities array nrow = MAX(ns,ni,nr)+1 ALLOCATE(d(nrow,ncol), n(ncol)) !--- Assemble the vectors into a strings array in the order indicated by "pattern" is = 1; ii = 1; ir = 1 DO ic = 1, ncol d(1,ic) = TRIM(titles(ic)) SELECT CASE(p(ic:ic)) CASE('s'); d(2:nrow,ic) = s(:,is) ; is = is + 1 CASE('i'); d(2:nrow,ic) = int2str(i(:,ii) ); ii = ii + 1 CASE('r'); d(2:nrow,ic) = real2str(r(:,ir),rFm); ir = ir + 1 END SELECT END DO CALL cleanZeros(d) DO ic = 1, ncol n(ic) = 0; DO ir=1, nrow; n(ic)=MAX(n(ic), LEN_TRIM(d(ir,ic))); END DO IF(needQuotes(d(2,ic)) .AND. ic/=1) n(ic) = n(ic) + 2 !--- For quotes, using second line only END DO !--- Display the strings array as a table DO ir = 1, nrow row = ''; sp = ' '; IF(TRIM(d(ir,1)) /= '') sp = ' = ' DO ic = 1, ncol el = d(ir,ic); IF(ic /= 1) el = addQuotes_1(el) row = row//TRIM(el)//REPEAT(' ',n(ic)-LEN_TRIM(el))//sp sp = ' '; IF(ic /= ncol-1) CYCLE IF(TRIM(d(MIN(ir+1,nrow),1)) /= '' .AND. (ir /= nrow .OR. .NOT.la)) sp = ' , ' END DO WRITE(unt,'(a)')TRIM(row) END DO !--- End of section IF(la) THEN WRITE(unt,'(a)')'/' WRITE(unt,'(a)') END IF END FUNCTION dispNameList !============================================================================================================================== !============================================================================================================================== LOGICAL FUNCTION dispOutliers_1(ll, a, n, err_msg, nam, subn, nRowmax, nColMax, nHead, unit) RESULT(lerr) ! Display outliers list in tables ! If "nam" is supplied, it means the last index is for tracers => one table each tracer for rank > 2. LOGICAL, INTENT(IN) :: ll(:) !--- Linearized mask of outliers REAL, INTENT(IN) :: a(:) !--- Linearized array of values INTEGER, INTENT(IN) :: n(:) !--- Profile before linearization CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: err_msg, nam(:), subn !--- Error message, variables and calling subroutine names INTEGER, OPTIONAL, INTENT(IN) :: nRowMax !--- Maximum number of lines to display (default: all) INTEGER, OPTIONAL, INTENT(IN) :: nColMax !--- Maximum number of characters per line (default: 2048) INTEGER, OPTIONAL, INTENT(IN) :: nHead !--- Number of front columns to duplicate (default: 1) INTEGER, OPTIONAL, INTENT(IN) :: unit !--- Output unit (def: lunout) !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen), ALLOCATABLE :: ttl(:) LOGICAL, ALLOCATABLE :: m(:) INTEGER, ALLOCATABLE :: ki(:), kj(:) INTEGER :: i, j, k, rk, rk1, ib, ie, itr, nm, unt, nRmx, nCmx, nHd, nv CHARACTER(LEN=maxlen) :: mes, sub, fm='(f12.9)', v, s CHARACTER(LEN=maxlen), ALLOCATABLE :: vnm(:) lerr = ANY(ll); IF(.NOT.lerr) RETURN !--- No outliers -> finished mes = 'outliers found'; IF(PRESENT(err_msg)) mes = err_msg !--- Error message vnm = ['a']; IF(PRESENT(nam )) vnm = nam !--- Variables names sub = 'dispOutliers'; IF(PRESENT(subn)) sub = subn !--- Calling subroutine name nRmx= SIZE(a); IF(PRESENT(nRowMax)) nRmx=MIN(nRmx,nRowMax)!-- Maximum number of lines to print nCmx= 2048; IF(PRESENT(nColMax)) nCmx=MIN(nCmx,nColMax)!-- Maximum number of characters each line nHd = 1; IF(PRESENT(nHead)) nHd = nHead !--- Number of front columns to duplicate unt = lunout; IF(PRESENT(unit)) unt = unit !--- Unit to print messages rk = SIZE(n); nv = SIZE(vnm) IF(test(fmsg('SIZE(nam) /= 1 and /= last "n" element', sub, nv /= 1 .AND. nv /= n(rk), unt),lerr)) RETURN IF(test(fmsg('ll" and "a" sizes mismatch', sub, SIZE(a) /= SIZE(ll), unt),lerr)) RETURN IF(test(fmsg('profile "n" does not match "a" and "ll', sub, SIZE(a) /= PRODUCT(n), unt),lerr)) RETURN CALL msg(mes, sub, unit=unt) !--- SCALAR CASE: single value to display IF(rk==1.AND.n(1)==1) THEN IF(ll(1)) WRITE(unt,'(a," = ",f12.9)')TRIM(nam(1)),a(1); RETURN END IF rk1 = rk; IF(nv==1) rk1 = rk-1 !--- Rank of each displayed table SELECT CASE(rk1) !--- Indices list CASE(1,2); ki = [ (i,i=1,n(1)) ] CASE(3); ki = [((i,i=1,n(1)),j=1,n(2))]; kj = [((j,i=1,n(1)),j=1,n(2))] CASE DEFAULT; WRITE(unt,*)'Sorry: routine "dispOutliers" is limited to rank 3'; RETURN END SELECT !--- VECTOR CASE: table " name | value " (known names) / ) / " i | a(i) " (unknown names) IF(rk==1) THEN ALLOCATE(ttl(2)); ttl(2) = TRIM(vnm(1))//'(i)'; ttl(1) = 'i' IF(nv == 1) lerr = dispTable('sr', ttl, s=cat(PACK(nam,ll)), r=cat(PACK(a,ll)), & rFmt=fm, nRowMax=nRmx, nColMax=nCmx, nHead=nHd, unit=unt, sub=sub) IF(nv /= 1) lerr = dispTable('ir', ['name ','value'], i=cat(PACK(ki,m)), r=cat(PACK(a,ll)), & rFmt=fm, nRowMax=nRmx, nColMax=nCmx, nHead=nHd, unit=unt, sub=sub) CALL msg("can't display outliers table", sub, lerr, unt) RETURN END IF !--- OTHER CASES: one table for each tracer (last index) ttl = [(ACHAR(k), k = 105, 104+rk)] !--- Titles list ('i', 'j', 'k'...) s = strStack( ttl(1:rk-1) ) !--- Tracer name dummy indexes: (i, j, k, ... DO itr=1,n(rk) nm = PRODUCT(n(1:rk-1)) !--- number of elements per tracer ie = itr*nm; ib = ie-nm+1; m=ll(ib:ie) !--- section bounds for tracer "itr" ; outlayers mask IF(.NOT.ANY(m)) CYCLE !--- no outlayers for tracer "itr" v = TRIM(vnm(MIN(itr,SIZE(vnm))))//'('//TRIM(s) !--- "(" IF(nv == 1) ttl(rk) = TRIM(v)//','//int2str(itr)//')' !--- "(i,j,itr)" (single name) IF(nv /= 1) ttl(rk) = TRIM(v)//')' !--- "(i,j)" (one name each table/itr index) IF(rk==2) lerr = dispTable('ir', ttl, i=cat(PACK(ki,m)), r=cat(PACK(a(ib:ie),m)), & rFmt=fm, nRowMax=nRmx, nColMax=nCmx, nHead=nHd, unit=unt, sub=sub) IF(rk==3) lerr = dispTable('iir', ttl, i=cat(PACK(ki,m),PACK(kj,m)), r=cat(PACK(a(ib:ie),m)), & rFmt=fm, nRowMax=nRmx, nColMax=nCmx, nHead=nHd, unit=unt, sub=sub) CALL msg("can't display outliers table", sub, lerr, unt) IF(lerr) RETURN END DO END FUNCTION dispOutliers_1 !============================================================================================================================== LOGICAL FUNCTION dispOutliers_2(ll, a, n, err_msg, nam, subn, nRowMax, nColMax, nHead, unit) RESULT(lerr) ! Display outliers list in tables ! If "nam" is supplied and, it means the last index is for tracers => one table each tracer for rank > 2. LOGICAL, INTENT(IN) :: ll(:) !--- Linearized mask of outliers REAL, INTENT(IN) :: a(:,:) !--- Linearized arrays of values stacked along 2nd dim. INTEGER, INTENT(IN) :: n(:) !--- Profile before linearization CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: err_msg, nam(:), subn !--- Error message, variables and calling subroutine names INTEGER, OPTIONAL, INTENT(IN) :: nRowMax !--- Maximum number of lines to display (default: all) INTEGER, OPTIONAL, INTENT(IN) :: nColMax !--- Maximum number of characters per line (default: 2048) INTEGER, OPTIONAL, INTENT(IN) :: nHead !--- Number of front columns to duplicate (default: 1) INTEGER, OPTIONAL, INTENT(IN) :: unit !--- Output unit (def: lunout) !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen) :: mes, sub, fm='(f12.9)', prf CHARACTER(LEN=maxlen), ALLOCATABLE :: ttl(:), vnm(:) INTEGER, ALLOCATABLE :: ki(:), kj(:), kl(:) INTEGER :: i, j, k, rk, nv, unt, nRmx, nCmx, nHd REAL, ALLOCATABLE :: val(:,:) lerr = ANY(ll); IF(.NOT.lerr) RETURN !--- No outliers -> finished rk = SIZE(n); nv = SIZE(a,2) mes = 'outliers found'; IF(PRESENT(err_msg)) mes = err_msg !--- Error message vnm = [(ACHAR(k+96),k=1,nv)]; IF(PRESENT(nam )) vnm = nam !--- Variables names sub = 'dispOutliers'; IF(PRESENT(subn)) sub = subn !--- Calling subroutine name nRmx= SIZE(a); IF(PRESENT(nRowMax)) nRmx=MIN(nRmx,nRowMax)!-- Maximum number of lines to print nCmx= 2048; IF(PRESENT(nColMax)) nCmx=MIN(nCmx,nColMax)!-- Maximum number of characters each line nHd = 1; IF(PRESENT(nHead)) nHd = nHead !--- Number of front columns to duplicate unt = lunout; IF(PRESENT(unit)) unt = unit !--- Unit to print messages lerr= SIZE(vnm) /= nv; IF(fmsg('SIZE(nam) /= SIZE(a,2)', sub, lerr, unt)) RETURN lerr= SIZE(a,1) /= SIZE(ll); IF(fmsg('"ll" and "a" sizes mismatch', sub, lerr, unt)) RETURN lerr= SIZE(a,1) /= PRODUCT(n); IF(fmsg('profile "n" does not match "a" and "ll"', sub, lerr, unt)) RETURN SELECT CASE(rk) !--- Indices list CASE(0); IF(ll(1)) THEN; WRITE(unt,'(a,", ",a," = ",2f12.9)')TRIM(vnm(1)),TRIM(vnm(2)),a(1,1),a(1,2); RETURN; END IF CASE(1); ki = [ (i,i=1,n(1)) ] CASE(2); ki = [ ((i,i=1,n(1)),j=1,n(2))]; kj = [ ((j,i=1,n(1)),j=1,n(2))] CASE(3); ki = [(((i,i=1,n(1)),j=1,n(2)),k=1,n(3))]; kj = [(((j,i=1,n(1)),j=1,n(2)),k=1,n(3))] kl = [(((k,i=1,n(1)),j=1,n(2)),k=1,n(3))] CASE DEFAULT; WRITE(unt,*)'Sorry: routine "dispOutliers_2" is limited to rank 3'; RETURN END SELECT ttl = [(ACHAR(k), k = 105, 104+rk), vnm] !--- Titles list ('i', 'j', 'k'...'var1', 'var2', ...) prf = REPEAT('i',rk)//REPEAT('r',nv) !--- Profile ALLOCATE(val(COUNT(ll),nv)); DO k=1, nv; val(:,k) = PACK(a(:,k),ll); END DO IF(rk == 1) lerr = dispTable(prf, ttl, i = cat(PACK(ki,ll)), r = val, & rFmt=fm, nRowMax=nRmx, nColMax=nCmx, nHead=nHd, unit=unt, sub=sub) IF(rk == 2) lerr = dispTable(prf, ttl, i = cat(PACK(ki,ll),PACK(kj,ll)), r = val, & rFmt=fm, nRowMax=nRmx, nColMax=nCmx, nHead=nHd, unit=unt, sub=sub) IF(rk == 3) lerr = dispTable(prf, ttl, i = cat(PACK(ki,ll),PACK(kj,ll),PACK(kl,ll)), r = val, & rFmt=fm, nRowMax=nRmx, nColMax=nCmx, nHead=nHd, unit=unt, sub=sub) CALL msg("can't display outliers table", sub, lerr, unt) END FUNCTION dispOutliers_2 !============================================================================================================================== !============================================================================================================================== !=== Reduce an algebrical expression (basic operations and parenthesis) to a single number (string format) ==================== !============================================================================================================================== LOGICAL FUNCTION reduceExpr_1(str, val) RESULT(lerr) CHARACTER(LEN=*), INTENT(IN) :: str CHARACTER(LEN=maxlen), INTENT(OUT) :: val !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen) :: v CHARACTER(LEN=1024) :: s, vv CHARACTER(LEN=1024), ALLOCATABLE :: vl(:) INTEGER, ALLOCATABLE :: ip(:) INTEGER :: nl, nn, i, j, im, ix LOGICAL :: ll s = str !--- Check wether the parenthesis are correctly formed ll = strCount(s,'(',nl) ll = strCount(s,')',nn) lerr = nl /= nn IF(fmsg('Mismatching number of opening and closing parenthesis: '//TRIM(s), ll=lerr)) RETURN nl = 2*nl-1 !--- Build vectors ; vl: parenthesis-separated elements ; ip: parenthesis types (1: opening, 2: closing) ALLOCATE(ip(nl-1),vl(nl)) j = 1; im = 1 DO i = 1, LEN_TRIM(str) ix = INDEX('()', str(i:i)) IF(ix == 0) CYCLE ip(j) = ix vl(j) = str(im:i-1) j = j + 1; im = i + 1 END DO vl(j) = str(im:LEN_TRIM(str)) !--- Search for each opening/closing parenthesis pair DO WHILE(nl > 1) i = 1; DO WHILE(ip(i) /= 1 .OR. ip(i+1) /= 2); i = i + 1; END DO !IF(i > SIZE(ip)+1) EXIT;END DO IF(test(reduceExpr_basic(vl(i+1), v), lerr)) RETURN v = TRIM(vl(i))//TRIM(v); IF(i+2<=nl) v=TRIM(v)//TRIM(vl(i+2)) vv = v//REPEAT(' ',768) IF(i == 1) THEN; ip = ip(3:nl-1); vl = [ vv, vl(4 :nl)] ELSE IF(i == nl-1) THEN; ip = ip(1:nl-2); vl = [vl(1:nl-3), vv ] ELSE; ip = [ip(1: i-1), ip(i+2:nl-1)]; vl = [vl(1: i-1), vv, vl(i+3:nl)]; END IF nl = SIZE(vl) END DO lerr = reduceExpr_basic(vl(1), val) END FUNCTION reduceExpr_1 !============================================================================================================================== !=== Reduce a simple algebrical expression (basic operations, no parenthesis) to a single number (string format) ============== !============================================================================================================================== LOGICAL FUNCTION reduceExpr_basic(str, val) RESULT(lerr) CHARACTER(LEN=*), INTENT(IN) :: str CHARACTER(LEN=*), INTENT(OUT) :: val DOUBLE PRECISION, ALLOCATABLE :: vl(:) INTEGER, ALLOCATABLE :: id(:) CHARACTER(LEN=maxlen), ALLOCATABLE :: ky(:) CHARACTER(LEN=1), ALLOCATABLE :: op(:) !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=1024) :: s DOUBLE PRECISION :: v, vm, vp INTEGER :: i, ni, io lerr = .FALSE. IF(is_numeric(str)) THEN; val=TRIM(str); RETURN; END IF op = ['^','/','*','+','-'] !--- List of recognized operations s = str IF(test(strParse_m(s, op, ky, lSc=.TRUE., id = id), lerr)) RETURN !--- Parse the values vl = str2dble(ky) !--- Conversion to doubles lerr = ANY(vl >= HUGE(1.d0)) IF(fmsg('Some values are non-numeric in: '//TRIM(s), ll=lerr)) RETURN !--- Non-numerical values found DO io = 1, SIZE(op) !--- Loop on known operators (order matters !) DO i = SIZE(id), 1, -1 !--- Loop on found operators ni = SIZE(id) IF(id(i) /= io) CYCLE !--- Current found operator is not op(io) vm = vl(i); vp = vl(i+1) !--- Couple of values used for current operation SELECT CASE(op(io)) !--- Perform operation on the two values CASE('^'); v = vm**vp CASE('/'); v = vm/vp CASE('*'); v = vm*vp CASE('+'); v = vm+vp CASE('-'); v = vm-vp END SELECT IF(i == ni) THEN; vl = [vl(1:ni-1), v]; ELSE; vl = [vl(1:i-1), v, vl(i+2:ni+1)]; END IF IF(i == ni) THEN; id = id(1:ni-1); ELSE; id = [id(1:i-1), id(i+1:ni )]; END IF END DO END DO val = dble2str(vl(1)) END FUNCTION reduceExpr_basic !============================================================================================================================== !============================================================================================================================== FUNCTION reduceExpr_m(str, val) RESULT(lerr) LOGICAL, ALLOCATABLE :: lerr(:) CHARACTER(LEN=*), INTENT(IN) :: str(:) CHARACTER(LEN=maxlen), ALLOCATABLE, INTENT(OUT) :: val(:) !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: i ALLOCATE(lerr(SIZE(str)),val(SIZE(str))) lerr(:) = [(reduceExpr_1(str(i), val(i)), i=1, SIZE(str))] END FUNCTION reduceExpr_m !============================================================================================================================== !============================================================================================================================== !=== Check whether a string is a number or not ================================================================================ !============================================================================================================================== ELEMENTAL LOGICAL FUNCTION is_numeric(str) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str REAL :: x INTEGER :: e CHARACTER(LEN=12) :: fmt IF(TRIM(str) == '') THEN; out = .FALSE.; RETURN; END IF WRITE(fmt,'("(f",i0,".0)")') LEN_TRIM(str) READ(str,fmt,IOSTAT=e) x out = e==0 .AND. INDEX('Ee',str(LEN_TRIM(str):LEN_TRIM(str)))==0 END FUNCTION is_numeric !============================================================================================================================== !============================================================================================================================== !=== Convert a string into a logical/integer integer or an integer/real into a string ========================================= !============================================================================================================================== ELEMENTAL LOGICAL FUNCTION str2bool(str) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str INTEGER :: ierr READ(str,*,IOSTAT=ierr) out IF(ierr==0) RETURN out = ANY(['t ','true ','.true.','y ','yes ']==strLower(str)) END FUNCTION str2bool !============================================================================================================================== ELEMENTAL INTEGER FUNCTION str2int(str) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str INTEGER :: ierr READ(str,*,IOSTAT=ierr) out IF(ierr/=0) out = -HUGE(1) END FUNCTION str2int !============================================================================================================================== ELEMENTAL REAL FUNCTION str2real(str) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str INTEGER :: ierr READ(str,*,IOSTAT=ierr) out IF(ierr/=0) out = -HUGE(1.) END FUNCTION str2real !============================================================================================================================== ELEMENTAL DOUBLE PRECISION FUNCTION str2dble(str) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: str INTEGER :: ierr READ(str,*,IOSTAT=ierr) out IF(ierr/=0) out = -HUGE(1.d0) END FUNCTION str2dble !============================================================================================================================== ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION bool2str(b) RESULT(out) LOGICAL, INTENT(IN) :: b WRITE(out,*)b out = ADJUSTL(out) END FUNCTION bool2str !============================================================================================================================== ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION int2str(i, nDigits) RESULT(out) INTEGER, INTENT(IN) :: i INTEGER, OPTIONAL, INTENT(IN) :: nDigits !------------------------------------------------------------------------------------------------------------------------------ WRITE(out,*)i out = ADJUSTL(out) IF(.NOT.PRESENT(nDigits)) RETURN IF(nDigits > LEN_TRIM(out)) out = REPEAT('0', nDigits - LEN_TRIM(out))//TRIM(out) END FUNCTION int2str !============================================================================================================================== ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION real2str(r,fmt) RESULT(out) REAL, INTENT(IN) :: r CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: fmt !------------------------------------------------------------------------------------------------------------------------------ IF( PRESENT(fmt)) WRITE(out,fmt)r IF(.NOT.PRESENT(fmt)) WRITE(out, * )r out = ADJUSTL(out) END FUNCTION real2str !============================================================================================================================== ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION dble2str(d,fmt) RESULT(out) DOUBLE PRECISION, INTENT(IN) :: d CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: fmt !------------------------------------------------------------------------------------------------------------------------------ IF( PRESENT(fmt)) WRITE(out,fmt)d IF(.NOT.PRESENT(fmt)) WRITE(out, * )d out = ADJUSTL(out) END FUNCTION dble2str !============================================================================================================================== ELEMENTAL SUBROUTINE cleanZeros(s) CHARACTER(LEN=*), INTENT(INOUT) :: s INTEGER :: ls, ix, i IF(is_numeric(s)) THEN ls = LEN_TRIM(s) ix = MAX(INDEX(s,'E'),INDEX(s,'e'),INDEX(s,'D'),INDEX(s,'d')) IF(ix == 0) THEN DO ix = ls,1,-1; IF(s(ix:ix) /= '0') EXIT; END DO; s=s(1:ix+1) ELSE IF(INDEX(s,'.')/=0) THEN i = ix-1; DO WHILE(s(i:i) == '0'); i = i-1; END DO; s=s(1:i)//s(ix:ls) END IF END IF END SUBROUTINE cleanZeros !============================================================================================================================== !============================================================================================================================== FUNCTION addQuotes_1(s) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: s CHARACTER(LEN=:), ALLOCATABLE :: out IF(needQuotes(s)) THEN; out = "'"//TRIM(s)//"'"; ELSE; out = s; END IF END FUNCTION addQuotes_1 !============================================================================================================================== FUNCTION addQuotes_m(s) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: s(:) CHARACTER(LEN=:), ALLOCATABLE :: out(:) !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: k, n n = MAXVAL(LEN_TRIM(s), MASK=.TRUE.) ALLOCATE(CHARACTER(LEN=n) :: out(SIZE(s))) DO k=1,SIZE(s) IF(needQuotes(s(k))) THEN; out(k) = "'"//TRIM(s(k))//"'"; ELSE; out(k) = s(k); END IF END DO END FUNCTION addQuotes_m !============================================================================================================================== ELEMENTAL LOGICAL FUNCTION needQuotes(s) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: s CHARACTER(LEN=1) :: b, e !------------------------------------------------------------------------------------------------------------------------------ out = .TRUE.; IF(TRIM(s) == '') RETURN b = s(1:1); e = s(MAX(1,LEN_TRIM(s)):MAX(1,LEN_TRIM(s))) out = .NOT.is_numeric(s) .AND. (b /= "'" .OR. e /= "'") .AND. ( b /= '"' .OR. e /= '"') END FUNCTION needQuotes !============================================================================================================================== !============================================================================================================================== !=== TEST WHETHER A FILE IS PRESENT OR NOT ==================================================================================== !============================================================================================================================== LOGICAL FUNCTION testFile_1(fname) RESULT(out) CHARACTER(LEN=*), INTENT(IN) :: fname !------------------------------------------------------------------------------------------------------------------------------ INTEGER :: ierr OPEN(90, FILE=fname, FORM='formatted', STATUS='old', IOSTAT=ierr); CLOSE(99) out = ierr/=0 END FUNCTION testFile_1 !============================================================================================================================== FUNCTION testFile_m(fname) RESULT(out) LOGICAL, ALLOCATABLE :: out(:) CHARACTER(LEN=*), INTENT(IN) :: fname(:) INTEGER :: k !------------------------------------------------------------------------------------------------------------------------------ out = [(testFile_1(fname(k)), k=1, SIZE(fname))] END FUNCTION testFile_m !============================================================================================================================== !============================================================================================================================== !=== DISPLAY ": the following are " FOLLOWED BY THE LIST OF FOR WHICH ==T. =============== !============================================================================================================================== LOGICAL FUNCTION checkList(str, lerr, message, items, reason, nmax) RESULT(out) ! Purpose: Messages in case a list contains wrong elements (indicated by lerr boolean vector). ! Note: Return value "out" is .TRUE. if there are errors (ie at least one element of "lerr" is TRUE). CHARACTER(LEN=*), INTENT(IN) :: str(:) LOGICAL, INTENT(IN) :: lerr(:) CHARACTER(LEN=*), INTENT(IN) :: message, items, reason INTEGER, OPTIONAL, INTENT(IN) :: nmax !------------------------------------------------------------------------------------------------------------------------------ CHARACTER(LEN=maxlen), ALLOCATABLE :: s(:) INTEGER :: i, nmx nmx = 256; IF(PRESENT(nmax)) nmx=nmax out = ANY(lerr); IF(.NOT.out) RETURN CALL msg(TRIM(message)//': the following '//TRIM(items)//' are '//TRIM(reason)//':') s = strStackm(PACK(str, MASK=lerr), ', ',nmx) DO i=1,SIZE(s,DIM=1); CALL msg(s(i)); END DO END FUNCTION checkList !============================================================================================================================== !============================================================================================================================== !=== Remove comment in line "str", ie all the characters from the first "#" sign found in "str". ============================== !============================================================================================================================== SUBROUTINE removeComment(str) CHARACTER(LEN=*), INTENT(INOUT) :: str INTEGER :: ix ix = INDEX(str,'# '); IF(ix /= 0) str = str(1:ix-1)//REPEAT(' ',LEN(str)-ix+1) END SUBROUTINE removeComment !============================================================================================================================== END MODULE strings_mod