source: LMDZ6/branches/cirrus/libf/phylmd/phyetat0_mod.F90 @ 5133

Last change on this file since 5133 was 4951, checked in by aborella, 19 months ago

New version of condensation and ice supersaturation in LSCP.
Multiple changes troughout the code (in particular, two new water phase tracers).

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