source: LMDZ6/trunk/libf/phylmd/phyetat0_mod.f90 @ 5687

Last change on this file since 5687 was 5662, checked in by Laurent Fairhead, 6 weeks 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)

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