Changeset 5754


Ignore:
Timestamp:
Jul 2, 2025, 4:26:06 PM (34 hours ago)
Author:
dcugnet
Message:

Make the ioipsl_getin_p routine more flexible: optional default value
and optional flag to print or not the effective value of the key
=> get rid of the get_in routine

Location:
LMDZ6/trunk/libf
Files:
5 edited

Legend:

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

    r5748 r5754  
    11MODULE readTracFiles_mod
    22
    3   USE strings_mod,    ONLY: msg, find, get_in, dispTable, strHead,  strReduce,  strFind, strStack, strIdx, &
     3  USE ioipsl_getin_p_mod, ONLY : getin_p
     4  USE strings_mod,    ONLY: msg, find, dispTable, strHead,  strReduce,  strFind, strStack, strIdx, &
    45             removeComment, cat,       maxlen, checkList, strParse, strReplace, strTail, strCount, reduceExpr, &
    56             num2str, str2int, str2real, str2bool
     
    11631164
    11641165  !--- GET THE isoCheck ENTRY FROM THE *.DEF FILES (MIGHT BE CHANGED TO A CLASS-DEPENDANT KEYWORD)
    1165   CALL get_in('ok_iso_verif', isot(strIdx(isot%parent, 'H2O'))%check, .FALSE.)
     1166  CALL getin_p('ok_iso_verif', isot(strIdx(isot%parent, 'H2O'))%check, .FALSE.)
    11661167
    11671168  lerr = dispIsotopes()
     
    13071308
    13081309  !--- GET THE isoCheck ENTRY FROM THE *.DEF FILES (MIGHT BE CHANGED TO A CLASS-DEPENDANT KEYWORD)
    1309   CALL get_in('ok_iso_verif', isoCheck, .TRUE.)
     1310  CALL getin_p('ok_iso_verif', isoCheck, .TRUE.)
    13101311
    13111312  !=== CHECK CONSISTENCY
  • LMDZ6/trunk/libf/misc/strings_mod.f90

    r5753 r5754  
    66
    77  PRIVATE
    8   PUBLIC :: maxlen, init_printout, msg, get_in, lunout, prt_level, maxTableWidth
     8  PUBLIC :: maxlen, init_printout, msg, lunout, prt_level, maxTableWidth
    99  PUBLIC :: strLower, strHead, strStack,  strCount, strReduce,  strClean, strIdx
    1010  PUBLIC :: strUpper, strTail, strStackm, strParse, strReplace, strFind, find, duplicate, cat
     
    1313  PUBLIC :: reduceExpr, addQuotes, checkList, removeComment
    1414
    15   INTERFACE get_in;     MODULE PROCEDURE getin_s,  getin_i,  getin_r,  getin_l;  END INTERFACE get_in
    1615  INTERFACE num2str;    MODULE PROCEDURE bool2str, int2str, real2str, dble2str;  END INTERFACE num2str
    1716  INTERFACE  msg;       MODULE PROCEDURE        msg_1,                    msg_m; END INTERFACE  msg
     
    5049  prt_level = prt_level_
    5150END SUBROUTINE init_printout
    52 !==============================================================================================================================
    53 
    54 
    55 !==============================================================================================================================
    56 !=== Same as getin ; additional last argument: the default value.
    57 !==============================================================================================================================
    58 SUBROUTINE getin_s(nam, val, def)
    59   USE ioipsl, ONLY: getin
    60   IMPLICIT NONE
    61   CHARACTER(LEN=*), INTENT(IN)    :: nam
    62   CHARACTER(LEN=*), INTENT(INOUT) :: val
    63   CHARACTER(LEN=*), INTENT(IN)    :: def
    64   val = def; CALL getin(nam, val)
    65   IF(val/=def) WRITE(lunout,*)TRIM(nam)//' = '//TRIM(val)
    66 END SUBROUTINE getin_s
    67 !==============================================================================================================================
    68 SUBROUTINE getin_i(nam, val, def)
    69   USE ioipsl, ONLY: getin
    70   IMPLICIT NONE
    71   CHARACTER(LEN=*), INTENT(IN)    :: nam
    72   INTEGER,          INTENT(INOUT) :: val
    73   INTEGER,          INTENT(IN)    :: def
    74   val = def; CALL getin(nam, val)
    75   IF(val/=def) WRITE(lunout,*)TRIM(nam)//' = '//TRIM(num2str(val))
    76 END SUBROUTINE getin_i
    77 !==============================================================================================================================
    78 SUBROUTINE getin_r(nam, val, def)
    79   USE ioipsl, ONLY: getin
    80   IMPLICIT NONE
    81   CHARACTER(LEN=*), INTENT(IN)    :: nam
    82   REAL,             INTENT(INOUT) :: val
    83   REAL,             INTENT(IN)    :: def
    84   val = def; CALL getin(nam, val)
    85   IF(val/=def) WRITE(lunout,*)TRIM(nam)//' = '//TRIM(num2str(val))
    86 END SUBROUTINE getin_r
    87 !==============================================================================================================================
    88 SUBROUTINE getin_l(nam, val, def)
    89   USE ioipsl, ONLY: getin
    90   IMPLICIT NONE
    91   CHARACTER(LEN=*), INTENT(IN)    :: nam
    92   LOGICAL,          INTENT(INOUT) :: val
    93   LOGICAL,          INTENT(IN)    :: def
    94   val = def; CALL getin(nam, val)
    95   IF(val.NEQV.def) WRITE(lunout,*)TRIM(nam)//' = '//TRIM(num2str(val))
    96 END SUBROUTINE getin_l
    9751!==============================================================================================================================
    9852
  • LMDZ6/trunk/libf/phy_common/ioipsl_getin_p_mod.f90

    r5268 r5754  
    66!---------------------------------------------------------------------
    77USE ioipsl, ONLY: getin
    8 USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    9 USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
     8USE strings_mod, ONLY: num2str, strStack, msg
     9USE mod_phys_lmdz_para, ONLY: is_master
    1010USE mod_phys_lmdz_transfert_para, ONLY : bcast
    1111!-
     
    3232!! -- Les chaines de caracteres -- !!
    3333 
    34   SUBROUTINE getincs_p(VarIn,VarOut)
    35     IMPLICIT NONE   
    36     CHARACTER(LEN=*),INTENT(IN) :: VarIn
    37     CHARACTER(LEN=*),INTENT(INOUT) :: VarOut   
    38 
    39 !$OMP BARRIER
    40     IF (is_mpi_root .AND. is_omp_root) THEN
    41         CALL getin(VarIn,VarOut)
    42     ENDIF
    43     CALL bcast(VarOut)
    44   END SUBROUTINE getincs_p
     34SUBROUTINE getincs_p(VarIn, VarOut, VarDef, lDisp)
     35  IMPLICIT NONE
     36  CHARACTER(LEN=*),           INTENT(IN)    :: VarIn
     37  CHARACTER(LEN=*),           INTENT(INOUT) :: VarOut
     38  CHARACTER(LEN=*), OPTIONAL, INTENT(IN)    :: VarDef
     39  LOGICAL,          OPTIONAL, INTENT(IN)    :: lDisp
     40  LOGICAL :: lD
     41!$OMP BARRIER
     42  IF(is_master) THEN
     43     lD = .TRUE.; IF(PRESENT(lDisp)) lD = lDisp
     44     IF(PRESENT(VarDef)) VarOut = VarDef
     45     CALL getin(VarIn,VarOut)
     46     IF(lD) CALL msg(TRIM(VarIn)//' = '//TRIM(VarOut))
     47  END IF
     48  CALL bcast(VarOut)
     49END SUBROUTINE getincs_p
    4550
    4651!! -- Les entiers -- !!
    4752 
    48   SUBROUTINE getinis_p(VarIn,VarOut)
    49     IMPLICIT NONE   
    50     CHARACTER(LEN=*),INTENT(IN) :: VarIn
    51     INTEGER,INTENT(INOUT) :: VarOut   
    52 
    53 !$OMP BARRIER
    54     IF (is_mpi_root .AND. is_omp_root) THEN
    55         CALL getin(VarIn,VarOut)
    56     ENDIF
    57     CALL bcast(VarOut)
     53SUBROUTINE getinis_p(VarIn, VarOut, VarDef, lDisp)
     54  IMPLICIT NONE
     55  CHARACTER(LEN=*),  INTENT(IN)    :: VarIn
     56  INTEGER,           INTENT(INOUT) :: VarOut
     57  INTEGER, OPTIONAL, INTENT(IN)    :: VarDef
     58  LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
     59  LOGICAL :: lD
     60!$OMP BARRIER
     61  IF(is_master) THEN
     62     lD = .TRUE.; IF(PRESENT(lDisp)) lD = lDisp
     63     IF(PRESENT(VarDef)) VarOut = VarDef
     64     CALL getin(VarIn,VarOut)
     65     IF(lD) CALL msg(TRIM(VarIn)//' = '//TRIM(num2str(VarOut)))
     66  END IF
     67  CALL bcast(VarOut)
    5868  END SUBROUTINE getinis_p
    5969
    60   SUBROUTINE getini1d_p(VarIn,VarOut)
    61     IMPLICIT NONE   
    62     CHARACTER(LEN=*),INTENT(IN) :: VarIn
    63     INTEGER,INTENT(INOUT) :: VarOut(:)
    64 
    65 !$OMP BARRIER
    66     IF (is_mpi_root .AND. is_omp_root) THEN
    67         CALL getin(VarIn,VarOut)
    68     ENDIF
    69     CALL bcast(VarOut)
     70  SUBROUTINE getini1d_p(VarIn, VarOut, VarDef, lDisp)
     71  IMPLICIT NONE
     72  CHARACTER(LEN=*),  INTENT(IN)    :: VarIn
     73  INTEGER,           INTENT(INOUT) :: VarOut(:)
     74  INTEGER, OPTIONAL, INTENT(IN)    :: VarDef
     75  LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
     76  LOGICAL :: lD
     77!$OMP BARRIER
     78  IF(is_master) THEN
     79     lD = .TRUE.; IF(PRESENT(lDisp)) lD = lDisp
     80     IF(PRESENT(VarDef)) VarOut = VarDef
     81     CALL getin(VarIn,VarOut)
     82     IF(lD) CALL msg(TRIM(VarIn)//' = '//TRIM(strStack(num2str(VarOut))))
     83  END IF
     84  CALL bcast(VarOut)
    7085  END SUBROUTINE getini1d_p
    7186
    72   SUBROUTINE getini2d_p(VarIn,VarOut)
    73     IMPLICIT NONE   
    74     CHARACTER(LEN=*),INTENT(IN) :: VarIn
    75     INTEGER,INTENT(INOUT) :: VarOut(:,:)
    76 
    77 !$OMP BARRIER
    78     IF (is_mpi_root .AND. is_omp_root) THEN
    79         CALL getin(VarIn,VarOut)
    80     ENDIF
    81     CALL bcast(VarOut)
     87  SUBROUTINE getini2d_p(VarIn, VarOut, VarDef)
     88  IMPLICIT NONE
     89  CHARACTER(LEN=*),  INTENT(IN)    :: VarIn
     90  INTEGER,           INTENT(INOUT) :: VarOut(:,:)
     91  INTEGER, OPTIONAL, INTENT(IN)    :: VarDef
     92!$OMP BARRIER
     93  IF(is_master) THEN
     94     IF(PRESENT(VarDef)) VarOut = VarDef
     95     CALL getin(VarIn,VarOut)
     96  END IF
     97  CALL bcast(VarOut)
    8298  END SUBROUTINE getini2d_p
    8399
    84100!! -- Les flottants -- !!
    85101 
    86   SUBROUTINE getinrs_p(VarIn,VarOut)
    87     IMPLICIT NONE   
    88     CHARACTER(LEN=*),INTENT(IN) :: VarIn
    89     REAL,INTENT(INOUT) :: VarOut
    90 
    91 !$OMP BARRIER
    92     IF (is_mpi_root .AND. is_omp_root) THEN
    93         CALL getin(VarIn,VarOut)
    94     ENDIF
    95     CALL bcast(VarOut)
     102  SUBROUTINE getinrs_p(VarIn, VarOut, VarDef, lDisp)
     103  IMPLICIT NONE
     104  CHARACTER(LEN=*),  INTENT(IN)    :: VarIn
     105  REAL,              INTENT(INOUT) :: VarOut
     106  REAL,    OPTIONAL, INTENT(IN)    :: VarDef
     107  LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
     108  LOGICAL :: lD
     109!$OMP BARRIER
     110  IF(is_master) THEN
     111     lD = .TRUE.; IF(PRESENT(lDisp)) lD = lDisp
     112     IF(PRESENT(VarDef)) VarOut = VarDef
     113     CALL getin(VarIn,VarOut)
     114     IF(lD) CALL msg(TRIM(VarIn)//' = '//TRIM(num2str(VarOut)))
     115  END IF
     116  CALL bcast(VarOut)
    96117  END SUBROUTINE getinrs_p
    97118
    98   SUBROUTINE getinr1d_p(VarIn,VarOut)
    99     IMPLICIT NONE   
    100     CHARACTER(LEN=*),INTENT(IN) :: VarIn
    101     REAL,INTENT(INOUT) :: VarOut(:)
    102 
    103 !$OMP BARRIER
    104     IF (is_mpi_root .AND. is_omp_root) THEN
    105         CALL getin(VarIn,VarOut)
    106     ENDIF
    107     CALL bcast(VarOut)
     119  SUBROUTINE getinr1d_p(VarIn, VarOut, VarDef, lDisp)
     120  IMPLICIT NONE
     121  CHARACTER(LEN=*),  INTENT(IN)    :: VarIn
     122  REAL,              INTENT(INOUT) :: VarOut(:)
     123  REAL,    OPTIONAL, INTENT(IN)    :: VarDef
     124  LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
     125  LOGICAL :: lD
     126!$OMP BARRIER
     127  IF(is_master) THEN
     128     lD = .TRUE.; IF(PRESENT(lDisp)) lD = lDisp
     129     IF(PRESENT(VarDef)) VarOut = VarDef
     130     CALL getin(VarIn,VarOut)
     131     IF(lD) CALL msg(TRIM(VarIn)//' = '//TRIM(strStack(num2str(VarOut))))
     132  END IF
     133  CALL bcast(VarOut)
    108134  END SUBROUTINE getinr1d_p
    109135
    110   SUBROUTINE getinr2d_p(VarIn,VarOut)
    111     IMPLICIT NONE   
    112     CHARACTER(LEN=*),INTENT(IN) :: VarIn
    113     REAL,INTENT(INOUT) :: VarOut(:,:)
    114 
    115 !$OMP BARRIER
    116     IF (is_mpi_root .AND. is_omp_root) THEN
    117         CALL getin(VarIn,VarOut)
    118     ENDIF
    119     CALL bcast(VarOut)
     136  SUBROUTINE getinr2d_p(VarIn, VarOut, VarDef)
     137  IMPLICIT NONE
     138  CHARACTER(LEN=*),  INTENT(IN)    :: VarIn
     139  REAL,              INTENT(INOUT) :: VarOut(:,:)
     140  REAL,    OPTIONAL, INTENT(IN)    :: VarDef
     141!$OMP BARRIER
     142  IF(is_master) THEN
     143     IF(PRESENT(VarDef)) VarOut = VarDef
     144     CALL getin(VarIn,VarOut)
     145  END IF
     146  CALL bcast(VarOut)
    120147  END SUBROUTINE getinr2d_p
    121148
    122149!! -- Les Booleens -- !!
    123150 
    124   SUBROUTINE getinls_p(VarIn,VarOut)
    125     IMPLICIT NONE   
    126     CHARACTER(LEN=*),INTENT(IN) :: VarIn
    127     LOGICAL,INTENT(INOUT) :: VarOut
    128 
    129 !$OMP BARRIER
    130     IF (is_mpi_root .AND. is_omp_root) THEN
    131         CALL getin(VarIn,VarOut)
    132     ENDIF
    133     CALL bcast(VarOut)
     151  SUBROUTINE getinls_p(VarIn, VarOut, VarDef, lDisp)
     152  IMPLICIT NONE
     153  CHARACTER(LEN=*),  INTENT(IN)    :: VarIn
     154  LOGICAL,           INTENT(INOUT) :: VarOut
     155  LOGICAL, OPTIONAL, INTENT(IN)    :: VarDef
     156  LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
     157  LOGICAL :: lD
     158!$OMP BARRIER
     159  IF(is_master) THEN
     160     lD = .TRUE.; IF(PRESENT(lDisp)) lD = lDisp
     161     IF(PRESENT(VarDef)) VarOut = VarDef
     162     CALL getin(VarIn,VarOut)
     163     IF(lD) CALL msg(TRIM(VarIn)//' = '//TRIM(num2str(VarOut)))
     164  END IF
     165  CALL bcast(VarOut)
    134166  END SUBROUTINE getinls_p
    135167
    136   SUBROUTINE getinl1d_p(VarIn,VarOut)
    137     IMPLICIT NONE   
    138     CHARACTER(LEN=*),INTENT(IN) :: VarIn
    139     LOGICAL,INTENT(INOUT) :: VarOut(:)
    140 
    141 !$OMP BARRIER
    142     IF (is_mpi_root .AND. is_omp_root) THEN
    143         CALL getin(VarIn,VarOut)
    144     ENDIF
    145     CALL bcast(VarOut)
     168  SUBROUTINE getinl1d_p(VarIn, VarOut, VarDef, lDisp)
     169  IMPLICIT NONE
     170  CHARACTER(LEN=*),  INTENT(IN)    :: VarIn
     171  LOGICAL,           INTENT(INOUT) :: VarOut(:)
     172  LOGICAL, OPTIONAL, INTENT(IN)    :: VarDef
     173  LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
     174  LOGICAL :: lD
     175!$OMP BARRIER
     176  IF(is_master) THEN
     177     lD = .TRUE.; IF(PRESENT(lDisp)) lD = lDisp
     178     IF(PRESENT(VarDef)) VarOut = VarDef
     179     CALL getin(VarIn,VarOut)
     180     IF(lD) CALL msg(TRIM(VarIn)//' = '//TRIM(strStack(num2str(VarOut))))
     181  END IF
     182  CALL bcast(VarOut)
    146183  END SUBROUTINE getinl1d_p
    147184
    148   SUBROUTINE getinl2d_p(VarIn,VarOut)
    149     IMPLICIT NONE   
    150     CHARACTER(LEN=*),INTENT(IN) :: VarIn
    151     LOGICAL,INTENT(INOUT) :: VarOut(:,:)
    152 
    153 !$OMP BARRIER
    154     IF (is_mpi_root .AND. is_omp_root) THEN
    155         CALL getin(VarIn,VarOut)
    156     ENDIF
    157     CALL bcast(VarOut)
     185  SUBROUTINE getinl2d_p(VarIn, VarOut, VarDef)
     186  IMPLICIT NONE
     187  CHARACTER(LEN=*),  INTENT(IN)    :: VarIn
     188  LOGICAL,           INTENT(INOUT) :: VarOut(:,:)
     189  LOGICAL, OPTIONAL, INTENT(IN)    :: VarDef
     190!$OMP BARRIER
     191  IF(is_master) THEN
     192     IF(PRESENT(VarDef)) VarOut = VarDef
     193     CALL getin(VarIn,VarOut)
     194  END IF
     195  CALL bcast(VarOut)
    158196  END SUBROUTINE getinl2d_p
    159197!-
  • LMDZ6/trunk/libf/phylmdiso/isotopes_mod.F90

    r5748 r5754  
    66   USE infotrac_phy, ONLY: isoName, niso, ntiso
    77   USE iso_params_mod
     8   USE ioipsl_getin_p_mod, ONLY : getin_p
    89   IMPLICIT NONE
    9    INTERFACE get_in; MODULE PROCEDURE getinp_s, getinp_i, getinp_r, getinp_l;  END INTERFACE get_in
    1010
    1111  !--- Contains all isotopic variables + their initialization
     
    187187
    188188         !--- Initialisation: reading the isotopic parameters.
    189          CALL get_in('lambda',     lambda_sursat, 0.004); IF(ok_nocinsat) lambda_sursat = 0.
    190          CALL get_in('thumxt1',    thumxt1,       0.75*1.2)
    191          CALL get_in('ntot',       ntot,          20,  .FALSE.)
    192          CALL get_in('h_land_ice', h_land_ice,    20., .FALSE.)
    193          CALL get_in('P_veg',      P_veg,         1.0, .FALSE.)
    194          CALL get_in('bidouille_anti_divergence', bidouille_anti_divergence, .FALSE.)
    195          CALL get_in('essai_convergence',         essai_convergence,         .FALSE.)
    196          CALL get_in('initialisation_iso',        initialisation_iso,        0)
     189         CALL getin_p('lambda',     lambda_sursat, 0.004); IF(ok_nocinsat) lambda_sursat = 0.
     190         CALL getin_p('thumxt1',    thumxt1,       0.75*1.2)
     191         CALL getin_p('ntot',       ntot,          20,  lDisp=.FALSE.)
     192         CALL getin_p('h_land_ice', h_land_ice,    20., lDisp=.FALSE.)
     193         CALL getin_p('P_veg',      P_veg,         1.0, lDisp=.FALSE.)
     194         CALL getin_p('bidouille_anti_divergence', bidouille_anti_divergence, .FALSE.)
     195         CALL getin_p('essai_convergence',         essai_convergence,         .FALSE.)
     196         CALL getin_p('initialisation_iso',        initialisation_iso,        0)
    197197
    198198!        IF(nzone>0 .AND. initialisation_iso==0) &
    199 !           CALL get_in('initialisation_isotrac',initialisation_isotrac)
    200          CALL get_in('modif_sst',      modif_sst,         0)
    201          CALL get_in('deltaTtest',     deltaTtest,      0.0)     !--- For modif_sst>=1
    202          CALL get_in('deltaTtestpoles',deltaTtestpoles, 0.0)     !--- For modif_sst>=2
    203          CALL get_in( 'sstlatcrit',    sstlatcrit,     30.0)     !--- For modif_sst>=3
    204          CALL get_in('dsstlatcrit',   dsstlatcrit,      0.0)     !--- For modif_sst>=3
     199!           CALL getin_p('initialisation_isotrac',initialisation_isotrac)
     200         CALL getin_p('modif_sst',      modif_sst,         0)
     201         CALL getin_p('deltaTtest',     deltaTtest,      0.0)     !--- For modif_sst>=1
     202         CALL getin_p('deltaTtestpoles',deltaTtestpoles, 0.0)     !--- For modif_sst>=2
     203         CALL getin_p( 'sstlatcrit',    sstlatcrit,     30.0)     !--- For modif_sst>=3
     204         CALL getin_p('dsstlatcrit',   dsstlatcrit,      0.0)     !--- For modif_sst>=3
    205205#ifdef ISOVERIF
    206206         CALL msg('iso_init 270:  sstlatcrit='//num2str( sstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=2
     
    209209#endif             
    210210
    211          CALL get_in('modif_sic', modif_sic,  0)
     211         CALL getin_p('modif_sic', modif_sic,  0)
    212212         IF(modif_sic >= 1) &
    213          CALL get_in('deltasic',  deltasic, 0.1)
    214 
    215          CALL get_in('albedo_prescrit', albedo_prescrit, 0)
     213         CALL getin_p('deltasic',  deltasic, 0.1)
     214
     215         CALL getin_p('albedo_prescrit', albedo_prescrit, 0)
    216216         IF(albedo_prescrit == 1) THEN
    217             CALL get_in('lon_min_albedo', lon_min_albedo, -200.)
    218             CALL get_in('lon_max_albedo', lon_max_albedo,  200.)
    219             CALL get_in('lat_min_albedo', lat_min_albedo, -100.)
    220             CALL get_in('lat_max_albedo', lat_max_albedo,  100.)
    221          END IF
    222          CALL get_in('deltaO18_oce',        deltaO18_oce,   0.0)
    223          CALL get_in('deltaP_BL',           deltaP_BL,     10.0)
    224          CALL get_in('ruissellement_pluie', ruissellement_pluie, 0)
    225          CALL get_in('alphak_stewart',      alphak_stewart,      1)
    226          CALL get_in('tdifexp_sol',         tdifexp_sol,      0.67)
    227          CALL get_in('calendrier_guide',    calendrier_guide,    0)
    228          CALL get_in('cste_surf_cond',      cste_surf_cond,      0)
    229          CALL get_in('mixlen',              mixlen,           35.0)
    230          CALL get_in('evap_cont_cste',      evap_cont_cste,      0)
    231          CALL get_in('deltaO18_evap_cont',  deltaO18_evap_cont,0.0)
    232          CALL get_in('d_evap_cont',         d_evap_cont,       0.0)
    233          CALL get_in('nudge_qsol',          nudge_qsol,          0)
    234          CALL get_in('region_nudge_qsol',   region_nudge_qsol,   1)
     217            CALL getin_p('lon_min_albedo', lon_min_albedo, -200.)
     218            CALL getin_p('lon_max_albedo', lon_max_albedo,  200.)
     219            CALL getin_p('lat_min_albedo', lat_min_albedo, -100.)
     220            CALL getin_p('lat_max_albedo', lat_max_albedo,  100.)
     221         END IF
     222         CALL getin_p('deltaO18_oce',        deltaO18_oce,   0.0)
     223         CALL getin_p('deltaP_BL',           deltaP_BL,     10.0)
     224         CALL getin_p('ruissellement_pluie', ruissellement_pluie, 0)
     225         CALL getin_p('alphak_stewart',      alphak_stewart,      1)
     226         CALL getin_p('tdifexp_sol',         tdifexp_sol,      0.67)
     227         CALL getin_p('calendrier_guide',    calendrier_guide,    0)
     228         CALL getin_p('cste_surf_cond',      cste_surf_cond,      0)
     229         CALL getin_p('mixlen',              mixlen,           35.0)
     230         CALL getin_p('evap_cont_cste',      evap_cont_cste,      0)
     231         CALL getin_p('deltaO18_evap_cont',  deltaO18_evap_cont,0.0)
     232         CALL getin_p('d_evap_cont',         d_evap_cont,       0.0)
     233         CALL getin_p('nudge_qsol',          nudge_qsol,          0)
     234         CALL getin_p('region_nudge_qsol',   region_nudge_qsol,   1)
    235235         nlevmaxO17 = 50
    236236         CALL msg('nlevmaxO17='//TRIM(num2str(nlevmaxO17)))
    237          CALL get_in('no_pce',   no_pce,     0)
    238          CALL get_in('A_satlim', A_satlim, 1.0)
    239          CALL get_in('ok_restrict_A_satlim', ok_restrict_A_satlim, 0)
     237         CALL getin_p('no_pce',   no_pce,     0)
     238         CALL getin_p('A_satlim', A_satlim, 1.0)
     239         CALL getin_p('ok_restrict_A_satlim', ok_restrict_A_satlim, 0)
    240240#ifdef ISOVERIF
    241          CALL msg(' 315: A_satlim='//num2str(A_satlim), modname, A_satlim > 1.0)
     241         CALL msg(' 315: A_satlim='//TRIM(num2str(A_satlim)), modname, A_satlim > 1.0)
    242242         IF(A_satlim > 1.0) STOP
    243243#endif
    244 !        CALL get_in('slope_limiterxy',   slope_limiterxy,  2.0)
    245 !        CALL get_in('slope_limiterz',    slope_limiterz,   2.0)
    246          CALL get_in('modif_ratqs',       modif_ratqs,        0)
    247          CALL get_in('Pcrit_ratqs',       Pcrit_ratqs,    500.0)
    248          CALL get_in('ratqsbasnew',       ratqsbasnew,     0.05)
    249          CALL get_in('fac_modif_evaoce',  fac_modif_evaoce, 1.0)
    250          CALL get_in('ok_bidouille_wake', ok_bidouille_wake,  0)
     244!        CALL getin_p('slope_limiterxy',   slope_limiterxy,  2.0)
     245!        CALL getin_p('slope_limiterz',    slope_limiterz,   2.0)
     246         CALL getin_p('modif_ratqs',       modif_ratqs,        0)
     247         CALL getin_p('Pcrit_ratqs',       Pcrit_ratqs,    500.0)
     248         CALL getin_p('ratqsbasnew',       ratqsbasnew,     0.05)
     249         CALL getin_p('fac_modif_evaoce',  fac_modif_evaoce, 1.0)
     250         CALL getin_p('ok_bidouille_wake', ok_bidouille_wake,  0)
    251251         ! si oui, la temperature de cond est celle de l'environnement, pour eviter
    252252         ! bugs quand temperature dans ascendances convs est mal calculee
    253          CALL get_in('cond_temp_env',        cond_temp_env,        .FALSE.)
     253         CALL getin_p('cond_temp_env',        cond_temp_env,        .FALSE.)
    254254         IF(ANY(isoName == 'HTO')) &
    255          CALL get_in('ok_prod_nucl_tritium', ok_prod_nucl_tritium, .FALSE., .FALSE.)
    256          CALL get_in('tnateq1', ltnat1, .TRUE.)
     255         CALL getin_p('ok_prod_nucl_tritium', ok_prod_nucl_tritium, .FALSE., lDisp=.FALSE.)
     256         CALL getin_p('tnateq1', ltnat1, .TRUE.)
    257257
    258258         CALL msg('iso_O18, iso_HDO, iso_eau = '//TRIM(strStack(num2str([iso_O18, iso_HDO, iso_eau]))), modname)
  • LMDZ6/trunk/libf/phylmdiso/isotrac_mod.F90

    r5748 r5754  
    44MODULE isotrac_mod
    55  USE infotrac_phy, ONLY: niso, ntiso, nzone, delPhase
    6   USE isotopes_mod, ONLY: ridicule, get_in
    7 
     6  USE isotopes_mod, ONLY: ridicule
     7  USE ioipsl_getin_p_mod, ONLY : getin_p
    88  IMPLICIT NONE
    99  SAVE
     
    148148   USE isotopes_mod, ONLY: iso_eau, ntracisoOR, initialisation_iso
    149149   USE dimphy,       ONLY: klon, klev
    150    USE  strings_mod, ONLY: num2str, strStack, strTail, strHead, strIdx
     150   USE  strings_mod, ONLY: num2str, strStack, strTail, strHead, strIdx, maxlen
    151151
    152152   IMPLICIT NONE
     
    156156   INTEGER :: izone_pres, izone_lat
    157157   INTEGER :: nzone_opt
    158 
    159    CALL msg("traceurs_init 18: isotrac ne marche que si on met l'eau comme isotope", 'iso_traceurs_init', iso_eau==0)
    160    IF(lerr) STOP
     158   LOGICAL :: lerr
     159   CHARACTER(LEN=maxlen) :: modname
     160
     161   modname = 'iso_traceurs_init'
     162   lerr = iso_eau == 0
     163   IF(lerr) CALL abort_physics(TRIM(modname)//' 18', 'isotrac does not work without H216O isotope', 1)
    161164
    162165   !--- Initialize
     
    172175   ALLOCATE( boite_map(klon,klev))
    173176
    174    IF(initialisation_iso == 0) CALL get_in('initialisation_isotrac', initialisation_isotrac)
     177   IF(initialisation_iso == 0) CALL getin_p('initialisation_isotrac', initialisation_isotrac)
    175178
    176179   !--- Read tracing option
    177    CALL get_in('option_traceurs', option_traceurs)
     180   CALL getin_p('option_traceurs', option_traceurs)
    178181
    179182   !--- Genral case: no traceurs in ORCHIDEE
     
    215218      !========================================================================================================================
    216219         ! lire les use_bassin
    217          CALL get_in('use_bassin_Atlantic',   use_bassin_Atlantic)
    218          CALL get_in('use_bassin_Medit',      use_bassin_Medit)
    219          CALL get_in('use_bassin_Indian',     use_bassin_Indian)
    220          CALL get_in('use_bassin_Austral',    use_bassin_Austral)
    221          CALL get_in('use_bassin_Pacific',    use_bassin_Pacific)
    222          CALL get_in('use_bassin_MerArabie',  use_bassin_MerArabie)
    223          CALL get_in('use_bassin_BengalGolf', use_bassin_BengalGolf)
    224          CALL get_in('use_bassin_SouthIndian',use_bassin_SouthIndian)
    225          CALL get_in('use_bassin_Tropics',    use_bassin_Tropics)
    226          CALL get_in('use_bassin_Midlats',    use_bassin_Midlats)
    227          CALL get_in('use_bassin_HighLats',   use_bassin_HighLats)
     220         CALL getin_p('use_bassin_Atlantic',   use_bassin_Atlantic)
     221         CALL getin_p('use_bassin_Medit',      use_bassin_Medit)
     222         CALL getin_p('use_bassin_Indian',     use_bassin_Indian)
     223         CALL getin_p('use_bassin_Austral',    use_bassin_Austral)
     224         CALL getin_p('use_bassin_Pacific',    use_bassin_Pacific)
     225         CALL getin_p('use_bassin_MerArabie',  use_bassin_MerArabie)
     226         CALL getin_p('use_bassin_BengalGolf', use_bassin_BengalGolf)
     227         CALL getin_p('use_bassin_SouthIndian',use_bassin_SouthIndian)
     228         CALL getin_p('use_bassin_Tropics',    use_bassin_Tropics)
     229         CALL getin_p('use_bassin_Midlats',    use_bassin_Midlats)
     230         CALL getin_p('use_bassin_HighLats',   use_bassin_HighLats)
    228231         nzone_opt  =  2  +  COUNT([use_bassin_Atlantic, use_bassin_Medit,     use_bassin_Indian,     &
    229232            use_bassin_Austral,     use_bassin_Pacific,  use_bassin_MerArabie, use_bassin_BengalGolf, &
     
    353356         ! 1 par defaut pour colorier a la fois condensat LS et condensat convectif.
    354357         ! Mais on peut mettre 2 si on ne veut que colorier que le condensat convectif.
    355          CALL get_in('option_cond',option_cond)
     358         CALL getin_p('option_cond',option_cond)
    356359         strtrac(izone_poubelle)='res'
    357360         strtrac(izone_cond)='con'
     
    587590      CASE(20)     !=== TRACING TROPICAL/EXTRATROPICAL/EXTRATROPICAL RECYCLING TO STUDY HUMIDITY AND SUBTROPICAL ISOTOPES CONTROL
    588591      !========================================================================================================================
    589          CALL get_in('lim_tag20', lim_tag20, 35.0)
     592         CALL getin_p('lim_tag20', lim_tag20, 35.0)
    590593         nzone_opt=3
    591594         izone_cont=1
     
    622625      CASE(22)     !=== TRACING WATER VAPOUR PROCESSED IN THE 3-LEVELS SCONVECTION ZONES BT, MT AND UT
    623626      !========================================================================================================================
    624          CALL get_in('lim_precip_tag22', lim_precip_tag22, 20.0)
     627         CALL getin_p('lim_precip_tag22', lim_precip_tag22, 20.0)
    625628         nzone_opt=3
    626629         izone_cont=1
     
    650653   IF(option_tmin == 1) THEN
    651654      seuil_tag_tmin = 0.01
    652       CALL get_in('seuil_tag_tmin',        seuil_tag_tmin,        0.01)
    653       CALL get_in('seuil_tag_tmin_ls',     seuil_tag_tmin_ls,     seuil_tag_tmin)
    654       CALL get_in('option_seuil_tag_tmin', option_seuil_tag_tmin, 1)
     655      CALL getin_p('seuil_tag_tmin',        seuil_tag_tmin,        0.01)
     656      CALL getin_p('seuil_tag_tmin_ls',     seuil_tag_tmin_ls,     seuil_tag_tmin)
     657      CALL getin_p('option_seuil_tag_tmin', option_seuil_tag_tmin, 1)
    655658   END IF
    656659
Note: See TracChangeset for help on using the changeset viewer.