source: LMDZ6/branches/contrails/libf/phylmd/phyetat0_mod.f90 @ 5790

Last change on this file since 5790 was 5790, checked in by aborella, 4 months ago

Major modifs to treatment of contrails (from 2 classes to 2 moments) + diagnostics. Increased numerical efficiency

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