source: LMDZ5/trunk/libf/phylmd/phyredem.F90 @ 2299

Last change on this file since 2299 was 2299, checked in by dcugnet, 9 years ago

In dyn3d/:
etat0dyn_netcdf.F90: "startget_dyn3d" syntax slightly simplified.
dynredem.F90: Shortcut routines (put_var*, cre_var,
dynredem_write_*, dynredem_read_u)

modified to match dyn3dmem version and put in

module dyredem_mod.F90.
dynetat0.F90 -> *.f90: Few simplifications (no usage of NC_DOUBLE
needed => no precompilation)

Add tracers initialization in the isotope case

suppressed by accident.
dynredem_mod.F90: Created to mimic dyn3dmem equivalent.

In dyn3dmem/:
dynetat0_loc.F -> *.f90: Converted into fortran 90 to match the dyn3d
version.
dynredem_loc.F -> *.F90: Converted into fortran 90.
dynredem_mod.F90: Add some shortcut routines to match the dyn3d
version.

In phylmd/:
phyredem.F90: Bug fix: nsw instead of nsoilmx was used as
Tsoil second maximum index.

Bug fix: fevap instead of snow was saved for

"SNOW".
etat0phys_netcdf.F90: "filtreg_mod" module usage suppressed.

Local variable rugo computation removed (not

used).

In dynlonlat_phylonlat/:
grid_atob_m.F90 -> *.f90 DOUBLE PRECISION variables usage removed.

Precompilation o longer needed => .F90 extension.

  • 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: 9.5 KB
Line 
1SUBROUTINE phyredem (fichnom)
2!
3!-------------------------------------------------------------------------------
4! Author: Z.X. Li (LMD/CNRS), 1993/08/18
5!-------------------------------------------------------------------------------
6! Purpose: Write restart state for physics.
7!-------------------------------------------------------------------------------
8  USE dimphy
9  USE mod_grid_phy_lmdz
10  USE mod_phys_lmdz_para
11  USE fonte_neige_mod,  ONLY : fonte_neige_final
12  USE pbl_surface_mod,  ONLY : pbl_surface_final
13  USE phys_state_var_mod
14  USE iostart
15  USE traclmdz_mod, ONLY : traclmdz_to_restart
16  USE infotrac
17  USE control_mod
18  USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
19  USE indice_sol_mod
20  USE surface_data
21  USE ocean_slab_mod, ONLY : tslab, seaice, tice, fsic
22
23  IMPLICIT none
24
25  include "iniprint.h"
26  include "dimsoil.h"
27  include "clesphys.h"
28  include "temps.h"
29  include "thermcell.h"
30  include "compbl.h"
31  !======================================================================
32  CHARACTER*(*) fichnom
33
34  ! les variables globales ecrites dans le fichier restart
35
36  REAL tsoil(klon, nsoilmx, nbsrf)
37  REAL qsurf(klon, nbsrf)
38  REAL snow(klon, nbsrf)
39  real fder(klon)
40  REAL run_off_lic_0(klon)
41  REAL trs(klon, nbtr)
42
43  INTEGER nid, nvarid, idim1, idim2, idim3
44  INTEGER ierr
45  INTEGER length
46  PARAMETER (length=100)
47  REAL tab_cntrl(length)
48
49  INTEGER isoil, nsrf,isw
50  CHARACTER (len=7) :: str7
51  CHARACTER (len=256) :: nam, lnam
52  INTEGER           :: it, iiq
53
54  !======================================================================
55
56  ! Get variables which will be written to restart file from module
57  ! pbl_surface_mod
58  CALL pbl_surface_final(fder, snow, qsurf,  tsoil)
59
60  ! Get a variable calculated in module fonte_neige_mod
61  CALL fonte_neige_final(run_off_lic_0)
62
63  !======================================================================
64
65  CALL open_restartphy(fichnom)
66
67  DO ierr = 1, length
68     tab_cntrl(ierr) = 0.0
69  ENDDO
70  tab_cntrl(1) = dtime
71  tab_cntrl(2) = radpas
72  ! co2_ppm : current value of atmospheric CO2
73  tab_cntrl(3) = co2_ppm
74  tab_cntrl(4) = solaire
75  tab_cntrl(5) = iflag_con
76  tab_cntrl(6) = nbapp_rad
77
78  IF( cycle_diurne ) tab_cntrl( 7 ) = 1.
79  IF(   soil_model ) tab_cntrl( 8 ) = 1.
80  IF(     new_oliq ) tab_cntrl( 9 ) = 1.
81  IF(     ok_orodr ) tab_cntrl(10 ) = 1.
82  IF(     ok_orolf ) tab_cntrl(11 ) = 1.
83
84  tab_cntrl(13) = day_end
85  tab_cntrl(14) = annee_ref
86  tab_cntrl(15) = itau_phy
87
88  ! co2_ppm0 : initial value of atmospheric CO2
89  tab_cntrl(16) = co2_ppm0
90
91  CALL put_var("controle", "Parametres de controle", tab_cntrl)
92
93  CALL put_field("longitude", &
94       "Longitudes de la grille physique", rlon)
95
96  CALL put_field("latitude", "Latitudes de la grille physique", rlat)
97
98  ! PB ajout du masque terre/mer
99
100  CALL put_field("masque", "masque terre mer", zmasq)
101
102  ! BP ajout des fraction de chaque sous-surface
103
104  ! Get last fractions from slab ocean
105  IF (type_ocean == 'slab' .AND. version_ocean == "sicINT") THEN
106      WHERE (1.-zmasq(:).GT.EPSFRA)
107          pctsrf(:,is_oce)=(1.-fsic(:))*(1.-zmasq(:))
108          pctsrf(:,is_sic)=fsic(:)*(1.-zmasq(:))
109      END WHERE
110  END IF
111
112  ! 1. fraction de terre
113
114  CALL put_field("FTER", "fraction de continent", pctsrf(:, is_ter))
115
116  ! 2. Fraction de glace de terre
117
118  CALL put_field("FLIC", "fraction glace de terre", pctsrf(:, is_lic))
119
120  ! 3. fraction ocean
121
122  CALL put_field("FOCE", "fraction ocean", pctsrf(:, is_oce))
123
124  ! 4. Fraction glace de mer
125
126  CALL put_field("FSIC", "fraction glace mer", pctsrf(:, is_sic))
127
128  IF(nbsrf>99) THEN
129    PRINT*, "Trop de sous-mailles";  CALL abort_gcm("phyredem", "", 1)
130  END IF
131  IF(nsoilmx>99) THEN
132    PRINT*, "Trop de sous-surfaces"; CALL abort_gcm("phyredem", "", 1)
133  END IF
134  IF(nsw>99) THEN
135    PRINT*, "Trop de bandes"; CALL abort_gcm("phyredem", "", 1)
136  END IF
137
138  CALL put_field_srf1("TS","Temperature",ftsol(:,:))
139
140! ================== Albedo =======================================
141  print*,'PHYREDEM NOUVEAU'
142  CALL put_field_srf2("A_dir_SW","Albedo direct",falb_dir(:,:,:))
143  CALL put_field_srf2("A_dif_SW","Albedo diffus",falb_dif(:,:,:))
144
145! ================== Tsoil =========================================
146  CALL put_field_srf2("Tsoil","Temperature",tsoil(:,:,:))
147
148  CALL put_field_srf1("QS"  , "Humidite",qsurf(:,:))
149
150  CALL put_field     ("QSOL", "Eau dans le sol (mm)", qsol)
151
152  CALL put_field_srf1("EVAP", "Evaporation", fevap(:,:))
153
154  CALL put_field_srf1("SNOW", "Neige", snow(:,:))
155
156  CALL put_field("RADS", "Rayonnement net a la surface", radsol)
157
158  CALL put_field("solsw", "Rayonnement solaire a la surface", solsw)
159
160  CALL put_field("sollw", "Rayonnement IF a la surface", sollw)
161
162  CALL put_field("sollwdown", "Rayonnement down IF a la surface", sollw)
163
164  CALL put_field("fder", "Derive de flux", fder)
165
166  CALL put_field("rain_f", "precipitation liquide", rain_fall)
167
168  CALL put_field("snow_f", "precipitation solide", snow_fall)
169
170  CALL put_field_srf1("Z0m", "rugosite", z0m(:,:))
171
172  CALL put_field_srf1("Z0h", "rugosite", z0h(:,:))
173
174  CALL put_field_srf1("AGESNO", "Age de la neige", agesno(:,:))
175
176  CALL put_field("ZMEA", "ZMEA", zmea)
177
178  CALL put_field("ZSTD", "ZSTD", zstd)
179
180  CALL put_field("ZSIG", "ZSIG", zsig)
181
182  CALL put_field("ZGAM", "ZGAM", zgam)
183
184  CALL put_field("ZTHE", "ZTHE", zthe)
185
186  CALL put_field("ZPIC", "ZPIC", zpic)
187
188  CALL put_field("ZVAL", "ZVAL", zval)
189
190  CALL put_field("RUGSREL", "RUGSREL", rugoro)
191
192  CALL put_field("TANCIEN", "TANCIEN", t_ancien)
193
194  CALL put_field("QANCIEN", "QANCIEN", q_ancien)
195
196  CALL put_field("UANCIEN", "", u_ancien)
197
198  CALL put_field("VANCIEN", "", v_ancien)
199
200  CALL put_field("CLWCON", "Eau liquide convective", clwcon)
201
202  CALL put_field("RNEBCON", "Nebulosite convective", rnebcon)
203
204  CALL put_field("RATQS", "Ratqs", ratqs)
205
206  ! run_off_lic_0
207
208  CALL put_field("RUNOFFLIC0", "Runofflic0", run_off_lic_0)
209
210  ! DEB TKE PBL !
211
212  IF (iflag_pbl>1) then
213    CALL put_field_srf3("TKE", "Energ. Cineti. Turb.", &
214         pbl_tke(:,:,:))
215    CALL put_field_srf3("DELTATKE", "Del TKE wk/env.", &
216         wake_delta_pbl_tke(:,:,:))
217  END IF
218
219  ! FIN TKE PBL !
220  !IM ajout zmax0, f0, sig1, w01
221  !IM wake_deltat, wake_deltaq, wake_s, wake_cstar, wake_pe, wake_fip
222
223  CALL put_field("ZMAX0", "ZMAX0", zmax0)
224
225  CALL put_field("F0", "F0", f0)
226
227  CALL put_field("sig1", "sig1 Emanuel", sig1)
228
229  CALL put_field("w01", "w01 Emanuel", w01)
230
231  ! wake_deltat
232  CALL put_field("WAKE_DELTAT", "WAKE_DELTAT", wake_deltat)
233
234  CALL put_field("WAKE_DELTAQ", "WAKE_DELTAQ", wake_deltaq)
235
236  CALL put_field("WAKE_S", "WAKE_S", wake_s)
237
238  CALL put_field("WAKE_CSTAR", "WAKE_CSTAR", wake_cstar)
239
240  CALL put_field("WAKE_PE", "WAKE_PE", wake_pe)
241
242  CALL put_field("WAKE_FIP", "WAKE_FIP", wake_fip)
243
244  ! thermiques
245
246  CALL put_field("FM_THERM", "FM_THERM", fm_therm)
247
248  CALL put_field("ENTR_THERM", "ENTR_THERM", entr_therm)
249
250  CALL put_field("DETR_THERM", "DETR_THERM", detr_therm)
251
252  CALL put_field("ALE_BL", "ALE_BL", Ale_bl)
253
254  CALL put_field("ALE_BL_TRIG", "ALE_BL_TRIG", Ale_bl_trig)
255
256  CALL put_field("ALP_BL", "ALP_BL", Alp_bl)
257
258  ! trs from traclmdz_mod
259  IF (type_trac == 'lmdz') THEN
260     CALL traclmdz_to_restart(trs)
261     DO it=1, nbtr
262!!        iiq=niadv(it+2)                                                           ! jyg
263        iiq=niadv(it+nqo)                                                           ! jyg
264        CALL put_field("trs_"//tname(iiq), "", trs(:, it))
265     END DO
266     IF (carbon_cycle_cpl) THEN
267        IF (.NOT. ALLOCATED(co2_send)) THEN
268           ! This is the case of create_etat0_limit, ce0l
269           ALLOCATE(co2_send(klon))
270           co2_send(:) = co2_ppm0
271        END IF
272        CALL put_field("co2_send", "co2_ppm for coupling", co2_send)
273     END IF
274  END IF
275
276  ! Restart variables for Slab ocean
277  IF (type_ocean == 'slab') THEN
278      CALL put_field("tslab", "Slab ocean temperature", tslab)
279      IF (version_ocean == 'sicINT') THEN
280          CALL put_field("seaice", "Slab seaice (kg/m2)", seaice)
281          CALL put_field("slab_tice", "Slab sea ice temperature", tice)
282      END IF
283  END IF
284
285  if (ok_gwd_rando) then
286     call put_field("du_gwd_rando", &
287          "tendency on zonal wind due to gravity waves", &
288          du_gwd_rando)
289     call put_field("dv_gwd_rando", &
290          "tendency on meriodional wind due to gravity waves", &
291          dv_gwd_rando)
292  end if
293
294  CALL close_restartphy
295  !$OMP BARRIER
296
297
298  CONTAINS
299
300
301SUBROUTINE put_field_srf1(nam,lnam,field)
302
303  IMPLICIT NONE
304  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
305  REAL,              INTENT(IN) :: field(:,:)
306  CHARACTER(LEN=256) :: nm, lm, str
307  DO nsrf = 1, SIZE(field,2)
308    WRITE(str, '(i2.2)') nsrf
309    nm=TRIM(nam)//TRIM(str)
310    lm=TRIM(lnam)//" de surface No. "//TRIM(str)
311    CALL put_field(nm,lm,field(:,nsrf))
312  END DO
313
314END SUBROUTINE put_field_srf1
315
316
317SUBROUTINE put_field_srf2(nam,lnam,field)
318
319  IMPLICIT NONE
320  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
321  REAL,              INTENT(IN) :: field(:,:,:)
322  CHARACTER(LEN=256) :: nm, lm, str
323  DO nsrf = 1, SIZE(field,3)
324    DO isoil=1, SIZE(field,2)
325      WRITE(str, '(i2.2,"srf",i2.2)')isoil,nsrf
326!      WRITE(lunout,*)"PHYREDEM ",TRIM(nam)//TRIM(str)
327      nm=TRIM(nam)//TRIM(str)
328      lm=TRIM(lnam)//" du sol No. "//TRIM(str)
329      CALL put_field(nm,lm,field(:,isoil,nsrf))
330    END DO
331  END DO
332
333END SUBROUTINE put_field_srf2
334
335
336SUBROUTINE put_field_srf3(nam,lnam,field)
337
338  IMPLICIT NONE
339  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
340  REAL,              INTENT(IN) :: field(:,:,:)
341  CHARACTER(LEN=256) :: nm, lm, str
342  DO nsrf = 1, SIZE(field,3)
343    WRITE(str, '(i2.2)') nsrf
344    nm=TRIM(nam)//TRIM(str)
345    lm=TRIM(lnam)//TRIM(str)
346    CALL put_field(nm,lm,field(:,1:klev+1,nsrf))
347  END DO
348
349END SUBROUTINE put_field_srf3
350
351
352END SUBROUTINE phyredem
Note: See TracBrowser for help on using the repository browser.