source: LMDZ6/trunk/libf/phylmdiso/phyetat0_mod.F90 @ 5213

Last change on this file since 5213 was 5204, checked in by Laurent Fairhead, 45 hours ago

Integrating A.Borella's work on cirrus in the trunk

File size: 25.0 KB
Line 
1! $Id: phyetat0.F90 3890 2021-05-05 15:15:06Z jyg $
2
3MODULE phyetat0_mod
4
5  PRIVATE
6  PUBLIC :: phyetat0
7
8CONTAINS
9
10SUBROUTINE phyetat0 (fichnom, clesphy0, tabcntr0)
11
12  USE dimphy, only: klon, zmasq, klev
13  USE iophy, ONLY : init_iophy_new
14  USE ocean_cpl_mod,    ONLY : ocean_cpl_init
15  USE fonte_neige_mod,  ONLY : fonte_neige_init
16  USE pbl_surface_mod,  ONLY : pbl_surface_init
17#ifdef ISO
18  USE fonte_neige_mod,  ONLY : fonte_neige_init_iso
19  USE pbl_surface_mod,  ONLY : pbl_surface_init_iso
20#endif
21  USE phyetat0_get_mod, ONLY : phyetat0_get, phyetat0_srf
22  USE surface_data,     ONLY : type_ocean, version_ocean
23  USE phys_state_var_mod, ONLY : ancien_ok, clwcon, detr_therm, phys_tstep, &
24       qsol, fevap, z0m, z0h, agesno, &
25       du_gwd_rando, du_gwd_front, entr_therm, f0, fm_therm, &
26       falb_dir, falb_dif, prw_ancien, prlw_ancien, prsw_ancien, prbsw_ancien, &
27       ftsol, pbl_tke, pctsrf, q_ancien, ql_ancien, qs_ancien, qbs_ancien, &
28       cf_ancien, rvc_ancien, radpas, radsol, rain_fall, ratqs, &
29       rnebcon, rugoro, sig1, snow_fall, bs_fall, solaire_etat0, sollw, sollwdown, &
30       solsw, solswfdiff, t_ancien, u_ancien, v_ancien, w01, wake_cstar, wake_deltaq, &
31       wake_deltat, wake_delta_pbl_TKE, delta_tsurf, beta_aridity, wake_fip, wake_pe, &
32       wake_s, awake_s, wake_dens, awake_dens, cv_gen, zgam, zmax0, zmea, zpic, zsig, &
33#ifdef ISO
34       fxtevap, xtsol, xt_ancien, xtl_ancien, xts_ancien, wake_deltaxt, &
35       xtrain_fall,xtsnow_fall, &
36#endif
37       zstd, zthe, zval, ale_bl, ale_bl_trig, alp_bl, u10m, v10m, treedrg, &
38       ale_wake, ale_bl_stat, ds_ns, dt_ns, delta_sst, delta_sal, dter, dser, &
39       dt_ds, ratqs_inter_
40!FC
41  USE geometry_mod,     ONLY: longitude_deg, latitude_deg
42  USE iostart,          ONLY: close_startphy, get_field, get_var, open_startphy
43  USE infotrac_phy,     ONLY: nqtot, nbtr, type_trac, tracers, new2oldH2O
44  USE strings_mod,      ONLY: maxlen
45  USE traclmdz_mod,     ONLY: traclmdz_from_restart
46  USE carbon_cycle_mod, ONLY: carbon_cycle_init, carbon_cycle_cpl, carbon_cycle_tr, carbon_cycle_rad, co2_send, RCO2_glo
47  USE indice_sol_mod,   ONLY: nbsrf, is_ter, epsfra, is_lic, is_oce, is_sic
48  USE ocean_slab_mod,   ONLY: nslay, tslab, seaice, tice, ocean_slab_init
49  USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
50  USE wxios, ONLY: missing_val_xios => missing_val, using_xios
51  use netcdf, only: missing_val_netcdf => nf90_fill_real
52  use config_ocean_skin_m, only: activate_ocean_skin
53#ifdef ISO
54  USE infotrac_phy, ONLY: niso
55  USE isotopes_routines_mod, ONLY: phyisoetat0
56  USE isotopes_mod, ONLY: iso_eau
57#ifdef ISOVERIF
58  USE isotopes_verif_mod, ONLY: iso_verif_egalite_vect2D,iso_verif_egalite
59#endif
60#endif
61
62  IMPLICIT none
63  !======================================================================
64  ! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
65  ! Objet: Lecture de l'etat initial pour la physique
66  !======================================================================
67  include "dimsoil.h"
68  include "clesphys.h"
69  include "alpale.h"
70  include "compbl.h"
71  include "YOMCST.h"
72  !======================================================================
73  CHARACTER*(*) fichnom
74
75  ! les variables globales lues dans le fichier restart
76
77  REAL tsoil(klon, nsoilmx, nbsrf)
78  REAL qsurf(klon, nbsrf)
79  REAL snow(klon, nbsrf)
80  real fder(klon)
81  REAL run_off_lic_0(klon)
82  REAL fractint(klon)
83  REAL trs(klon, nbtr)
84  REAL zts(klon)
85  ! pour drag arbres FC
86  REAL drg_ter(klon,klev)
87
88  CHARACTER*6 ocean_in
89  LOGICAL ok_veget_in
90
91  INTEGER        longcles
92  PARAMETER    ( longcles = 20 )
93  REAL clesphy0( longcles )
94
95  REAL xmin, xmax
96
97  INTEGER nid, nvarid
98  INTEGER ierr, i, nsrf, isoil , k
99  INTEGER length
100  PARAMETER (length=100)
101  INTEGER it, iq, isw
102  REAL tab_cntrl(length), tabcntr0(length)
103  CHARACTER*7 str7
104  CHARACTER*2 str2
105  LOGICAL :: found
106  REAL :: lon_startphy(klon), lat_startphy(klon)
107  CHARACTER(LEN=maxlen) :: tname, t(2)
108  REAL :: missing_val
109#ifdef ISO
110  REAL xtsnow(niso,klon, nbsrf)
111  REAL xtrun_off_lic_0(niso,klon)
112  REAL Rland_ice(niso,klon)
113#endif
114
115  IF (using_xios) THEN
116    missing_val=missing_val_xios
117  ELSE
118    missing_val=missing_val_netcdf
119  ENDIF
120
121  ! FH1D
122  !     real iolat(jjm+1)
123  !real iolat(jjm+1-1/(iim*jjm))
124
125  ! Ouvrir le fichier contenant l'etat initial:
126
127  CALL open_startphy(fichnom)
128
129  ! Lecture des parametres de controle:
130
131  CALL get_var("controle", tab_cntrl)
132
133!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
134  ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
135  ! Les constantes de la physiques sont lues dans la physique seulement.
136  ! Les egalites du type
137  !             tab_cntrl( 5 )=clesphy0(1)
138  ! sont remplacees par
139  !             clesphy0(1)=tab_cntrl( 5 )
140  ! On inverse aussi la logique.
141  ! On remplit les tab_cntrl avec les parametres lus dans les .def
142!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
143
144  DO i = 1, length
145     tabcntr0( i ) = tab_cntrl( i )
146  ENDDO
147
148  tab_cntrl(1)=pdtphys
149  tab_cntrl(2)=radpas
150
151  ! co2_ppm : value from the previous time step
152
153  ! co2_ppm0 : initial value of atmospheric CO2 (from create_etat0_limit.e .def)
154  co2_ppm0 = 284.32
155  ! when no initial value is available e.g., from a restart
156  ! this variable must be set  in a .def file which will then be
157  ! used by the conf_phys_m.F90 routine.
158  ! co2_ppm0 = 284.32 (illustrative example on how to set the variable in .def
159  ! file, for a pre-industrial CO2 concentration value)
160
161  IF (carbon_cycle_tr .OR. carbon_cycle_cpl) THEN
162     co2_ppm = tab_cntrl(3)
163     RCO2    = co2_ppm * 1.0e-06 * RMCO2 / RMD
164     IF (tab_cntrl(17) > 0. .AND. carbon_cycle_rad) THEN
165           RCO2_glo = tab_cntrl(17)
166       ELSE
167           RCO2_glo    = co2_ppm0 * 1.0e-06 * RMCO2 / RMD
168     ENDIF
169     ! ELSE : keep value from .def
170  ENDIF
171
172  solaire_etat0      = tab_cntrl(4)
173  tab_cntrl(5)=iflag_con
174  tab_cntrl(6)=nbapp_rad
175
176  IF (iflag_cycle_diurne.GE.1) tab_cntrl( 7) = iflag_cycle_diurne
177  IF (soil_model) tab_cntrl( 8) =1.
178  IF (new_oliq) tab_cntrl( 9) =1.
179  IF (ok_orodr) tab_cntrl(10) =1.
180  IF (ok_orolf) tab_cntrl(11) =1.
181  IF (ok_limitvrai) tab_cntrl(12) =1.
182
183  itau_phy = tab_cntrl(15)
184
185  clesphy0(1)=tab_cntrl( 5 )
186  clesphy0(2)=tab_cntrl( 6 )
187  clesphy0(3)=tab_cntrl( 7 )
188  clesphy0(4)=tab_cntrl( 8 )
189  clesphy0(5)=tab_cntrl( 9 )
190  clesphy0(6)=tab_cntrl( 10 )
191  clesphy0(7)=tab_cntrl( 11 )
192  clesphy0(8)=tab_cntrl( 12 )
193  clesphy0(9)=tab_cntrl( 17 )
194
195  ! set time iteration
196   CALL init_iteration(itau_phy)
197
198  ! read latitudes and make a sanity check (because already known from dyn)
199  CALL get_field("latitude",lat_startphy)
200  DO i=1,klon
201    IF (ABS(lat_startphy(i)-latitude_deg(i))>=1) THEN
202      WRITE(*,*) "phyetat0: Error! Latitude discrepancy wrt startphy file:",&
203                 " i=",i," lat_startphy(i)=",lat_startphy(i),&
204                 " latitude_deg(i)=",latitude_deg(i)
205      ! This is presumably serious enough to abort run
206      CALL abort_physic("phyetat0","discrepancy in latitudes!",1)
207    ENDIF
208    IF (ABS(lat_startphy(i)-latitude_deg(i))>=0.0001) THEN
209      WRITE(*,*) "phyetat0: Warning! Latitude discrepancy wrt startphy file:",&
210                 " i=",i," lat_startphy(i)=",lat_startphy(i),&
211                 " latitude_deg(i)=",latitude_deg(i)
212    ENDIF
213  ENDDO
214
215  ! read longitudes and make a sanity check (because already known from dyn)
216  CALL get_field("longitude",lon_startphy)
217  DO i=1,klon
218    IF (ABS(lon_startphy(i)-longitude_deg(i))>=1) THEN
219      IF (ABS(360-ABS(lon_startphy(i)-longitude_deg(i)))>=1) THEN
220        WRITE(*,*) "phyetat0: Error! Longitude discrepancy wrt startphy file:",&
221                   " i=",i," lon_startphy(i)=",lon_startphy(i),&
222                   " longitude_deg(i)=",longitude_deg(i)
223        ! This is presumably serious enough to abort run
224        CALL abort_physic("phyetat0","discrepancy in longitudes!",1)
225      ENDIF
226    ENDIF
227    IF (ABS(lon_startphy(i)-longitude_deg(i))>=1) THEN
228      IF (ABS(360-ABS(lon_startphy(i)-longitude_deg(i))) > 0.0001) THEN
229        WRITE(*,*) "phyetat0: Warning! Longitude discrepancy wrt startphy file:",&
230                   " i=",i," lon_startphy(i)=",lon_startphy(i),&
231                   " longitude_deg(i)=",longitude_deg(i)
232      ENDIF
233    ENDIF
234  ENDDO
235
236  ! Lecture du masque terre mer
237
238  CALL get_field("masque", zmasq, found)
239  IF (.NOT. found) THEN
240     PRINT*, 'phyetat0: Le champ <masque> est absent'
241     PRINT *, 'fichier startphy non compatible avec phyetat0'
242  ENDIF
243
244  ! Lecture des fractions pour chaque sous-surface
245
246  ! initialisation des sous-surfaces
247
248  pctsrf = 0.
249
250  ! fraction de terre
251
252  CALL get_field("FTER", pctsrf(:, is_ter), found)
253  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FTER> est absent'
254
255  ! fraction de glace de terre
256
257  CALL get_field("FLIC", pctsrf(:, is_lic), found)
258  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FLIC> est absent'
259
260  ! fraction d'ocean
261
262  CALL get_field("FOCE", pctsrf(:, is_oce), found)
263  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FOCE> est absent'
264
265  ! fraction glace de mer
266
267  CALL get_field("FSIC", pctsrf(:, is_sic), found)
268  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FSIC> est absent'
269
270  !  Verification de l'adequation entre le masque et les sous-surfaces
271
272  fractint( 1 : klon) = pctsrf(1 : klon, is_ter)  &
273       + pctsrf(1 : klon, is_lic)
274  DO i = 1 , klon
275     IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN
276        WRITE(*, *) 'phyetat0: attention fraction terre pas ',  &
277             'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
278             , pctsrf(i, is_lic)
279        WRITE(*, *) 'Je force la coherence zmasq=fractint'
280        zmasq(i) = fractint(i)
281     ENDIF
282  ENDDO
283  fractint (1 : klon) =  pctsrf(1 : klon, is_oce)  &
284       + pctsrf(1 : klon, is_sic)
285  DO i = 1 , klon
286     IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN
287        WRITE(*, *) 'phyetat0 attention fraction ocean pas ',  &
288             'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
289             , pctsrf(i, is_sic)
290        WRITE(*, *) 'Je force la coherence zmasq=1.-fractint'
291        zmasq(i) = 1. - fractint(i)
292     ENDIF
293  ENDDO
294
295!===================================================================
296! Lecture des temperatures du sol:
297!===================================================================
298
299  found=phyetat0_get(ftsol(:,1),"TS","Surface temperature",283.)
300  IF (found) THEN
301     DO nsrf=2,nbsrf
302        ftsol(:,nsrf)=ftsol(:,1)
303     ENDDO
304  ELSE
305     found=phyetat0_srf(ftsol,"TS","Surface temperature",283.)
306  ENDIF
307
308!===================================================================
309  ! Lecture des albedo difus et direct
310!===================================================================
311
312  DO nsrf = 1, nbsrf
313     DO isw=1, nsw
314        IF (isw.GT.99) THEN
315           PRINT*, "Trop de bandes SW"
316           call abort_physic("phyetat0", "", 1)
317        ENDIF
318        WRITE(str2, '(i2.2)') isw
319        found=phyetat0_srf(falb_dir(:, isw,:),"A_dir_SW"//str2//"srf","Direct Albedo",0.2)
320        found=phyetat0_srf(falb_dif(:, isw,:),"A_dif_SW"//str2//"srf","Direct Albedo",0.2)
321     ENDDO
322  ENDDO
323
324  found=phyetat0_srf(u10m,"U10M","u a 10m",0.)
325  found=phyetat0_srf(v10m,"V10M","v a 10m",0.)
326
327!===================================================================
328! Lecture dans le cas iflag_pbl_surface =1
329!===================================================================
330
331   if ( iflag_physiq <= 1 ) then
332!===================================================================
333  ! Lecture des temperatures du sol profond:
334!===================================================================
335
336   DO isoil=1, nsoilmx
337        IF (isoil.GT.99) THEN
338           PRINT*, "Trop de couches "
339           call abort_physic("phyetat0", "", 1)
340        ENDIF
341        WRITE(str2,'(i2.2)') isoil
342        found=phyetat0_srf(tsoil(:, isoil,:),"Tsoil"//str2//"srf","Temp soil",0.)
343        IF (.NOT. found) THEN
344           PRINT*, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
345           PRINT*, "          Il prend donc la valeur de surface"
346           tsoil(:, isoil, :)=ftsol(:, :)
347        ENDIF
348   ENDDO
349
350!=======================================================================
351! Lecture precipitation/evaporation
352!=======================================================================
353
354  found=phyetat0_srf(qsurf,"QS","Near surface hmidity",0.)
355  found=phyetat0_get(qsol,"QSOL","Surface hmidity / bucket",0.)
356  found=phyetat0_srf(snow,"SNOW","Surface snow",0.)
357  found=phyetat0_srf(fevap,"EVAP","evaporation",0.)
358  found=phyetat0_get(snow_fall,"snow_f","snow fall",0.)
359  found=phyetat0_get(rain_fall,"rain_f","rain fall",0.)
360  IF (ok_bs) THEN
361     found=phyetat0_get(bs_fall,"bs_f","blowing snow fall",0.)
362  ELSE
363     bs_fall(:)=0.
364  ENDIF
365
366
367!=======================================================================
368! Radiation
369!=======================================================================
370
371  found=phyetat0_get(solsw,"solsw","net SW radiation surf",0.)
372  found=phyetat0_get(solswfdiff,"solswfdiff","fraction of SW radiation surf that is diffuse",1.)
373  found=phyetat0_get(sollw,"sollw","net LW radiation surf",0.)
374  found=phyetat0_get(sollwdown,"sollwdown","down LW radiation surf",0.)
375  IF (.NOT. found) THEN
376     sollwdown(:) = 0. ;  zts(:)=0.
377     DO nsrf=1,nbsrf
378        zts(:)=zts(:)+ftsol(:,nsrf)*pctsrf(:,nsrf)
379     ENDDO
380     sollwdown(:)=sollw(:)+RSIGMA*zts(:)**4
381  ENDIF
382
383  found=phyetat0_get(radsol,"RADS","Solar radiation",0.)
384  found=phyetat0_get(fder,"fder","Flux derivative",0.)
385
386
387  ! Lecture de la longueur de rugosite
388  found=phyetat0_srf(z0m,"RUG","Z0m ancien",0.001)
389  IF (found) THEN
390     z0h(:,1:nbsrf)=z0m(:,1:nbsrf)
391  ELSE
392     found=phyetat0_srf(z0m,"Z0m","Roughness length, momentum ",0.001)
393     found=phyetat0_srf(z0h,"Z0h","Roughness length, enthalpy ",0.001)
394  ENDIF
395!FC
396  IF (ifl_pbltree>0) THEN
397!CALL get_field("FTER", pctsrf(:, is_ter), found)
398    treedrg(:,1:klev,1:nbsrf)= 0.0
399    CALL get_field("treedrg_ter", drg_ter(:,:), found)
400!  found=phyetat0_srf(treedrg,"treedrg","drag from vegetation" , 0.)
401    !lecture du profile de freinage des arbres
402    IF (.not. found ) THEN
403      treedrg(:,1:klev,1:nbsrf)= 0.0
404    ELSE
405      treedrg(:,1:klev,is_ter)= drg_ter(:,:)
406!     found=phyetat0_get(treedrg,"treedrg","freinage arbres",0.)
407    ENDIF
408  ELSE
409    ! initialize treedrg(), because it will be written in restartphy.nc
410    treedrg(:,:,:) = 0.0
411  ENDIF
412
413  endif ! iflag_physiq <= 1
414
415  ! Lecture de l'age de la neige:
416  found=phyetat0_srf(agesno,"AGESNO","SNOW AGE",0.001)
417
418  ancien_ok=.true.
419  ancien_ok=ancien_ok.AND.phyetat0_get(t_ancien,"TANCIEN","TANCIEN",0.)
420  ancien_ok=ancien_ok.AND.phyetat0_get(q_ancien,"QANCIEN","QANCIEN",0.)
421  ancien_ok=ancien_ok.AND.phyetat0_get(ql_ancien,"QLANCIEN","QLANCIEN",0.)
422  ancien_ok=ancien_ok.AND.phyetat0_get(qs_ancien,"QSANCIEN","QSANCIEN",0.)
423  ancien_ok=ancien_ok.AND.phyetat0_get(u_ancien,"UANCIEN","UANCIEN",0.)
424  ancien_ok=ancien_ok.AND.phyetat0_get(v_ancien,"VANCIEN","VANCIEN",0.)
425  ancien_ok=ancien_ok.AND.phyetat0_get(prw_ancien,"PRWANCIEN","PRWANCIEN",0.)
426  ancien_ok=ancien_ok.AND.phyetat0_get(prlw_ancien,"PRLWANCIEN","PRLWANCIEN",0.)
427  ancien_ok=ancien_ok.AND.phyetat0_get(prsw_ancien,"PRSWANCIEN","PRSWANCIEN",0.)
428
429  ! cas specifique des variables de la neige soufflee
430  IF (ok_bs) THEN
431     ancien_ok=ancien_ok.AND.phyetat0_get(qbs_ancien,"QBSANCIEN","QBSANCIEN",0.)
432     ancien_ok=ancien_ok.AND.phyetat0_get(prbsw_ancien,"PRBSWANCIEN","PRBSWANCIEN",0.)
433  ELSE
434     qbs_ancien(:,:)=0.
435     prbsw_ancien(:)=0.
436  ENDIF
437 
438  ! cas specifique des variables de la sursaturation par rapport a la glace
439  IF ( ok_ice_supersat ) THEN
440    ancien_ok=ancien_ok.AND.phyetat0_get(cf_ancien,"CFANCIEN","CFANCIEN",0.)
441    ancien_ok=ancien_ok.AND.phyetat0_get(rvc_ancien,"RVCANCIEN","RVCANCIEN",0.)
442  ELSE
443    cf_ancien(:,:)=0.
444    rvc_ancien(:,:)=0.
445  ENDIF
446
447  ! Ehouarn: addtional tests to check if t_ancien, q_ancien contain
448  !          dummy values (as is the case when generated by ce0l,
449  !          or by iniaqua)
450  IF ( (maxval(q_ancien).EQ.minval(q_ancien))       .OR. &
451       (maxval(ql_ancien).EQ.minval(ql_ancien))     .OR. &
452       (maxval(qs_ancien).EQ.minval(qs_ancien))     .OR. &
453       (maxval(prw_ancien).EQ.minval(prw_ancien))   .OR. &
454       (maxval(prlw_ancien).EQ.minval(prlw_ancien)) .OR. &
455       (maxval(prsw_ancien).EQ.minval(prsw_ancien)) .OR. &
456       (maxval(t_ancien).EQ.minval(t_ancien)) ) THEN
457    ancien_ok=.false.
458  ENDIF
459
460  IF (ok_bs) THEN
461    IF ( (maxval(qbs_ancien).EQ.minval(qbs_ancien))       .OR. &
462         (maxval(prbsw_ancien).EQ.minval(prbsw_ancien)) ) THEN
463       ancien_ok=.false.
464    ENDIF
465  ENDIF
466
467  IF ( ok_ice_supersat ) THEN
468    IF ( (maxval(cf_ancien).EQ.minval(cf_ancien))     .OR. &
469         (maxval(rvc_ancien).EQ.minval(rvc_ancien)) ) THEN
470       ancien_ok=.false.
471     ENDIF
472  ENDIF
473
474  found=phyetat0_get(clwcon,"CLWCON","CLWCON",0.)
475  found=phyetat0_get(rnebcon,"RNEBCON","RNEBCON",0.)
476  found=phyetat0_get(ratqs,"RATQS","RATQS",0.)
477
478  found=phyetat0_get(run_off_lic_0,"RUNOFFLIC0","RUNOFFLIC0",0.)
479
480!==================================
481!  TKE
482!==================================
483!
484  IF (iflag_pbl>1) then
485     found=phyetat0_srf(pbl_tke,"TKE","Turb. Kinetic. Energ. ",1.e-8)
486  ENDIF
487
488  IF (iflag_pbl>1 .AND. iflag_wake>=1  .AND. iflag_pbl_split >=1 ) then
489    found=phyetat0_srf(wake_delta_pbl_tke,"DELTATKE","Del TKE wk/env",0.)
490!!    found=phyetat0_srf(delta_tsurf,"DELTA_TSURF","Delta Ts wk/env ",0.)
491    found=phyetat0_srf(delta_tsurf,"DELTATS","Delta Ts wk/env ",0.)
492!!    found=phyetat0_srf(beta_aridity,"BETA_S","Aridity factor ",1.)
493    found=phyetat0_srf(beta_aridity,"BETAS","Aridity factor ",1.)
494  ENDIF   !(iflag_pbl>1 .AND. iflag_wake>=1 .AND. iflag_pbl_split >=1 )
495
496!==================================
497!  thermiques, poches, convection
498!==================================
499
500! Emanuel
501  found=phyetat0_get(sig1,"sig1","sig1",0.)
502  found=phyetat0_get(w01,"w01","w01",0.)
503
504! Wake
505  found=phyetat0_get(wake_deltat,"WAKE_DELTAT","Delta T wake/env",0.)
506  found=phyetat0_get(wake_deltaq,"WAKE_DELTAQ","Delta hum. wake/env",0.)
507  found=phyetat0_get(wake_s,"WAKE_S","Wake frac. area",0.)
508  found=phyetat0_get(awake_s,"AWAKE_S","Active Wake frac. area",0.)
509!jyg<
510!  Set wake_dens to -1000. when there is no restart so that the actual
511!  initialization is made in calwake.
512!!  found=phyetat0_get(1,wake_dens,"WAKE_DENS","Wake num. /unit area",0.)
513  found=phyetat0_get(wake_dens,"WAKE_DENS","Wake num. /unit area",-1000.)
514  found=phyetat0_get(awake_dens,"AWAKE_DENS","Active Wake num. /unit area",0.)
515  found=phyetat0_get(cv_gen,"CV_GEN","CB birth rate",0.)
516!>jyg
517  found=phyetat0_get(wake_cstar,"WAKE_CSTAR","WAKE_CSTAR",0.)
518  found=phyetat0_get(wake_pe,"WAKE_PE","WAKE_PE",0.)
519  found=phyetat0_get(wake_fip,"WAKE_FIP","WAKE_FIP",0.)
520
521! Thermiques
522  found=phyetat0_get(zmax0,"ZMAX0","ZMAX0",40.)
523  found=phyetat0_get(f0,"F0","F0",1.e-5)
524  found=phyetat0_get(fm_therm,"FM_THERM","Thermals mass flux",0.)
525  found=phyetat0_get(entr_therm,"ENTR_THERM","Thermals Entrain.",0.)
526  found=phyetat0_get(detr_therm,"DETR_THERM","Thermals Detrain.",0.)
527
528! ALE/ALP
529  found=phyetat0_get(ale_bl,"ALE_BL","ALE BL",0.)
530  found=phyetat0_get(ale_bl_trig,"ALE_BL_TRIG","ALE BL_TRIG",0.)
531  found=phyetat0_get(alp_bl,"ALP_BL","ALP BL",0.)
532  found=phyetat0_get(ale_wake,"ALE_WAKE","ALE_WAKE",0.)
533  found=phyetat0_get(ale_bl_stat,"ALE_BL_STAT","ALE_BL_STAT",0.)
534
535! fisrtilp/Clouds 0.002 could be ratqsbas. But can stay like this as well
536  found=phyetat0_get(ratqs_inter_,"RATQS_INTER","Relative width of the lsc sugrid scale water",0.002)
537
538!===========================================
539  ! Read and send field trs to traclmdz
540!===========================================
541
542!--OB now this is for co2i - ThL: and therefore also for inco
543  IF (ANY(type_trac == ['co2i','inco'])) THEN
544     IF (carbon_cycle_cpl) THEN
545        ALLOCATE(co2_send(klon), stat=ierr)
546        IF (ierr /= 0) CALL abort_physic('phyetat0', 'pb allocation co2_send', 1)
547        found=phyetat0_get(co2_send,"co2_send","co2 send",co2_ppm0)
548     ENDIF
549  ELSE IF (type_trac == 'lmdz') THEN
550     it = 0
551     DO iq = 1, nqtot
552        IF(.NOT.(tracers(iq)%isAdvected .AND. tracers(iq)%isInPhysics)) CYCLE
553        it = it+1
554        tname = tracers(iq)%name
555        t(1) = 'trs_'//TRIM(tname); t(2) = 'trs_'//TRIM(new2oldH2O(tname))
556        found = phyetat0_get(trs(:,it), t(:), "Surf trac"//TRIM(tname), 0.)
557     END DO
558     CALL traclmdz_from_restart(trs)
559  ENDIF
560
561#ifdef ISO
562        ! initialise les isotopes       
563        write(*,*) 'phyetat0 1069'
564         CALL phyisoetat0 (snow,run_off_lic_0, &
565     &           xtsnow,xtrun_off_lic_0, &
566     &           Rland_ice)
567#ifdef ISOVERIF
568      write(*,*) 'phyetat0 1074'
569      if (iso_eau.gt.0) then
570      call iso_verif_egalite_vect2D(  &
571     &           xtsnow,snow, &
572     &           'phyetat0 1101a',niso,klon,nbsrf)
573        do i=1,klon 
574              call iso_verif_egalite(Rland_ice(iso_eau,i),1.0, &
575     &         'phyetat0 1101b')
576         enddo
577      endif
578      write(*,*) 'phyetat0 1102'
579#endif
580#endif
581
582!===========================================
583!  ondes de gravite / relief
584!===========================================
585
586!  ondes de gravite non orographiques
587  IF (ok_gwd_rando) found = &
588       phyetat0_get(du_gwd_rando,"du_gwd_rando","du_gwd_rando",0.)
589  IF (.NOT. ok_hines .AND. ok_gwd_rando) found &
590       = phyetat0_get(du_gwd_front,"du_gwd_front","du_gwd_front",0.)
591
592!  prise en compte du relief sous-maille
593  found=phyetat0_get(zmea,"ZMEA","sub grid orography",0.)
594  found=phyetat0_get(zstd,"ZSTD","sub grid orography",0.)
595  found=phyetat0_get(zsig,"ZSIG","sub grid orography",0.)
596  found=phyetat0_get(zgam,"ZGAM","sub grid orography",0.)
597  found=phyetat0_get(zthe,"ZTHE","sub grid orography",0.)
598  found=phyetat0_get(zpic,"ZPIC","sub grid orography",0.)
599  found=phyetat0_get(zval,"ZVAL","sub grid orography",0.)
600  found=phyetat0_get(zmea,"ZMEA","sub grid orography",0.)
601  found=phyetat0_get(rugoro,"RUGSREL","sub grid orography",0.)
602
603!===========================================
604! Initialize ocean
605!===========================================
606
607  IF ( type_ocean == 'slab' ) THEN
608      CALL ocean_slab_init(phys_tstep, pctsrf)
609      IF (nslay.EQ.1) THEN
610        found=phyetat0_get(tslab,["tslab01","tslab  "],"tslab",0.)
611      ELSE
612          DO i=1,nslay
613            WRITE(str2,'(i2.2)') i
614            found=phyetat0_get(tslab(:,i),"tslab"//str2,"tslab",0.) 
615          ENDDO
616      ENDIF
617      IF (.NOT. found) THEN
618          PRINT*, "phyetat0: Le champ <tslab> est absent"
619          PRINT*, "Initialisation a tsol_oce"
620          DO i=1,nslay
621              tslab(:,i)=MAX(ftsol(:,is_oce),271.35)
622          ENDDO
623      ENDIF
624
625      ! Sea ice variables
626      IF (version_ocean == 'sicINT') THEN
627          found=phyetat0_get(tice,"slab_tice","slab_tice",0.)
628          IF (.NOT. found) THEN
629              PRINT*, "phyetat0: Le champ <tice> est absent"
630              PRINT*, "Initialisation a tsol_sic"
631                  tice(:)=ftsol(:,is_sic)
632          ENDIF
633          found=phyetat0_get(seaice,"seaice","seaice",0.)
634          IF (.NOT. found) THEN
635              PRINT*, "phyetat0: Le champ <seaice> est absent"
636              PRINT*, "Initialisation a 0/1m suivant fraction glace"
637              seaice(:)=0.
638              WHERE (pctsrf(:,is_sic).GT.EPSFRA)
639                  seaice=917.
640              ENDWHERE
641          ENDIF
642      ENDIF !sea ice INT
643  ENDIF ! Slab       
644
645  if (activate_ocean_skin >= 1) then
646     if (activate_ocean_skin == 2 .and. type_ocean == 'couple') then
647        found = phyetat0_get(delta_sal, "delta_sal", &
648             "ocean-air interface salinity minus bulk salinity", 0.)
649        found = phyetat0_get(delta_sst, "delta_SST", &
650             "ocean-air interface temperature minus bulk SST", 0.)
651        found = phyetat0_get(dter, "dter", &
652             "ocean-air interface temperature minus subskin temperature", 0.)
653        found = phyetat0_get(dser, "dser", &
654             "ocean-air interface salinity minus subskin salinity", 0.)
655        found = phyetat0_get(dt_ds, "dt_ds", "(tks / tkt) * dTer", 0.)
656
657        where (pctsrf(:, is_oce) == 0.)
658           delta_sst = missing_val
659           delta_sal = missing_val
660           dter = missing_val
661           dser = missing_val
662           dt_ds = missing_val
663        end where
664     end if
665     
666     found = phyetat0_get(ds_ns, "dS_ns", "delta salinity near surface", 0.)
667     found = phyetat0_get(dt_ns, "dT_ns", "delta temperature near surface", &
668          0.)
669
670     where (pctsrf(:, is_oce) == 0.)
671        ds_ns = missing_val
672        dt_ns = missing_val
673        delta_sst = missing_val
674        delta_sal = missing_val
675     end where
676  end if
677
678  ! on ferme le fichier
679  CALL close_startphy
680
681  ! Initialize module pbl_surface_mod
682
683! 994 est trop grand quand OpenMP est activé : on sort du tableau
684!#ifdef ISOVERIF
685!        write(*,*) 'phyetat0 572: snow(994,:)=',snow(994,2)
686!        write(*,*) 'xtsnow(:,994,2)=',xtsnow(:,994,2)
687!#endif
688  if ( iflag_physiq <= 1 ) then
689  CALL pbl_surface_init(fder, snow, qsurf, tsoil)
690#ifdef ISO
691  CALL pbl_surface_init_iso(xtsnow,Rland_ice)
692#endif
693  endif
694
695  ! Initialize module ocean_cpl_mod for the case of coupled ocean
696  IF ( type_ocean == 'couple' ) THEN
697     CALL ocean_cpl_init(phys_tstep, longitude_deg, latitude_deg)
698  ENDIF
699
700!  CALL init_iophy_new(latitude_deg, longitude_deg)
701
702  ! Initilialize module fonte_neige_mod     
703  CALL fonte_neige_init(run_off_lic_0)
704#ifdef ISO
705   CALL fonte_neige_init_iso(xtrun_off_lic_0)
706#endif
707
708END SUBROUTINE phyetat0
709
710END MODULE phyetat0_mod
711
Note: See TracBrowser for help on using the repository browser.