source: LMDZ6/trunk/libf/phylmdiso/phyetat0.F90 @ 4050

Last change on this file since 4050 was 4050, checked in by dcugnet, 2 years ago

Second commit for new tracers.

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