source: LMDZ6/branches/ICOLMDZISO/libf/phylmdiso/isotopes_mod.F90

Last change on this file was 5592, checked in by yann meurdesoif, 8 months ago

Update ICOLMDZISO branch.
YM

  • Property svn:executable set to *
File size: 21.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, 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   LOGICAL, SAVE :: using_iso = .FALSE.   !--- TRUE isotope version is used
146!$OMP THREADPRIVATE(using_iso)
147   
148CONTAINS
149
150SUBROUTINE iso_init()
151   IMPLICIT NONE
152
153   !=== Local variables:
154   INTEGER :: ixt, is
155   LOGICAL :: ltnat1
156   CHARACTER(LEN=maxlen) :: modname, sxt
157 
158   !--- For H2[17]O
159   REAL    :: fac_kcin, pente_MWL
160     
161   !--- Sensitivity tests
162   LOGICAL, PARAMETER ::   ok_nocinsfc = .FALSE. ! if T: no kinetic effect in sfc evap
163   LOGICAL, PARAMETER ::   ok_nocinsat = .FALSE. ! if T: no sursaturation effect for ice
164   LOGICAL, PARAMETER :: Rdefault_smow = .FALSE. ! if T: Rdefault=smow; if F: nul
165
166   !--- For [3]H
167   INTEGER :: iessai
168
169   using_iso=.TRUE.
170   
171   modname = 'iso_init'
172   CALL msg('219: entree', modname)
173
174   !--------------------------------------------------------------
175   ! General:
176   !--------------------------------------------------------------
177
178   !--- Check number of isotopes
179   CALL msg('64: niso = '//TRIM(int2str(niso)), modname)
180
181         !--- Init de ntracisoOR: on ecrasera en cas de traceurs de tagging isotopiques
182         !                     (nzone>0) si complications avec ORCHIDEE
183         ntracisoOR = ntiso
184
185         !--- Type of water isotopes:
186         iso_eau = strIdx(isoName, 'H216O'); CALL msg('iso_eau='//int2str(iso_eau), modname)
187         iso_HDO = strIdx(isoName, 'HDO');   CALL msg('iso_HDO='//int2str(iso_HDO), modname)
188         iso_O18 = strIdx(isoName, 'H218O'); CALL msg('iso_O18='//int2str(iso_O18), modname)
189         iso_O17 = strIdx(isoName, 'H217O'); CALL msg('iso_O17='//int2str(iso_O17), modname)
190         iso_HTO = strIdx(isoName, 'HTO');   CALL msg('iso_HTO='//int2str(iso_HTO), modname)
191
192         !--- Initialisation: reading the isotopic parameters.
193         CALL get_in('lambda',     lambda_sursat, 0.004); IF(ok_nocinsat) lambda_sursat = 0.
194         CALL get_in('thumxt1',    thumxt1,       0.75*1.2)
195         CALL get_in('ntot',       ntot,          20,  .FALSE.)
196         CALL get_in('h_land_ice', h_land_ice,    20., .FALSE.)
197         CALL get_in('P_veg',      P_veg,         1.0, .FALSE.)
198         CALL get_in('bidouille_anti_divergence', bidouille_anti_divergence, .FALSE.)
199         CALL get_in('essai_convergence',         essai_convergence,         .FALSE.)
200         CALL get_in('initialisation_iso',        initialisation_iso,        0)
201
202!        IF(nzone>0 .AND. initialisation_iso==0) &
203!           CALL get_in('initialisation_isotrac',initialisation_isotrac)
204         CALL get_in('modif_sst',      modif_sst,         0)
205         CALL get_in('deltaTtest',     deltaTtest,      0.0)     !--- For modif_sst>=1
206         CALL get_in('deltaTtestpoles',deltaTtestpoles, 0.0)     !--- For modif_sst>=2
207         CALL get_in( 'sstlatcrit',    sstlatcrit,     30.0)     !--- For modif_sst>=3
208         CALL get_in('dsstlatcrit',   dsstlatcrit,      0.0)     !--- For modif_sst>=3
209#ifdef ISOVERIF
210         CALL msg('iso_init 270:  sstlatcrit='//real2str( sstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=2
211         CALL msg('iso_init 279: dsstlatcrit='//real2str(dsstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=3
212         IF(modif_sst >= 2 .AND. sstlatcrit < 0.0) STOP
213#endif             
214
215         CALL get_in('modif_sic', modif_sic,  0)
216         IF(modif_sic >= 1) &
217         CALL get_in('deltasic',  deltasic, 0.1)
218
219         CALL get_in('albedo_prescrit', albedo_prescrit, 0)
220         IF(albedo_prescrit == 1) THEN
221            CALL get_in('lon_min_albedo', lon_min_albedo, -200.)
222            CALL get_in('lon_max_albedo', lon_max_albedo,  200.)
223            CALL get_in('lat_min_albedo', lat_min_albedo, -100.)
224            CALL get_in('lat_max_albedo', lat_max_albedo,  100.)
225         END IF
226         CALL get_in('deltaO18_oce',        deltaO18_oce,   0.0)
227         CALL get_in('deltaP_BL',           deltaP_BL,     10.0)
228         CALL get_in('ruissellement_pluie', ruissellement_pluie, 0)
229         CALL get_in('alphak_stewart',      alphak_stewart,      1)
230         CALL get_in('tdifexp_sol',         tdifexp_sol,      0.67)
231         CALL get_in('calendrier_guide',    calendrier_guide,    0)
232         CALL get_in('cste_surf_cond',      cste_surf_cond,      0)
233         CALL get_in('mixlen',              mixlen,           35.0)
234         CALL get_in('evap_cont_cste',      evap_cont_cste,      0)
235         CALL get_in('deltaO18_evap_cont',  deltaO18_evap_cont,0.0)
236         CALL get_in('d_evap_cont',         d_evap_cont,       0.0)
237         CALL get_in('nudge_qsol',          nudge_qsol,          0)
238         CALL get_in('region_nudge_qsol',   region_nudge_qsol,   1)
239         nlevmaxO17 = 50
240         CALL msg('nlevmaxO17='//TRIM(int2str(nlevmaxO17)))
241         CALL get_in('no_pce',   no_pce,     0)
242         CALL get_in('A_satlim', A_satlim, 1.0)
243         CALL get_in('ok_restrict_A_satlim', ok_restrict_A_satlim, 0)
244#ifdef ISOVERIF
245         CALL msg(' 315: A_satlim='//real2str(A_satlim), modname, A_satlim > 1.0)
246         IF(A_satlim > 1.0) STOP
247#endif
248!        CALL get_in('slope_limiterxy',   slope_limiterxy,  2.0)
249!        CALL get_in('slope_limiterz',    slope_limiterz,   2.0)
250         CALL get_in('modif_ratqs',       modif_ratqs,        0)
251         CALL get_in('Pcrit_ratqs',       Pcrit_ratqs,    500.0)
252         CALL get_in('ratqsbasnew',       ratqsbasnew,     0.05)
253         CALL get_in('fac_modif_evaoce',  fac_modif_evaoce, 1.0)
254         CALL get_in('ok_bidouille_wake', ok_bidouille_wake,  0)
255         ! si oui, la temperature de cond est celle de l'environnement, pour eviter
256         ! bugs quand temperature dans ascendances convs est mal calculee
257         CALL get_in('cond_temp_env',        cond_temp_env,        .FALSE.)
258         IF(ANY(isoName == 'HTO')) &
259         CALL get_in('ok_prod_nucl_tritium', ok_prod_nucl_tritium, .FALSE., .FALSE.)
260         CALL get_in('tnateq1', ltnat1, .TRUE.)
261
262         CALL msg('iso_O18, iso_HDO, iso_eau = '//TRIM(strStack(int2str([iso_O18, iso_HDO, iso_eau]))), modname)
263
264         !--------------------------------------------------------------
265         ! Parameters that depend on the nature of water isotopes:
266         !--------------------------------------------------------------
267         ALLOCATE(tnat (niso), talph1(niso),  talps1(niso), tkcin0(niso), tdifrel (niso), alpha        (niso))
268         ALLOCATE(toce (niso), talph2(niso),  talps2(niso), tkcin1(niso), Rdefault(niso), alpha_liq_sol(niso))
269         ALLOCATE(tcorr(niso), talph3(niso),                tkcin2(niso), Rmethox (niso))
270
271         !=== H216O
272         is = iso_eau
273         IF(is /= 0) THEN
274            tdifrel (is) = 1.0
275            alpha   (is) = alpha_ideal_H216O
276            tnat    (is) = tnat_H216O; IF(ltnat1) tnat(is) = 1.0
277            toce    (is) = tnat(is)
278            tcorr   (is) = 1.0
279            talph1  (is) = 0.0;  talps1(is) = 0.0;  tkcin0(is)  = 0.0
280            talph2  (is) = 0.0;  talps2(is) = 0.0;  tkcin1(is)  = 0.0
281            talph3  (is) = 0.0;                     tkcin2(is)  = 0.0
282            Rdefault(is) = tnat(is)*1.0
283            Rmethox (is) = 1.0
284            alpha_liq_sol(is) = 1.0
285         END IF
286
287         !=== H217O
288         is = iso_O17
289         IF(is /= 0) THEN; pente_MWL = 0.528
290            tdifrel (is) = 1./0.98555  ! used in 1D and in LdG model ; tdifrel=1./0.985452: from Amaelle
291            alpha   (is) = alpha_ideal_H217O
292            tnat    (is) = tnat_H217O; IF(ltnat1) tnat(is) = 1.0
293            toce    (is) = tnat(is)*(1.0+deltaO18_oce/1000.0)**pente_MWL
294            tcorr   (is) = 1.0+fac_enrichoce18*pente_MWL
295            fac_kcin = (tdifrel(is)-1.0)/(tdifrel_O18-1.0)           ! fac_kcin=0.5145:     from Amaelle
296            talph1  (is) = talph1_O18;  talps1(is) = talps1_O18;  tkcin0(is) = tkcin0_O18*fac_kcin
297            talph2  (is) = talph2_O18;  talps2(is) = talps2_O18;  tkcin1(is) = tkcin1_O18*fac_kcin
298            talph3  (is) = talph3_O18;                            tkcin2(is) = tkcin2_O18*fac_kcin
299            Rdefault(is) = tnat(is)*(1.0-3.15/1000.)
300            Rmethox (is) = tnat(is)*(1.0+230./1000.)
301            alpha_liq_sol(is) = alpha_liq_sol_O18**fac_coeff_eq17_liq
302         END IF
303
304         !=== H218O
305         is = iso_O18
306         IF(is /= 0) THEN
307            tdifrel (is) = tdifrel_O18
308            alpha   (is) = alpha_ideal_H218O
309            tnat    (is) = tnat_H218O; IF(ltnat1) tnat(is) = 1.0
310            toce    (is) = tnat(is)*(1.0+deltaO18_oce/1000.0)
311            tcorr   (is) = 1.0+fac_enrichoce18
312            talph1  (is) = talph1_O18;  talps1(is) = talps1_O18;  tkcin0(is) = tkcin0_O18
313            talph2  (is) = talph2_O18;  talps2(is) = talps2_O18;  tkcin1(is) = tkcin1_O18
314            talph3  (is) = talph3_O18;                            tkcin2(is) = tkcin2_O18
315            Rdefault(is) = tnat(is)*(1.0-6.00/1000.)
316            Rmethox (is) = tnat(is)*(1.0+130./1000.)  ! Zahn & al. 2006
317            alpha_liq_sol(is) = alpha_liq_sol_O18
318         END IF
319
320         !=== HDO
321         is = iso_HDO
322         IF(is /= 0) THEN; pente_MWL = 8.0
323            tdifrel (is) = 1./0.9755                  ! fac_kcin=0.88
324            alpha   (is) = alpha_ideal_HDO
325            tnat    (is) = tnat_HDO; IF(ltnat1) tnat(is) = 1.0
326            toce    (is) = tnat(is)*(1.0+deltaO18_oce/1000.0*pente_MWL)
327            tcorr   (is) = 1.0+fac_enrichoce18*pente_MWL
328            fac_kcin = (tdifrel(is)-1.0)/(tdifrel_O18-1.0)
329            talph1  (is) = 24844.;      talps1(is) = 16288.;      tkcin0(is) = tkcin0_O18*fac_kcin
330            talph2  (is) = -76.248;     talps2(is) = -0.0934;     tkcin1(is) = tkcin1_O18*fac_kcin
331            talph3  (is) = 52.612E-3;                             tkcin2(is) = tkcin2_O18*fac_kcin
332            Rdefault(is) = tnat(is)*(1.0+(10.0-6.0*pente_MWL)/1000.)
333            Rmethox (is) = tnat(is)*(1.0-25.0/1000.)
334            alpha_liq_sol(is) = 1.0212      ! Lehmann & Siegenthaler, 1991, Jo. of Glaciology, vol 37, p 23
335                                            ! alpha_liq_sol=1.0192: Weston, Ralph, 1955
336         END IF
337
338         !=== HTO
339         is = iso_HTO
340         IF(is /= 0) THEN
341            tdifrel (is) = 1./0.968
342            alpha   (is) = alpha_ideal_HTO
343            tnat    (is) = tnat_HTO; IF(ltnat1) tnat(is) = 1.0
344            toce    (is) = 4.0E-19          ! ratio T/H = 0.2 TU Dreisigacker & Roether 1978
345            tcorr   (is) = 1.0
346            talph1  (is) = 46480.;      talps1(is) = 46480.;      tkcin0(is) = 0.01056
347            talph2  (is) = -103.87;     talps2(is) = -103.87;     tkcin1(is) = 0.0005016
348            talph3  (is) = 0.0;                                   tkcin2(is) = 0.0014432
349            Rdefault(is) = 0.0
350            Rmethox (is) = 0.0
351            alpha_liq_sol(is) = 1.0
352         END IF
353
354         IF(.NOT. Rdefault_smow) THEN
355            Rdefault(:) = 0.0; IF(iso_eau > 0) Rdefault(iso_eau) = 1.0
356         END IF
357         WRITE(*,*) 'Rdefault = ',Rdefault
358         WRITE(*,*) 'toce = ', toce
359
360         !--- Sensitivity test: no kinetic effect in sfc evaporation
361         IF(ok_nocinsfc) THEN
362            tkcin0(1:niso) = 0.0
363            tkcin1(1:niso) = 0.0
364            tkcin2(1:niso) = 0.0
365         END IF
366
367         CALL msg('285: verif initialisation:', modname)
368         DO ixt=1,niso
369            sxt=int2str(ixt)
370            CALL msg(' * isoName('//TRIM(sxt)//') = <'//TRIM(isoName(ixt))//'>',  modname)
371            CALL msg(  '    tnat('//TRIM(sxt)//') = '//TRIM(real2str(tnat(ixt))), modname)
372!           CALL msg('    alpha_liq_sol('//TRIM(sxt)//') = '//TRIM(real2str(alpha_liq_sol(ixt))), modname)
373!           CALL msg(        '   tkcin0('//TRIM(sxt)//') = '//TRIM(real2str(tkcin0(ixt))),        modname)
374!           CALL msg(       '   tdifrel('//TRIM(sxt)//') = '//TRIM(real2str(tdifrel(ixt))),       modname)
375         END DO
376         CALL msg('69:     lambda = '//TRIM(real2str(lambda_sursat)), modname)
377         CALL msg('69:    thumxt1 = '//TRIM(real2str(thumxt1)),       modname)
378         CALL msg('69: h_land_ice = '//TRIM(real2str(h_land_ice)),    modname)
379         CALL msg('69:      P_veg = '//TRIM(real2str(P_veg)),         modname)
380
381END SUBROUTINE iso_init
382
383
384SUBROUTINE getinp_s(nam, val, def, lDisp)
385   USE ioipsl_getincom, ONLY: getin
386   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
387   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
388   USE mod_phys_lmdz_transfert_para, ONLY : bcast
389   CHARACTER(LEN=*),           INTENT(IN)    :: nam
390   CHARACTER(LEN=*),           INTENT(INOUT) :: val
391   CHARACTER(LEN=*), OPTIONAL, INTENT(IN)    :: def
392   LOGICAL,          OPTIONAL, INTENT(IN)    :: lDisp
393   LOGICAL :: lD
394!$OMP BARRIER
395   IF(is_mpi_root.AND.is_omp_root) THEN
396      IF(PRESENT(def)) val=def; CALL getin(nam,val)
397      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
398      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(val))
399  END IF
400  CALL bcast(val)
401END SUBROUTINE getinp_s
402
403SUBROUTINE getinp_i(nam, val, def, lDisp)
404   USE ioipsl_getincom, ONLY: getin
405   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
406   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
407   USE mod_phys_lmdz_transfert_para, ONLY : bcast
408   CHARACTER(LEN=*),  INTENT(IN)    :: nam
409   INTEGER,           INTENT(INOUT) :: val
410   INTEGER, OPTIONAL, INTENT(IN)    :: def
411   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
412   LOGICAL :: lD
413!$OMP BARRIER
414   IF(is_mpi_root.AND.is_omp_root) THEN
415      IF(PRESENT(def)) val=def; CALL getin(nam,val)
416      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
417      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(int2str(val)))
418  END IF
419  CALL bcast(val)
420END SUBROUTINE getinp_i
421
422SUBROUTINE getinp_r(nam, val, def, lDisp)
423   USE ioipsl_getincom, ONLY: getin
424   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
425   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
426   USE mod_phys_lmdz_transfert_para, ONLY : bcast
427   CHARACTER(LEN=*),  INTENT(IN)    :: nam
428   REAL,              INTENT(INOUT) :: val
429   REAL,    OPTIONAL, INTENT(IN)    :: def
430   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
431   LOGICAL :: lD
432!$OMP BARRIER
433   IF(is_mpi_root.AND.is_omp_root) THEN
434      IF(PRESENT(def)) val=def; CALL getin(nam,val)
435      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
436      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(real2str(val)))
437  END IF
438  CALL bcast(val)
439END SUBROUTINE getinp_r
440
441SUBROUTINE getinp_l(nam, val, def, lDisp)
442   USE ioipsl_getincom, ONLY: getin
443   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
444   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
445   USE mod_phys_lmdz_transfert_para, ONLY : bcast
446   CHARACTER(LEN=*),  INTENT(IN)    :: nam
447   LOGICAL,           INTENT(INOUT) :: val
448   LOGICAL, OPTIONAL, INTENT(IN)    :: def
449   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
450   LOGICAL :: lD
451!$OMP BARRIER
452   IF(is_mpi_root.AND.is_omp_root) THEN
453      IF(PRESENT(def)) val=def; CALL getin(nam,val)
454      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
455      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(bool2str(val)))
456  END IF
457  CALL bcast(val)
458END SUBROUTINE getinp_l
459
460END MODULE isotopes_mod
461#endif
462
463
Note: See TracBrowser for help on using the repository browser.