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

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

Initial states creation routines have been reorganized and simplified.
As far as possible, dynamics and physics related routines have been
separated.
Some routines have been converted to fortran 90 and repeated codes sections
have been "factorized".
Array/vector arguments have become implicit in some routines to avoid usage
of "dimensions.h" ; possible for routines with explicit interfaces and if
iim and jjm can be deduced from arguments sizes.

  • dynlonlat_phylonlat/ce0l.F90 calls now phylmd/etat0phys_netcdf.F90 and dyn3d/etat0dyn_netcdf.F90 that replace phylmd/etat0_netcdf.F90. start.nc and startphy.nc creations are now independant.
  • startvar.F90 has been suppressed ; corresponding operations have been simplified and embedded in etat0*_netcdf.F90 routines as internal procedures.
  • Routines converted to fortran 90 and "factorized":
    • dyn3d_common/conf_dat_m.F90 (replaces dyn3d_common/conf_dat2d.F

and dyn3d_common/conf_dat3d.F)

  • dyn3d/dynredem.F90 (replaces dyn3d/dynredem.F)
  • dyn3d/dynetat0.F90 (replaces dyn3d/dynetat0.F)
  • phylmd/grid_noro_m.F90 (replaces dyn3d_common/grid_noro.F)
  • dynlonlat_phylonlat/grid_atob_m.F90 (replaces dyn3d_common/grid_atob.F)
  • dyn3d_common/caldyn0.F90 (replaces dyn3d_common/caldyn0.F)
  • dyn3d_common/covcont.F90 (replaces dyn3d_common/covcont.F)
  • dyn3d_common/pression.F90 (replaces dyn3d_common/pression.F)
  • phylmd/phyredem.F90 and phylmd/limit_netcdf.F90 have been slightly factorized.

TO DO:

  • little fix needed in grid_noro_m.F90 ; untouched yet to ensure results are exactly the same as before. Unsmoothed orography is used to compute "zphi", but smoothed (should be unsmoothed) one is used at poles.
  • add the dyn3dmem versions of dynredem.F90 and dynetat0.F90 (dynredem_loc.F90 and dynetat0_loc.F90, untested yet).
  • test compilation in parallel mode for a single processor.
  • 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.4 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
135  CALL put_field_srf1("TS","Temperature",ftsol(:,:))
136
137! ================== Albedo =======================================
138  print*,'PHYREDEM NOUVEAU'
139  CALL put_field_srf2("A_dir_SW","Albedo direct",falb_dir(:,:,:))
140  CALL put_field_srf2("A_dif_SW","Albedo diffus",falb_dif(:,:,:))
141
142! ================== Tsoil =========================================
143  CALL put_field_srf2("Tsoil","Temperature",tsoil(:,:,:))
144
145  CALL put_field_srf1("QS"  , "Humidite",qsurf(:,:))
146
147  CALL put_field     ("QSOL", "Eau dans le sol (mm)", qsol)
148
149  CALL put_field_srf1("EVAP", "Evaporation", fevap(:,:))
150
151  CALL put_field_srf1("SNOW", "Neige", fevap(:,:))
152
153  CALL put_field("RADS", "Rayonnement net a la surface", radsol)
154
155  CALL put_field("solsw", "Rayonnement solaire a la surface", solsw)
156
157  CALL put_field("sollw", "Rayonnement IF a la surface", sollw)
158
159  CALL put_field("sollwdown", "Rayonnement down IF a la surface", sollw)
160
161  CALL put_field("fder", "Derive de flux", fder)
162
163  CALL put_field("rain_f", "precipitation liquide", rain_fall)
164
165  CALL put_field("snow_f", "precipitation solide", snow_fall)
166
167  CALL put_field_srf1("Z0m", "rugosite", z0m(:,:))
168
169  CALL put_field_srf1("Z0h", "rugosite", z0h(:,:))
170
171  CALL put_field_srf1("AGESNO", "Age de la neige", agesno(:,:))
172
173  CALL put_field("ZMEA", "ZMEA", zmea)
174
175  CALL put_field("ZSTD", "ZSTD", zstd)
176
177  CALL put_field("ZSIG", "ZSIG", zsig)
178
179  CALL put_field("ZGAM", "ZGAM", zgam)
180
181  CALL put_field("ZTHE", "ZTHE", zthe)
182
183  CALL put_field("ZPIC", "ZPIC", zpic)
184
185  CALL put_field("ZVAL", "ZVAL", zval)
186
187  CALL put_field("RUGSREL", "RUGSREL", rugoro)
188
189  CALL put_field("TANCIEN", "TANCIEN", t_ancien)
190
191  CALL put_field("QANCIEN", "QANCIEN", q_ancien)
192
193  CALL put_field("UANCIEN", "", u_ancien)
194
195  CALL put_field("VANCIEN", "", v_ancien)
196
197  CALL put_field("CLWCON", "Eau liquide convective", clwcon)
198
199  CALL put_field("RNEBCON", "Nebulosite convective", rnebcon)
200
201  CALL put_field("RATQS", "Ratqs", ratqs)
202
203  ! run_off_lic_0
204
205  CALL put_field("RUNOFFLIC0", "Runofflic0", run_off_lic_0)
206
207  ! DEB TKE PBL !
208
209  IF (iflag_pbl>1) then
210    CALL put_field_srf3("TKE", "Energ. Cineti. Turb.", &
211         pbl_tke(:,:,:))
212    CALL put_field_srf3("DELTATKE", "Del TKE wk/env.", &
213         wake_delta_pbl_tke(:,:,:))
214  END IF
215
216  ! FIN TKE PBL !
217  !IM ajout zmax0, f0, sig1, w01
218  !IM wake_deltat, wake_deltaq, wake_s, wake_cstar, wake_pe, wake_fip
219
220  CALL put_field("ZMAX0", "ZMAX0", zmax0)
221
222  CALL put_field("F0", "F0", f0)
223
224  CALL put_field("sig1", "sig1 Emanuel", sig1)
225
226  CALL put_field("w01", "w01 Emanuel", w01)
227
228  ! wake_deltat
229  CALL put_field("WAKE_DELTAT", "WAKE_DELTAT", wake_deltat)
230
231  CALL put_field("WAKE_DELTAQ", "WAKE_DELTAQ", wake_deltaq)
232
233  CALL put_field("WAKE_S", "WAKE_S", wake_s)
234
235  CALL put_field("WAKE_CSTAR", "WAKE_CSTAR", wake_cstar)
236
237  CALL put_field("WAKE_PE", "WAKE_PE", wake_pe)
238
239  CALL put_field("WAKE_FIP", "WAKE_FIP", wake_fip)
240
241  ! thermiques
242
243  CALL put_field("FM_THERM", "FM_THERM", fm_therm)
244
245  CALL put_field("ENTR_THERM", "ENTR_THERM", entr_therm)
246
247  CALL put_field("DETR_THERM", "DETR_THERM", detr_therm)
248
249  CALL put_field("ALE_BL", "ALE_BL", Ale_bl)
250
251  CALL put_field("ALE_BL_TRIG", "ALE_BL_TRIG", Ale_bl_trig)
252
253  CALL put_field("ALP_BL", "ALP_BL", Alp_bl)
254
255  ! trs from traclmdz_mod
256  IF (type_trac == 'lmdz') THEN
257     CALL traclmdz_to_restart(trs)
258     DO it=1, nbtr
259!!        iiq=niadv(it+2)                                                           ! jyg
260        iiq=niadv(it+nqo)                                                           ! jyg
261        CALL put_field("trs_"//tname(iiq), "", trs(:, it))
262     END DO
263     IF (carbon_cycle_cpl) THEN
264        IF (.NOT. ALLOCATED(co2_send)) THEN
265           ! This is the case of create_etat0_limit, ce0l
266           ALLOCATE(co2_send(klon))
267           co2_send(:) = co2_ppm0
268        END IF
269        CALL put_field("co2_send", "co2_ppm for coupling", co2_send)
270     END IF
271  END IF
272
273  ! Restart variables for Slab ocean
274  IF (type_ocean == 'slab') THEN
275      CALL put_field("tslab", "Slab ocean temperature", tslab)
276      IF (version_ocean == 'sicINT') THEN
277          CALL put_field("seaice", "Slab seaice (kg/m2)", seaice)
278          CALL put_field("slab_tice", "Slab sea ice temperature", tice)
279      END IF
280  END IF
281
282  if (ok_gwd_rando) then
283     call put_field("du_gwd_rando", &
284          "tendency on zonal wind due to gravity waves", &
285          du_gwd_rando)
286     call put_field("dv_gwd_rando", &
287          "tendency on meriodional wind due to gravity waves", &
288          dv_gwd_rando)
289  end if
290
291  CALL close_restartphy
292  !$OMP BARRIER
293
294
295  CONTAINS
296
297
298SUBROUTINE put_field_srf1(nam,lnam,field)
299
300  IMPLICIT NONE
301  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
302  REAL,              INTENT(IN) :: field(:,:)
303  CHARACTER(LEN=256) :: nm, lm, str
304  DO nsrf = 1, nbsrf
305    WRITE(str, '(i2.2)') nsrf
306    nm=TRIM(nam)//TRIM(str)
307    lm=TRIM(lnam)//" de surface No. "//TRIM(str)
308    CALL put_field(nm,lm,field(:,nsrf))
309  END DO
310
311END SUBROUTINE put_field_srf1
312
313
314SUBROUTINE put_field_srf2(nam,lnam,field)
315
316  IMPLICIT NONE
317  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
318  REAL,              INTENT(IN) :: field(:,:,:)
319  CHARACTER(LEN=256) :: nm, lm, str
320  DO nsrf = 1, nbsrf
321    DO isoil=1, nsw
322      WRITE(str, '(i2.2,"srf",i2.2)')isoil,nsrf
323!      WRITE(lunout,*)"PHYREDEM ",TRIM(nam)//TRIM(str)
324      nm=TRIM(nam)//TRIM(str)
325      lm=TRIM(lnam)//" du sol No. "//TRIM(str)
326      CALL put_field(nm,lm,field(:,isoil,nsrf))
327    END DO
328  END DO
329
330END SUBROUTINE put_field_srf2
331
332
333SUBROUTINE put_field_srf3(nam,lnam,field)
334
335  IMPLICIT NONE
336  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
337  REAL,              INTENT(IN) :: field(:,:,:)
338  CHARACTER(LEN=256) :: nm, lm, str
339  DO nsrf = 1, nbsrf
340    WRITE(str, '(i2.2)') nsrf
341    nm=TRIM(nam)//TRIM(str)
342    lm=TRIM(lnam)//TRIM(str)
343    CALL put_field(nm,lm,field(:,1:klev+1,nsrf))
344  END DO
345
346END SUBROUTINE put_field_srf3
347
348
349END SUBROUTINE phyredem
Note: See TracBrowser for help on using the repository browser.