source: LMDZ6/trunk/libf/phylmd/phys_output_mod.F90 @ 5927

Last change on this file since 5927 was 5927, checked in by Sebastien Nguyen, 11 days ago

Changes to compile LMDZ-OR-ISO and wrtie output variables Rsol isotopes soil ratio) xtevap xtcoastal xtrivflu. Changes from CA and ND to write output variables xtprw (precipitatble water) uxt and vxt (meridional and zonal advected humidity) Rlandice and xtsnow.

  • 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 Id
File size: 33.5 KB
Line 
1! $Id: phys_output_mod.F90 5927 2025-12-12 16:26:10Z snguyen $
2!
3
4MODULE phys_output_mod
5  USE indice_sol_mod
6  USE phys_output_var_mod
7  USE phys_output_write_mod, ONLY : phys_output_write
8
9  REAL, DIMENSION(nfiles),SAVE :: ecrit_files
10  LOGICAL, DIMENSION(nfiles)   :: phys_out_filekeys
11
12
13! Abderrahmane 12 2007
14!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
15!!! Ecreture des Sorties du modele dans les fichiers Netcdf :
16! histmth.nc : moyennes mensuelles
17! histday.nc : moyennes journalieres
18! histhf.nc  : moyennes toutes les 3 heures
19! histins.nc : valeurs instantanees
20! AI. nov 2024 : Modifs pour rajouter plus de choix pour la frequence temporelle d'archivage
21!                dans les fichiers de sorties (avec IOIPSL) :
22!                month(s),m,mth,mois,m,day(s),d,jour(s),j, ...
23!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
24
25CONTAINS
26
27!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
28!!!!!!!!! Ouverture des fichier et definition des variable de sortie !!!!!!!!
29  !! histbeg, histvert et histdef
30!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
31
32  SUBROUTINE phys_output_open(rlon,rlat,pim,tabij,ipt,jpt,plon,plat, &
33       jjmp1,nlevSTD,clevSTD,rlevSTD, dtime, ok_veget, &
34       type_ocean, iflag_pbl,iflag_pbl_split,ok_mensuel,ok_journe, &
35       ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, read_climoz, &
36       phys_out_filestations, &
37       aerosol_couple, flag_aerosol_strat, &
38       pdtphys, paprs, pphis, pplay, lmax_th, ptconv, ptconvth, ivap, &
39       d_u, d_t, qx, d_qx, zmasse, ok_sync)   
40
41    USE iophy
42    USE dimphy
43    USE infotrac_phy, ONLY: nqtot, tracers, niso, ntraciso=>ntiso
44    USE strings_mod,  ONLY: maxlen
45    USE ioipsl
46    USE phys_cal_mod, only : hour, calend
47    USE mod_phys_lmdz_para
48    !Martin
49    USE surface_data, ONLY : landice_opt
50    USE phys_output_ctrlout_mod
51    USE mod_grid_phy_lmdz, only: klon_glo,nbp_lon,nbp_lat
52    USE print_control_mod, ONLY: prt_level,lunout
53    USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs, aps, bps, pseudoalt, presinter
54    USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref
55
56    USE AERO_MOD, ONLY : nbands_lw_rrtm !FC
57
58    ! ug Pour les sorties XIOS
59    USE wxios_mod
60    USE infotrac_phy, ONLY: nbtr_bin
61#ifdef ISO
62    USE isotopes_mod, ONLY: isoName,iso_HTO
63#ifdef ISOTRAC
64    USE isotrac_mod, ONLY: index_zone,index_iso,strtrac
65#endif
66#endif
67
68    USE clesphys_mod_h
69    USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_STRATAER
70    USE yomcst_mod_h
71
72    IMPLICIT NONE
73
74
75    ! ug Nouveaux arguments necessaires au histwrite_mod:
76    INTEGER, INTENT(IN)                         :: ivap
77    INTEGER, DIMENSION(klon), INTENT(IN)        :: lmax_th
78    LOGICAL, INTENT(IN)                         :: ok_sync
79    LOGICAL, DIMENSION(klon, klev), INTENT(IN)  :: ptconv, ptconvth
80    REAL, INTENT(IN)                            :: pdtphys
81    REAL, DIMENSION(klon), INTENT(IN)           :: pphis
82    REAL, DIMENSION(klon, klev), INTENT(IN)     :: pplay, d_u, d_t
83    REAL, DIMENSION(klon, klev+1), INTENT(IN)   :: paprs
84    REAL, DIMENSION(klon,klev,nqtot), INTENT(IN):: qx, d_qx
85    REAL, DIMENSION(klon, klev), INTENT(IN)     :: zmasse
86
87
88    REAL,DIMENSION(klon),INTENT(IN) :: rlon
89    REAL,DIMENSION(klon),INTENT(IN) :: rlat
90    INTEGER, INTENT(IN)             :: pim
91    INTEGER, DIMENSION(pim)            :: tabij
92    INTEGER,DIMENSION(pim), INTENT(IN) :: ipt, jpt
93    REAL,DIMENSION(pim), INTENT(IN) :: plat, plon
94    REAL,DIMENSION(pim,2) :: plat_bounds, plon_bounds
95
96    INTEGER                               :: jjmp1
97    INTEGER                               :: nlevSTD, radpas
98    LOGICAL                               :: ok_mensuel, ok_journe, ok_hf, ok_instan
99    LOGICAL                               :: ok_LES,ok_ade,ok_aie
100    INTEGER                               :: flag_aerosol_strat
101    LOGICAL                               :: aerosol_couple
102    INTEGER, INTENT(IN)::  read_climoz ! read ozone climatology
103    !     Allowed values are 0, 1 and 2
104    !     0: do not read an ozone climatology
105    !     1: read a single ozone climatology that will be used day and night
106    !     2: read two ozone climatologies, the average day and night
107    !     climatology and the daylight climatology
108
109    REAL                                  :: dtime
110    INTEGER                               :: idayref
111    REAL                                  :: zjulian_start, zjulian
112    CHARACTER(LEN=4), DIMENSION(nlevSTD)  :: clevSTD
113    REAL, DIMENSION(nlevSTD)              :: rlevSTD
114    INTEGER                               :: nsrf, k, iq, iff, i, j, ilev, itr, itrb, ixt, iiso, izone
115    INTEGER                               :: naero
116    LOGICAL                               :: ok_veget
117    INTEGER                               :: iflag_pbl
118    INTEGER                               :: iflag_pbl_split
119    CHARACTER(LEN=4)                      :: bb2
120    CHARACTER(LEN=2)                      :: bb3
121    CHARACTER(LEN=6)                      :: type_ocean
122    INTEGER, DIMENSION(nbp_lon*jjmp1)         ::  ndex2d
123    INTEGER, DIMENSION(nbp_lon*jjmp1*klev)    :: ndex3d
124    INTEGER                               :: imin_ins, imax_ins
125    INTEGER                               :: jmin_ins, jmax_ins
126    INTEGER, DIMENSION(nfiles)            :: phys_out_levmin, phys_out_levmax
127    INTEGER, DIMENSION(nfiles)            :: phys_out_filelevels
128    CHARACTER(LEN=20), DIMENSION(nfiles)  :: chtimestep = (/ 'Default', 'Default', 'Default', 'Default', 'Default', &
129                                                             'Default', 'Default', 'Default', 'Default', 'Default' /)
130    LOGICAL, DIMENSION(nfiles)            :: phys_out_filestations
131
132#ifdef ISO
133    CHARACTER(LEN=maxlen) :: outiso
134    CHARACTER(LEN=20) :: unit
135#endif
136    CHARACTER(LEN=maxlen) :: tnam, lnam, dn
137    INTEGER :: flag(nfiles)
138
139!!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
140    !                 entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax]
141    LOGICAL, DIMENSION(nfiles), SAVE :: phys_out_regfkey = [.FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE.]
142    REAL, DIMENSION(nfiles), SAVE ::  phys_out_lonmin  = [  -180.,   -180.,   -180.,   -180.,   -180.,   -180.,   -180.,   -180.,   -180.,   -180.]
143    REAL, DIMENSION(nfiles), SAVE ::  phys_out_lonmax  = [   180.,    180.,    180.,    180.,    180.,    180.,    180.,    180.,    180.,    180.]
144    REAL, DIMENSION(nfiles), SAVE ::  phys_out_latmin  = [   -90.,    -90.,    -90.,    -90.,    -90.,    -90.,    -90.,    -90.,    -90.,    -90.]
145    REAL, DIMENSION(nfiles), SAVE ::  phys_out_latmax  = [    90.,     90.,     90.,     90.,     90.,     90.,     90.,     90.,     90.,     90.]
146
147    REAL, DIMENSION(klev,2) :: Ahyb_bounds, Bhyb_bounds
148    REAL, DIMENSION(klev+1)   :: lev_index
149               
150    ! ug Variables utilisees pour recuperer le calendrier pour xios
151    INTEGER :: x_an, x_mois, x_jour
152    REAL :: x_heure
153    INTEGER :: ini_an, ini_mois, ini_jour
154    REAL :: ini_heure
155
156    INTEGER                         :: ISW
157    REAL, DIMENSION(NSW)            :: wl1_sun, wl2_sun !wavelength bounds (in um) for SW
158    REAL, DIMENSION(NSW)            :: wn1_sun, wn2_sun !wavenumber bounds (in m-1) for SW
159    REAL, DIMENSION(NSW)            :: spectband  !mean wavenumb. of each sp.band
160    REAL, DIMENSION(NSW,2)          :: spbnds_sun !bounds of spectband
161!FC
162    INTEGER                         :: ILW
163    REAL,  DIMENSION(nbands_lw_rrtm):: wl1_lw, wl2_lw
164
165    WRITE(lunout,*) 'Debut phys_output_mod.F90'
166! Initialisations (Valeurs par defaut
167!FC
168       wl1_lw = [ 10., 250., 500., 630., 700., 820., 980.,1080. &
169     & ,1180.,1390.,1480.,1800.,2080.,2250.,2380.,2600.]
170       wl2_lw = [250., 500., 630., 700., 820., 980.,1080.,1180. &
171     & ,1390.,1480.,1800.,2080.,2250.,2380.,2600.,3000.]
172!         print*, 'avant boucle', nbands_lw_rrtm
173!        DO ILW=1,nbands_lw_rrtm
174!        spectbandLW(ILW)= (wl1_lw(ilw) + wl2_lw(ILW) )/2
175!        print*, 'on a les canaux ? ',ILW,spectbandLW(ILW),wl1_lw(ILW),wl2_lw(ilw)
176!        enddo
177!        print*, 'spectbandLW',spectbandLW
178
179!FC
180
181
182    DO ilev=1,klev
183      Ahyb_bounds(ilev,1) = ap(ilev)
184      Ahyb_bounds(ilev,2) = ap(ilev+1)
185      Bhyb_bounds(ilev,1) = bp(ilev)
186      Bhyb_bounds(ilev,2) = bp(ilev+1)
187      lev_index(ilev) = REAL(ilev)
188    END DO
189    lev_index(klev+1) = REAL(klev+1)
190
191    IF (.NOT. ALLOCATED(o_trac)) ALLOCATE(o_trac(nqtot))
192    IF (.NOT. ALLOCATED(o_trac_cum)) ALLOCATE(o_trac_cum(nqtot))
193    ALLOCATE(o_dtr_the(nqtot),o_dtr_con(nqtot),o_dtr_lessi_impa(nqtot))
194    ALLOCATE(o_dtr_lessi_nucl(nqtot),o_dtr_insc(nqtot),o_dtr_bcscav(nqtot))
195    ALLOCATE(o_dtr_evapls(nqtot),o_dtr_ls(nqtot),o_dtr_trsp(nqtot))
196    ALLOCATE(o_dtr_sscav(nqtot),o_dtr_sat(nqtot),o_dtr_uscav(nqtot))
197    ALLOCATE(o_dtr_wet_cv(nqtot), o_dtr_wet(nqtot))
198    ALLOCATE(o_dtr_dry(nqtot),o_dtr_vdf(nqtot))
199IF (CPPKEY_STRATAER) THEN
200    ALLOCATE(o_nd_mode(nbtr_bin),o_sulfmmr_mode(nbtr_bin))
201END IF
202#ifdef ISO
203    ALLOCATE(o_xtprw(ntraciso)) ! CAa
204    ALLOCATE(o_uxtflux(ntraciso))   ! CAa
205    ALLOCATE(o_vxtflux(ntraciso))   ! CAa
206    ALLOCATE(o_xtprecip(ntraciso))
207    ALLOCATE(o_Rland_ice(ntraciso))         ! Niels
208    ALLOCATE(o_xtsnow_srf(ntraciso, nbsrf)) ! Niels 18 janvier 2024
209    ALLOCATE(o_xtplul(ntraciso))
210    ALLOCATE(o_xtpluc(ntraciso))
211    ALLOCATE(o_xtevap(ntraciso))
212    ALLOCATE(o_xtevap_srf(ntraciso,4))
213    ALLOCATE(o_xtovap(ntraciso))
214    ALLOCATE(o_xtoliq(ntraciso))
215    ALLOCATE(o_xtcond(ntraciso))
216    ALLOCATE(o_xtrunoff_diag(ntraciso))
217    ALLOCATE(o_xtriverflow(ntraciso))   !PRSN
218    ALLOCATE(o_xtcoastalflow(ntraciso))
219    ALLOCATE(o_Rsol(ntraciso))          !PRSN
220    ALLOCATE(o_dxtdyn(ntraciso))
221    ALLOCATE(o_dxtldyn(ntraciso))
222    ALLOCATE(o_dxtcon(ntraciso))
223    ALLOCATE(o_dxtlsc(ntraciso))
224    ALLOCATE(o_dxteva(ntraciso))
225    ALLOCATE(o_dxtajs(ntraciso))
226    ALLOCATE(o_dxtvdf(ntraciso))
227    ALLOCATE(o_dxtthe(ntraciso))
228    ALLOCATE(o_dxtch4(ntraciso))
229    IF (iso_HTO.GT.0) THEN
230      ALLOCATE(o_dxtprod_nucl(ntraciso))
231      ALLOCATE(o_dxtcosmo(ntraciso))
232      ALLOCATE(o_dxtdecroiss(ntraciso))
233    ENDIF
234#endif
235
236    levmax = [klev, klev, klev, klev, klev, klev, nlevSTD, nlevSTD, nlevSTD, klev]
237
238    phys_out_filenames(1) = 'histmth'
239    phys_out_filenames(2) = 'histday'
240    phys_out_filenames(3) = 'histhf6h'
241    phys_out_filenames(4) = 'histhf3h'
242    phys_out_filenames(5) = 'histhf3hm'
243    phys_out_filenames(6) = 'histstn'
244    phys_out_filenames(7) = 'histmthNMC'
245    phys_out_filenames(8) = 'histdayNMC'
246    phys_out_filenames(9) = 'histhfNMC'
247    phys_out_filenames(10)= 'histstrataer'
248
249    type_ecri(1) = 'ave(X)'
250    type_ecri(2) = 'ave(X)'
251    type_ecri(3) = 'inst(X)'
252    type_ecri(4) = 'inst(X)'
253    type_ecri(5) = 'ave(X)'
254    type_ecri(6) = 'inst(X)'
255    type_ecri(7) = 'inst(X)'
256    type_ecri(8) = 'inst(X)'
257    type_ecri(9) = 'inst(X)'
258    type_ecri(10)= 'ave(X)'
259
260    clef_files(1:3) = .TRUE.
261    clef_files(4:10) = .FALSE.
262    IF (CPPKEY_STRATAER) THEN
263      clef_files(10)= .TRUE.
264    ELSE
265      clef_files(10)= .FALSE.
266    END IF
267
268    !sortir des fichiers "stations" si clef_stations(:)=.TRUE.
269    clef_stations(1:10) = .FALSE.
270    lev_files(1:10) = 5
271
272    print*,'A ecrit_mth=',ecrit_mth
273    ! Frequencies of the history files;
274    ! Defaut
275    ! overwritten by chtimestep given to convers_timesteps
276    ecrit_files(1) = ecrit_mth
277    ecrit_files(2) = ecrit_day
278    ecrit_files(3) = ecrit_hf
279    ecrit_files(4) = ecrit_ins
280    ecrit_files(5) = ecrit_LES
281    ecrit_files(6:10) = ecrit_ins
282
283    !! Lectures des parametres de sorties dans physiq.def
284
285    CALL getin('phys_out_regfkey',phys_out_regfkey)
286    CALL getin('phys_out_lonmin',phys_out_lonmin)
287    CALL getin('phys_out_lonmax',phys_out_lonmax)
288    CALL getin('phys_out_latmin',phys_out_latmin)
289    CALL getin('phys_out_latmax',phys_out_latmax)
290    phys_out_levmin(:)=levmin(:)
291    CALL getin('phys_out_levmin',levmin)
292    phys_out_levmax(:)=levmax(:)
293    CALL getin('phys_out_levmax',levmax)
294    CALL getin('phys_out_filenames',phys_out_filenames)
295    phys_out_filekeys(:)=clef_files(:)
296    CALL getin('phys_out_filekeys',clef_files)
297    phys_out_filestations(:)=clef_stations(:)
298    CALL getin('phys_out_filestations',clef_stations)
299    phys_out_filelevels(:)=lev_files(:)
300    CALL getin('phys_out_filelevels',lev_files)
301    CALL getin('phys_out_filetimesteps',chtimestep)
302    phys_out_filetypes(:)=type_ecri(:)
303    CALL getin('phys_out_filetypes',type_ecri)
304
305    type_ecri_files(:)=type_ecri(:)
306
307!    if (ok_all_xml) phys_out_filelevels = 999
308
309    WRITE(lunout,*)'phys_out_lonmin=',phys_out_lonmin
310    WRITE(lunout,*)'phys_out_lonmax=',phys_out_lonmax
311    WRITE(lunout,*)'phys_out_latmin=',phys_out_latmin
312    WRITE(lunout,*)'phys_out_latmax=',phys_out_latmax
313    WRITE(lunout,*)'phys_out_filenames=',phys_out_filenames
314    WRITE(lunout,*)'phys_out_filetypes=',type_ecri
315    WRITE(lunout,*)'phys_out_filekeys=',clef_files
316    WRITE(lunout,*)'phys_out_filestations=',clef_stations
317    WRITE(lunout,*)'phys_out_filelevels=',lev_files
318    WRITE(lunout,*)'phys_out_regfkey=',phys_out_regfkey
319
320! A noter pour
321! l heure initiale - dans les fichiers histoire hist* - on met comme 
322! heure de debut soit la vraie heure (pour le 1D) soit 0h (pour le 3D)
323! afin d avoir une seule sortie mensuelle par mois lorsque l on tourne
324! par annee (IM).
325!
326     idayref = day_ref
327     IF (klon_glo==1) THEN
328       ! current_time (used to compute hour) is updated at the begining of
329       ! the physics; to set the correct outputs "initial time" we thus
330       ! have to use (hour-dtphys).
331         CALL ymds2ju(annee_ref, 1, idayref, hour-pdtphys, zjulian)
332         print *,'phys_output_mod: annee,iday,hour,zjulian=',annee_ref,idayref, hour, zjulian
333     ELSE
334         CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
335         CALL ymds2ju(annee_ref, 1, day_ini, start_time*rday, zjulian_start)
336     ENDIF
337
338    IF (using_xios) THEN
339      ! ug R\'eglage du calendrier xios
340      !Temps julian => an, mois, jour, heure
341      CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
342      CALL ju2ymds(zjulian_start, ini_an, ini_mois, ini_jour, ini_heure)
343      CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure, ini_an, &
344                         ini_mois, ini_jour, ini_heure )
345    ENDIF
346
347!!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
348    ! Appel de histbeg et histvert pour creer le fichier et les niveaux verticaux !!
349    ! Appel des histbeg pour definir les variables (nom, moy ou inst, freq de sortie ..
350!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
351
352    zdtime_moy = dtime         ! Frequence ou l on moyenne
353
354
355  ecrit_files(7) = ecrit_files(1)
356  ecrit_files(8) = ecrit_files(2)
357  ecrit_files(9) = ecrit_files(3)
358
359  DO iff=1,nfiles
360
361       ! Calculate ecrit_files for all files
362      IF ( chtimestep(iff).eq.'Default' ) THEN
363          ! Par defaut ecrit_files = (ecrit_mensuel ecrit_jour ecrit_hf
364          ! ...)*86400.
365          ecrit_files(iff)=ecrit_files(iff)*86400.
366      ELSE IF (chtimestep(iff).eq.'-1') THEN
367          PRINT*,'ecrit_files(',iff,') < 0 so IOIPSL work on different'
368          PRINT*,'months length'
369          ecrit_files(iff)=-1.
370      ELSE
371       CALL convers_timesteps(chtimestep(iff),dtime,ecrit_files(iff))
372       PRINT*,'Dans phys_output_open, iff=',iff,' ecrit_files=',ecrit_files(iff)
373      ENDIF
374      ! ecrit_files contains frequency of file iif in seconds
375
376
377       WRITE(lunout,*)'ecrit_files(',iff,')= ',ecrit_files(iff)
378       zoutm(iff) = ecrit_files(iff) ! Frequence ou l on ecrit en seconde
379
380
381    IF (using_xios) THEN
382      !!! Ouverture de chaque fichier XIOS !!!!!!!!!!!
383      IF (.not. ok_all_xml) THEN
384        IF (prt_level >= 10) THEN
385         print*,'phys_output_open: call wxios_add_file with phys_out_filenames(iff)=',trim(phys_out_filenames(iff))   
386        ENDIF
387        CALL wxios_add_file(phys_out_filenames(iff),chtimestep(iff),lev_files(iff)) 
388      ENDIF
389
390      !!! Declaration des axes verticaux de chaque fichier:
391      IF (prt_level >= 10) THEN
392        print*,'phys_output_open: Declare vertical axes for each file'
393      ENDIF
394
395      IF (iff.LE.6.OR.iff.EQ.10) THEN
396        CALL wxios_add_vaxis("presnivs", &
397              levmax(iff) - levmin(iff) + 1, presnivs(levmin(iff):levmax(iff)))
398        CALL wxios_add_vaxis("presinter", &
399              klev + 1, presinter(1:klev+1))
400        CALL wxios_add_vaxis("Ahyb", &
401              levmax(iff) - levmin(iff) + 1, aps(levmin(iff):levmax(iff)), positif='down', &
402              bnds=Ahyb_bounds(levmin(iff):levmax(iff),:))
403        CALL wxios_add_vaxis("Bhyb", &
404              levmax(iff) - levmin(iff) + 1, bps(levmin(iff):levmax(iff)), positif='down', &
405              bnds=Bhyb_bounds(levmin(iff):levmax(iff),:))
406        CALL wxios_add_vaxis("klev", levmax(iff) - levmin(iff) + 1, &
407                              lev_index(levmin(iff):levmax(iff)))
408        CALL wxios_add_vaxis("klevp1", klev+1, &
409                              lev_index(1:klev+1))
410        CALL wxios_add_vaxis("bnds", 2, (/1.,2./))
411 
412        CALL wxios_add_vaxis("Alt", &
413                levmax(iff) - levmin(iff) + 1, pseudoalt)
414
415        ! wl1_sun/wl2_sun: minimum/maximum bound of wavelength (in um)
416        SELECT CASE(NSW)
417          CASE(6)
418            wl1_sun(1:6) = [0.180, 0.250, 0.440, 0.690, 1.190, 2.380]
419            wl2_sun(1:6) = [0.250, 0.440, 0.690, 1.190, 2.380, 4.000]
420          CASE(2)
421            wl1_sun(1:2) = [0.250, 0.690]
422            wl2_sun(1:2) = [0.690, 4.000]
423        END SELECT
424
425        DO ISW=1, NSW
426          wn1_sun(ISW)=1.e+6/wl1_sun(ISW)
427          wn2_sun(ISW)=1.e+6/wl2_sun(ISW)
428          spbnds_sun(ISW,1)=wn2_sun(ISW)
429          spbnds_sun(ISW,2)=wn1_sun(ISW)
430          spectband(ISW)=(wn1_sun(ISW)+wn2_sun(ISW))/2
431        ENDDO
432!
433!!! ajout axe vertical spectband : solar band number
434        CALL wxios_add_vaxis("spectband", NSW, spectband, positif='down')
435      ELSE
436        ! NMC files
437        CALL wxios_add_vaxis("plev", &
438                levmax(iff) - levmin(iff) + 1, rlevSTD(levmin(iff):levmax(iff)))
439      ENDIF
440    ENDIF !using_xios
441
442        IF (clef_files(iff)) THEN
443!!!!!!!!!!!!!!!!! Traitement dans le cas ou l'on veut stocker sur un domaine limite !!
444!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
445          IF (phys_out_regfkey(iff)) THEN
446             imin_ins=1
447             imax_ins=nbp_lon
448             jmin_ins=1
449             jmax_ins=jjmp1
450
451             ! correction abderr       
452             DO i=1,nbp_lon
453                WRITE(lunout,*)'io_lon(i)=',io_lon(i)
454                IF (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
455                IF (io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1
456             ENDDO
457
458             DO j=1,jjmp1
459                WRITE(lunout,*)'io_lat(j)=',io_lat(j)
460                IF (io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1
461                IF (io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j
462             ENDDO
463
464             WRITE(lunout,*)'On stoke le fichier histoire numero ',iff,' sur ', &
465                  imin_ins,imax_ins,jmin_ins,jmax_ins
466             WRITE(lunout,*)'longitudes : ', &
467                  io_lon(imin_ins),io_lon(imax_ins), &
468                  'latitudes : ', &
469                  io_lat(jmax_ins),io_lat(jmin_ins)
470
471             CALL histbeg(phys_out_filenames(iff),nbp_lon,io_lon,jjmp1,io_lat, &
472                  imin_ins,imax_ins-imin_ins+1, &
473                  jmin_ins,jmax_ins-jmin_ins+1, &
474                  itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
475!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
476             !IM fichiers stations
477          ELSE IF (clef_stations(iff)) THEN
478
479             IF (prt_level >= 10) THEN
480             WRITE(lunout,*)'phys_output_open: iff=',iff,'  phys_out_filenames(iff)=',phys_out_filenames(iff)
481             ENDIF
482             
483             CALL histbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, &
484                  phys_out_filenames(iff), &
485                  itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
486          ELSE
487
488             IF (prt_level >= 10) THEN
489             WRITE(lunout,*)'phys_output_open: iff=',iff,'  phys_out_filenames(iff)=',phys_out_filenames(iff)
490             ENDIF
491
492             CALL histbeg_phy_all(phys_out_filenames(iff),itau_phy,zjulian,&
493                 dtime,nhorim(iff),nid_files(iff))
494          ENDIF
495
496#ifndef CPP_IOIPSL_NO_OUTPUT
497          IF (iff.LE.6.OR.iff.EQ.10) THEN
498             CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "Pa", & 
499               levmax(iff) - levmin(iff) + 1, &
500               presnivs(levmin(iff):levmax(iff)), nvertm(iff),"down")
501!!!! Composantes de la coordonnee sigma-hybride
502          CALL histvert(nid_files(iff), "Ahyb","Ahyb comp of Hyb Cord ", "Pa", &
503               levmax(iff) - levmin(iff) + 1,aps,nvertap(iff))
504
505          CALL histvert(nid_files(iff), "Bhyb","Bhyb comp of Hyb Cord", " ", &
506               levmax(iff) - levmin(iff) + 1,bps,nvertbp(iff))
507
508          CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", &                       
509               levmax(iff) - levmin(iff) + 1,pseudoalt,nvertAlt(iff))
510!FC
511!          CALL histvert(nid_files(iff), "spectbandLW"," LW bands ", "cm-1", &
512!                  nbands_lw_rrtm ,wl1_lw, ncanaux(iff))
513!          print *, ' apres ncanaux = ' , ncanaux(iff),iff
514!FC
515
516
517          ELSE
518          ! NMC files
519             CALL histvert(nid_files(iff), "plev", "pressure", "Pa", &
520               levmax(iff) - levmin(iff) + 1, &
521              rlevSTD(levmin(iff):levmax(iff)), nvertm(iff), "down")
522          ENDIF
523#endif
524
525     ENDIF ! clef_files
526
527          itr = 0; itrb = 0
528          DO iq = 1, nqtot
529            IF(.NOT.tracers(iq)%isInPhysics) CYCLE
530            itr = itr + 1
531            dn = 'd'//TRIM(tracers(iq)%name)//'_'
532
533            flag = [1, 5, 5, 5, 10, 10, 11, 11, 11, 11]
534            lnam = 'Tracer '//TRIM(tracers(iq)%longName)
535            tnam = TRIM(tracers(iq)%name);  o_trac          (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
536
537            flag = [4, 7, 7, 7, 10, 10, 11, 11, 11, 11]
538            lnam = 'Tendance tracer '//TRIM(tracers(iq)%longName)
539            tnam = TRIM(dn)//'vdf';         o_dtr_vdf       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
540
541            flag = [5, 7, 7, 7, 10, 10, 11, 11, 11, 11]
542            tnam = TRIM(dn)//'the';         o_dtr_the       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
543            tnam = TRIM(dn)//'con';         o_dtr_con       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
544
545            flag = [7, 7, 7, 7, 10, 10, 11, 11, 11, 11]
546            tnam = TRIM(dn)//'lessi_impa';  o_dtr_lessi_impa(itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
547            tnam = TRIM(dn)//'lessi_nucl';  o_dtr_lessi_nucl(itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
548            tnam = TRIM(dn)//'insc';        o_dtr_insc      (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
549            tnam = TRIM(dn)//'bcscav';      o_dtr_bcscav    (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
550            tnam = TRIM(dn)//'evapls';      o_dtr_evapls    (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
551            tnam = TRIM(dn)//'ls';          o_dtr_ls        (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
552            tnam = TRIM(dn)//'trsp';        o_dtr_trsp      (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
553            tnam = TRIM(dn)//'sscav';       o_dtr_sscav     (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
554            tnam = TRIM(dn)//'sat';         o_dtr_sat       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
555            tnam = TRIM(dn)//'uscav';       o_dtr_uscav     (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
556
557            lnam = 'tracer convective wet deposition'//TRIM(tracers(iq)%longName)
558            tnam = TRIM(dn)//'wet_cv';       o_dtr_wet_cv       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
559            lnam = 'tracer total wet deposition'//TRIM(tracers(iq)%longName)
560            tnam = TRIM(dn)//'wet';       o_dtr_wet       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
561            lnam = 'tracer tendency dry deposition'//TRIM(tracers(iq)%longName)
562            tnam = 'cum'//TRIM(dn)//'dry';  o_dtr_dry       (itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
563
564            flag = [1, 4, 10, 10, 10, 10, 11, 11, 11, 11]
565            lnam = 'Cumulated tracer '//TRIM(tracers(iq)%longName)
566            tnam = 'cum'//TRIM(tracers(iq)%name); o_trac_cum(itr) = ctrl_out(flag, tnam, lnam, "-", [('',i=1,nfiles)])
567           
568IF (CPPKEY_STRATAER) THEN
569            if(tracers(iq)%name(1:3)=='BIN') then
570               itrb = itrb + 1
571               flag = [11, 11, 11, 11, 11, 11, 11, 11, 11, 1]
572               lnam = 'Dry particle concentration in '//TRIM(tracers(iq)%longName)
573               tnam = TRIM(tracers(iq)%name)//'_nd_mode';     o_nd_mode       (itrb) = ctrl_out(flag, tnam, lnam, "part/m3", [('',i=1,nfiles)])
574               lnam = 'Sulfate MMR in '//TRIM(tracers(iq)%longName)
575               tnam = TRIM(tracers(iq)%name)//'_sulfmmr_mode';o_sulfmmr_mode  (itrb) = ctrl_out(flag, tnam, lnam, "kg(H2SO4)/kg(air)", [('',i=1,nfiles)])
576            endif
577END IF
578         ENDDO
579
580   ENDDO !  iff
581
582#ifdef ISO
583    write(*,*) 'phys_output_mid 589'
584    do ixt=1,ntraciso
585      outiso = TRIM(isoName(ixt))
586      i = INDEX(outiso, '_', .TRUE.)
587      outiso = outiso(1:i-1)//outiso(i+1:LEN_TRIM(outiso))
588
589      flag = [1, 1, 10, 10, 10, 10, 11, 11, 11, 11]
590      unit = 'kg/m2'
591      o_xtprw(ixt)=ctrl_out(flag, 'prw'//TRIM(outiso), 'Precipitable water', unit, [('',i=1,nfiles)])
592      unit = 'kg/m/s'
593      o_uxtflux(ixt)=ctrl_out(flag, 'uq'//TRIM(outiso), 'Zonal humidity transport', unit, [('',i=1,nfiles)])
594      o_vxtflux(ixt)=ctrl_out(flag, 'vq'//TRIM(outiso), 'Merid humidity transport', unit, [('',i=1,nfiles)])
595
596      flag = [1,  1,  1, 10,  5, 10, 11, 11, 11, 11]; unit = 'kg/(s*m2)'
597      o_xtprecip(ixt)=ctrl_out(flag, 'precip'//TRIM(outiso), 'Precip Totale liq+sol', unit, [('',i=1,nfiles)])
598      o_xtpluc  (ixt)=ctrl_out(flag,   'pluc'//TRIM(outiso),    'Convective Precip.', unit, [('',i=1,nfiles)])
599
600      flag = [1,  1,  1, 10, 10, 10, 11, 11, 11, 11]
601      o_xtplul  (ixt)=ctrl_out(flag,   'plul'//TRIM(outiso),   'Large-scale Precip.', unit, [('',i=1,nfiles)])
602      o_xtevap  (ixt)=ctrl_out(flag,   'evap'//TRIM(outiso),             'Evaporat.', unit, [('',i=1,nfiles)])
603
604      ! ajout Camille 8 mai 2023
605      flag = [1, 6, 10, 10, 10, 10, 11, 11, 11, 11]
606      o_xtevap_srf (ixt,1)=ctrl_out(flag,   'evap_ter'//TRIM(outiso), 'Evap sfc'//clnsurf(1), unit, [('',i=1,nfiles)])
607      o_xtevap_srf (ixt,2)=ctrl_out(flag,   'evap_lic'//TRIM(outiso), 'Evap sfc'//clnsurf(2), unit, [('',i=1,nfiles)])
608      o_xtevap_srf (ixt,3)=ctrl_out(flag,   'evap_oce'//TRIM(outiso), 'Evap sfc'//clnsurf(3), unit, [('',i=1,nfiles)])
609      o_xtevap_srf (ixt,4)=ctrl_out(flag,   'evap_sic'//TRIM(outiso), 'Evap sfc'//clnsurf(4), unit, [('',i=1,nfiles)])
610
611      flag = [2,  3,  4, 10, 10, 10, 11, 11, 11, 11]; unit = 'kg/kg'
612      o_xtovap  (ixt)=ctrl_out(flag,   'ovap'//TRIM(outiso),     'Specific humidity', unit, [('',i=1,nfiles)])
613      o_xtoliq  (ixt)=ctrl_out(flag,   'oliq'//TRIM(outiso),          'Liquid water', unit, [('',i=1,nfiles)])
614      o_xtcond  (ixt)=ctrl_out(flag,  'ocond'//TRIM(outiso),       'Condensed water', unit, [('',i=1,nfiles)])
615
616      flag = [1,  1,  1, 10, 5, 10, 11, 11, 11, 11]; unit = 'kg/m2/s'
617      o_xtrunoff_diag  (ixt)=ctrl_out(flag, 'runoffland'//TRIM(outiso), 'Run-off rate land for bucket', unit, [('',i=1,nfiles)])
618
619      ! Niels 14 janvier 2024
620      flag = [1,  1,  1, 10, 10, 10, 11, 11, 11, 11]; unit = '1'
621      o_Rland_ice(ixt) = ctrl_out(flag, 'Rland_ice'//TRIM(outiso), 'R land ice', unit, [('',i=1,nfiles)])
622     
623      ! Snow above soil
624      flag = [1,  1,  1, 10, 10, 10, 11, 11, 11, 11]; unit = 'kg/m2'
625      !do nsrf = 1, nbsrf
626      !  o_xtsnow_srf (ixt, nsrf) = &
627      !      ctrl_out(flag, 'snow_'//clnsurf(nsrf)//TRIM(outiso), 'Snow sfc'//clnsurf(nsrf), unit, [('',i=1,nfiles)])
628      !end do
629      o_xtsnow_srf (ixt,1)=ctrl_out(flag, 'snow_ter'//TRIM(outiso), 'Snow sfc'//clnsurf(1), unit, [('',i=1,nfiles)])
630      o_xtsnow_srf (ixt,2)=ctrl_out(flag, 'snow_lic'//TRIM(outiso), 'Snow sfc'//clnsurf(2), unit, [('',i=1,nfiles)])
631      o_xtsnow_srf (ixt,3)=ctrl_out(flag, 'snow_oce'//TRIM(outiso), 'Snow sfc'//clnsurf(3), unit, [('',i=1,nfiles)])
632      o_xtsnow_srf (ixt,4)=ctrl_out(flag, 'snow_sic'//TRIM(outiso), 'Snow sfc'//clnsurf(4), unit, [('',i=1,nfiles)])
633      ! end Niels
634
635      !PRSN
636
637      flag = [1,  1,  1, 10, 5, 10, 11, 11, 11, 11]; unit = 'kg/(s*m2)'
638      o_xtriverflow  (ixt)=ctrl_out(flag, 'rivflow'//TRIM(outiso), 'River flow to ocean', unit, [('',i=1,nfiles)])
639      o_xtcoastalflow  (ixt)=ctrl_out(flag, 'coastflow'//TRIM(outiso), 'Coastal flow to ocean', unit, [('',i=1,nfiles)])
640
641      flag = [1,  1,  1, 10, 5, 10, 11, 11, 11, 11]; unit = 'kg/kg'
642      o_Rsol  (ixt)=ctrl_out(flag, 'Rsol'//TRIM(outiso), 'Isotopic soil ratio', unit, [('',i=1,nfiles)])
643      !PRSN
644
645      flag = [4, 10, 10, 10, 10, 10, 11, 11, 11, 11]; unit = '(kg/kg)/s'
646      o_dxtdyn  (ixt)=ctrl_out(flag,  'dqdyn'//TRIM(outiso),           'Dynamics dQ', unit, [('',i=1,nfiles)])
647      o_dxtldyn (ixt)=ctrl_out(flag, 'dqldyn'//TRIM(outiso),          'Dynamics dQL', unit, [('',i=1,nfiles)])
648      o_dxtcon  (ixt)=ctrl_out(flag,  'dqcon'//TRIM(outiso),         'Convection dQ', unit, [('',i=1,nfiles)])
649      o_dxteva  (ixt)=ctrl_out(flag,  'dqeva'//TRIM(outiso),      'Reevaporation dQ', unit, [('',i=1,nfiles)])
650      o_dxtlsc  (ixt)=ctrl_out(flag,  'dqlsc'//TRIM(outiso),       'Condensation dQ', unit, [('',i=1,nfiles)])
651      o_dxtajs  (ixt)=ctrl_out(flag,  'dqajs'//TRIM(outiso),        'Dry adjust. dQ', unit, [('',i=1,nfiles)])
652      o_dxtvdf  (ixt)=ctrl_out(flag,  'dqvdf'//TRIM(outiso),     'Boundary-layer dQ', unit, [('',i=1,nfiles)])
653      o_dxtthe  (ixt)=ctrl_out(flag,  'dqthe'//TRIM(outiso),            'Thermal dQ', unit, [('',i=1,nfiles)])
654
655      IF(ok_qch4) o_dxtch4(ixt)=ctrl_out(flag, 'dqch4'//TRIM(outiso), 'H2O due to CH4 oxidation & photolysis', &
656                                                                                      unit, [('',i=1,nfiles)])
657      IF(ixt == iso_HTO) THEN
658      o_dxtprod_nucl(ixt)=ctrl_out(flag, 'dqprodnucl'//TRIM(outiso), 'dHTO/dt due to nuclear production',      &
659                                                                                      unit, [('',i=1,nfiles)])
660      o_dxtcosmo    (ixt)=ctrl_out(flag,    'dqcosmo'//TRIM(outiso), 'dHTO/dt due to cosmogenic production',   &
661                                                                                      unit, [('',i=1,nfiles)])
662      o_dxtdecroiss (ixt)=ctrl_out(flag, 'dqdecroiss'//TRIM(outiso), 'dHTO/dt due to radiative destruction',   &
663                                                                                      unit, [('',i=1,nfiles)])
664      END IF
665    enddo !do ixt=1,niso
666    write(*,*) 'phys_output_mid 596'
667#endif
668
669   ! Updated write frequencies due to phys_out_filetimesteps.
670    ! Write frequencies are now in seconds. 
671! WHY CHANGING ecrit_mth ?
672! For Cosp ?
673!    ecrit_mth = ecrit_files(1)
674!    print*,'B ecrit_mth=',ecrit_mth
675!    ecrit_day = ecrit_files(2)
676!    ecrit_hf  = ecrit_files(3)
677!    ecrit_ins = ecrit_files(4)
678!    ecrit_LES = ecrit_files(5)
679!    ecrit_ins = ecrit_files(6)
680
681    IF (prt_level >= 10) THEN
682      WRITE(lunout,*)'swaerofree_diag=',swaerofree_diag
683      WRITE(lunout,*)'swaero_diag=',swaero_diag
684      WRITE(lunout,*)'dryaod_diag=',dryaod_diag
685      WRITE(lunout,*)'ok_4xCO2atm=',ok_4xCO2atm
686      WRITE(lunout,*)'phys_output_open: ends here'
687    ENDIF
688    PRINT*,'Dans phys_output_open,ecrit_files B',ecrit_files(1:6)
689
690!  DO iq=1,nqtot
691!    IF(.NOT.tracers(iq)%isInPhysics) CYCLE
692!    WRITE(*,'(a,i1,a,10i3)')'trac(',iq,')%flag = ',o_trac(iq)%flag
693!    WRITE(*,'(a,i1,a)')'trac(',iq,')%name = '//TRIM(o_trac(iq)%name)
694!    WRITE(*,'(a,i1,a)')'trac(',iq,')%description = '//TRIM(o_trac(iq)%description)
695!  END DO
696
697  END SUBROUTINE phys_output_open
698
699  SUBROUTINE convers_timesteps(str,dtime,timestep)
700
701    use ioipsl
702    USE phys_cal_mod
703    USE time_phylmdz_mod, ONLY: day_ref, annee_ref
704    USE print_control_mod, ONLY: lunout
705
706    IMPLICIT NONE
707
708    CHARACTER(LEN=20)   :: str
709    CHARACTER(LEN=10)   :: type
710    INTEGER             :: ipos,il
711    real                :: ttt,xxx,timestep,dayseconde,dtime
712    parameter (dayseconde=86400.)
713
714    ipos=scan(str,'0123456789.',.TRUE.)
715    ! 
716    il=len_trim(str)
717    WRITE(lunout,*) "ipos = ", ipos
718    WRITE(lunout,*) "il = ", il
719    IF (ipos == 0) CALL abort_physic("convers_timesteps", "bad str", 1)
720    read(str(1:ipos),*) ttt
721    WRITE(lunout,*)ttt
722    type=str(ipos+1:il)
723
724    IF ( il == ipos ) THEN
725       type='day'
726    ENDIF
727
728    IF ( type == 'day'.or.type == 'days'.or.type == 'd'.or.type == 'jours'.or.type == 'jour'.or.type == 'j' )&
729           &  timestep = ttt * dayseconde
730    IF ( type == 'months'.or.type == 'month'.or.type == 'mth'.or.type == 'mois'.or.type == 'm' .or.type == 'mo' ) THEN
731       WRITE(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref,mth_len
732       timestep = ttt * dayseconde * mth_len
733    ENDIF
734    IF ( type == 'hours'.or.type == 'hour'.or.type == 'hr'.or.type == 'heures'.or.type == 'heure'.or.type =='h' )&
735           &  timestep = ttt * dayseconde / 24.
736    IF ( type == 'mn'.or.type == 'minutes'.or.type == 'minute'.or.type == 'm' ) timestep = ttt * 60.
737    IF ( type == 's'.or.type == 'sec'.or.type == 'secondes'.or.type =='seconde'   ) timestep = ttt
738    IF ( type == 'TS' .or. type == 'ts' ) timestep = ttt * dtime
739
740    WRITE(lunout,*)'type =      ',type
741    WRITE(lunout,*)'nb j/h/m =  ',ttt
742    WRITE(lunout,*)'timestep(s)=',timestep
743
744  END SUBROUTINE convers_timesteps
745
746END MODULE phys_output_mod
Note: See TracBrowser for help on using the repository browser.