source: LMDZ6/branches/Amaury_dev/libf/phylmdiso/phyetat0_mod.F90 @ 5367

Last change on this file since 5367 was 5224, checked in by abarral, 2 months ago

Merge r5204 r5205
Light lint
Correct missing IOIPSL includes

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