Ignore:
Timestamp:
Jul 28, 2025, 7:23:15 PM (7 days ago)
Author:
aborella
Message:

Merge with trunk r5789

Location:
LMDZ6/branches/contrails
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

  • LMDZ6/branches/contrails/libf/phylmdiso/isotopes_mod.F90

    r5267 r5791  
    33
    44MODULE isotopes_mod
    5    USE strings_mod,  ONLY: msg, real2str, int2str, bool2str, maxlen, strIdx, strStack
    6    USE infotrac_phy, ONLY: isoName, niso, ntiso
     5   USE strings_mod,  ONLY: msg, num2str, maxlen, strIdx, strStack
     6   USE infotrac_phy, ONLY: isoName, niso, ntiso, nbIso, isoFamilies, isoSelect, isoCheck
    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
     
    150150
    151151   !=== Local variables:
    152    INTEGER :: ixt, is
     152   INTEGER :: ixt, is, ii
    153153   LOGICAL :: ltnat1
    154154   CHARACTER(LEN=maxlen) :: modname, sxt
     
    173173
    174174   !--- Check number of isotopes
    175    CALL msg('64: niso = '//TRIM(int2str(niso)), modname)
    176 
     175   CALL msg('64: niso = '//TRIM(num2str(niso)), modname)
     176
     177   DO ii = 1, nbIso
     178      CALL msg('Can''t select isotopes class "'//TRIM(isoFamilies(ii))//'"', modname, isoSelect(ii, lVerbose=.TRUE.))
     179
     180!==============================================================================================================================
     181      IF(isoFamilies(ii) == 'H2O') THEN
     182!==============================================================================================================================
    177183         !--- Init de ntracisoOR: on ecrasera en cas de traceurs de tagging isotopiques
    178184         !                     (nzone>0) si complications avec ORCHIDEE
     
    180186
    181187         !--- Type of water isotopes:
    182          iso_eau = strIdx(isoName, 'H216O'); CALL msg('iso_eau='//int2str(iso_eau), modname)
    183          iso_HDO = strIdx(isoName, 'HDO');   CALL msg('iso_HDO='//int2str(iso_HDO), modname)
    184          iso_O18 = strIdx(isoName, 'H218O'); CALL msg('iso_O18='//int2str(iso_O18), modname)
    185          iso_O17 = strIdx(isoName, 'H217O'); CALL msg('iso_O17='//int2str(iso_O17), modname)
    186          iso_HTO = strIdx(isoName, 'HTO');   CALL msg('iso_HTO='//int2str(iso_HTO), modname)
     188         iso_eau = strIdx(isoName, 'H216O'); CALL msg('iso_eau='//num2str(iso_eau), modname)
     189         iso_HDO = strIdx(isoName, 'HDO');   CALL msg('iso_HDO='//num2str(iso_HDO), modname)
     190         iso_O18 = strIdx(isoName, 'H218O'); CALL msg('iso_O18='//num2str(iso_O18), modname)
     191         iso_O17 = strIdx(isoName, 'H217O'); CALL msg('iso_O17='//num2str(iso_O17), modname)
     192         iso_HTO = strIdx(isoName, 'HTO');   CALL msg('iso_HTO='//num2str(iso_HTO), modname)
    187193
    188194         !--- 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)
     195         CALL getin_p('lambda',     lambda_sursat, 0.004); IF(ok_nocinsat) lambda_sursat = 0.
     196         CALL getin_p('thumxt1',    thumxt1,       0.75*1.2)
     197         CALL getin_p('ntot',       ntot,          20,  lDisp=.FALSE.)
     198         CALL getin_p('h_land_ice', h_land_ice,    20., lDisp=.FALSE.)
     199         CALL getin_p('P_veg',      P_veg,         1.0, lDisp=.FALSE.)
     200         CALL getin_p('bidouille_anti_divergence', bidouille_anti_divergence, .FALSE.)
     201         CALL getin_p('essai_convergence',         essai_convergence,         .FALSE.)
     202         CALL getin_p('initialisation_iso',        initialisation_iso,        0)
    197203
    198204!        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
    205 #ifdef ISOVERIF
    206          CALL msg('iso_init 270:  sstlatcrit='//real2str( sstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=2
    207          CALL msg('iso_init 279: dsstlatcrit='//real2str(dsstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=3
     205!           CALL getin_p('initialisation_isotrac',initialisation_isotrac)
     206         CALL getin_p('modif_sst',      modif_sst,         0)
     207         CALL getin_p('deltaTtest',     deltaTtest,      0.0)     !--- For modif_sst>=1
     208         CALL getin_p('deltaTtestpoles',deltaTtestpoles, 0.0)     !--- For modif_sst>=2
     209         CALL getin_p( 'sstlatcrit',    sstlatcrit,     30.0)     !--- For modif_sst>=3
     210         CALL getin_p('dsstlatcrit',   dsstlatcrit,      0.0)     !--- For modif_sst>=3
     211         IF(isoCheck) THEN
     212         CALL msg('iso_init 270:  sstlatcrit='//num2str( sstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=2
     213         CALL msg('iso_init 279: dsstlatcrit='//num2str(dsstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=3
    208214         IF(modif_sst >= 2 .AND. sstlatcrit < 0.0) STOP
    209 #endif             
    210 
    211          CALL get_in('modif_sic', modif_sic,  0)
     215         END IF
     216         CALL getin_p('modif_sic', modif_sic,  0)
    212217         IF(modif_sic >= 1) &
    213          CALL get_in('deltasic',  deltasic, 0.1)
    214 
    215          CALL get_in('albedo_prescrit', albedo_prescrit, 0)
     218         CALL getin_p('deltasic',  deltasic, 0.1)
     219
     220         CALL getin_p('albedo_prescrit', albedo_prescrit, 0)
    216221         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)
     222            CALL getin_p('lon_min_albedo', lon_min_albedo, -200.)
     223            CALL getin_p('lon_max_albedo', lon_max_albedo,  200.)
     224            CALL getin_p('lat_min_albedo', lat_min_albedo, -100.)
     225            CALL getin_p('lat_max_albedo', lat_max_albedo,  100.)
     226         END IF
     227         CALL getin_p('deltaO18_oce',        deltaO18_oce,   0.0)
     228         CALL getin_p('deltaP_BL',           deltaP_BL,     10.0)
     229         CALL getin_p('ruissellement_pluie', ruissellement_pluie, 0)
     230         CALL getin_p('alphak_stewart',      alphak_stewart,      1)
     231         CALL getin_p('tdifexp_sol',         tdifexp_sol,      0.67)
     232         CALL getin_p('calendrier_guide',    calendrier_guide,    0)
     233         CALL getin_p('cste_surf_cond',      cste_surf_cond,      0)
     234         CALL getin_p('mixlen',              mixlen,           35.0)
     235         CALL getin_p('evap_cont_cste',      evap_cont_cste,      0)
     236         CALL getin_p('deltaO18_evap_cont',  deltaO18_evap_cont,0.0)
     237         CALL getin_p('d_evap_cont',         d_evap_cont,       0.0)
     238         CALL getin_p('nudge_qsol',          nudge_qsol,          0)
     239         CALL getin_p('region_nudge_qsol',   region_nudge_qsol,   1)
    235240         nlevmaxO17 = 50
    236          CALL msg('nlevmaxO17='//TRIM(int2str(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)
    240 #ifdef ISOVERIF
    241          CALL msg(' 315: A_satlim='//real2str(A_satlim), modname, A_satlim > 1.0)
     241         CALL msg('nlevmaxO17='//TRIM(num2str(nlevmaxO17)))
     242         CALL getin_p('no_pce',   no_pce,     0)
     243         CALL getin_p('A_satlim', A_satlim, 1.0)
     244         CALL getin_p('ok_restrict_A_satlim', ok_restrict_A_satlim, 0)
     245         IF(isoCheck) THEN
     246         CALL msg(' 315: A_satlim='//TRIM(num2str(A_satlim)), modname, A_satlim > 1.0)
    242247         IF(A_satlim > 1.0) STOP
    243 #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)
     248         END IF
     249!        CALL getin_p('slope_limiterxy',   slope_limiterxy,  2.0)
     250!        CALL getin_p('slope_limiterz',    slope_limiterz,   2.0)
     251         CALL getin_p('modif_ratqs',       modif_ratqs,        0)
     252         CALL getin_p('Pcrit_ratqs',       Pcrit_ratqs,    500.0)
     253         CALL getin_p('ratqsbasnew',       ratqsbasnew,     0.05)
     254         CALL getin_p('fac_modif_evaoce',  fac_modif_evaoce, 1.0)
     255         CALL getin_p('ok_bidouille_wake', ok_bidouille_wake,  0)
    251256         ! si oui, la temperature de cond est celle de l'environnement, pour eviter
    252257         ! bugs quand temperature dans ascendances convs est mal calculee
    253          CALL get_in('cond_temp_env',        cond_temp_env,        .FALSE.)
     258         CALL getin_p('cond_temp_env',        cond_temp_env,        .FALSE.)
    254259         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.)
    257 
    258          CALL msg('iso_O18, iso_HDO, iso_eau = '//TRIM(strStack(int2str([iso_O18, iso_HDO, iso_eau]))), modname)
     260         CALL getin_p('ok_prod_nucl_tritium', ok_prod_nucl_tritium, .FALSE., lDisp=.FALSE.)
     261         CALL getin_p('tnateq1', ltnat1, .TRUE.)
     262
     263         CALL msg('iso_O18, iso_HDO, iso_eau = '//TRIM(strStack(num2str([iso_O18, iso_HDO, iso_eau]))), modname)
    259264
    260265         !--------------------------------------------------------------
     
    363368         CALL msg('285: verif initialisation:', modname)
    364369         DO ixt=1,niso
    365             sxt=int2str(ixt)
     370            sxt=num2str(ixt)
    366371            CALL msg(' * isoName('//TRIM(sxt)//') = <'//TRIM(isoName(ixt))//'>',  modname)
    367             CALL msg(  '    tnat('//TRIM(sxt)//') = '//TRIM(real2str(tnat(ixt))), modname)
    368 !           CALL msg('    alpha_liq_sol('//TRIM(sxt)//') = '//TRIM(real2str(alpha_liq_sol(ixt))), modname)
    369 !           CALL msg(        '   tkcin0('//TRIM(sxt)//') = '//TRIM(real2str(tkcin0(ixt))),        modname)
    370 !           CALL msg(       '   tdifrel('//TRIM(sxt)//') = '//TRIM(real2str(tdifrel(ixt))),       modname)
     372            CALL msg(  '    tnat('//TRIM(sxt)//') = '//TRIM(num2str(tnat(ixt))), modname)
     373!           CALL msg('    alpha_liq_sol('//TRIM(sxt)//') = '//TRIM(num2str(alpha_liq_sol(ixt))), modname)
     374!           CALL msg(        '   tkcin0('//TRIM(sxt)//') = '//TRIM(num2str(tkcin0(ixt))),        modname)
     375!           CALL msg(       '   tdifrel('//TRIM(sxt)//') = '//TRIM(num2str(tdifrel(ixt))),       modname)
    371376         END DO
    372          CALL msg('69:     lambda = '//TRIM(real2str(lambda_sursat)), modname)
    373          CALL msg('69:    thumxt1 = '//TRIM(real2str(thumxt1)),       modname)
    374          CALL msg('69: h_land_ice = '//TRIM(real2str(h_land_ice)),    modname)
    375          CALL msg('69:      P_veg = '//TRIM(real2str(P_veg)),         modname)
     377         CALL msg('69:     lambda = '//TRIM(num2str(lambda_sursat)), modname)
     378         CALL msg('69:    thumxt1 = '//TRIM(num2str(thumxt1)),       modname)
     379         CALL msg('69: h_land_ice = '//TRIM(num2str(h_land_ice)),    modname)
     380         CALL msg('69:      P_veg = '//TRIM(num2str(P_veg)),         modname)
     381!==============================================================================================================================
     382      ELSE
     383!==============================================================================================================================
     384         CALL abort_physic('"isotopes_mod" is not set up yet for isotopes family "'//TRIM(isoFamilies(ii))//'"', modname, 1)
     385!==============================================================================================================================
     386      END IF
     387!==============================================================================================================================
     388   END DO
    376389
    377390END SUBROUTINE iso_init
    378 
    379 
    380 SUBROUTINE getinp_s(nam, val, def, lDisp)
    381    USE ioipsl, ONLY: getin
    382    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    383    USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
    384    USE mod_phys_lmdz_transfert_para, ONLY : bcast
    385    CHARACTER(LEN=*),           INTENT(IN)    :: nam
    386    CHARACTER(LEN=*),           INTENT(INOUT) :: val
    387    CHARACTER(LEN=*), OPTIONAL, INTENT(IN)    :: def
    388    LOGICAL,          OPTIONAL, INTENT(IN)    :: lDisp
    389    LOGICAL :: lD
    390 !$OMP BARRIER
    391    IF(is_mpi_root.AND.is_omp_root) THEN
    392       IF(PRESENT(def)) val=def; CALL getin(nam,val)
    393       lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
    394       IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(val))
    395   END IF
    396   CALL bcast(val)
    397 END SUBROUTINE getinp_s
    398 
    399 SUBROUTINE getinp_i(nam, val, def, lDisp)
    400    USE ioipsl, ONLY: getin
    401    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    402    USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
    403    USE mod_phys_lmdz_transfert_para, ONLY : bcast
    404    CHARACTER(LEN=*),  INTENT(IN)    :: nam
    405    INTEGER,           INTENT(INOUT) :: val
    406    INTEGER, OPTIONAL, INTENT(IN)    :: def
    407    LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
    408    LOGICAL :: lD
    409 !$OMP BARRIER
    410    IF(is_mpi_root.AND.is_omp_root) THEN
    411       IF(PRESENT(def)) val=def; CALL getin(nam,val)
    412       lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
    413       IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(int2str(val)))
    414   END IF
    415   CALL bcast(val)
    416 END SUBROUTINE getinp_i
    417 
    418 SUBROUTINE getinp_r(nam, val, def, lDisp)
    419    USE ioipsl, ONLY: getin
    420    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    421    USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
    422    USE mod_phys_lmdz_transfert_para, ONLY : bcast
    423    CHARACTER(LEN=*),  INTENT(IN)    :: nam
    424    REAL,              INTENT(INOUT) :: val
    425    REAL,    OPTIONAL, INTENT(IN)    :: def
    426    LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
    427    LOGICAL :: lD
    428 !$OMP BARRIER
    429    IF(is_mpi_root.AND.is_omp_root) THEN
    430       IF(PRESENT(def)) val=def; CALL getin(nam,val)
    431       lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
    432       IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(real2str(val)))
    433   END IF
    434   CALL bcast(val)
    435 END SUBROUTINE getinp_r
    436 
    437 SUBROUTINE getinp_l(nam, val, def, lDisp)
    438    USE ioipsl, ONLY: getin
    439    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    440    USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
    441    USE mod_phys_lmdz_transfert_para, ONLY : bcast
    442    CHARACTER(LEN=*),  INTENT(IN)    :: nam
    443    LOGICAL,           INTENT(INOUT) :: val
    444    LOGICAL, OPTIONAL, INTENT(IN)    :: def
    445    LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
    446    LOGICAL :: lD
    447 !$OMP BARRIER
    448    IF(is_mpi_root.AND.is_omp_root) THEN
    449       IF(PRESENT(def)) val=def; CALL getin(nam,val)
    450       lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
    451       IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(bool2str(val)))
    452   END IF
    453   CALL bcast(val)
    454 END SUBROUTINE getinp_l
    455391
    456392END MODULE isotopes_mod
Note: See TracChangeset for help on using the changeset viewer.