| 1 | ! $Id: phys_output_mod.F90 1795 2013-07-18 08:20:28Z emillour $ |
|---|
| 2 | ! |
|---|
| 3 | ! Abderrahmane 12 2007 |
|---|
| 4 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 5 | !!! Ecreture des Sorties du modele dans les fichiers Netcdf : |
|---|
| 6 | ! histmth.nc : moyennes mensuelles |
|---|
| 7 | ! histday.nc : moyennes journalieres |
|---|
| 8 | ! histhf.nc : moyennes toutes les 3 heures |
|---|
| 9 | ! histins.nc : valeurs instantanees |
|---|
| 10 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 11 | |
|---|
| 12 | MODULE phys_output_mod |
|---|
| 13 | USE indice_sol_mod |
|---|
| 14 | USE phys_output_var_mod |
|---|
| 15 | USE phys_output_ctrlout_mod |
|---|
| 16 | USE aero_mod, only : naero_spc,name_aero |
|---|
| 17 | |
|---|
| 18 | IMPLICIT NONE |
|---|
| 19 | |
|---|
| 20 | PRIVATE histdef2d, histdef3d, conf_physoutputs |
|---|
| 21 | |
|---|
| 22 | REAL, PRIVATE, SAVE :: zdtime |
|---|
| 23 | !$OMP THREADPRIVATE(zdtime) |
|---|
| 24 | |
|---|
| 25 | |
|---|
| 26 | |
|---|
| 27 | CONTAINS |
|---|
| 28 | |
|---|
| 29 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 30 | !!!!!!!!! Ouverture des fichier et definition des variable de sortie !!!!!!!! |
|---|
| 31 | !! histbeg, histvert et histdef |
|---|
| 32 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 33 | |
|---|
| 34 | SUBROUTINE phys_output_open(rlon,rlat,pim,tabij,ipt,jpt,plon,plat, & |
|---|
| 35 | jjmp1,nlevSTD,clevSTD,nbteta, & |
|---|
| 36 | ctetaSTD, dtime, ok_veget, & |
|---|
| 37 | type_ocean, iflag_pbl,ok_mensuel,ok_journe, & |
|---|
| 38 | ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, read_climoz, & |
|---|
| 39 | phys_out_filestations, & |
|---|
| 40 | new_aod, aerosol_couple, flag_aerosol_strat) |
|---|
| 41 | |
|---|
| 42 | USE iophy |
|---|
| 43 | USE dimphy |
|---|
| 44 | USE infotrac |
|---|
| 45 | USE ioipsl |
|---|
| 46 | USE phys_cal_mod, only : hour |
|---|
| 47 | USE mod_phys_lmdz_para |
|---|
| 48 | USE aero_mod, only : naero_spc,name_aero |
|---|
| 49 | |
|---|
| 50 | IMPLICIT NONE |
|---|
| 51 | include "dimensions.h" |
|---|
| 52 | include "temps.h" |
|---|
| 53 | include "clesphys.h" |
|---|
| 54 | include "thermcell.h" |
|---|
| 55 | include "comvert.h" |
|---|
| 56 | include "iniprint.h" |
|---|
| 57 | |
|---|
| 58 | real,dimension(klon),intent(in) :: rlon |
|---|
| 59 | real,dimension(klon),intent(in) :: rlat |
|---|
| 60 | INTEGER, intent(in) :: pim |
|---|
| 61 | INTEGER, DIMENSION(pim) :: tabij |
|---|
| 62 | INTEGER,dimension(pim), intent(in) :: ipt, jpt |
|---|
| 63 | REAL,dimension(pim), intent(in) :: plat, plon |
|---|
| 64 | REAL,dimension(pim,2) :: plat_bounds, plon_bounds |
|---|
| 65 | |
|---|
| 66 | INTEGER :: jjmp1 |
|---|
| 67 | INTEGER :: nbteta, nlevSTD, radpas |
|---|
| 68 | LOGICAL :: ok_mensuel, ok_journe, ok_hf, ok_instan |
|---|
| 69 | LOGICAL :: ok_LES,ok_ade,ok_aie,flag_aerosol_strat |
|---|
| 70 | LOGICAL :: new_aod, aerosol_couple |
|---|
| 71 | INTEGER, intent(in):: read_climoz ! read ozone climatology |
|---|
| 72 | ! Allowed values are 0, 1 and 2 |
|---|
| 73 | ! 0: do not read an ozone climatology |
|---|
| 74 | ! 1: read a single ozone climatology that will be used day and night |
|---|
| 75 | ! 2: read two ozone climatologies, the average day and night |
|---|
| 76 | ! climatology and the daylight climatology |
|---|
| 77 | |
|---|
| 78 | REAL :: dtime |
|---|
| 79 | INTEGER :: idayref |
|---|
| 80 | REAL :: zjulian |
|---|
| 81 | REAL, DIMENSION(klev) :: Ahyb, Bhyb, Alt |
|---|
| 82 | CHARACTER(LEN=4), DIMENSION(nlevSTD) :: clevSTD |
|---|
| 83 | INTEGER :: nsrf, k, iq, iiq, iff, i, j, ilev |
|---|
| 84 | INTEGER :: naero |
|---|
| 85 | LOGICAL :: ok_veget |
|---|
| 86 | INTEGER :: iflag_pbl |
|---|
| 87 | CHARACTER(LEN=4) :: bb2 |
|---|
| 88 | CHARACTER(LEN=2) :: bb3 |
|---|
| 89 | CHARACTER(LEN=6) :: type_ocean |
|---|
| 90 | CHARACTER(LEN=3) :: ctetaSTD(nbteta) |
|---|
| 91 | REAL, DIMENSION(nfiles) :: ecrit_files |
|---|
| 92 | CHARACTER(LEN=20), DIMENSION(nfiles) :: phys_out_filenames |
|---|
| 93 | INTEGER, DIMENSION(iim*jjmp1) :: ndex2d |
|---|
| 94 | INTEGER, DIMENSION(iim*jjmp1*klev) :: ndex3d |
|---|
| 95 | INTEGER :: imin_ins, imax_ins |
|---|
| 96 | INTEGER :: jmin_ins, jmax_ins |
|---|
| 97 | INTEGER, DIMENSION(nfiles) :: phys_out_levmin, phys_out_levmax |
|---|
| 98 | INTEGER, DIMENSION(nfiles) :: phys_out_filelevels |
|---|
| 99 | CHARACTER(LEN=20), DIMENSION(nfiles) :: chtimestep = (/ 'DefFreq', 'DefFreq','DefFreq', 'DefFreq', 'DefFreq', 'DefFreq' /) |
|---|
| 100 | LOGICAL, DIMENSION(nfiles) :: phys_out_filekeys |
|---|
| 101 | LOGICAL, DIMENSION(nfiles) :: phys_out_filestations |
|---|
| 102 | |
|---|
| 103 | !!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 104 | ! entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax] |
|---|
| 105 | |
|---|
| 106 | LOGICAL, DIMENSION(nfiles), SAVE :: phys_out_regfkey = (/ .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE. /) |
|---|
| 107 | REAL, DIMENSION(nfiles), SAVE :: phys_out_lonmin = (/ -180., -180., -180., -180., -180., -180. /) |
|---|
| 108 | REAL, DIMENSION(nfiles), SAVE :: phys_out_lonmax = (/ 180., 180., 180., 180., 180., 180. /) |
|---|
| 109 | REAL, DIMENSION(nfiles), SAVE :: phys_out_latmin = (/ -90., -90., -90., -90., -90., -90. /) |
|---|
| 110 | REAL, DIMENSION(nfiles), SAVE :: phys_out_latmax = (/ 90., 90., 90., 90., 90., 90. /) |
|---|
| 111 | |
|---|
| 112 | !Lluis |
|---|
| 113 | INTEGER ix,iy,lp,il,jl |
|---|
| 114 | |
|---|
| 115 | WRITE(lunout,*) 'Debut phys_output_mod.F90' |
|---|
| 116 | ! Initialisations (Valeurs par defaut |
|---|
| 117 | |
|---|
| 118 | IF (.NOT. ALLOCATED(o_trac)) ALLOCATE(o_trac(nqtot)) |
|---|
| 119 | IF (.NOT. ALLOCATED(o_trac_cum)) ALLOCATE(o_trac_cum(nqtot)) |
|---|
| 120 | |
|---|
| 121 | levmax = (/ klev, klev, klev, klev, klev, klev /) |
|---|
| 122 | |
|---|
| 123 | phys_out_filenames(1) = 'histmth' |
|---|
| 124 | phys_out_filenames(2) = 'histday' |
|---|
| 125 | phys_out_filenames(3) = 'histhf' |
|---|
| 126 | phys_out_filenames(4) = 'histins' |
|---|
| 127 | phys_out_filenames(5) = 'histLES' |
|---|
| 128 | phys_out_filenames(6) = 'histstn' |
|---|
| 129 | |
|---|
| 130 | type_ecri(1) = 'ave(X)' |
|---|
| 131 | type_ecri(2) = 'ave(X)' |
|---|
| 132 | type_ecri(3) = 'ave(X)' |
|---|
| 133 | type_ecri(4) = 'inst(X)' |
|---|
| 134 | type_ecri(5) = 'ave(X)' |
|---|
| 135 | type_ecri(6) = 'inst(X)' |
|---|
| 136 | |
|---|
| 137 | clef_files(1) = ok_mensuel |
|---|
| 138 | clef_files(2) = ok_journe |
|---|
| 139 | clef_files(3) = ok_hf |
|---|
| 140 | clef_files(4) = ok_instan |
|---|
| 141 | clef_files(5) = ok_LES |
|---|
| 142 | clef_files(6) = ok_instan |
|---|
| 143 | |
|---|
| 144 | !sortir des fichiers "stations" si clef_stations(:)=.TRUE. |
|---|
| 145 | clef_stations(1) = .FALSE. |
|---|
| 146 | clef_stations(2) = .FALSE. |
|---|
| 147 | clef_stations(3) = .FALSE. |
|---|
| 148 | clef_stations(4) = .FALSE. |
|---|
| 149 | clef_stations(5) = .FALSE. |
|---|
| 150 | clef_stations(6) = .FALSE. |
|---|
| 151 | |
|---|
| 152 | lev_files(1) = lev_histmth |
|---|
| 153 | lev_files(2) = lev_histday |
|---|
| 154 | lev_files(3) = lev_histhf |
|---|
| 155 | lev_files(4) = lev_histins |
|---|
| 156 | lev_files(5) = lev_histLES |
|---|
| 157 | lev_files(6) = lev_histins |
|---|
| 158 | |
|---|
| 159 | ecrit_files(1) = ecrit_mth |
|---|
| 160 | ecrit_files(2) = ecrit_day |
|---|
| 161 | ecrit_files(3) = ecrit_hf |
|---|
| 162 | ecrit_files(4) = ecrit_ins |
|---|
| 163 | ecrit_files(5) = ecrit_LES |
|---|
| 164 | ecrit_files(6) = ecrit_ins |
|---|
| 165 | |
|---|
| 166 | !! Lectures des parametres de sorties dans physiq.def |
|---|
| 167 | |
|---|
| 168 | CALL getin('phys_out_regfkey',phys_out_regfkey) |
|---|
| 169 | CALL getin('phys_out_lonmin',phys_out_lonmin) |
|---|
| 170 | CALL getin('phys_out_lonmax',phys_out_lonmax) |
|---|
| 171 | CALL getin('phys_out_latmin',phys_out_latmin) |
|---|
| 172 | CALL getin('phys_out_latmax',phys_out_latmax) |
|---|
| 173 | phys_out_levmin(:)=levmin(:) |
|---|
| 174 | CALL getin('phys_out_levmin',levmin) |
|---|
| 175 | phys_out_levmax(:)=levmax(:) |
|---|
| 176 | CALL getin('phys_out_levmax',levmax) |
|---|
| 177 | CALL getin('phys_out_filenames',phys_out_filenames) |
|---|
| 178 | phys_out_filekeys(:)=clef_files(:) |
|---|
| 179 | CALL getin('phys_out_filekeys',clef_files) |
|---|
| 180 | phys_out_filestations(:)=clef_stations(:) |
|---|
| 181 | CALL getin('phys_out_filestations',clef_stations) |
|---|
| 182 | phys_out_filelevels(:)=lev_files(:) |
|---|
| 183 | CALL getin('phys_out_filelevels',lev_files) |
|---|
| 184 | CALL getin('phys_out_filetimesteps',chtimestep) |
|---|
| 185 | phys_out_filetypes(:)=type_ecri(:) |
|---|
| 186 | CALL getin('phys_out_filetypes',type_ecri) |
|---|
| 187 | |
|---|
| 188 | type_ecri_files(:)=type_ecri(:) |
|---|
| 189 | |
|---|
| 190 | WRITE(lunout,*)'phys_out_lonmin=',phys_out_lonmin |
|---|
| 191 | WRITE(lunout,*)'phys_out_lonmax=',phys_out_lonmax |
|---|
| 192 | WRITE(lunout,*)'phys_out_latmin=',phys_out_latmin |
|---|
| 193 | WRITE(lunout,*)'phys_out_latmax=',phys_out_latmax |
|---|
| 194 | WRITE(lunout,*)'phys_out_filenames=',phys_out_filenames |
|---|
| 195 | WRITE(lunout,*)'phys_out_filetypes=',type_ecri |
|---|
| 196 | WRITE(lunout,*)'phys_out_filekeys=',clef_files |
|---|
| 197 | WRITE(lunout,*)'phys_out_filestations=',clef_stations |
|---|
| 198 | WRITE(lunout,*)'phys_out_filelevels=',lev_files |
|---|
| 199 | |
|---|
| 200 | !!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 201 | ! Appel de histbeg et histvert pour creer le fichier et les niveaux verticaux !! |
|---|
| 202 | ! Appel des histbeg pour definir les variables (nom, moy ou inst, freq de sortie .. |
|---|
| 203 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 204 | |
|---|
| 205 | zdtime = dtime ! Frequence ou l on moyenne |
|---|
| 206 | |
|---|
| 207 | ! Calcul des Ahyb, Bhyb et Alt |
|---|
| 208 | DO k=1,klev |
|---|
| 209 | Ahyb(k)=(ap(k)+ap(k+1))/2. |
|---|
| 210 | Bhyb(k)=(bp(k)+bp(k+1))/2. |
|---|
| 211 | Alt(k)=log(preff/presnivs(k))*8. |
|---|
| 212 | ENDDO |
|---|
| 213 | ! if(prt_level.ge.1) then |
|---|
| 214 | WRITE(lunout,*)'Ap Hybrid = ',Ahyb(1:klev) |
|---|
| 215 | WRITE(lunout,*)'Bp Hybrid = ',Bhyb(1:klev) |
|---|
| 216 | WRITE(lunout,*)'Alt approx des couches pour une haut d echelle de 8km = ',Alt(1:klev) |
|---|
| 217 | ! endif |
|---|
| 218 | DO iff=1,nfiles |
|---|
| 219 | |
|---|
| 220 | ! Calculate ecrit_files for all files |
|---|
| 221 | IF ( chtimestep(iff).eq.'DefFreq' ) then |
|---|
| 222 | ! Par defaut ecrit_files = (ecrit_mensuel ecrit_jour ecrit_hf ...)*86400. |
|---|
| 223 | ecrit_files(iff)=ecrit_files(iff)*86400. |
|---|
| 224 | ELSE |
|---|
| 225 | CALL convers_timesteps(chtimestep(iff),dtime,ecrit_files(iff)) |
|---|
| 226 | ENDIF |
|---|
| 227 | WRITE(lunout,*)'ecrit_files(',iff,')= ',ecrit_files(iff) |
|---|
| 228 | |
|---|
| 229 | zoutm(iff) = ecrit_files(iff) ! Frequence ou l on ecrit en seconde |
|---|
| 230 | |
|---|
| 231 | IF (clef_files(iff)) THEN |
|---|
| 232 | |
|---|
| 233 | idayref = day_ref |
|---|
| 234 | ! CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian) |
|---|
| 235 | ! correction pour l heure initiale !jyg |
|---|
| 236 | ! !jyg |
|---|
| 237 | CALL ymds2ju(annee_ref, 1, idayref, hour, zjulian) !jyg |
|---|
| 238 | ! correction pour l heure initiale !jyg |
|---|
| 239 | ! !jyg |
|---|
| 240 | !!! CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian) !jyg |
|---|
| 241 | ! correction pour l heure initiale !jyg |
|---|
| 242 | ! !jyg |
|---|
| 243 | ! CALL ymds2ju(annee_ref, 1, idayref, hour, zjulian) !jyg |
|---|
| 244 | |
|---|
| 245 | !!!!!!!!!!!!!!!!! Traitement dans le cas ou l'on veut stocker sur un domaine limite !! |
|---|
| 246 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 247 | IF (phys_out_regfkey(iff)) then |
|---|
| 248 | |
|---|
| 249 | imin_ins=1 |
|---|
| 250 | imax_ins=iim |
|---|
| 251 | jmin_ins=1 |
|---|
| 252 | jmax_ins=jjmp1 |
|---|
| 253 | |
|---|
| 254 | ! correction abderr |
|---|
| 255 | do i=1,iim |
|---|
| 256 | WRITE(lunout,*)'io_lon(i)=',io_lon(i) |
|---|
| 257 | IF (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i |
|---|
| 258 | IF (io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1 |
|---|
| 259 | enddo |
|---|
| 260 | |
|---|
| 261 | do j=1,jjmp1 |
|---|
| 262 | WRITE(lunout,*)'io_lat(j)=',io_lat(j) |
|---|
| 263 | IF (io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1 |
|---|
| 264 | IF (io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j |
|---|
| 265 | enddo |
|---|
| 266 | |
|---|
| 267 | WRITE(lunout,*)'On stoke le fichier histoire numero ',iff,' sur ', & |
|---|
| 268 | imin_ins,imax_ins,jmin_ins,jmax_ins |
|---|
| 269 | WRITE(lunout,*)'longitudes : ', & |
|---|
| 270 | io_lon(imin_ins),io_lon(imax_ins), & |
|---|
| 271 | 'latitudes : ', & |
|---|
| 272 | io_lat(jmax_ins),io_lat(jmin_ins) |
|---|
| 273 | |
|---|
| 274 | CALL histbeg(phys_out_filenames(iff),iim,io_lon,jjmp1,io_lat, & |
|---|
| 275 | imin_ins,imax_ins-imin_ins+1, & |
|---|
| 276 | jmin_ins,jmax_ins-jmin_ins+1, & |
|---|
| 277 | itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff)) |
|---|
| 278 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 279 | !IM fichiers stations |
|---|
| 280 | else IF (clef_stations(iff)) THEN |
|---|
| 281 | |
|---|
| 282 | WRITE(lunout,*)'phys_output_mod phys_out_filenames=',phys_out_filenames(iff) |
|---|
| 283 | |
|---|
| 284 | CALL histbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, & |
|---|
| 285 | phys_out_filenames(iff), & |
|---|
| 286 | itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff)) |
|---|
| 287 | else |
|---|
| 288 | CALL histbeg_phy(phys_out_filenames(iff),itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff)) |
|---|
| 289 | endif |
|---|
| 290 | |
|---|
| 291 | CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "Pa", & |
|---|
| 292 | levmax(iff) - levmin(iff) + 1, & |
|---|
| 293 | presnivs(levmin(iff):levmax(iff)), nvertm(iff),"down") |
|---|
| 294 | |
|---|
| 295 | !!!!!!!!!!!!! Traitement des champs 3D pour histhf !!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 296 | !!!!!!!!!!!!!!! A Revoir plus tard !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 297 | ! IF (iff.eq.3.and.lev_files(iff).ge.4) THEN |
|---|
| 298 | ! CALL histbeg_phy("histhf3d",itau_phy, & |
|---|
| 299 | ! & zjulian, dtime, & |
|---|
| 300 | ! & nhorim, nid_hf3d) |
|---|
| 301 | |
|---|
| 302 | ! CALL histvert(nid_hf3d, "presnivs", & |
|---|
| 303 | ! & "Vertical levels", "mb", & |
|---|
| 304 | ! & klev, presnivs/100., nvertm) |
|---|
| 305 | ! ENDIF |
|---|
| 306 | ! |
|---|
| 307 | !!!! Composentes de la coordonnee sigma-hybride |
|---|
| 308 | CALL histvert(nid_files(iff), "Ahyb","Ahyb comp of Hyb Cord ", "Pa", & |
|---|
| 309 | levmax(iff) - levmin(iff) + 1,Ahyb,nvertap(iff)) |
|---|
| 310 | |
|---|
| 311 | CALL histvert(nid_files(iff), "Bhyb","Bhyb comp of Hyb Cord", " ", & |
|---|
| 312 | levmax(iff) - levmin(iff) + 1,Bhyb,nvertbp(iff)) |
|---|
| 313 | |
|---|
| 314 | CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", & |
|---|
| 315 | levmax(iff) - levmin(iff) + 1,Alt,nvertAlt(iff)) |
|---|
| 316 | |
|---|
| 317 | ! CALL histvert(nid_files(iff), "preff","Reference pressure", "Pa", & |
|---|
| 318 | ! 1,preff,nvertp0(iff)) |
|---|
| 319 | !!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 320 | CALL histdef2d(iff,o_aire) |
|---|
| 321 | CALL histdef2d(iff,o_contfracATM) |
|---|
| 322 | |
|---|
| 323 | !!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
|---|
| 324 | CALL histdef2d(iff,o_phis) |
|---|
| 325 | CALL histdef2d(iff,o_contfracOR) |
|---|
| 326 | CALL histdef2d(iff,o_aireTER) |
|---|
| 327 | CALL histdef2d(iff,o_flat) |
|---|
| 328 | CALL histdef2d(iff,o_slp) |
|---|
| 329 | CALL histdef2d(iff,o_tsol) |
|---|
| 330 | CALL histdef2d(iff,o_t2m) |
|---|
| 331 | CALL histdef2d(iff,o_t2m_min) |
|---|
| 332 | CALL histdef2d(iff,o_t2m_max) |
|---|
| 333 | CALL histdef2d(iff,o_wind10m) |
|---|
| 334 | CALL histdef2d(iff,o_wind10max) |
|---|
| 335 | CALL histdef2d(iff,o_sicf) |
|---|
| 336 | CALL histdef2d(iff,o_q2m) |
|---|
| 337 | CALL histdef2d(iff,o_ustar) |
|---|
| 338 | CALL histdef2d(iff,o_u10m) |
|---|
| 339 | CALL histdef2d(iff,o_v10m) |
|---|
| 340 | CALL histdef2d(iff,o_psol) |
|---|
| 341 | CALL histdef2d(iff,o_qsurf) |
|---|
| 342 | |
|---|
| 343 | IF (.NOT. ok_veget) THEN |
|---|
| 344 | CALL histdef2d(iff,o_qsol) |
|---|
| 345 | ENDIF |
|---|
| 346 | CALL histdef2d(iff,o_ndayrain) |
|---|
| 347 | CALL histdef2d(iff,o_precip) |
|---|
| 348 | CALL histdef2d(iff,o_plul) |
|---|
| 349 | CALL histdef2d(iff,o_pluc) |
|---|
| 350 | CALL histdef2d(iff,o_snow) |
|---|
| 351 | CALL histdef2d(iff,o_msnow) |
|---|
| 352 | CALL histdef2d(iff,o_fsnow) |
|---|
| 353 | CALL histdef2d(iff,o_evap) |
|---|
| 354 | CALL histdef2d(iff,o_tops) |
|---|
| 355 | CALL histdef2d(iff,o_tops0) |
|---|
| 356 | CALL histdef2d(iff,o_topl) |
|---|
| 357 | CALL histdef2d(iff,o_topl0) |
|---|
| 358 | CALL histdef2d(iff,o_SWupTOA) |
|---|
| 359 | CALL histdef2d(iff,o_SWupTOAclr) |
|---|
| 360 | CALL histdef2d(iff,o_SWdnTOA) |
|---|
| 361 | CALL histdef2d(iff,o_SWdnTOAclr) |
|---|
| 362 | CALL histdef2d(iff,o_nettop) |
|---|
| 363 | CALL histdef2d(iff,o_SWup200) |
|---|
| 364 | CALL histdef2d(iff,o_SWup200clr) |
|---|
| 365 | CALL histdef2d(iff,o_SWdn200) |
|---|
| 366 | CALL histdef2d(iff,o_SWdn200clr) |
|---|
| 367 | CALL histdef2d(iff,o_LWup200) |
|---|
| 368 | CALL histdef2d(iff,o_LWup200clr) |
|---|
| 369 | CALL histdef2d(iff,o_LWdn200) |
|---|
| 370 | CALL histdef2d(iff,o_LWdn200clr) |
|---|
| 371 | CALL histdef2d(iff,o_sols) |
|---|
| 372 | CALL histdef2d(iff,o_sols0) |
|---|
| 373 | CALL histdef2d(iff,o_soll) |
|---|
| 374 | CALL histdef2d(iff,o_radsol) |
|---|
| 375 | CALL histdef2d(iff,o_soll0) |
|---|
| 376 | CALL histdef2d(iff,o_SWupSFC) |
|---|
| 377 | CALL histdef2d(iff,o_SWupSFCclr) |
|---|
| 378 | CALL histdef2d(iff,o_SWdnSFC) |
|---|
| 379 | CALL histdef2d(iff,o_SWdnSFCclr) |
|---|
| 380 | CALL histdef2d(iff,o_LWupSFC) |
|---|
| 381 | CALL histdef2d(iff,o_LWdnSFC) |
|---|
| 382 | CALL histdef2d(iff,o_LWupSFCclr) |
|---|
| 383 | CALL histdef2d(iff,o_LWdnSFCclr) |
|---|
| 384 | CALL histdef2d(iff,o_bils) |
|---|
| 385 | CALL histdef2d(iff,o_bils_ec) |
|---|
| 386 | CALL histdef2d(iff,o_bils_tke) |
|---|
| 387 | CALL histdef2d(iff,o_bils_diss) |
|---|
| 388 | CALL histdef2d(iff,o_bils_kinetic) |
|---|
| 389 | CALL histdef2d(iff,o_bils_enthalp) |
|---|
| 390 | CALL histdef2d(iff,o_bils_latent) |
|---|
| 391 | CALL histdef2d(iff,o_sens) |
|---|
| 392 | CALL histdef2d(iff,o_fder) |
|---|
| 393 | CALL histdef2d(iff,o_ffonte) |
|---|
| 394 | CALL histdef2d(iff,o_fqcalving) |
|---|
| 395 | CALL histdef2d(iff,o_fqfonte) |
|---|
| 396 | CALL histdef2d(iff,o_taux) |
|---|
| 397 | CALL histdef2d(iff,o_tauy) |
|---|
| 398 | |
|---|
| 399 | DO nsrf = 1, nbsrf |
|---|
| 400 | CALL histdef2d(iff,o_pourc_srf(nsrf)) |
|---|
| 401 | CALL histdef2d(iff,o_fract_srf(nsrf)) |
|---|
| 402 | CALL histdef2d(iff, o_taux_srf(nsrf)) |
|---|
| 403 | CALL histdef2d(iff, o_tauy_srf(nsrf)) |
|---|
| 404 | CALL histdef2d(iff, o_tsol_srf(nsrf)) |
|---|
| 405 | CALL histdef2d(iff, o_evappot_srf(nsrf)) |
|---|
| 406 | CALL histdef2d(iff, o_ustar_srf(nsrf)) |
|---|
| 407 | CALL histdef2d(iff, o_u10m_srf(nsrf)) |
|---|
| 408 | CALL histdef2d(iff, o_evap_srf(nsrf)) |
|---|
| 409 | CALL histdef2d(iff, o_v10m_srf(nsrf)) |
|---|
| 410 | CALL histdef2d(iff, o_t2m_srf(nsrf)) |
|---|
| 411 | CALL histdef2d(iff, o_sens_srf(nsrf)) |
|---|
| 412 | CALL histdef2d(iff, o_lat_srf(nsrf)) |
|---|
| 413 | CALL histdef2d(iff, o_flw_srf(nsrf)) |
|---|
| 414 | CALL histdef2d(iff, o_fsw_srf(nsrf)) |
|---|
| 415 | CALL histdef2d(iff, o_wbils_srf(nsrf)) |
|---|
| 416 | CALL histdef2d(iff, o_wbilo_srf(nsrf)) |
|---|
| 417 | IF (iflag_pbl>1 ) then |
|---|
| 418 | CALL histdef2d(iff, o_tke_srf(nsrf)) |
|---|
| 419 | CALL histdef2d(iff, o_tke_max_srf(nsrf)) |
|---|
| 420 | ENDIF |
|---|
| 421 | |
|---|
| 422 | CALL histdef2d(iff, o_albe_srf(nsrf)) |
|---|
| 423 | CALL histdef2d(iff, o_rugs_srf(nsrf)) |
|---|
| 424 | CALL histdef2d(iff, o_ages_srf(nsrf)) |
|---|
| 425 | END DO |
|---|
| 426 | |
|---|
| 427 | IF (new_aod .AND. (.NOT. aerosol_couple)) THEN |
|---|
| 428 | IF (ok_ade.OR.ok_aie) THEN |
|---|
| 429 | CALL histdef2d(iff,o_od550aer) |
|---|
| 430 | CALL histdef2d(iff,o_od865aer) |
|---|
| 431 | CALL histdef2d(iff,o_absvisaer) |
|---|
| 432 | CALL histdef2d(iff,o_od550lt1aer) |
|---|
| 433 | CALL histdef2d(iff,o_sconcso4) |
|---|
| 434 | CALL histdef2d(iff,o_sconcoa) |
|---|
| 435 | CALL histdef2d(iff,o_sconcbc) |
|---|
| 436 | CALL histdef2d(iff,o_sconcss) |
|---|
| 437 | CALL histdef2d(iff,o_sconcdust) |
|---|
| 438 | CALL histdef3d(iff,o_concso4) |
|---|
| 439 | CALL histdef3d(iff,o_concoa) |
|---|
| 440 | CALL histdef3d(iff,o_concbc) |
|---|
| 441 | CALL histdef3d(iff,o_concss) |
|---|
| 442 | CALL histdef3d(iff,o_concdust) |
|---|
| 443 | CALL histdef2d(iff,o_loadso4) |
|---|
| 444 | CALL histdef2d(iff,o_loadoa) |
|---|
| 445 | CALL histdef2d(iff,o_loadbc) |
|---|
| 446 | CALL histdef2d(iff,o_loadss) |
|---|
| 447 | CALL histdef2d(iff,o_loaddust) |
|---|
| 448 | !--STRAT AER |
|---|
| 449 | ENDIF |
|---|
| 450 | IF (ok_ade.OR.ok_aie.OR.flag_aerosol_strat) THEN |
|---|
| 451 | DO naero = 1, naero_spc |
|---|
| 452 | CALL histdef2d(iff, o_tausumaero(naero)) |
|---|
| 453 | END DO |
|---|
| 454 | ENDIF |
|---|
| 455 | ENDIF |
|---|
| 456 | |
|---|
| 457 | IF (ok_ade) THEN |
|---|
| 458 | CALL histdef2d(iff,o_topswad) |
|---|
| 459 | CALL histdef2d(iff,o_topswad0) |
|---|
| 460 | CALL histdef2d(iff,o_solswad) |
|---|
| 461 | CALL histdef2d(iff,o_solswad0) |
|---|
| 462 | CALL histdef2d(iff,o_swtoaas_nat) |
|---|
| 463 | CALL histdef2d(iff,o_swsrfas_nat) |
|---|
| 464 | CALL histdef2d(iff,o_swtoacs_nat) |
|---|
| 465 | CALL histdef2d(iff,o_swsrfcs_nat) |
|---|
| 466 | CALL histdef2d(iff,o_swtoaas_ant) |
|---|
| 467 | CALL histdef2d(iff,o_swsrfas_ant) |
|---|
| 468 | CALL histdef2d(iff,o_swtoacs_ant) |
|---|
| 469 | CALL histdef2d(iff,o_swsrfcs_ant) |
|---|
| 470 | |
|---|
| 471 | IF (.NOT. aerosol_couple) THEN |
|---|
| 472 | CALL histdef2d(iff,o_swtoacf_nat) |
|---|
| 473 | CALL histdef2d(iff,o_swsrfcf_nat) |
|---|
| 474 | CALL histdef2d(iff,o_swtoacf_ant) |
|---|
| 475 | CALL histdef2d(iff,o_swsrfcf_ant) |
|---|
| 476 | CALL histdef2d(iff,o_swtoacf_zero) |
|---|
| 477 | CALL histdef2d(iff,o_swsrfcf_zero) |
|---|
| 478 | ENDIF |
|---|
| 479 | ENDIF |
|---|
| 480 | |
|---|
| 481 | IF (ok_aie) THEN |
|---|
| 482 | CALL histdef2d(iff,o_topswai) |
|---|
| 483 | CALL histdef2d(iff,o_solswai) |
|---|
| 484 | !Cloud droplet number concentration |
|---|
| 485 | CALL histdef3d(iff,o_scdnc) |
|---|
| 486 | CALL histdef2d(iff,o_cldncl) |
|---|
| 487 | CALL histdef3d(iff,o_reffclws) |
|---|
| 488 | CALL histdef3d(iff,o_reffclwc) |
|---|
| 489 | CALL histdef2d(iff,o_cldnvi) |
|---|
| 490 | CALL histdef3d(iff,o_lcc3d) |
|---|
| 491 | CALL histdef3d(iff,o_lcc3dcon) |
|---|
| 492 | CALL histdef3d(iff,o_lcc3dstra) |
|---|
| 493 | CALL histdef2d(iff,o_lcc) |
|---|
| 494 | CALL histdef2d(iff,o_reffclwtop) |
|---|
| 495 | ENDIF |
|---|
| 496 | CALL histdef2d(iff,o_alb1) |
|---|
| 497 | CALL histdef2d(iff,o_alb2) |
|---|
| 498 | CALL histdef2d(iff,o_cdrm) |
|---|
| 499 | CALL histdef2d(iff,o_cdrh) |
|---|
| 500 | CALL histdef2d(iff,o_cldl) |
|---|
| 501 | CALL histdef2d(iff,o_cldm) |
|---|
| 502 | CALL histdef2d(iff,o_cldh) |
|---|
| 503 | CALL histdef2d(iff,o_cldt) |
|---|
| 504 | CALL histdef2d(iff,o_cldq) |
|---|
| 505 | CALL histdef2d(iff,o_lwp) |
|---|
| 506 | CALL histdef2d(iff,o_iwp) |
|---|
| 507 | CALL histdef2d(iff,o_ue) |
|---|
| 508 | CALL histdef2d(iff,o_ve) |
|---|
| 509 | CALL histdef2d(iff,o_uq) |
|---|
| 510 | CALL histdef2d(iff,o_vq) |
|---|
| 511 | |
|---|
| 512 | IF(iflag_con.GE.3) THEN ! sb |
|---|
| 513 | CALL histdef2d(iff,o_cape) |
|---|
| 514 | CALL histdef2d(iff,o_pbase) |
|---|
| 515 | CALL histdef2d(iff,o_ptop) |
|---|
| 516 | CALL histdef2d(iff,o_fbase) |
|---|
| 517 | IF (iflag_con /= 30) THEN |
|---|
| 518 | CALL histdef2d(iff,o_plcl) |
|---|
| 519 | CALL histdef2d(iff,o_plfc) |
|---|
| 520 | CALL histdef2d(iff,o_wbeff) |
|---|
| 521 | ENDIF |
|---|
| 522 | CALL histdef2d(iff,o_cape_max) |
|---|
| 523 | CALL histdef3d(iff,o_upwd) |
|---|
| 524 | CALL histdef3d(iff,o_Ma) |
|---|
| 525 | CALL histdef3d(iff,o_dnwd) |
|---|
| 526 | CALL histdef3d(iff,o_dnwd0) |
|---|
| 527 | CALL histdef3d(iff,o_mc) |
|---|
| 528 | CALL histdef2d(iff,o_ftime_con) |
|---|
| 529 | ENDIF !iflag_con .GE. 3 |
|---|
| 530 | CALL histdef2d(iff,o_prw) |
|---|
| 531 | CALL histdef2d(iff,o_s_pblh) |
|---|
| 532 | CALL histdef2d(iff,o_s_pblt) |
|---|
| 533 | CALL histdef2d(iff,o_s_lcl) |
|---|
| 534 | CALL histdef2d(iff,o_s_therm) |
|---|
| 535 | !IM : Les champs suivants (s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F |
|---|
| 536 | !CALL histdef2d(iff, & |
|---|
| 537 | !o_s_capCL%flag,o_s_capCL%name, "Conv avlbl pot enerfor ABL", "J/m2" ) |
|---|
| 538 | !CALL histdef2d(iff, & |
|---|
| 539 | !o_s_oliqCL%flag,o_s_oliqCL%name, "Liq Water in BL", "kg/m2") |
|---|
| 540 | !CALL histdef2d(iff, & |
|---|
| 541 | !o_s_cteiCL%flag,o_s_cteiCL%name, "Instability criteria(ABL)", "K") |
|---|
| 542 | !CALL histdef2d(iff, & |
|---|
| 543 | !o_s_trmb1%flag,o_s_trmb1%name, "deep_cape(HBTM2)", "J/m2") |
|---|
| 544 | !CALL histdef2d(iff, & |
|---|
| 545 | !o_s_trmb2%flag,o_s_trmb2%name, "inhibition (HBTM2)", "J/m2") |
|---|
| 546 | !CALL histdef2d(iff, & |
|---|
| 547 | !o_s_trmb3%flag,o_s_trmb3%name, "Point Omega (HBTM2)", "m") |
|---|
| 548 | |
|---|
| 549 | ! Champs interpolles sur des niveaux de pression |
|---|
| 550 | |
|---|
| 551 | ! Attention a reverifier |
|---|
| 552 | |
|---|
| 553 | ilev=0 |
|---|
| 554 | DO k=1, nlevSTD |
|---|
| 555 | bb2=clevSTD(k) |
|---|
| 556 | IF(bb2.EQ."850".OR.bb2.EQ."700".OR.bb2.EQ."500".OR.bb2.EQ."200" & |
|---|
| 557 | .OR.bb2.EQ."100".OR.bb2.EQ."50".OR.bb2.EQ."10")THEN |
|---|
| 558 | ilev=ilev+1 |
|---|
| 559 | ! print*,'ilev k bb2 flag name ',ilev,k, bb2,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name |
|---|
| 560 | CALL histdef2d(iff,o_uSTDlevs(ilev)) |
|---|
| 561 | CALL histdef2d(iff,o_vSTDlevs(ilev)) |
|---|
| 562 | CALL histdef2d(iff,o_wSTDlevs(ilev)) |
|---|
| 563 | CALL histdef2d(iff,o_zSTDlevs(ilev)) |
|---|
| 564 | CALL histdef2d(iff,o_qSTDlevs(ilev)) |
|---|
| 565 | CALL histdef2d(iff,o_tSTDlevs(ilev)) |
|---|
| 566 | ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10") |
|---|
| 567 | ENDDO |
|---|
| 568 | |
|---|
| 569 | CALL histdef2d(iff,o_t_oce_sic) |
|---|
| 570 | |
|---|
| 571 | IF (type_ocean=='slab') THEN |
|---|
| 572 | CALL histdef2d(iff,o_slab_bils) |
|---|
| 573 | ENDIF |
|---|
| 574 | |
|---|
| 575 | ! Couplage conv-CL |
|---|
| 576 | IF (iflag_con.GE.3) THEN |
|---|
| 577 | IF (iflag_coupl>=1) THEN |
|---|
| 578 | CALL histdef2d(iff,o_ale_bl) |
|---|
| 579 | CALL histdef2d(iff,o_alp_bl) |
|---|
| 580 | ENDIF |
|---|
| 581 | ENDIF !(iflag_con.GE.3) |
|---|
| 582 | |
|---|
| 583 | CALL histdef2d(iff,o_weakinv) |
|---|
| 584 | CALL histdef2d(iff,o_dthmin) |
|---|
| 585 | |
|---|
| 586 | CALL histdef2d(iff,o_rh2m) |
|---|
| 587 | CALL histdef2d(iff,o_rh2m_min) |
|---|
| 588 | CALL histdef2d(iff,o_rh2m_max) |
|---|
| 589 | |
|---|
| 590 | CALL histdef2d(iff,o_qsat2m) |
|---|
| 591 | CALL histdef2d(iff,o_tpot) |
|---|
| 592 | CALL histdef2d(iff,o_tpote) |
|---|
| 593 | CALL histdef2d(iff,o_SWnetOR) |
|---|
| 594 | CALL histdef2d(iff,o_SWdownOR) |
|---|
| 595 | CALL histdef2d(iff,o_LWdownOR) |
|---|
| 596 | CALL histdef2d(iff,o_snowl) |
|---|
| 597 | CALL histdef2d(iff,o_solldown) |
|---|
| 598 | CALL histdef2d(iff,o_dtsvdfo) |
|---|
| 599 | CALL histdef2d(iff,o_dtsvdft) |
|---|
| 600 | CALL histdef2d(iff,o_dtsvdfg) |
|---|
| 601 | CALL histdef2d(iff,o_dtsvdfi) |
|---|
| 602 | CALL histdef2d(iff,o_rugs) |
|---|
| 603 | |
|---|
| 604 | ! Champs 3D: |
|---|
| 605 | CALL histdef3d(iff,o_ec550aer) |
|---|
| 606 | CALL histdef3d(iff,o_lwcon) |
|---|
| 607 | CALL histdef3d(iff,o_iwcon) |
|---|
| 608 | CALL histdef3d(iff,o_temp) |
|---|
| 609 | CALL histdef3d(iff,o_theta) |
|---|
| 610 | CALL histdef3d(iff,o_ovap) |
|---|
| 611 | CALL histdef3d(iff,o_oliq) |
|---|
| 612 | CALL histdef3d(iff,o_ovapinit) |
|---|
| 613 | CALL histdef3d(iff,o_geop) |
|---|
| 614 | CALL histdef3d(iff,o_vitu) |
|---|
| 615 | CALL histdef3d(iff,o_vitv) |
|---|
| 616 | CALL histdef3d(iff,o_vitw) |
|---|
| 617 | CALL histdef3d(iff,o_pres) |
|---|
| 618 | CALL histdef3d(iff,o_paprs) |
|---|
| 619 | CALL histdef3d(iff,o_mass) |
|---|
| 620 | CALL histdef3d(iff,o_zfull) |
|---|
| 621 | CALL histdef3d(iff,o_zhalf) |
|---|
| 622 | CALL histdef3d(iff,o_rneb) |
|---|
| 623 | CALL histdef3d(iff,o_rnebcon) |
|---|
| 624 | CALL histdef3d(iff,o_rnebls) |
|---|
| 625 | CALL histdef3d(iff,o_rhum) |
|---|
| 626 | CALL histdef3d(iff,o_ozone) |
|---|
| 627 | |
|---|
| 628 | IF (read_climoz == 2) THEN |
|---|
| 629 | CALL histdef3d(iff,o_ozone_light) |
|---|
| 630 | END IF |
|---|
| 631 | |
|---|
| 632 | CALL histdef3d(iff,o_dtphy) |
|---|
| 633 | CALL histdef3d(iff,o_dqphy) |
|---|
| 634 | CALL histdef3d(iff,o_cldtau) |
|---|
| 635 | CALL histdef3d(iff,o_cldemi) |
|---|
| 636 | !IM: bug ?? dimensionnement variables (klon,klev+1) pmflxr, pmflxs, prfl, psfl |
|---|
| 637 | CALL histdef3d(iff,o_pr_con_l) |
|---|
| 638 | CALL histdef3d(iff,o_pr_con_i) |
|---|
| 639 | CALL histdef3d(iff,o_pr_lsc_l) |
|---|
| 640 | CALL histdef3d(iff,o_pr_lsc_i) |
|---|
| 641 | !Cloud droplet effective radius |
|---|
| 642 | CALL histdef3d(iff,o_re) |
|---|
| 643 | CALL histdef3d(iff,o_fl) |
|---|
| 644 | !FH Sorties pour la couche limite |
|---|
| 645 | IF (iflag_pbl>1) THEN |
|---|
| 646 | CALL histdef3d(iff,o_tke) |
|---|
| 647 | CALL histdef3d(iff,o_tke_max) |
|---|
| 648 | ENDIF |
|---|
| 649 | CALL histdef3d(iff,o_kz) |
|---|
| 650 | CALL histdef3d(iff,o_kz_max) |
|---|
| 651 | CALL histdef3d(iff,o_clwcon) |
|---|
| 652 | CALL histdef3d(iff,o_dtdyn) |
|---|
| 653 | CALL histdef3d(iff,o_dqdyn) |
|---|
| 654 | CALL histdef3d(iff,o_dudyn) |
|---|
| 655 | CALL histdef3d(iff,o_dvdyn) |
|---|
| 656 | CALL histdef3d(iff,o_dtcon) |
|---|
| 657 | CALL histdef3d(iff,o_ducon) |
|---|
| 658 | CALL histdef3d(iff,o_dvcon) |
|---|
| 659 | CALL histdef3d(iff,o_dqcon) |
|---|
| 660 | |
|---|
| 661 | ! Wakes |
|---|
| 662 | IF(iflag_con.EQ.3) THEN |
|---|
| 663 | IF (iflag_wake >= 1) THEN |
|---|
| 664 | CALL histdef2d(iff,o_ale_wk) |
|---|
| 665 | CALL histdef2d(iff,o_alp_wk) |
|---|
| 666 | CALL histdef2d(iff,o_ale) |
|---|
| 667 | CALL histdef2d(iff,o_alp) |
|---|
| 668 | CALL histdef2d(iff,o_cin) |
|---|
| 669 | CALL histdef2d(iff,o_wape) |
|---|
| 670 | CALL histdef2d(iff,o_wake_h) |
|---|
| 671 | CALL histdef2d(iff,o_wake_s) |
|---|
| 672 | CALL histdef3d(iff,o_dtwak) |
|---|
| 673 | CALL histdef3d(iff,o_dqwak) |
|---|
| 674 | CALL histdef3d(iff,o_wake_deltat) |
|---|
| 675 | CALL histdef3d(iff,o_wake_deltaq) |
|---|
| 676 | CALL histdef3d(iff,o_wake_omg) |
|---|
| 677 | ENDIF |
|---|
| 678 | !!! RomP CALL histdef3d(iff,o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-") |
|---|
| 679 | CALL histdef3d(iff,o_ftd) |
|---|
| 680 | CALL histdef3d(iff,o_fqd) |
|---|
| 681 | ENDIF !(iflag_con.EQ.3) |
|---|
| 682 | |
|---|
| 683 | IF(iflag_con.GE.3) THEN ! RomP >>> |
|---|
| 684 | CALL histdef3d(iff,o_wdtrainA) |
|---|
| 685 | CALL histdef3d(iff,o_wdtrainM) |
|---|
| 686 | CALL histdef3d(iff,o_Vprecip) |
|---|
| 687 | ENDIF !(iflag_con.GE.3) ! <<< RomP |
|---|
| 688 | |
|---|
| 689 | !!! nrlmd le 10/04/2012 |
|---|
| 690 | |
|---|
| 691 | IF (iflag_trig_bl>=1) THEN |
|---|
| 692 | CALL histdef2d(iff,o_n2) |
|---|
| 693 | CALL histdef2d(iff,o_s2) |
|---|
| 694 | CALL histdef2d(iff,o_proba_notrig) |
|---|
| 695 | CALL histdef2d(iff,o_random_notrig) |
|---|
| 696 | CALL histdef2d(iff,o_ale_bl_trig) |
|---|
| 697 | CALL histdef2d(iff,o_ale_bl_stat) |
|---|
| 698 | ENDIF !(iflag_trig_bl>=1) |
|---|
| 699 | |
|---|
| 700 | IF (iflag_clos_bl>=1) THEN |
|---|
| 701 | CALL histdef2d(iff,o_alp_bl_det) |
|---|
| 702 | CALL histdef2d(iff,o_alp_bl_fluct_m) |
|---|
| 703 | CALL histdef2d(iff,o_alp_bl_fluct_tke) |
|---|
| 704 | CALL histdef2d(iff,o_alp_bl_conv) |
|---|
| 705 | CALL histdef2d(iff,o_alp_bl_stat) |
|---|
| 706 | ENDIF !(iflag_clos_bl>=1) |
|---|
| 707 | |
|---|
| 708 | !!! fin nrlmd le 10/04/2012 |
|---|
| 709 | CALL histdef3d(iff,o_dtlsc) |
|---|
| 710 | CALL histdef3d(iff,o_dtlschr) |
|---|
| 711 | CALL histdef3d(iff,o_dqlsc) |
|---|
| 712 | CALL histdef3d(iff,o_beta_prec) |
|---|
| 713 | CALL histdef3d(iff,o_dtvdf) |
|---|
| 714 | CALL histdef3d(iff,o_dtdis) |
|---|
| 715 | CALL histdef3d(iff,o_dqvdf) |
|---|
| 716 | CALL histdef3d(iff,o_dteva) |
|---|
| 717 | CALL histdef3d(iff,o_dqeva) |
|---|
| 718 | CALL histdef3d(iff,o_ptconv) |
|---|
| 719 | CALL histdef3d(iff,o_ratqs) |
|---|
| 720 | CALL histdef3d(iff,o_dtthe) |
|---|
| 721 | |
|---|
| 722 | IF (iflag_thermals.ge.1) THEN |
|---|
| 723 | CALL histdef3d(iff,o_dqlscth) |
|---|
| 724 | CALL histdef3d(iff,o_dqlscst) |
|---|
| 725 | CALL histdef3d(iff,o_dtlscth) |
|---|
| 726 | CALL histdef3d(iff,o_dtlscst) |
|---|
| 727 | CALL histdef2d(iff,o_plulth) |
|---|
| 728 | CALL histdef2d(iff,o_plulst) |
|---|
| 729 | CALL histdef2d(iff,o_lmaxth) |
|---|
| 730 | CALL histdef3d(iff,o_ptconvth) |
|---|
| 731 | CALL histdef3d(iff,o_f_th) |
|---|
| 732 | CALL histdef3d(iff,o_e_th) |
|---|
| 733 | CALL histdef3d(iff,o_w_th) |
|---|
| 734 | CALL histdef3d(iff,o_lambda_th) |
|---|
| 735 | CALL histdef2d(iff,o_ftime_th) |
|---|
| 736 | CALL histdef3d(iff,o_q_th) |
|---|
| 737 | CALL histdef3d(iff,o_a_th) |
|---|
| 738 | CALL histdef3d(iff,o_d_th) |
|---|
| 739 | CALL histdef2d(iff,o_f0_th) |
|---|
| 740 | CALL histdef2d(iff,o_zmax_th) |
|---|
| 741 | CALL histdef3d(iff,o_dqthe) |
|---|
| 742 | ENDIF !iflag_thermals.ge.1 |
|---|
| 743 | |
|---|
| 744 | CALL histdef3d(iff,o_dtajs) |
|---|
| 745 | CALL histdef3d(iff,o_dqajs) |
|---|
| 746 | CALL histdef3d(iff,o_dtswr) |
|---|
| 747 | CALL histdef3d(iff,o_dtsw0) |
|---|
| 748 | CALL histdef3d(iff,o_dtlwr) |
|---|
| 749 | CALL histdef3d(iff,o_dtlw0) |
|---|
| 750 | CALL histdef3d(iff,o_dtec) |
|---|
| 751 | CALL histdef3d(iff,o_duvdf) |
|---|
| 752 | CALL histdef3d(iff,o_dvvdf) |
|---|
| 753 | |
|---|
| 754 | IF (ok_orodr) THEN |
|---|
| 755 | CALL histdef3d(iff,o_duoro) |
|---|
| 756 | CALL histdef3d(iff,o_dvoro) |
|---|
| 757 | CALL histdef3d(iff,o_dtoro) |
|---|
| 758 | ENDIF |
|---|
| 759 | |
|---|
| 760 | IF (ok_orolf) THEN |
|---|
| 761 | CALL histdef3d(iff,o_dulif) |
|---|
| 762 | CALL histdef3d(iff,o_dvlif) |
|---|
| 763 | CALL histdef3d(iff,o_dtlif) |
|---|
| 764 | ENDIF |
|---|
| 765 | |
|---|
| 766 | IF (ok_hines) then |
|---|
| 767 | CALL histdef3d(iff,o_duhin) |
|---|
| 768 | CALL histdef3d(iff,o_dvhin) |
|---|
| 769 | CALL histdef3d(iff,o_dthin) |
|---|
| 770 | ENDIF |
|---|
| 771 | |
|---|
| 772 | CALL histdef3d(iff,o_rsu) |
|---|
| 773 | CALL histdef3d(iff,o_rsd) |
|---|
| 774 | CALL histdef3d(iff,o_rlu) |
|---|
| 775 | CALL histdef3d(iff,o_rld) |
|---|
| 776 | CALL histdef3d(iff,o_rsucs) |
|---|
| 777 | CALL histdef3d(iff,o_rsdcs) |
|---|
| 778 | CALL histdef3d(iff,o_rlucs) |
|---|
| 779 | CALL histdef3d(iff,o_rldcs) |
|---|
| 780 | CALL histdef3d(iff,o_tnt) |
|---|
| 781 | CALL histdef3d(iff,o_tntc) |
|---|
| 782 | CALL histdef3d(iff,o_tntr) |
|---|
| 783 | CALL histdef3d(iff,o_tntscpbl) |
|---|
| 784 | CALL histdef3d(iff,o_tnhus) |
|---|
| 785 | CALL histdef3d(iff,o_tnhusc) |
|---|
| 786 | CALL histdef3d(iff,o_tnhusscpbl) |
|---|
| 787 | CALL histdef3d(iff,o_evu) |
|---|
| 788 | CALL histdef3d(iff,o_h2o) |
|---|
| 789 | CALL histdef3d(iff,o_mcd) |
|---|
| 790 | CALL histdef3d(iff,o_dmc) |
|---|
| 791 | CALL histdef3d(iff,o_ref_liq) |
|---|
| 792 | CALL histdef3d(iff,o_ref_ice) |
|---|
| 793 | |
|---|
| 794 | IF (RCO2_per.NE.RCO2_act.OR.RCH4_per.NE.RCH4_act.OR. & |
|---|
| 795 | RN2O_per.NE.RN2O_act.OR.RCFC11_per.NE.RCFC11_act.OR. & |
|---|
| 796 | RCFC12_per.NE.RCFC12_act) THEN |
|---|
| 797 | CALL histdef2d(iff,o_rsut4co2) |
|---|
| 798 | CALL histdef2d(iff,o_rlut4co2) |
|---|
| 799 | CALL histdef2d(iff,o_rsutcs4co2) |
|---|
| 800 | CALL histdef2d(iff,o_rlutcs4co2) |
|---|
| 801 | CALL histdef3d(iff,o_rsu4co2) |
|---|
| 802 | CALL histdef3d(iff,o_rlu4co2) |
|---|
| 803 | CALL histdef3d(iff,o_rsucs4co2) |
|---|
| 804 | CALL histdef3d(iff,o_rlucs4co2) |
|---|
| 805 | CALL histdef3d(iff,o_rsd4co2) |
|---|
| 806 | CALL histdef3d(iff,o_rld4co2) |
|---|
| 807 | CALL histdef3d(iff,o_rsdcs4co2) |
|---|
| 808 | CALL histdef3d(iff,o_rldcs4co2) |
|---|
| 809 | |
|---|
| 810 | ENDIF |
|---|
| 811 | |
|---|
| 812 | |
|---|
| 813 | IF (nqtot>=3) THEN |
|---|
| 814 | DO iq=3,nqtot |
|---|
| 815 | iiq=niadv(iq) |
|---|
| 816 | o_trac(iq-2) = ctrl_out((/ 4, 5, 1, 1, 1, 10 /),tname(iiq),'Tracer '//ttext(iiq), "-",& |
|---|
| 817 | (/ '', '', '', '', '', '' /)) |
|---|
| 818 | CALL histdef3d(iff, o_trac(iq-2)) |
|---|
| 819 | o_trac_cum(iq-2) = ctrl_out((/ 3, 4, 10, 10, 10, 10 /),'cum'//tname(iiq),& |
|---|
| 820 | 'Cumulated tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /)) |
|---|
| 821 | CALL histdef2d(iff, o_trac_cum(iq-2)) |
|---|
| 822 | ENDDO |
|---|
| 823 | ENDIF |
|---|
| 824 | |
|---|
| 825 | CALL histend(nid_files(iff)) |
|---|
| 826 | |
|---|
| 827 | ndex2d = 0 |
|---|
| 828 | ndex3d = 0 |
|---|
| 829 | |
|---|
| 830 | ENDIF ! clef_files |
|---|
| 831 | |
|---|
| 832 | ENDDO ! iff |
|---|
| 833 | |
|---|
| 834 | ! Updated write frequencies due to phys_out_filetimesteps. |
|---|
| 835 | ! Write frequencies are now in seconds. |
|---|
| 836 | ecrit_mth = ecrit_files(1) |
|---|
| 837 | ecrit_day = ecrit_files(2) |
|---|
| 838 | ecrit_hf = ecrit_files(3) |
|---|
| 839 | ecrit_ins = ecrit_files(4) |
|---|
| 840 | ecrit_LES = ecrit_files(5) |
|---|
| 841 | ecrit_ins = ecrit_files(6) |
|---|
| 842 | |
|---|
| 843 | WRITE(lunout,*)'swaero_diag=',swaero_diag |
|---|
| 844 | WRITE(lunout,*)'Fin phys_output_mod.F90' |
|---|
| 845 | end SUBROUTINE phys_output_open |
|---|
| 846 | |
|---|
| 847 | SUBROUTINE histdef2d_old (iff,lpoint,flag_var,nomvar,titrevar,unitvar) |
|---|
| 848 | |
|---|
| 849 | USE ioipsl |
|---|
| 850 | USE dimphy |
|---|
| 851 | USE mod_phys_lmdz_para |
|---|
| 852 | USE iophy |
|---|
| 853 | |
|---|
| 854 | IMPLICIT NONE |
|---|
| 855 | |
|---|
| 856 | INCLUDE "dimensions.h" |
|---|
| 857 | INCLUDE "temps.h" |
|---|
| 858 | INCLUDE "clesphys.h" |
|---|
| 859 | |
|---|
| 860 | INTEGER :: iff |
|---|
| 861 | LOGICAL :: lpoint |
|---|
| 862 | INTEGER, DIMENSION(nfiles) :: flag_var |
|---|
| 863 | CHARACTER(LEN=20) :: nomvar |
|---|
| 864 | CHARACTER(LEN=*) :: titrevar |
|---|
| 865 | CHARACTER(LEN=*) :: unitvar |
|---|
| 866 | |
|---|
| 867 | REAL zstophym |
|---|
| 868 | |
|---|
| 869 | IF (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') THEN |
|---|
| 870 | zstophym=zoutm(iff) |
|---|
| 871 | ELSE |
|---|
| 872 | zstophym=zdtime |
|---|
| 873 | ENDIF |
|---|
| 874 | |
|---|
| 875 | ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def |
|---|
| 876 | CALL conf_physoutputs(nomvar,flag_var) |
|---|
| 877 | |
|---|
| 878 | IF(.NOT.lpoint) THEN |
|---|
| 879 | IF ( flag_var(iff)<=lev_files(iff) ) THEN |
|---|
| 880 | CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, & |
|---|
| 881 | iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, & |
|---|
| 882 | type_ecri(iff), zstophym,zoutm(iff)) |
|---|
| 883 | ENDIF |
|---|
| 884 | ELSE |
|---|
| 885 | IF ( flag_var(iff)<=lev_files(iff) ) THEN |
|---|
| 886 | CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, & |
|---|
| 887 | npstn,1,nhorim(iff), 1,1,1, -99, 32, & |
|---|
| 888 | type_ecri(iff), zstophym,zoutm(iff)) |
|---|
| 889 | ENDIF |
|---|
| 890 | ENDIF |
|---|
| 891 | |
|---|
| 892 | ! Set swaero_diag=true if at least one of the concerned variables are defined |
|---|
| 893 | IF (nomvar=='topswad' .OR. nomvar=='topswai' .OR. nomvar=='solswad' .OR. nomvar=='solswai' ) THEN |
|---|
| 894 | IF ( flag_var(iff)<=lev_files(iff) ) THEN |
|---|
| 895 | swaero_diag=.TRUE. |
|---|
| 896 | END IF |
|---|
| 897 | END IF |
|---|
| 898 | END SUBROUTINE histdef2d_old |
|---|
| 899 | |
|---|
| 900 | SUBROUTINE histdef2d (iff,var) |
|---|
| 901 | |
|---|
| 902 | USE ioipsl |
|---|
| 903 | USE dimphy |
|---|
| 904 | USE mod_phys_lmdz_para |
|---|
| 905 | USE iophy |
|---|
| 906 | |
|---|
| 907 | IMPLICIT NONE |
|---|
| 908 | |
|---|
| 909 | INCLUDE "dimensions.h" |
|---|
| 910 | INCLUDE "temps.h" |
|---|
| 911 | INCLUDE "clesphys.h" |
|---|
| 912 | |
|---|
| 913 | INTEGER :: iff |
|---|
| 914 | TYPE(ctrl_out) :: var |
|---|
| 915 | |
|---|
| 916 | REAL zstophym |
|---|
| 917 | CHARACTER(LEN=20) :: typeecrit |
|---|
| 918 | |
|---|
| 919 | ! ug On récupère le type écrit de la structure: |
|---|
| 920 | ! Assez moche, à refaire si meilleure méthode... |
|---|
| 921 | IF (INDEX(var%type_ecrit(iff), "once") > 0) THEN |
|---|
| 922 | typeecrit = 'once' |
|---|
| 923 | ELSE IF(INDEX(var%type_ecrit(iff), "t_min") > 0) THEN |
|---|
| 924 | typeecrit = 't_min(X)' |
|---|
| 925 | ELSE IF(INDEX(var%type_ecrit(iff), "t_max") > 0) THEN |
|---|
| 926 | typeecrit = 't_max(X)' |
|---|
| 927 | ELSE IF(INDEX(var%type_ecrit(iff), "inst") > 0) THEN |
|---|
| 928 | typeecrit = 'inst(X)' |
|---|
| 929 | ELSE |
|---|
| 930 | typeecrit = type_ecri_files(iff) |
|---|
| 931 | ENDIF |
|---|
| 932 | |
|---|
| 933 | IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN |
|---|
| 934 | zstophym=zoutm(iff) |
|---|
| 935 | ELSE |
|---|
| 936 | zstophym=zdtime |
|---|
| 937 | ENDIF |
|---|
| 938 | |
|---|
| 939 | ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def |
|---|
| 940 | CALL conf_physoutputs(var%name, var%flag) |
|---|
| 941 | |
|---|
| 942 | IF(.NOT.clef_stations(iff)) THEN |
|---|
| 943 | IF ( var%flag(iff)<=lev_files(iff) ) THEN |
|---|
| 944 | CALL histdef (nid_files(iff), var%name, var%description, var%unit, & |
|---|
| 945 | iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, & |
|---|
| 946 | typeecrit, zstophym,zoutm(iff)) |
|---|
| 947 | ENDIF |
|---|
| 948 | ELSE |
|---|
| 949 | IF ( var%flag(iff)<=lev_files(iff)) THEN |
|---|
| 950 | CALL histdef (nid_files(iff), var%name, var%description, var%unit, & |
|---|
| 951 | npstn,1,nhorim(iff), 1,1,1, -99, 32, & |
|---|
| 952 | typeecrit, zstophym,zoutm(iff)) |
|---|
| 953 | ENDIF |
|---|
| 954 | ENDIF |
|---|
| 955 | |
|---|
| 956 | ! Set swaero_diag=true if at least one of the concerned variables are defined |
|---|
| 957 | IF (var%name=='topswad' .OR. var%name=='topswai' .OR. var%name=='solswad' .OR. var%name=='solswai' ) THEN |
|---|
| 958 | IF ( var%flag(iff)<=lev_files(iff) ) THEN |
|---|
| 959 | swaero_diag=.TRUE. |
|---|
| 960 | END IF |
|---|
| 961 | END IF |
|---|
| 962 | END SUBROUTINE histdef2d |
|---|
| 963 | |
|---|
| 964 | SUBROUTINE histdef3d_old (iff,lpoint,flag_var,nomvar,titrevar,unitvar) |
|---|
| 965 | |
|---|
| 966 | USE ioipsl |
|---|
| 967 | USE dimphy |
|---|
| 968 | USE mod_phys_lmdz_para |
|---|
| 969 | USE iophy |
|---|
| 970 | |
|---|
| 971 | IMPLICIT NONE |
|---|
| 972 | |
|---|
| 973 | INCLUDE "dimensions.h" |
|---|
| 974 | INCLUDE "temps.h" |
|---|
| 975 | ! INCLUDE "indicesol.h" |
|---|
| 976 | INCLUDE "clesphys.h" |
|---|
| 977 | |
|---|
| 978 | INTEGER :: iff |
|---|
| 979 | LOGICAL :: lpoint |
|---|
| 980 | INTEGER, DIMENSION(nfiles) :: flag_var |
|---|
| 981 | CHARACTER(LEN=20) :: nomvar |
|---|
| 982 | CHARACTER(LEN=*) :: titrevar |
|---|
| 983 | CHARACTER(LEN=*) :: unitvar |
|---|
| 984 | |
|---|
| 985 | REAL zstophym |
|---|
| 986 | |
|---|
| 987 | ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def |
|---|
| 988 | CALL conf_physoutputs(nomvar,flag_var) |
|---|
| 989 | |
|---|
| 990 | IF (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') THEN |
|---|
| 991 | zstophym=zoutm(iff) |
|---|
| 992 | ELSE |
|---|
| 993 | zstophym=zdtime |
|---|
| 994 | ENDIF |
|---|
| 995 | |
|---|
| 996 | IF(.NOT.lpoint) THEN |
|---|
| 997 | IF ( flag_var(iff)<=lev_files(iff) ) THEN |
|---|
| 998 | CALL histdef (nid_files(iff), nomvar, titrevar, unitvar, & |
|---|
| 999 | iim, jj_nb, nhorim(iff), klev, levmin(iff), & |
|---|
| 1000 | levmax(iff)-levmin(iff)+1, nvertm(iff), 32, type_ecri(iff), & |
|---|
| 1001 | zstophym, zoutm(iff)) |
|---|
| 1002 | ENDIF |
|---|
| 1003 | ELSE |
|---|
| 1004 | IF ( flag_var(iff)<=lev_files(iff) ) THEN |
|---|
| 1005 | CALL histdef (nid_files(iff), nomvar, titrevar, unitvar, & |
|---|
| 1006 | npstn,1,nhorim(iff), klev, levmin(iff), & |
|---|
| 1007 | levmax(iff)-levmin(iff)+1, nvertm(iff), 32, & |
|---|
| 1008 | type_ecri(iff), zstophym,zoutm(iff)) |
|---|
| 1009 | ENDIF |
|---|
| 1010 | ENDIF |
|---|
| 1011 | END SUBROUTINE histdef3d_old |
|---|
| 1012 | |
|---|
| 1013 | SUBROUTINE histdef3d (iff,var) |
|---|
| 1014 | |
|---|
| 1015 | USE ioipsl |
|---|
| 1016 | USE dimphy |
|---|
| 1017 | USE mod_phys_lmdz_para |
|---|
| 1018 | USE iophy |
|---|
| 1019 | |
|---|
| 1020 | IMPLICIT NONE |
|---|
| 1021 | |
|---|
| 1022 | INCLUDE "dimensions.h" |
|---|
| 1023 | INCLUDE "temps.h" |
|---|
| 1024 | INCLUDE "clesphys.h" |
|---|
| 1025 | |
|---|
| 1026 | INTEGER :: iff |
|---|
| 1027 | TYPE(ctrl_out) :: var |
|---|
| 1028 | |
|---|
| 1029 | REAL zstophym |
|---|
| 1030 | CHARACTER(LEN=20) :: typeecrit |
|---|
| 1031 | |
|---|
| 1032 | ! ug On récupère le type écrit de la structure: |
|---|
| 1033 | ! Assez moche, à refaire si meilleure méthode... |
|---|
| 1034 | IF (INDEX(var%type_ecrit(iff), "once") > 0) THEN |
|---|
| 1035 | typeecrit = 'once' |
|---|
| 1036 | ELSE IF(INDEX(var%type_ecrit(iff), "t_min") > 0) THEN |
|---|
| 1037 | typeecrit = 't_min(X)' |
|---|
| 1038 | ELSE IF(INDEX(var%type_ecrit(iff), "t_max") > 0) THEN |
|---|
| 1039 | typeecrit = 't_max(X)' |
|---|
| 1040 | ELSE IF(INDEX(var%type_ecrit(iff), "inst") > 0) THEN |
|---|
| 1041 | typeecrit = 'inst(X)' |
|---|
| 1042 | ELSE |
|---|
| 1043 | typeecrit = type_ecri_files(iff) |
|---|
| 1044 | ENDIF |
|---|
| 1045 | |
|---|
| 1046 | |
|---|
| 1047 | ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def |
|---|
| 1048 | CALL conf_physoutputs(var%name,var%flag) |
|---|
| 1049 | |
|---|
| 1050 | IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN |
|---|
| 1051 | zstophym=zoutm(iff) |
|---|
| 1052 | ELSE |
|---|
| 1053 | zstophym=zdtime |
|---|
| 1054 | ENDIF |
|---|
| 1055 | |
|---|
| 1056 | IF(.NOT.clef_stations(iff)) THEN |
|---|
| 1057 | IF ( var%flag(iff)<=lev_files(iff) ) THEN |
|---|
| 1058 | CALL histdef (nid_files(iff), var%name, var%description, var%unit, & |
|---|
| 1059 | iim, jj_nb, nhorim(iff), klev, levmin(iff), & |
|---|
| 1060 | levmax(iff)-levmin(iff)+1, nvertm(iff), 32, typeecrit, & |
|---|
| 1061 | zstophym, zoutm(iff)) |
|---|
| 1062 | ENDIF |
|---|
| 1063 | ELSE |
|---|
| 1064 | IF ( var%flag(iff)<=lev_files(iff)) THEN |
|---|
| 1065 | CALL histdef (nid_files(iff), var%name, var%description, var%unit, & |
|---|
| 1066 | npstn,1,nhorim(iff), klev, levmin(iff), & |
|---|
| 1067 | levmax(iff)-levmin(iff)+1, nvertm(iff), 32, & |
|---|
| 1068 | typeecrit, zstophym,zoutm(iff)) |
|---|
| 1069 | ENDIF |
|---|
| 1070 | ENDIF |
|---|
| 1071 | END SUBROUTINE histdef3d |
|---|
| 1072 | |
|---|
| 1073 | SUBROUTINE conf_physoutputs(nam_var,flag_var) |
|---|
| 1074 | !!! Lecture des noms et niveau de sortie des variables dans output.def |
|---|
| 1075 | ! en utilisant les routines getin de IOIPSL |
|---|
| 1076 | use ioipsl |
|---|
| 1077 | |
|---|
| 1078 | IMPLICIT NONE |
|---|
| 1079 | |
|---|
| 1080 | include 'iniprint.h' |
|---|
| 1081 | |
|---|
| 1082 | CHARACTER(LEN=20) :: nam_var |
|---|
| 1083 | INTEGER, DIMENSION(nfiles) :: flag_var |
|---|
| 1084 | |
|---|
| 1085 | IF(prt_level>10) WRITE(lunout,*)'Avant getin: nam_var flag_var ',nam_var,flag_var(:) |
|---|
| 1086 | CALL getin('flag_'//nam_var,flag_var) |
|---|
| 1087 | CALL getin('name_'//nam_var,nam_var) |
|---|
| 1088 | IF(prt_level>10) WRITE(lunout,*)'Apres getin: nam_var flag_var ',nam_var,flag_var(:) |
|---|
| 1089 | |
|---|
| 1090 | END SUBROUTINE conf_physoutputs |
|---|
| 1091 | |
|---|
| 1092 | SUBROUTINE convers_timesteps(str,dtime,timestep) |
|---|
| 1093 | |
|---|
| 1094 | use ioipsl |
|---|
| 1095 | USE phys_cal_mod |
|---|
| 1096 | |
|---|
| 1097 | IMPLICIT NONE |
|---|
| 1098 | |
|---|
| 1099 | CHARACTER(LEN=20) :: str |
|---|
| 1100 | CHARACTER(LEN=10) :: type |
|---|
| 1101 | INTEGER :: ipos,il |
|---|
| 1102 | real :: ttt,xxx,timestep,dayseconde,dtime |
|---|
| 1103 | parameter (dayseconde=86400.) |
|---|
| 1104 | include "temps.h" |
|---|
| 1105 | include "comconst.h" |
|---|
| 1106 | include "iniprint.h" |
|---|
| 1107 | |
|---|
| 1108 | ipos=scan(str,'0123456789.',.TRUE.) |
|---|
| 1109 | ! |
|---|
| 1110 | il=len_trim(str) |
|---|
| 1111 | WRITE(lunout,*)ipos,il |
|---|
| 1112 | read(str(1:ipos),*) ttt |
|---|
| 1113 | WRITE(lunout,*)ttt |
|---|
| 1114 | type=str(ipos+1:il) |
|---|
| 1115 | |
|---|
| 1116 | |
|---|
| 1117 | IF ( il == ipos ) then |
|---|
| 1118 | type='day' |
|---|
| 1119 | endif |
|---|
| 1120 | |
|---|
| 1121 | IF ( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde |
|---|
| 1122 | IF ( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) then |
|---|
| 1123 | WRITE(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref,mth_len |
|---|
| 1124 | timestep = ttt * dayseconde * mth_len |
|---|
| 1125 | endif |
|---|
| 1126 | IF ( type == 'hours'.or.type == 'hr'.or.type == 'heurs') timestep = ttt * dayseconde / 24. |
|---|
| 1127 | IF ( type == 'mn'.or.type == 'minutes' ) timestep = ttt * 60. |
|---|
| 1128 | IF ( type == 's'.or.type == 'sec'.or.type == 'secondes' ) timestep = ttt |
|---|
| 1129 | IF ( type == 'TS' ) timestep = ttt * dtime |
|---|
| 1130 | |
|---|
| 1131 | WRITE(lunout,*)'type = ',type |
|---|
| 1132 | WRITE(lunout,*)'nb j/h/m = ',ttt |
|---|
| 1133 | WRITE(lunout,*)'timestep(s)=',timestep |
|---|
| 1134 | |
|---|
| 1135 | END SUBROUTINE convers_timesteps |
|---|
| 1136 | |
|---|
| 1137 | END MODULE phys_output_mod |
|---|
| 1138 | |
|---|