source: LMDZ6/trunk/libf/phylmd/phyetat0_mod.F90 @ 4537

Last change on this file since 4537 was 4537, checked in by fhourdin, 14 months ago

Travail preparatoire au couplage avec mesoNH

Travail preparatoire aux test d'integration de la physique de MesoNH
et plus generalement a la reecriture du moniteur de la physique.
phylmd appelle phylmdex si une cle iflag_physiq=2 est ajoutee dans run.def
Il a ete necessaire en plus d'eliminer un certain nombre d'appels dans
phyetat0 et phyredem.

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