GCC Code Coverage Report


Directory: ./
File: phys/phys_output_mod.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 178 215 82.8%
Branches: 172 274 62.8%

Line Branch Exec Source
1 ! $Id: phys_output_mod.F90 3792 2021-01-04 17:01:25Z evignon $
2 !
3
4 MODULE 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 REAL, DIMENSION(nfiles),SAVE :: ecrit_files
9
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
19 CONTAINS
20
21 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
22 !!!!!!!!! Ouverture des fichier et definition des variable de sortie !!!!!!!!
23 !! histbeg, histvert et histdef
24 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
25
26 1 SUBROUTINE phys_output_open(rlon,rlat,pim,tabij,ipt,jpt,plon,plat, &
27 jjmp1,nlevSTD,clevSTD,rlevSTD, dtime, ok_veget, &
28 type_ocean, iflag_pbl,iflag_pbl_split,ok_mensuel,ok_journe, &
29 ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, read_climoz, &
30 phys_out_filestations, &
31 aerosol_couple, flag_aerosol_strat, &
32 pdtphys, paprs, pphis, pplay, lmax_th, ptconv, ptconvth, ivap, &
33 d_u, d_t, qx, d_qx, zmasse, ok_sync)
34
35 USE iophy
36 USE dimphy
37 USE infotrac_phy, ONLY: nqtot, nqo, niadv, tname, ttext, type_trac
38 USE ioipsl
39 USE phys_cal_mod, only : hour, calend
40 USE mod_phys_lmdz_para
41 !Martin
42 USE surface_data, ONLY : landice_opt
43 USE phys_output_ctrlout_mod
44 USE mod_grid_phy_lmdz, only: klon_glo,nbp_lon,nbp_lat
45 USE print_control_mod, ONLY: prt_level,lunout
46 USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs, aps, bps, pseudoalt
47 USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref
48
49 IMPLICIT NONE
50 include "clesphys.h"
51 include "thermcell.h"
52 include "YOMCST.h"
53
54 ! ug Nouveaux arguments n\'ecessaires au histwrite_mod:
55 INTEGER, INTENT(IN) :: ivap
56 INTEGER, DIMENSION(klon), INTENT(IN) :: lmax_th
57 LOGICAL, INTENT(IN) :: ok_sync
58 LOGICAL, DIMENSION(klon, klev), INTENT(IN) :: ptconv, ptconvth
59 REAL, INTENT(IN) :: pdtphys
60 REAL, DIMENSION(klon), INTENT(IN) :: pphis
61 REAL, DIMENSION(klon, klev), INTENT(IN) :: pplay, d_u, d_t
62 REAL, DIMENSION(klon, klev+1), INTENT(IN) :: paprs
63 REAL, DIMENSION(klon,klev,nqtot), INTENT(IN):: qx, d_qx
64 REAL, DIMENSION(klon, klev), INTENT(IN) :: zmasse
65
66
67 REAL,DIMENSION(klon),INTENT(IN) :: rlon
68 REAL,DIMENSION(klon),INTENT(IN) :: rlat
69 INTEGER, INTENT(IN) :: pim
70 INTEGER, DIMENSION(pim) :: tabij
71 INTEGER,DIMENSION(pim), INTENT(IN) :: ipt, jpt
72 REAL,DIMENSION(pim), INTENT(IN) :: plat, plon
73 2 REAL,DIMENSION(pim,2) :: plat_bounds, plon_bounds
74
75 INTEGER :: jjmp1
76 INTEGER :: nlevSTD, radpas
77 LOGICAL :: ok_mensuel, ok_journe, ok_hf, ok_instan
78 LOGICAL :: ok_LES,ok_ade,ok_aie
79 INTEGER :: flag_aerosol_strat
80 LOGICAL :: aerosol_couple
81 INTEGER, INTENT(IN):: read_climoz ! read ozone climatology
82 ! Allowed values are 0, 1 and 2
83 ! 0: do not read an ozone climatology
84 ! 1: read a single ozone climatology that will be used day and night
85 ! 2: read two ozone climatologies, the average day and night
86 ! climatology and the daylight climatology
87
88 REAL :: dtime
89 INTEGER :: idayref
90 REAL :: zjulian_start, zjulian
91 CHARACTER(LEN=4), DIMENSION(nlevSTD) :: clevSTD
92 REAL, DIMENSION(nlevSTD) :: rlevSTD
93 INTEGER :: nsrf, k, iq, iiq, iff, i, j, ilev
94 INTEGER :: naero
95 LOGICAL :: ok_veget
96 INTEGER :: iflag_pbl
97 INTEGER :: iflag_pbl_split
98 CHARACTER(LEN=4) :: bb2
99 CHARACTER(LEN=2) :: bb3
100 CHARACTER(LEN=6) :: type_ocean
101 INTEGER, DIMENSION(nbp_lon*jjmp1) :: ndex2d
102 INTEGER, DIMENSION(nbp_lon*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 = (/ 'Default', 'Default', 'Default', 'Default', 'Default', &
108 'Default', 'Default', 'Default', 'Default', 'Default' /)
109 LOGICAL, DIMENSION(nfiles) :: phys_out_filekeys
110 LOGICAL, DIMENSION(nfiles) :: phys_out_filestations
111
112 !!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
113 ! entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax]
114
115 LOGICAL, DIMENSION(nfiles), SAVE :: phys_out_regfkey = (/ .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., &
116 .FALSE., .FALSE., .FALSE., .FALSE., .FALSE. /)
117 REAL, DIMENSION(nfiles), SAVE :: phys_out_lonmin = (/ -180., -180., -180., -180., -180., &
118 -180., -180., -180., -180., -180. /)
119 REAL, DIMENSION(nfiles), SAVE :: phys_out_lonmax = (/ 180., 180., 180., 180., 180., &
120 180., 180., 180., 180., 180. /)
121 REAL, DIMENSION(nfiles), SAVE :: phys_out_latmin = (/ -90., -90., -90., -90., -90., &
122 -90., -90., -90., -90., -90. /)
123 REAL, DIMENSION(nfiles), SAVE :: phys_out_latmax = (/ 90., 90., 90., 90., 90., &
124 90., 90., 90., 90., 90. /)
125 2 REAL, DIMENSION(klev,2) :: Ahyb_bounds, Bhyb_bounds
126 2 REAL, DIMENSION(klev+1) :: lev_index
127
128 INTEGER :: ISW
129 REAL, DIMENSION(NSW) :: wl1_sun, wl2_sun !wavelength bounds (in um) for SW
130 REAL, DIMENSION(NSW) :: wn1_sun, wn2_sun !wavenumber bounds (in m-1) for SW
131 REAL, DIMENSION(NSW) :: spectband !mean wavenumb. of each sp.band
132 REAL, DIMENSION(NSW,2) :: spbnds_sun !bounds of spectband
133
134 1 WRITE(lunout,*) 'Debut phys_output_mod.F90'
135 ! Initialisations (Valeurs par defaut
136
137
2/2
✓ Branch 0 taken 39 times.
✓ Branch 1 taken 1 times.
40 DO ilev=1,klev
138 39 Ahyb_bounds(ilev,1) = ap(ilev)
139 39 Ahyb_bounds(ilev,2) = ap(ilev+1)
140 39 Bhyb_bounds(ilev,1) = bp(ilev)
141 39 Bhyb_bounds(ilev,2) = bp(ilev+1)
142 40 lev_index(ilev) = REAL(ilev)
143 END DO
144 1 lev_index(klev+1) = REAL(klev+1)
145
146
3/6
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 1 times.
1 IF (.NOT. ALLOCATED(o_trac)) ALLOCATE(o_trac(nqtot))
147
3/6
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 1 times.
1 IF (.NOT. ALLOCATED(o_trac_cum)) ALLOCATE(o_trac_cum(nqtot))
148
7/14
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 1 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 1 times.
1 ALLOCATE(o_dtr_the(nqtot),o_dtr_con(nqtot),o_dtr_lessi_impa(nqtot))
149
6/12
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 1 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 1 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 1 times.
1 ALLOCATE(o_dtr_lessi_nucl(nqtot),o_dtr_insc(nqtot),o_dtr_bcscav(nqtot))
150
6/12
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 1 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 1 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 1 times.
1 ALLOCATE(o_dtr_evapls(nqtot),o_dtr_ls(nqtot),o_dtr_trsp(nqtot))
151
6/12
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 1 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 1 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 1 times.
1 ALLOCATE(o_dtr_sscav(nqtot),o_dtr_sat(nqtot),o_dtr_uscav(nqtot))
152
4/8
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 1 times.
1 ALLOCATE(o_dtr_dry(nqtot),o_dtr_vdf(nqtot))
153
154
2/2
✓ Branch 0 taken 10 times.
✓ Branch 1 taken 1 times.
11 levmax = (/ klev, klev, klev, klev, klev, klev, nlevSTD, nlevSTD, nlevSTD, klev /)
155
156 1 phys_out_filenames(1) = 'histmth'
157 1 phys_out_filenames(2) = 'histday'
158 1 phys_out_filenames(3) = 'histhf6h'
159 1 phys_out_filenames(4) = 'histhf3h'
160 1 phys_out_filenames(5) = 'histhf3hm'
161 1 phys_out_filenames(6) = 'histstn'
162 1 phys_out_filenames(7) = 'histmthNMC'
163 1 phys_out_filenames(8) = 'histdayNMC'
164 1 phys_out_filenames(9) = 'histhfNMC'
165 1 phys_out_filenames(10)= 'histstrataer'
166
167 1 type_ecri(1) = 'ave(X)'
168 1 type_ecri(2) = 'ave(X)'
169 1 type_ecri(3) = 'inst(X)'
170 1 type_ecri(4) = 'inst(X)'
171 1 type_ecri(5) = 'ave(X)'
172 1 type_ecri(6) = 'inst(X)'
173 1 type_ecri(7) = 'inst(X)'
174 1 type_ecri(8) = 'inst(X)'
175 1 type_ecri(9) = 'inst(X)'
176 1 type_ecri(10)= 'ave(X)'
177
178 1 clef_files(1) = ok_mensuel
179 1 clef_files(2) = ok_journe
180 1 clef_files(3) = ok_hf
181 1 clef_files(4) = ok_instan
182 1 clef_files(5) = ok_LES
183 1 clef_files(6) = ok_instan
184 1 clef_files(7) = ok_histNMC(1)
185 1 clef_files(8) = ok_histNMC(2)
186 1 clef_files(9) = ok_histNMC(3)
187 1 clef_files(10)= .FALSE.
188
189 !sortir des fichiers "stations" si clef_stations(:)=.TRUE.
190 1 clef_stations(1) = .FALSE.
191 1 clef_stations(2) = .FALSE.
192 1 clef_stations(3) = .FALSE.
193 1 clef_stations(4) = .FALSE.
194 1 clef_stations(5) = .FALSE.
195 1 clef_stations(6) = .FALSE.
196 1 clef_stations(7) = .FALSE.
197 1 clef_stations(8) = .FALSE.
198 1 clef_stations(9) = .FALSE.
199 1 clef_stations(10)= .FALSE.
200
201 1 lev_files(1) = lev_histmth
202 1 lev_files(2) = lev_histday
203 1 lev_files(3) = lev_histhf
204 1 lev_files(4) = lev_histins
205 1 lev_files(5) = lev_histLES
206 1 lev_files(6) = lev_histins
207 1 lev_files(7) = levout_histNMC(1)
208 1 lev_files(8) = levout_histNMC(2)
209 1 lev_files(9) = levout_histNMC(3)
210 1 lev_files(10)= 5
211
212 1 ecrit_files(1) = ecrit_mth
213 1 ecrit_files(2) = ecrit_day
214 1 ecrit_files(3) = ecrit_hf
215 1 ecrit_files(4) = ecrit_ins
216 1 ecrit_files(5) = ecrit_LES
217 1 ecrit_files(6) = ecrit_ins
218 1 ecrit_files(7) = freq_outNMC(1)
219 1 ecrit_files(8) = freq_outNMC(2)
220 1 ecrit_files(9) = freq_outNMC(3)
221 1 ecrit_files(10)= ecrit_mth
222
223 !! Lectures des parametres de sorties dans physiq.def
224
225 1 CALL getin('phys_out_regfkey',phys_out_regfkey)
226 1 CALL getin('phys_out_lonmin',phys_out_lonmin)
227 1 CALL getin('phys_out_lonmax',phys_out_lonmax)
228 1 CALL getin('phys_out_latmin',phys_out_latmin)
229 1 CALL getin('phys_out_latmax',phys_out_latmax)
230 phys_out_levmin(:)=levmin(:)
231 1 CALL getin('phys_out_levmin',levmin)
232 phys_out_levmax(:)=levmax(:)
233 1 CALL getin('phys_out_levmax',levmax)
234 1 CALL getin('phys_out_filenames',phys_out_filenames)
235 phys_out_filekeys(:)=clef_files(:)
236 1 CALL getin('phys_out_filekeys',clef_files)
237 1 phys_out_filestations(:)=clef_stations(:)
238 1 CALL getin('phys_out_filestations',clef_stations)
239 phys_out_filelevels(:)=lev_files(:)
240 1 CALL getin('phys_out_filelevels',lev_files)
241 1 CALL getin('phys_out_filetimesteps',chtimestep)
242
2/2
✓ Branch 0 taken 10 times.
✓ Branch 1 taken 1 times.
11 phys_out_filetypes(:)=type_ecri(:)
243 1 CALL getin('phys_out_filetypes',type_ecri)
244
245
2/2
✓ Branch 0 taken 10 times.
✓ Branch 1 taken 1 times.
11 type_ecri_files(:)=type_ecri(:)
246
247 ! if (ok_all_xml) phys_out_filelevels = 999
248
249 1 WRITE(lunout,*)'phys_out_lonmin=',phys_out_lonmin
250 1 WRITE(lunout,*)'phys_out_lonmax=',phys_out_lonmax
251 1 WRITE(lunout,*)'phys_out_latmin=',phys_out_latmin
252 1 WRITE(lunout,*)'phys_out_latmax=',phys_out_latmax
253 1 WRITE(lunout,*)'phys_out_filenames=',phys_out_filenames
254 1 WRITE(lunout,*)'phys_out_filetypes=',type_ecri
255 1 WRITE(lunout,*)'phys_out_filekeys=',clef_files
256 1 WRITE(lunout,*)'phys_out_filestations=',clef_stations
257 1 WRITE(lunout,*)'phys_out_filelevels=',lev_files
258 1 WRITE(lunout,*)'phys_out_regfkey=',phys_out_regfkey
259
260 ! A noter pour
261 ! l heure initiale - dans les fichiers histoire hist* - on met comme
262 ! heure de debut soit la vraie heure (pour le 1D) soit 0h (pour le 3D)
263 ! afin d avoir une seule sortie mensuelle par mois lorsque l on tourne
264 ! par annee (IM).
265 !
266 1 idayref = day_ref
267
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (klon_glo==1) THEN
268 ! current_time (used to compute hour) is updated at the begining of
269 ! the physics; to set the correct outputs "initial time" we thus
270 ! have to use (hour-dtphys).
271 CALL ymds2ju(annee_ref, 1, idayref, hour-pdtphys, zjulian)
272 print *,'phys_output_mod: annee,iday,hour,zjulian=',annee_ref,idayref, hour, zjulian
273 ELSE
274 1 CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
275 1 CALL ymds2ju(annee_ref, 1, day_ini, start_time*rday, zjulian_start)
276 ENDIF
277
278
279 !!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
280 ! Appel de histbeg et histvert pour creer le fichier et les niveaux verticaux !!
281 ! Appel des histbeg pour definir les variables (nom, moy ou inst, freq de sortie ..
282 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
283
284 1 zdtime_moy = dtime ! Frequence ou l on moyenne
285
286
287 1 ecrit_files(7) = ecrit_files(1)
288 1 ecrit_files(8) = ecrit_files(2)
289 1 ecrit_files(9) = ecrit_files(3)
290
291
2/2
✓ Branch 0 taken 10 times.
✓ Branch 1 taken 1 times.
11 DO iff=1,nfiles
292
293 ! Calculate ecrit_files for all files
294
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 5 times.
10 IF ( chtimestep(iff).eq.'Default' ) THEN
295 ! Par defaut ecrit_files = (ecrit_mensuel ecrit_jour ecrit_hf
296 ! ...)*86400.
297 5 ecrit_files(iff)=ecrit_files(iff)*86400.
298
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
5 ELSE IF (chtimestep(iff).eq.'-1') THEN
299 PRINT*,'ecrit_files(',iff,') < 0 so IOIPSL work on different'
300 PRINT*,'months length'
301 ecrit_files(iff)=-1.
302 ELSE
303 5 CALL convers_timesteps(chtimestep(iff),dtime,ecrit_files(iff))
304 ENDIF
305
306 10 WRITE(lunout,*)'ecrit_files(',iff,')= ',ecrit_files(iff)
307 10 zoutm(iff) = ecrit_files(iff) ! Frequence ou l on ecrit en seconde
308
309
310
311
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 6 times.
10 IF (clef_files(iff)) THEN
312 !!!!!!!!!!!!!!!!! Traitement dans le cas ou l'on veut stocker sur un domaine limite !!
313 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
314
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
4 IF (phys_out_regfkey(iff)) THEN
315 imin_ins=1
316 imax_ins=nbp_lon
317 jmin_ins=1
318 jmax_ins=jjmp1
319
320 ! correction abderr
321 DO i=1,nbp_lon
322 WRITE(lunout,*)'io_lon(i)=',io_lon(i)
323 IF (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
324 IF (io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1
325 ENDDO
326
327 DO j=1,jjmp1
328 WRITE(lunout,*)'io_lat(j)=',io_lat(j)
329 IF (io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1
330 IF (io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j
331 ENDDO
332
333 WRITE(lunout,*)'On stoke le fichier histoire numero ',iff,' sur ', &
334 imin_ins,imax_ins,jmin_ins,jmax_ins
335 WRITE(lunout,*)'longitudes : ', &
336 io_lon(imin_ins),io_lon(imax_ins), &
337 'latitudes : ', &
338 io_lat(jmax_ins),io_lat(jmin_ins)
339
340 CALL histbeg(phys_out_filenames(iff),nbp_lon,io_lon,jjmp1,io_lat, &
341 imin_ins,imax_ins-imin_ins+1, &
342 jmin_ins,jmax_ins-jmin_ins+1, &
343 itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
344 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
345 !IM fichiers stations
346
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
4 ELSE IF (clef_stations(iff)) THEN
347
348 IF (prt_level >= 10) THEN
349 WRITE(lunout,*)'phys_output_open: iff=',iff,' phys_out_filenames(iff)=',phys_out_filenames(iff)
350 ENDIF
351
352 CALL histbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, &
353 phys_out_filenames(iff), &
354 itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
355 ELSE
356
357
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
4 IF (prt_level >= 10) THEN
358 WRITE(lunout,*)'phys_output_open: iff=',iff,' phys_out_filenames(iff)=',phys_out_filenames(iff)
359 ENDIF
360
361 CALL histbeg_phy_all(phys_out_filenames(iff),itau_phy,zjulian,&
362 4 dtime,nhorim(iff),nid_files(iff))
363 ENDIF
364
365
1/2
✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
4 IF (iff.LE.6.OR.iff.EQ.10) THEN
366 CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "Pa", &
367 levmax(iff) - levmin(iff) + 1, &
368 4 presnivs(levmin(iff):levmax(iff)), nvertm(iff),"down")
369 !!!! Composantes de la coordonnee sigma-hybride
370 CALL histvert(nid_files(iff), "Ahyb","Ahyb comp of Hyb Cord ", "Pa", &
371 4 levmax(iff) - levmin(iff) + 1,aps,nvertap(iff))
372
373 CALL histvert(nid_files(iff), "Bhyb","Bhyb comp of Hyb Cord", " ", &
374 4 levmax(iff) - levmin(iff) + 1,bps,nvertbp(iff))
375
376 CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", &
377 4 levmax(iff) - levmin(iff) + 1,pseudoalt,nvertAlt(iff))
378
379 ELSE
380 ! NMC files
381 CALL histvert(nid_files(iff), "plev", "pressure", "Pa", &
382 levmax(iff) - levmin(iff) + 1, &
383 rlevSTD(levmin(iff):levmax(iff)), nvertm(iff), "down")
384 ENDIF
385
386 ENDIF ! clef_files
387
388
1/2
✓ Branch 0 taken 10 times.
✗ Branch 1 not taken.
11 IF (nqtot>=nqo+1) THEN
389 !
390
2/2
✓ Branch 0 taken 20 times.
✓ Branch 1 taken 10 times.
30 DO iq=nqo+1,nqtot
391 20 iiq=niadv(iq)
392 o_trac(iq-nqo) = ctrl_out((/ 1, 5, 5, 5, 10, 10, 11, 11, 11, 11 /), &
393 tname(iiq),'Tracer '//ttext(iiq), "-", &
394
4/4
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 3 taken 200 times.
✓ Branch 4 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
395 o_dtr_vdf(iq-nqo) = ctrl_out((/ 4, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
396 'd'//trim(tname(iq))//'_vdf', &
397 'Tendance tracer '//ttext(iiq), "-" , &
398
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
399
400 o_dtr_the(iq-nqo) = ctrl_out((/ 5, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
401 'd'//trim(tname(iq))//'_the', &
402 'Tendance tracer '//ttext(iiq), "-", &
403
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
404
405 o_dtr_con(iq-nqo) = ctrl_out((/ 5, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
406 'd'//trim(tname(iq))//'_con', &
407 'Tendance tracer '//ttext(iiq), "-", &
408
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
409
410 o_dtr_lessi_impa(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
411 'd'//trim(tname(iq))//'_lessi_impa', &
412 'Tendance tracer '//ttext(iiq), "-", &
413
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
414
415 o_dtr_lessi_nucl(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
416 'd'//trim(tname(iq))//'_lessi_nucl', &
417 'Tendance tracer '//ttext(iiq), "-", &
418
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
419
420 o_dtr_insc(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
421 'd'//trim(tname(iq))//'_insc', &
422 'Tendance tracer '//ttext(iiq), "-", &
423
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
424
425 o_dtr_bcscav(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
426 'd'//trim(tname(iq))//'_bcscav', &
427 'Tendance tracer '//ttext(iiq), "-", &
428
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
429
430 o_dtr_evapls(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
431 'd'//trim(tname(iq))//'_evapls', &
432 'Tendance tracer '//ttext(iiq), "-", &
433
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
434
435 o_dtr_ls(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
436 'd'//trim(tname(iq))//'_ls', &
437 'Tendance tracer '//ttext(iiq), "-", &
438
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
439
440 o_dtr_trsp(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
441 'd'//trim(tname(iq))//'_trsp', &
442 'Tendance tracer '//ttext(iiq), "-", &
443
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
444
445 o_dtr_sscav(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
446 'd'//trim(tname(iq))//'_sscav', &
447 'Tendance tracer '//ttext(iiq), "-", &
448
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
449
450 o_dtr_sat(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
451 'd'//trim(tname(iq))//'_sat', &
452 'Tendance tracer '//ttext(iiq), "-", &
453
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
454
455 o_dtr_uscav(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
456 'd'//trim(tname(iq))//'_uscav', &
457 'Tendance tracer '//ttext(iiq), "-", &
458
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
459
460 o_dtr_dry(iq-nqo) = ctrl_out((/ 7, 7, 7, 7, 10, 10, 11, 11, 11, 11 /), &
461 'cum'//'d'//trim(tname(iq))//'_dry', &
462 'tracer tendency dry deposition'//ttext(iiq), "-", &
463
6/8
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 20 times.
✗ Branch 5 not taken.
✓ Branch 7 taken 20 times.
✗ Branch 8 not taken.
✓ Branch 10 taken 200 times.
✓ Branch 11 taken 20 times.
420 (/ '', '', '', '', '', '', '', '', '', '' /))
464
465 o_trac_cum(iq-nqo) = ctrl_out((/ 1, 4, 10, 10, 10, 10, 11, 11, 11, 11 /), &
466 'cum'//tname(iiq),&
467 'Cumulated tracer '//ttext(iiq), "-", &
468
4/4
✓ Branch 0 taken 200 times.
✓ Branch 1 taken 20 times.
✓ Branch 4 taken 200 times.
✓ Branch 5 taken 20 times.
430 (/ '', '', '', '', '', '', '', '', '', '' /))
469 ENDDO
470 ENDIF
471
472 ENDDO ! iff
473
474 ! Updated write frequencies due to phys_out_filetimesteps.
475 ! Write frequencies are now in seconds.
476 1 ecrit_mth = ecrit_files(1)
477 1 ecrit_day = ecrit_files(2)
478 1 ecrit_hf = ecrit_files(3)
479 ecrit_ins = ecrit_files(4)
480 1 ecrit_LES = ecrit_files(5)
481 1 ecrit_ins = ecrit_files(6)
482
483
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (prt_level >= 10) THEN
484 WRITE(lunout,*)'swaerofree_diag=',swaerofree_diag
485 WRITE(lunout,*)'swaero_diag=',swaero_diag
486 WRITE(lunout,*)'dryaod_diag=',dryaod_diag
487 WRITE(lunout,*)'ok_4xCO2atm=',ok_4xCO2atm
488 WRITE(lunout,*)'phys_output_open: ends here'
489 ENDIF
490
491 1 END SUBROUTINE phys_output_open
492
493 5 SUBROUTINE convers_timesteps(str,dtime,timestep)
494
495 2 use ioipsl
496 USE phys_cal_mod
497 USE time_phylmdz_mod, ONLY: day_ref, annee_ref
498 USE print_control_mod, ONLY: lunout
499
500 IMPLICIT NONE
501
502 CHARACTER(LEN=20) :: str
503 CHARACTER(LEN=10) :: type
504 INTEGER :: ipos,il
505 real :: ttt,xxx,timestep,dayseconde,dtime
506 parameter (dayseconde=86400.)
507
508 5 ipos=scan(str,'0123456789.',.TRUE.)
509 !
510 5 il=len_trim(str)
511 5 WRITE(lunout,*) "ipos = ", ipos
512 5 WRITE(lunout,*) "il = ", il
513
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
5 IF (ipos == 0) CALL abort_physic("convers_timesteps", "bad str", 1)
514 5 read(str(1:ipos),*) ttt
515 5 WRITE(lunout,*)ttt
516
1/2
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
5 type=str(ipos+1:il)
517
518
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
5 IF ( il == ipos ) THEN
519 type='day'
520 ENDIF
521
522
5/8
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 2 times.
✓ Branch 2 taken 3 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 3 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 3 times.
5 IF ( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde
523
3/6
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 5 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 5 times.
5 IF ( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) THEN
524 WRITE(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref,mth_len
525 timestep = ttt * dayseconde * mth_len
526 ENDIF
527
4/6
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 2 times.
✓ Branch 3 taken 3 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2 times.
5 IF ( type == 'hours'.or.type == 'hr'.or.type == 'heurs') timestep = ttt * dayseconde / 24.
528
2/4
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
5 IF ( type == 'mn'.or.type == 'minutes' ) timestep = ttt * 60.
529
3/6
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 5 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 5 times.
5 IF ( type == 's'.or.type == 'sec'.or.type == 'secondes' ) timestep = ttt
530
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
5 IF ( type == 'TS' ) timestep = ttt * dtime
531
532 5 WRITE(lunout,*)'type = ',type
533 5 WRITE(lunout,*)'nb j/h/m = ',ttt
534 5 WRITE(lunout,*)'timestep(s)=',timestep
535
536 5 END SUBROUTINE convers_timesteps
537
538 END MODULE phys_output_mod
539