source: LMDZ6/branches/Ocean_skin/libf/phylmd/phyredem.F90 @ 3740

Last change on this file since 3740 was 3740, checked in by lguez, 4 years ago

Send delta temperature to the ocean

The grid of Nemo is finer than the grid of LMDZ. So LMDZ receives from
Oasis a spatial average of bulk SST. If we send to Nemo the interface
temperature computed by LMDZ, it is regridded as a step function
by Oasis and, in Nemo, the difference between bulk SST and interface
temperature has spatial oscillations. To avoid this, we send to Nemo
the difference between bulk SST and interface temperature computed by
LMDZ, instead of the interface temperature.

So, in module cpl_mod, rename cpl_t_int to cpl_delta_temp,
cpl_t_int_2D to cpl_delta_temp_2D. In module oasis, rename
ids_t_int to ids_delta_temp. Change
infosend(ids_delta_temp)%name to "CODTEMP".

In procedure cpl_send_ocean_fields, rename dummy argument
t_int to tsurf_in just for clarity, because this argument is
passed also when activate_ocean_skin /= 2. Add dummy argument
sst_nff. We cannot just replace dummy argument t_int by a dummy
argument that would receive tsurf_in - sst_nff because sst_nff is
not defined when activate_ocean_skin == 0.

In procedure ocean_cpl_noice, add dummy argument sst_nff.

As for interface salinity, we have to send delta temperature from the
previous time step. So we have to transform sst_nff into a state
variable. So move sst_nff from module phys_output_var_mod to
module phys_state_var_mod. Define ysst_nff in procedure
pbl_surface before the call to surf_ocean. Choose a value of
sst_nff for an appearing ocean fraction. Read sst_nff in procedure
phyetat0, write it in procedure phyredem. Change the intent of dummy argument
sst_nff in procedure surf_ocean to inout.

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