source: LMDZ6/trunk/libf/phylmdiso/phyetat0_mod.F90 @ 5285

Last change on this file since 5285 was 5285, checked in by abarral, 13 months ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

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