28 jjmp1,nlevstd,clevstd,rlevstd,
dtime, ok_veget, &
29 type_ocean,
iflag_pbl,iflag_pbl_split,ok_mensuel,ok_journe, &
30 ok_hf,ok_instan,ok_les,ok_ade,ok_aie, read_climoz, &
31 phys_out_filestations, &
32 new_aod, aerosol_couple, flag_aerosol_strat, &
34 d_t, qx, d_qx,
zmasse, ok_sync)
60 INTEGER,
INTENT(IN) :: ivap
61 INTEGER,
DIMENSION(klon),
INTENT(IN) :: lmax_th
62 LOGICAL,
INTENT(IN) :: ok_sync
63 LOGICAL,
DIMENSION(klon, klev),
INTENT(IN) :: ptconv, ptconvth
64 REAL,
INTENT(IN) :: pdtphys
65 REAL,
DIMENSION(klon),
INTENT(IN) :: pphis
66 REAL,
DIMENSION(klon, klev),
INTENT(IN) :: pplay, d_t
67 REAL,
DIMENSION(klon, klev+1),
INTENT(IN) :: paprs
68 REAL,
DIMENSION(klon,klev,nqtot),
INTENT(IN):: qx, d_qx
69 REAL,
DIMENSION(klon, klev),
INTENT(IN) :: zmasse
72 REAL,
DIMENSION(klon),
INTENT(IN) :: rlon
73 REAL,
DIMENSION(klon),
INTENT(IN) :: rlat
74 INTEGER,
INTENT(IN) :: pim
75 INTEGER,
DIMENSION(pim) :: tabij
76 INTEGER,
DIMENSION(pim),
INTENT(IN) :: ipt, jpt
77 REAL,
DIMENSION(pim),
INTENT(IN) :: plat, plon
78 REAL,
DIMENSION(pim,2) :: plat_bounds, plon_bounds
81 INTEGER :: nlevSTD, radpas
82 LOGICAL :: ok_mensuel, ok_journe, ok_hf, ok_instan
83 LOGICAL :: ok_LES,ok_ade,ok_aie,flag_aerosol_strat
84 LOGICAL :: new_aod, aerosol_couple
85 INTEGER,
INTENT(IN):: read_climoz
94 REAL :: zjulian_start, zjulian
95 REAL,
DIMENSION(klev) :: Ahyb, Bhyb, Alt
96 CHARACTER(LEN=4),
DIMENSION(nlevSTD) :: clevSTD
97 REAL,
DIMENSION(nlevSTD) :: rlevSTD
98 INTEGER :: nsrf, k, iq, iiq, iff, i, j, ilev
102 INTEGER :: iflag_pbl_split
103 CHARACTER(LEN=4) :: bb2
104 CHARACTER(LEN=2) :: bb3
105 CHARACTER(LEN=6) :: type_ocean
106 INTEGER,
DIMENSION(nbp_lon*jjmp1) :: ndex2d
107 INTEGER,
DIMENSION(nbp_lon*jjmp1*klev) :: ndex3d
108 INTEGER :: imin_ins, imax_ins
109 INTEGER :: jmin_ins, jmax_ins
110 INTEGER,
DIMENSION(nfiles) :: phys_out_levmin, phys_out_levmax
111 INTEGER,
DIMENSION(nfiles) :: phys_out_filelevels
112 CHARACTER(LEN=20),
DIMENSION(nfiles) :: chtimestep = (/
'Default',
'Default',
'Default',
'Default',
'Default', &
113 'Default',
'Default',
'Default',
'Default' /)
114 LOGICAL,
DIMENSION(nfiles) :: phys_out_filekeys
115 LOGICAL,
DIMENSION(nfiles) :: phys_out_filestations
122 REAL,
DIMENSION(nfiles),
SAVE :: phys_out_lonmin = (/ -180., -180., -180., -180., &
123 -180., -180., -180., -180., -180. /)
124 REAL,
DIMENSION(nfiles),
SAVE :: phys_out_lonmax = (/ 180., 180., 180., 180., &
125 180., 180., 180., 180., 180. /)
126 REAL,
DIMENSION(nfiles),
SAVE :: phys_out_latmin = (/ -90., -90., -90., -90., &
127 -90., -90., -90., -90., -90. /)
128 REAL,
DIMENSION(nfiles),
SAVE :: phys_out_latmax = (/ 90., 90., 90., 90., &
129 90., 90., 90., 90., 90. /)
132 INTEGER :: x_an, x_mois, x_jour
134 INTEGER :: ini_an, ini_mois, ini_jour
138 WRITE(
lunout,*)
'Debut phys_output_mod.F90'
215 CALL getin(
'phys_out_regfkey',phys_out_regfkey)
216 CALL getin(
'phys_out_lonmin',phys_out_lonmin)
217 CALL getin(
'phys_out_lonmax',phys_out_lonmax)
218 CALL getin(
'phys_out_latmin',phys_out_latmin)
219 CALL getin(
'phys_out_latmax',phys_out_latmax)
220 phys_out_levmin(:)=
levmin(:)
221 CALL getin(
'phys_out_levmin',
levmin)
222 phys_out_levmax(:)=
levmax(:)
223 CALL getin(
'phys_out_levmax',
levmax)
230 CALL getin(
'phys_out_filelevels',
lev_files)
231 CALL getin(
'phys_out_filetimesteps',chtimestep)
233 CALL getin(
'phys_out_filetypes',
type_ecri)
239 WRITE(
lunout,*)
'phys_out_lonmin=',phys_out_lonmin
240 WRITE(
lunout,*)
'phys_out_lonmax=',phys_out_lonmax
241 WRITE(
lunout,*)
'phys_out_latmin=',phys_out_latmin
242 WRITE(
lunout,*)
'phys_out_latmax=',phys_out_latmax
266 CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
267 CALL ju2ymds(zjulian_start, ini_an, ini_mois, ini_jour, ini_heure)
268 CALL wxios_set_cal(dtime,
calend, x_an, x_mois, x_jour, x_heure, ini_an, &
269 ini_mois, ini_jour, ini_heure )
281 ahyb(k)=(
ap(k)+
ap(k+1))/2.
282 bhyb(k)=(
bp(k)+
bp(k+1))/2.
288 WRITE(
lunout,*)
'Alt approx des couches pour une haut d echelle de 8km = ',alt(1:
klev)
298 IF ( chtimestep(iff).eq.
'Default' )
then
302 ELSE IF (chtimestep(iff).eq.
'-1')
then
303 print*,
'ecrit_files(',iff,
') < 0 so IOIPSL work on different'
304 print*,
'months length'
316 IF (.not. ok_all_xml)
then
318 print*,
'phys_output_open: call wxios_add_file with phys_out_filenames(iff)=',trim(
phys_out_filenames(iff))
325 print*,
'phys_output_open: Declare vertical axes for each file'
328 CALL wxios_add_vaxis(
"presnivs", &
330 CALL wxios_add_vaxis(
"Ahyb", &
332 CALL wxios_add_vaxis(
"Bhyb", &
334 CALL wxios_add_vaxis(
"Alt", &
338 CALL wxios_add_vaxis(
"plev", &
346 IF (phys_out_regfkey(iff))
then
355 IF (
io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
356 IF (
io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1
361 IF (
io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1
362 IF (
io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j
365 WRITE(
lunout,*)
'On stoke le fichier histoire numero ',iff,
' sur ', &
366 imin_ins,imax_ins,jmin_ins,jmax_ins
367 WRITE(
lunout,*)
'longitudes : ', &
373 imin_ins,imax_ins-imin_ins+1, &
374 jmin_ins,jmax_ins-jmin_ins+1, &
384 CALL histbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, &
392 #ifndef CPP_IOIPSL_NO_OUTPUT
404 CALL histvert(
nid_files(iff),
"Alt",
"Height approx for scale heigh of 8km at levels",
"Km", &
425 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
427 'd'//trim(
tname(iq))//
'_vdf', &
428 'Tendance tracer '//
ttext(iiq),
"-" , &
429 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
432 'd'//trim(
tname(iq))//
'_the', &
433 'Tendance tracer '//
ttext(iiq),
"-", &
434 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
437 'd'//trim(
tname(iq))//
'_con', &
438 'Tendance tracer '//
ttext(iiq),
"-", &
439 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
442 'd'//trim(
tname(iq))//
'_lessi_impa', &
443 'Tendance tracer '//
ttext(iiq),
"-", &
444 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
447 'd'//trim(
tname(iq))//
'_lessi_nucl', &
448 'Tendance tracer '//
ttext(iiq),
"-", &
449 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
452 'd'//trim(
tname(iq))//
'_insc', &
453 'Tendance tracer '//
ttext(iiq),
"-", &
454 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
457 'd'//trim(
tname(iq))//
'_bcscav', &
458 'Tendance tracer '//
ttext(iiq),
"-", &
459 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
462 'd'//trim(
tname(iq))//
'_evapls', &
463 'Tendance tracer '//
ttext(iiq),
"-", &
464 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
467 'd'//trim(
tname(iq))//
'_ls', &
468 'Tendance tracer '//
ttext(iiq),
"-", &
469 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
472 'd'//trim(
tname(iq))//
'_trsp', &
473 'Tendance tracer '//
ttext(iiq),
"-", &
474 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
477 'd'//trim(
tname(iq))//
'_sscav', &
478 'Tendance tracer '//
ttext(iiq),
"-", &
479 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
482 'd'//trim(
tname(iq))//
'_sat', &
483 'Tendance tracer '//
ttext(iiq),
"-", &
484 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
487 'd'//trim(
tname(iq))//
'_uscav', &
488 'Tendance tracer '//
ttext(iiq),
"-", &
489 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
492 'cum'//
'd'//trim(
tname(iq))//
'_dry', &
493 'tracer tendency dry deposition'//
ttext(iiq),
"-", &
494 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
498 'Cumulated tracer '//
ttext(iiq),
"-", &
499 (/
'',
'',
'',
'',
'',
'',
'',
'',
'' /))
517 WRITE(
lunout,*)
'phys_output_open: ends here'
533 CHARACTER(LEN=20) :: str
534 CHARACTER(LEN=10) :: type
536 real :: ttt,xxx,timestep,dayseconde,dtime
539 ipos=scan(str,
'0123456789.',.
true.)
542 WRITE(
lunout,*)
"ipos = ", ipos
543 WRITE(
lunout,*)
"il = ", il
544 if (ipos == 0)
call abort_physic(
"convers_timesteps",
"bad str", 1)
545 read(str(1:ipos),*) ttt
550 IF ( il == ipos )
then
554 IF (
type ==
'day'.or.type ==
'days'.or.
type ==
'jours'.or.type ==
'jour' ) timestep = ttt * dayseconde
555 IF (
type ==
'mounths'.or.type ==
'mth'.or.
type ==
'mois' ) then
557 timestep = ttt * dayseconde *
mth_len
559 IF (
type ==
'hours'.or.type ==
'hr'.or.
type ==
'heurs') timestep = ttt * dayseconde / 24.
560 IF (
type ==
'mn'.or.type ==
'minutes' ) timestep = ttt * 60.
561 IF (
type ==
's'.or.type ==
'sec'.or.
type ==
'secondes' ) timestep = ttt
562 IF (
type ==
'TS' ) timestep = ttt * dtime
564 WRITE(
lunout,*)
'type = ',
type
565 WRITE(
lunout,*)
'nb j/h/m = ',ttt
566 WRITE(
lunout,*)
'timestep(s)=',timestep
type(ctrl_out), dimension(:), allocatable, save o_dtr_sat
type(ctrl_out), dimension(:), allocatable, save o_dtr_vdf
character(len=20), dimension(nfiles), save phys_out_filenames
!$Id ***************************************!ECRITURE DU pphis CALL zmasse
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL ymds2ju(annee_ref, 1, day_ref, hour, zjulian)!jyg CALL histbeg_phy("histrac"
real, dimension(:), allocatable, save io_lat
integer, dimension(nfiles), save nid_files
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL solaire RCFC12 RCFC12_act CFC12_ppt!IM ajout CFMIP2 CMIP5 LOGICAL ok_4xCO2atm RCFC12_per CFC12_ppt_per!OM correction du bilan d eau global!OM Correction sur precip KE REAL cvl_corr!OM Fonte calotte dans bilan eau LOGICAL ok_lic_melt!IM simulateur ISCCP INTEGER overlap!IM seuils cdrh REAL cdhmax!IM param stabilite s terres et en dehors REAL f_ri_cd_min!IM MAFo pmagic evap0!Frottement au f_cdrag_oce REAL f_z0qh_oce REAL z0h_seaice INTEGER iflag_z0_oce!Rugoro Real z0min!IM lev_histmth INTEGER lev_histdayNMC Integer lev_histins
type(ctrl_out), dimension(:), allocatable, save o_dtr_sscav
!$Header!integer nvarmx dtime
character(len=20), dimension(nfiles), save phys_out_filetypes
real, dimension(nfiles), save zoutm
subroutine phys_output_open(rlon, rlat, pim, tabij, ipt, jpt, plon, plat, jjmp1, nlevSTD, clevSTD, rlevSTD, dtime, ok_veget, type_ocean, iflag_pbl, iflag_pbl_split, ok_mensuel, ok_journe, ok_hf, ok_instan, ok_LES, ok_ade, ok_aie, read_climoz, phys_out_filestations, new_aod, aerosol_couple, flag_aerosol_strat, pdtphys, paprs, pphis, pplay, lmax_th, ptconv, ptconvth, ivap, d_t, qx, d_qx, zmasse, ok_sync)
logical, save swaero_diag
!$Id iflag_pbl_split common compbl iflag_pbl
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL solaire RCFC12 RCFC12_act CFC12_ppt!IM ajout CFMIP2 CMIP5 LOGICAL ok_4xCO2atm RCFC12_per CFC12_ppt_per!OM correction du bilan d eau global!OM Correction sur precip KE REAL cvl_corr!OM Fonte calotte dans bilan eau LOGICAL ok_lic_melt!IM simulateur ISCCP INTEGER overlap!IM seuils cdrh REAL cdhmax!IM param stabilite s terres et en dehors REAL f_ri_cd_min!IM MAFo pmagic evap0!Frottement au f_cdrag_oce REAL f_z0qh_oce REAL z0h_seaice INTEGER iflag_z0_oce!Rugoro Real z0min!IM lev_histday
type(ctrl_out), dimension(:), allocatable, save o_dtr_lessi_impa
type(ctrl_out), dimension(:), allocatable, save o_dtr_con
type(ctrl_out), dimension(:), allocatable, save o_dtr_uscav
type(ctrl_out), dimension(:), allocatable, save o_dtr_bcscav
type(ctrl_out), dimension(:), allocatable, save o_dtr_trsp
integer, dimension(nfiles), save nhorim
type(ctrl_out), dimension(:), allocatable, save o_dtr_dry
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
type(ctrl_out), dimension(:), allocatable, save o_trac_cum
integer, dimension(:), allocatable, save niadv
logical, dimension(nfiles), save clef_stations
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL nid_tra CALL histvert(nid_tra,"presnivs","Vertical levels","Pa", klev, presnivs, nvert,"down") zsto
integer, dimension(nfiles), save levmin
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL pplay
!FH On elimine toutes les clefs physiques dans la dynamique prt_level
subroutine phys_output_write(itap, pdtphys, paprs, pphis, pplay, lmax_th, aerosol_couple, ok_ade, ok_aie, ivap, new_aod, ok_sync, ptconv, read_climoz, clevSTD, ptconvth, d_t, qx, d_qx, zmasse, flag_aerosol, flag_aerosol_strat, ok_cdnc)
integer, dimension(nfiles), save levmax
!$Header!integer nvarmx parameter(nfmx=10, imx=200, jmx=150, lmx=200, nvarmx=1000) real xd(imx
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL &zphi geo500!IM on interpole a chaque pas de temps le paprs
type(ctrl_out), dimension(:), allocatable, save o_dtr_insc
subroutine convers_timesteps(str, dtime, timestep)
character(len=23), dimension(:), allocatable, save ttext
type(ctrl_out), dimension(:), allocatable, save o_dtr_evapls
real, dimension(:), allocatable, save io_lon
c c zjulian c cym CALL iim cym klev jjmp1
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
character(len=20), dimension(:), allocatable, save tname
character(len=20), dimension(nfiles), save type_ecri
real, dimension(:), allocatable, save ap
type(ctrl_out), dimension(:), allocatable, save o_dtr_lessi_nucl
integer, dimension(nfiles), save nvertap
integer, parameter nfiles
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL pdtphys
type(ctrl_out), dimension(:), allocatable, save o_dtr_ls
real, dimension(nfiles), save ecrit_files
character(len=20), dimension(nfiles), save type_ecri_files
integer, parameter naero_spc
subroutine abort_physic(modname, message, ierr)
character(len=7), dimension(naero_spc), parameter name_aero
integer, dimension(nfiles), save nvertbp
integer, dimension(nfiles), save lev_files
c c zjulian c cym CALL iim cym klev iim cym jjmp1 cym On stoke le fichier bilKP instantanne s jmax_ins print On stoke le fichier bilKP instantanne s s cym cym nid_bilKPins ENDIF c cIM BEG c cIM cf AM BEG region cym CALL histbeg("histbilKP_ins", iim, zx_lon(:, 1), cym.jjmp1, zx_lat(1,:), cym.imin_ins, imax_ins-imin_ins+1, cym.jmin_ins, jmax_ins-jmin_ins+1, cym.itau_phy, zjulian, dtime, cym.nhori, nid_bilKPins) CALL histbeg_phy("histbilKP_ins"
logical, dimension(nfiles), save clef_files
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL solaire RCFC12 RCFC12_act CFC12_ppt!IM ajout CFMIP2 CMIP5 LOGICAL ok_4xCO2atm RCFC12_per CFC12_ppt_per!OM correction du bilan d eau global!OM Correction sur precip KE REAL cvl_corr!OM Fonte calotte dans bilan eau LOGICAL ok_lic_melt!IM simulateur ISCCP INTEGER overlap!IM seuils cdrh REAL cdhmax!IM param stabilite s terres et en dehors REAL f_ri_cd_min!IM MAFo pmagic evap0!Frottement au f_cdrag_oce REAL f_z0qh_oce REAL z0h_seaice INTEGER iflag_z0_oce!Rugoro Real z0min!IM lev_histhf
real, dimension(:), allocatable, save bp
integer, dimension(nfiles), save nvertalt
type(ctrl_out), dimension(:), allocatable, save o_trac
integer, dimension(nfiles), save nvertm
real, dimension(:), allocatable, save presnivs
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
type(ctrl_out), dimension(:), allocatable, save o_dtr_the