--- trunk/libf/phylmd/physiq.f90 2008/08/05 13:31:32 17 +++ trunk/libf/phylmd/physiq.f90 2010/04/06 17:52:58 32 @@ -10,7 +10,7 @@ contains SUBROUTINE physiq(nq, firstcal, lafin, rdayvrai, gmtime, pdtphys, paprs, & - pplay, pphi, pphis, presnivs, u, v, t, qx, omega, d_u, d_v, & + pplay, pphi, pphis, u, v, t, qx, omega, d_u, d_v, & d_t, d_qx, d_ps, dudyn, PVteta) ! From phylmd/physiq.F, v 1.22 2006/02/20 09:38:28 @@ -23,37 +23,41 @@ !AA - stockage des moyennes des champs necessaires !AA en mode traceur off-line - USE ioipsl, only: ymds2ju, histwrite, histsync - use dimens_m, only: jjm, iim, llm - use indicesol, only: nbsrf, is_ter, is_lic, is_sic, is_oce, & - clnsurf, epsfra - use dimphy, only: klon, nbtr - use conf_gcm_m, only: raz_date, offline, iphysiq - use dimsoil, only: nsoilmx - use temps, only: itau_phy, day_ref, annee_ref, itaufin + use abort_gcm_m, only: abort_gcm + USE calendar, only: ymds2ju use clesphys, only: ecrit_hf, ecrit_ins, ecrit_mth, & cdmmax, cdhmax, & co2_ppm, ecrit_reg, ecrit_tra, ksta, ksta_ter, & ok_kzmin use clesphys2, only: iflag_con, ok_orolf, ok_orodr, nbapp_rad, & cycle_diurne, new_oliq, soil_model - use iniprint, only: prt_level - use abort_gcm_m, only: abort_gcm - use YOMCST, only: rcpd, rtt, rlvtt, rg, ra, rsigma, retv, romega use comgeomphy + use conf_gcm_m, only: raz_date, offline + use conf_phys_m, only: conf_phys use ctherm - use phytrac_m, only: phytrac - use oasis_m - use radepsi - use radopt - use yoethf + use dimens_m, only: jjm, iim, llm + use dimphy, only: klon, nbtr + use dimsoil, only: nsoilmx + use hgardfou_m, only: hgardfou + USE histcom, only: histsync + USE histwrite_m, only: histwrite + use indicesol, only: nbsrf, is_ter, is_lic, is_sic, is_oce, & + clnsurf, epsfra use ini_hist, only: ini_histhf, ini_histday, ini_histins + use iniprint, only: prt_level + use oasis_m use orbite_m, only: orbite, zenang + use ozonecm_m, only: ozonecm use phyetat0_m, only: phyetat0, rlat, rlon - use hgardfou_m, only: hgardfou - use conf_phys_m, only: conf_phys use phyredem_m, only: phyredem + use phystokenc_m, only: phystokenc + use phytrac_m, only: phytrac use qcheck_m, only: qcheck + use radepsi + use radopt + use temps, only: itau_phy, day_ref, annee_ref + use yoethf + use YOMCST, only: rcpd, rtt, rlvtt, rg, ra, rsigma, retv, romega ! Declaration des constantes et des fonctions thermodynamiques : use fcttre, only: thermcep, foeew, qsats, qsatl @@ -81,9 +85,6 @@ REAL pphis(klon) ! input geopotentiel du sol - REAL presnivs(llm) - ! (input pressions approximat. des milieux couches ( en PA)) - REAL u(klon, llm) ! input vitesse dans la direction X (de O a E) en m/s REAL v(klon, llm) ! input vitesse Y (de S a N) en m/s REAL t(klon, llm) ! input temperature (K) @@ -182,18 +183,10 @@ REAL swup0(klon, klevp1), swup(klon, klevp1) SAVE swdn0, swdn, swup0, swup - REAL SWdn200clr(klon), SWdn200(klon) - REAL SWup200clr(klon), SWup200(klon) - SAVE SWdn200clr, SWdn200, SWup200clr, SWup200 - REAL lwdn0(klon, klevp1), lwdn(klon, klevp1) REAL lwup0(klon, klevp1), lwup(klon, klevp1) SAVE lwdn0, lwdn, lwup0, lwup - REAL LWdn200clr(klon), LWdn200(klon) - REAL LWup200clr(klon), LWup200(klon) - SAVE LWdn200clr, LWdn200, LWup200clr, LWup200 - !IM Amip2 ! variables a une pression donnee @@ -208,34 +201,6 @@ '500 ', '400 ', '300 ', '250 ', '200 ', '150 ', '100 ', & '70 ', '50 ', '30 ', '20 ', '10 '/ - real tlevSTD(klon, nlevSTD), qlevSTD(klon, nlevSTD) - real rhlevSTD(klon, nlevSTD), philevSTD(klon, nlevSTD) - real ulevSTD(klon, nlevSTD), vlevSTD(klon, nlevSTD) - real wlevSTD(klon, nlevSTD) - - ! nout : niveau de output des variables a une pression donnee - INTEGER nout - PARAMETER(nout=3) !nout=1 : day; =2 : mth; =3 : NMC - - logical oknondef(klon, nlevSTD, nout) - real tnondef(klon, nlevSTD, nout) - save tnondef - - ! les produits uvSTD, vqSTD, .., T2STD sont calcules - ! a partir des valeurs instantannees toutes les 6 h - ! qui sont moyennees sur le mois - - real uvSTD(klon, nlevSTD) - real vqSTD(klon, nlevSTD) - real vTSTD(klon, nlevSTD) - real wqSTD(klon, nlevSTD) - - real vphiSTD(klon, nlevSTD) - real wTSTD(klon, nlevSTD) - real u2STD(klon, nlevSTD) - real v2STD(klon, nlevSTD) - real T2STD(klon, nlevSTD) - ! prw: precipitable water real prw(klon) @@ -244,7 +209,7 @@ REAL flwp(klon), fiwp(klon) REAL flwc(klon, llm), fiwc(klon, llm) - INTEGER l, kmax, lmax + INTEGER kmax, lmax PARAMETER(kmax=8, lmax=8) INTEGER kmaxm1, lmaxm1 PARAMETER(kmaxm1=kmax-1, lmaxm1=lmax-1) @@ -296,9 +261,6 @@ integer nid_hf, nid_hf3d save nid_hf, nid_hf3d - INTEGER longcles - PARAMETER ( longcles = 20 ) - ! Variables propres a la physique INTEGER, save:: radpas @@ -446,7 +408,6 @@ EXTERNAL conema3 ! convect4.3 EXTERNAL fisrtilp ! schema de condensation a grande echelle (pluie) EXTERNAL nuage ! calculer les proprietes radiatives - EXTERNAL ozonecm ! prescrire l'ozone EXTERNAL radlwsw ! rayonnements solaire et infrarouge EXTERNAL transp ! transport total de l'eau et de l'energie @@ -627,8 +588,6 @@ REAL dudyn(iim+1, jjm + 1, llm) REAL zx_tmp_fi2d(klon) ! variable temporaire grille physique - REAL zx_tmp_fi3d(klon, llm) ! variable temporaire pour champs 3D - REAL zx_tmp_2d(iim, jjm + 1), zx_tmp_3d(iim, jjm + 1, llm) INTEGER, SAVE:: nid_day, nid_ins @@ -656,8 +615,7 @@ INTEGER ip_ebil ! PRINT level for energy conserv. diag. SAVE ip_ebil DATA ip_ebil/0/ - INTEGER if_ebil ! level for energy conserv. dignostics - SAVE if_ebil + INTEGER, SAVE:: if_ebil ! level for energy conservation diagnostics !+jld ec_conser REAL d_t_ec(klon, llm) ! tendance du a la conersion Ec -> E thermique REAL ZRCPD @@ -876,9 +834,9 @@ ! Initialisation des sorties - call ini_histhf(pdtphys, presnivs, nid_hf, nid_hf3d) - call ini_histday(pdtphys, presnivs, ok_journe, nid_day, nq) - call ini_histins(pdtphys, presnivs, ok_instan, nid_ins) + call ini_histhf(pdtphys, nid_hf, nid_hf3d) + call ini_histday(pdtphys, ok_journe, nid_day, nq) + call ini_histins(pdtphys, ok_instan, nid_ins) CALL ymds2ju(annee_ref, 1, int(day_ref), 0., date0) !XXXPB Positionner date0 pour initialisation de ORCHIDEE WRITE(*, *) 'physiq date0 : ', date0 @@ -992,11 +950,10 @@ ! Mettre en action les conditions aux limites (albedo, sst, etc.). ! Prescrire l'ozone et calculer l'albedo sur l'ocean. -!!$ if (nq >= 5) then -!!$ wo = qx(:, :, 5) * zmasse / dobson_u / 1e3 -!!$ else IF (MOD(itap - 1, lmt_pas) == 0) THEN - IF (MOD(itap - 1, lmt_pas) == 0) THEN - CALL ozonecm(REAL(julien), rlat, paprs, wo) + if (nq >= 5) then + wo = qx(:, :, 5) * zmasse / dobson_u / 1e3 + else IF (MOD(itap - 1, lmt_pas) == 0) THEN + wo = ozonecm(REAL(julien), paprs) ENDIF ! Re-evaporer l'eau liquide nuageuse @@ -1284,7 +1241,7 @@ ! (driver commun aux versions 3 et 4) IF (ok_cvl) THEN ! new driver for convectL - CALL concvl (iflag_con, pdtphys, paprs, pplay, t_seri, q_seri, & + CALL concvl(iflag_con, pdtphys, paprs, pplay, t_seri, q_seri, & u_seri, v_seri, tr_seri, ntra, & ema_work1, ema_work2, & d_t_con, d_q_con, d_u_con, d_v_con, d_tr, & @@ -1843,36 +1800,25 @@ , d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec) END IF - !AA Installation de l'interface online-offline pour traceurs - - ! Calcul des tendances traceurs - + ! Calcul des tendances traceurs call phytrac(rnpb, itap, lmt_pas, julien, gmtime, firstcal, lafin, nq-2, & pdtphys, u, v, t, paprs, pplay, pmfu, pmfd, pen_u, pde_u, pen_d, & pde_d, ycoefh, fm_therm, entr_therm, yu1, yv1, ftsol, pctsrf, & - frac_impa, frac_nucl, presnivs, pphis, pphi, albsol, rhcl, cldfra, & + frac_impa, frac_nucl, pphis, pphi, albsol, rhcl, cldfra, & rneb, diafra, cldliq, itop_con, ibas_con, pmflxr, pmflxs, prfl, & psfl, da, phi, mp, upwd, dnwd, tr_seri, zmasse) IF (offline) THEN - - print*, 'Attention on met a 0 les thermiques pour phystoke' - call phystokenc(pdtphys, rlon, rlat, & - t, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, & - fm_therm, entr_therm, & - ycoefh, yu1, yv1, ftsol, pctsrf, & - frac_impa, frac_nucl, & - pphis, airephy, pdtphys, itap) - + call phystokenc(pdtphys, rlon, rlat, t, pmfu, pmfd, pen_u, pde_u, & + pen_d, pde_d, fm_therm, entr_therm, ycoefh, yu1, yv1, ftsol, & + pctsrf, frac_impa, frac_nucl, pphis, airephy, pdtphys, itap) ENDIF ! Calculer le transport de l'eau et de l'energie (diagnostique) + CALL transp(paprs, zxtsol, t_seri, q_seri, u_seri, v_seri, zphi, ve, vq, & + ue, uq) - CALL transp (paprs, zxtsol, & - t_seri, q_seri, u_seri, v_seri, zphi, & - ve, vq, ue, uq) - - !IM diag. bilKP + ! diag. bilKP CALL transp_lay (paprs, zxtsol, & t_seri, q_seri, u_seri, v_seri, zphi, & @@ -1971,7 +1917,7 @@ subroutine write_histday - use grid_change, only: gr_phy_write_3d + use gr_phy_write_3d_m, only: gr_phy_write_3d integer itau_w ! pas de temps ecriture !------------------------------------------------