source: LMDZ5/trunk/libf/phylmd/phys_output_mod.F90 @ 1822

Last change on this file since 1822 was 1821, checked in by Ehouarn Millour, 11 years ago

Le passage de définition est maintenant effectué automatiquement lors du premier appel d'écriture à phys_output_write.
UG
.................................................
The definition run is now automatically triggered by the first writing call to phys_output_write.
UG

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 18.9 KB
RevLine 
[1279]1! $Id: phys_output_mod.F90 1821 2013-07-30 12:46:15Z emillour $
2!
[1813]3
4MODULE phys_output_mod
5  USE indice_sol_mod
6  USE phys_output_var_mod
7  USE aero_mod, only : naero_spc,name_aero
8  USE phys_output_write_mod, ONLY : phys_output_write
9
[907]10! Abderrahmane 12 2007
11!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
12!!! Ecreture des Sorties du modele dans les fichiers Netcdf :
13! histmth.nc : moyennes mensuelles
14! histday.nc : moyennes journalieres
15! histhf.nc  : moyennes toutes les 3 heures
16! histins.nc : valeurs instantanees
17!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
18
[1562]19CONTAINS
[907]20
21!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
22!!!!!!!!! Ouverture des fichier et definition des variable de sortie !!!!!!!!
[1562]23  !! histbeg, histvert et histdef
[907]24!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[1562]25
[1539]26  SUBROUTINE phys_output_open(rlon,rlat,pim,tabij,ipt,jpt,plon,plat, &
27       jjmp1,nlevSTD,clevSTD,nbteta, &
28       ctetaSTD, dtime, ok_veget, &
[1279]29       type_ocean, iflag_pbl,ok_mensuel,ok_journe, &
30       ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, read_climoz, &
[1539]31       phys_out_filestations, &
[1807]32       new_aod, aerosol_couple, flag_aerosol_strat, &
33       pdtphys, paprs, pphis, pplay, lmax_th, ptconv, ptconvth, ivap, &
34       d_t, qx, d_qx, zmasse, ok_sync)   
[907]35
[1562]36    USE iophy
37    USE dimphy
38    USE infotrac
39    USE ioipsl
[1742]40    USE phys_cal_mod, only : hour
[1562]41    USE mod_phys_lmdz_para
42    USE aero_mod, only : naero_spc,name_aero
[1807]43    USE phys_output_ctrlout_mod
[907]44
[1562]45    IMPLICIT NONE
46    include "dimensions.h"
47    include "temps.h"
48    include "clesphys.h"
49    include "thermcell.h"
50    include "comvert.h"
[1575]51    include "iniprint.h"
[907]52
[1807]53    ! ug Nouveaux arguments nécessaires au histwrite_mod:
54    INTEGER, INTENT(IN)                         :: ivap
55    INTEGER, DIMENSION(klon), INTENT(IN)        :: lmax_th
56    LOGICAL, INTENT(IN)                         :: ok_sync
57    LOGICAL, DIMENSION(klon, klev), INTENT(IN)  :: ptconv, ptconvth
58    REAL, INTENT(IN)                            :: pdtphys
59    REAL, DIMENSION(klon), INTENT(IN)           :: pphis
60    REAL, DIMENSION(klon, klev), INTENT(IN)     :: pplay, d_t
61    REAL, DIMENSION(klon, klev+1), INTENT(IN)   :: paprs
62    REAL, DIMENSION(klon,klev,nqtot), INTENT(IN):: qx, d_qx
63    REAL, DIMENSION(klon, llm), INTENT(IN)      :: zmasse
64
65
66    REAL,DIMENSION(klon),INTENT(IN) :: rlon
67    REAL,DIMENSION(klon),INTENT(IN) :: rlat
68    INTEGER, INTENT(IN)             :: pim
[1539]69    INTEGER, DIMENSION(pim)            :: tabij
[1807]70    INTEGER,DIMENSION(pim), INTENT(IN) :: ipt, jpt
71    REAL,DIMENSION(pim), INTENT(IN) :: plat, plon
72    REAL,DIMENSION(pim,2) :: plat_bounds, plon_bounds
[1539]73
[1791]74    INTEGER                               :: jjmp1
75    INTEGER                               :: nbteta, nlevSTD, radpas
76    LOGICAL                               :: ok_mensuel, ok_journe, ok_hf, ok_instan
77    LOGICAL                               :: ok_LES,ok_ade,ok_aie,flag_aerosol_strat
78    LOGICAL                               :: new_aod, aerosol_couple
[1807]79    INTEGER, INTENT(IN)::  read_climoz ! read ozone climatology
[1562]80    !     Allowed values are 0, 1 and 2
81    !     0: do not read an ozone climatology
82    !     1: read a single ozone climatology that will be used day and night
83    !     2: read two ozone climatologies, the average day and night
84    !     climatology and the daylight climatology
[1279]85
[1791]86    REAL                                  :: dtime
87    INTEGER                               :: idayref
88    REAL                                  :: zjulian
89    REAL, DIMENSION(klev)                 :: Ahyb, Bhyb, Alt
90    CHARACTER(LEN=4), DIMENSION(nlevSTD)  :: clevSTD
91    INTEGER                               :: nsrf, k, iq, iiq, iff, i, j, ilev
92    INTEGER                               :: naero
93    LOGICAL                               :: ok_veget
94    INTEGER                               :: iflag_pbl
95    CHARACTER(LEN=4)                      :: bb2
96    CHARACTER(LEN=2)                      :: bb3
97    CHARACTER(LEN=6)                      :: type_ocean
98    CHARACTER(LEN=3)                      :: ctetaSTD(nbteta)
99    REAL, DIMENSION(nfiles)               :: ecrit_files
100    CHARACTER(LEN=20), DIMENSION(nfiles)  :: phys_out_filenames
101    INTEGER, DIMENSION(iim*jjmp1)         ::  ndex2d
102    INTEGER, DIMENSION(iim*jjmp1*klev)    :: ndex3d
103    INTEGER                               :: imin_ins, imax_ins
104    INTEGER                               :: jmin_ins, jmax_ins
105    INTEGER, DIMENSION(nfiles)            :: phys_out_levmin, phys_out_levmax
106    INTEGER, DIMENSION(nfiles)            :: phys_out_filelevels
107    CHARACTER(LEN=20), DIMENSION(nfiles)  :: chtimestep   = (/ 'DefFreq', 'DefFreq','DefFreq', 'DefFreq', 'DefFreq', 'DefFreq' /)
108    LOGICAL, DIMENSION(nfiles)            :: phys_out_filekeys
109    LOGICAL, DIMENSION(nfiles)            :: phys_out_filestations
[907]110
[1065]111!!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[1562]112    !                 entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax]
[1054]113
[1791]114    LOGICAL, DIMENSION(nfiles), SAVE  :: phys_out_regfkey       = (/ .FALSE., .FALSE., .FALSE.,  .FALSE., .FALSE., .FALSE. /)
115    REAL, DIMENSION(nfiles), SAVE     :: phys_out_lonmin        = (/   -180.,   -180.,   -180.,    -180.,   -180.,   -180. /)
116    REAL, DIMENSION(nfiles), SAVE     :: phys_out_lonmax        = (/    180.,    180.,    180.,     180.,    180.,    180. /)
117    REAL, DIMENSION(nfiles), SAVE     :: phys_out_latmin        = (/    -90.,    -90.,    -90.,     -90.,    -90.,    -90. /)
118    REAL, DIMENSION(nfiles), SAVE     :: phys_out_latmax        = (/     90.,     90.,     90.,     90.,     90.,     90. /)
[1065]119
[1791]120    WRITE(lunout,*) 'Debut phys_output_mod.F90'
[1562]121    ! Initialisations (Valeurs par defaut
[1403]122
[1791]123    IF (.NOT. ALLOCATED(o_trac)) ALLOCATE(o_trac(nqtot))
124    IF (.NOT. ALLOCATED(o_trac_cum)) ALLOCATE(o_trac_cum(nqtot))
[1813]125    ALLOCATE(o_dtr_the(nqtot),o_dtr_con(nqtot),o_dtr_lessi_impa(nqtot))
126    ALLOCATE(o_dtr_lessi_nucl(nqtot),o_dtr_insc(nqtot),o_dtr_bcscav(nqtot))
127    ALLOCATE(o_dtr_evapls(nqtot),o_dtr_ls(nqtot),o_dtr_trsp(nqtot))
128    ALLOCATE(o_dtr_sscav(nqtot),o_dtr_sat(nqtot),o_dtr_uscav(nqtot))
129    ALLOCATE(o_dtr_dry(nqtot),o_dtr_vdf(nqtot))
[1403]130
[1813]131
[1562]132    levmax = (/ klev, klev, klev, klev, klev, klev /)
[1065]133
[1562]134    phys_out_filenames(1) = 'histmth'
135    phys_out_filenames(2) = 'histday'
136    phys_out_filenames(3) = 'histhf'
137    phys_out_filenames(4) = 'histins'
138    phys_out_filenames(5) = 'histLES'
139    phys_out_filenames(6) = 'histstn'
[907]140
[1562]141    type_ecri(1) = 'ave(X)'
142    type_ecri(2) = 'ave(X)'
143    type_ecri(3) = 'ave(X)'
144    type_ecri(4) = 'inst(X)'
145    type_ecri(5) = 'ave(X)'
146    type_ecri(6) = 'inst(X)'
[907]147
[1562]148    clef_files(1) = ok_mensuel
149    clef_files(2) = ok_journe
150    clef_files(3) = ok_hf
151    clef_files(4) = ok_instan
152    clef_files(5) = ok_LES
153    clef_files(6) = ok_instan
[907]154
[1562]155    !sortir des fichiers "stations" si clef_stations(:)=.TRUE.
156    clef_stations(1) = .FALSE.
157    clef_stations(2) = .FALSE.
158    clef_stations(3) = .FALSE.
159    clef_stations(4) = .FALSE.
160    clef_stations(5) = .FALSE.
161    clef_stations(6) = .FALSE.
[1539]162
[1562]163    lev_files(1) = lev_histmth
164    lev_files(2) = lev_histday
165    lev_files(3) = lev_histhf
166    lev_files(4) = lev_histins
167    lev_files(5) = lev_histLES
168    lev_files(6) = lev_histins
[907]169
[1562]170    ecrit_files(1) = ecrit_mth
171    ecrit_files(2) = ecrit_day
172    ecrit_files(3) = ecrit_hf
173    ecrit_files(4) = ecrit_ins
174    ecrit_files(5) = ecrit_LES
175    ecrit_files(6) = ecrit_ins
[1279]176
[1562]177    !! Lectures des parametres de sorties dans physiq.def
[1279]178
[1791]179    CALL getin('phys_out_regfkey',phys_out_regfkey)
180    CALL getin('phys_out_lonmin',phys_out_lonmin)
181    CALL getin('phys_out_lonmax',phys_out_lonmax)
182    CALL getin('phys_out_latmin',phys_out_latmin)
183    CALL getin('phys_out_latmax',phys_out_latmax)
[1562]184    phys_out_levmin(:)=levmin(:)
[1791]185    CALL getin('phys_out_levmin',levmin)
[1562]186    phys_out_levmax(:)=levmax(:)
[1791]187    CALL getin('phys_out_levmax',levmax)
188    CALL getin('phys_out_filenames',phys_out_filenames)
[1562]189    phys_out_filekeys(:)=clef_files(:)
[1791]190    CALL getin('phys_out_filekeys',clef_files)
[1562]191    phys_out_filestations(:)=clef_stations(:)
[1791]192    CALL getin('phys_out_filestations',clef_stations)
[1562]193    phys_out_filelevels(:)=lev_files(:)
[1791]194    CALL getin('phys_out_filelevels',lev_files)
195    CALL getin('phys_out_filetimesteps',chtimestep)
[1562]196    phys_out_filetypes(:)=type_ecri(:)
[1791]197    CALL getin('phys_out_filetypes',type_ecri)
[1279]198
[1562]199    type_ecri_files(:)=type_ecri(:)
[1279]200
[1791]201    WRITE(lunout,*)'phys_out_lonmin=',phys_out_lonmin
202    WRITE(lunout,*)'phys_out_lonmax=',phys_out_lonmax
203    WRITE(lunout,*)'phys_out_latmin=',phys_out_latmin
204    WRITE(lunout,*)'phys_out_latmax=',phys_out_latmax
205    WRITE(lunout,*)'phys_out_filenames=',phys_out_filenames
206    WRITE(lunout,*)'phys_out_filetypes=',type_ecri
207    WRITE(lunout,*)'phys_out_filekeys=',clef_files
208    WRITE(lunout,*)'phys_out_filestations=',clef_stations
209    WRITE(lunout,*)'phys_out_filelevels=',lev_files
[1562]210
[907]211!!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[1562]212    ! Appel de histbeg et histvert pour creer le fichier et les niveaux verticaux !!
213    ! Appel des histbeg pour definir les variables (nom, moy ou inst, freq de sortie ..
[907]214!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
215
[1807]216    zdtime_moy = dtime         ! Frequence ou l on moyenne
[1279]217
[1562]218    ! Calcul des Ahyb, Bhyb et Alt
[1791]219    DO k=1,klev
[1562]220       Ahyb(k)=(ap(k)+ap(k+1))/2.
221       Bhyb(k)=(bp(k)+bp(k+1))/2.
222       Alt(k)=log(preff/presnivs(k))*8.
[1791]223    ENDDO
[1562]224    !          if(prt_level.ge.1) then
[1791]225    WRITE(lunout,*)'Ap Hybrid = ',Ahyb(1:klev)
226    WRITE(lunout,*)'Bp Hybrid = ',Bhyb(1:klev)
227    WRITE(lunout,*)'Alt approx des couches pour une haut d echelle de 8km = ',Alt(1:klev)
[1562]228    !          endif
229    DO iff=1,nfiles
[929]230
[1641]231       ! Calculate ecrit_files for all files
[1791]232       IF ( chtimestep(iff).eq.'DefFreq' ) then
[1641]233          ! Par defaut ecrit_files = (ecrit_mensuel ecrit_jour ecrit_hf ...)*86400.
234          ecrit_files(iff)=ecrit_files(iff)*86400.
[1791]235       ELSE
236          CALL convers_timesteps(chtimestep(iff),dtime,ecrit_files(iff))
237       ENDIF
238       WRITE(lunout,*)'ecrit_files(',iff,')= ',ecrit_files(iff)
[907]239
[1641]240       zoutm(iff) = ecrit_files(iff) ! Frequence ou l on ecrit en seconde
[1279]241
[1641]242       IF (clef_files(iff)) THEN
[1279]243
[1562]244          idayref = day_ref
[1742]245!          CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)       
[1638]246! correction pour l heure initiale                               !jyg
247!                                                                !jyg
[1742]248          CALL ymds2ju(annee_ref, 1, idayref, hour, zjulian)         !jyg
249! correction pour l heure initiale                               !jyg
250!                                                                !jyg
251!!!      CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)       !jyg
252! correction pour l heure initiale                               !jyg
253!                                                                !jyg
[1638]254!      CALL ymds2ju(annee_ref, 1, idayref, hour, zjulian)         !jyg
[907]255
256!!!!!!!!!!!!!!!!! Traitement dans le cas ou l'on veut stocker sur un domaine limite !!
257!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[1791]258          IF (phys_out_regfkey(iff)) then
[907]259
[1562]260             imin_ins=1
261             imax_ins=iim
262             jmin_ins=1
263             jmax_ins=jjmp1
[907]264
[1562]265             ! correction abderr       
266             do i=1,iim
[1791]267                WRITE(lunout,*)'io_lon(i)=',io_lon(i)
268                IF (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
269                IF (io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1
[1562]270             enddo
[907]271
[1562]272             do j=1,jjmp1
[1791]273                WRITE(lunout,*)'io_lat(j)=',io_lat(j)
274                IF (io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1
275                IF (io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j
[1562]276             enddo
[907]277
[1791]278             WRITE(lunout,*)'On stoke le fichier histoire numero ',iff,' sur ', &
[1562]279                  imin_ins,imax_ins,jmin_ins,jmax_ins
[1791]280             WRITE(lunout,*)'longitudes : ', &
[1562]281                  io_lon(imin_ins),io_lon(imax_ins), &
282                  'latitudes : ', &
283                  io_lat(jmax_ins),io_lat(jmin_ins)
[907]284
[1562]285             CALL histbeg(phys_out_filenames(iff),iim,io_lon,jjmp1,io_lat, &
286                  imin_ins,imax_ins-imin_ins+1, &
287                  jmin_ins,jmax_ins-jmin_ins+1, &
288                  itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
[907]289!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[1562]290             !IM fichiers stations
[1791]291          else IF (clef_stations(iff)) THEN
[1539]292
[1791]293             WRITE(lunout,*)'phys_output_mod phys_out_filenames=',phys_out_filenames(iff)
[1539]294
[1791]295             CALL histbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, &
[1562]296                  phys_out_filenames(iff), &
297                  itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
298          else
299             CALL histbeg_phy(phys_out_filenames(iff),itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
300          endif
[907]301
[1562]302          CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "Pa", &
303               levmax(iff) - levmin(iff) + 1, &
304               presnivs(levmin(iff):levmax(iff)), nvertm(iff),"down")
305
[907]306!!!!!!!!!!!!! Traitement des champs 3D pour histhf !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
307!!!!!!!!!!!!!!! A Revoir plus tard !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[1562]308          !          IF (iff.eq.3.and.lev_files(iff).ge.4) THEN
309          !          CALL histbeg_phy("histhf3d",itau_phy, &
310          !     &                     zjulian, dtime, &
311          !     &                     nhorim, nid_hf3d)
[907]312
[1562]313          !         CALL histvert(nid_hf3d, "presnivs", &
314          !     &                 "Vertical levels", "mb", &
315          !     &                 klev, presnivs/100., nvertm)
316          !          ENDIF
317          !
[1807]318!!!! Composantes de la coordonnee sigma-hybride
[1562]319          CALL histvert(nid_files(iff), "Ahyb","Ahyb comp of Hyb Cord ", "Pa", &
320               levmax(iff) - levmin(iff) + 1,Ahyb,nvertap(iff))
[907]321
[1562]322          CALL histvert(nid_files(iff), "Bhyb","Bhyb comp of Hyb Cord", " ", &
323               levmax(iff) - levmin(iff) + 1,Bhyb,nvertbp(iff))
[1279]324
[1562]325          CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", &
326               levmax(iff) - levmin(iff) + 1,Alt,nvertAlt(iff))
[1279]327
[1562]328          !   CALL histvert(nid_files(iff), "preff","Reference pressure", "Pa", &
329          !                 1,preff,nvertp0(iff))
[1036]330
[907]331
[1791]332      IF (nqtot>=3) THEN
333            DO iq=3,nqtot 
334            iiq=niadv(iq)
335            o_trac(iq-2) = ctrl_out((/ 4, 5, 1, 1, 1, 10 /),tname(iiq),'Tracer '//ttext(iiq), "-",&
336                  (/ '', '', '', '', '', '' /))
[1813]337
338            o_dtr_vdf(iq-2) = ctrl_out((/ 5, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_vdf' &
339               ,'Tendance tracer '//ttext(iiq), "-" , (/ '', '', '', '', '', '' /))
340
341            o_dtr_the(iq-2) = ctrl_out((/ 5, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_the' &
342               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
343
344            o_dtr_con(iq-2) = ctrl_out((/ 5, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_con' &
345               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
346
347            o_dtr_lessi_impa(iq-2) = ctrl_out((/ 7, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_lessi_impa' &
348               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
349
350            o_dtr_lessi_nucl(iq-2) = ctrl_out((/ 7, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_lessi_nucl' &
351               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
352
353            o_dtr_insc(iq-2) = ctrl_out((/ 7, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_insc' &
354               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
355
356            o_dtr_bcscav(iq-2) = ctrl_out((/ 7, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_bcscav' &
357               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
358
359            o_dtr_evapls(iq-2) = ctrl_out((/ 7, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_evapls' &
360               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
361
362            o_dtr_ls(iq-2) = ctrl_out((/ 7, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_ls' &
363               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
364
365            o_dtr_trsp(iq-2) = ctrl_out((/ 7, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_trsp' &
366               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
367
368            o_dtr_sscav(iq-2) = ctrl_out((/ 7, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_sscav' &
369               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
370
371            o_dtr_sat(iq-2) = ctrl_out((/ 7, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_sat' &
372               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
373
374            o_dtr_uscav(iq-2) = ctrl_out((/ 7, 7, 7, 7, 10, 10 /),'d'//trim(tname(iq))//'_uscav' &
375               ,'Tendance tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
376
377            o_dtr_dry(iq-2) = ctrl_out((/ 7, 7, 7, 7, 10, 10 /),'cum'//'d'//trim(tname(iq))//'_dry' &
378               ,'tracer tendency dry deposition'//ttext(iiq), "-", (/ '', '', '', '', '', '' /) )
379
[1791]380            o_trac_cum(iq-2) = ctrl_out((/ 3, 4, 10, 10, 10, 10 /),'cum'//tname(iiq),&
381                  'Cumulated tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /))
382            ENDDO
383      ENDIF
[1539]384
[1807]385    ENDIF ! clef_files
[1539]386
[1807]387    ENDDO !  iff
[1539]388
[1807]389
[1641]390    ! Updated write frequencies due to phys_out_filetimesteps.
391    ! Write frequencies are now in seconds. 
392    ecrit_mth = ecrit_files(1)
393    ecrit_day = ecrit_files(2)
394    ecrit_hf  = ecrit_files(3)
395    ecrit_ins = ecrit_files(4)
396    ecrit_LES = ecrit_files(5)
397    ecrit_ins = ecrit_files(6)
398
[1791]399    WRITE(lunout,*)'swaero_diag=',swaero_diag
400    WRITE(lunout,*)'Fin phys_output_mod.F90'
401  end SUBROUTINE phys_output_open
[907]402
403
404
[1562]405  SUBROUTINE convers_timesteps(str,dtime,timestep)
[1279]406
[1562]407    use ioipsl
408    USE phys_cal_mod
[1279]409
[1562]410    IMPLICIT NONE
[1279]411
[1791]412    CHARACTER(LEN=20)   :: str
413    CHARACTER(LEN=10)   :: type
414    INTEGER             :: ipos,il
[1562]415    real                :: ttt,xxx,timestep,dayseconde,dtime
416    parameter (dayseconde=86400.)
417    include "temps.h"
418    include "comconst.h"
[1575]419    include "iniprint.h"
[1279]420
[1791]421    ipos=scan(str,'0123456789.',.TRUE.)
[1562]422    ! 
423    il=len_trim(str)
[1791]424    WRITE(lunout,*)ipos,il
[1562]425    read(str(1:ipos),*) ttt
[1791]426    WRITE(lunout,*)ttt
[1562]427    type=str(ipos+1:il)
[1279]428
429
[1791]430    IF ( il == ipos ) then
[1562]431       type='day'
432    endif
[1279]433
[1791]434    IF ( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde
435    IF ( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) then
436       WRITE(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref,mth_len
[1562]437       timestep = ttt * dayseconde * mth_len
438    endif
[1791]439    IF ( type == 'hours'.or.type == 'hr'.or.type == 'heurs') timestep = ttt * dayseconde / 24.
440    IF ( type == 'mn'.or.type == 'minutes'  ) timestep = ttt * 60.
441    IF ( type == 's'.or.type == 'sec'.or.type == 'secondes'   ) timestep = ttt
442    IF ( type == 'TS' ) timestep = ttt * dtime
[1279]443
[1791]444    WRITE(lunout,*)'type =      ',type
445    WRITE(lunout,*)'nb j/h/m =  ',ttt
446    WRITE(lunout,*)'timestep(s)=',timestep
[1279]447
[1562]448  END SUBROUTINE convers_timesteps
[1279]449
[907]450END MODULE phys_output_mod
451
Note: See TracBrowser for help on using the repository browser.