Changeset 5229 for LMDZ6/branches
- Timestamp:
- Sep 25, 2024, 12:03:08 PM (4 months ago)
- Location:
- LMDZ6/branches/Amaury_dev/libf
- Files:
-
- 1 added
- 8 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/Amaury_dev/libf/dyn3d/iniacademic.F90
r5223 r5229 1 ! $Id$2 3 1 SUBROUTINE iniacademic(vcov, ucov, teta, q, masse, ps, phis, time_0) 4 2 5 3 USE lmdz_filtreg, ONLY: inifilr 6 USE lmdz_infotrac, ONLY: nqtot, niso, iqIsoPha, tracers, getKey,isoName, addPhase4 USE lmdz_infotrac, ONLY: nqtot, niso, iqIsoPha, tracers, isoName, addPhase 7 5 USE control_mod, ONLY: day_step, planet_type 8 6 USE exner_hyb_m, ONLY: exner_hyb … … 20 18 USE lmdz_academic, ONLY: tetarappel, knewt_t, kfrict, knewt_g, clat4 21 19 USE lmdz_comgeom 20 USE iso_params_mod ! tnat_* and alpha_ideal_* 22 21 23 22 ! Author: Frederic Hourdin original: 15/01/93 … … 323 322 WRITE(lunout, *)'In '//TRIM(modname)//': !!! Beware: alpha_ideal put to 1 !!!' 324 323 ELSE 325 IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) & 326 CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1) 324 SELECT CASE(isoName(iName)) 325 CASE('H216O'); tnat = tnat_H216O; alpha_ideal = alpha_ideal_H216O 326 CASE('H217O'); tnat = tnat_H217O; alpha_ideal = alpha_ideal_H217O 327 CASE('H218O'); tnat = tnat_H218O; alpha_ideal = alpha_ideal_H218O 328 CASE('HDO'); tnat = tnat_HDO; alpha_ideal = alpha_ideal_HDO 329 CASE('HTO'); tnat = tnat_HTO; alpha_ideal = alpha_ideal_HTO 330 CASE DEFAULT 331 CALL abort_gcm(TRIM(modname),'unknown isotope "'//TRIM(isoName(iName))//'" ; check tracer.def file',1) 332 END SELECT 327 333 END IF 328 334 q(:,:,iq) = q(:,:,iqParent)*tnat*(q(:,:,iqParent)/30.e-3)**(alpha_ideal-1.) -
LMDZ6/branches/Amaury_dev/libf/dyn3d/lmdz_check_isotopes.f90
r5224 r5229 9 9 USE lmdz_strings, ONLY: maxlen, msg, strIdx, strStack, int2str, real2str 10 10 USE lmdz_infotrac, ONLY: nqtot, niso, nphas, isotope, isoCheck, iqIsoPha, isoSelect, & 11 ntiso, iH2O, nzone, tracers, isoName, itZonIso, getKey 11 ntiso, iH2O, nzone, tracers, isoName, itZonIso 12 USE iso_params_mod, ONLY: tnat_H216O, tnat_H217O, tnat_H218O, tnat_HDO, tnat_HTO 12 13 13 14 USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm … … 31 32 ridicule = 1e-12 32 33 INTEGER, SAVE :: iso_eau, iso_O17, iso_O18, iso_HDO, iso_HTO 33 LOGICAL, SAVE :: ltnat1, first = .TRUE. 34 LOGICAL :: ltnat1 35 LOGICAL, SAVE :: first = .TRUE. 34 36 35 37 modname = 'check_isotopes' … … 40 42 ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1) 41 43 ALLOCATE(tnat(niso)) 42 iso_eau = strIdx(isoName, 'H216O') 43 iso_O17 = strIdx(isoName, 'H217O') 44 iso_O18 = strIdx(isoName, 'H218O') 45 iso_HDO = strIdx(isoName, 'HDO') 46 iso_HTO = strIdx(isoName, 'HTO') 47 IF(ltnat1) THEN 48 tnat(:) = 1.0 49 ELSE 50 IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1) 51 END IF 44 iso_eau = strIdx(isoName, 'H216O'); IF(iso_eau /= 0) tnat(iso_eau) = tnat_H216O 45 iso_O17 = strIdx(isoName, 'H217O'); IF(iso_O17 /= 0) tnat(iso_O17) = tnat_H217O 46 iso_O18 = strIdx(isoName, 'H218O'); IF(iso_O18 /= 0) tnat(iso_O18) = tnat_H218O 47 iso_HDO = strIdx(isoName, 'HDO'); IF(iso_HDO /= 0) tnat(iso_HDO) = tnat_HDO 48 iso_HTO = strIdx(isoName, 'HTO'); IF(iso_HTO /= 0) tnat(iso_HTO) = tnat_HTO 49 IF(ltnat1) tnat(:) = 1. 52 50 first = .FALSE. 53 51 END IF … … 61 59 DO k = 1, llm 62 60 DO i = 1, ip1jmp1 63 IF(ABS(q(i, k, iq)) < =borne) CYCLE61 IF(ABS(q(i, k, iq)) < borne) CYCLE 64 62 WRITE(msg1, '(s,"(",i0,",",i0,",",i0,") = ",ES12.4)')TRIM(isoName(ixt)), i, k, iq, q(i, k, iq) 65 63 CALL msg(msg1, modname) -
LMDZ6/branches/Amaury_dev/libf/dyn3d/lmdz_dynetat0.f90
r5224 r5229 12 12 !------------------------------------------------------------------------------- 13 13 USE lmdz_infotrac, ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName, & 14 new2oldH2O, newHNO3, oldHNO3 , getKey14 new2oldH2O, newHNO3, oldHNO3 15 15 USE lmdz_strings, ONLY: maxlen, msg, strStack, real2str, int2str 16 16 USE netcdf, ONLY: nf90_open, nf90_nowrite, nf90_inq_varid, nf90_close, nf90_get_var, nf90_noerr … … 28 28 USE lmdz_strings, ONLY: strIdx 29 29 USE ioipsl, ONLY: getin 30 USE iso_params_mod ! tnat_* and alpha_ideal_* 30 31 31 32 USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm … … 169 170 CALL msg(' !!! Beware: alpha_ideal put to 1 !!!', modname) 170 171 ELSE 171 IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) & 172 CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1) 172 SELECT CASE(isoName(iName)) 173 CASE('H216O'); tnat = tnat_H216O; alpha_ideal = alpha_ideal_H216O 174 CASE('H217O'); tnat = tnat_H217O; alpha_ideal = alpha_ideal_H217O 175 CASE('H218O'); tnat = tnat_H218O; alpha_ideal = alpha_ideal_H218O 176 CASE('HDO'); tnat = tnat_HDO; alpha_ideal = alpha_ideal_HDO 177 CASE('HTO'); tnat = tnat_HTO; alpha_ideal = alpha_ideal_HTO 178 CASE DEFAULT; CALL abort_gcm(TRIM(modname), 'unknown isotope "' // TRIM(isoName(iName)) // '" ; check tracer.def file', 1) 179 END SELECT 173 180 END IF 174 181 CALL msg('Missing tracer <' // TRIM(var) // '> => initialized with a simplified Rayleigh distillation law.', modname) -
LMDZ6/branches/Amaury_dev/libf/dyn3d_common/iso_verif_dyn.f90
r5224 r5229 1 function iso_verif_noNaN_nostop(x, err_msg) 2 IMPLICIT NONE 3 ! si x est NaN, on affiche message 4 ! d'erreur et return 1 si erreur 1 LOGICAL FUNCTION iso_verif_noNaN_nostop(x, err_msg) RESULT(lerr) 2 IMPLICIT NONE 3 ! If "x" is NaN, print an error message . 4 REAL, INTENT(IN) :: x 5 CHARACTER(LEN=*), INTENT(IN) :: err_msg 6 REAL, PARAMETER :: borne = 1e19 7 lerr = x > -borne .AND. x < borne 8 IF(.NOT.lerr) RETURN 9 WRITE(*,*) 'erreur detectee par iso_verif_nonNaN:' 10 WRITE(*,*) err_msg 11 WRITE(*,*) 'x=',x 12 END FUNCTION iso_verif_noNaN_nostop 5 13 6 ! input: 7 REAL :: x 8 CHARACTER(LEN = *) :: err_msg ! message d''erreur à afficher 9 10 ! output 11 REAL :: borne 12 parameter (borne = 1e19) 13 INTEGER :: iso_verif_noNaN_nostop 14 15 IF ((x>-borne).AND.(x<borne)) THEN 16 iso_verif_noNAN_nostop = 0 17 else 18 WRITE(*, *) 'erreur detectee par iso_verif_nonNaN:' 19 WRITE(*, *) err_msg 20 WRITE(*, *) 'x=', x 21 iso_verif_noNaN_nostop = 1 22 endif 23 24 RETURN 25 END FUNCTION iso_verif_nonan_nostop 26 27 function iso_verif_egalite_nostop & 28 (a, b, err_msg) 29 IMPLICIT NONE 30 ! compare a et b. Si pas egal, on affiche message 31 ! d'erreur et stoppe 32 ! pour egalite, on verifie erreur absolue et arreur relative 33 34 ! input: 35 REAL :: a, b 36 CHARACTER(LEN = *) :: err_msg ! message d''erreur à afficher 37 38 ! locals 39 REAL :: errmax ! erreur maximale en absolu. 40 REAL :: errmaxrel ! erreur maximale en relatif autorisée 41 parameter (errmax = 1e-8) 42 parameter (errmaxrel = 1e-3) 43 44 ! output 45 INTEGER :: iso_verif_egalite_nostop 46 47 iso_verif_egalite_nostop = 0 48 49 IF (abs(a - b)>errmax) THEN 50 IF (abs((a - b) / max(max(abs(b), abs(a)), 1e-18)) & 51 >errmaxrel) THEN 52 WRITE(*, *) 'erreur detectee par iso_verif_egalite:' 53 WRITE(*, *) err_msg 54 WRITE(*, *) 'a=', a 55 WRITE(*, *) 'b=', b 56 iso_verif_egalite_nostop = 1 57 endif 58 endif 59 60 RETURN 14 LOGICAL FUNCTION iso_verif_egalite_nostop(a, b, err_msg) RESULT(lerr) 15 IMPLICIT NONE 16 ! Compare "a" and "b". If a/=b, print an error message. 17 ! Both absolute and relative errors are checked for equality. 18 REAL, INTENT(IN) :: a, b 19 CHARACTER(LEN=*), INTENT(IN) :: err_msg 20 REAL, PARAMETER :: errmax = 1e-8, & ! max absolute error 21 errmaxrel = 1e-3 ! max relative error 22 lerr = ABS(a-b) > errmax 23 IF(.NOT.lerr) RETURN 24 lerr = ABS( (a-b) / MAX(MAX(ABS(b), ABS(a)),1e-18) ) > errmaxrel 25 IF(.NOT.lerr) RETURN 26 WRITE(*,*) 'erreur detectee par iso_verif_egalite:' 27 WRITE(*,*) err_msg 28 WRITE(*,*) 'a=',a 29 WRITE(*,*) 'b=',b 61 30 END FUNCTION iso_verif_egalite_nostop 62 31 63 32 64 function iso_verif_aberrant_nostop & 65 (x, iso, q, err_msg) 66 USE lmdz_infotrac, ONLY: isoName, getKey 33 LOGICAL FUNCTION iso_verif_aberrant_nostop(x, iso, q, err_msg) RESULT(lerr) 67 34 USE ioipsl, ONLY: getin 35 USE iso_params_mod, ONLY: tnat_HDO 68 36 69 37 IMPLICIT NONE 70 38 71 ! input: 72 REAL :: x, q 73 INTEGER :: iso ! 2=HDO, 1=O18 74 CHARACTER(LEN = *) :: err_msg ! message d''erreur à afficher 39 REAL, INTENT(IN) :: x, q 40 INTEGER, INTENT(IN) :: iso ! 2=HDO, 1=O18 41 CHARACTER(LEN = *), INTENT(IN) :: err_msg 75 42 76 ! locals 77 REAL :: qmin, deltaD 78 REAL :: deltaDmax, deltaDmin, tnat 79 parameter (qmin = 1e-11) 80 parameter (deltaDmax = 200.0, deltaDmin = -999.9) 81 LOGICAL, SAVE :: ltnat1 82 LOGICAL, SAVE :: lFirst = .TRUE. 83 84 ! output 85 INTEGER :: iso_verif_aberrant_nostop 86 87 IF(lFirst) THEN 88 ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1) 89 lFirst = .FALSE. 90 END IF 91 iso_verif_aberrant_nostop = 0 92 93 ! verifier que HDO est raisonable 94 IF (q>qmin) THEN 95 IF(ltnat1) THEN 96 tnat = 1.0 97 ELSE IF(getKey('tnat', tnat, isoName(iso))) THEN 98 err_msg = 'Missing isotopic parameter "tnat"' 99 iso_verif_aberrant_nostop = 1 100 RETURN 101 END IF 102 deltaD = (x / q / tnat - 1) * 1000 103 IF ((deltaD>deltaDmax).OR.(deltaD<deltaDmin)) THEN 104 WRITE(*, *) 'erreur detectee par iso_verif_aberrant:' 105 WRITE(*, *) err_msg 106 WRITE(*, *) 'q=', q 107 WRITE(*, *) 'deltaD=', deltaD 108 WRITE(*, *) 'iso=', iso 109 iso_verif_aberrant_nostop = 1 110 endif !if ((deltaD.gt.deltaDmax).OR.(deltaD.lt.deltaDmin)) THEN 111 endif !if (q(i,k,iq).gt.qmin) THEN 112 RETURN 43 REAL, PARAMETER :: qmin = 1e-11, & 44 deltaDmax = 200.0, & 45 deltaDmin =-999.9 46 LOGICAL :: ltnat1 47 LOGICAL, SAVE :: lFirst=.TRUE. 48 REAL, SAVE :: tnat 49 REAL :: deltaD 50 IF(lFirst) THEN 51 ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1) 52 tnat = tnat_HDO; IF(ltnat1) tnat = 1.0 53 lFirst = .FALSE. 54 END IF 55 lerr = q > qmin 56 IF(.NOT.lerr) RETURN 57 deltaD = (x / q /tnat - 1.) * 1000. 58 lerr = deltaD > deltaDmax .OR. deltaD < deltaDmin 59 IF(.NOT.lerr) RETURN 60 WRITE(*,*) 'erreur detectee par iso_verif_aberrant:' 61 WRITE(*,*) err_msg 62 WRITE(*,*) 'q=',q 63 WRITE(*,*) 'deltaD=',deltaD 64 WRITE(*,*) 'iso=',iso 113 65 END FUNCTION iso_verif_aberrant_nostop 114 -
LMDZ6/branches/Amaury_dev/libf/dyn3dmem/check_isotopes_loc.F90
r5223 r5229 3 3 USE lmdz_strings, ONLY: maxlen, msg, strIdx, strStack, int2str, real2str 4 4 USE lmdz_infotrac, ONLY: nqtot, niso, nphas, isotope, isoCheck, iqIsoPha, isoSelect, & 5 ntiso, iH2O, nzone, tracers, isoName, itZonIso, getKey 5 ntiso, iH2O, nzone, tracers, isoName, itZonIso 6 USE iso_params_mod, ONLY: tnat_H216O, tnat_H217O, tnat_H218O, tnat_HDO, tnat_HTO 6 7 7 8 … … 14 15 CHARACTER(LEN=maxlen) :: modname, msg1, nm(2) 15 16 INTEGER :: ixt, ipha, k, i, iq, iiso, izon, ieau, iqeau, iqpar 16 INTEGER, ALLOCATABLE :: ix(:)17 INTEGER, ALLOCATABLE :: ix(:) 17 18 REAL, ALLOCATABLE, SAVE :: tnat(:) !--- OpenMP shared variable 18 REAL 19 REAL :: xtractot, xiiso, deltaD, q1, q2 19 20 REAL, PARAMETER :: borne = 1e19, & 20 21 errmax = 1e-8, & !--- Max. absolute error … … 38 39 ltnat1 = .TRUE.; CALL getin('tnateq1', ltnat1) 39 40 ALLOCATE(tnat(niso)) 40 iso_eau = strIdx(isoName,'H216O') 41 iso_O17 = strIdx(isoName,'H217O') 42 iso_O18 = strIdx(isoName,'H218O') 43 iso_HDO = strIdx(isoName,'HDO') 44 iso_HTO = strIdx(isoName,'HTO') 45 IF(ltnat1) THEN 46 tnat(:)=1.0 47 ELSE 48 IF(getKey('tnat', tnat)) CALL abort_gcm(modname, 'missing isotopic parameter', 1) 49 END IF 41 iso_eau = strIdx(isoName,'H216O'); IF(iso_eau /= 0) tnat(iso_eau) = tnat_H216O 42 iso_O17 = strIdx(isoName,'H217O'); IF(iso_O17 /= 0) tnat(iso_O17) = tnat_H217O 43 iso_O18 = strIdx(isoName,'H218O'); IF(iso_O18 /= 0) tnat(iso_O18) = tnat_H218O 44 iso_HDO = strIdx(isoName,'HDO'); IF(iso_HDO /= 0) tnat(iso_HDO) = tnat_HDO 45 iso_HTO = strIdx(isoName,'HTO'); IF(iso_HTO /= 0) tnat(iso_HTO) = tnat_HTO 46 IF(ltnat1) tnat(:) = 1.0 50 47 !$OMP END MASTER 51 48 !$OMP BARRIER … … 62 59 DO k = 1, llm 63 60 DO i = ijb, ije 64 IF(ABS(q(i,k,iq)) < =borne) CYCLE61 IF(ABS(q(i,k,iq)) < borne) CYCLE 65 62 WRITE(msg1,'(s,"(",i0,",",i0,",",i0,") = ",ES12.4)')TRIM(isoName(ixt)),i,k,iq,q(i,k,iq) 66 63 CALL msg(msg1, modname) -
LMDZ6/branches/Amaury_dev/libf/dyn3dmem/dynetat0_loc.f90
r5223 r5229 8 8 USE parallel_lmdz 9 9 USE lmdz_infotrac, ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName, & 10 new2oldH2O, newHNO3, oldHNO3 , getKey10 new2oldH2O, newHNO3, oldHNO3 11 11 USE lmdz_strings, ONLY: maxlen, msg, strStack, real2str, int2str, strIdx 12 12 USE netcdf, ONLY: nf90_open, nf90_nowrite, nf90_inquire_dimension, nf90_inq_varid, & … … 23 23 USE lmdz_iniprint, ONLY: lunout, prt_level 24 24 USE lmdz_comgeom 25 USE iso_params_mod ! tnat_* and alpha_ideal_* 25 26 26 27 USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm … … 188 189 CALL msg(' !!! Beware: alpha_ideal put to 1 !!!', modname) 189 190 ELSE 190 IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) & 191 CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1) 191 SELECT CASE(isoName(iName)) 192 CASE('H216O'); tnat = tnat_H216O; alpha_ideal = alpha_ideal_H216O 193 CASE('H217O'); tnat = tnat_H217O; alpha_ideal = alpha_ideal_H217O 194 CASE('H218O'); tnat = tnat_H218O; alpha_ideal = alpha_ideal_H218O 195 CASE('HDO'); tnat = tnat_HDO; alpha_ideal = alpha_ideal_HDO 196 CASE('HTO'); tnat = tnat_HTO; alpha_ideal = alpha_ideal_HTO 197 CASE DEFAULT; CALL abort_gcm(TRIM(modname), 'unknown isotope "' // TRIM(isoName(iName)) // '" ; check tracer.def file', 1) 198 END SELECT 192 199 END IF 193 200 CALL msg('Missing tracer <' // TRIM(var) // '> => initialized with a simplified Rayleigh distillation law.', modname) -
LMDZ6/branches/Amaury_dev/libf/dyn3dmem/iniacademic_loc.F90
r5223 r5229 1 ! $Id: iniacademic.F90 1625 2012-05-09 13:14:48Z lguez $2 3 1 SUBROUTINE iniacademic_loc(vcov, ucov, teta, q, masse, ps, phis, time_0) 4 2 5 3 USE lmdz_filtreg, ONLY: inifilr 6 USE lmdz_infotrac, ONLY: nqtot, niso, iqIsoPha, tracers, getKey,isoName, addPhase4 USE lmdz_infotrac, ONLY: nqtot, niso, iqIsoPha, tracers, isoName, addPhase 7 5 USE control_mod, ONLY: day_step, planet_type 8 6 USE exner_hyb_m, ONLY: exner_hyb … … 21 19 USE lmdz_academic, ONLY: tetarappel, knewt_t, kfrict, knewt_g, clat4 22 20 USE lmdz_comgeom 21 USE iso_params_mod ! tnat_* and alpha_ideal_* 23 22 24 23 ! Author: Frederic Hourdin original: 15/01/93 … … 322 321 WRITE(lunout, *) 'In '//TRIM(modname)//': !!! Beware: alpha_ideal put to 1 !!!' 323 322 ELSE 324 IF(getKey('tnat', tnat, isoName(iName)) .OR. getKey('alpha', alpha_ideal, isoName(iName))) & 325 CALL abort_gcm(TRIM(modname), 'missing isotopic parameters', 1) 323 SELECT CASE(isoName(iName)) 324 CASE('H216O'); tnat = tnat_H216O; alpha_ideal = alpha_ideal_H216O 325 CASE('H217O'); tnat = tnat_H217O; alpha_ideal = alpha_ideal_H217O 326 CASE('H218O'); tnat = tnat_H218O; alpha_ideal = alpha_ideal_H218O 327 CASE('HDO'); tnat = tnat_HDO; alpha_ideal = alpha_ideal_HDO 328 CASE('HTO'); tnat = tnat_HTO; alpha_ideal = alpha_ideal_HTO 329 CASE DEFAULT 330 CALL abort_gcm(TRIM(modname),'unknown isotope "'//TRIM(isoName(iName))//'" ; check tracer.def file',1) 331 END SELECT 326 332 END IF 327 333 q(ijb_u:ije_u,:,iq) = q(ijb_u:ije_u,:,iqParent)*tnat*(q(ijb_u:ije_u,:,iqParent)/30.e-3)**(alpha_ideal-1.) -
LMDZ6/branches/Amaury_dev/libf/phylmdiso/isotopes_mod.F90
r5223 r5229 4 4 MODULE isotopes_mod 5 5 USE lmdz_strings, ONLY: msg, real2str, int2str, bool2str, maxlen, strIdx, strStack 6 USE infotrac_phy, ONLY: isoName 6 USE infotrac_phy, ONLY: isoName, niso, ntiso 7 USE iso_params_mod 7 8 IMPLICIT NONE 8 9 INTERFACE get_in; MODULE PROCEDURE getinp_s, getinp_i, getinp_r, getinp_l; END INTERFACE get_in … … 10 11 !--- Contains all isotopic variables + their initialization 11 12 !--- Isotopes-specific routines are in isotopes_routines_mod to avoid circular dependencies with isotopes_verif_mod. 13 14 !--- Negligible lower thresholds: no need to check for absurd values under these lower limits 15 REAL, PARAMETER :: & 16 ridicule = 1e-12, & ! For mixing ratios 17 ridicule_rain = 1e-8, & ! For rain fluxes (rain, zrfl...) in kg/s <-> 1e-3 mm/day 18 ridicule_evap = ridicule_rain*1e-2, & ! For evaporations in kg/s <-> 1e-3 mm/day 19 ridicule_qsol = ridicule_rain, & ! For qsol in kg <-> 1e-8 kg 20 ridicule_snow = ridicule_qsol ! For snow in kg <-> 1e-8 kg 21 REAL, PARAMETER :: expb_max = 30.0 22 23 !--- Fractionation coefficients for H217O 24 REAL, PARAMETER :: fac_coeff_eq17_liq = 0.529, & 25 fac_coeff_eq17_ice = 0.529 26 27 !--- H218O reference 28 REAL, PARAMETER :: fac_enrichoce18 = 0.0005, alpha_liq_sol_O18 = 1.00291, & 29 talph1_O18 = 1137., talps1_O18 = 11.839, tkcin0_O18 = 0.006, & 30 talph2_O18 = -0.4156, talps2_O18 = -0.028244, tkcin1_O18 = 0.000285, & 31 talph3_O18 = -2.0667E-3, tdifrel_O18 = 1./0.9723, tkcin2_O18 = 0.00082 32 33 !--- Parameters that do not depend on the nature of water isotopes: 34 REAL, PARAMETER :: pxtmelt= 273.15, & !--- temperature at which ice formation starts 35 pxtice = 273.15 - 10.0, & !--- temperature at which all condensate is ice: 36 pxtmin = 273.15 - 120.0, & !--- computation done only under -120°C 37 pxtmax = 273.15 + 60.0, & !--- computation done only over +60°C 38 tdifexp= 0.58, & !--- a constant for alpha_eff for equilibrium below cloud base: 39 tv0cin = 7.0, & !--- wind threshold (m/s) for smooth/rough regime (Merlivat and Jouzel 1979) 40 musi = 1.0, & !--- facteurs lambda et mu dans Si=musi-lambda*T 41 Kd = 2.5e-9, & !--- diffusion in soil ; m2/s 42 rh_cste_surf_cond = 0.6, & !--- cste_surf_cond case: rhs and/or Ts set to constants 43 T_cste_surf_cond = 288.0 12 44 13 45 !--- Isotopes indices (in [1,niso] ; non-existing => 0 index) … … 88 120 !--- Vectors of length "niso" 89 121 REAL, ALLOCATABLE, DIMENSION(:), SAVE :: & 90 tnat, toce, tcorr, tdifrel91 !$OMP THREADPRIVATE( tnat, toce, tcorr, tdifrel)122 alpha, tnat, toce, tcorr, tdifrel 123 !$OMP THREADPRIVATE(alpha, tnat, toce, tcorr, tdifrel) 92 124 REAL, ALLOCATABLE, DIMENSION(:), SAVE :: & 93 125 talph1, talph2, talph3, talps1, talps2 … … 99 131 alpha_liq_sol, Rdefault, Rmethox 100 132 !$OMP THREADPRIVATE(alpha_liq_sol, Rdefault, Rmethox) 101 ! REAL, SAVE :: fac_coeff_eq17_liq, fac_coeff_eq17_ice102 !!$OMP THREADPRIVATE(fac_coeff_eq17_liq, fac_coeff_eq17_ice)103 104 !--- H2[18]O reference105 REAL, PARAMETER :: fac_enrichoce18=0.0005106 REAL, PARAMETER :: alpha_liq_sol_O18=1.00291107 REAL, PARAMETER :: talph1_O18=1137.108 REAL, PARAMETER :: talph2_O18=-0.4156109 REAL, PARAMETER :: talph3_O18=-2.0667E-3110 REAL, PARAMETER :: talps1_O18=11.839111 REAL, PARAMETER :: talps2_O18=-0.028244112 REAL, PARAMETER :: tdifrel_O18=1./0.9723113 REAL, PARAMETER :: tkcin0_O18=0.006114 REAL, PARAMETER :: tkcin1_O18=0.000285115 REAL, PARAMETER :: tkcin2_O18=0.00082116 REAL, PARAMETER :: fac_coeff_eq17_liq=0.529117 REAL, PARAMETER :: fac_coeff_eq17_ice=0.529118 119 !---- Parameters that do not depend on the nature of water isotopes:120 REAL, PARAMETER :: pxtmelt = 273.15 ! temperature at which ice formation starts121 REAL, PARAMETER :: pxtice = 273.15-10.0 ! -- temperature at which all condensate is ice:122 REAL, PARAMETER :: pxtmin = 273.15 - 120.0 ! On ne calcule qu'au dessus de -120°C123 REAL, PARAMETER :: pxtmax = 273.15 + 60.0 ! On ne calcule qu'au dessus de +60°C124 REAL, PARAMETER :: tdifexp = 0.58 ! -- a constant for alpha_eff for equilibrium below cloud base:125 REAL, PARAMETER :: tv0cin = 7.0 ! wind threshold (m/s) for smooth/rough regime (Merlivat and Jouzel 1979)126 REAL, PARAMETER :: musi=1.0 ! facteurs lambda et mu dans Si=musi-lambda*T127 REAL, PARAMETER :: Kd=2.5e-9 ! m2/s ! diffusion dans le sol128 REAL, PARAMETER :: rh_cste_surf_cond = 0.6 ! cas où cste_surf_cond: on met rhs ou/et Ts cste pour voir129 REAL, PARAMETER :: T_cste_surf_cond = 288.0130 131 132 !--- Negligible lower thresholds: no need to check for absurd values under these lower limits133 REAL, PARAMETER :: &134 ridicule = 1e-12, & ! For mixing ratios135 ridicule_rain = 1e-8, & ! For rain fluxes (rain, zrfl...) in kg/s <-> 1e-3 mm/day136 ridicule_evap = ridicule_rain*1e-2, & ! For evaporations in kg/s <-> 1e-3 mm/day137 ridicule_qsol = ridicule_rain, & ! For qsol in kg <-> 1e-8 kg138 ridicule_snow = ridicule_qsol ! For snow in kg <-> 1e-8 kg139 REAL, PARAMETER :: expb_max = 30.0140 133 141 134 !--- Specific to HTO: … … 154 147 155 148 SUBROUTINE iso_init() 156 USE infotrac_phy, ONLY: ntiso, niso, getKey157 USE lmdz_strings, ONLY: maxlen158 149 IMPLICIT NONE 159 150 160 151 !=== Local variables: 161 INTEGER :: ixt 152 INTEGER :: ixt, is 162 153 LOGICAL :: ltnat1 163 154 CHARACTER(LEN=maxlen) :: modname, sxt … … 184 175 CALL msg('64: niso = '//TRIM(int2str(niso)), modname) 185 176 186 !--- Init de ntracisoOR: on ecrasera en cas de traceurs de tagging isotopiques187 ! (nzone>0) si complications avec ORCHIDEE188 ntracisoOR = ntiso189 190 !--- Type of water isotopes:191 iso_eau = strIdx(isoName, 'H216O'); CALL msg('iso_eau='//int2str(iso_eau), modname)192 iso_HDO = strIdx(isoName, 'HDO'); CALL msg('iso_HDO='//int2str(iso_HDO), modname)193 iso_O18 = strIdx(isoName, 'H218O'); CALL msg('iso_O18='//int2str(iso_O18), modname)194 iso_O17 = strIdx(isoName, 'H217O'); CALL msg('iso_O17='//int2str(iso_O17), modname)195 iso_HTO = strIdx(isoName, 'HTO'); CALL msg('iso_HTO='//int2str(iso_HTO), modname)196 197 !--- Initialiaation: reading the isotopic parameters.198 CALL get_in('lambda', lambda_sursat, 0.004)199 CALL get_in('thumxt1', thumxt1, 0.75*1.2)200 CALL get_in('ntot', ntot, 20, .FALSE.)201 CALL get_in('h_land_ice', h_land_ice, 20., .FALSE.)202 CALL get_in('P_veg', P_veg, 1.0, .FALSE.)203 CALL get_in('bidouille_anti_divergence', bidouille_anti_divergence, .FALSE.)204 CALL get_in('essai_convergence', essai_convergence, .FALSE.)205 CALL get_in('initialisation_iso', initialisation_iso, 0)206 207 ! IF(nzone>0 .AND. initialisation_iso==0) &208 ! CALL get_in('initialisation_isotrac',initialisation_isotrac)209 CALL get_in('modif_sst', modif_sst, 0)210 CALL get_in('deltaTtest', deltaTtest, 0.0) !--- For modif_sst>=1211 CALL get_in('deltaTtestpoles',deltaTtestpoles, 0.0) !--- For modif_sst>=2212 CALL get_in( 'sstlatcrit', sstlatcrit, 30.0) !--- For modif_sst>=3213 CALL get_in('dsstlatcrit', dsstlatcrit, 0.0) !--- For modif_sst>=3177 !--- Init de ntracisoOR: on ecrasera en cas de traceurs de tagging isotopiques 178 ! (nzone>0) si complications avec ORCHIDEE 179 ntracisoOR = ntiso 180 181 !--- 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) 187 188 !--- 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) 197 198 ! 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 214 205 #ifdef ISOVERIF 215 CALL msg('iso_init 270: sstlatcrit='//real2str( sstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=2216 CALL msg('iso_init 279: dsstlatcrit='//real2str(dsstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=3217 IF(modif_sst >= 2 .AND. sstlatcrit < 0.0) STOP206 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 208 IF(modif_sst >= 2 .AND. sstlatcrit < 0.0) STOP 218 209 #endif 219 210 220 CALL get_in('modif_sic', modif_sic, 0) 221 IF(modif_sic >= 1) & 222 CALL get_in('deltasic', deltasic, 0.1) 223 224 CALL get_in('albedo_prescrit', albedo_prescrit, 0) 225 IF(albedo_prescrit == 1) THEN 226 CALL get_in('lon_min_albedo', lon_min_albedo, -200.) 227 CALL get_in('lon_max_albedo', lon_max_albedo, 200.) 228 CALL get_in('lat_min_albedo', lat_min_albedo, -100.) 229 CALL get_in('lat_max_albedo', lat_max_albedo, 100.) 230 END IF 231 CALL get_in('deltaP_BL', deltaP_BL, 10.0) 232 CALL get_in('ruissellement_pluie', ruissellement_pluie, 0) 233 CALL get_in('alphak_stewart', alphak_stewart, 1) 234 CALL get_in('tdifexp_sol', tdifexp_sol, 0.67) 235 CALL get_in('calendrier_guide', calendrier_guide, 0) 236 CALL get_in('cste_surf_cond', cste_surf_cond, 0) 237 CALL get_in('mixlen', mixlen, 35.0) 238 CALL get_in('evap_cont_cste', evap_cont_cste, 0) 239 CALL get_in('deltaO18_evap_cont', deltaO18_evap_cont,0.0) 240 CALL get_in('d_evap_cont', d_evap_cont, 0.0) 241 CALL get_in('nudge_qsol', nudge_qsol, 0) 242 CALL get_in('region_nudge_qsol', region_nudge_qsol, 1) 243 nlevmaxO17 = 50 244 CALL msg('nlevmaxO17='//TRIM(int2str(nlevmaxO17))) 245 CALL get_in('no_pce', no_pce, 0) 246 CALL get_in('A_satlim', A_satlim, 1.0) 247 CALL get_in('ok_restrict_A_satlim', ok_restrict_A_satlim, 0) 211 CALL get_in('modif_sic', modif_sic, 0) 212 IF(modif_sic >= 1) & 213 CALL get_in('deltasic', deltasic, 0.1) 214 215 CALL get_in('albedo_prescrit', albedo_prescrit, 0) 216 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) 235 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) 248 240 #ifdef ISOVERIF 249 CALL msg(' 315: A_satlim='//real2str(A_satlim), modname, A_satlim > 1.0)250 IF(A_satlim > 1.0) STOP241 CALL msg(' 315: A_satlim='//real2str(A_satlim), modname, A_satlim > 1.0) 242 IF(A_satlim > 1.0) STOP 251 243 #endif 252 ! CALL get_in('slope_limiterxy', slope_limiterxy, 2.0) 253 ! CALL get_in('slope_limiterz', slope_limiterz, 2.0) 254 CALL get_in('modif_ratqs', modif_ratqs, 0) 255 CALL get_in('Pcrit_ratqs', Pcrit_ratqs, 500.0) 256 CALL get_in('ratqsbasnew', ratqsbasnew, 0.05) 257 CALL get_in('fac_modif_evaoce', fac_modif_evaoce, 1.0) 258 CALL get_in('ok_bidouille_wake', ok_bidouille_wake, 0) 259 ! si oui, la temperature de cond est celle de l'environnement, pour eviter 260 ! bugs quand temperature dans ascendances convs est mal calculee 261 CALL get_in('cond_temp_env', cond_temp_env, .FALSE.) 262 IF(ANY(isoName == 'HTO')) & 263 CALL get_in('ok_prod_nucl_tritium', ok_prod_nucl_tritium, .FALSE., .FALSE.) 264 CALL get_in('tnateq1', ltnat1, .TRUE.) 265 266 ! Ocean composition 267 CALL get_in('deltaO18_oce', deltaO18_oce, 0.0) 268 269 CALL msg('iso_O18, iso_HDO, iso_eau = '//TRIM(strStack(int2str([iso_O18, iso_HDO, iso_eau]))), modname) 270 271 !-------------------------------------------------------------- 272 ! Isotope fractionation factors and a few isotopic constants 273 !-------------------------------------------------------------- 274 ALLOCATE(tkcin0(niso)) 275 ALLOCATE(tkcin1(niso)) 276 ALLOCATE(tkcin2(niso)) 277 ALLOCATE(tnat(niso)) 278 ALLOCATE(tdifrel(niso)) 279 ALLOCATE(toce(niso)) 280 ALLOCATE(tcorr(niso)) 281 ALLOCATE(talph1(niso)) 282 ALLOCATE(talph2(niso)) 283 ALLOCATE(talph3(niso)) 284 ALLOCATE(talps1(niso)) 285 ALLOCATE(talps2(niso)) 286 ALLOCATE(alpha_liq_sol(niso)) 287 ALLOCATE(Rdefault(niso)) 288 ALLOCATE(Rmethox(niso)) 289 290 DO ixt=1,niso 291 IF (ixt.EQ.iso_HTO) then ! Tritium 292 tkcin0(ixt) = 0.01056 293 tkcin1(ixt) = 0.0005016 294 tkcin2(ixt) = 0.0014432 295 tnat(ixt) = 0.0; IF(ltnat1) tnat(ixt)=1 296 toce(ixt)=4.0E-19 ! rapport T/H = 0.2 TU Dreisigacker and Roether 1978 297 tcorr(ixt)=1. 298 tdifrel(ixt)=1./0.968 299 talph1(ixt)=46480. 300 talph2(ixt)=-103.87 301 talph3(ixt)=0. 302 talps1(ixt)=46480. 303 talps2(ixt)=-103.87 304 alpha_liq_sol(ixt)=1. 305 Rmethox(ixt)=0.0 306 endif 307 IF (ixt.EQ.iso_O17) then ! O17 308 pente_MWL=0.528 309 tdifrel(ixt)=1./0.98555 ! valeur utilisée en 1D et dans modèle de LdG ! tdifrel(ixt)=1./0.985452 ! donné par Amaelle 310 fac_kcin= (tdifrel(ixt)-1.0)/(tdifrel_O18-1.0) ! fac_kcin=0.5145 ! donné par Amaelle 311 tkcin0(ixt) = tkcin0_O18*fac_kcin 312 tkcin1(ixt) = tkcin1_O18*fac_kcin 313 tkcin2(ixt) = tkcin2_O18*fac_kcin 314 tnat(ixt)=0.004/100. ! O17 représente 0.004% de l'oxygène 315 IF(ltnat1) tnat(ixt)=1 316 toce(ixt)=tnat(ixt)*(1.0+deltaO18_oce/1000.0)**pente_MWL 317 tcorr(ixt)=1.0+fac_enrichoce18*pente_MWL ! donné par Amaelle 318 talph1(ixt)=talph1_O18 319 talph2(ixt)=talph2_O18 320 talph3(ixt)=talph3_O18 321 talps1(ixt)=talps1_O18 322 talps2(ixt)=talps2_O18 323 alpha_liq_sol(ixt)=(alpha_liq_sol_O18)**fac_coeff_eq17_liq 324 Rdefault(ixt)=tnat(ixt)*(-3.15/1000.0+1.0) 325 Rmethox(ixt)=(230./1000.+1.)*tnat(ixt) !Zahn et al 2006 326 endif 327 IF (ixt.EQ.iso_O18) then ! Oxygene18 328 tkcin0(ixt) = tkcin0_O18 329 tkcin1(ixt) = tkcin1_O18 330 tkcin2(ixt) = tkcin2_O18 331 tnat(ixt)=2005.2E-6; IF(ltnat1) tnat(ixt)=1 332 toce(ixt)=tnat(ixt)*(1.0+deltaO18_oce/1000.0) 333 tcorr(ixt)=1.0+fac_enrichoce18 334 tdifrel(ixt)=tdifrel_O18 335 talph1(ixt)=talph1_O18 336 talph2(ixt)=talph2_O18 337 talph3(ixt)=talph3_O18 338 talps1(ixt)=talps1_O18 339 talps2(ixt)=talps2_O18 340 alpha_liq_sol(ixt)=alpha_liq_sol_O18 341 Rdefault(ixt)=tnat(ixt)*(-6.0/1000.0+1.0) 342 Rmethox(ixt)=(130./1000.+1.)*tnat(ixt) !Zahn et al 2006 343 endif 344 IF (ixt.EQ.iso_HDO) then ! Deuterium 345 pente_MWL=8.0 346 tdifrel(ixt)=1./0.9755 ! fac_kcin=0.88 347 fac_kcin= (tdifrel(ixt)-1)/(tdifrel_O18-1) 348 tkcin0(ixt) = tkcin0_O18*fac_kcin 349 tkcin1(ixt) = tkcin1_O18*fac_kcin 350 tkcin2(ixt) = tkcin2_O18*fac_kcin 351 tnat(ixt)=155.76E-6; IF(ltnat1) tnat(ixt)=1 352 toce(ixt)=tnat(ixt)*(1.0+pente_MWL*deltaO18_oce/1000.0) 353 tcorr(ixt)=1.0+fac_enrichoce18*pente_MWL 354 talph1(ixt)=24844. 355 talph2(ixt)=-76.248 356 talph3(ixt)=52.612E-3 357 talps1(ixt)=16288. 358 talps2(ixt)=-0.0934 359 !ZXalpha_liq_sol=1.0192 ! Weston, Ralph, 1955 360 alpha_liq_sol(ixt)=1.0212 361 ! valeur de Lehmann & Siegenthaler, 1991, Journal of 362 ! Glaciology, vol 37, p 23 363 Rdefault(ixt)=tnat(ixt)*((-6.0*pente_MWL+10.0)/1000.0+1.0) 364 Rmethox(ixt)=tnat(ixt)*(-25.0/1000.+1.) ! Zahn et al 2006 365 endif 366 IF (ixt.EQ.iso_eau) then ! Oxygene16 367 tkcin0(ixt) = 0.0 368 tkcin1(ixt) = 0.0 369 tkcin2(ixt) = 0.0 370 tnat(ixt)=1. 371 toce(ixt)=tnat(ixt) 372 tcorr(ixt)=1.0 373 tdifrel(ixt)=1. 374 talph1(ixt)=0. 375 talph2(ixt)=0. 376 talph3(ixt)=0. 377 talps1(ixt)=0. 378 talph3(ixt)=0. 379 alpha_liq_sol(ixt)=1. 380 Rdefault(ixt)=tnat(ixt)*1.0 381 Rmethox(ixt)=1.0 382 endif 383 enddo ! ixt=1,niso 384 385 IF(.NOT.Rdefault_smow) THEN 386 Rdefault(:) = 0.0 387 IF (iso_eau.gt.0) Rdefault(iso_eau) = 1.0 ! correction Camille 30 mars 2023 388 ENDIF 389 WRITE(*,*) 'Rdefault=',Rdefault 390 WRITE(*,*) 'toce=',toce 391 392 !--- Sensitivity test: no kinetic effect in sfc evaporation 393 IF(ok_nocinsfc) THEN 394 tkcin0(1:niso) = 0.0 395 tkcin1(1:niso) = 0.0 396 tkcin2(1:niso) = 0.0 397 END IF 398 399 CALL msg('285: verif initialisation:', modname) 400 DO ixt=1,niso 401 sxt=int2str(ixt) 402 CALL msg(' * isoName('//TRIM(sxt)//') = <'//TRIM(isoName(ixt))//'>', modname) 403 CALL msg( ' tnat('//TRIM(sxt)//') = '//TRIM(real2str(tnat(ixt))), modname) 404 ! CALL msg(' alpha_liq_sol('//TRIM(sxt)//') = '//TRIM(real2str(alpha_liq_sol(ixt))), modname) 405 ! CALL msg( ' tkcin0('//TRIM(sxt)//') = '//TRIM(real2str(tkcin0(ixt))), modname) 406 ! CALL msg( ' tdifrel('//TRIM(sxt)//') = '//TRIM(real2str(tdifrel(ixt))), modname) 407 END DO 408 CALL msg('69: lambda = '//TRIM(real2str(lambda_sursat)), modname) 409 CALL msg('69: thumxt1 = '//TRIM(real2str(thumxt1)), modname) 410 CALL msg('69: h_land_ice = '//TRIM(real2str(h_land_ice)), modname) 411 CALL msg('69: P_veg = '//TRIM(real2str(P_veg)), modname) 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) 251 ! si oui, la temperature de cond est celle de l'environnement, pour eviter 252 ! bugs quand temperature dans ascendances convs est mal calculee 253 CALL get_in('cond_temp_env', cond_temp_env, .FALSE.) 254 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) 259 260 !-------------------------------------------------------------- 261 ! Parameters that depend on the nature of water isotopes: 262 !-------------------------------------------------------------- 263 ALLOCATE(tnat (niso), talph1(niso), talps1(niso), tkcin0(niso), tdifrel (niso), alpha (niso)) 264 ALLOCATE(toce (niso), talph2(niso), talps2(niso), tkcin1(niso), Rdefault(niso), alpha_liq_sol(niso)) 265 ALLOCATE(tcorr(niso), talph3(niso), tkcin2(niso), Rmethox (niso)) 266 267 !=== H216O 268 is = iso_eau 269 IF(is /= 0) THEN 270 tdifrel (is) = 1.0 271 alpha (is) = alpha_ideal_H216O 272 tnat (is) = tnat_H216O; IF(ltnat1) tnat(is) = 1.0 273 toce (is) = tnat(is) 274 tcorr (is) = 1.0 275 talph1 (is) = 0.0; talps1(is) = 0.0; tkcin0(is) = 0.0 276 talph2 (is) = 0.0; talps2(is) = 0.0; tkcin1(is) = 0.0 277 talph3 (is) = 0.0; tkcin2(is) = 0.0 278 Rdefault(is) = tnat(is)*1.0 279 Rmethox (is) = 1.0 280 alpha_liq_sol(is) = 1.0 281 END IF 282 283 !=== H217O 284 is = iso_O17 285 IF(is /= 0) THEN; pente_MWL = 0.528 286 tdifrel (is) = 1./0.98555 ! used in 1D and in LdG model ; tdifrel=1./0.985452: from Amaelle 287 alpha (is) = alpha_ideal_H217O 288 tnat (is) = tnat_H217O; IF(ltnat1) tnat(is) = 1.0 289 toce (is) = tnat(is)*(1.0+deltaO18_oce/1000.0)**pente_MWL 290 tcorr (is) = 1.0+fac_enrichoce18*pente_MWL 291 fac_kcin = (tdifrel(is)-1.0)/(tdifrel_O18-1.0) ! fac_kcin=0.5145: from Amaelle 292 talph1 (is) = talph1_O18; talps1(is) = talps1_O18; tkcin0(is) = tkcin0_O18*fac_kcin 293 talph2 (is) = talph2_O18; talps2(is) = talps2_O18; tkcin1(is) = tkcin1_O18*fac_kcin 294 talph3 (is) = talph3_O18; tkcin2(is) = tkcin2_O18*fac_kcin 295 Rdefault(is) = tnat(is)*(1.0-3.15/1000.) 296 Rmethox (is) = tnat(is)*(1.0+230./1000.) 297 alpha_liq_sol(is) = alpha_liq_sol_O18**fac_coeff_eq17_liq 298 END IF 299 300 !=== H218O 301 is = iso_O18 302 IF(is /= 0) THEN 303 tdifrel (is) = tdifrel_O18 304 alpha (is) = alpha_ideal_H218O 305 tnat (is) = tnat_H218O; IF(ltnat1) tnat(is) = 1.0 306 toce (is) = tnat(is)*(1.0+deltaO18_oce/1000.0) 307 tcorr (is) = 1.0+fac_enrichoce18 308 talph1 (is) = talph1_O18; talps1(is) = talps1_O18; tkcin0(is) = tkcin0_O18 309 talph2 (is) = talph2_O18; talps2(is) = talps2_O18; tkcin1(is) = tkcin1_O18 310 talph3 (is) = talph3_O18; tkcin2(is) = tkcin2_O18 311 Rdefault(is) = tnat(is)*(1.0-6.00/1000.) 312 Rmethox (is) = tnat(is)*(1.0+130./1000.) ! Zahn & al. 2006 313 alpha_liq_sol(is) = alpha_liq_sol_O18 314 END IF 315 316 !=== HDO 317 is = iso_HDO 318 IF(is /= 0) THEN; pente_MWL = 8.0 319 tdifrel (is) = 1./0.9755 ! fac_kcin=0.88 320 alpha (is) = alpha_ideal_HDO 321 tnat (is) = tnat_HDO; IF(ltnat1) tnat(is) = 1.0 322 toce (is) = tnat(is)*(1.0+deltaO18_oce/1000.0*pente_MWL) 323 tcorr (is) = 1.0+fac_enrichoce18*pente_MWL 324 fac_kcin = (tdifrel(is)-1.0)/(tdifrel_O18-1.0) 325 talph1 (is) = 24844.; talps1(is) = 16288.; tkcin0(is) = tkcin0_O18*fac_kcin 326 talph2 (is) = -76.248; talps2(is) = -0.0934; tkcin1(is) = tkcin1_O18*fac_kcin 327 talph3 (is) = 52.612E-3; tkcin2(is) = tkcin2_O18*fac_kcin 328 Rdefault(is) = tnat(is)*(1.0+(10.0-6.0*pente_MWL)/1000.) 329 Rmethox (is) = tnat(is)*(1.0-25.0/1000.) 330 alpha_liq_sol(is) = 1.0212 ! Lehmann & Siegenthaler, 1991, Jo. of Glaciology, vol 37, p 23 331 ! alpha_liq_sol=1.0192: Weston, Ralph, 1955 332 END IF 333 334 !=== HTO 335 is = iso_HTO 336 IF(is /= 0) THEN 337 tdifrel (is) = 1./0.968 338 alpha (is) = alpha_ideal_HTO 339 tnat (is) = tnat_HTO; IF(ltnat1) tnat(is) = 1.0 340 toce (is) = 4.0E-19 ! ratio T/H = 0.2 TU Dreisigacker & Roether 1978 341 tcorr (is) = 1.0 342 talph1 (is) = 46480.; talps1(is) = 46480.; tkcin0(is) = 0.01056 343 talph2 (is) = -103.87; talps2(is) = -103.87; tkcin1(is) = 0.0005016 344 talph3 (is) = 0.0; tkcin2(is) = 0.0014432 345 Rdefault(is) = 0.0 346 Rmethox (is) = 0.0 347 alpha_liq_sol(is) = 1.0 348 END IF 349 350 IF(.NOT. Rdefault_smow) THEN 351 Rdefault(:) = 0.0; IF(iso_eau > 0) Rdefault(iso_eau) = 1.0 352 END IF 353 WRITE(*,*) 'Rdefault = ',Rdefault 354 WRITE(*,*) 'toce = ', toce 355 356 357 !--- Sensitivity test: no kinetic effect in sfc evaporation 358 IF(ok_nocinsfc) THEN 359 tkcin0(1:niso) = 0.0 360 tkcin1(1:niso) = 0.0 361 tkcin2(1:niso) = 0.0 362 END IF 363 364 CALL msg('285: verif initialisation:', modname) 365 DO ixt=1,niso 366 sxt=int2str(ixt) 367 CALL msg(' * isoName('//TRIM(sxt)//') = <'//TRIM(isoName(ixt))//'>', modname) 368 CALL msg( ' tnat('//TRIM(sxt)//') = '//TRIM(real2str(tnat(ixt))), modname) 369 ! CALL msg(' alpha_liq_sol('//TRIM(sxt)//') = '//TRIM(real2str(alpha_liq_sol(ixt))), modname) 370 ! CALL msg( ' tkcin0('//TRIM(sxt)//') = '//TRIM(real2str(tkcin0(ixt))), modname) 371 ! CALL msg( ' tdifrel('//TRIM(sxt)//') = '//TRIM(real2str(tdifrel(ixt))), modname) 372 END DO 373 CALL msg('69: lambda = '//TRIM(real2str(lambda_sursat)), modname) 374 CALL msg('69: thumxt1 = '//TRIM(real2str(thumxt1)), modname) 375 CALL msg('69: h_land_ice = '//TRIM(real2str(h_land_ice)), modname) 376 CALL msg('69: P_veg = '//TRIM(real2str(P_veg)), modname) 412 377 413 378 END SUBROUTINE iso_init
Note: See TracChangeset
for help on using the changeset viewer.