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

Last change on this file since 5244 was 5214, checked in by dcugnet, 4 weeks ago

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.
The "getKey" routine is only used in "infotrac" and "infotrac_phy" routines, but could be used outside this scope to get tracers parameters (read from "tracer.def") or isotopic parameters (read from "isotopes_params.def" - disabled for now).

  • Property svn:executable set to *
File size: 21.4 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, niso, ntiso
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
11  !--- Contains all isotopic variables + their initialization
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
44
45   !--- Isotopes indices (in [1,niso] ; non-existing => 0 index)
46   INTEGER, SAVE :: iso_eau, iso_HDO, iso_O18, iso_O17, iso_HTO
47!$OMP THREADPRIVATE(iso_eau, iso_HDO, iso_O18, iso_O17, iso_HTO)
48
49   INTEGER, SAVE :: ntracisoOR
50!$OMP THREADPRIVATE(ntracisoOR)
51
52   !--- Variables not depending on isotopes
53   REAL,    SAVE :: thumxt1
54   !$OMP THREADPRIVATE(thumxt1)
55   INTEGER, SAVE :: ntot
56!$OMP THREADPRIVATE(ntot)
57   REAL,    SAVE :: h_land_ice
58!$OMP THREADPRIVATE(h_land_ice)
59   REAL,    SAVE :: P_veg
60!$OMP THREADPRIVATE(P_veg)
61   REAL,    SAVE :: lambda_sursat
62!$OMP THREADPRIVATE(lambda_sursat)
63   LOGICAL, SAVE :: bidouille_anti_divergence    ! T: regularly, xteau <- q to avoid slow drifts
64!$OMP THREADPRIVATE(bidouille_anti_divergence)
65   LOGICAL, SAVE :: essai_convergence            ! F: as in LMDZ without isotopes (bad for isotopes)
66!$OMP THREADPRIVATE(essai_convergence)
67   INTEGER, SAVE :: initialisation_iso           ! 0: file ; 1: R=0 ; 2: R=distill. Rayleigh ; 3: R=Rsmow
68!$OMP THREADPRIVATE(initialisation_iso)
69   INTEGER, SAVE :: modif_SST                    ! 0: default ; 1: modified SST ; 2, 3: SST profiles
70!$OMP THREADPRIVATE(modif_SST)
71   REAL,    SAVE :: deltaTtest                   ! Uniform modification of the SST
72!$OMP THREADPRIVATE(deltaTtest)
73   INTEGER, SAVE :: modif_sic                    ! Holes in the Sea Ice
74!$OMP THREADPRIVATE(modif_sic)
75   REAL,    SAVE :: deltasic                     ! Minimal holes fraction
76!$OMP THREADPRIVATE(deltasic)
77   REAL,    SAVE :: deltaTtestpoles
78!$OMP THREADPRIVATE(deltaTtestpoles)
79   REAL,    SAVE :: sstlatcrit, dsstlatcrit
80!$OMP THREADPRIVATE(sstlatcrit, dsstlatcrit)
81   INTEGER, SAVE :: albedo_prescrit              ! 0: default ; 1: constant albedo
82!$OMP THREADPRIVATE(albedo_prescrit)
83   REAL,    SAVE :: lon_min_albedo, lon_max_albedo, lat_min_albedo, lat_max_albedo
84!$OMP THREADPRIVATE(lon_min_albedo, lon_max_albedo, lat_min_albedo, lat_max_albedo)
85   REAL,    SAVE :: deltaP_BL,tdifexp_sol
86!$OMP THREADPRIVATE(deltaP_BL,tdifexp_sol)
87   INTEGER, SAVE :: ruissellement_pluie, alphak_stewart
88!$OMP THREADPRIVATE(ruissellement_pluie, alphak_stewart)
89   INTEGER, SAVE :: calendrier_guide
90!$OMP THREADPRIVATE(calendrier_guide)
91   INTEGER, SAVE :: cste_surf_cond
92!$OMP THREADPRIVATE(cste_surf_cond)
93   REAL,    SAVE :: mixlen
94!$OMP THREADPRIVATE(mixlen)
95   INTEGER, SAVE :: evap_cont_cste
96!$OMP THREADPRIVATE(evap_cont_cste)
97   REAL,    SAVE :: deltaO18_evap_cont, d_evap_cont
98!$OMP THREADPRIVATE(deltaO18_evap_cont, d_evap_cont)
99   INTEGER, SAVE :: nudge_qsol, region_nudge_qsol
100!$OMP THREADPRIVATE(nudge_qsol, region_nudge_qsol)
101   INTEGER, SAVE :: nlevmaxO17
102!$OMP THREADPRIVATE(nlevmaxO17)
103   INTEGER, SAVE :: no_pce
104!$OMP THREADPRIVATE(no_pce)
105   REAL,    SAVE :: A_satlim
106!$OMP THREADPRIVATE(A_satlim)
107   INTEGER, SAVE :: ok_restrict_A_satlim, modif_ratqs
108!$OMP THREADPRIVATE(ok_restrict_A_satlim, modif_ratqs)
109   REAL,    SAVE :: Pcrit_ratqs, ratqsbasnew
110!$OMP THREADPRIVATE(Pcrit_ratqs, ratqsbasnew)
111   REAL,    SAVE :: fac_modif_evaoce
112!$OMP THREADPRIVATE(fac_modif_evaoce)
113   REAL,    SAVE :: deltaO18_oce
114!$OMP THREADPRIVATE(deltaO18_oce)
115   INTEGER, SAVE :: ok_bidouille_wake
116!$OMP THREADPRIVATE(ok_bidouille_wake)
117   LOGICAL, SAVE :: cond_temp_env
118!$OMP THREADPRIVATE(cond_temp_env)
119
120   !--- Vectors of length "niso"
121   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
122                    alpha, tnat, toce, tcorr, tdifrel
123!$OMP THREADPRIVATE(alpha, tnat, toce, tcorr, tdifrel)
124   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
125                    talph1, talph2, talph3, talps1, talps2
126!$OMP THREADPRIVATE(talph1, talph2, talph3, talps1, talps2)
127   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
128                    tkcin0, tkcin1, tkcin2
129!$OMP THREADPRIVATE(tkcin0, tkcin1, tkcin2)
130   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
131                    alpha_liq_sol, Rdefault, Rmethox
132!$OMP THREADPRIVATE(alpha_liq_sol, Rdefault, Rmethox)
133
134   !--- Specific to HTO:
135   LOGICAL, SAVE :: ok_prod_nucl_tritium    !--- TRUE => HTO production by nuclear tests
136!$OMP THREADPRIVATE(ok_prod_nucl_tritium)
137   INTEGER, PARAMETER :: nessai = 486
138   INTEGER, DIMENSION(nessai), SAVE :: &
139                    day_nucl, month_nucl, year_nucl
140!$OMP THREADPRIVATE(day_nucl, month_nucl, year_nucl)
141   REAL,    DIMENSION(nessai), SAVE :: &
142                    lat_nucl, lon_nucl, zmin_nucl, zmax_nucl, HTO_nucl
143!$OMP THREADPRIVATE(lat_nucl, lon_nucl, zmin_nucl, zmax_nucl, HTO_nucl)
144 
145 
146CONTAINS
147
148SUBROUTINE iso_init()
149   IMPLICIT NONE
150
151   !=== Local variables:
152   INTEGER :: ixt, is
153   LOGICAL :: ltnat1
154   CHARACTER(LEN=maxlen) :: modname, sxt
155 
156   !--- For H2[17]O
157   REAL    :: fac_kcin, pente_MWL
158     
159   !--- Sensitivity tests
160   LOGICAL, PARAMETER ::   ok_nocinsfc = .FALSE. ! if T: no kinetic effect in sfc evap
161   LOGICAL, PARAMETER ::   ok_nocinsat = .FALSE. ! if T: no sursaturation effect for ice
162   LOGICAL, PARAMETER :: Rdefault_smow = .FALSE. ! if T: Rdefault=smow; if F: nul
163
164   !--- For [3]H
165   INTEGER :: iessai
166
167   modname = 'iso_init'
168   CALL msg('219: entree', modname)
169
170   !--------------------------------------------------------------
171   ! General:
172   !--------------------------------------------------------------
173
174   !--- Check number of isotopes
175   CALL msg('64: niso = '//TRIM(int2str(niso)), modname)
176
177         !--- 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
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
208         IF(modif_sst >= 2 .AND. sstlatcrit < 0.0) STOP
209#endif             
210
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)
240#ifdef ISOVERIF
241         CALL msg(' 315: A_satlim='//real2str(A_satlim), modname, A_satlim > 1.0)
242         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)
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         !--- Sensitivity test: no kinetic effect in sfc evaporation
357         IF(ok_nocinsfc) THEN
358            tkcin0(1:niso) = 0.0
359            tkcin1(1:niso) = 0.0
360            tkcin2(1:niso) = 0.0
361         END IF
362
363         CALL msg('285: verif initialisation:', modname)
364         DO ixt=1,niso
365            sxt=int2str(ixt)
366            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)
371         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)
376
377END SUBROUTINE iso_init
378
379
380SUBROUTINE getinp_s(nam, val, def, lDisp)
381   USE ioipsl_getincom, 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)
397END SUBROUTINE getinp_s
398
399SUBROUTINE getinp_i(nam, val, def, lDisp)
400   USE ioipsl_getincom, 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)
416END SUBROUTINE getinp_i
417
418SUBROUTINE getinp_r(nam, val, def, lDisp)
419   USE ioipsl_getincom, 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)
435END SUBROUTINE getinp_r
436
437SUBROUTINE getinp_l(nam, val, def, lDisp)
438   USE ioipsl_getincom, 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)
454END SUBROUTINE getinp_l
455
456END MODULE isotopes_mod
457#endif
458
459
Note: See TracBrowser for help on using the repository browser.