source: LMDZ6/branches/Amaury_dev/libf/phylmdiso/isotopes_mod.F90 @ 5209

Last change on this file since 5209 was 5158, checked in by abarral, 7 weeks ago

Add missing klon on strataer_emiss_mod.F90
Correct various missing explicit declarations
Replace tabs by spaces (tabs are not part of the fortran charset)
Continue cleaning modules
Removed unused arguments and variables

  • Property svn:executable set to *
File size: 20.4 KB
RevLine 
[3927]1#ifdef ISO
2! $Id: $
3
4MODULE isotopes_mod
[5117]5   USE lmdz_strings,  ONLY: msg, real2str, int2str, bool2str, maxlen, strIdx, strStack
[4149]6   USE infotrac_phy, ONLY: isoName
[4143]7   IMPLICIT NONE
8   INTERFACE get_in; MODULE PROCEDURE getinp_s, getinp_i, getinp_r, getinp_l;  END INTERFACE get_in
[3927]9
[4143]10  !--- Contains all isotopic variables + their initialization
11  !--- Isotopes-specific routines are in isotopes_routines_mod to avoid circular dependencies with isotopes_verif_mod.
[3927]12
[4143]13   !--- Isotopes indices (in [1,niso] ; non-existing => 0 index)
14   INTEGER, SAVE :: iso_eau, iso_HDO, iso_O18, iso_O17, iso_HTO
15!$OMP THREADPRIVATE(iso_eau, iso_HDO, iso_O18, iso_O17, iso_HTO)
[3927]16
[4143]17   INTEGER, SAVE :: ntracisoOR
[3927]18!$OMP THREADPRIVATE(ntracisoOR)
19
[4143]20   !--- Variables not depending on isotopes
[4982]21   REAL,    SAVE :: thumxt1
22   !$OMP THREADPRIVATE(thumxt1)
[4143]23   INTEGER, SAVE :: ntot
[3927]24!$OMP THREADPRIVATE(ntot)
[4143]25   REAL,    SAVE :: h_land_ice
[3927]26!$OMP THREADPRIVATE(h_land_ice)
[4143]27   REAL,    SAVE :: P_veg
[3927]28!$OMP THREADPRIVATE(P_veg)
[4982]29   REAL,    SAVE :: lambda_sursat
30!$OMP THREADPRIVATE(lambda_sursat)
[4143]31   LOGICAL, SAVE :: bidouille_anti_divergence    ! T: regularly, xteau <- q to avoid slow drifts
[3927]32!$OMP THREADPRIVATE(bidouille_anti_divergence)
[4143]33   LOGICAL, SAVE :: essai_convergence            ! F: as in LMDZ without isotopes (bad for isotopes)
[3927]34!$OMP THREADPRIVATE(essai_convergence)
[4143]35   INTEGER, SAVE :: initialisation_iso           ! 0: file ; 1: R=0 ; 2: R=distill. Rayleigh ; 3: R=Rsmow
[3927]36!$OMP THREADPRIVATE(initialisation_iso)
[4143]37   INTEGER, SAVE :: modif_SST                    ! 0: default ; 1: modified SST ; 2, 3: SST profiles
[3927]38!$OMP THREADPRIVATE(modif_SST)
[4143]39   REAL,    SAVE :: deltaTtest                   ! Uniform modification of the SST
[3927]40!$OMP THREADPRIVATE(deltaTtest)
[4143]41   INTEGER, SAVE :: modif_sic                    ! Holes in the Sea Ice
[3927]42!$OMP THREADPRIVATE(modif_sic)
[4143]43   REAL,    SAVE :: deltasic                     ! Minimal holes fraction
[3927]44!$OMP THREADPRIVATE(deltasic)
[4143]45   REAL,    SAVE :: deltaTtestpoles
[3927]46!$OMP THREADPRIVATE(deltaTtestpoles)
[4143]47   REAL,    SAVE :: sstlatcrit, dsstlatcrit
48!$OMP THREADPRIVATE(sstlatcrit, dsstlatcrit)
49   INTEGER, SAVE :: albedo_prescrit              ! 0: default ; 1: constant albedo
[3927]50!$OMP THREADPRIVATE(albedo_prescrit)
[4143]51   REAL,    SAVE :: lon_min_albedo, lon_max_albedo, lat_min_albedo, lat_max_albedo
52!$OMP THREADPRIVATE(lon_min_albedo, lon_max_albedo, lat_min_albedo, lat_max_albedo)
53   REAL,    SAVE :: deltaP_BL,tdifexp_sol
[3927]54!$OMP THREADPRIVATE(deltaP_BL,tdifexp_sol)
[4143]55   INTEGER, SAVE :: ruissellement_pluie, alphak_stewart
56!$OMP THREADPRIVATE(ruissellement_pluie, alphak_stewart)
57   INTEGER, SAVE :: calendrier_guide
[3927]58!$OMP THREADPRIVATE(calendrier_guide)
[4143]59   INTEGER, SAVE :: cste_surf_cond
[3927]60!$OMP THREADPRIVATE(cste_surf_cond)
[4143]61   REAL,    SAVE :: mixlen
[3927]62!$OMP THREADPRIVATE(mixlen)
[4143]63   INTEGER, SAVE :: evap_cont_cste
[3927]64!$OMP THREADPRIVATE(evap_cont_cste)
[4143]65   REAL,    SAVE :: deltaO18_evap_cont, d_evap_cont
66!$OMP THREADPRIVATE(deltaO18_evap_cont, d_evap_cont)
67   INTEGER, SAVE :: nudge_qsol, region_nudge_qsol
68!$OMP THREADPRIVATE(nudge_qsol, region_nudge_qsol)
69   INTEGER, SAVE :: nlevmaxO17
[3927]70!$OMP THREADPRIVATE(nlevmaxO17)
[4143]71   INTEGER, SAVE :: no_pce
[3927]72!$OMP THREADPRIVATE(no_pce)
[4143]73   REAL,    SAVE :: A_satlim
[3927]74!$OMP THREADPRIVATE(A_satlim)
[4143]75   INTEGER, SAVE :: ok_restrict_A_satlim, modif_ratqs
76!$OMP THREADPRIVATE(ok_restrict_A_satlim, modif_ratqs)
77   REAL,    SAVE :: Pcrit_ratqs, ratqsbasnew
78!$OMP THREADPRIVATE(Pcrit_ratqs, ratqsbasnew)
79   REAL,    SAVE :: fac_modif_evaoce
[3927]80!$OMP THREADPRIVATE(fac_modif_evaoce)
[4982]81   REAL,    SAVE :: deltaO18_oce
82!$OMP THREADPRIVATE(deltaO18_oce)
[4143]83   INTEGER, SAVE :: ok_bidouille_wake
[3927]84!$OMP THREADPRIVATE(ok_bidouille_wake)
[4143]85   LOGICAL, SAVE :: cond_temp_env
[3927]86!$OMP THREADPRIVATE(cond_temp_env)
87
[4143]88   !--- Vectors of length "niso"
89   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
90                    tnat, toce, tcorr, tdifrel
91!$OMP THREADPRIVATE(tnat, toce, tcorr, tdifrel)
92   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
93                    talph1, talph2, talph3, talps1, talps2
94!$OMP THREADPRIVATE(talph1, talph2, talph3, talps1, talps2)
95   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
96                    tkcin0, tkcin1, tkcin2
[3927]97!$OMP THREADPRIVATE(tkcin0, tkcin1, tkcin2)
[4143]98   REAL, ALLOCATABLE, DIMENSION(:), SAVE :: &
99                    alpha_liq_sol, Rdefault, Rmethox
100!$OMP THREADPRIVATE(alpha_liq_sol, Rdefault, Rmethox)
[4982]101!   REAL, SAVE ::    fac_coeff_eq17_liq, fac_coeff_eq17_ice
102!!$OMP THREADPRIVATE(fac_coeff_eq17_liq, fac_coeff_eq17_ice)
[3927]103
[4982]104   !--- H2[18]O reference
105   REAL, PARAMETER :: fac_enrichoce18=0.0005
106   REAL, PARAMETER :: alpha_liq_sol_O18=1.00291
107   REAL, PARAMETER :: talph1_O18=1137.
108   REAL, PARAMETER :: talph2_O18=-0.4156
109   REAL, PARAMETER :: talph3_O18=-2.0667E-3
110   REAL, PARAMETER :: talps1_O18=11.839
111   REAL, PARAMETER :: talps2_O18=-0.028244
112   REAL, PARAMETER :: tdifrel_O18=1./0.9723
113   REAL, PARAMETER :: tkcin0_O18=0.006
114   REAL, PARAMETER :: tkcin1_O18=0.000285
115   REAL, PARAMETER :: tkcin2_O18=0.00082
116   REAL, PARAMETER :: fac_coeff_eq17_liq=0.529
117   REAL, PARAMETER :: fac_coeff_eq17_ice=0.529
118
119   !---- Parameters that do not depend on the nature of water isotopes:
120   REAL, PARAMETER :: pxtmelt = 273.15 ! temperature at which ice formation starts
121   REAL, PARAMETER :: pxtice  = 273.15-10.0 ! -- temperature at which all condensate is ice:
122   REAL, PARAMETER :: pxtmin = 273.15 - 120.0   ! On ne calcule qu'au dessus de -120°C
123   REAL, PARAMETER :: pxtmax = 273.15 +  60.0   ! On ne calcule qu'au dessus de +60°C
124   REAL, PARAMETER :: tdifexp = 0.58 ! -- a constant for alpha_eff for equilibrium below cloud base:
125   REAL, PARAMETER :: tv0cin  = 7.0 ! wind threshold (m/s) for smooth/rough regime (Merlivat and Jouzel 1979)
126   REAL, PARAMETER :: musi=1.0  ! facteurs lambda et mu dans Si=musi-lambda*T
127   REAL, PARAMETER :: Kd=2.5e-9 ! m2/s ! diffusion dans le sol
128   REAL, PARAMETER :: rh_cste_surf_cond = 0.6 ! cas où cste_surf_cond: on met rhs ou/et Ts cste pour voir
129   REAL, PARAMETER :: T_cste_surf_cond = 288.0
130
131
[4143]132   !--- Negligible lower thresholds: no need to check for absurd values under these lower limits
133   REAL, PARAMETER :: &
134      ridicule      = 1e-12,              & ! For mixing ratios
135      ridicule_rain = 1e-8,               & ! For rain fluxes (rain, zrfl...) in kg/s <-> 1e-3 mm/day
136      ridicule_evap = ridicule_rain*1e-2, & ! For evaporations                in kg/s <-> 1e-3 mm/day
137      ridicule_qsol = ridicule_rain,      & ! For qsol                        in kg <-> 1e-8 kg
138      ridicule_snow = ridicule_qsol         ! For snow                        in kg <-> 1e-8 kg
139   REAL, PARAMETER :: expb_max = 30.0
[3927]140
[4143]141   !--- Specific to HTO:
142   LOGICAL, SAVE :: ok_prod_nucl_tritium    !--- TRUE => HTO production by nuclear tests
[3927]143!$OMP THREADPRIVATE(ok_prod_nucl_tritium)
[4143]144   INTEGER, PARAMETER :: nessai = 486
[5098]145   INTEGER, DIMENSION(nessai) :: &
[4143]146                    day_nucl, month_nucl, year_nucl
147!$OMP THREADPRIVATE(day_nucl, month_nucl, year_nucl)
[5098]148   REAL,    DIMENSION(nessai) :: &
[4143]149                    lat_nucl, lon_nucl, zmin_nucl, zmax_nucl, HTO_nucl
150!$OMP THREADPRIVATE(lat_nucl, lon_nucl, zmin_nucl, zmax_nucl, HTO_nucl)
[3927]151 
[4143]152 
[3927]153CONTAINS
154
[4143]155SUBROUTINE iso_init()
[4149]156   USE infotrac_phy,       ONLY: ntiso, niso, getKey
[5117]157    USE lmdz_strings,       ONLY: maxlen
[4143]158   IMPLICIT NONE
[3927]159
[4143]160   !=== Local variables:
161   INTEGER :: ixt
[3927]162
[4982]163 
[4143]164   !--- For H2[17]O
165   REAL    :: fac_kcin, pente_MWL
[3927]166     
[4143]167   !--- Sensitivity tests
168   LOGICAL, PARAMETER ::   ok_nocinsfc = .FALSE. ! if T: no kinetic effect in sfc evap
169   LOGICAL, PARAMETER ::   ok_nocinsat = .FALSE. ! if T: no sursaturation effect for ice
170   LOGICAL, PARAMETER :: Rdefault_smow = .FALSE. ! if T: Rdefault=smow; if F: nul
[4982]171   LOGICAL, PARAMETER :: tnat1 = .TRUE. ! If T: all tnats are 1.
[3927]172
[4143]173   !--- For [3]H
174   INTEGER :: iessai
[3927]175
[4143]176   CHARACTER(LEN=maxlen) :: modname, sxt
[3927]177
[4143]178   modname = 'iso_init'
179   CALL msg('219: entree', modname)
[3927]180
[4143]181   !--------------------------------------------------------------
182   ! General:
183   !--------------------------------------------------------------
[3927]184
[4143]185   !--- Check number of isotopes
186   CALL msg('64: niso = '//TRIM(int2str(niso)), modname)
[3927]187
[4143]188   !--- Init de ntracisoOR: on ecrasera en cas de traceurs de tagging isotopiques
189   !                     (nzone>0) si complications avec ORCHIDEE
190   ntracisoOR = ntiso 
[3927]191
[4143]192   !--- Type of water isotopes:
[4399]193   iso_eau = strIdx(isoName, 'H216O'); CALL msg('iso_eau='//int2str(iso_eau), modname)
194   iso_HDO = strIdx(isoName, 'HDO');   CALL msg('iso_HDO='//int2str(iso_HDO), modname)
195   iso_O18 = strIdx(isoName, 'H218O'); CALL msg('iso_O18='//int2str(iso_O18), modname)
196   iso_O17 = strIdx(isoName, 'H217O'); CALL msg('iso_O17='//int2str(iso_O17), modname)
197   iso_HTO = strIdx(isoName, 'HTO');   CALL msg('iso_HTO='//int2str(iso_HTO), modname)
[3927]198
[4325]199   !--- Initialiaation: reading the isotopic parameters.
[4143]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
[3927]216#ifdef ISOVERIF
[4143]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
[3927]220#endif             
221
[4143]222   CALL get_in('modif_sic', modif_sic,  0)
223   IF(modif_sic >= 1) &
224   CALL get_in('deltasic',  deltasic, 0.1)
[3927]225
[4143]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   CALL get_in('deltaP_BL',           deltaP_BL,     10.0)
234   CALL get_in('ruissellement_pluie', ruissellement_pluie, 0)
235   CALL get_in('alphak_stewart',      alphak_stewart,      1)
236   CALL get_in('tdifexp_sol',         tdifexp_sol,      0.67)
237   CALL get_in('calendrier_guide',    calendrier_guide,    0)
238   CALL get_in('cste_surf_cond',      cste_surf_cond,      0)
239   CALL get_in('mixlen',              mixlen,           35.0)
240   CALL get_in('evap_cont_cste',      evap_cont_cste,      0)
241   CALL get_in('deltaO18_evap_cont',  deltaO18_evap_cont,0.0)
242   CALL get_in('d_evap_cont',         d_evap_cont,       0.0)
243   CALL get_in('nudge_qsol',          nudge_qsol,          0)
244   CALL get_in('region_nudge_qsol',   region_nudge_qsol,   1)
245   nlevmaxO17 = 50
246   CALL msg('nlevmaxO17='//TRIM(int2str(nlevmaxO17)))
247   CALL get_in('no_pce',   no_pce,     0)
248   CALL get_in('A_satlim', A_satlim, 1.0)
249   CALL get_in('ok_restrict_A_satlim', ok_restrict_A_satlim, 0)
250#ifdef ISOVERIF
251   CALL msg(' 315: A_satlim='//real2str(A_satlim), modname, A_satlim > 1.0)
252   IF(A_satlim > 1.0) STOP
253#endif
254!  CALL get_in('slope_limiterxy',   slope_limiterxy,  2.0)
255!  CALL get_in('slope_limiterz',    slope_limiterz,   2.0)
256   CALL get_in('modif_ratqs',       modif_ratqs,        0)
257   CALL get_in('Pcrit_ratqs',       Pcrit_ratqs,    500.0)
258   CALL get_in('ratqsbasnew',       ratqsbasnew,     0.05)
259   CALL get_in('fac_modif_evaoce',  fac_modif_evaoce, 1.0)
260   CALL get_in('ok_bidouille_wake', ok_bidouille_wake,  0)
261   ! si oui, la temperature de cond est celle de l'environnement, pour eviter
262   ! bugs quand temperature dans ascendances convs est mal calculee
263   CALL get_in('cond_temp_env',        cond_temp_env,        .FALSE.)
[4399]264   IF(ANY(isoName == 'HTO')) &
[4143]265   CALL get_in('ok_prod_nucl_tritium', ok_prod_nucl_tritium, .FALSE., .FALSE.)
[3927]266
[4982]267   ! Ocean composition
268   CALL get_in('deltaO18_oce',  deltaO18_oce, 0.0)
[4143]269   
[4149]270   CALL msg('iso_O18, iso_HDO, iso_eau = '//TRIM(strStack(int2str([iso_O18, iso_HDO, iso_eau]))), modname)
271
[4143]272   !--------------------------------------------------------------
[4982]273   ! Isotope fractionation factors and a few isotopic constants
[4143]274   !--------------------------------------------------------------
[4982]275   ALLOCATE(tkcin0(niso))
276   ALLOCATE(tkcin1(niso))
277   ALLOCATE(tkcin2(niso))
278   ALLOCATE(tnat(niso))
279   ALLOCATE(tdifrel(niso))
280   ALLOCATE(toce(niso))
281   ALLOCATE(tcorr(niso))
282   ALLOCATE(talph1(niso))
283   ALLOCATE(talph2(niso))
284   ALLOCATE(talph3(niso))
285   ALLOCATE(talps1(niso))
286   ALLOCATE(talps2(niso))
287   ALLOCATE(alpha_liq_sol(niso))
288   ALLOCATE(Rdefault(niso))
289   ALLOCATE(Rmethox(niso))
[4149]290
[5158]291   DO ixt=1,niso
[5117]292     IF (ixt.EQ.iso_HTO) then  ! Tritium
[4982]293       tkcin0(ixt) = 0.01056
294       tkcin1(ixt) = 0.0005016
295       tkcin2(ixt) = 0.0014432
[5117]296       IF (tnat1) THEN
[4982]297               tnat(ixt)=1
298       else
299               tnat(ixt)=0.
300       endif
301       toce(ixt)=4.0E-19 ! rapport T/H = 0.2 TU Dreisigacker and Roether 1978
302       tcorr(ixt)=1.
303       tdifrel(ixt)=1./0.968
304       talph1(ixt)=46480.
305       talph2(ixt)=-103.87
306       talph3(ixt)=0.
307       talps1(ixt)=46480.
308       talps2(ixt)=-103.87
309       alpha_liq_sol(ixt)=1.
310       Rmethox(ixt)=0.0
311     endif
[5117]312     IF (ixt.EQ.iso_O17) then  ! O17
[4982]313       pente_MWL=0.528
314       tdifrel(ixt)=1./0.98555 ! valeur utilisée en 1D et dans modèle de LdG ! tdifrel(ixt)=1./0.985452 ! donné par Amaelle
315       fac_kcin= (tdifrel(ixt)-1.0)/(tdifrel_O18-1.0) ! fac_kcin=0.5145 ! donné par Amaelle
316       tkcin0(ixt) = tkcin0_O18*fac_kcin
317       tkcin1(ixt) = tkcin1_O18*fac_kcin
318       tkcin2(ixt) = tkcin2_O18*fac_kcin
[5117]319       IF (tnat1) THEN
[4982]320               tnat(ixt)=1
321       else
322               tnat(ixt)=0.004/100. ! O17 représente 0.004% de l'oxygène
323       endif
324       toce(ixt)=tnat(ixt)*(1.0+deltaO18_oce/1000.0)**pente_MWL
325       tcorr(ixt)=1.0+fac_enrichoce18*pente_MWL ! donné par Amaelle           
326       talph1(ixt)=talph1_O18
327       talph2(ixt)=talph2_O18
328       talph3(ixt)=talph3_O18
329       talps1(ixt)=talps1_O18
330       talps2(ixt)=talps2_O18     
331       alpha_liq_sol(ixt)=(alpha_liq_sol_O18)**fac_coeff_eq17_liq
332       Rdefault(ixt)=tnat(ixt)*(-3.15/1000.0+1.0)
333       Rmethox(ixt)=(230./1000.+1.)*tnat(ixt) !Zahn et al 2006
334     endif
[5117]335     IF (ixt.EQ.iso_O18) then  ! Oxygene18
[4982]336       tkcin0(ixt) = tkcin0_O18
337       tkcin1(ixt) = tkcin1_O18
338       tkcin2(ixt) = tkcin2_O18
[5117]339       IF (tnat1) THEN
[4982]340               tnat(ixt)=1
341       else
342               tnat(ixt)=2005.2E-6
343       endif
344       toce(ixt)=tnat(ixt)*(1.0+deltaO18_oce/1000.0)
345       tcorr(ixt)=1.0+fac_enrichoce18
346       tdifrel(ixt)=tdifrel_O18
347       talph1(ixt)=talph1_O18
348       talph2(ixt)=talph2_O18
349       talph3(ixt)=talph3_O18
350       talps1(ixt)=talps1_O18
351       talps2(ixt)=talps2_O18
352       alpha_liq_sol(ixt)=alpha_liq_sol_O18   
353       Rdefault(ixt)=tnat(ixt)*(-6.0/1000.0+1.0)
354       Rmethox(ixt)=(130./1000.+1.)*tnat(ixt) !Zahn et al 2006 
355     endif
[5117]356     IF (ixt.EQ.iso_HDO) then ! Deuterium
[4982]357       pente_MWL=8.0
358       tdifrel(ixt)=1./0.9755 !          fac_kcin=0.88
359       fac_kcin= (tdifrel(ixt)-1)/(tdifrel_O18-1)
360       tkcin0(ixt) = tkcin0_O18*fac_kcin
361       tkcin1(ixt) = tkcin1_O18*fac_kcin
362       tkcin2(ixt) = tkcin2_O18*fac_kcin
[5117]363       IF (tnat1) THEN
[4982]364               tnat(ixt)=1
365       else
366               tnat(ixt)=155.76E-6
367       endif
368       toce(ixt)=tnat(ixt)*(1.0+pente_MWL*deltaO18_oce/1000.0)
369       tcorr(ixt)=1.0+fac_enrichoce18*pente_MWL         
370       talph1(ixt)=24844.
371       talph2(ixt)=-76.248
372       talph3(ixt)=52.612E-3
373       talps1(ixt)=16288.
374       talps2(ixt)=-0.0934
375       !ZXalpha_liq_sol=1.0192 ! Weston, Ralph, 1955
376       alpha_liq_sol(ixt)=1.0212
377       ! valeur de Lehmann & Siegenthaler, 1991, Journal of
378       ! Glaciology, vol 37, p 23
379       Rdefault(ixt)=tnat(ixt)*((-6.0*pente_MWL+10.0)/1000.0+1.0)
380       Rmethox(ixt)=tnat(ixt)*(-25.0/1000.+1.) ! Zahn et al 2006
381     endif
[5117]382     IF (ixt.EQ.iso_eau) then ! Oxygene16
[4982]383       tkcin0(ixt) = 0.0
384       tkcin1(ixt) = 0.0
385       tkcin2(ixt) = 0.0
386       tnat(ixt)=1.
387       toce(ixt)=tnat(ixt)
388       tcorr(ixt)=1.0
389       tdifrel(ixt)=1.
390       talph1(ixt)=0.
391       talph2(ixt)=0.
392       talph3(ixt)=0.
393       talps1(ixt)=0.
394       talph3(ixt)=0.
395       alpha_liq_sol(ixt)=1.
396       Rdefault(ixt)=tnat(ixt)*1.0
397       Rmethox(ixt)=1.0
398     endif
399   enddo ! ixt=1,niso
400
[5116]401   IF(.NOT.Rdefault_smow) THEN
[4491]402        Rdefault(:) = 0.0
[5117]403        IF (iso_eau.gt.0) Rdefault(iso_eau) = 1.0 ! correction Camille 30 mars 2023
[4491]404   ENDIF
[5116]405   WRITE(*,*) 'Rdefault=',Rdefault
406   WRITE(*,*) 'toce=',toce
[4491]407
[4143]408   !--- Sensitivity test: no kinetic effect in sfc evaporation
409   IF(ok_nocinsfc) THEN
410      tkcin0(1:niso) = 0.0
411      tkcin1(1:niso) = 0.0
412      tkcin2(1:niso) = 0.0
413   END IF
[3927]414
[4143]415   CALL msg('285: verif initialisation:', modname)
416   DO ixt=1,niso
[4149]417      sxt=int2str(ixt)
418      CALL msg(' * isoName('//TRIM(sxt)//') = <'//TRIM(isoName(ixt))//'>',  modname)
419      CALL msg(  '    tnat('//TRIM(sxt)//') = '//TRIM(real2str(tnat(ixt))), modname)
420!     CALL msg('    alpha_liq_sol('//TRIM(sxt)//') = '//TRIM(real2str(alpha_liq_sol(ixt))), modname)
421!     CALL msg(        '   tkcin0('//TRIM(sxt)//') = '//TRIM(real2str(tkcin0(ixt))),        modname)
422!     CALL msg(       '   tdifrel('//TRIM(sxt)//') = '//TRIM(real2str(tdifrel(ixt))),       modname)
[4143]423   END DO
424   CALL msg('69:     lambda = '//TRIM(real2str(lambda_sursat)), modname)
425   CALL msg('69:    thumxt1 = '//TRIM(real2str(thumxt1)),       modname)
426   CALL msg('69: h_land_ice = '//TRIM(real2str(h_land_ice)),    modname)
427   CALL msg('69:      P_veg = '//TRIM(real2str(P_veg)),         modname)
[3927]428
[4143]429END SUBROUTINE iso_init
[3927]430
431
[4143]432SUBROUTINE getinp_s(nam, val, def, lDisp)
[5132]433   USE IOIPSL, ONLY: getin
[5110]434   USE lmdz_phys_mpi_data, ONLY:  is_mpi_root
435   USE lmdz_phys_omp_data, ONLY:  is_omp_root
436   USE lmdz_phys_transfert_para, ONLY: bcast
[4325]437   CHARACTER(LEN=*),           INTENT(IN)    :: nam
438   CHARACTER(LEN=*),           INTENT(INOUT) :: val
439   CHARACTER(LEN=*), OPTIONAL, INTENT(IN)    :: def
440   LOGICAL,          OPTIONAL, INTENT(IN)    :: lDisp
[4143]441   LOGICAL :: lD
442!$OMP BARRIER
[4319]443   IF(is_mpi_root.AND.is_omp_root) THEN
[4325]444      IF(PRESENT(def)) val=def; CALL getin(nam,val)
[4319]445      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
446      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(val))
[4325]447  END IF
448  CALL bcast(val)
[4143]449END SUBROUTINE getinp_s
[3927]450
[4143]451SUBROUTINE getinp_i(nam, val, def, lDisp)
[5132]452   USE IOIPSL, ONLY: getin
[5110]453   USE lmdz_phys_mpi_data, ONLY:  is_mpi_root
454   USE lmdz_phys_omp_data, ONLY:  is_omp_root
455   USE lmdz_phys_transfert_para, ONLY: bcast
[4143]456   CHARACTER(LEN=*),  INTENT(IN)    :: nam
457   INTEGER,           INTENT(INOUT) :: val
[4325]458   INTEGER, OPTIONAL, INTENT(IN)    :: def
[4143]459   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
460   LOGICAL :: lD
461!$OMP BARRIER
[4319]462   IF(is_mpi_root.AND.is_omp_root) THEN
[4325]463      IF(PRESENT(def)) val=def; CALL getin(nam,val)
[4319]464      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
465      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(int2str(val)))
[4325]466  END IF
467  CALL bcast(val)
[4143]468END SUBROUTINE getinp_i
[3927]469
[4143]470SUBROUTINE getinp_r(nam, val, def, lDisp)
[5132]471   USE IOIPSL, ONLY: getin
[5110]472   USE lmdz_phys_mpi_data, ONLY:  is_mpi_root
473   USE lmdz_phys_omp_data, ONLY:  is_omp_root
474   USE lmdz_phys_transfert_para, ONLY: bcast
[4143]475   CHARACTER(LEN=*),  INTENT(IN)    :: nam
476   REAL,              INTENT(INOUT) :: val
[4325]477   REAL,    OPTIONAL, INTENT(IN)    :: def
[4143]478   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
479   LOGICAL :: lD
480!$OMP BARRIER
[4319]481   IF(is_mpi_root.AND.is_omp_root) THEN
[4325]482      IF(PRESENT(def)) val=def; CALL getin(nam,val)
[4319]483      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
484      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(real2str(val)))
[4325]485  END IF
486  CALL bcast(val)
[4143]487END SUBROUTINE getinp_r
[3927]488
[4143]489SUBROUTINE getinp_l(nam, val, def, lDisp)
[5132]490   USE IOIPSL, ONLY: getin
[5110]491   USE lmdz_phys_mpi_data, ONLY:  is_mpi_root
492   USE lmdz_phys_omp_data, ONLY:  is_omp_root
493   USE lmdz_phys_transfert_para, ONLY: bcast
[4143]494   CHARACTER(LEN=*),  INTENT(IN)    :: nam
495   LOGICAL,           INTENT(INOUT) :: val
[4325]496   LOGICAL, OPTIONAL, INTENT(IN)    :: def
[4143]497   LOGICAL, OPTIONAL, INTENT(IN)    :: lDisp
498   LOGICAL :: lD
499!$OMP BARRIER
[4319]500   IF(is_mpi_root.AND.is_omp_root) THEN
[4325]501      IF(PRESENT(def)) val=def; CALL getin(nam,val)
[4319]502      lD=.TRUE.; IF(PRESENT(lDisp)) lD=lDisp
503      IF(lD) CALL msg(TRIM(nam)//' = '//TRIM(bool2str(val)))
[4325]504  END IF
505  CALL bcast(val)
[4143]506END SUBROUTINE getinp_l
[3927]507
508END MODULE isotopes_mod
509#endif
510
511
Note: See TracBrowser for help on using the repository browser.