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

Last change on this file since 5774 was 5662, checked in by Laurent Fairhead, 6 months ago

Ajout du modèle thermodynamique de glace de mer interactive améliorant les flux échangés à la surface de la banquise (Doctorat de Nicolas Michalezyk, Contact : Nicolas Michaleyk, Guillaume Gastineau)

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