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

Last change on this file since 4155 was 4155, checked in by Sebastien Nguyen, 2 years ago

remove thread_private for ridicule parameters

  • Property svn:executable set to *
File size: 24.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
7   IMPLICIT NONE
8   INTERFACE get_in; MODULE PROCEDURE getinp_s, getinp_i, getinp_r, getinp_l;  END INTERFACE get_in
9   SAVE
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  LOGICAL, PARAMETER :: lOldCode=.FALSE.
15
16   !--- Isotopes indices (in [1,niso] ; non-existing => 0 index)
17   INTEGER, SAVE :: iso_eau, iso_HDO, iso_O18, iso_O17, iso_HTO
18!$OMP THREADPRIVATE(iso_eau, iso_HDO, iso_O18, iso_O17, iso_HTO)
19
20   INTEGER, SAVE :: ntracisoOR
21!$OMP THREADPRIVATE(ntracisoOR)
22
23   !--- Variables not depending on isotopes
24   REAL,    SAVE :: pxtmelt, pxtice, pxtmin, pxtmax
25!$OMP THREADPRIVATE(pxtmelt, pxtice, pxtmin, pxtmax)
26   REAL,    SAVE :: tdifexp, tv0cin, thumxt1
27!$OMP THREADPRIVATE(tdifexp, tv0cin, thumxt1)
28   INTEGER, SAVE :: ntot
29!$OMP THREADPRIVATE(ntot)
30   REAL,    SAVE :: h_land_ice
31!$OMP THREADPRIVATE(h_land_ice)
32   REAL,    SAVE :: P_veg
33!$OMP THREADPRIVATE(P_veg)
34   REAL,    SAVE :: musi, lambda_sursat
35!$OMP THREADPRIVATE(musi, lambda_sursat)
36   REAL,    SAVE :: Kd
37!$OMP THREADPRIVATE(Kd)
38   REAL,    SAVE :: rh_cste_surf_cond, T_cste_surf_cond
39!$OMP THREADPRIVATE(rh_cste_surf_cond, T_cste_surf_cond)
40   LOGICAL, SAVE :: bidouille_anti_divergence    ! T: regularly, xteau <- q to avoid slow drifts
41!$OMP THREADPRIVATE(bidouille_anti_divergence)
42   LOGICAL, SAVE :: essai_convergence            ! F: as in LMDZ without isotopes (bad for isotopes)
43!$OMP THREADPRIVATE(essai_convergence)
44   INTEGER, SAVE :: initialisation_iso           ! 0: file ; 1: R=0 ; 2: R=distill. Rayleigh ; 3: R=Rsmow
45!$OMP THREADPRIVATE(initialisation_iso)
46   INTEGER, SAVE :: modif_SST                    ! 0: default ; 1: modified SST ; 2, 3: SST profiles
47!$OMP THREADPRIVATE(modif_SST)
48   REAL,    SAVE :: deltaTtest                   ! Uniform modification of the SST
49!$OMP THREADPRIVATE(deltaTtest)
50   INTEGER, SAVE :: modif_sic                    ! Holes in the Sea Ice
51!$OMP THREADPRIVATE(modif_sic)
52   REAL,    SAVE :: deltasic                     ! Minimal holes fraction
53!$OMP THREADPRIVATE(deltasic)
54   REAL,    SAVE :: deltaTtestpoles
55!$OMP THREADPRIVATE(deltaTtestpoles)
56   REAL,    SAVE :: sstlatcrit, dsstlatcrit
57!$OMP THREADPRIVATE(sstlatcrit, dsstlatcrit)
58   REAL,    SAVE :: deltaO18_oce
59!$OMP THREADPRIVATE(deltaO18_oce)
60   INTEGER, SAVE :: albedo_prescrit              ! 0: default ; 1: constant albedo
61!$OMP THREADPRIVATE(albedo_prescrit)
62   REAL,    SAVE :: lon_min_albedo, lon_max_albedo, lat_min_albedo, lat_max_albedo
63!$OMP THREADPRIVATE(lon_min_albedo, lon_max_albedo, lat_min_albedo, lat_max_albedo)
64   REAL,    SAVE :: deltaP_BL,tdifexp_sol
65!$OMP THREADPRIVATE(deltaP_BL,tdifexp_sol)
66   INTEGER, SAVE :: ruissellement_pluie, alphak_stewart
67!$OMP THREADPRIVATE(ruissellement_pluie, alphak_stewart)
68   INTEGER, SAVE :: calendrier_guide
69!$OMP THREADPRIVATE(calendrier_guide)
70   INTEGER, SAVE :: cste_surf_cond
71!$OMP THREADPRIVATE(cste_surf_cond)
72   REAL,    SAVE :: mixlen
73!$OMP THREADPRIVATE(mixlen)
74   INTEGER, SAVE :: evap_cont_cste
75!$OMP THREADPRIVATE(evap_cont_cste)
76   REAL,    SAVE :: deltaO18_evap_cont, d_evap_cont
77!$OMP THREADPRIVATE(deltaO18_evap_cont, d_evap_cont)
78   INTEGER, SAVE :: nudge_qsol, region_nudge_qsol
79!$OMP THREADPRIVATE(nudge_qsol, region_nudge_qsol)
80   INTEGER, SAVE :: nlevmaxO17
81!$OMP THREADPRIVATE(nlevmaxO17)
82   INTEGER, SAVE :: no_pce
83!$OMP THREADPRIVATE(no_pce)
84   REAL,    SAVE :: A_satlim
85!$OMP THREADPRIVATE(A_satlim)
86   INTEGER, SAVE :: ok_restrict_A_satlim, modif_ratqs
87!$OMP THREADPRIVATE(ok_restrict_A_satlim, modif_ratqs)
88   REAL,    SAVE :: Pcrit_ratqs, ratqsbasnew
89!$OMP THREADPRIVATE(Pcrit_ratqs, ratqsbasnew)
90   REAL,    SAVE :: fac_modif_evaoce
91!$OMP THREADPRIVATE(fac_modif_evaoce)
92   INTEGER, SAVE :: ok_bidouille_wake
93!$OMP THREADPRIVATE(ok_bidouille_wake)
94   LOGICAL, SAVE :: cond_temp_env
95!$OMP THREADPRIVATE(cond_temp_env)
96
97   !--- Vectors of length "niso"
98   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
99                    tnat, toce, tcorr, tdifrel
100!$OMP THREADPRIVATE(tnat, toce, tcorr, tdifrel)
101   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
102                    talph1, talph2, talph3, talps1, talps2
103!$OMP THREADPRIVATE(talph1, talph2, talph3, talps1, talps2)
104   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
105                    tkcin0, tkcin1, tkcin2
106!$OMP THREADPRIVATE(tkcin0, tkcin1, tkcin2)
107   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
108                    alpha_liq_sol, Rdefault, Rmethox
109!$OMP THREADPRIVATE(alpha_liq_sol, Rdefault, Rmethox)
110   REAL, SAVE ::    fac_coeff_eq17_liq, fac_coeff_eq17_ice
111!$OMP THREADPRIVATE(fac_coeff_eq17_liq, fac_coeff_eq17_ice)
112
113   !--- Negligible lower thresholds: no need to check for absurd values under these lower limits
114   REAL, PARAMETER :: &
115      ridicule      = 1e-12,              & ! For mixing ratios
116      ridicule_rain = 1e-8,               & ! For rain fluxes (rain, zrfl...) in kg/s <-> 1e-3 mm/day
117      ridicule_evap = ridicule_rain*1e-2, & ! For evaporations                in kg/s <-> 1e-3 mm/day
118      ridicule_qsol = ridicule_rain,      & ! For qsol                        in kg <-> 1e-8 kg
119      ridicule_snow = ridicule_qsol         ! For snow                        in kg <-> 1e-8 kg
120   REAL, PARAMETER :: expb_max = 30.0
121
122   !--- Specific to HTO:
123   LOGICAL, SAVE :: ok_prod_nucl_tritium    !--- TRUE => HTO production by nuclear tests
124!$OMP THREADPRIVATE(ok_prod_nucl_tritium)
125   INTEGER, PARAMETER :: nessai = 486
126   INTEGER, DIMENSION(nessai), SAVE :: &
127                    day_nucl, month_nucl, year_nucl
128!$OMP THREADPRIVATE(day_nucl, month_nucl, year_nucl)
129   REAL,    DIMENSION(nessai), SAVE :: &
130                    lat_nucl, lon_nucl, zmin_nucl, zmax_nucl, HTO_nucl
131!$OMP THREADPRIVATE(lat_nucl, lon_nucl, zmin_nucl, zmax_nucl, HTO_nucl)
132 
133 
134CONTAINS
135
136SUBROUTINE iso_init()
137   USE ioipsl_getin_p_mod, ONLY: getin_p
138   USE infotrac_phy,       ONLY: ntiso, niso, getKey
139    USE strings_mod,       ONLY: maxlen
140   IMPLICIT NONE
141
142   !=== Local variables:
143   INTEGER :: ixt
144
145   !--- H2[18]O reference
146   REAL :: fac_enrichoce18, alpha_liq_sol_O18, &
147           talph1_O18, talph2_O18, talph3_O18, talps1_O18, talps2_O18, &
148           tkcin0_O18, tkcin1_O18, tkcin2_O18, tdifrel_O18 
149
150   !--- For H2[17]O
151   REAL    :: fac_kcin, pente_MWL
152     
153   !--- Sensitivity tests
154   LOGICAL, PARAMETER ::   ok_nocinsfc = .FALSE. ! if T: no kinetic effect in sfc evap
155   LOGICAL, PARAMETER ::   ok_nocinsat = .FALSE. ! if T: no sursaturation effect for ice
156   LOGICAL, PARAMETER :: Rdefault_smow = .FALSE. ! if T: Rdefault=smow; if F: nul
157
158   !--- For [3]H
159   INTEGER :: iessai
160
161   CHARACTER(LEN=maxlen) :: modname, sxt
162   REAL, ALLOCATABLE :: tmp(:)
163
164   modname = 'iso_init'
165   CALL msg('219: entree', modname)
166
167   !--- Memory allocations
168   IF(lOldCode) THEN
169   ALLOCATE(talph1(niso), tkcin0(niso),  talps1(niso),  tnat(niso))
170   ALLOCATE(talph2(niso), tkcin1(niso),  talps2(niso),  toce(niso))
171   ALLOCATE(talph3(niso), tkcin2(niso), tdifrel(niso), tcorr(niso))
172   ALLOCATE(alpha_liq_sol(niso),   Rdefault(niso),   Rmethox(niso))
173   END IF
174
175
176   !--------------------------------------------------------------
177   ! General:
178   !--------------------------------------------------------------
179
180   !--- Check number of isotopes
181   CALL msg('64: niso = '//TRIM(int2str(niso)), modname)
182
183   !--- Init de ntracisoOR: on ecrasera en cas de traceurs de tagging isotopiques
184   !                     (nzone>0) si complications avec ORCHIDEE
185   ntracisoOR = ntiso 
186
187   !--- Type of water isotopes:
188   iso_eau = strIdx(isoName, 'H2[16]O'); CALL msg('iso_eau='//int2str(iso_eau), modname)
189   iso_HDO = strIdx(isoName, 'H[2]HO');  CALL msg('iso_HDO='//int2str(iso_HDO), modname)
190   iso_O18 = strIdx(isoName, 'H2[18]O'); CALL msg('iso_O18='//int2str(iso_O18), modname)
191   iso_O17 = strIdx(isoName, 'H2[17]O'); CALL msg('iso_O17='//int2str(iso_O17), modname)
192   iso_HTO = strIdx(isoName, 'H[3]HO');  CALL msg('iso_HTO='//int2str(iso_HTO), modname)
193
194   ! initialisation
195   ! lecture des parametres isotopiques:
196   ! pour que ca marche en openMP, il faut utiliser getin_p. Car le getin ne peut
197   ! etre appele que par un thread a la fois, et ca pose tout un tas de problemes,
198   ! d'ou tout un tas de magouilles comme dans conf_phys_m. A terme, tout le monde
199   ! lira par getin_p.
200   CALL get_in('lambda',     lambda_sursat, 0.004)
201   CALL get_in('thumxt1',    thumxt1,       0.75*1.2)
202   CALL get_in('ntot',       ntot,          20,  .FALSE.)
203   CALL get_in('h_land_ice', h_land_ice,    20., .FALSE.)
204   CALL get_in('P_veg',      P_veg,         1.0, .FALSE.)
205   CALL get_in('bidouille_anti_divergence', bidouille_anti_divergence, .FALSE.)
206   CALL get_in('essai_convergence',         essai_convergence,         .FALSE.)
207   CALL get_in('initialisation_iso',        initialisation_iso,        0)
208
209!  IF(nzone>0 .AND. initialisation_iso==0) &
210!      CALL get_in('initialisation_isotrac',initialisation_isotrac)
211   CALL get_in('modif_sst',      modif_sst,         0)
212   CALL get_in('deltaTtest',     deltaTtest,      0.0)     !--- For modif_sst>=1
213   CALL get_in('deltaTtestpoles',deltaTtestpoles, 0.0)     !--- For modif_sst>=2
214   CALL get_in( 'sstlatcrit',    sstlatcrit,     30.0)     !--- For modif_sst>=3
215   CALL get_in('dsstlatcrit',   dsstlatcrit,      0.0)     !--- For modif_sst>=3
216#ifdef ISOVERIF
217   CALL msg('iso_init 270:  sstlatcrit='//real2str( sstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=2
218   CALL msg('iso_init 279: dsstlatcrit='//real2str(dsstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=3
219   IF(modif_sst >= 2 .AND. sstlatcrit < 0.0) STOP
220#endif             
221
222   CALL get_in('modif_sic', modif_sic,  0)
223   IF(modif_sic >= 1) &
224   CALL get_in('deltasic',  deltasic, 0.1)
225
226   CALL get_in('albedo_prescrit', albedo_prescrit, 0)
227   IF(albedo_prescrit == 1) THEN
228      CALL get_in('lon_min_albedo', lon_min_albedo, -200.)
229      CALL get_in('lon_max_albedo', lon_max_albedo,  200.)
230      CALL get_in('lat_min_albedo', lat_min_albedo, -100.)
231      CALL get_in('lat_max_albedo', lat_max_albedo,  100.)
232   END IF
233   IF(lOldCode) &
234   CALL get_in('deltaO18_oce',        deltaO18_oce,   0.0)
235   deltaO18_oce=0.0
236   CALL get_in('deltaP_BL',           deltaP_BL,     10.0)
237   CALL get_in('ruissellement_pluie', ruissellement_pluie, 0)
238   CALL get_in('alphak_stewart',      alphak_stewart,      1)
239   CALL get_in('tdifexp_sol',         tdifexp_sol,      0.67)
240   CALL get_in('calendrier_guide',    calendrier_guide,    0)
241   CALL get_in('cste_surf_cond',      cste_surf_cond,      0)
242   CALL get_in('mixlen',              mixlen,           35.0)
243   CALL get_in('evap_cont_cste',      evap_cont_cste,      0)
244   CALL get_in('deltaO18_evap_cont',  deltaO18_evap_cont,0.0)
245   CALL get_in('d_evap_cont',         d_evap_cont,       0.0)
246   CALL get_in('nudge_qsol',          nudge_qsol,          0)
247   CALL get_in('region_nudge_qsol',   region_nudge_qsol,   1)
248   nlevmaxO17 = 50
249   CALL msg('nlevmaxO17='//TRIM(int2str(nlevmaxO17)))
250   CALL get_in('no_pce',   no_pce,     0)
251   CALL get_in('A_satlim', A_satlim, 1.0)
252   CALL get_in('ok_restrict_A_satlim', ok_restrict_A_satlim, 0)
253#ifdef ISOVERIF
254   CALL msg(' 315: A_satlim='//real2str(A_satlim), modname, A_satlim > 1.0)
255   IF(A_satlim > 1.0) STOP
256#endif
257!  CALL get_in('slope_limiterxy',   slope_limiterxy,  2.0)
258!  CALL get_in('slope_limiterz',    slope_limiterz,   2.0)
259   CALL get_in('modif_ratqs',       modif_ratqs,        0)
260   CALL get_in('Pcrit_ratqs',       Pcrit_ratqs,    500.0)
261   CALL get_in('ratqsbasnew',       ratqsbasnew,     0.05)
262   CALL get_in('fac_modif_evaoce',  fac_modif_evaoce, 1.0)
263   CALL get_in('ok_bidouille_wake', ok_bidouille_wake,  0)
264   ! si oui, la temperature de cond est celle de l'environnement, pour eviter
265   ! bugs quand temperature dans ascendances convs est mal calculee
266   CALL get_in('cond_temp_env',        cond_temp_env,        .FALSE.)
267   IF(ANY(isoName == 'H[3]HO')) &
268   CALL get_in('ok_prod_nucl_tritium', ok_prod_nucl_tritium, .FALSE., .FALSE.)
269
270   !--------------------------------------------------------------
271   ! Parameters that do not depend on the nature of water isotopes:
272   !--------------------------------------------------------------
273   ! -- temperature at which ice condensate starts to form (valeur ECHAM?):
274   pxtmelt = 273.15
275
276   ! -- temperature at which all condensate is ice:
277   pxtice  = 273.15-10.0
278
279   !- -- test PHASE
280!   pxtmelt = 273.15 - 10.0
281!   pxtice  = 273.15 - 30.0
282
283   ! -- minimum temperature to calculate fractionation coeff
284   pxtmin = 273.15 - 120.0   ! On ne calcule qu'au dessus de -120°C
285   pxtmax = 273.15 +  60.0   ! On ne calcule qu'au dessus de +60°C
286   !    Remarque: les coeffs ont ete mesures seulement jusq'à -40!
287
288   ! -- a constant for alpha_eff for equilibrium below cloud base:
289   tdifexp = 0.58
290   tv0cin  = 7.0
291
292   ! facteurs lambda et mu dans Si=musi-lambda*T
293   musi=1.0
294   if (ok_nocinsat) lambda_sursat = 0.0          ! no sursaturation effect
295
296   ! diffusion dans le sol
297   Kd=2.5e-9 ! m2/s   
298
299   ! cas où cste_surf_cond: on met rhs ou/et Ts cste pour voir
300   rh_cste_surf_cond = 0.6
301    T_cste_surf_cond = 288.0
302   
303   CALL msg('iso_O18, iso_HDO, iso_eau = '//TRIM(strStack(int2str([iso_O18, iso_HDO, iso_eau]))), modname)
304
305   !--------------------------------------------------------------
306   ! Parameters that depend on the nature of water isotopes:
307   !--------------------------------------------------------------
308
309   !===========================================================================================================================
310   IF(lOldCode) THEN
311   !===========================================================================================================================
312
313   ! Local constants
314   fac_enrichoce18 = 0.0005            ! Then: tcorO18 = 1 + fac_enrichoce18
315                                       !       tcorD   = 1 + fac_enrichoce18*8
316                                       !       tcorO17 = 1 + fac_enrichoce18*0.528
317   alpha_liq_sol_O18 = 1.00291         ! From Lehmann & Siegenthaler, 1991,
318                                       ! Journal of Glaciology, vol 37, p 23
319   talph1_O18 = 1137.  ; talph2_O18 = -0.4156   ; talph3_O18 = -2.0667E-3
320   talps1_O18 = 11.839 ; talps2_O18 = -0.028244
321   tkcin0_O18 = 0.006  ; tkcin1_O18 =  0.000285 ; tkcin2_O18 =  0.00082
322   tdifrel_O18 = 1./0.9723
323
324   ! ln(alphaeq) ratio between O18 and O17
325   fac_coeff_eq17_liq = 0.529          ! From Amaelle
326  !fac_coeff_eq17_ice = 0.528          ! slope MWL
327   fac_coeff_eq17_ice = 0.529
328
329   !--- Kinetic factor for surface evaporation:
330   ! (cf: kcin = tkcin0                  if |V|<tv0cin
331   !      kcin = tkcin1*|Vsurf| + tkcin2 if |V|>tv0cin )
332   ! (Rq: formula discontinuous for |V|=tv0cin... )       
333
334   DO ixt = 1, niso
335      sxt=int2str(ixt)
336      CALL msg('80: ixt='//TRIM(int2str(ixt)),modname)
337
338      Rdefault(ixt) = 0.0
339      IF(ixt == iso_HTO) THEN          !=== H[3]HO
340         tdifrel(ixt) = 1./0.968
341         tkcin0(ixt) = 0.01056
342         tkcin1(ixt) = 0.0005016
343         tkcin2(ixt) = 0.0014432
344         tnat  (ixt) = 0.
345         toce  (ixt) = 4.0E-19         ! Ratio T/H = 0.2 TU, Dreisigacker and Roether 1978
346        !toce  (ixt) = 2.2222E-8       ! Corrected by Alex Cauquoin
347        !toce  (ixt) = 1.0E-18         ! Ratio 3H/1H ocean
348         tcorr (ixt) = 1.
349         talph1(ixt) = 46480. ; talph2(ixt) = -103.87 ; talph3(ixt) = 0.
350         talps1(ixt) = 46480. ; talps2(ixt) = -103.87
351         alpha_liq_sol(ixt) = 1.
352         Rmethox(ixt) = 0.0
353      ELSE IF(ixt == iso_O17) THEN     !=== H2[17]O
354         tdifrel(ixt)=1./0.98555       ! Used in 1D and in LdG's model
355        !tdifrel(ixt)=1./0.985452      ! From Amaelle
356        !fac_kcin=0.5145               ! From Amaelle
357         fac_kcin= (tdifrel(ixt)-1.0)/(tdifrel_O18-1.0)
358         tkcin0(ixt) = tkcin0_O18*fac_kcin
359         tkcin1(ixt) = tkcin1_O18*fac_kcin
360         tkcin2(ixt) = tkcin2_O18*fac_kcin
361         tnat  (ixt) = 0.004/100.      ! O17 = 0.004% of oxygen
362         pente_MWL=0.528
363         toce  (ixt) = tnat(ixt)*(1.0+deltaO18_oce/1000.0)**pente_MWL
364         tcorr (ixt) = 1.0+fac_enrichoce18*pente_MWL  ! From Amaelle           
365         talph1(ixt) = talph1_O18 ; talph2(ixt) = talph2_O18 ; talph3(ixt) = talph3_O18
366         talps1(ixt) = talps1_O18 ; talps2(ixt) = talps2_O18     
367         alpha_liq_sol(ixt) = (alpha_liq_sol_O18)**fac_coeff_eq17_liq
368         IF(Rdefault_smow) Rdefault(ixt) = tnat(ixt)*(-3.15/1000.0+1.0)
369         Rmethox(ixt) = (230./1000.+1.)*tnat(ixt)     ! Zahn et al 2006
370      ELSE IF(ixt == iso_O18) THEN     !=== H2[18]O
371         tdifrel(ixt) = tdifrel_O18
372         tkcin0(ixt) = tkcin0_O18
373         tkcin1(ixt) = tkcin1_O18
374         tkcin2(ixt) = tkcin2_O18
375         tnat  (ixt) = 2005.2E-6
376         toce  (ixt) = tnat(ixt)*(1.0+deltaO18_oce/1000.0)
377         tcorr (ixt) = 1.0+fac_enrichoce18
378         talph1(ixt) = talph1_O18 ; talph2(ixt) = talph2_O18 ; talph3(ixt) = talph3_O18
379         talps1(ixt) = talps1_O18 ; talps2(ixt) = talps2_O18
380         alpha_liq_sol(ixt) = alpha_liq_sol_O18   
381         IF(Rdefault_smow) Rdefault(ixt) = tnat(ixt)*(-6.0/1000.0+1.0)
382         Rmethox(ixt) = (130./1000.+1.)*tnat(ixt) ! Zahn et al 2006   
383      ELSE IF(ixt == iso_HDO) THEN     !=== H[2]HO
384         tdifrel(ixt) = 1./0.9755
385        !fac_kcin=0.88
386         fac_kcin= (tdifrel(ixt)-1.0)/(tdifrel_O18-1.0)
387         tkcin0(ixt) = tkcin0_O18*fac_kcin
388         tkcin1(ixt) = tkcin1_O18*fac_kcin
389         tkcin2(ixt) = tkcin2_O18*fac_kcin
390         tnat  (ixt) = 155.76E-6
391         pente_MWL = 8.0
392         toce  (ixt) = tnat(ixt)*(1.0+pente_MWL*deltaO18_oce/1000.0)
393         tcorr (ixt) = 1.0+fac_enrichoce18*pente_MWL         
394         talph1(ixt) = 24844. ; talph2(ixt) = -76.248 ; talph3(ixt) = 52.612E-3
395         talps1(ixt) = 16288. ; talps2(ixt) = -0.0934
396        !alpha_liq_sol(ixt)=1.0192 ZX  ! From Weston, Ralph, 1955
397         alpha_liq_sol(ixt)=1.0212     ! From Lehmann & Siegenthaler, 1991,
398                                       ! Journal of Glaciology, vol 37, p 23
399         IF(Rdefault_smow) Rdefault(ixt) = tnat(ixt)*((-6.0*pente_MWL+10.0)/1000.0+1.0)
400         Rmethox(ixt) = tnat(ixt)*(-25.0/1000.+1.) ! Zahn et al 2006
401      ELSE IF(ixt  == iso_eau) THEN    !=== H2O[16]
402         tkcin0(ixt) = 0.0
403         tkcin1(ixt) = 0.0
404         tkcin2(ixt) = 0.0
405         tnat  (ixt) = 1.
406         toce  (ixt)=tnat(ixt)
407         tcorr (ixt) = 1.0
408         tdifrel(ixt) = 1.
409         talph1(ixt) = 0. ; talph2(ixt) = 0. ; talph3(ixt) = 0.
410         talps1(ixt) = 0. ; talps2(ixt) = 0.
411         alpha_liq_sol(ixt)=1.
412         IF(Rdefault_smow) Rdefault(ixt) = tnat(ixt)*1.0
413         Rmethox(ixt) = 1.0
414      END IF
415   END DO
416   !===========================================================================================================================
417   ELSE
418   !===========================================================================================================================
419
420   IF(getKey('tnat',    tnat,    isoName)) CALL abort_physic(modname, 'can''t get tnat',    1)
421   IF(getKey('toce',    toce,    isoName)) CALL abort_physic(modname, 'can''t get toce',    1)
422   IF(getKey('tcorr',   tcorr,   isoName)) CALL abort_physic(modname, 'can''t get tcorr',   1)
423   IF(getKey('talph1',  talph1,  isoName)) CALL abort_physic(modname, 'can''t get talph1',  1)
424   IF(getKey('talph2',  talph2,  isoName)) CALL abort_physic(modname, 'can''t get talph2',  1)
425   IF(getKey('talph3',  talph3,  isoName)) CALL abort_physic(modname, 'can''t get talph3',  1)
426   IF(getKey('talps1',  talps1,  isoName)) CALL abort_physic(modname, 'can''t get talps1',  1)
427   IF(getKey('talps2',  talps2,  isoName)) CALL abort_physic(modname, 'can''t get talps2',  1)
428   IF(getKey('tkcin0',  tkcin0,  isoName)) CALL abort_physic(modname, 'can''t get tkcin0',  1)
429   IF(getKey('tkcin1',  tkcin1,  isoName)) CALL abort_physic(modname, 'can''t get tkcin1',  1)
430   IF(getKey('tkcin2',  tkcin2,  isoName)) CALL abort_physic(modname, 'can''t get tkcin2',  1)
431   IF(getKey('tdifrel', tdifrel, isoName)) CALL abort_physic(modname, 'can''t get tdifrel', 1)
432   DO ixt = 1, niso
433      IF     (ixt == iso_HTO) THEN; tdifrel(ixt) = 1./0.968
434      ELSE IF(ixt == iso_HDO) THEN; tdifrel(ixt) = 1./0.9755
435      ELSE IF(ixt == iso_O17) THEN; tdifrel(ixt) = 1./0.98555
436      ELSE IF(ixt == iso_O18) THEN; tdifrel(ixt) = 1./0.9723
437      ELSE IF(ixt == iso_eau) THEN; tdifrel(ixt) = 1.; END IF
438   END DO
439   IF(getKey('alpha_liq_sol', alpha_liq_sol, isoName)) CALL abort_physic(modname, 'can''t get alpha_liq_sol',  1)
440   IF(getKey('Rdefault',Rdefault,isoName)) CALL abort_physic(modname, 'can''t get Rdefault',1)
441   IF(getKey('Rmethox', Rmethox, isoName)) CALL abort_physic(modname, 'can''t get Rmethox', 1)
442   IF(.NOT.Rdefault_smow) Rdefault(:) = 0.0
443
444   !===========================================================================================================================
445   END IF
446   !===========================================================================================================================
447
448   !--- Sensitivity test: no kinetic effect in sfc evaporation
449   IF(ok_nocinsfc) THEN
450      tkcin0(1:niso) = 0.0
451      tkcin1(1:niso) = 0.0
452      tkcin2(1:niso) = 0.0
453   END IF
454
455   CALL msg('285: verif initialisation:', modname)
456   DO ixt=1,niso
457      sxt=int2str(ixt)
458      CALL msg(' * isoName('//TRIM(sxt)//') = <'//TRIM(isoName(ixt))//'>',  modname)
459      CALL msg(  '    tnat('//TRIM(sxt)//') = '//TRIM(real2str(tnat(ixt))), modname)
460!     CALL msg('    alpha_liq_sol('//TRIM(sxt)//') = '//TRIM(real2str(alpha_liq_sol(ixt))), modname)
461!     CALL msg(        '   tkcin0('//TRIM(sxt)//') = '//TRIM(real2str(tkcin0(ixt))),        modname)
462!     CALL msg(       '   tdifrel('//TRIM(sxt)//') = '//TRIM(real2str(tdifrel(ixt))),       modname)
463   END DO
464   CALL msg('69:     lambda = '//TRIM(real2str(lambda_sursat)), modname)
465   CALL msg('69:    thumxt1 = '//TRIM(real2str(thumxt1)),       modname)
466   CALL msg('69: h_land_ice = '//TRIM(real2str(h_land_ice)),    modname)
467   CALL msg('69:      P_veg = '//TRIM(real2str(P_veg)),         modname)
468
469END SUBROUTINE iso_init
470
471
472SUBROUTINE getinp_s(nam, val, def, lDisp)
473   USE ioipsl_getincom, ONLY: getin
474   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
475   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
476   USE mod_phys_lmdz_transfert_para, ONLY : bcast
477   CHARACTER(LEN=*),  INTENT(IN)    :: nam
478   CHARACTER(LEN=*),  INTENT(INOUT) :: val
479   CHARACTER(LEN=*),  INTENT(IN)    :: def
480   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
481   LOGICAL :: lD
482!$OMP BARRIER
483   IF(.NOT.(is_mpi_root.AND.is_omp_root)) RETURN
484   val=def; CALL getin(nam,val); CALL bcast(val)
485   lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
486   IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(val))
487END SUBROUTINE getinp_s
488
489SUBROUTINE getinp_i(nam, val, def, lDisp)
490   USE ioipsl_getincom, ONLY: getin
491   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
492   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
493   USE mod_phys_lmdz_transfert_para, ONLY : bcast
494   CHARACTER(LEN=*),  INTENT(IN)    :: nam
495   INTEGER,           INTENT(INOUT) :: val
496   INTEGER,           INTENT(IN)    :: def
497   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
498   LOGICAL :: lD
499!$OMP BARRIER
500   IF(.NOT.(is_mpi_root.AND.is_omp_root)) RETURN
501   val=def; CALL getin(nam,val); CALL bcast(val)
502   lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
503   IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(int2str(val)))
504END SUBROUTINE getinp_i
505
506SUBROUTINE getinp_r(nam, val, def, lDisp)
507   USE ioipsl_getincom, ONLY: getin
508   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
509   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
510   USE mod_phys_lmdz_transfert_para, ONLY : bcast
511   CHARACTER(LEN=*),  INTENT(IN)    :: nam
512   REAL,              INTENT(INOUT) :: val
513   REAL,              INTENT(IN)    :: def
514   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
515   LOGICAL :: lD
516!$OMP BARRIER
517   IF(.NOT.(is_mpi_root.AND.is_omp_root)) RETURN
518   val=def; CALL getin(nam,val); CALL bcast(val)
519   lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
520   IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(real2str(val)))
521END SUBROUTINE getinp_r
522
523SUBROUTINE getinp_l(nam, val, def, lDisp)
524   USE ioipsl_getincom, ONLY: getin
525   USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
526   USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
527   USE mod_phys_lmdz_transfert_para, ONLY : bcast
528   CHARACTER(LEN=*),  INTENT(IN)    :: nam
529   LOGICAL,           INTENT(INOUT) :: val
530   LOGICAL,           INTENT(IN)    :: def
531   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
532   LOGICAL :: lD
533!$OMP BARRIER
534   IF(.NOT.(is_mpi_root.AND.is_omp_root)) RETURN
535   val=def; CALL getin(nam,val); CALL bcast(val)
536   lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
537   IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(bool2str(val)))
538END SUBROUTINE getinp_l
539
540END MODULE isotopes_mod
541#endif
542
543
Note: See TracBrowser for help on using the repository browser.