source: LMDZ6/trunk/libf/phylmdiso/isotopes_mod.F90 @ 5183

Last change on this file since 5183 was 5183, checked in by dcugnet, 10 days ago
  • Remove INCA retro-compatibility with "traceur.def" (containing only water tracers but getting chemical species from an internal INCA routine).
  • The "trac_type" derived type internal to "readTracFiles_mod" is removed because a generic "keys_type" is enough: no explicit key ("%" operator) is needed, even %name.
  • The "trac_type" and "isot_type" derived types are now defined locally in "infotrac" and "infotrac_phy" (and more generally in each context: dynamic, lmdz dynamics, lmdz physics, etc.). The "readTracFiles_mod" module is now only used in these two routines:
    • few internal routines/variables (addPhase, delPhase, new2oldH2O, newHNO3, oldHNO3) are made available through "infotrac" and "infotrac_phy".
    • the "getKey" routine is only used in these two routines to define the explicit keys ("%" operator) of the local derived types "trac_type" and "isot_type". It could be in principle used outside this scope to get tracers parameters (read from "tracer.def") or isotopic parameters (read from "isotopes_params.def" - disabled for now).
  • The fortran parameters file "iso_params_mod.F90" is introduced so that "tnat" and "alpha_ideal" are defined in a single place but used in several. "ltnat1" is no longer hardcoded but defined with the *.def files parameter "tnat1"
  • Few minor changes:
    • use "infotrac_phy" instead of "infotrac" in calfis* because "tracers(:)%isAdvected" is defined in physics only.
    • "isotopes_mod" now ready for several isotopes classes (currently: only H2O)
    • isotopes class name (the name of the parent of the isotopes) is now %name and no longer %parent.
    • improvement of "getKey"
  • Property svn:executable set to *
File size: 22.5 KB
Line 
1#ifdef ISO
2! $Id: $
3
4MODULE isotopes_mod
5   USE strings_mod,  ONLY: msg, real2str, int2str, bool2str, maxlen, strIdx, strStack
6   USE infotrac_phy, ONLY: isoName, isoSelect, niso, ntiso, nbIso, isoFamilies
7   USE iso_params_mod
8   IMPLICIT NONE
9   INTERFACE get_in; MODULE PROCEDURE getinp_s, getinp_i, getinp_r, getinp_l;  END INTERFACE get_in
10   SAVE
11
12  !--- Contains all isotopic variables + their initialization
13  !--- Isotopes-specific routines are in isotopes_routines_mod to avoid circular dependencies with isotopes_verif_mod.
14
15   !--- Negligible lower thresholds: no need to check for absurd values under these lower limits
16   REAL, PARAMETER :: &
17      ridicule      = 1e-12,              & ! For mixing ratios
18      ridicule_rain = 1e-8,               & ! For rain fluxes (rain, zrfl...) in kg/s <-> 1e-3 mm/day
19      ridicule_evap = ridicule_rain*1e-2, & ! For evaporations                in kg/s <-> 1e-3 mm/day
20      ridicule_qsol = ridicule_rain,      & ! For qsol                        in kg <-> 1e-8 kg
21      ridicule_snow = ridicule_qsol         ! For snow                        in kg <-> 1e-8 kg
22   REAL, PARAMETER :: expb_max = 30.0
23
24   !--- Fractionation coefficients for H217O
25   REAL, PARAMETER :: fac_coeff_eq17_liq = 0.529,    &
26                      fac_coeff_eq17_ice = 0.529
27
28   !--- H218O reference
29   REAL, PARAMETER :: fac_enrichoce18 = 0.0005,  alpha_liq_sol_O18 = 1.00291,                    &
30                      talph1_O18 = 1137.,        talps1_O18 = 11.839,     tkcin0_O18 = 0.006,    &
31                      talph2_O18 = -0.4156,      talps2_O18 = -0.028244,  tkcin1_O18 = 0.000285, &
32                      talph3_O18 = -2.0667E-3,  tdifrel_O18 = 1./0.9723,  tkcin2_O18 = 0.00082
33
34   !--- Parameters that do not depend on the nature of water isotopes:
35   REAL, PARAMETER :: pxtmelt = 273.15           !--- temperature at which ice formation starts
36   REAL, PARAMETER :: pxtice  = 273.15 -  10.0   !--- temperature at which all condensate is ice:
37   REAL, PARAMETER :: pxtmin  = 273.15 - 120.0   !--- computation done only under -120°C
38   REAL, PARAMETER :: pxtmax  = 273.15 +  60.0   !--- computation done only  over  +60°C
39   REAL, PARAMETER :: tdifexp = 0.58             !--- a constant for alpha_eff for equilibrium below cloud base:
40   REAL, PARAMETER :: tv0cin  = 7.0              !--- wind threshold (m/s) for smooth/rough regime (Merlivat and Jouzel 1979)
41   REAL, PARAMETER :: musi    = 1.0              !--- facteurs lambda et mu dans Si=musi-lambda*T
42   REAL, PARAMETER :: Kd      = 2.5e-9    ! m2/s !--- diffusion in soil
43   REAL, PARAMETER :: rh_cste_surf_cond = 0.6    !--- cste_surf_cond case: rhs and/or Ts set to constants
44   REAL, PARAMETER :: T_cste_surf_cond = 288.0
45
46   !--- Isotopes indices (in [1,niso] ; non-existing => 0 index)
47   INTEGER, SAVE :: iso_eau, iso_HDO, iso_O18, iso_O17, iso_HTO
48!$OMP THREADPRIVATE(iso_eau, iso_HDO, iso_O18, iso_O17, iso_HTO)
49
50   INTEGER, SAVE :: ntracisoOR
51!$OMP THREADPRIVATE(ntracisoOR)
52
53   !--- Variables not depending on isotopes
54   REAL,    SAVE :: thumxt1
55   !$OMP THREADPRIVATE(thumxt1)
56   INTEGER, SAVE :: ntot
57!$OMP THREADPRIVATE(ntot)
58   REAL,    SAVE :: h_land_ice
59!$OMP THREADPRIVATE(h_land_ice)
60   REAL,    SAVE :: P_veg
61!$OMP THREADPRIVATE(P_veg)
62   REAL,    SAVE :: lambda_sursat
63!$OMP THREADPRIVATE(lambda_sursat)
64   LOGICAL, SAVE :: bidouille_anti_divergence    ! T: regularly, xteau <- q to avoid slow drifts
65!$OMP THREADPRIVATE(bidouille_anti_divergence)
66   LOGICAL, SAVE :: essai_convergence            ! F: as in LMDZ without isotopes (bad for isotopes)
67!$OMP THREADPRIVATE(essai_convergence)
68   INTEGER, SAVE :: initialisation_iso           ! 0: file ; 1: R=0 ; 2: R=distill. Rayleigh ; 3: R=Rsmow
69!$OMP THREADPRIVATE(initialisation_iso)
70   INTEGER, SAVE :: modif_SST                    ! 0: default ; 1: modified SST ; 2, 3: SST profiles
71!$OMP THREADPRIVATE(modif_SST)
72   REAL,    SAVE :: deltaTtest                   ! Uniform modification of the SST
73!$OMP THREADPRIVATE(deltaTtest)
74   INTEGER, SAVE :: modif_sic                    ! Holes in the Sea Ice
75!$OMP THREADPRIVATE(modif_sic)
76   REAL,    SAVE :: deltasic                     ! Minimal holes fraction
77!$OMP THREADPRIVATE(deltasic)
78   REAL,    SAVE :: deltaTtestpoles
79!$OMP THREADPRIVATE(deltaTtestpoles)
80   REAL,    SAVE :: sstlatcrit, dsstlatcrit
81!$OMP THREADPRIVATE(sstlatcrit, dsstlatcrit)
82   INTEGER, SAVE :: albedo_prescrit              ! 0: default ; 1: constant albedo
83!$OMP THREADPRIVATE(albedo_prescrit)
84   REAL,    SAVE :: lon_min_albedo, lon_max_albedo, lat_min_albedo, lat_max_albedo
85!$OMP THREADPRIVATE(lon_min_albedo, lon_max_albedo, lat_min_albedo, lat_max_albedo)
86   REAL,    SAVE :: deltaP_BL,tdifexp_sol
87!$OMP THREADPRIVATE(deltaP_BL,tdifexp_sol)
88   INTEGER, SAVE :: ruissellement_pluie, alphak_stewart
89!$OMP THREADPRIVATE(ruissellement_pluie, alphak_stewart)
90   INTEGER, SAVE :: calendrier_guide
91!$OMP THREADPRIVATE(calendrier_guide)
92   INTEGER, SAVE :: cste_surf_cond
93!$OMP THREADPRIVATE(cste_surf_cond)
94   REAL,    SAVE :: mixlen
95!$OMP THREADPRIVATE(mixlen)
96   INTEGER, SAVE :: evap_cont_cste
97!$OMP THREADPRIVATE(evap_cont_cste)
98   REAL,    SAVE :: deltaO18_evap_cont, d_evap_cont
99!$OMP THREADPRIVATE(deltaO18_evap_cont, d_evap_cont)
100   INTEGER, SAVE :: nudge_qsol, region_nudge_qsol
101!$OMP THREADPRIVATE(nudge_qsol, region_nudge_qsol)
102   INTEGER, SAVE :: nlevmaxO17
103!$OMP THREADPRIVATE(nlevmaxO17)
104   INTEGER, SAVE :: no_pce
105!$OMP THREADPRIVATE(no_pce)
106   REAL,    SAVE :: A_satlim
107!$OMP THREADPRIVATE(A_satlim)
108   INTEGER, SAVE :: ok_restrict_A_satlim, modif_ratqs
109!$OMP THREADPRIVATE(ok_restrict_A_satlim, modif_ratqs)
110   REAL,    SAVE :: Pcrit_ratqs, ratqsbasnew
111!$OMP THREADPRIVATE(Pcrit_ratqs, ratqsbasnew)
112   REAL,    SAVE :: fac_modif_evaoce
113!$OMP THREADPRIVATE(fac_modif_evaoce)
114   REAL,    SAVE :: deltaO18_oce
115!$OMP THREADPRIVATE(deltaO18_oce)
116   INTEGER, SAVE :: ok_bidouille_wake
117!$OMP THREADPRIVATE(ok_bidouille_wake)
118   LOGICAL, SAVE :: cond_temp_env
119!$OMP THREADPRIVATE(cond_temp_env)
120
121   !--- Vectors of length "niso"
122   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
123                    alpha, tnat, toce, tcorr, tdifrel
124!$OMP THREADPRIVATE(alpha, tnat, toce, tcorr, tdifrel)
125   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
126                    talph1, talph2, talph3, talps1, talps2
127!$OMP THREADPRIVATE(talph1, talph2, talph3, talps1, talps2)
128   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
129                    tkcin0, tkcin1, tkcin2
130!$OMP THREADPRIVATE(tkcin0, tkcin1, tkcin2)
131   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
132                    alpha_liq_sol, Rdefault, Rmethox
133!$OMP THREADPRIVATE(alpha_liq_sol, Rdefault, Rmethox)
134
135   !--- Specific to HTO:
136   LOGICAL, SAVE :: ok_prod_nucl_tritium    !--- TRUE => HTO production by nuclear tests
137!$OMP THREADPRIVATE(ok_prod_nucl_tritium)
138   INTEGER, PARAMETER :: nessai = 486
139   INTEGER, DIMENSION(nessai), SAVE :: &
140                    day_nucl, month_nucl, year_nucl
141!$OMP THREADPRIVATE(day_nucl, month_nucl, year_nucl)
142   REAL,    DIMENSION(nessai), SAVE :: &
143                    lat_nucl, lon_nucl, zmin_nucl, zmax_nucl, HTO_nucl
144!$OMP THREADPRIVATE(lat_nucl, lon_nucl, zmin_nucl, zmax_nucl, HTO_nucl)
145 
146 
147CONTAINS
148
149SUBROUTINE iso_init()
150   IMPLICIT NONE
151
152   !=== Local variables:
153   INTEGER :: ixt, ii, is
154   LOGICAL :: ltnat1
155   CHARACTER(LEN=maxlen) :: modname, sxt
156 
157   !--- For H2[17]O
158   REAL    :: fac_kcin, pente_MWL
159     
160   !--- Sensitivity tests
161   LOGICAL, PARAMETER ::   ok_nocinsfc = .FALSE. ! if T: no kinetic effect in sfc evap
162   LOGICAL, PARAMETER ::   ok_nocinsat = .FALSE. ! if T: no sursaturation effect for ice
163   LOGICAL, PARAMETER :: Rdefault_smow = .FALSE. ! if T: Rdefault=smow; if F: nul
164
165   !--- For [3]H
166   INTEGER :: iessai
167
168   modname = 'iso_init'
169   CALL msg('219: entree', modname)
170
171   !--------------------------------------------------------------
172   ! General:
173   !--------------------------------------------------------------
174
175   !--- Check number of isotopes
176   CALL msg('64: niso = '//TRIM(int2str(niso)), modname)
177
178   DO ii = 1, nbIso
179      CALL msg('Can''t select isotopes class "'//TRIM(isoFamilies(ii))//'"', modname, isoSelect(ii, lVerbose=.TRUE.))
180
181!==============================================================================================================================
182      IF(isoFamilies(ii) == 'H2O') THEN
183!==============================================================================================================================
184         !--- Init de ntracisoOR: on ecrasera en cas de traceurs de tagging isotopiques
185         !                     (nzone>0) si complications avec ORCHIDEE
186         ntracisoOR = ntiso
187
188         !--- Type of water isotopes:
189         iso_eau = strIdx(isoName, 'H216O'); CALL msg('iso_eau='//int2str(iso_eau), modname)
190         iso_HDO = strIdx(isoName, 'HDO');   CALL msg('iso_HDO='//int2str(iso_HDO), modname)
191         iso_O18 = strIdx(isoName, 'H218O'); CALL msg('iso_O18='//int2str(iso_O18), modname)
192         iso_O17 = strIdx(isoName, 'H217O'); CALL msg('iso_O17='//int2str(iso_O17), modname)
193         iso_HTO = strIdx(isoName, 'HTO');   CALL msg('iso_HTO='//int2str(iso_HTO), modname)
194
195         !--- Initialisation: reading the isotopic parameters.
196         CALL get_in('lambda',     lambda_sursat, 0.004); IF(ok_nocinsat) lambda_sursat = 0.
197         CALL get_in('thumxt1',    thumxt1,       0.75*1.2)
198         CALL get_in('ntot',       ntot,          20,  .FALSE.)
199         CALL get_in('h_land_ice', h_land_ice,    20., .FALSE.)
200         CALL get_in('P_veg',      P_veg,         1.0, .FALSE.)
201         CALL get_in('bidouille_anti_divergence', bidouille_anti_divergence, .FALSE.)
202         CALL get_in('essai_convergence',         essai_convergence,         .FALSE.)
203         CALL get_in('initialisation_iso',        initialisation_iso,        0)
204
205!        IF(nzone>0 .AND. initialisation_iso==0) &
206!           CALL get_in('initialisation_isotrac',initialisation_isotrac)
207         CALL get_in('modif_sst',      modif_sst,         0)
208         CALL get_in('deltaTtest',     deltaTtest,      0.0)     !--- For modif_sst>=1
209         CALL get_in('deltaTtestpoles',deltaTtestpoles, 0.0)     !--- For modif_sst>=2
210         CALL get_in( 'sstlatcrit',    sstlatcrit,     30.0)     !--- For modif_sst>=3
211         CALL get_in('dsstlatcrit',   dsstlatcrit,      0.0)     !--- For modif_sst>=3
212#ifdef ISOVERIF
213         CALL msg('iso_init 270:  sstlatcrit='//real2str( sstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=2
214         CALL msg('iso_init 279: dsstlatcrit='//real2str(dsstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=3
215         IF(modif_sst >= 2 .AND. sstlatcrit < 0.0) STOP
216#endif             
217
218         CALL get_in('modif_sic', modif_sic,  0)
219         IF(modif_sic >= 1) &
220         CALL get_in('deltasic',  deltasic, 0.1)
221
222         CALL get_in('albedo_prescrit', albedo_prescrit, 0)
223         IF(albedo_prescrit == 1) THEN
224            CALL get_in('lon_min_albedo', lon_min_albedo, -200.)
225            CALL get_in('lon_max_albedo', lon_max_albedo,  200.)
226            CALL get_in('lat_min_albedo', lat_min_albedo, -100.)
227            CALL get_in('lat_max_albedo', lat_max_albedo,  100.)
228         END IF
229         CALL get_in('deltaO18_oce',        deltaO18_oce,   0.0)
230         CALL get_in('deltaP_BL',           deltaP_BL,     10.0)
231         CALL get_in('ruissellement_pluie', ruissellement_pluie, 0)
232         CALL get_in('alphak_stewart',      alphak_stewart,      1)
233         CALL get_in('tdifexp_sol',         tdifexp_sol,      0.67)
234         CALL get_in('calendrier_guide',    calendrier_guide,    0)
235         CALL get_in('cste_surf_cond',      cste_surf_cond,      0)
236         CALL get_in('mixlen',              mixlen,           35.0)
237         CALL get_in('evap_cont_cste',      evap_cont_cste,      0)
238         CALL get_in('deltaO18_evap_cont',  deltaO18_evap_cont,0.0)
239         CALL get_in('d_evap_cont',         d_evap_cont,       0.0)
240         CALL get_in('nudge_qsol',          nudge_qsol,          0)
241         CALL get_in('region_nudge_qsol',   region_nudge_qsol,   1)
242         nlevmaxO17 = 50
243         CALL msg('nlevmaxO17='//TRIM(int2str(nlevmaxO17)))
244         CALL get_in('no_pce',   no_pce,     0)
245         CALL get_in('A_satlim', A_satlim, 1.0)
246         CALL get_in('ok_restrict_A_satlim', ok_restrict_A_satlim, 0)
247#ifdef ISOVERIF
248         CALL msg(' 315: A_satlim='//real2str(A_satlim), modname, A_satlim > 1.0)
249         IF(A_satlim > 1.0) STOP
250#endif
251!        CALL get_in('slope_limiterxy',   slope_limiterxy,  2.0)
252!        CALL get_in('slope_limiterz',    slope_limiterz,   2.0)
253         CALL get_in('modif_ratqs',       modif_ratqs,        0)
254         CALL get_in('Pcrit_ratqs',       Pcrit_ratqs,    500.0)
255         CALL get_in('ratqsbasnew',       ratqsbasnew,     0.05)
256         CALL get_in('fac_modif_evaoce',  fac_modif_evaoce, 1.0)
257         CALL get_in('ok_bidouille_wake', ok_bidouille_wake,  0)
258         ! si oui, la temperature de cond est celle de l'environnement, pour eviter
259         ! bugs quand temperature dans ascendances convs est mal calculee
260         CALL get_in('cond_temp_env',        cond_temp_env,        .FALSE.)
261         IF(ANY(isoName == 'HTO')) &
262         CALL get_in('ok_prod_nucl_tritium', ok_prod_nucl_tritium, .FALSE., .FALSE.)
263         CALL get_in('tnateq1', ltnat1, .TRUE.)
264
265         CALL msg('iso_O18, iso_HDO, iso_eau = '//TRIM(strStack(int2str([iso_O18, iso_HDO, iso_eau]))), modname)
266
267         !--------------------------------------------------------------
268         ! Parameters that depend on the nature of water isotopes:
269         !--------------------------------------------------------------
270         ALLOCATE(tnat (niso), talph1(niso),  talps1(niso), tkcin0(niso), tdifrel (niso), alpha        (niso))
271         ALLOCATE(toce (niso), talph2(niso),  talps2(niso), tkcin1(niso), Rdefault(niso), alpha_liq_sol(niso))
272         ALLOCATE(tcorr(niso), talph3(niso),                tkcin2(niso), Rmethox (niso))
273
274         !=== H216O
275         is = iso_eau
276         IF(is /= 0) THEN
277            tdifrel (is) = 1.0
278            alpha   (is) = alpha_ideal_H216O
279            tnat    (is) = tnat_H216O; IF(ltnat1) tnat(is) = 1.0
280            toce    (is) = tnat(is)
281            tcorr   (is) = 1.0
282            talph1  (is) = 0.0;  talps1(is) = 0.0;  tkcin0(is)  = 0.0
283            talph2  (is) = 0.0;  talps2(is) = 0.0;  tkcin1(is)  = 0.0
284            talph3  (is) = 0.0;                     tkcin2(is)  = 0.0
285            Rdefault(is) = tnat(is)*1.0
286            Rmethox (is) = 1.0
287            alpha_liq_sol(is) = 1.0
288         END IF
289
290         !=== H217O
291         is = iso_O17
292         IF(is /= 0) THEN; pente_MWL = 0.528
293            tdifrel (is) = 1./0.98555  ! used in 1D and in LdG model ; tdifrel=1./0.985452: from Amaelle
294            alpha   (is) = alpha_ideal_H217O
295            tnat    (is) = tnat_H217O; IF(ltnat1) tnat(is) = 1.0
296            toce    (is) = tnat(is)*(1.0+deltaO18_oce/1000.0)**pente_MWL
297            tcorr   (is) = 1.0+fac_enrichoce18*pente_MWL
298            fac_kcin = (tdifrel(is)-1.0)/(tdifrel_O18-1.0)           ! fac_kcin=0.5145:     from Amaelle
299            talph1  (is) = talph1_O18;  talps1(is) = talps1_O18;  tkcin0(is) = tkcin0_O18*fac_kcin
300            talph2  (is) = talph2_O18;  talps2(is) = talps2_O18;  tkcin1(is) = tkcin1_O18*fac_kcin
301            talph3  (is) = talph3_O18;                            tkcin2(is) = tkcin2_O18*fac_kcin
302            Rdefault(is) = tnat(is)*(1.0-3.15/1000.)
303            Rmethox (is) = tnat(is)*(1.0+230./1000.)
304            alpha_liq_sol(is) = alpha_liq_sol_O18**fac_coeff_eq17_liq
305         END IF
306
307         !=== H218O
308         is = iso_O18
309         IF(is /= 0) THEN
310            tdifrel (is) = tdifrel_O18
311            alpha   (is) = alpha_ideal_H218O
312            tnat    (is) = tnat_H218O; IF(ltnat1) tnat(is) = 1.0
313            toce    (is) = tnat(is)*(1.0+deltaO18_oce/1000.0)
314            tcorr   (is) = 1.0+fac_enrichoce18
315            talph1  (is) = talph1_O18;  talps1(is) = talps1_O18;  tkcin0(is) = tkcin0_O18
316            talph2  (is) = talph2_O18;  talps2(is) = talps2_O18;  tkcin1(is) = tkcin1_O18
317            talph3  (is) = talph3_O18;                            tkcin2(is) = tkcin2_O18
318            Rdefault(is) = tnat(is)*(1.0-6.00/1000.)
319            Rmethox (is) = tnat(is)*(1.0+130./1000.)  ! Zahn & al. 2006
320            alpha_liq_sol(is) = alpha_liq_sol_O18
321         END IF
322
323         !=== HDO
324         is = iso_HDO
325         IF(is /= 0) THEN; pente_MWL = 8.0
326            tdifrel (is) = 1./0.9755                  ! fac_kcin=0.88
327            alpha   (is) = alpha_ideal_HDO
328            tnat    (is) = tnat_HDO; IF(ltnat1) tnat(is) = 1.0
329            toce    (is) = tnat(is)*(1.0+deltaO18_oce/1000.0*pente_MWL)
330            tcorr   (is) = 1.0+fac_enrichoce18*pente_MWL
331            fac_kcin = (tdifrel(is)-1.0)/(tdifrel_O18-1.0)
332            talph1  (is) = 24844.;      talps1(is) = 16288.;      tkcin0(is) = tkcin0_O18*fac_kcin
333            talph2  (is) = -76.248;     talps2(is) = -0.0934;     tkcin1(is) = tkcin1_O18*fac_kcin
334            talph3  (is) = 52.612E-3;                             tkcin2(is) = tkcin2_O18*fac_kcin
335            Rdefault(is) = tnat(is)*(1.0+(10.0-6.0*pente_MWL)/1000.)
336            Rmethox (is) = tnat(is)*(1.0-25.0/1000.)
337            alpha_liq_sol(is) = 1.0212      ! Lehmann & Siegenthaler, 1991, Jo. of Glaciology, vol 37, p 23
338                                            ! alpha_liq_sol=1.0192: Weston, Ralph, 1955
339         END IF
340
341         !=== HTO
342         is = iso_HTO
343         IF(is /= 0) THEN
344            tdifrel (is) = 1./0.968
345            alpha   (is) = alpha_ideal_HTO
346            tnat    (is) = tnat_HTO; IF(ltnat1) tnat(is) = 1.0
347            toce    (is) = 4.0E-19          ! ratio T/H = 0.2 TU Dreisigacker & Roether 1978
348            tcorr   (is) = 1.0
349            talph1  (is) = 46480.;      talps1(is) = 46480.;      tkcin0(is) = 0.01056
350            talph2  (is) = -103.87;     talps2(is) = -103.87;     tkcin1(is) = 0.0005016
351            talph3  (is) = 0.0;                                   tkcin2(is) = 0.0014432
352            Rdefault(is) = 0.0
353            Rmethox (is) = 0.0
354            alpha_liq_sol(is) = 1.0
355         END IF
356
357         IF(.NOT. Rdefault_smow) THEN
358            Rdefault(:) = 0.0; IF(iso_eau > 0) Rdefault(iso_eau) = 1.0
359         END IF
360         WRITE(*,*) 'Rdefault = ',Rdefault
361         WRITE(*,*) 'toce = ', toce
362
363         !--- Sensitivity test: no kinetic effect in sfc evaporation
364         IF(ok_nocinsfc) THEN
365            tkcin0(1:niso) = 0.0
366            tkcin1(1:niso) = 0.0
367            tkcin2(1:niso) = 0.0
368         END IF
369
370         CALL msg('285: verif initialisation:', modname)
371         DO ixt=1,niso
372            sxt=int2str(ixt)
373            CALL msg(' * isoName('//TRIM(sxt)//') = <'//TRIM(isoName(ixt))//'>',  modname)
374            CALL msg(  '    tnat('//TRIM(sxt)//') = '//TRIM(real2str(tnat(ixt))), modname)
375!           CALL msg('    alpha_liq_sol('//TRIM(sxt)//') = '//TRIM(real2str(alpha_liq_sol(ixt))), modname)
376!           CALL msg(        '   tkcin0('//TRIM(sxt)//') = '//TRIM(real2str(tkcin0(ixt))),        modname)
377!           CALL msg(       '   tdifrel('//TRIM(sxt)//') = '//TRIM(real2str(tdifrel(ixt))),       modname)
378         END DO
379         CALL msg('69:     lambda = '//TRIM(real2str(lambda_sursat)), modname)
380         CALL msg('69:    thumxt1 = '//TRIM(real2str(thumxt1)),       modname)
381         CALL msg('69: h_land_ice = '//TRIM(real2str(h_land_ice)),    modname)
382         CALL msg('69:      P_veg = '//TRIM(real2str(P_veg)),         modname)
383!==============================================================================================================================
384      ELSE
385!==============================================================================================================================
386         CALL abort_physic('"isotopes_mod" is not set up yet for isotopes family "'//TRIM(isoFamilies(ii))//'"', modname, 1)
387!==============================================================================================================================
388      END IF
389!==============================================================================================================================
390   END DO
391
392END SUBROUTINE iso_init
393
394
395SUBROUTINE getinp_s(nam, val, def, lDisp)
396   USE ioipsl_getincom, ONLY: getin
397   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
398   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
399   USE mod_phys_lmdz_transfert_para, ONLY : bcast
400   CHARACTER(LEN=*),           INTENT(IN)    :: nam
401   CHARACTER(LEN=*),           INTENT(INOUT) :: val
402   CHARACTER(LEN=*), OPTIONAL, INTENT(IN)    :: def
403   LOGICAL,          OPTIONAL, INTENT(IN)    :: lDisp
404   LOGICAL :: lD
405!$OMP BARRIER
406   IF(is_mpi_root.AND.is_omp_root) THEN
407      IF(PRESENT(def)) val=def; CALL getin(nam,val)
408      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
409      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(val))
410  END IF
411  CALL bcast(val)
412END SUBROUTINE getinp_s
413
414SUBROUTINE getinp_i(nam, val, def, lDisp)
415   USE ioipsl_getincom, ONLY: getin
416   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
417   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
418   USE mod_phys_lmdz_transfert_para, ONLY : bcast
419   CHARACTER(LEN=*),  INTENT(IN)    :: nam
420   INTEGER,           INTENT(INOUT) :: val
421   INTEGER, OPTIONAL, INTENT(IN)    :: def
422   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
423   LOGICAL :: lD
424!$OMP BARRIER
425   IF(is_mpi_root.AND.is_omp_root) THEN
426      IF(PRESENT(def)) val=def; CALL getin(nam,val)
427      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
428      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(int2str(val)))
429  END IF
430  CALL bcast(val)
431END SUBROUTINE getinp_i
432
433SUBROUTINE getinp_r(nam, val, def, lDisp)
434   USE ioipsl_getincom, ONLY: getin
435   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
436   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
437   USE mod_phys_lmdz_transfert_para, ONLY : bcast
438   CHARACTER(LEN=*),  INTENT(IN)    :: nam
439   REAL,              INTENT(INOUT) :: val
440   REAL,    OPTIONAL, INTENT(IN)    :: def
441   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
442   LOGICAL :: lD
443!$OMP BARRIER
444   IF(is_mpi_root.AND.is_omp_root) THEN
445      IF(PRESENT(def)) val=def; CALL getin(nam,val)
446      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
447      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(real2str(val)))
448  END IF
449  CALL bcast(val)
450END SUBROUTINE getinp_r
451
452SUBROUTINE getinp_l(nam, val, def, lDisp)
453   USE ioipsl_getincom, ONLY: getin
454   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
455   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
456   USE mod_phys_lmdz_transfert_para, ONLY : bcast
457   CHARACTER(LEN=*),  INTENT(IN)    :: nam
458   LOGICAL,           INTENT(INOUT) :: val
459   LOGICAL, OPTIONAL, INTENT(IN)    :: def
460   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
461   LOGICAL :: lD
462!$OMP BARRIER
463   IF(is_mpi_root.AND.is_omp_root) THEN
464      IF(PRESENT(def)) val=def; CALL getin(nam,val)
465      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
466      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(bool2str(val)))
467  END IF
468  CALL bcast(val)
469END SUBROUTINE getinp_l
470
471END MODULE isotopes_mod
472#endif
473
474
Note: See TracBrowser for help on using the repository browser.