source: LMDZ6/trunk/libf/phylmd/phyetat0_mod.F90 @ 4443

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