source: LMDZ6/branches/Amaury_dev/libf/phylmd/phyetat0_mod.F90 @ 5225

Last change on this file since 5225 was 5224, checked in by abarral, 7 weeks ago

Merge r5204 r5205
Light lint
Correct missing IOIPSL includes

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