Ignore:
Timestamp:
Nov 7, 2022, 3:09:43 AM (20 months ago)
Author:
dcugnet
Message:
  • simplify the parser usage:
    • the getKey_init routine is now embedded in the readTracersFile routine.
    • the initIsotopes routine is now embedded in the readIsotopesFile routine.
    • the database is now unique, but can be changed using the get/setKeysDBase.
    • the derived types descriptions, originally located in trac_types_mod, are moved to readTracFiles_mod.
    • few checkings moved from infotrac to the routine testIsotopes, contained in the readIsotopesFile function from readTracFiles_mod.
    • the readTracersFiles and readIsotopesFile routines no longer use a tracers/isotopes argument.
  • remove tnat and alpha_ideal from infotrac ; use instead getKey to get them where they are used (check_isotopes, dynetat0, iniacademic)
  • the trac_type field %Childs is renamed %Children
  • move the isoSelect routine and the corresponding variables routine from infotrac and infotrac_phy to readTracFiles_mod
  • infotrac_phy routine is now fully independant of the (very similar) routine infotrac (init_infotrac_phy has no arguments left).
  • all the explicit keys of the trac_type are now included in the embedded keys database, accessible using the getKey function.
  • the getKey/addKey routines are expanded to handle vectors of integers, reals, logicals or strings.
  • few subroutines converted into functions with error return value.
  • corrections for isotopic tagging tracers mode (to be continued).
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmdiso/isotopes_mod.F90

    r4319 r4325  
    133133
    134134SUBROUTINE iso_init()
    135    USE ioipsl_getin_p_mod, ONLY: getin_p
    136135   USE infotrac_phy,       ONLY: ntiso, niso, getKey
    137136    USE strings_mod,       ONLY: maxlen
     
    181180   iso_HTO = strIdx(isoName, 'H[3]HO');  CALL msg('iso_HTO='//int2str(iso_HTO), modname)
    182181
    183    ! initialisation
    184    ! lecture des parametres isotopiques:
    185    ! pour que ca marche en openMP, il faut utiliser getin_p. Car le getin ne peut
    186    ! etre appele que par un thread a la fois, et ca pose tout un tas de problemes,
    187    ! d'ou tout un tas de magouilles comme dans conf_phys_m. A terme, tout le monde
    188    ! lira par getin_p.
     182   !--- Initialiaation: reading the isotopic parameters.
    189183   CALL get_in('lambda',     lambda_sursat, 0.004)
    190184   CALL get_in('thumxt1',    thumxt1,       0.75*1.2)
     
    339333   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
    340334   USE mod_phys_lmdz_transfert_para, ONLY : bcast
    341    CHARACTER(LEN=*),  INTENT(IN)    :: nam
    342    CHARACTER(LEN=*),  INTENT(INOUT) :: val
    343    CHARACTER(LEN=*), INTENT(IN)    :: def
    344    LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
     335   CHARACTER(LEN=*),           INTENT(IN)    :: nam
     336   CHARACTER(LEN=*),           INTENT(INOUT) :: val
     337   CHARACTER(LEN=*), OPTIONAL, INTENT(IN)    :: def
     338   LOGICAL,          OPTIONAL, INTENT(IN)    :: lDisp
    345339   LOGICAL :: lD
    346340!$OMP BARRIER
    347341   IF(is_mpi_root.AND.is_omp_root) THEN
    348       val=def; CALL getin(nam,val)
     342      IF(PRESENT(def)) val=def; CALL getin(nam,val)
    349343      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
    350344      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(val))
    351    END IF
    352    CALL bcast(val)
     345  END IF
     346  CALL bcast(val)
    353347END SUBROUTINE getinp_s
    354348
     
    360354   CHARACTER(LEN=*),  INTENT(IN)    :: nam
    361355   INTEGER,           INTENT(INOUT) :: val
    362    INTEGER,           INTENT(IN)    :: def
     356   INTEGER, OPTIONAL, INTENT(IN)    :: def
    363357   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
    364358   LOGICAL :: lD
    365359!$OMP BARRIER
    366360   IF(is_mpi_root.AND.is_omp_root) THEN
    367       val=def; CALL getin(nam,val)
     361      IF(PRESENT(def)) val=def; CALL getin(nam,val)
    368362      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
    369363      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(int2str(val)))
    370    END IF
    371    CALL bcast(val)
     364  END IF
     365  CALL bcast(val)
    372366END SUBROUTINE getinp_i
    373367
     
    379373   CHARACTER(LEN=*),  INTENT(IN)    :: nam
    380374   REAL,              INTENT(INOUT) :: val
    381    REAL,              INTENT(IN)    :: def
     375   REAL,    OPTIONAL, INTENT(IN)    :: def
    382376   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
    383377   LOGICAL :: lD
    384378!$OMP BARRIER
    385379   IF(is_mpi_root.AND.is_omp_root) THEN
    386       Val=def; CALL getin(nam,val)
     380      IF(PRESENT(def)) val=def; CALL getin(nam,val)
    387381      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
    388382      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(real2str(val)))
    389    ENDIF
    390    CALL bcast(val)
     383  END IF
     384  CALL bcast(val)
    391385END SUBROUTINE getinp_r
    392386
     
    398392   CHARACTER(LEN=*),  INTENT(IN)    :: nam
    399393   LOGICAL,           INTENT(INOUT) :: val
    400    LOGICAL,           INTENT(IN)    :: def
     394   LOGICAL, OPTIONAL, INTENT(IN)    :: def
    401395   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
    402396   LOGICAL :: lD
    403397!$OMP BARRIER
    404398   IF(is_mpi_root.AND.is_omp_root) THEN
    405       val=def; CALL getin(nam,val)
     399      IF(PRESENT(def)) val=def; CALL getin(nam,val)
    406400      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
    407401      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(bool2str(val)))
    408    END IF
    409    CALL bcast(val)
     402  END IF
     403  CALL bcast(val)
    410404END SUBROUTINE getinp_l
    411405
Note: See TracChangeset for help on using the changeset viewer.