Ignore:
Timestamp:
Jul 24, 2024, 4:23:34 PM (2 months ago)
Author:
abarral
Message:

rename modules properly lmdz_*
move some unused files to obsolete/
(lint) uppercase fortran keywords

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/misc/lmdz_strings.f90

    r5116 r5117  
    1 MODULE strings_mod
     1MODULE lmdz_strings
    22  IMPLICIT NONE; PRIVATE
    33  PUBLIC :: maxlen, init_printout, msg, fmsg, get_in, lunout, prt_level
     
    163163!=== Lower/upper case conversion function. ====================================================================================
    164164!==============================================================================================================================
    165 ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION strLower(str) RESULT(out)
     165ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION strLower(str) RESULT(OUT)
    166166    CHARACTER(LEN=*), INTENT(IN) :: str
    167167  INTEGER :: k
     
    172172END FUNCTION strLower
    173173!==============================================================================================================================
    174 ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION strUpper(str) RESULT(out)
     174ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION strUpper(str) RESULT(OUT)
    175175    CHARACTER(LEN=*), INTENT(IN) :: str
    176176  INTEGER :: k
     
    189189!===    * strHead(..,.TRUE.)  = 'a_b'         ${str%$sep*}                                                     ================
    190190!==============================================================================================================================
    191 CHARACTER(LEN=maxlen) FUNCTION strHead_1(str, sep, lBackward) RESULT(out)
     191CHARACTER(LEN=maxlen) FUNCTION strHead_1(str, sep, lBackward) RESULT(OUT)
    192192    CHARACTER(LEN=*),           INTENT(IN) :: str
    193193  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: sep
     
    204204END FUNCTION strHead_1
    205205!==============================================================================================================================
    206 FUNCTION strHead_m(str, sep, lBackward) RESULT(out)
     206FUNCTION strHead_m(str, sep, lBackward) RESULT(OUT)
    207207    CHARACTER(LEN=maxlen),     ALLOCATABLE :: out(:)
    208208  CHARACTER(LEN=*),           INTENT(IN) :: str(:)
     
    225225!===    * strTail(str, '_', .TRUE.)  = 'c'           ${str##*$sep}                                             ================
    226226!==============================================================================================================================
    227 CHARACTER(LEN=maxlen) FUNCTION strTail_1(str, sep, lBackWard) RESULT(out)
     227CHARACTER(LEN=maxlen) FUNCTION strTail_1(str, sep, lBackWard) RESULT(OUT)
    228228    CHARACTER(LEN=*),           INTENT(IN) :: str
    229229  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: sep
     
    240240END FUNCTION strTail_1
    241241!==============================================================================================================================
    242 FUNCTION strTail_m(str, sep, lBackWard) RESULT(out)
     242FUNCTION strTail_m(str, sep, lBackWard) RESULT(OUT)
    243243    CHARACTER(LEN=maxlen),     ALLOCATABLE :: out(:)
    244244  CHARACTER(LEN=*),           INTENT(IN) :: str(:)
     
    261261!=== Concatenates the strings "str(:)" with separator "sep" into a single string using a separator (',' by default). ==========
    262262!==============================================================================================================================
    263 FUNCTION strStack(str, sep, mask) RESULT(out)
     263FUNCTION strStack(str, sep, mask) RESULT(OUT)
    264264    CHARACTER(LEN=:),          ALLOCATABLE :: out
    265265  CHARACTER(LEN=*),           INTENT(IN) :: str(:)
     
    274274    IF(ALL(.NOT.mask)) THEN; out = ''; RETURN; END IF
    275275    i0 = 0; DO WHILE(.NOT.mask(i0+1)); i0 = i0+1; END DO
    276     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
     276    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
    277277  ELSE
    278     out = str(1); DO is=2,SIZE(str, DIM=1); out = TRIM(out)//s//TRIM(str(is)); END DO
     278    out = str(1); DO is=2,SIZE(str, DIM=1); out = TRIM(OUT)//s//TRIM(str(is)); END DO
    279279  END IF
    280280END FUNCTION strStack
     
    282282!=== Concatenate the strings "str(:)" with separator "sep" into one or several lines of "nmax" characters max (for display) ===
    283283!==============================================================================================================================
    284 FUNCTION strStackm(str, sep, nmax) RESULT(out)
     284FUNCTION strStackm(str, sep, nmax) RESULT(OUT)
    285285    CHARACTER(LEN=maxlen),     ALLOCATABLE :: out(:)
    286286  CHARACTER(LEN=*),           INTENT(IN) :: str(:)
     
    382382!=== OPTIONALY: GET THE NUMBER OF FOUND ELEMENTS "n". NB: UNFOUND => INDEX=0                       ============================
    383383!==============================================================================================================================
    384 INTEGER FUNCTION strIdx_1(str, s) RESULT(out)
     384INTEGER FUNCTION strIdx_1(str, s) RESULT(OUT)
    385385    CHARACTER(LEN=*), INTENT(IN) :: str(:), s
    386   DO out = 1, SIZE(str); IF(str(out) == s) EXIT; END DO
     386  DO out = 1, SIZE(str); IF(str(OUT) == s) EXIT; END DO
    387387  IF(out == 1+SIZE(str) .OR. SIZE(str)==0) out = 0
    388388END FUNCTION strIdx_1
    389389!==============================================================================================================================
    390 FUNCTION strIdx_m(str, s, n) RESULT(out)
     390FUNCTION strIdx_m(str, s, n) RESULT(OUT)
    391391    CHARACTER(LEN=*),  INTENT(IN)  :: str(:), s(:)
    392392  INTEGER, OPTIONAL, INTENT(OUT) :: n
     
    403403!=== GET THE INDEX LIST OF THE ELEMENTS OF "str(:)" EQUAL TO "s" AND OPTIONALY, ITS LENGTH "n" ================================
    404404!==============================================================================================================================
    405 FUNCTION strFind_1(str, s, n) RESULT(out)
     405FUNCTION strFind_1(str, s, n) RESULT(OUT)
    406406    CHARACTER(LEN=*),  INTENT(IN)  :: str(:), s
    407407  INTEGER, OPTIONAL, INTENT(OUT) :: n
     
    413413END FUNCTION strFind_1
    414414!==============================================================================================================================
    415 FUNCTION strFind_m(str, s, n) RESULT(out)
     415FUNCTION strFind_m(str, s, n) RESULT(OUT)
    416416    CHARACTER(LEN=*),  INTENT(IN)  :: str(:), s(:)
    417417  INTEGER, OPTIONAL, INTENT(OUT) :: n
     
    423423END FUNCTION strFind_m
    424424!==============================================================================================================================
    425 FUNCTION intFind_1(i,j,n) RESULT(out)
     425FUNCTION intFind_1(i,j,n) RESULT(OUT)
    426426    INTEGER,           INTENT(IN)  :: i(:), j
    427427  INTEGER, OPTIONAL, INTENT(OUT) :: n
     
    433433END FUNCTION intFind_1
    434434!==============================================================================================================================
    435 FUNCTION intFind_m(i,j,n) RESULT(out)
     435FUNCTION intFind_m(i,j,n) RESULT(OUT)
    436436    INTEGER,           INTENT(IN)  :: i(:), j(:)
    437437  INTEGER, OPTIONAL, INTENT(OUT) :: n
     
    443443END FUNCTION intFind_m
    444444!==============================================================================================================================
    445 FUNCTION booFind(l,n) RESULT(out)
     445FUNCTION booFind(l,n) RESULT(OUT)
    446446    LOGICAL,           INTENT(IN)  :: l(:)
    447447  INTEGER, OPTIONAL, INTENT(OUT) :: n
     
    738738!=== Contatenate horizontally scalars/vectors of strings/integers/reals into a vector/array ===================================
    739739!==============================================================================================================================
    740 FUNCTION horzcat_s00(s0, s1, s2, s3, s4, s5, s6, s7, s8, s9) RESULT(out)
     740FUNCTION horzcat_s00(s0, s1, s2, s3, s4, s5, s6, s7, s8, s9) RESULT(OUT)
    741741    CHARACTER(LEN=*),                   INTENT(IN) :: s0
    742742  CHARACTER(LEN=*), OPTIONAL, TARGET, INTENT(IN) :: s1, s2, s3, s4, s5, s6, s7, s8, s9
     
    759759END FUNCTION horzcat_s00
    760760!==============================================================================================================================
    761 FUNCTION horzcat_s10(s0, s1, s2, s3, s4, s5, s6, s7, s8, s9) RESULT(out)
     761FUNCTION horzcat_s10(s0, s1, s2, s3, s4, s5, s6, s7, s8, s9) RESULT(OUT)
    762762    CHARACTER(LEN=*),           INTENT(IN) :: s0(:), s1
    763763  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: s2, s3, s4, s5, s6, s7, s8, s9
     
    770770END FUNCTION horzcat_s10
    771771!==============================================================================================================================
    772 FUNCTION horzcat_s11(s0, s1, s2, s3, s4, s5, s6, s7, s8, s9) RESULT(out)
     772FUNCTION horzcat_s11(s0, s1, s2, s3, s4, s5, s6, s7, s8, s9) RESULT(OUT)
    773773    CHARACTER(LEN=*),                   INTENT(IN) :: s0(:)
    774774  CHARACTER(LEN=*), OPTIONAL, TARGET, INTENT(IN) :: s1(:), s2(:), s3(:), s4(:), s5(:), s6(:), s7(:), s8(:), s9(:)
     
    794794END FUNCTION horzcat_s11
    795795!==============================================================================================================================
    796 FUNCTION horzcat_s21(s0, s1, s2, s3, s4, s5, s6, s7, s8, s9) RESULT(out)
     796FUNCTION horzcat_s21(s0, s1, s2, s3, s4, s5, s6, s7, s8, s9) RESULT(OUT)
    797797    CHARACTER(LEN=*),           INTENT(IN) :: s0(:,:), s1(:)
    798798  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: s2(:), s3(:), s4(:), s5(:), s6(:), s7(:), s8(:), s9(:)
     
    805805END FUNCTION horzcat_s21
    806806!==============================================================================================================================
    807 FUNCTION horzcat_i00(i0, i1, i2, i3, i4, i5, i6, i7, i8, i9) RESULT(out)
     807FUNCTION horzcat_i00(i0, i1, i2, i3, i4, i5, i6, i7, i8, i9) RESULT(OUT)
    808808    INTEGER,                   INTENT(IN) :: i0
    809809  INTEGER, OPTIONAL, TARGET, INTENT(IN) :: i1, i2, i3, i4, i5, i6, i7, i8, i9
     
    826826END FUNCTION horzcat_i00
    827827!==============================================================================================================================
    828 FUNCTION horzcat_i10(i0, i1, i2, i3, i4, i5, i6, i7, i8, i9) RESULT(out)
     828FUNCTION horzcat_i10(i0, i1, i2, i3, i4, i5, i6, i7, i8, i9) RESULT(OUT)
    829829    INTEGER,           INTENT(IN) :: i0(:), i1
    830830  INTEGER, OPTIONAL, INTENT(IN) :: i2, i3, i4, i5, i6, i7, i8, i9
     
    837837END FUNCTION horzcat_i10
    838838!==============================================================================================================================
    839 FUNCTION horzcat_i11(i0, i1, i2, i3, i4, i5, i6, i7, i8, i9) RESULT(out)
     839FUNCTION horzcat_i11(i0, i1, i2, i3, i4, i5, i6, i7, i8, i9) RESULT(OUT)
    840840    INTEGER,                   INTENT(IN) :: i0(:)
    841841  INTEGER, OPTIONAL, TARGET, INTENT(IN) :: i1(:), i2(:), i3(:), i4(:), i5(:), i6(:), i7(:), i8(:), i9(:)
     
    861861END FUNCTION horzcat_i11
    862862!==============================================================================================================================
    863 FUNCTION horzcat_i21(i0, i1, i2, i3, i4, i5, i6, i7, i8, i9) RESULT(out)
     863FUNCTION horzcat_i21(i0, i1, i2, i3, i4, i5, i6, i7, i8, i9) RESULT(OUT)
    864864    INTEGER,           INTENT(IN) :: i0(:,:), i1(:)
    865865  INTEGER, OPTIONAL, INTENT(IN) :: i2(:), i3(:), i4(:), i5(:), i6(:), i7(:), i8(:), i9(:)
     
    872872END FUNCTION horzcat_i21
    873873!==============================================================================================================================
    874 FUNCTION horzcat_r00(r0, r1, r2, r3, r4, r5, r6, r7, r8, r9) RESULT(out)
     874FUNCTION horzcat_r00(r0, r1, r2, r3, r4, r5, r6, r7, r8, r9) RESULT(OUT)
    875875    REAL,                   INTENT(IN) :: r0
    876876  REAL, OPTIONAL, TARGET, INTENT(IN) :: r1, r2, r3, r4, r5, r6, r7, r8, r9
     
    893893END FUNCTION horzcat_r00
    894894!==============================================================================================================================
    895 FUNCTION horzcat_r10(r0, r1, r2, r3, r4, r5, r6, r7, r8, r9) RESULT(out)
     895FUNCTION horzcat_r10(r0, r1, r2, r3, r4, r5, r6, r7, r8, r9) RESULT(OUT)
    896896    REAL,           INTENT(IN) :: r0(:), r1
    897897  REAL, OPTIONAL, INTENT(IN) :: r2, r3, r4, r5, r6, r7, r8, r9
     
    904904END FUNCTION horzcat_r10
    905905!==============================================================================================================================
    906 FUNCTION horzcat_r11(r0, r1, r2, r3, r4, r5, r6, r7, r8, r9) RESULT(out)
     906FUNCTION horzcat_r11(r0, r1, r2, r3, r4, r5, r6, r7, r8, r9) RESULT(OUT)
    907907    REAL,                   INTENT(IN) :: r0(:)
    908908  REAL, OPTIONAL, TARGET, INTENT(IN) :: r1(:), r2(:), r3(:), r4(:), r5(:), r6(:), r7(:), r8(:), r9(:)
     
    928928END FUNCTION horzcat_r11
    929929!==============================================================================================================================
    930 FUNCTION horzcat_r21(r0, r1, r2, r3, r4, r5, r6, r7, r8, r9) RESULT(out)
     930FUNCTION horzcat_r21(r0, r1, r2, r3, r4, r5, r6, r7, r8, r9) RESULT(OUT)
    931931    REAL,           INTENT(IN) :: r0(:,:), r1(:)
    932932  REAL, OPTIONAL, INTENT(IN) :: r2(:), r3(:), r4(:), r5(:), r6(:), r7(:), r8(:), r9(:)
     
    939939END FUNCTION horzcat_r21
    940940!==============================================================================================================================
    941 FUNCTION horzcat_d00(d0, d1, d2, d3, d4, d5, d6, d7, d8, d9) RESULT(out)
     941FUNCTION horzcat_d00(d0, d1, d2, d3, d4, d5, d6, d7, d8, d9) RESULT(OUT)
    942942    DOUBLE PRECISION,                   INTENT(IN) :: d0
    943943  DOUBLE PRECISION, OPTIONAL, TARGET, INTENT(IN) :: d1, d2, d3, d4, d5, d6, d7, d8, d9
     
    960960END FUNCTION horzcat_d00
    961961!==============================================================================================================================
    962 FUNCTION horzcat_d10(d0, d1, d2, d3, d4, d5, d6, d7, d8, d9) RESULT(out)
     962FUNCTION horzcat_d10(d0, d1, d2, d3, d4, d5, d6, d7, d8, d9) RESULT(OUT)
    963963    DOUBLE PRECISION,           INTENT(IN) :: d0(:), d1
    964964  DOUBLE PRECISION, OPTIONAL, INTENT(IN) :: d2, d3, d4, d5, d6, d7, d8, d9
     
    971971END FUNCTION horzcat_d10
    972972!==============================================================================================================================
    973 FUNCTION horzcat_d11(d0, d1, d2, d3, d4, d5, d6, d7, d8, d9) RESULT(out)
     973FUNCTION horzcat_d11(d0, d1, d2, d3, d4, d5, d6, d7, d8, d9) RESULT(OUT)
    974974    DOUBLE PRECISION,                   INTENT(IN) :: d0(:)
    975975  DOUBLE PRECISION, OPTIONAL, TARGET, INTENT(IN) :: d1(:), d2(:), d3(:), d4(:), d5(:), d6(:), d7(:), d8(:), d9(:)
     
    994994END FUNCTION horzcat_d11
    995995!==============================================================================================================================
    996 FUNCTION horzcat_d21(d0, d1, d2, d3, d4, d5, d6, d7, d8, d9) RESULT(out)
     996FUNCTION horzcat_d21(d0, d1, d2, d3, d4, d5, d6, d7, d8, d9) RESULT(OUT)
    997997    DOUBLE PRECISION,           INTENT(IN) :: d0(:,:), d1(:)
    998998  DOUBLE PRECISION, OPTIONAL, INTENT(IN) :: d2(:), d3(:), d4(:), d5(:), d6(:), d7(:), d8(:), d9(:)
     
    10411041  np = LEN_TRIM(p); ns = 0; ni = 0; nr = 0; ncol = 0
    10421042  ls = PRESENT(s); li = PRESENT(i); lr = PRESENT(r)
    1043   lerr = .FALSE.; IF(.NOT.ANY([ls,li,lr])) RETURN          !--- Nothing to do
     1043  lerr = .FALSE.; IF(.NOT.ANY([ls,li,lr])) RETURN          !--- Nothing to DO
    10441044  sp = '|'                                                 !--- Separator
    10451045
     
    11411141  rFm = '*';    IF(PRESENT(rFmt)) rFm = rFmt               !--- Specified format for reals
    11421142  ls = PRESENT(s); li = PRESENT(i); lr = PRESENT(r)
    1143   lerr = .FALSE.; IF(.NOT.ANY([ls,li,lr])) RETURN          !--- Nothing to do
     1143  lerr = .FALSE.; IF(.NOT.ANY([ls,li,lr])) RETURN          !--- Nothing to DO
    11441144  la = .FALSE.; IF(PRESENT(llast)) la = llast
    11451145
     
    14461446!=== Check whether a string is a number or not ================================================================================
    14471447!==============================================================================================================================
    1448 ELEMENTAL LOGICAL FUNCTION is_numeric(str) RESULT(out)
     1448ELEMENTAL LOGICAL FUNCTION is_numeric(str) RESULT(OUT)
    14491449    CHARACTER(LEN=*), INTENT(IN) :: str
    14501450  REAL    :: x
     
    14621462!=== Convert a string into a logical/integer integer or an integer/real into a string =========================================
    14631463!==============================================================================================================================
    1464 ELEMENTAL INTEGER FUNCTION str2bool(str) RESULT(out)  !--- Result: 0/1 for .FALSE./.TRUE., -1 if not a valid boolean
     1464ELEMENTAL INTEGER FUNCTION str2bool(str) RESULT(OUT)  !--- Result: 0/1 for .FALSE./.TRUE., -1 if not a valid boolean
    14651465    CHARACTER(LEN=*), INTENT(IN) :: str
    14661466  INTEGER :: ierr
     
    14761476END FUNCTION str2bool
    14771477!==============================================================================================================================
    1478 ELEMENTAL INTEGER FUNCTION str2int(str) RESULT(out)
     1478ELEMENTAL INTEGER FUNCTION str2int(str) RESULT(OUT)
    14791479    CHARACTER(LEN=*), INTENT(IN) :: str
    14801480  INTEGER :: ierr
     
    14831483END FUNCTION str2int
    14841484!==============================================================================================================================
    1485 ELEMENTAL REAL FUNCTION str2real(str) RESULT(out)
     1485ELEMENTAL REAL FUNCTION str2real(str) RESULT(OUT)
    14861486    CHARACTER(LEN=*), INTENT(IN) :: str
    14871487  INTEGER :: ierr
     
    14901490END FUNCTION str2real
    14911491!==============================================================================================================================
    1492 ELEMENTAL DOUBLE PRECISION FUNCTION str2dble(str) RESULT(out)
     1492ELEMENTAL DOUBLE PRECISION FUNCTION str2dble(str) RESULT(OUT)
    14931493    CHARACTER(LEN=*), INTENT(IN) :: str
    14941494  INTEGER :: ierr
     
    14971497END FUNCTION str2dble
    14981498!==============================================================================================================================
    1499 ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION bool2str(b) RESULT(out)
     1499ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION bool2str(b) RESULT(OUT)
    15001500    LOGICAL, INTENT(IN) :: b
    15011501  WRITE(out,*)b
    1502   out = ADJUSTL(out)
     1502  out = ADJUSTL(OUT)
    15031503END FUNCTION bool2str
    15041504!==============================================================================================================================
    1505 ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION int2str(i, nDigits) RESULT(out)
     1505ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION int2str(i, nDigits) RESULT(OUT)
    15061506    INTEGER,           INTENT(IN) :: i
    15071507  INTEGER, OPTIONAL, INTENT(IN) :: nDigits
    15081508!------------------------------------------------------------------------------------------------------------------------------
    15091509  WRITE(out,*)i
    1510   out = ADJUSTL(out)
     1510  out = ADJUSTL(OUT)
    15111511  IF(.NOT.PRESENT(nDigits)) RETURN
    1512   IF(nDigits > LEN_TRIM(out)) out = REPEAT('0', nDigits - LEN_TRIM(out))//TRIM(out)
     1512  IF(nDigits > LEN_TRIM(out)) out = REPEAT('0', nDigits - LEN_TRIM(out))//TRIM(OUT)
    15131513END FUNCTION int2str
    15141514!==============================================================================================================================
    1515 ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION real2str(r,fmt) RESULT(out)
     1515ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION real2str(r,fmt) RESULT(OUT)
    15161516    REAL,                       INTENT(IN) :: r
    15171517  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: fmt
     
    15191519  IF(     PRESENT(fmt)) WRITE(out,fmt)r
    15201520  IF(.NOT.PRESENT(fmt)) WRITE(out, * )r
    1521   out = ADJUSTL(out)
     1521  out = ADJUSTL(OUT)
    15221522END FUNCTION real2str
    15231523!==============================================================================================================================
    1524 ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION dble2str(d,fmt) RESULT(out)
     1524ELEMENTAL CHARACTER(LEN=maxlen) FUNCTION dble2str(d,fmt) RESULT(OUT)
    15251525    DOUBLE PRECISION,           INTENT(IN) :: d
    15261526  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: fmt
     
    15281528  IF(     PRESENT(fmt)) WRITE(out,fmt)d
    15291529  IF(.NOT.PRESENT(fmt)) WRITE(out, * )d
    1530   out = ADJUSTL(out)
     1530  out = ADJUSTL(OUT)
    15311531END FUNCTION dble2str
    15321532!==============================================================================================================================
     
    15481548
    15491549!==============================================================================================================================
    1550 FUNCTION addQuotes_1(s) RESULT(out)
     1550FUNCTION addQuotes_1(s) RESULT(OUT)
    15511551    CHARACTER(LEN=*), INTENT(IN)  :: s
    15521552  CHARACTER(LEN=:), ALLOCATABLE :: out
     
    15541554END FUNCTION addQuotes_1
    15551555!==============================================================================================================================
    1556 FUNCTION addQuotes_m(s) RESULT(out)
     1556FUNCTION addQuotes_m(s) RESULT(OUT)
    15571557    CHARACTER(LEN=*), INTENT(IN)  :: s(:)
    15581558  CHARACTER(LEN=:), ALLOCATABLE :: out(:)
     
    15661566END FUNCTION addQuotes_m
    15671567!==============================================================================================================================
    1568 ELEMENTAL LOGICAL FUNCTION needQuotes(s) RESULT(out)
     1568ELEMENTAL LOGICAL FUNCTION needQuotes(s) RESULT(OUT)
    15691569    CHARACTER(LEN=*), INTENT(IN) :: s
    15701570  CHARACTER(LEN=1) :: b, e
     
    15801580!=== DISPLAY "<message>: the following <items> are <reason>" FOLLOWED BY THE LIST OF <str> FOR WHICH <lerr>==T. ===============
    15811581!==============================================================================================================================
    1582 LOGICAL FUNCTION checkList(str, lerr, message, items, reason, nmax) RESULT(out)
     1582LOGICAL FUNCTION checkList(str, lerr, message, items, reason, nmax) RESULT(OUT)
    15831583  ! Purpose: Messages in case a list contains wrong elements (indicated by lerr boolean vector).
    15841584! Note:    Return value "out" is .TRUE. if there are errors (ie at least one element of "lerr" is TRUE).
     
    16101610
    16111611
    1612 END MODULE strings_mod
     1612END MODULE lmdz_strings
Note: See TracChangeset for help on using the changeset viewer.