source: LMDZ6/trunk/libf/phylmdiso/phyredem.F90 @ 4387

Last change on this file since 4387 was 4374, checked in by lguez, 19 months ago

Report modifications from phylmd into phylmdiso

Report modifications of revision 4370 from phylmd into phylmdiso.

File size: 20.7 KB
Line 
1!
2! $Id: phyredem.F90 3506 2019-05-16 14:38:11Z ymeurdesoif $
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                                awake_dens, cv_gen,                          &
26                                wake_cstar,                                  &
27                                wake_pe, wake_fip, fm_therm, entr_therm,     &
28                                detr_therm, ale_bl, ale_bl_trig, alp_bl,     &
29                                ale_wake, ale_bl_stat,                       &
30                                du_gwd_rando, du_gwd_front, u10m, v10m, &
31                                treedrg, solswfdiff, delta_sal, ds_ns, dt_ns, &
32                                delta_sst, ratqs_inter, dter, dser, dt_ds
33#ifdef ISO
34  USE phys_state_var_mod, ONLY: xtsol, fxtevap,xtrain_fall, xtsnow_fall,     &
35                                xt_ancien, xtl_ancien, xts_ancien,           &
36                                wake_deltaxt                             
37#endif
38  USE geometry_mod, ONLY : longitude_deg, latitude_deg
39  USE iostart, ONLY: open_restartphy, close_restartphy, enddef_restartphy, put_field, put_var
40  USE traclmdz_mod, ONLY : traclmdz_to_restart
41  USE infotrac_phy, ONLY: types_trac, nqtot, tracers, nbtr, niso
42#ifdef ISO
43#ifdef ISOVERIF
44  USE isotopes_verif_mod
45#endif
46#endif
47  USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send, carbon_cycle_rad, RCO2_glo
48  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic, epsfra
49  USE surface_data, ONLY: type_ocean, version_ocean
50  USE ocean_slab_mod, ONLY : nslay, tslab, seaice, tice, fsic
51  USE time_phylmdz_mod, ONLY: annee_ref, day_end, itau_phy, pdtphys
52  use config_ocean_skin_m, only: activate_ocean_skin 
53
54  IMPLICIT none
55
56  include "dimsoil.h"
57  include "clesphys.h"
58  include "alpale.h"
59  include "compbl.h"
60  !======================================================================
61  CHARACTER*(*) fichnom
62
63  ! les variables globales ecrites dans le fichier restart
64
65  REAL tsoil(klon, nsoilmx, nbsrf)
66  REAL qsurf(klon, nbsrf)
67  REAL snow(klon, nbsrf)
68  real fder(klon)
69  REAL run_off_lic_0(klon)
70  REAL trs(klon, nbtr)
71#ifdef ISO
72  REAL xtsnow(niso,klon, nbsrf)
73  REAL xtrun_off_lic_0(niso,klon)
74  REAL Rland_ice(niso,klon)
75#endif
76
77  INTEGER nid, nvarid, idim1, idim2, idim3
78  INTEGER ierr
79  INTEGER length
80  PARAMETER (length=100)
81  REAL tab_cntrl(length)
82
83  INTEGER isoil, nsrf,isw
84  CHARACTER (len=2) :: str2
85  CHARACTER (len=256) :: nam, lnam
86  INTEGER           :: it, iq, pass
87
88  !======================================================================
89
90  ! Get variables which will be written to restart file from module
91  ! pbl_surface_mod
92  CALL pbl_surface_final(fder, snow, qsurf,  tsoil &
93#ifdef ISO
94       ,xtsnow,Rland_ice &
95#endif       
96       )
97
98  ! Get a variable calculated in module fonte_neige_mod
99  CALL fonte_neige_final(run_off_lic_0 &
100#ifdef ISO
101       ,xtrun_off_lic_0 &
102#endif       
103       )
104
105  !======================================================================
106
107  CALL open_restartphy(fichnom)
108
109 
110  DO ierr = 1, length
111     tab_cntrl(ierr) = 0.0
112  ENDDO
113  tab_cntrl(1) = pdtphys
114  tab_cntrl(2) = radpas
115  ! co2_ppm : current value of atmospheric CO2
116  tab_cntrl(3) = co2_ppm
117  tab_cntrl(4) = solaire
118  tab_cntrl(5) = iflag_con
119  tab_cntrl(6) = nbapp_rad
120
121  IF( iflag_cycle_diurne.GE.1 ) tab_cntrl( 7 ) = iflag_cycle_diurne
122  IF(   soil_model ) tab_cntrl( 8 ) = 1.
123  IF(     new_oliq ) tab_cntrl( 9 ) = 1.
124  IF(     ok_orodr ) tab_cntrl(10 ) = 1.
125  IF(     ok_orolf ) tab_cntrl(11 ) = 1.
126
127  tab_cntrl(13) = day_end
128  tab_cntrl(14) = annee_ref
129  tab_cntrl(15) = itau_phy
130
131  ! co2_ppm0 : initial value of atmospheric CO2
132  ! tab_cntrl(16) = co2_ppm0
133
134  !  PC -- initial value of RCO2 for the radiation scheme
135  !  tab_cntrl(17) = co2_ppm * 1.0e-06 * RMCO2 / RMD
136  IF (carbon_cycle_rad) tab_cntrl(17) = RCO2_glo
137  !PRINT*, "PC : phyredem RCO2_glo =",RCO2_glo
138
139  DO pass=1,2   ! pass=1 netcdf definition ; pass=2 netcdf write
140 
141    CALL put_var(pass, "controle", "Parametres de controle", tab_cntrl)
142
143    CALL put_field(pass,"longitude", &
144         "Longitudes de la grille physique", longitude_deg)
145
146    CALL put_field(pass,"latitude", "Latitudes de la grille physique", latitude_deg)
147
148    ! PB ajout du masque terre/mer
149
150    CALL put_field(pass,"masque", "masque terre mer", zmasq)
151
152    ! BP ajout des fraction de chaque sous-surface
153
154    ! Get last fractions from slab ocean
155    IF (type_ocean == 'slab' .AND. version_ocean == "sicINT") THEN
156        WHERE (1.-zmasq(:).GT.EPSFRA)
157            pctsrf(:,is_oce)=(1.-fsic(:))*(1.-zmasq(:))
158            pctsrf(:,is_sic)=fsic(:)*(1.-zmasq(:))
159        END WHERE
160    END IF
161
162    ! 1. fraction de terre
163
164    CALL put_field(pass,"FTER", "fraction de continent", pctsrf(:, is_ter))
165
166    ! 2. Fraction de glace de terre
167
168    CALL put_field(pass,"FLIC", "fraction glace de terre", pctsrf(:, is_lic))
169
170    ! 3. fraction ocean
171
172    CALL put_field(pass,"FOCE", "fraction ocean", pctsrf(:, is_oce))
173
174    ! 4. Fraction glace de mer
175
176    CALL put_field(pass,"FSIC", "fraction glace mer", pctsrf(:, is_sic))
177
178    IF(nbsrf>99) THEN
179      PRINT*, "Trop de sous-mailles";  CALL abort_physic("phyredem", "", 1)
180    END IF
181    IF(nsoilmx>99) THEN
182      PRINT*, "Trop de sous-surfaces"; CALL abort_physic("phyredem", "", 1)
183    END IF
184    IF(nsw>99) THEN
185      PRINT*, "Trop de bandes"; CALL abort_physic("phyredem", "", 1)
186    END IF
187
188!    Surface variables
189    CALL put_field_srf1(pass,"TS","Temperature",ftsol(:,:))
190
191    IF (iflag_pbl>1 .AND. iflag_wake>=1  .AND. iflag_pbl_split >=1) then
192       CALL put_field_srf1(pass, "DELTATS", &
193                      "w-x surface temperature difference",  delta_tsurf(:,:))
194       CALL put_field_srf1(pass, "BETAS", "Aridity factor", beta_aridity(:,:))
195    end IF
196!    End surface variables
197
198! ================== Albedo =======================================
199    print*,'PHYREDEM NOUVEAU'
200    CALL put_field_srf2(pass,"A_dir_SW","Albedo direct",falb_dir(:,:,:))
201    CALL put_field_srf2(pass,"A_dif_SW","Albedo diffus",falb_dif(:,:,:))
202
203    CALL put_field_srf1(pass,"U10M", "u a 10m", u10m)
204
205    CALL put_field_srf1(pass,"V10M", "v a 10m", v10m)
206
207
208! ================== Tsoil =========================================
209    CALL put_field_srf2(pass,"Tsoil","Temperature",tsoil(:,:,:))
210!FC
211!  CALL put_field_srf2("treedrg","freinage arbres",treedrg(:,:,:))
212    CALL put_field(pass,"treedrg_ter","freinage arbres",treedrg(:,:,is_ter))
213
214
215    CALL put_field_srf1(pass,"QS"  , "Humidite",qsurf(:,:))
216
217    CALL put_field     (pass,"QSOL", "Eau dans le sol (mm)", qsol)
218
219    CALL put_field_srf1(pass,"EVAP", "Evaporation", fevap(:,:))
220
221    CALL put_field_srf1(pass,"SNOW", "Neige", snow(:,:))
222
223    CALL put_field(pass,"RADS", "Rayonnement net a la surface", radsol)
224
225    CALL put_field(pass,"solsw", "Rayonnement solaire a la surface", solsw)
226
227    CALL put_field(pass,"solswfdiff", "Fraction du rayonnement solaire a la surface qui est diffus", solswfdiff)
228
229    CALL put_field(pass,"sollw", "Rayonnement IF a la surface", sollw)
230
231    CALL put_field(pass,"sollwdown", "Rayonnement down IF a la surface", sollwdown)
232
233    CALL put_field(pass,"fder", "Derive de flux", fder)
234
235    CALL put_field(pass,"rain_f", "precipitation liquide", rain_fall)
236
237    CALL put_field(pass,"snow_f", "precipitation solide", snow_fall)
238
239    CALL put_field_srf1(pass,"Z0m", "rugosite", z0m(:,:))
240
241    CALL put_field_srf1(pass,"Z0h", "rugosite", z0h(:,:))
242
243    CALL put_field_srf1(pass,"AGESNO", "Age de la neige", agesno(:,:))
244
245    CALL put_field(pass,"ZMEA", "ZMEA", zmea)
246
247    CALL put_field(pass,"ZSTD", "ZSTD", zstd)
248
249    CALL put_field(pass,"ZSIG", "ZSIG", zsig)
250
251    CALL put_field(pass,"ZGAM", "ZGAM", zgam)
252
253    CALL put_field(pass,"ZTHE", "ZTHE", zthe)
254
255    CALL put_field(pass,"ZPIC", "ZPIC", zpic)
256
257    CALL put_field(pass,"ZVAL", "ZVAL", zval)
258
259    CALL put_field(pass,"RUGSREL", "RUGSREL", rugoro)
260
261    CALL put_field(pass,"TANCIEN", "TANCIEN", t_ancien)
262
263    CALL put_field(pass,"QANCIEN", "QANCIEN", q_ancien)
264
265    CALL put_field(pass,"QLANCIEN", "QLANCIEN", ql_ancien)
266
267    CALL put_field(pass,"QSANCIEN", "QSANCIEN", qs_ancien)
268
269    CALL put_field(pass,"PRWANCIEN", "PRWANCIEN", prw_ancien)
270
271    CALL put_field(pass,"PRLWANCIEN", "PRLWANCIEN", prlw_ancien)
272
273    CALL put_field(pass,"PRSWANCIEN", "PRSWANCIEN", prsw_ancien)
274
275    CALL put_field(pass,"UANCIEN", "UANCIEN", u_ancien)
276
277    CALL put_field(pass,"VANCIEN", "VANCIEN", v_ancien)
278
279    CALL put_field(pass,"CLWCON", "Eau liquide convective", clwcon)
280
281    CALL put_field(pass,"RNEBCON", "Nebulosite convective", rnebcon)
282
283    CALL put_field(pass,"RATQS", "Ratqs", ratqs)
284
285    ! run_off_lic_0
286
287    CALL put_field(pass,"RUNOFFLIC0", "Runofflic0", run_off_lic_0)
288
289    ! DEB TKE PBL !
290
291    IF (iflag_pbl>1) then
292      CALL put_field_srf3(pass,"TKE", "Energ. Cineti. Turb.", &
293           pbl_tke(:,:,:))
294      CALL put_field_srf3(pass,"DELTATKE", "Del TKE wk/env.", &
295           wake_delta_pbl_tke(:,:,:))
296    END IF
297
298    ! FIN TKE PBL !
299    !IM ajout zmax0, f0, sig1, w01
300    !IM wake_deltat, wake_deltaq, wake_s, wake_cstar, wake_pe, wake_fip
301
302    CALL put_field(pass,"ZMAX0", "ZMAX0", zmax0)
303
304    CALL put_field(pass,"F0", "F0", f0)
305
306    CALL put_field(pass,"sig1", "sig1 Emanuel", sig1)
307
308    CALL put_field(pass,"w01", "w01 Emanuel", w01)
309
310    ! wake_deltat
311    CALL put_field(pass,"WAKE_DELTAT", "WAKE_DELTAT", wake_deltat)
312
313    CALL put_field(pass,"WAKE_DELTAQ", "WAKE_DELTAQ", wake_deltaq)
314
315    CALL put_field(pass,"WAKE_S", "Wake frac. area", wake_s)
316
317    CALL put_field(pass,"WAKE_DENS", "Wake num. /unit area", wake_dens)
318
319    CALL put_field(pass,"AWAKE_DENS", "Active Wake num. /unit area", awake_dens)
320
321    CALL put_field(pass,"CV_GEN", "CB birth rate", cv_gen)
322
323    CALL put_field(pass,"WAKE_CSTAR", "WAKE_CSTAR", wake_cstar)
324
325    CALL put_field(pass,"WAKE_PE", "WAKE_PE", wake_pe)
326
327    CALL put_field(pass,"WAKE_FIP", "WAKE_FIP", wake_fip)
328
329    ! thermiques
330
331    CALL put_field(pass,"FM_THERM", "FM_THERM", fm_therm)
332
333    CALL put_field(pass,"ENTR_THERM", "ENTR_THERM", entr_therm)
334
335    CALL put_field(pass,"DETR_THERM", "DETR_THERM", detr_therm)
336
337    CALL put_field(pass,"ALE_BL", "ALE_BL", ale_bl)
338
339    CALL put_field(pass,"ALE_BL_TRIG", "ALE_BL_TRIG", ale_bl_trig)
340
341    CALL put_field(pass,"ALP_BL", "ALP_BL", alp_bl)
342
343    CALL put_field(pass,"ALE_WAKE", "ALE_WAKE", ale_wake)
344
345    CALL put_field(pass,"ALE_BL_STAT", "ALE_BL_STAT", ale_bl_stat)
346
347
348    ! fisrtilp/clouds
349    CALL put_field(pass,"RATQS_INTER","Relative width of the lsc sugrid scale water",ratqs_inter)
350
351
352    IF (ANY(types_trac == 'co2i') .OR. ANY(types_trac == 'inco')) THEN
353       IF (carbon_cycle_cpl) THEN
354          IF (.NOT. ALLOCATED(co2_send)) THEN
355             ! This is the case of create_etat0_limit, ce0l
356             ALLOCATE(co2_send(klon))
357             co2_send(:) = co2_ppm0
358          END IF
359          CALL put_field(pass,"co2_send", "co2_ppm for coupling", co2_send)
360       END IF
361
362    ! trs from traclmdz_mod
363    ELSE IF (ANY(types_trac == 'lmdz')) THEN
364       CALL traclmdz_to_restart(trs)
365       it = 0
366       DO iq = 1, nqtot
367          IF(.NOT.(tracers(iq)%isAdvected .AND. tracers(iq)%isInPhysics)) CYCLE
368          it = it+1
369          CALL put_field(pass,"trs_"//tracers(iq)%name, "", trs(:, it))
370       END DO
371    END IF
372
373    ! Restart variables for Slab ocean
374    IF (type_ocean == 'slab') THEN
375        IF (nslay.EQ.1) THEN
376          CALL put_field(pass,"tslab", "Slab ocean temperature", tslab)
377        ELSE
378          DO it=1,nslay
379            WRITE(str2,'(i2.2)') it
380            CALL put_field(pass,"tslab"//str2, "Slab ocean temperature", tslab(:,it))
381          END DO
382        END IF
383        IF (version_ocean == 'sicINT') THEN
384            CALL put_field(pass,"seaice", "Slab seaice (kg/m2)", seaice)
385            CALL put_field(pass,"slab_tice", "Slab sea ice temperature", tice)
386        END IF
387    END IF
388
389    if (ok_gwd_rando) call put_field(pass,"du_gwd_rando", &
390         "tendency on zonal wind due to flott gravity waves", du_gwd_rando)
391
392    IF (.not. ok_hines .and. ok_gwd_rando) call put_field(pass,"du_gwd_front", &
393         "tendency on zonal wind due to acama gravity waves", du_gwd_front)
394
395    if (activate_ocean_skin >= 1) then
396       if (activate_ocean_skin == 2 .and. type_ocean == 'couple') then
397          CALL put_field(pass, "delta_sal", &
398               "ocean-air interface salinity minus bulk salinity", delta_sal)
399          CALL put_field(pass, "delta_SST", &
400               "ocean-air interface temperature minus bulk SST", delta_sst)
401          CALL put_field(pass, "dter", &
402               "ocean-air interface temperature minus subskin temperature", &
403               dter)
404          CALL put_field(pass, "dser", &
405               "ocean-air interface salinity minus subskin salinity", dser)
406          CALL put_field(pass, "dt_ds", &
407               "(tks / tkt) * dTer", dt_ds)
408       end if
409       
410       CALL put_field(pass, "dS_ns", "delta salinity near surface", ds_ns)
411       CALL put_field(pass, "dT_ns", "delta temperature near surface", dT_ns)
412    end if
413
414#ifdef ISO
415      write(*,*) 'phyredem 342'
416      call phyisoredem (pass, &
417     &           xtsnow, &
418     &           xtrun_off_lic_0,Rland_ice, &
419     &           run_off_lic_0)
420#endif
421
422    IF (pass==1) CALL enddef_restartphy
423    IF (pass==2) CALL close_restartphy
424  ENDDO ! DO pass=1,2   ! pass=1 netcdf definition ; pass=2 netcdf write
425 
426  !$OMP BARRIER
427
428
429  CONTAINS
430
431
432SUBROUTINE put_field_srf1(pass,nam,lnam,field)
433
434  IMPLICIT NONE
435  INTEGER, INTENT(IN)           :: pass
436  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
437  REAL,              INTENT(IN) :: field(:,:)
438  CHARACTER(LEN=256) :: nm, lm, str
439  DO nsrf = 1, SIZE(field,2)
440    WRITE(str, '(i2.2)') nsrf
441    nm=TRIM(nam)//TRIM(str)
442    lm=TRIM(lnam)//" de surface No. "//TRIM(str)
443    CALL put_field(pass,nm,lm,field(:,nsrf))
444  END DO
445
446END SUBROUTINE put_field_srf1
447
448
449SUBROUTINE put_field_srf2(pass,nam,lnam,field)
450
451  IMPLICIT NONE
452  INTEGER, INTENT(IN)            :: pass
453  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
454  REAL,              INTENT(IN) :: field(:,:,:)
455  CHARACTER(LEN=256) :: nm, lm, str
456  DO nsrf = 1, SIZE(field,3)
457    DO isoil=1, SIZE(field,2)
458      WRITE(str, '(i2.2,"srf",i2.2)')isoil,nsrf
459!      WRITE(lunout,*)"PHYREDEM ",TRIM(nam)//TRIM(str)
460      nm=TRIM(nam)//TRIM(str)
461      lm=TRIM(lnam)//" du sol No. "//TRIM(str)
462      CALL put_field(pass,nm,lm,field(:,isoil,nsrf))
463    END DO
464  END DO
465
466END SUBROUTINE put_field_srf2
467
468
469SUBROUTINE put_field_srf3(pass,nam,lnam,field)
470
471  IMPLICIT NONE
472  INTEGER, INTENT(IN)            :: pass
473  CHARACTER(LEN=*),  INTENT(IN) :: nam, lnam
474  REAL,              INTENT(IN) :: field(:,:,:)
475  CHARACTER(LEN=256) :: nm, lm, str
476  DO nsrf = 1, SIZE(field,3)
477    WRITE(str, '(i2.2)') nsrf
478    nm=TRIM(nam)//TRIM(str)
479    lm=TRIM(lnam)//TRIM(str)
480    CALL put_field(pass,nm,lm,field(:,1:klev+1,nsrf))
481  END DO
482
483END SUBROUTINE put_field_srf3
484
485#ifdef ISO
486! je voulais mettre cette subroutine dans isotopes_mod, mais elle a besoin de put_field_srf1 qui est contenue dans la subroutine phyredem. Si on veut mettre cette routine dans isotopes_mod, il faudrait convertir ce fichier en module pour pouvoir en appeler des routines
487
488      SUBROUTINE phyisoredem (pass, &
489     &          xtsnow, &
490     &          xtrun_off_lic_0,Rland_ice, &
491     &          run_off_lic_0)
492      USE dimphy
493      !USE mod_grid_phy_lmdz
494      !USE mod_phys_lmdz_para
495      USE phys_state_var_mod, ONLY: q_ancien,xt_ancien,wake_deltaq,wake_deltaxt, &
496        xtrain_fall,xtsnow_fall, ql_ancien,xtl_ancien,qs_ancien,xts_ancien, &
497        xtsol,fxtevap
498      USE infotrac_phy,ONLY: niso, ntiso
499      !USE control_mod
500      USE indice_sol_mod, ONLY: nbsrf
501      USE iostart, ONLY: put_field
502      USE isotopes_mod, ONLY: isoName,iso_eau
503#ifdef ISOVERIF
504      USE isotopes_verif_mod
505#endif
506#ifdef ISOTRAC
507    use isotrac_mod, only: index_zone,index_iso,strtrac
508#endif
509      !USE phyredem, ONLY: put_field_srf1
510
511        implicit none
512
513        ! equivalent isotopique de phyredem
514
515#include "dimsoil.h"
516#include "clesphys.h"
517#include "alpale.h"
518#include "compbl.h"     
519      ! inputs
520      !REAL xtsol(niso,klon)
521      REAL xtsnow(niso,klon,nbsrf)
522      !REAL xtevap(ntiso,klon,nbsrf)     
523      REAL xtrun_off_lic_0(niso,klon)
524      REAL Rland_ice(niso,klon)
525      real run_off_lic_0(klon)
526      integer, intent(in) :: pass
527
528      ! locals
529      real iso_tmp(klon)
530      real iso_tmp_lonlev(klon,klev)
531      real iso_tmp_lonsrf(klon,nbsrf)
532      integer i,ixt,k,nsrf
533      INTEGER nid, nvarid
534      INTEGER ierr
535      CHARACTER*7 str7
536      CHARACTER*2 str2
537      CHARACTER*50 outiso
538      integer lnblnk
539#ifdef ISOTRAC
540      integer iiso,izone
541#endif     
542
543      write(*,*) 'phyisoredem 41: entrée'
544#ifdef ISOVERIF
545     if (iso_eau.gt.0) then
546      do k=1,klev
547        do i=1,klon
548           call iso_verif_egalite(xt_ancien(iso_eau,i,k),q_ancien(i,k), &
549     &           'phyisoredem 50a')
550           call iso_verif_egalite(xtl_ancien(iso_eau,i,k),ql_ancien(i,k), &
551     &           'phyisoredem 50b')
552           call iso_verif_egalite(xts_ancien(iso_eau,i,k),qs_ancien(i,k), &
553     &           'phyisoredem 50c')
554         
555        enddo !do i=1,klon
556      enddo !do k=1,klev
557      do i=1,klon
558        DO nsrf = 1, nbsrf
559           call iso_verif_egalite(fxtevap(iso_eau,i,nsrf),fevap(i,nsrf), &
560     &           'phyisoredem 50d')
561        enddo !DO nsrf = 1, nbsrf
562       enddo
563      endif !if (iso_eau.gt.0) then
564      do i=1,klon
565       do ixt=1,niso
566        call iso_verif_noNaN(xtsol(ixt,i),'phyisoredem 72')
567       enddo !do ixt=1,niso
568      enddo !do i=1,klon
569#ifdef ISOTRAC       
570      do k=1,klev
571        do i=1,klon 
572          call iso_verif_traceur(xt_ancien(1,i,k), &
573     &                   'phyisoredem 60') 
574        enddo !do i=1,klon
575      enddo !do k=1,kle
576#endif
577#endif
578
579   do ixt=1,ntiso
580
581      outiso = TRIM(isoName(ixt))
582      i = INDEX(outiso, '_', .TRUE.)
583      outiso = outiso(1:i-1)//outiso(i+1:LEN_TRIM(outiso))
584      write(*,*) 'phyredem 550: ixt,outiso=',ixt,TRIM(outiso)
585     
586      iso_tmp_lonsrf(:,:)=fxtevap(ixt,:,:)
587      CALL put_field_srf1(pass, "XTEVAP"//TRIM(outiso), "Evaporation de surface",iso_tmp_lonsrf)
588
589      iso_tmp_lonsrf(:,:)=xtsnow(ixt,:,:)
590      CALL put_field_srf1(pass, "XTSNOW"//TRIM(outiso), "NEIGE",       iso_tmp_lonsrf)       
591
592      iso_tmp(:)=xtrain_fall(ixt,:)
593      CALL put_field(pass,    "xtrain_f"//TRIM(outiso), "precipitation liquide",iso_tmp)
594
595      iso_tmp(:)=xtsnow_fall(ixt,:)
596      CALL put_field(pass,    "xtsnow_f"//TRIM(outiso), "precipitation solide",iso_tmp)
597
598      iso_tmp_lonlev(:,:)=xt_ancien(ixt,:,:)
599      CALL put_field(pass,    "XTANCIEN"//TRIM(outiso), "QANCIEN",     iso_tmp_lonlev)
600
601      iso_tmp_lonlev(:,:)=xtl_ancien(ixt,:,:)
602      CALL put_field(pass,   "XTLANCIEN"//TRIM(outiso), "QLANCIEN",    iso_tmp_lonlev)
603
604      iso_tmp_lonlev(:,:)=xts_ancien(ixt,:,:)
605      CALL put_field(pass,   "XTSANCIEN"//TRIM(outiso), "QSANCIEN",    iso_tmp_lonlev)
606
607      iso_tmp_lonlev(:,:)=wake_deltaxt(ixt,:,:)
608      CALL put_field(pass,"WAKE_DELTAXT"//TRIM(outiso), "WAKE_DELTAQ", iso_tmp_lonlev)
609
610      iso_tmp(:)=xtrun_off_lic_0(ixt,:)
611      CALL put_field(pass,"XTRUNOFFLIC0"//TRIM(outiso), "Runofflic0",  iso_tmp)
612
613      iso_tmp_lonlev(:,:)=wake_deltaxt(ixt,:,:)
614      CALL put_field(pass,"WAKE_DELTAXT"//TRIM(outiso), "WAKE_DELTAXT",iso_tmp_lonlev)
615
616      ! variables seulement pour niso:
617      if (ixt.le.niso) then
618
619      iso_tmp(:)=xtsol(ixt,:)
620      CALL put_field(pass,      "XTSOL"//TRIM(outiso), "Eau dans le sol (mm)",iso_tmp)
621
622      iso_tmp(:)=Rland_ice(ixt,:)
623      CALL put_field(pass,  "Rland_ice"//TRIM(outiso), "ratio land ice",      iso_tmp)
624
625      endif ! if (ixt.le.niso) then
626
627      enddo !do ixt=1,niso
628
629      write(*,*) 'phyisoredem 261: sortie'
630      END SUBROUTINE phyisoredem
631#endif
632
633END SUBROUTINE phyredem
Note: See TracBrowser for help on using the repository browser.