Changeset 4454


Ignore:
Timestamp:
Mar 7, 2023, 4:17:13 PM (16 months ago)
Author:
dcugnet
Message:

Fix for the strange language dependent bug (workaround was "unset LANG"): replace testFile routines with INQUIRE intrinsic function.

Location:
LMDZ6/trunk/libf/misc
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/misc/readTracFiles_mod.f90

    r4403 r4454  
    11MODULE readTracFiles_mod
    22
    3   USE strings_mod,    ONLY: msg, find, get_in, str2int, dispTable, testFile, strReduce,  strFind, strStack, strHead, &
    4        test, removeComment, cat, fmsg, maxlen, int2str, checkList, strParse, strReplace, strTail, strCount, strIdx, reduceExpr
     3  USE strings_mod,    ONLY: msg, find, get_in, str2int, dispTable, strHead,  strReduce,  strFind, strStack, strIdx, &
     4       test, removeComment, cat, fmsg, maxlen, int2str, checkList, strParse, strReplace, strTail, strCount, reduceExpr
    55
    66  IMPLICIT NONE
     
    292292  CHARACTER(LEN=maxlen), ALLOCATABLE :: trac_files(:), sections(:)
    293293  LOGICAL, ALLOCATABLE :: ll(:)
    294   LOGICAL :: lD
     294  LOGICAL :: lD, lFound
    295295  INTEGER :: is, nsec
    296296  lD = .FALSE.; IF(PRESENT(lDisp)) lD = lDisp
     
    301301  IF(test(strParse(type_trac, '|', sections,  n=nsec), lerr)) RETURN !--- Parse "type_trac" list
    302302  IF(PRESENT(sects)) sects = sections
    303   ALLOCATE(trac_files(nsec)); DO is=1, nsec; trac_files(is) = 'tracer_'//TRIM(sections(is))//'.def'; END DO
     303  ALLOCATE(trac_files(nsec), ll(nsec))
     304  DO is=1, nsec
     305     trac_files(is) = 'tracer_'//TRIM(sections(is))//'.def'
     306     INQUIRE(FILE=TRIM(trac_files(is)), EXIST=ll(is))
     307  END DO
    304308  IF(PRESENT(tracf)) tracf = trac_files
    305   ll = .NOT.testFile(trac_files)
    306309  fType = 0
    307   IF(.NOT.testFile('traceur.def')) fType = 1                         !--- OLD STYLE FILE
    308   IF(.NOT.testFile('tracer.def'))  fType = 2                         !--- NEW STYLE ; SINGLE  FILE, SEVERAL SECTIONS
    309   IF(ALL(ll))                      fType = 3                         !--- NEW STYLE ; SEVERAL FILES, SINGLE SECTION USED
     310  INQUIRE(FILE='traceur.def', EXIST=lFound); IF(lFound)  fType = 1   !--- OLD STYLE FILE
     311  INQUIRE(FILE='tracer.def',  EXIST=lFound); IF(lFound)  fType = 2   !--- NEW STYLE ; SINGLE  FILE, SEVERAL SECTIONS
     312                                             IF(ALL(ll)) fType = 3   !--- NEW STYLE ; SEVERAL FILES, SINGLE SECTION USED
    310313  IF(.NOT.lD) RETURN                                                 !--- NO CHECKING/DISPLAY NEEDED: JUST GET type_trac,fType
    311314  IF(ANY(ll) .AND. fType/=3) THEN                                    !--- MISSING FILES
     
    10321035  CHARACTER(LEN=*),        INTENT(IN)    :: fnam                     !--- Input file name
    10331036  TYPE(isot_type), TARGET, INTENT(INOUT) :: isot(:)                  !--- Isotopes descriptors (field %parent must be defined!)
     1037  LOGICAL :: lFound
    10341038  INTEGER :: is, iis, it, idb, ndb, nb0
    10351039  CHARACTER(LEN=maxlen), ALLOCATABLE :: vals(:)
     
    10401044
    10411045  !--- THE INPUT FILE MUST BE PRESENT
    1042   IF(test(fmsg('Missing isotopes parameters file "'//TRIM(fnam)//'"', modname, testFile(fnam)),lerr)) RETURN
     1046  INQUIRE(FILE=TRIM(fnam), EXIST=lFound); lerr = .NOT.lFound
     1047  IF(fmsg('Missing isotopes parameters file "'//TRIM(fnam)//'"', modname, lerr)) RETURN
    10431048
    10441049  !--- READ THE FILE SECTIONS, ONE EACH PARENT TRACER
  • LMDZ6/trunk/libf/misc/strings_mod.F90

    r4403 r4454  
    1010  PUBLIC :: is_numeric, bool2str, int2str, real2str, dble2str
    1111  PUBLIC :: reduceExpr, str2bool, str2int, str2real, str2dble
    12   PUBLIC :: addQuotes, testFile, checkList, removeComment, test
     12  PUBLIC :: addQuotes, checkList, removeComment, test
    1313
    1414  INTERFACE get_in;     MODULE PROCEDURE getin_s,  getin_i,  getin_r,  getin_l;  END INTERFACE get_in
     
    2929  INTERFACE reduceExpr;   MODULE PROCEDURE   reduceExpr_1,   reduceExpr_m; END INTERFACE reduceExpr
    3030  INTERFACE addQuotes;    MODULE PROCEDURE    addQuotes_1,    addQuotes_m; END INTERFACE addQuotes
    31   INTERFACE testFile;     MODULE PROCEDURE     testFile_1,     testFile_m; END INTERFACE testFile
    3231
    3332  INTEGER, PARAMETER :: maxlen    = 256                    !--- Standard maximum length for strings
     
    14521451
    14531452!==============================================================================================================================
    1454 !=== TEST WHETHER A FILE IS PRESENT OR NOT ====================================================================================
    1455 !==============================================================================================================================
    1456 LOGICAL FUNCTION testFile_1(fname) RESULT(out)
    1457   CHARACTER(LEN=*), INTENT(IN) :: fname
    1458 !------------------------------------------------------------------------------------------------------------------------------
    1459   INTEGER :: ierr
    1460   OPEN(90, FILE=fname, FORM='formatted', STATUS='old', IOSTAT=ierr); CLOSE(99)
    1461   out = ierr/=0
    1462 END FUNCTION testFile_1
    1463 !==============================================================================================================================
    1464 FUNCTION testFile_m(fname) RESULT(out)
    1465   LOGICAL,         ALLOCATABLE ::   out(:)
    1466   CHARACTER(LEN=*), INTENT(IN) :: fname(:)
    1467   INTEGER :: k
    1468 !------------------------------------------------------------------------------------------------------------------------------
    1469   out = [(testFile_1(fname(k)), k=1, SIZE(fname))]
    1470 END FUNCTION testFile_m
    1471 !==============================================================================================================================
    1472 
    1473 
    1474 !==============================================================================================================================
    14751453!=== DISPLAY "<message>: the following <items> are <reason>" FOLLOWED BY THE LIST OF <str> FOR WHICH <lerr>==T. ===============
    14761454!==============================================================================================================================
Note: See TracChangeset for help on using the changeset viewer.