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

Last change on this file since 5786 was 5756, checked in by dcugnet, 5 months ago

Add "isoFamilies", the list of defined isotopes families (==H2O? for now).

  • Property svn:executable set to *
File size: 19.8 KB
Line 
1#ifdef ISO
2! $Id: $
3
4MODULE isotopes_mod
5   USE strings_mod,  ONLY: msg, num2str, maxlen, strIdx, strStack
6   USE infotrac_phy, ONLY: isoName, niso, ntiso, nbIso, isoFamilies, isoSelect, isoCheck
7   USE iso_params_mod
8   USE ioipsl_getin_p_mod, ONLY : getin_p
9   IMPLICIT NONE
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, ii
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(num2str(niso)), modname)
176
177   DO ii = 1, nbIso
178      CALL msg('Can''t select isotopes class "'//TRIM(isoFamilies(ii))//'"', modname, isoSelect(ii, lVerbose=.TRUE.))
179
180!==============================================================================================================================
181      IF(isoFamilies(ii) == 'H2O') THEN
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, 'H216O'); CALL msg('iso_eau='//num2str(iso_eau), modname)
189         iso_HDO = strIdx(isoName, 'HDO');   CALL msg('iso_HDO='//num2str(iso_HDO), modname)
190         iso_O18 = strIdx(isoName, 'H218O'); CALL msg('iso_O18='//num2str(iso_O18), modname)
191         iso_O17 = strIdx(isoName, 'H217O'); CALL msg('iso_O17='//num2str(iso_O17), modname)
192         iso_HTO = strIdx(isoName, 'HTO');   CALL msg('iso_HTO='//num2str(iso_HTO), modname)
193
194         !--- Initialisation: reading the isotopic parameters.
195         CALL getin_p('lambda',     lambda_sursat, 0.004); IF(ok_nocinsat) lambda_sursat = 0.
196         CALL getin_p('thumxt1',    thumxt1,       0.75*1.2)
197         CALL getin_p('ntot',       ntot,          20,  lDisp=.FALSE.)
198         CALL getin_p('h_land_ice', h_land_ice,    20., lDisp=.FALSE.)
199         CALL getin_p('P_veg',      P_veg,         1.0, lDisp=.FALSE.)
200         CALL getin_p('bidouille_anti_divergence', bidouille_anti_divergence, .FALSE.)
201         CALL getin_p('essai_convergence',         essai_convergence,         .FALSE.)
202         CALL getin_p('initialisation_iso',        initialisation_iso,        0)
203
204!        IF(nzone>0 .AND. initialisation_iso==0) &
205!           CALL getin_p('initialisation_isotrac',initialisation_isotrac)
206         CALL getin_p('modif_sst',      modif_sst,         0)
207         CALL getin_p('deltaTtest',     deltaTtest,      0.0)     !--- For modif_sst>=1
208         CALL getin_p('deltaTtestpoles',deltaTtestpoles, 0.0)     !--- For modif_sst>=2
209         CALL getin_p( 'sstlatcrit',    sstlatcrit,     30.0)     !--- For modif_sst>=3
210         CALL getin_p('dsstlatcrit',   dsstlatcrit,      0.0)     !--- For modif_sst>=3
211         IF(isoCheck) THEN
212         CALL msg('iso_init 270:  sstlatcrit='//num2str( sstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=2
213         CALL msg('iso_init 279: dsstlatcrit='//num2str(dsstlatcrit), modname, sstlatcrit < 0.0) !--- For modif_sst>=3
214         IF(modif_sst >= 2 .AND. sstlatcrit < 0.0) STOP
215         END IF
216         CALL getin_p('modif_sic', modif_sic,  0)
217         IF(modif_sic >= 1) &
218         CALL getin_p('deltasic',  deltasic, 0.1)
219
220         CALL getin_p('albedo_prescrit', albedo_prescrit, 0)
221         IF(albedo_prescrit == 1) THEN
222            CALL getin_p('lon_min_albedo', lon_min_albedo, -200.)
223            CALL getin_p('lon_max_albedo', lon_max_albedo,  200.)
224            CALL getin_p('lat_min_albedo', lat_min_albedo, -100.)
225            CALL getin_p('lat_max_albedo', lat_max_albedo,  100.)
226         END IF
227         CALL getin_p('deltaO18_oce',        deltaO18_oce,   0.0)
228         CALL getin_p('deltaP_BL',           deltaP_BL,     10.0)
229         CALL getin_p('ruissellement_pluie', ruissellement_pluie, 0)
230         CALL getin_p('alphak_stewart',      alphak_stewart,      1)
231         CALL getin_p('tdifexp_sol',         tdifexp_sol,      0.67)
232         CALL getin_p('calendrier_guide',    calendrier_guide,    0)
233         CALL getin_p('cste_surf_cond',      cste_surf_cond,      0)
234         CALL getin_p('mixlen',              mixlen,           35.0)
235         CALL getin_p('evap_cont_cste',      evap_cont_cste,      0)
236         CALL getin_p('deltaO18_evap_cont',  deltaO18_evap_cont,0.0)
237         CALL getin_p('d_evap_cont',         d_evap_cont,       0.0)
238         CALL getin_p('nudge_qsol',          nudge_qsol,          0)
239         CALL getin_p('region_nudge_qsol',   region_nudge_qsol,   1)
240         nlevmaxO17 = 50
241         CALL msg('nlevmaxO17='//TRIM(num2str(nlevmaxO17)))
242         CALL getin_p('no_pce',   no_pce,     0)
243         CALL getin_p('A_satlim', A_satlim, 1.0)
244         CALL getin_p('ok_restrict_A_satlim', ok_restrict_A_satlim, 0)
245         IF(isoCheck) THEN
246         CALL msg(' 315: A_satlim='//TRIM(num2str(A_satlim)), modname, A_satlim > 1.0)
247         IF(A_satlim > 1.0) STOP
248         END IF
249!        CALL getin_p('slope_limiterxy',   slope_limiterxy,  2.0)
250!        CALL getin_p('slope_limiterz',    slope_limiterz,   2.0)
251         CALL getin_p('modif_ratqs',       modif_ratqs,        0)
252         CALL getin_p('Pcrit_ratqs',       Pcrit_ratqs,    500.0)
253         CALL getin_p('ratqsbasnew',       ratqsbasnew,     0.05)
254         CALL getin_p('fac_modif_evaoce',  fac_modif_evaoce, 1.0)
255         CALL getin_p('ok_bidouille_wake', ok_bidouille_wake,  0)
256         ! si oui, la temperature de cond est celle de l'environnement, pour eviter
257         ! bugs quand temperature dans ascendances convs est mal calculee
258         CALL getin_p('cond_temp_env',        cond_temp_env,        .FALSE.)
259         IF(ANY(isoName == 'HTO')) &
260         CALL getin_p('ok_prod_nucl_tritium', ok_prod_nucl_tritium, .FALSE., lDisp=.FALSE.)
261         CALL getin_p('tnateq1', ltnat1, .TRUE.)
262
263         CALL msg('iso_O18, iso_HDO, iso_eau = '//TRIM(strStack(num2str([iso_O18, iso_HDO, iso_eau]))), modname)
264
265         !--------------------------------------------------------------
266         ! Parameters that depend on the nature of water isotopes:
267         !--------------------------------------------------------------
268         ALLOCATE(tnat (niso), talph1(niso),  talps1(niso), tkcin0(niso), tdifrel (niso), alpha        (niso))
269         ALLOCATE(toce (niso), talph2(niso),  talps2(niso), tkcin1(niso), Rdefault(niso), alpha_liq_sol(niso))
270         ALLOCATE(tcorr(niso), talph3(niso),                tkcin2(niso), Rmethox (niso))
271
272         !=== H216O
273         is = iso_eau
274         IF(is /= 0) THEN
275            tdifrel (is) = 1.0
276            alpha   (is) = alpha_ideal_H216O
277            tnat    (is) = tnat_H216O; IF(ltnat1) tnat(is) = 1.0
278            toce    (is) = tnat(is)
279            tcorr   (is) = 1.0
280            talph1  (is) = 0.0;  talps1(is) = 0.0;  tkcin0(is)  = 0.0
281            talph2  (is) = 0.0;  talps2(is) = 0.0;  tkcin1(is)  = 0.0
282            talph3  (is) = 0.0;                     tkcin2(is)  = 0.0
283            Rdefault(is) = tnat(is)*1.0
284            Rmethox (is) = 1.0
285            alpha_liq_sol(is) = 1.0
286         END IF
287
288         !=== H217O
289         is = iso_O17
290         IF(is /= 0) THEN; pente_MWL = 0.528
291            tdifrel (is) = 1./0.98555  ! used in 1D and in LdG model ; tdifrel=1./0.985452: from Amaelle
292            alpha   (is) = alpha_ideal_H217O
293            tnat    (is) = tnat_H217O; IF(ltnat1) tnat(is) = 1.0
294            toce    (is) = tnat(is)*(1.0+deltaO18_oce/1000.0)**pente_MWL
295            tcorr   (is) = 1.0+fac_enrichoce18*pente_MWL
296            fac_kcin = (tdifrel(is)-1.0)/(tdifrel_O18-1.0)           ! fac_kcin=0.5145:     from Amaelle
297            talph1  (is) = talph1_O18;  talps1(is) = talps1_O18;  tkcin0(is) = tkcin0_O18*fac_kcin
298            talph2  (is) = talph2_O18;  talps2(is) = talps2_O18;  tkcin1(is) = tkcin1_O18*fac_kcin
299            talph3  (is) = talph3_O18;                            tkcin2(is) = tkcin2_O18*fac_kcin
300            Rdefault(is) = tnat(is)*(1.0-3.15/1000.)
301            Rmethox (is) = tnat(is)*(1.0+230./1000.)
302            alpha_liq_sol(is) = alpha_liq_sol_O18**fac_coeff_eq17_liq
303         END IF
304
305         !=== H218O
306         is = iso_O18
307         IF(is /= 0) THEN
308            tdifrel (is) = tdifrel_O18
309            alpha   (is) = alpha_ideal_H218O
310            tnat    (is) = tnat_H218O; IF(ltnat1) tnat(is) = 1.0
311            toce    (is) = tnat(is)*(1.0+deltaO18_oce/1000.0)
312            tcorr   (is) = 1.0+fac_enrichoce18
313            talph1  (is) = talph1_O18;  talps1(is) = talps1_O18;  tkcin0(is) = tkcin0_O18
314            talph2  (is) = talph2_O18;  talps2(is) = talps2_O18;  tkcin1(is) = tkcin1_O18
315            talph3  (is) = talph3_O18;                            tkcin2(is) = tkcin2_O18
316            Rdefault(is) = tnat(is)*(1.0-6.00/1000.)
317            Rmethox (is) = tnat(is)*(1.0+130./1000.)  ! Zahn & al. 2006
318            alpha_liq_sol(is) = alpha_liq_sol_O18
319         END IF
320
321         !=== HDO
322         is = iso_HDO
323         IF(is /= 0) THEN; pente_MWL = 8.0
324            tdifrel (is) = 1./0.9755                  ! fac_kcin=0.88
325            alpha   (is) = alpha_ideal_HDO
326            tnat    (is) = tnat_HDO; IF(ltnat1) tnat(is) = 1.0
327            toce    (is) = tnat(is)*(1.0+deltaO18_oce/1000.0*pente_MWL)
328            tcorr   (is) = 1.0+fac_enrichoce18*pente_MWL
329            fac_kcin = (tdifrel(is)-1.0)/(tdifrel_O18-1.0)
330            talph1  (is) = 24844.;      talps1(is) = 16288.;      tkcin0(is) = tkcin0_O18*fac_kcin
331            talph2  (is) = -76.248;     talps2(is) = -0.0934;     tkcin1(is) = tkcin1_O18*fac_kcin
332            talph3  (is) = 52.612E-3;                             tkcin2(is) = tkcin2_O18*fac_kcin
333            Rdefault(is) = tnat(is)*(1.0+(10.0-6.0*pente_MWL)/1000.)
334            Rmethox (is) = tnat(is)*(1.0-25.0/1000.)
335            alpha_liq_sol(is) = 1.0212      ! Lehmann & Siegenthaler, 1991, Jo. of Glaciology, vol 37, p 23
336                                            ! alpha_liq_sol=1.0192: Weston, Ralph, 1955
337         END IF
338
339         !=== HTO
340         is = iso_HTO
341         IF(is /= 0) THEN
342            tdifrel (is) = 1./0.968
343            alpha   (is) = alpha_ideal_HTO
344            tnat    (is) = tnat_HTO; IF(ltnat1) tnat(is) = 1.0
345            toce    (is) = 4.0E-19          ! ratio T/H = 0.2 TU Dreisigacker & Roether 1978
346            tcorr   (is) = 1.0
347            talph1  (is) = 46480.;      talps1(is) = 46480.;      tkcin0(is) = 0.01056
348            talph2  (is) = -103.87;     talps2(is) = -103.87;     tkcin1(is) = 0.0005016
349            talph3  (is) = 0.0;                                   tkcin2(is) = 0.0014432
350            Rdefault(is) = 0.0
351            Rmethox (is) = 0.0
352            alpha_liq_sol(is) = 1.0
353         END IF
354
355         IF(.NOT. Rdefault_smow) THEN
356            Rdefault(:) = 0.0; IF(iso_eau > 0) Rdefault(iso_eau) = 1.0
357         END IF
358         WRITE(*,*) 'Rdefault = ',Rdefault
359         WRITE(*,*) 'toce = ', toce
360
361         !--- Sensitivity test: no kinetic effect in sfc evaporation
362         IF(ok_nocinsfc) THEN
363            tkcin0(1:niso) = 0.0
364            tkcin1(1:niso) = 0.0
365            tkcin2(1:niso) = 0.0
366         END IF
367
368         CALL msg('285: verif initialisation:', modname)
369         DO ixt=1,niso
370            sxt=num2str(ixt)
371            CALL msg(' * isoName('//TRIM(sxt)//') = <'//TRIM(isoName(ixt))//'>',  modname)
372            CALL msg(  '    tnat('//TRIM(sxt)//') = '//TRIM(num2str(tnat(ixt))), modname)
373!           CALL msg('    alpha_liq_sol('//TRIM(sxt)//') = '//TRIM(num2str(alpha_liq_sol(ixt))), modname)
374!           CALL msg(        '   tkcin0('//TRIM(sxt)//') = '//TRIM(num2str(tkcin0(ixt))),        modname)
375!           CALL msg(       '   tdifrel('//TRIM(sxt)//') = '//TRIM(num2str(tdifrel(ixt))),       modname)
376         END DO
377         CALL msg('69:     lambda = '//TRIM(num2str(lambda_sursat)), modname)
378         CALL msg('69:    thumxt1 = '//TRIM(num2str(thumxt1)),       modname)
379         CALL msg('69: h_land_ice = '//TRIM(num2str(h_land_ice)),    modname)
380         CALL msg('69:      P_veg = '//TRIM(num2str(P_veg)),         modname)
381!==============================================================================================================================
382      ELSE
383!==============================================================================================================================
384         CALL abort_physic('"isotopes_mod" is not set up yet for isotopes family "'//TRIM(isoFamilies(ii))//'"', modname, 1)
385!==============================================================================================================================
386      END IF
387!==============================================================================================================================
388   END DO
389
390END SUBROUTINE iso_init
391
392END MODULE isotopes_mod
393#endif
394
395
Note: See TracBrowser for help on using the repository browser.