source: LMDZ6/trunk/libf/phylmd/phyredem.F90 @ 3888

Last change on this file since 3888 was 3888, checked in by jyg, 3 years ago

New provisional version of the splitting of the
diffusive boundary layer into inwake and offwake
PBLs. The splitting of the diffuse BL should NOT
be activated yet for general purpose simulations.

The splitting is activated by:
mod(iflag_pbl_split,10)=1 for the option with
fixed surface temperature and
mod(iflag_pbl_split,10)=2 for the option with
coupled surface temperature.

iflag_pbl_split=0 ==> no splittingat all.
iflag_pbl_split=10 ==> splitting of thermals.
iflag_pbl_split=11 ==> splitting of thermals and
of vertical diffusion (fixed surf. temp.).
iflag_pbl_split=12 ==> splitting of thermals and
of vertical diffusion (coupled surf. temp.).

  • 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: 14.1 KB
Line 
1!
2! $Id: phyredem.F90 3888 2021-05-05 10:50:37Z jyg $
3!
4SUBROUTINE phyredem (fichnom)
5!
6!-------------------------------------------------------------------------------
7! Author: Z.X. Li (LMD/CNRS), 1993/08/18
8!-------------------------------------------------------------------------------
9! Purpose: Write restart state for physics.
10!-------------------------------------------------------------------------------
11  USE dimphy, ONLY: klon, klev
12  USE fonte_neige_mod,  ONLY : fonte_neige_final
13  USE pbl_surface_mod,  ONLY : pbl_surface_final
14  USE phys_state_var_mod, ONLY: radpas, zmasq, pctsrf,                       &
15                                ftsol, beta_aridity, delta_tsurf, falb_dir,  &
16                                falb_dif, qsol, fevap, radsol, solsw, sollw, &
17                                sollwdown, rain_fall, snow_fall, z0m, z0h,   &
18                                agesno, zmea, zstd, zsig, zgam, zthe, zpic,  &
19                                zval, rugoro, t_ancien, q_ancien,            &
20                                prw_ancien, prlw_ancien, prsw_ancien,        &
21                                ql_ancien, qs_ancien,  u_ancien,             &
22                                v_ancien, clwcon, rnebcon, ratqs, pbl_tke,   &
23                                wake_delta_pbl_tke, zmax0, f0, sig1, w01,    &
24                                wake_deltat, wake_deltaq, wake_s, wake_dens, &
25                                wake_cstar,                                  &
26                                wake_pe, wake_fip, fm_therm, entr_therm,     &
27                                detr_therm, ale_bl, ale_bl_trig, alp_bl,     &
28                                ale_wake, ale_bl_stat,                       &
29                                du_gwd_rando, du_gwd_front, u10m, v10m, &
30                                treedrg, solswfdiff, delta_sal, ds_ns, dt_ns, &
31                                delta_sst, ratqs_inter
32
33  USE geometry_mod, ONLY : longitude_deg, latitude_deg
34  USE iostart, ONLY: open_restartphy, close_restartphy, enddef_restartphy, put_field, put_var
35  USE traclmdz_mod, ONLY : traclmdz_to_restart
36  USE infotrac_phy, ONLY: type_trac, niadv, tname, nbtr, nqo
37  USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
38  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic, epsfra
39  USE surface_data, ONLY: type_ocean, version_ocean
40  USE ocean_slab_mod, ONLY : nslay, tslab, seaice, tice, fsic
41  USE time_phylmdz_mod, ONLY: annee_ref, day_end, itau_phy, pdtphys
42  use config_ocean_skin_m, only: activate_ocean_skin 
43
44  IMPLICIT none
45
46  include "dimsoil.h"
47  include "clesphys.h"
48  include "thermcell.h"
49  include "compbl.h"
50  !======================================================================
51  CHARACTER*(*) fichnom
52
53  ! les variables globales ecrites dans le fichier restart
54
55  REAL tsoil(klon, nsoilmx, nbsrf)
56  REAL qsurf(klon, nbsrf)
57  REAL snow(klon, nbsrf)
58  real fder(klon)
59  REAL run_off_lic_0(klon)
60  REAL trs(klon, nbtr)
61
62  INTEGER nid, nvarid, idim1, idim2, idim3
63  INTEGER ierr
64  INTEGER length
65  PARAMETER (length=100)
66  REAL tab_cntrl(length)
67
68  INTEGER isoil, nsrf,isw
69  CHARACTER (len=2) :: str2
70  CHARACTER (len=256) :: nam, lnam
71  INTEGER           :: it, iiq, pass
72
73  !======================================================================
74
75  ! Get variables which will be written to restart file from module
76  ! pbl_surface_mod
77  CALL pbl_surface_final(fder, snow, qsurf,  tsoil)
78
79  ! Get a variable calculated in module fonte_neige_mod
80  CALL fonte_neige_final(run_off_lic_0)
81
82  !======================================================================
83
84  CALL open_restartphy(fichnom)
85
86 
87  DO ierr = 1, length
88     tab_cntrl(ierr) = 0.0
89  ENDDO
90  tab_cntrl(1) = pdtphys
91  tab_cntrl(2) = radpas
92  ! co2_ppm : current value of atmospheric CO2
93  tab_cntrl(3) = co2_ppm
94  tab_cntrl(4) = solaire
95  tab_cntrl(5) = iflag_con
96  tab_cntrl(6) = nbapp_rad
97
98  IF( iflag_cycle_diurne.GE.1 ) tab_cntrl( 7 ) = iflag_cycle_diurne
99  IF(   soil_model ) tab_cntrl( 8 ) = 1.
100  IF(     new_oliq ) tab_cntrl( 9 ) = 1.
101  IF(     ok_orodr ) tab_cntrl(10 ) = 1.
102  IF(     ok_orolf ) tab_cntrl(11 ) = 1.
103
104  tab_cntrl(13) = day_end
105  tab_cntrl(14) = annee_ref
106  tab_cntrl(15) = itau_phy
107
108  ! co2_ppm0 : initial value of atmospheric CO2
109  tab_cntrl(16) = co2_ppm0
110
111  DO pass=1,2   ! pass=1 netcdf definition ; pass=2 netcdf write
112 
113    CALL put_var(pass, "controle", "Parametres de controle", tab_cntrl)
114
115    CALL put_field(pass,"longitude", &
116         "Longitudes de la grille physique", longitude_deg)
117
118    CALL put_field(pass,"latitude", "Latitudes de la grille physique", latitude_deg)
119
120    ! PB ajout du masque terre/mer
121
122    CALL put_field(pass,"masque", "masque terre mer", zmasq)
123
124    ! BP ajout des fraction de chaque sous-surface
125
126    ! Get last fractions from slab ocean
127    IF (type_ocean == 'slab' .AND. version_ocean == "sicINT") THEN
128        WHERE (1.-zmasq(:).GT.EPSFRA)
129            pctsrf(:,is_oce)=(1.-fsic(:))*(1.-zmasq(:))
130            pctsrf(:,is_sic)=fsic(:)*(1.-zmasq(:))
131        END WHERE
132    END IF
133
134    ! 1. fraction de terre
135
136    CALL put_field(pass,"FTER", "fraction de continent", pctsrf(:, is_ter))
137
138    ! 2. Fraction de glace de terre
139
140    CALL put_field(pass,"FLIC", "fraction glace de terre", pctsrf(:, is_lic))
141
142    ! 3. fraction ocean
143
144    CALL put_field(pass,"FOCE", "fraction ocean", pctsrf(:, is_oce))
145
146    ! 4. Fraction glace de mer
147
148    CALL put_field(pass,"FSIC", "fraction glace mer", pctsrf(:, is_sic))
149
150    IF(nbsrf>99) THEN
151      PRINT*, "Trop de sous-mailles";  CALL abort_physic("phyredem", "", 1)
152    END IF
153    IF(nsoilmx>99) THEN
154      PRINT*, "Trop de sous-surfaces"; CALL abort_physic("phyredem", "", 1)
155    END IF
156    IF(nsw>99) THEN
157      PRINT*, "Trop de bandes"; CALL abort_physic("phyredem", "", 1)
158    END IF
159
160!    Surface variables
161    CALL put_field_srf1(pass,"TS","Temperature",ftsol(:,:))
162
163    CALL put_field_srf1(pass,"DELTA_TS","w-x surface temperature difference", delta_tsurf(:,:))
164
165    CALL put_field_srf1(pass,"BETA_S","Aridity factor", beta_aridity(:,:))
166!    End surface variables
167
168! ================== Albedo =======================================
169    print*,'PHYREDEM NOUVEAU'
170    CALL put_field_srf2(pass,"A_dir_SW","Albedo direct",falb_dir(:,:,:))
171    CALL put_field_srf2(pass,"A_dif_SW","Albedo diffus",falb_dif(:,:,:))
172
173    CALL put_field_srf1(pass,"U10M", "u a 10m", u10m)
174
175    CALL put_field_srf1(pass,"V10M", "v a 10m", v10m)
176
177
178! ================== Tsoil =========================================
179    CALL put_field_srf2(pass,"Tsoil","Temperature",tsoil(:,:,:))
180!FC
181!  CALL put_field_srf2("treedrg","freinage arbres",treedrg(:,:,:))
182    CALL put_field(pass,"treedrg_ter","freinage arbres",treedrg(:,:,is_ter))
183
184
185    CALL put_field_srf1(pass,"QS"  , "Humidite",qsurf(:,:))
186
187    CALL put_field     (pass,"QSOL", "Eau dans le sol (mm)", qsol)
188
189    CALL put_field_srf1(pass,"EVAP", "Evaporation", fevap(:,:))
190
191    CALL put_field_srf1(pass,"SNOW", "Neige", snow(:,:))
192
193    CALL put_field(pass,"RADS", "Rayonnement net a la surface", radsol)
194
195    CALL put_field(pass,"solsw", "Rayonnement solaire a la surface", solsw)
196
197    CALL put_field(pass,"solswfdiff", "Fraction du rayonnement solaire a la surface qui est diffus", solswfdiff)
198
199    CALL put_field(pass,"sollw", "Rayonnement IF a la surface", sollw)
200
201    CALL put_field(pass,"sollwdown", "Rayonnement down IF a la surface", sollwdown)
202
203    CALL put_field(pass,"fder", "Derive de flux", fder)
204
205    CALL put_field(pass,"rain_f", "precipitation liquide", rain_fall)
206
207    CALL put_field(pass,"snow_f", "precipitation solide", snow_fall)
208
209    CALL put_field_srf1(pass,"Z0m", "rugosite", z0m(:,:))
210
211    CALL put_field_srf1(pass,"Z0h", "rugosite", z0h(:,:))
212
213    CALL put_field_srf1(pass,"AGESNO", "Age de la neige", agesno(:,:))
214
215    CALL put_field(pass,"ZMEA", "ZMEA", zmea)
216
217    CALL put_field(pass,"ZSTD", "ZSTD", zstd)
218
219    CALL put_field(pass,"ZSIG", "ZSIG", zsig)
220
221    CALL put_field(pass,"ZGAM", "ZGAM", zgam)
222
223    CALL put_field(pass,"ZTHE", "ZTHE", zthe)
224
225    CALL put_field(pass,"ZPIC", "ZPIC", zpic)
226
227    CALL put_field(pass,"ZVAL", "ZVAL", zval)
228
229    CALL put_field(pass,"RUGSREL", "RUGSREL", rugoro)
230
231    CALL put_field(pass,"TANCIEN", "TANCIEN", t_ancien)
232
233    CALL put_field(pass,"QANCIEN", "QANCIEN", q_ancien)
234
235    CALL put_field(pass,"QLANCIEN", "QLANCIEN", ql_ancien)
236
237    CALL put_field(pass,"QSANCIEN", "QSANCIEN", qs_ancien)
238
239    CALL put_field(pass,"PRWANCIEN", "PRWANCIEN", prw_ancien)
240
241    CALL put_field(pass,"PRLWANCIEN", "PRLWANCIEN", prlw_ancien)
242
243    CALL put_field(pass,"PRSWANCIEN", "PRSWANCIEN", prsw_ancien)
244
245    CALL put_field(pass,"UANCIEN", "UANCIEN", u_ancien)
246
247    CALL put_field(pass,"VANCIEN", "VANCIEN", v_ancien)
248
249    CALL put_field(pass,"CLWCON", "Eau liquide convective", clwcon)
250
251    CALL put_field(pass,"RNEBCON", "Nebulosite convective", rnebcon)
252
253    CALL put_field(pass,"RATQS", "Ratqs", ratqs)
254
255    ! run_off_lic_0
256
257    CALL put_field(pass,"RUNOFFLIC0", "Runofflic0", run_off_lic_0)
258
259    ! DEB TKE PBL !
260
261    IF (iflag_pbl>1) then
262      CALL put_field_srf3(pass,"TKE", "Energ. Cineti. Turb.", &
263           pbl_tke(:,:,:))
264      CALL put_field_srf3(pass,"DELTATKE", "Del TKE wk/env.", &
265           wake_delta_pbl_tke(:,:,:))
266    END IF
267
268    ! FIN TKE PBL !
269    !IM ajout zmax0, f0, sig1, w01
270    !IM wake_deltat, wake_deltaq, wake_s, wake_cstar, wake_pe, wake_fip
271
272    CALL put_field(pass,"ZMAX0", "ZMAX0", zmax0)
273
274    CALL put_field(pass,"F0", "F0", f0)
275
276    CALL put_field(pass,"sig1", "sig1 Emanuel", sig1)
277
278    CALL put_field(pass,"w01", "w01 Emanuel", w01)
279
280    ! wake_deltat
281    CALL put_field(pass,"WAKE_DELTAT", "WAKE_DELTAT", wake_deltat)
282
283    CALL put_field(pass,"WAKE_DELTAQ", "WAKE_DELTAQ", wake_deltaq)
284
285    CALL put_field(pass,"WAKE_S", "Wake frac. area", wake_s)
286
287    CALL put_field(pass,"WAKE_DENS", "Wake num. /unit area", wake_dens)
288
289    CALL put_field(pass,"WAKE_CSTAR", "WAKE_CSTAR", wake_cstar)
290
291    CALL put_field(pass,"WAKE_PE", "WAKE_PE", wake_pe)
292
293    CALL put_field(pass,"WAKE_FIP", "WAKE_FIP", wake_fip)
294
295    ! thermiques
296
297    CALL put_field(pass,"FM_THERM", "FM_THERM", fm_therm)
298
299    CALL put_field(pass,"ENTR_THERM", "ENTR_THERM", entr_therm)
300
301    CALL put_field(pass,"DETR_THERM", "DETR_THERM", detr_therm)
302
303    CALL put_field(pass,"ALE_BL", "ALE_BL", ale_bl)
304
305    CALL put_field(pass,"ALE_BL_TRIG", "ALE_BL_TRIG", ale_bl_trig)
306
307    CALL put_field(pass,"ALP_BL", "ALP_BL", alp_bl)
308
309    CALL put_field(pass,"ALE_WAKE", "ALE_WAKE", ale_wake)
310
311    CALL put_field(pass,"ALE_BL_STAT", "ALE_BL_STAT", ale_bl_stat)
312
313
314    ! fisrtilp/clouds
315    CALL put_field(pass,"RATQS_INTER","Relative width of the lsc sugrid scale water",ratqs_inter)
316
317
318    ! trs from traclmdz_mod
319    IF (type_trac == 'lmdz') THEN
320       CALL traclmdz_to_restart(trs)
321       DO it=1, nbtr
322!!        iiq=niadv(it+2)                                                           ! jyg
323          iiq=niadv(it+nqo)                                                           ! jyg
324          CALL put_field(pass,"trs_"//tname(iiq), "", trs(:, it))
325       END DO
326       IF (carbon_cycle_cpl) THEN
327          IF (.NOT. ALLOCATED(co2_send)) THEN
328             ! This is the case of create_etat0_limit, ce0l
329             ALLOCATE(co2_send(klon))
330             co2_send(:) = co2_ppm0
331          END IF
332          CALL put_field(pass,"co2_send", "co2_ppm for coupling", co2_send)
333       END IF
334    END IF
335
336    ! Restart variables for Slab ocean
337    IF (type_ocean == 'slab') THEN
338        IF (nslay.EQ.1) THEN
339          CALL put_field(pass,"tslab", "Slab ocean temperature", tslab)
340        ELSE
341          DO it=1,nslay
342            WRITE(str2,'(i2.2)') it
343            CALL put_field(pass,"tslab"//str2, "Slab ocean temperature", tslab(:,it))
344          END DO
345        END IF
346        IF (version_ocean == 'sicINT') THEN
347            CALL put_field(pass,"seaice", "Slab seaice (kg/m2)", seaice)
348            CALL put_field(pass,"slab_tice", "Slab sea ice temperature", tice)
349        END IF
350    END IF
351
352    if (ok_gwd_rando) call put_field(pass,"du_gwd_rando", &
353         "tendency on zonal wind due to flott gravity waves", du_gwd_rando)
354
355    IF (.not. ok_hines .and. ok_gwd_rando) call put_field(pass,"du_gwd_front", &
356         "tendency on zonal wind due to acama gravity waves", du_gwd_front)
357
358    if (activate_ocean_skin >= 1) then
359       if (activate_ocean_skin == 2 .and. type_ocean == 'couple') then
360          CALL put_field(pass, "delta_sal", &
361               "ocean-air interface salinity minus bulk salinity", delta_sal)
362          CALL put_field(pass, "delta_SST", &
363               "ocean-air interface temperature minus bulk SST", delta_sst)
364       end if
365       
366       CALL put_field(pass, "dS_ns", "delta salinity near surface", ds_ns)
367       CALL put_field(pass, "dT_ns", "delta temperature near surface", dT_ns)
368    end if
369   
370    IF (pass==1) CALL enddef_restartphy
371    IF (pass==2) CALL close_restartphy
372 ENDDO
373 
374  !$OMP BARRIER
375
376
377  CONTAINS
378
379
380SUBROUTINE put_field_srf1(pass,nam,lnam,field)
381
382  IMPLICIT NONE
383  INTEGER, INTENT(IN)            :: pass
384  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
385  REAL,              INTENT(IN) :: field(:,:)
386  CHARACTER(LEN=256) :: nm, lm, str
387  DO nsrf = 1, SIZE(field,2)
388    WRITE(str, '(i2.2)') nsrf
389    nm=TRIM(nam)//TRIM(str)
390    lm=TRIM(lnam)//" de surface No. "//TRIM(str)
391    CALL put_field(pass,nm,lm,field(:,nsrf))
392  END DO
393
394END SUBROUTINE put_field_srf1
395
396
397SUBROUTINE put_field_srf2(pass,nam,lnam,field)
398
399  IMPLICIT NONE
400  INTEGER, INTENT(IN)            :: pass
401  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
402  REAL,              INTENT(IN) :: field(:,:,:)
403  CHARACTER(LEN=256) :: nm, lm, str
404  DO nsrf = 1, SIZE(field,3)
405    DO isoil=1, SIZE(field,2)
406      WRITE(str, '(i2.2,"srf",i2.2)')isoil,nsrf
407!      WRITE(lunout,*)"PHYREDEM ",TRIM(nam)//TRIM(str)
408      nm=TRIM(nam)//TRIM(str)
409      lm=TRIM(lnam)//" du sol No. "//TRIM(str)
410      CALL put_field(pass,nm,lm,field(:,isoil,nsrf))
411    END DO
412  END DO
413
414END SUBROUTINE put_field_srf2
415
416
417SUBROUTINE put_field_srf3(pass,nam,lnam,field)
418
419  IMPLICIT NONE
420  INTEGER, INTENT(IN)            :: pass
421  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
422  REAL,              INTENT(IN) :: field(:,:,:)
423  CHARACTER(LEN=256) :: nm, lm, str
424  DO nsrf = 1, SIZE(field,3)
425    WRITE(str, '(i2.2)') nsrf
426    nm=TRIM(nam)//TRIM(str)
427    lm=TRIM(lnam)//TRIM(str)
428    CALL put_field(pass,nm,lm,field(:,1:klev+1,nsrf))
429  END DO
430
431END SUBROUTINE put_field_srf3
432
433
434END SUBROUTINE phyredem
Note: See TracBrowser for help on using the repository browser.