source: LMDZ6/trunk/libf/phylmd/phyetat0_mod.f90 @ 5624

Last change on this file since 5624 was 5481, checked in by dcugnet, 10 months ago

Remove tracers attributes "isAdvected" and "isInPhysics" from infotrac (iadv is enough).
Remove tracers attribute "isAdvected" from infotrac_phy (isInPhysics is now equivalent
to former isInPhysics .AND. iadv > 0

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