GCC Code Coverage Report
Directory: ./ Exec Total Coverage
File: phylmd/phyetat0_mod.F90 Lines: 181 274 66.1 %
Date: 2023-06-30 12:51:15 Branches: 231 566 40.8 %

Line Branch Exec Source
1
! $Id: phyetat0_mod.F90 4581 2023-06-20 18:38:17Z evignon $
2
3
MODULE phyetat0_mod
4
5
  PRIVATE
6
  PUBLIC :: phyetat0
7
8
CONTAINS
9
10
20
SUBROUTINE phyetat0 (fichnom, clesphy0, tabcntr0)
11
12
  USE dimphy, only: klon, zmasq, klev
13
  USE iophy, ONLY : init_iophy_new
14
  USE ocean_cpl_mod,    ONLY : ocean_cpl_init
15
  USE fonte_neige_mod,  ONLY : fonte_neige_init
16
  USE pbl_surface_mod,  ONLY : pbl_surface_init
17
  USE surface_data,     ONLY : type_ocean, version_ocean
18
  USE phyetat0_get_mod, ONLY : phyetat0_get, phyetat0_srf
19
  USE phys_state_var_mod, ONLY : ancien_ok, clwcon, detr_therm, phys_tstep, &
20
       qsol, fevap, z0m, z0h, agesno, &
21
       du_gwd_rando, du_gwd_front, entr_therm, f0, fm_therm, &
22
       falb_dir, falb_dif, prw_ancien, prlw_ancien, prsw_ancien, prbsw_ancien, &
23
       ftsol, pbl_tke, pctsrf, q_ancien, ql_ancien, qs_ancien, qbs_ancien, rneb_ancien, radpas, radsol, rain_fall, ratqs, &
24
       rnebcon, rugoro, sig1, snow_fall, bs_fall, solaire_etat0, sollw, sollwdown, &
25
       solsw, solswfdiff, t_ancien, u_ancien, v_ancien, w01, wake_cstar, wake_deltaq, &
26
       wake_deltat, wake_delta_pbl_TKE, delta_tsurf, beta_aridity, wake_fip, wake_pe, &
27
       wake_s, wake_dens, awake_dens, cv_gen, zgam, zmax0, zmea, zpic, zsig, &
28
       zstd, zthe, zval, ale_bl, ale_bl_trig, alp_bl, u10m, v10m, treedrg, &
29
       ale_wake, ale_bl_stat, ds_ns, dt_ns, delta_sst, delta_sal, dter, dser, &
30
       dt_ds, ratqs_inter
31
!FC
32
  USE geometry_mod,     ONLY: longitude_deg, latitude_deg
33
  USE iostart,          ONLY: close_startphy, get_field, get_var, open_startphy
34
  USE infotrac_phy,     ONLY: nqtot, nbtr, type_trac, tracers
35
  USE readTracFiles_mod,ONLY: maxlen, new2oldH2O
36
  USE traclmdz_mod,     ONLY: traclmdz_from_restart
37
  USE carbon_cycle_mod, ONLY: carbon_cycle_init, carbon_cycle_cpl, carbon_cycle_tr, carbon_cycle_rad, co2_send, RCO2_glo
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
40
  USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
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
47
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"
55
  include "alpale.h"
56
  include "compbl.h"
57
  include "YOMCST.h"
58
  !======================================================================
59
  CHARACTER*(*) fichnom
60
61
  ! les variables globales lues dans le fichier restart
62
63
2
  REAL tsoil(klon, nsoilmx, nbsrf)
64
2
  REAL qsurf(klon, nbsrf)
65
2
  REAL snow(klon, nbsrf)
66
2
  real fder(klon)
67
2
  REAL run_off_lic_0(klon)
68
2
  REAL fractint(klon)
69
2
  REAL trs(klon, nbtr)
70
2
  REAL zts(klon)
71
  ! pour drag arbres FC
72
2
  REAL drg_ter(klon,klev)
73
74
  CHARACTER*6 ocean_in
75
  LOGICAL ok_veget_in
76
77
  INTEGER        longcles
78
  PARAMETER    ( longcles = 20 )
79
  REAL clesphy0( longcles )
80
81
  REAL xmin, xmax
82
83
  INTEGER nid, nvarid
84
  INTEGER ierr, i, nsrf, isoil , k
85
  INTEGER length
86
  PARAMETER (length=100)
87
  INTEGER it, iq, isw
88
  REAL tab_cntrl(length), tabcntr0(length)
89
  CHARACTER*7 str7
90
  CHARACTER*2 str2
91
  LOGICAL :: found
92
2
  REAL :: lon_startphy(klon), lat_startphy(klon)
93
  CHARACTER(LEN=maxlen) :: tname, t(2)
94
95
  ! FH1D
96
  !     real iolat(jjm+1)
97
  !real iolat(jjm+1-1/(iim*jjm))
98
99
  ! Ouvrir le fichier contenant l'etat initial:
100
101
1
  CALL open_startphy(fichnom)
102
103
  ! Lecture des parametres de controle:
104
105
1
  CALL get_var("controle", tab_cntrl)
106
107
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
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
116
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
117
118
101
  DO i = 1, length
119
101
     tabcntr0( i ) = tab_cntrl( i )
120
  ENDDO
121
122
1
  tab_cntrl(1)=pdtphys
123
1
  tab_cntrl(2)=radpas
124
125
  ! co2_ppm : value from the previous time step
126
127
  ! co2_ppm0 : initial value of atmospheric CO2 (from create_etat0_limit.e .def)
128
1
  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
135

1
  IF (carbon_cycle_tr .OR. carbon_cycle_cpl) THEN
136
     co2_ppm = tab_cntrl(3)
137
     RCO2    = co2_ppm * 1.0e-06 * RMCO2 / RMD
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
143
     ! ELSE : keep value from .def
144
  ENDIF
145
146
1
  solaire_etat0      = tab_cntrl(4)
147
1
  tab_cntrl(5)=iflag_con
148
1
  tab_cntrl(6)=nbapp_rad
149
150
1
  IF (iflag_cycle_diurne.GE.1) tab_cntrl( 7) = iflag_cycle_diurne
151
1
  IF (soil_model) tab_cntrl( 8) =1.
152
1
  IF (new_oliq) tab_cntrl( 9) =1.
153
1
  IF (ok_orodr) tab_cntrl(10) =1.
154
1
  IF (ok_orolf) tab_cntrl(11) =1.
155
1
  IF (ok_limitvrai) tab_cntrl(12) =1.
156
157
1
  itau_phy = tab_cntrl(15)
158
159
1
  clesphy0(1)=tab_cntrl( 5 )
160
1
  clesphy0(2)=tab_cntrl( 6 )
161
1
  clesphy0(3)=tab_cntrl( 7 )
162
1
  clesphy0(4)=tab_cntrl( 8 )
163
1
  clesphy0(5)=tab_cntrl( 9 )
164
1
  clesphy0(6)=tab_cntrl( 10 )
165
1
  clesphy0(7)=tab_cntrl( 11 )
166
1
  clesphy0(8)=tab_cntrl( 12 )
167
1
  clesphy0(9)=tab_cntrl( 17 )
168
169
  ! set time iteration
170
1
   CALL init_iteration(itau_phy)
171
172
  ! read latitudes and make a sanity check (because already known from dyn)
173
1
  CALL get_field("latitude",lat_startphy)
174
995
  DO i=1,klon
175
994
    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
995
    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
188
189
  ! read longitudes and make a sanity check (because already known from dyn)
190
1
  CALL get_field("longitude",lon_startphy)
191
995
  DO i=1,klon
192
994
    IF (ABS(lon_startphy(i)-longitude_deg(i))>=1) THEN
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
200
    ENDIF
201
995
    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
207
    ENDIF
208
  ENDDO
209
210
  ! Lecture du masque terre mer
211
212
1
  CALL get_field("masque", zmasq, found)
213
1
  IF (.NOT. found) THEN
214
     PRINT*, 'phyetat0: Le champ <masque> est absent'
215
     PRINT *, 'fichier startphy non compatible avec phyetat0'
216
  ENDIF
217
218
  ! Lecture des fractions pour chaque sous-surface
219
220
  ! initialisation des sous-surfaces
221
222

3981
  pctsrf = 0.
223
224
  ! fraction de terre
225
226
1
  CALL get_field("FTER", pctsrf(:, is_ter), found)
227
1
  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FTER> est absent'
228
229
  ! fraction de glace de terre
230
231
1
  CALL get_field("FLIC", pctsrf(:, is_lic), found)
232
1
  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FLIC> est absent'
233
234
  ! fraction d'ocean
235
236
1
  CALL get_field("FOCE", pctsrf(:, is_oce), found)
237
1
  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FOCE> est absent'
238
239
  ! fraction glace de mer
240
241
1
  CALL get_field("FSIC", pctsrf(:, is_sic), found)
242
1
  IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FSIC> est absent'
243
244
  !  Verification de l'adequation entre le masque et les sous-surfaces
245
246
  fractint( 1 : klon) = pctsrf(1 : klon, is_ter)  &
247
995
       + pctsrf(1 : klon, is_lic)
248
995
  DO i = 1 , klon
249
995
     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
256
  ENDDO
257
  fractint (1 : klon) =  pctsrf(1 : klon, is_oce)  &
258
995
       + pctsrf(1 : klon, is_sic)
259
995
  DO i = 1 , klon
260
995
     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)
264
        WRITE(*, *) 'Je force la coherence zmasq=1.-fractint'
265
        zmasq(i) = 1. - fractint(i)
266
     ENDIF
267
  ENDDO
268
269
!===================================================================
270
! Lecture des temperatures du sol:
271
!===================================================================
272
273
1
  found=phyetat0_get(ftsol(:,1),"TS","Surface temperature",283.)
274
1
  IF (found) THEN
275
     DO nsrf=2,nbsrf
276
        ftsol(:,nsrf)=ftsol(:,1)
277
     ENDDO
278
  ELSE
279
1
     found=phyetat0_srf(ftsol,"TS","Surface temperature",283.)
280
  ENDIF
281
282
!===================================================================
283
  ! Lecture des albedo difus et direct
284
!===================================================================
285
286
5
  DO nsrf = 1, nbsrf
287
29
     DO isw=1, nsw
288
24
        IF (isw.GT.99) THEN
289
           PRINT*, "Trop de bandes SW"
290
           call abort_physic("phyetat0", "", 1)
291
        ENDIF
292
24
        WRITE(str2, '(i2.2)') isw
293
24
        found=phyetat0_srf(falb_dir(:, isw,:),"A_dir_SW"//str2//"srf","Direct Albedo",0.2)
294
28
        found=phyetat0_srf(falb_dif(:, isw,:),"A_dif_SW"//str2//"srf","Direct Albedo",0.2)
295
     ENDDO
296
  ENDDO
297
298
1
  found=phyetat0_srf(u10m,"U10M","u a 10m",0.)
299
1
  found=phyetat0_srf(v10m,"V10M","v a 10m",0.)
300
301
!===================================================================
302
! Lecture dans le cas iflag_pbl_surface =1
303
!===================================================================
304
305
1
   if ( iflag_physiq <= 1 ) then
306
!===================================================================
307
  ! Lecture des temperatures du sol profond:
308
!===================================================================
309
310
12
   DO isoil=1, nsoilmx
311
        IF (isoil.GT.99) THEN
312
           PRINT*, "Trop de couches "
313
           call abort_physic("phyetat0", "", 1)
314
        ENDIF
315
11
        WRITE(str2,'(i2.2)') isoil
316
11
        found=phyetat0_srf(tsoil(:, isoil,:),"Tsoil"//str2//"srf","Temp soil",0.)
317
12
        IF (.NOT. found) THEN
318
           PRINT*, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
319
           PRINT*, "          Il prend donc la valeur de surface"
320
           tsoil(:, isoil, :)=ftsol(:, :)
321
        ENDIF
322
   ENDDO
323
324
!=======================================================================
325
! Lecture precipitation/evaporation
326
!=======================================================================
327
328
1
  found=phyetat0_srf(qsurf,"QS","Near surface hmidity",0.)
329
1
  found=phyetat0_get(qsol,"QSOL","Surface hmidity / bucket",0.)
330
1
  found=phyetat0_srf(snow,"SNOW","Surface snow",0.)
331
1
  found=phyetat0_srf(fevap,"EVAP","evaporation",0.)
332
1
  found=phyetat0_get(snow_fall,"snow_f","snow fall",0.)
333
1
  found=phyetat0_get(rain_fall,"rain_f","rain fall",0.)
334
1
  IF (ok_bs) THEN
335
     found=phyetat0_get(bs_fall,"bs_f","blowing snow fall",0.)
336
  ELSE
337
995
     bs_fall(:)=0.
338
  ENDIF
339
!=======================================================================
340
! Radiation
341
!=======================================================================
342
343
1
  found=phyetat0_get(solsw,"solsw","net SW radiation surf",0.)
344
1
  found=phyetat0_get(solswfdiff,"solswfdiff","fraction of SW radiation surf that is diffuse",1.)
345
1
  found=phyetat0_get(sollw,"sollw","net LW radiation surf",0.)
346
1
  found=phyetat0_get(sollwdown,"sollwdown","down LW radiation surf",0.)
347
1
  IF (.NOT. found) THEN
348
     sollwdown(:) = 0. ;  zts(:)=0.
349
     DO nsrf=1,nbsrf
350
        zts(:)=zts(:)+ftsol(:,nsrf)*pctsrf(:,nsrf)
351
     ENDDO
352
     sollwdown(:)=sollw(:)+RSIGMA*zts(:)**4
353
  ENDIF
354
355
1
  found=phyetat0_get(radsol,"RADS","Solar radiation",0.)
356
1
  found=phyetat0_get(fder,"fder","Flux derivative",0.)
357
358
359
  ! Lecture de la longueur de rugosite
360
1
  found=phyetat0_srf(z0m,"RUG","Z0m ancien",0.001)
361
1
  IF (found) THEN
362
     z0h(:,1:nbsrf)=z0m(:,1:nbsrf)
363
  ELSE
364
1
     found=phyetat0_srf(z0m,"Z0m","Roughness length, momentum ",0.001)
365
1
     found=phyetat0_srf(z0h,"Z0h","Roughness length, enthalpy ",0.001)
366
  ENDIF
367
!FC
368
1
  IF (ifl_pbltree>0) THEN
369
!CALL get_field("FTER", pctsrf(:, is_ter), found)
370
    treedrg(:,1:klev,1:nbsrf)= 0.0
371
    CALL get_field("treedrg_ter", drg_ter(:,:), found)
372
!  found=phyetat0_srf(treedrg,"treedrg","drag from vegetation" , 0.)
373
    !lecture du profile de freinage des arbres
374
    IF (.not. found ) THEN
375
      treedrg(:,1:klev,1:nbsrf)= 0.0
376
    ELSE
377
      treedrg(:,1:klev,is_ter)= drg_ter(:,:)
378
!     found=phyetat0_get(treedrg,"treedrg","freinage arbres",0.)
379
    ENDIF
380
  ELSE
381
    ! initialize treedrg(), because it will be written in restartphy.nc
382

155225
    treedrg(:,:,:) = 0.0
383
  ENDIF
384
385
  endif ! iflag_physiq <= 1
386
387
  ! Lecture de l'age de la neige:
388
1
  found=phyetat0_srf(agesno,"AGESNO","SNOW AGE",0.001)
389
390
1
  ancien_ok=.true.
391
1
  ancien_ok=ancien_ok.AND.phyetat0_get(t_ancien,"TANCIEN","TANCIEN",0.)
392

1
  ancien_ok=ancien_ok.AND.phyetat0_get(q_ancien,"QANCIEN","QANCIEN",0.)
393

1
  ancien_ok=ancien_ok.AND.phyetat0_get(ql_ancien,"QLANCIEN","QLANCIEN",0.)
394

1
  ancien_ok=ancien_ok.AND.phyetat0_get(qs_ancien,"QSANCIEN","QSANCIEN",0.)
395

1
  ancien_ok=ancien_ok.AND.phyetat0_get(rneb_ancien,"RNEBANCIEN","RNEBANCIEN",0.)
396

1
  ancien_ok=ancien_ok.AND.phyetat0_get(u_ancien,"UANCIEN","UANCIEN",0.)
397

1
  ancien_ok=ancien_ok.AND.phyetat0_get(v_ancien,"VANCIEN","VANCIEN",0.)
398

1
  ancien_ok=ancien_ok.AND.phyetat0_get(prw_ancien,"PRWANCIEN","PRWANCIEN",0.)
399

1
  ancien_ok=ancien_ok.AND.phyetat0_get(prlw_ancien,"PRLWANCIEN","PRLWANCIEN",0.)
400

1
  ancien_ok=ancien_ok.AND.phyetat0_get(prsw_ancien,"PRSWANCIEN","PRSWANCIEN",0.)
401
402
  ! cas specifique des variables de la neige soufflee
403
1
  IF (ok_bs) THEN
404
     ancien_ok=ancien_ok.AND.phyetat0_get(qbs_ancien,"QBSANCIEN","QBSANCIEN",0.)
405
     ancien_ok=ancien_ok.AND.phyetat0_get(prbsw_ancien,"PRBSWANCIEN","PRBSWANCIEN",0.)
406
  ELSE
407

38806
     qbs_ancien(:,:)=0.
408
995
     prbsw_ancien(:)=0.
409
  ENDIF
410
411
  ! Ehouarn: addtional tests to check if t_ancien, q_ancien contain
412
  !          dummy values (as is the case when generated by ce0l,
413
  !          or by iniaqua)
414
  IF ( (maxval(q_ancien).EQ.minval(q_ancien))       .OR. &
415
       (maxval(ql_ancien).EQ.minval(ql_ancien))     .OR. &
416
       (maxval(qs_ancien).EQ.minval(qs_ancien))     .OR. &
417
       (maxval(rneb_ancien).EQ.minval(rneb_ancien)) .OR. &
418
       (maxval(prw_ancien).EQ.minval(prw_ancien))   .OR. &
419
       (maxval(prlw_ancien).EQ.minval(prlw_ancien)) .OR. &
420




















































394029
       (maxval(prsw_ancien).EQ.minval(prsw_ancien)) .OR. &
421
       (maxval(t_ancien).EQ.minval(t_ancien)) ) THEN
422
1
    ancien_ok=.false.
423
  ENDIF
424
425
1
  IF (ok_bs) THEN
426
    IF ( (maxval(qbs_ancien).EQ.minval(qbs_ancien))       .OR. &
427
         (maxval(prbsw_ancien).EQ.minval(prbsw_ancien)) ) THEN
428
       ancien_ok=.false.
429
    ENDIF
430
  ENDIF
431
432
1
  found=phyetat0_get(clwcon,"CLWCON","CLWCON",0.)
433
1
  found=phyetat0_get(rnebcon,"RNEBCON","RNEBCON",0.)
434
1
  found=phyetat0_get(ratqs,"RATQS","RATQS",0.)
435
436
1
  found=phyetat0_get(run_off_lic_0,"RUNOFFLIC0","RUNOFFLIC0",0.)
437
438
!==================================
439
!  TKE
440
!==================================
441
!
442
1
  IF (iflag_pbl>1) then
443
1
     found=phyetat0_srf(pbl_tke,"TKE","Turb. Kinetic. Energ. ",1.e-8)
444
  ENDIF
445
446

1
  IF (iflag_pbl>1 .AND. iflag_wake>=1  .AND. iflag_pbl_split >=1 ) then
447
1
    found=phyetat0_srf(wake_delta_pbl_tke,"DELTATKE","Del TKE wk/env",0.)
448
!!    found=phyetat0_srf(delta_tsurf,"DELTA_TSURF","Delta Ts wk/env ",0.)
449
1
    found=phyetat0_srf(delta_tsurf,"DELTATS","Delta Ts wk/env ",0.)
450
!!    found=phyetat0_srf(beta_aridity,"BETA_S","Aridity factor ",1.)
451
1
    found=phyetat0_srf(beta_aridity,"BETAS","Aridity factor ",1.)
452
  ENDIF   !(iflag_pbl>1 .AND. iflag_wake>=1 .AND. iflag_pbl_split >=1 )
453
454
!==================================
455
!  thermiques, poches, convection
456
!==================================
457
458
! Emanuel
459
1
  found=phyetat0_get(sig1,"sig1","sig1",0.)
460
1
  found=phyetat0_get(w01,"w01","w01",0.)
461
462
! Wake
463
1
  found=phyetat0_get(wake_deltat,"WAKE_DELTAT","Delta T wake/env",0.)
464
1
  found=phyetat0_get(wake_deltaq,"WAKE_DELTAQ","Delta hum. wake/env",0.)
465
1
  found=phyetat0_get(wake_s,"WAKE_S","Wake frac. area",0.)
466
!jyg<
467
!  Set wake_dens to -1000. when there is no restart so that the actual
468
!  initialization is made in calwake.
469
!!  found=phyetat0_get(1,wake_dens,"WAKE_DENS","Wake num. /unit area",0.)
470
1
  found=phyetat0_get(wake_dens,"WAKE_DENS","Wake num. /unit area",-1000.)
471
1
  found=phyetat0_get(awake_dens,"AWAKE_DENS","Active Wake num. /unit area",0.)
472
1
  found=phyetat0_get(cv_gen,"CV_GEN","CB birth rate",0.)
473
!>jyg
474
1
  found=phyetat0_get(wake_cstar,"WAKE_CSTAR","WAKE_CSTAR",0.)
475
1
  found=phyetat0_get(wake_pe,"WAKE_PE","WAKE_PE",0.)
476
1
  found=phyetat0_get(wake_fip,"WAKE_FIP","WAKE_FIP",0.)
477
478
! Thermiques
479
1
  found=phyetat0_get(zmax0,"ZMAX0","ZMAX0",40.)
480
1
  found=phyetat0_get(f0,"F0","F0",1.e-5)
481
1
  found=phyetat0_get(fm_therm,"FM_THERM","Thermals mass flux",0.)
482
1
  found=phyetat0_get(entr_therm,"ENTR_THERM","Thermals Entrain.",0.)
483
1
  found=phyetat0_get(detr_therm,"DETR_THERM","Thermals Detrain.",0.)
484
485
! ALE/ALP
486
1
  found=phyetat0_get(ale_bl,"ALE_BL","ALE BL",0.)
487
1
  found=phyetat0_get(ale_bl_trig,"ALE_BL_TRIG","ALE BL_TRIG",0.)
488
1
  found=phyetat0_get(alp_bl,"ALP_BL","ALP BL",0.)
489
1
  found=phyetat0_get(ale_wake,"ALE_WAKE","ALE_WAKE",0.)
490
1
  found=phyetat0_get(ale_bl_stat,"ALE_BL_STAT","ALE_BL_STAT",0.)
491
492
! fisrtilp/Clouds 0.002 could be ratqsbas. But can stay like this as well
493
1
  found=phyetat0_get(ratqs_inter,"RATQS_INTER","Relative width of the lsc sugrid scale water",0.002)
494
495
!===========================================
496
  ! Read and send field trs to traclmdz
497
!===========================================
498
499
!--OB now this is for co2i - ThL: and therefore also for inco
500

3
  IF (ANY(type_trac == ['co2i','inco'])) THEN
501
     IF (carbon_cycle_cpl) THEN
502
        ALLOCATE(co2_send(klon), stat=ierr)
503
        IF (ierr /= 0) CALL abort_physic('phyetat0', 'pb allocation co2_send', 1)
504
        found=phyetat0_get(co2_send,"co2_send","co2 send",co2_ppm0)
505
     ENDIF
506
1
  ELSE IF (type_trac == 'lmdz') THEN
507
     it = 0
508
6
     DO iq = 1, nqtot
509

5
        IF(.NOT.(tracers(iq)%isAdvected .AND. tracers(iq)%isInPhysics)) CYCLE
510
2
        it = it+1
511
2
        tname = tracers(iq)%name
512
2
        t(1) = 'trs_'//TRIM(tname); t(2) = 'trs_'//TRIM(new2oldH2O(tname))
513
6
        found = phyetat0_get(trs(:,it), t(:), "Surf trac"//TRIM(tname), 0.)
514
     END DO
515
1
     CALL traclmdz_from_restart(trs)
516
  ENDIF
517
518
519
!===========================================
520
!  ondes de gravite / relief
521
!===========================================
522
523
!  ondes de gravite non orographiques
524
1
  IF (ok_gwd_rando) found = &
525
1
       phyetat0_get(du_gwd_rando,"du_gwd_rando","du_gwd_rando",0.)
526

1
  IF (.NOT. ok_hines .AND. ok_gwd_rando) found &
527
1
       = phyetat0_get(du_gwd_front,"du_gwd_front","du_gwd_front",0.)
528
529
!  prise en compte du relief sous-maille
530
1
  found=phyetat0_get(zmea,"ZMEA","sub grid orography",0.)
531
1
  found=phyetat0_get(zstd,"ZSTD","sub grid orography",0.)
532
1
  found=phyetat0_get(zsig,"ZSIG","sub grid orography",0.)
533
1
  found=phyetat0_get(zgam,"ZGAM","sub grid orography",0.)
534
1
  found=phyetat0_get(zthe,"ZTHE","sub grid orography",0.)
535
1
  found=phyetat0_get(zpic,"ZPIC","sub grid orography",0.)
536
1
  found=phyetat0_get(zval,"ZVAL","sub grid orography",0.)
537
1
  found=phyetat0_get(zmea,"ZMEA","sub grid orography",0.)
538
1
  found=phyetat0_get(rugoro,"RUGSREL","sub grid orography",0.)
539
540
!===========================================
541
! Initialize ocean
542
!===========================================
543
544
1
  IF ( type_ocean == 'slab' ) THEN
545
      CALL ocean_slab_init(phys_tstep, pctsrf)
546
      IF (nslay.EQ.1) THEN
547
        found=phyetat0_get(tslab,["tslab01","tslab  "],"tslab",0.)
548
      ELSE
549
          DO i=1,nslay
550
            WRITE(str2,'(i2.2)') i
551
            found=phyetat0_get(tslab(:,i),"tslab"//str2,"tslab",0.)
552
          ENDDO
553
      ENDIF
554
      IF (.NOT. found) THEN
555
          PRINT*, "phyetat0: Le champ <tslab> est absent"
556
          PRINT*, "Initialisation a tsol_oce"
557
          DO i=1,nslay
558
              tslab(:,i)=MAX(ftsol(:,is_oce),271.35)
559
          ENDDO
560
      ENDIF
561
562
      ! Sea ice variables
563
      IF (version_ocean == 'sicINT') THEN
564
          found=phyetat0_get(tice,"slab_tice","slab_tice",0.)
565
          IF (.NOT. found) THEN
566
              PRINT*, "phyetat0: Le champ <tice> est absent"
567
              PRINT*, "Initialisation a tsol_sic"
568
                  tice(:)=ftsol(:,is_sic)
569
          ENDIF
570
          found=phyetat0_get(seaice,"seaice","seaice",0.)
571
          IF (.NOT. found) THEN
572
              PRINT*, "phyetat0: Le champ <seaice> est absent"
573
              PRINT*, "Initialisation a 0/1m suivant fraction glace"
574
              seaice(:)=0.
575
              WHERE (pctsrf(:,is_sic).GT.EPSFRA)
576
                  seaice=917.
577
              ENDWHERE
578
          ENDIF
579
      ENDIF !sea ice INT
580
  ENDIF ! Slab
581
582
1
  if (activate_ocean_skin >= 1) then
583
     if (activate_ocean_skin == 2 .and. type_ocean == 'couple') then
584
        found = phyetat0_get(delta_sal, "delta_sal", &
585
             "ocean-air interface salinity minus bulk salinity", 0.)
586
        found = phyetat0_get(delta_sst, "delta_SST", &
587
             "ocean-air interface temperature minus bulk SST", 0.)
588
        found = phyetat0_get(dter, "dter", &
589
             "ocean-air interface temperature minus subskin temperature", 0.)
590
        found = phyetat0_get(dser, "dser", &
591
             "ocean-air interface salinity minus subskin salinity", 0.)
592
        found = phyetat0_get(dt_ds, "dt_ds", "(tks / tkt) * dTer", 0.)
593
594
        where (pctsrf(:, is_oce) == 0.)
595
           delta_sst = missing_val
596
           delta_sal = missing_val
597
           dter = missing_val
598
           dser = missing_val
599
           dt_ds = missing_val
600
        end where
601
     end if
602
603
     found = phyetat0_get(ds_ns, "dS_ns", "delta salinity near surface", 0.)
604
     found = phyetat0_get(dt_ns, "dT_ns", "delta temperature near surface", &
605
          0.)
606
607
     where (pctsrf(:, is_oce) == 0.)
608
        ds_ns = missing_val
609
        dt_ns = missing_val
610
        delta_sst = missing_val
611
        delta_sal = missing_val
612
     end where
613
  end if
614
615
  ! on ferme le fichier
616
1
  CALL close_startphy
617
618
  ! Initialize module pbl_surface_mod
619
620
1
  if ( iflag_physiq <= 1 ) then
621
1
  CALL pbl_surface_init(fder, snow, qsurf, tsoil)
622
  endif
623
624
  ! Initialize module ocean_cpl_mod for the case of coupled ocean
625
1
  IF ( type_ocean == 'couple' ) THEN
626
     CALL ocean_cpl_init(phys_tstep, longitude_deg, latitude_deg)
627
  ENDIF
628
629
!  CALL init_iophy_new(latitude_deg, longitude_deg)
630
631
  ! Initilialize module fonte_neige_mod
632
1
  CALL fonte_neige_init(run_off_lic_0)
633
634
1
END SUBROUTINE phyetat0
635
636
END MODULE phyetat0_mod
637