--- trunk/libf/phylmd/physiq.f90 2008/07/25 19:59:34 13 +++ trunk/libf/phylmd/physiq.f90 2010/04/01 09:07:28 30 @@ -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,16 +23,17 @@ !AA - stockage des moyennes des champs necessaires !AA en mode traceur off-line - USE ioipsl, only: ymds2ju, histwrite, histsync + USE calendar, only: ymds2ju + USE histwrite_m, only: histwrite + USE histcom, only: 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 conf_gcm_m, only: raz_date, offline use dimsoil, only: nsoilmx - use temps, only: itau_phy, day_ref, annee_ref, itaufin - use clesphys, only: ecrit_hf, ecrit_hf2mth, & - ecrit_ins, ecrit_mth, ecrit_day, & + use temps, only: itau_phy, day_ref, annee_ref + use clesphys, only: ecrit_hf, ecrit_ins, ecrit_mth, & cdmmax, cdhmax, & co2_ppm, ecrit_reg, ecrit_tra, ksta, ksta_ter, & ok_kzmin @@ -53,14 +54,20 @@ 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 qcheck_m, only: qcheck + use ozonecm_m, only: ozonecm ! Declaration des constantes et des fonctions thermodynamiques : use fcttre, only: thermcep, foeew, qsats, qsatl ! Variables argument: - INTEGER nq ! input nombre de traceurs (y compris vapeur d'eau) - REAL, intent(in):: rdayvrai ! input numero du jour de l'experience + INTEGER, intent(in):: nq ! nombre de traceurs (y compris vapeur d'eau) + + REAL, intent(in):: rdayvrai + ! (elapsed time since January 1st 0h of the starting year, in days) + REAL, intent(in):: gmtime ! heure de la journée en fraction de jour REAL, intent(in):: pdtphys ! pas d'integration pour la physique (seconde) LOGICAL, intent(in):: firstcal ! first call to "calfis" @@ -68,7 +75,7 @@ REAL, intent(in):: paprs(klon, llm+1) ! (pression pour chaque inter-couche, en Pa) - + REAL, intent(in):: pplay(klon, llm) ! (input pression pour le mileu de chaque couche (en Pa)) @@ -77,9 +84,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) @@ -130,10 +134,8 @@ REAL fluxg(klon) !flux turbulents ocean-atmosphere ! Modele thermique du sol, a activer pour le cycle diurne: - logical ok_veget - save ok_veget - LOGICAL ok_journe ! sortir le fichier journalier - save ok_journe + logical, save:: ok_veget + LOGICAL, save:: ok_journe ! sortir le fichier journalier LOGICAL ok_mensuel ! sortir le fichier mensuel @@ -180,18 +182,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 @@ -206,57 +200,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 - - REAL tsumSTD(klon, nlevSTD, nout) - REAL usumSTD(klon, nlevSTD, nout), vsumSTD(klon, nlevSTD, nout) - REAL wsumSTD(klon, nlevSTD, nout), phisumSTD(klon, nlevSTD, nout) - REAL qsumSTD(klon, nlevSTD, nout), rhsumSTD(klon, nlevSTD, nout) - - SAVE tsumSTD, usumSTD, vsumSTD, wsumSTD, phisumSTD, & - qsumSTD, rhsumSTD - - 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 uvsumSTD(klon, nlevSTD, nout) - real vqsumSTD(klon, nlevSTD, nout) - real vTsumSTD(klon, nlevSTD, nout) - real wqsumSTD(klon, nlevSTD, nout) - - real vphiSTD(klon, nlevSTD) - real wTSTD(klon, nlevSTD) - real u2STD(klon, nlevSTD) - real v2STD(klon, nlevSTD) - real T2STD(klon, nlevSTD) - - real vphisumSTD(klon, nlevSTD, nout) - real wTsumSTD(klon, nlevSTD, nout) - real u2sumSTD(klon, nlevSTD, nout) - real v2sumSTD(klon, nlevSTD, nout) - real T2sumSTD(klon, nlevSTD, nout) - - SAVE uvsumSTD, vqsumSTD, vTsumSTD, wqsumSTD - SAVE vphisumSTD, wTsumSTD, u2sumSTD, v2sumSTD, T2sumSTD - !MI Amip2 - ! prw: precipitable water real prw(klon) @@ -265,7 +208,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) @@ -317,9 +260,6 @@ integer nid_hf, nid_hf3d save nid_hf, nid_hf3d - INTEGER longcles - PARAMETER ( longcles = 20 ) - ! Variables propres a la physique INTEGER, save:: radpas @@ -425,9 +365,6 @@ !IM cf FH pour Tiedtke 080604 REAL rain_tiedtke(klon), snow_tiedtke(klon) - REAL total_rain(klon), nday_rain(klon) - save nday_rain - REAL evap(klon), devap(klon) ! evaporation et sa derivee REAL sens(klon), dsens(klon) ! chaleur sensible et sa derivee REAL dlw(klon) ! derivee infra rouge @@ -459,7 +396,7 @@ REAL albsollw(klon) SAVE albsollw ! albedo du sol total - REAL, SAVE:: wo(klon, llm) ! ozone + REAL, SAVE:: wo(klon, llm) ! column density of ozone in a cell, in kDU ! Declaration des procedures appelees @@ -470,16 +407,9 @@ 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 phyredem ! ecrire l'etat de redemarrage de la physique EXTERNAL radlwsw ! rayonnements solaire et infrarouge EXTERNAL transp ! transport total de l'eau et de l'energie - EXTERNAL ini_undefSTD !initialise a 0 une variable a 1 niveau de pression - - EXTERNAL undefSTD - ! (somme les valeurs definies d'1 var a 1 niveau de pression) - ! Variables locales real clwcon(klon, llm), rnebcon(klon, llm) @@ -627,11 +557,10 @@ save ratqsbas, ratqshaut, ratqs ! Parametres lies au nouveau schema de nuages (SB, PDF) - real fact_cldcon - real facttemps + real, save:: fact_cldcon + real, save:: facttemps logical ok_newmicro save ok_newmicro - save fact_cldcon, facttemps real facteur integer iflag_cldcon @@ -639,10 +568,6 @@ logical ptconv(klon, llm) - ! Variables liees a l'ecriture de la bande histoire physique - - integer itau_w ! pas de temps ecriture = itap + itau_phy - ! Variables locales pour effectuer les appels en serie REAL t_seri(klon, llm), q_seri(klon, llm) @@ -653,7 +578,6 @@ REAL d_tr(klon, llm, nbtr) REAL zx_rh(klon, llm) - INTEGER ndex2d(iim*(jjm + 1)), ndex3d(iim*(jjm + 1)*llm) REAL zustrdr(klon), zvstrdr(klon) REAL zustrli(klon), zvstrli(klon) @@ -663,12 +587,9 @@ 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 nid_day, nid_ins - SAVE nid_day, nid_ins + INTEGER, SAVE:: nid_day, nid_ins REAL ve_lay(klon, llm) ! transport meri. de l'energie a chaque niveau vert. REAL vq_lay(klon, llm) ! transport meri. de l'eau a chaque niveau vert. @@ -693,8 +614,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 @@ -766,6 +686,11 @@ SAVE trmb2 SAVE trmb3 + real zmasse(klon, llm) + ! (column-density of mass of air in a cell, in kg m-2) + + real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2 + !---------------------------------------------------------------- modname = 'physiq' @@ -848,10 +773,7 @@ radpas = NINT( 86400. / pdtphys / nbapp_rad) ! on remet le calendrier a zero - - IF (raz_date == 1) THEN - itau_phy = 0 - ENDIF + IF (raz_date) itau_phy = 0 PRINT *, 'cycle_diurne = ', cycle_diurne @@ -898,7 +820,6 @@ ecrit_ins = NINT(ecrit_ins/pdtphys) ecrit_hf = NINT(ecrit_hf/pdtphys) - ecrit_day = NINT(ecrit_day/pdtphys) ecrit_mth = NINT(ecrit_mth/pdtphys) ecrit_tra = NINT(86400.*ecrit_tra/pdtphys) ecrit_reg = NINT(ecrit_reg/pdtphys) @@ -912,9 +833,9 @@ ! Initialisation des sorties - call ini_histhf(pdtphys, presnivs, nid_hf, nid_hf3d) - call ini_histday(pdtphys, presnivs, ok_journe, nid_day) - 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 @@ -1023,11 +944,15 @@ julien = MOD(NINT(rdayvrai), 360) if (julien == 0) julien = 360 + forall (k = 1: llm) zmasse(:, k) = (paprs(:, k)-paprs(:, k+1)) / rg + ! Mettre en action les conditions aux limites (albedo, sst, etc.). ! Prescrire l'ozone et calculer l'albedo sur l'ocean. - 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 @@ -1287,7 +1212,7 @@ DO k = 1, llm DO i = 1, klon z_avant(i) = z_avant(i) + (q_seri(i, k)+ql_seri(i, k)) & - *(paprs(i, k)-paprs(i, k+1))/RG + *zmasse(i, k) ENDDO ENDDO ENDIF @@ -1315,8 +1240,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, & @@ -1331,8 +1255,7 @@ pmfu=upwd+dnwd ELSE ! ok_cvl ! MAF conema3 ne contient pas les traceurs - CALL conema3 (pdtphys, & - paprs, pplay, t_seri, q_seri, & + CALL conema3 (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, & @@ -1422,7 +1345,7 @@ DO k = 1, llm DO i = 1, klon z_apres(i) = z_apres(i) + (q_seri(i, k)+ql_seri(i, k)) & - *(paprs(i, k)-paprs(i, k+1))/RG + *zmasse(i, k) ENDDO ENDDO DO i = 1, klon @@ -1579,7 +1502,7 @@ do i=1, klon if (d_q_con(i, k) < 0.) then rain_tiedtke(i)=rain_tiedtke(i)-d_q_con(i, k)/pdtphys & - *(paprs(i, k)-paprs(i, k+1))/rg + *zmasse(i, k) endif enddo enddo @@ -1854,16 +1777,14 @@ ENDDO DO k = 1, llm DO i = 1, klon - zustrph(i)=zustrph(i)+(u_seri(i, k)-u(i, k))/pdtphys* & - (paprs(i, k)-paprs(i, k+1))/rg - zvstrph(i)=zvstrph(i)+(v_seri(i, k)-v(i, k))/pdtphys* & - (paprs(i, k)-paprs(i, k+1))/rg + zustrph(i)=zustrph(i)+(u_seri(i, k)-u(i, k))/pdtphys* zmasse(i, k) + zvstrph(i)=zvstrph(i)+(v_seri(i, k)-v(i, k))/pdtphys* zmasse(i, k) ENDDO ENDDO !IM calcul composantes axiales du moment angulaire et couple des montagnes - CALL aaam_bud (27, klon, llm, gmtime, & + CALL aaam_bud(27, klon, llm, gmtime, & ra, rg, romega, & rlat, rlon, pphis, & zustrdr, zustrli, zustrph, & @@ -1885,9 +1806,9 @@ 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) + psfl, da, phi, mp, upwd, dnwd, tr_seri, zmasse) IF (offline) THEN @@ -1947,21 +1868,14 @@ ! SORTIES - !IM Interpolation sur les niveaux de pression du NMC - call calcul_STDlev - !cc prw = eau precipitable DO i = 1, klon prw(i) = 0. DO k = 1, llm - prw(i) = prw(i) + & - q_seri(i, k)*(paprs(i, k)-paprs(i, k+1))/RG + prw(i) = prw(i) + q_seri(i, k)*zmasse(i, k) ENDDO ENDDO - !IM initialisation + calculs divers diag AMIP2 - call calcul_divers - ! Convertir les incrementations en tendances DO k = 1, llm @@ -1985,7 +1899,6 @@ ENDIF ! Sauvegarder les valeurs de t et q a la fin de la physique: - DO k = 1, llm DO i = 1, klon t_ancien(i, k) = t_seri(i, k) @@ -1994,13 +1907,11 @@ ENDDO ! Ecriture des sorties - call write_histhf call write_histday call write_histins ! Si c'est la fin, il faut conserver l'etat de redemarrage - IF (lafin) THEN itau_phy = itau_phy + itap CALL phyredem("restartphy.nc", rlat, rlon, pctsrf, ftsol, & @@ -2014,379 +1925,23 @@ contains - subroutine calcul_STDlev - - ! From phylmd/calcul_STDlev.h, v 1.1 2005/05/25 13:10:09 - - !IM on initialise les champs en debut du jour ou du mois - - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, tsumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, usumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, vsumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, wsumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, phisumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, qsumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, rhsumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, uvsumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, vqsumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, vTsumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, wqsumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, vphisumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, wTsumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, u2sumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, v2sumSTD) - CALL ini_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, & - tnondef, T2sumSTD) - - !IM on interpole sur les niveaux STD de pression a chaque pas de - !temps de la physique - - DO k=1, nlevSTD - - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - t_seri, tlevSTD(:, k)) - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - u_seri, ulevSTD(:, k)) - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - v_seri, vlevSTD(:, k)) - - DO l=1, llm - DO i=1, klon - zx_tmp_fi3d(i, l)=paprs(i, l) - ENDDO !i - ENDDO !l - CALL plevel(klon, llm, .true., zx_tmp_fi3d, rlevSTD(k), & - omega, wlevSTD(:, k)) - - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - zphi/RG, philevSTD(:, k)) - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - qx(:, :, ivap), qlevSTD(:, k)) - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - zx_rh*100., rhlevSTD(:, k)) - - DO l=1, llm - DO i=1, klon - zx_tmp_fi3d(i, l)=u_seri(i, l)*v_seri(i, l) - ENDDO !i - ENDDO !l - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - zx_tmp_fi3d, uvSTD(:, k)) - - DO l=1, llm - DO i=1, klon - zx_tmp_fi3d(i, l)=v_seri(i, l)*q_seri(i, l) - ENDDO !i - ENDDO !l - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - zx_tmp_fi3d, vqSTD(:, k)) - - DO l=1, llm - DO i=1, klon - zx_tmp_fi3d(i, l)=v_seri(i, l)*t_seri(i, l) - ENDDO !i - ENDDO !l - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - zx_tmp_fi3d, vTSTD(:, k)) - - DO l=1, llm - DO i=1, klon - zx_tmp_fi3d(i, l)=omega(i, l)*qx(i, l, ivap) - ENDDO !i - ENDDO !l - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - zx_tmp_fi3d, wqSTD(:, k)) - - DO l=1, llm - DO i=1, klon - zx_tmp_fi3d(i, l)=v_seri(i, l)*zphi(i, l)/RG - ENDDO !i - ENDDO !l - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - zx_tmp_fi3d, vphiSTD(:, k)) - - DO l=1, llm - DO i=1, klon - zx_tmp_fi3d(i, l)=omega(i, l)*t_seri(i, l) - ENDDO !i - ENDDO !l - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - zx_tmp_fi3d, wTSTD(:, k)) - - DO l=1, llm - DO i=1, klon - zx_tmp_fi3d(i, l)=u_seri(i, l)*u_seri(i, l) - ENDDO !i - ENDDO !l - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - zx_tmp_fi3d, u2STD(:, k)) - - DO l=1, llm - DO i=1, klon - zx_tmp_fi3d(i, l)=v_seri(i, l)*v_seri(i, l) - ENDDO !i - ENDDO !l - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - zx_tmp_fi3d, v2STD(:, k)) - - DO l=1, llm - DO i=1, klon - zx_tmp_fi3d(i, l)=t_seri(i, l)*t_seri(i, l) - ENDDO !i - ENDDO !l - CALL plevel(klon, llm, .true., pplay, rlevSTD(k), & - zx_tmp_fi3d, T2STD(:, k)) - - ENDDO !k=1, nlevSTD - - !IM on somme les valeurs definies a chaque pas de temps de la - ! physique ou toutes les 6 heures - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.TRUE. - CALL undefSTD(nlevSTD, itap, tlevSTD, & - ecrit_hf, & - oknondef, tnondef, tsumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, ulevSTD, & - ecrit_hf, & - oknondef, tnondef, usumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, vlevSTD, & - ecrit_hf, & - oknondef, tnondef, vsumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, wlevSTD, & - ecrit_hf, & - oknondef, tnondef, wsumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, philevSTD, & - ecrit_hf, & - oknondef, tnondef, phisumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, qlevSTD, & - ecrit_hf, & - oknondef, tnondef, qsumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, rhlevSTD, & - ecrit_hf, & - oknondef, tnondef, rhsumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, uvSTD, & - ecrit_hf, & - oknondef, tnondef, uvsumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, vqSTD, & - ecrit_hf, & - oknondef, tnondef, vqsumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, vTSTD, & - ecrit_hf, & - oknondef, tnondef, vTsumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, wqSTD, & - ecrit_hf, & - oknondef, tnondef, wqsumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, vphiSTD, & - ecrit_hf, & - oknondef, tnondef, vphisumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, wTSTD, & - ecrit_hf, & - oknondef, tnondef, wTsumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, u2STD, & - ecrit_hf, & - oknondef, tnondef, u2sumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, v2STD, & - ecrit_hf, & - oknondef, tnondef, v2sumSTD) - - oknondef(1:klon, 1:nlevSTD, 1:nout)=.FALSE. - CALL undefSTD(nlevSTD, itap, T2STD, & - ecrit_hf, & - oknondef, tnondef, T2sumSTD) - - !IM on moyenne a la fin du jour ou du mois - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, tsumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, usumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, vsumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, wsumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, phisumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, qsumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, rhsumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, uvsumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, vqsumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, vTsumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, wqsumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, vphisumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, wTsumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, u2sumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, v2sumSTD) - - CALL moy_undefSTD(nlevSTD, itap, & - ecrit_day, ecrit_mth, ecrit_hf2mth, & - tnondef, T2sumSTD) - - !IM interpolation a chaque pas de temps du SWup(clr) et - !SWdn(clr) a 200 hPa - - CALL plevel(klon, klevp1, .true., paprs, 20000., & - swdn0, SWdn200clr) - CALL plevel(klon, klevp1, .false., paprs, 20000., & - swdn, SWdn200) - CALL plevel(klon, klevp1, .false., paprs, 20000., & - swup0, SWup200clr) - CALL plevel(klon, klevp1, .false., paprs, 20000., & - swup, SWup200) - - CALL plevel(klon, klevp1, .false., paprs, 20000., & - lwdn0, LWdn200clr) - CALL plevel(klon, klevp1, .false., paprs, 20000., & - lwdn, LWdn200) - CALL plevel(klon, klevp1, .false., paprs, 20000., & - lwup0, LWup200clr) - CALL plevel(klon, klevp1, .false., paprs, 20000., & - lwup, LWup200) - - end SUBROUTINE calcul_STDlev - - !**************************************************** - - SUBROUTINE calcul_divers - - ! From phylmd/calcul_divers.h, v 1.1 2005/05/25 13:10:09 - - ! initialisations diverses au "debut" du mois - - IF(MOD(itap, ecrit_mth) == 1) THEN - DO i=1, klon - nday_rain(i)=0. - ENDDO - ENDIF - - IF(MOD(itap, ecrit_day) == 0) THEN - !IM calcul total_rain, nday_rain - DO i = 1, klon - total_rain(i)=rain_fall(i)+snow_fall(i) - IF(total_rain(i).GT.0.) nday_rain(i)=nday_rain(i)+1. - ENDDO - ENDIF - - End SUBROUTINE calcul_divers - - !*********************************************** - subroutine write_histday - ! From phylmd/write_histday.h, v 1.3 2005/05/25 13:10:09 - - if (ok_journe) THEN - - ndex2d = 0 - ndex3d = 0 + use grid_change, only: gr_phy_write_3d + integer itau_w ! pas de temps ecriture - ! Champs 2D: + !------------------------------------------------ + if (ok_journe) THEN itau_w = itau_phy + itap - - ! FIN ECRITURE DES CHAMPS 3D - + if (nq <= 4) then + call histwrite(nid_day, "Sigma_O3_Royer", itau_w, & + gr_phy_write_3d(wo) * 1e3) + ! (convert "wo" from kDU to DU) + end if if (ok_sync) then call histsync(nid_day) endif - ENDIF End subroutine write_histday @@ -2397,10 +1952,7 @@ ! From phylmd/write_histhf.h, v 1.5 2005/05/25 13:10:09 - ndex2d = 0 - ndex3d = 0 - - itau_w = itau_phy + itap + !------------------------------------------------ call write_histhf3d @@ -2417,14 +1969,11 @@ ! From phylmd/write_histins.h, v 1.2 2005/05/25 13:10:09 real zout + integer itau_w ! pas de temps ecriture !-------------------------------------------------- IF (ok_instan) THEN - - ndex2d = 0 - ndex3d = 0 - ! Champs 2D: zsto = pdtphys * ecrit_ins @@ -2433,231 +1982,212 @@ i = NINT(zout/zsto) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), pphis, zx_tmp_2d) - CALL histwrite(nid_ins, "phis", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "phis", itau_w, zx_tmp_2d) i = NINT(zout/zsto) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), airephy, zx_tmp_2d) - CALL histwrite(nid_ins, "aire", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "aire", itau_w, zx_tmp_2d) DO i = 1, klon zx_tmp_fi2d(i) = paprs(i, 1) ENDDO CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) - CALL histwrite(nid_ins, "psol", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "psol", itau_w, zx_tmp_2d) DO i = 1, klon zx_tmp_fi2d(i) = rain_fall(i) + snow_fall(i) ENDDO CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) - CALL histwrite(nid_ins, "precip", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "precip", itau_w, zx_tmp_2d) DO i = 1, klon zx_tmp_fi2d(i) = rain_lsc(i) + snow_lsc(i) ENDDO CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) - CALL histwrite(nid_ins, "plul", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "plul", itau_w, zx_tmp_2d) DO i = 1, klon zx_tmp_fi2d(i) = rain_con(i) + snow_con(i) ENDDO CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) - CALL histwrite(nid_ins, "pluc", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "pluc", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zxtsol, zx_tmp_2d) - CALL histwrite(nid_ins, "tsol", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "tsol", itau_w, zx_tmp_2d) !ccIM CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zt2m, zx_tmp_2d) - CALL histwrite(nid_ins, "t2m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "t2m", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zq2m, zx_tmp_2d) - CALL histwrite(nid_ins, "q2m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "q2m", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zu10m, zx_tmp_2d) - CALL histwrite(nid_ins, "u10m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "u10m", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zv10m, zx_tmp_2d) - CALL histwrite(nid_ins, "v10m", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "v10m", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), snow_fall, zx_tmp_2d) - CALL histwrite(nid_ins, "snow", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "snow", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), cdragm, zx_tmp_2d) - CALL histwrite(nid_ins, "cdrm", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "cdrm", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), cdragh, zx_tmp_2d) - CALL histwrite(nid_ins, "cdrh", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "cdrh", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), toplw, zx_tmp_2d) - CALL histwrite(nid_ins, "topl", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "topl", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), evap, zx_tmp_2d) - CALL histwrite(nid_ins, "evap", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "evap", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), solsw, zx_tmp_2d) - CALL histwrite(nid_ins, "sols", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "sols", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sollw, zx_tmp_2d) - CALL histwrite(nid_ins, "soll", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "soll", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sollwdown, zx_tmp_2d) - CALL histwrite(nid_ins, "solldown", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "solldown", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), bils, zx_tmp_2d) - CALL histwrite(nid_ins, "bils", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "bils", itau_w, zx_tmp_2d) zx_tmp_fi2d(1:klon)=-1*sens(1:klon) ! CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), sens, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) - CALL histwrite(nid_ins, "sens", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "sens", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), fder, zx_tmp_2d) - CALL histwrite(nid_ins, "fder", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "fder", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_oce), zx_tmp_2d) - CALL histwrite(nid_ins, "dtsvdfo", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "dtsvdfo", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_ter), zx_tmp_2d) - CALL histwrite(nid_ins, "dtsvdft", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "dtsvdft", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_lic), zx_tmp_2d) - CALL histwrite(nid_ins, "dtsvdfg", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "dtsvdfg", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), d_ts(1, is_sic), zx_tmp_2d) - CALL histwrite(nid_ins, "dtsvdfi", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "dtsvdfi", itau_w, zx_tmp_2d) DO nsrf = 1, nbsrf !XXX zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)*100. CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) CALL histwrite(nid_ins, "pourc_"//clnsurf(nsrf), itau_w, & - zx_tmp_2d, iim*(jjm + 1), ndex2d) + zx_tmp_2d) zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) CALL histwrite(nid_ins, "fract_"//clnsurf(nsrf), itau_w, & - zx_tmp_2d, iim*(jjm + 1), ndex2d) + zx_tmp_2d) zx_tmp_fi2d(1 : klon) = fluxt( 1 : klon, 1, nsrf) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) CALL histwrite(nid_ins, "sens_"//clnsurf(nsrf), itau_w, & - zx_tmp_2d, iim*(jjm + 1), ndex2d) + zx_tmp_2d) zx_tmp_fi2d(1 : klon) = fluxlat( 1 : klon, nsrf) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) CALL histwrite(nid_ins, "lat_"//clnsurf(nsrf), itau_w, & - zx_tmp_2d, iim*(jjm + 1), ndex2d) + zx_tmp_2d) zx_tmp_fi2d(1 : klon) = ftsol( 1 : klon, nsrf) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) CALL histwrite(nid_ins, "tsol_"//clnsurf(nsrf), itau_w, & - zx_tmp_2d, iim*(jjm + 1), ndex2d) + zx_tmp_2d) zx_tmp_fi2d(1 : klon) = fluxu( 1 : klon, 1, nsrf) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) CALL histwrite(nid_ins, "taux_"//clnsurf(nsrf), itau_w, & - zx_tmp_2d, iim*(jjm + 1), ndex2d) + zx_tmp_2d) zx_tmp_fi2d(1 : klon) = fluxv( 1 : klon, 1, nsrf) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) CALL histwrite(nid_ins, "tauy_"//clnsurf(nsrf), itau_w, & - zx_tmp_2d, iim*(jjm + 1), ndex2d) + zx_tmp_2d) zx_tmp_fi2d(1 : klon) = frugs( 1 : klon, nsrf) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) CALL histwrite(nid_ins, "rugs_"//clnsurf(nsrf), itau_w, & - zx_tmp_2d, iim*(jjm + 1), ndex2d) + zx_tmp_2d) zx_tmp_fi2d(1 : klon) = falbe( 1 : klon, nsrf) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zx_tmp_fi2d, zx_tmp_2d) CALL histwrite(nid_ins, "albe_"//clnsurf(nsrf), itau_w, & - zx_tmp_2d, iim*(jjm + 1), ndex2d) + zx_tmp_2d) END DO CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), albsol, zx_tmp_2d) - CALL histwrite(nid_ins, "albs", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "albs", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), albsollw, zx_tmp_2d) - CALL histwrite(nid_ins, "albslw", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "albslw", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), zxrugs, zx_tmp_2d) - CALL histwrite(nid_ins, "rugs", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "rugs", itau_w, zx_tmp_2d) !IM cf. AM 081204 BEG !HBTM2 CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_pblh, zx_tmp_2d) - CALL histwrite(nid_ins, "s_pblh", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "s_pblh", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_pblt, zx_tmp_2d) - CALL histwrite(nid_ins, "s_pblt", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "s_pblt", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_lcl, zx_tmp_2d) - CALL histwrite(nid_ins, "s_lcl", itau_w, zx_tmp_2d, iim*(jjm + 1), ndex2d) + CALL histwrite(nid_ins, "s_lcl", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_capCL, zx_tmp_2d) - CALL histwrite(nid_ins, "s_capCL", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "s_capCL", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_oliqCL, zx_tmp_2d) - CALL histwrite(nid_ins, "s_oliqCL", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "s_oliqCL", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_cteiCL, zx_tmp_2d) - CALL histwrite(nid_ins, "s_cteiCL", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "s_cteiCL", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_therm, zx_tmp_2d) - CALL histwrite(nid_ins, "s_therm", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "s_therm", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb1, zx_tmp_2d) - CALL histwrite(nid_ins, "s_trmb1", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "s_trmb1", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb2, zx_tmp_2d) - CALL histwrite(nid_ins, "s_trmb2", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "s_trmb2", itau_w, zx_tmp_2d) CALL gr_fi_ecrit(1, klon, iim, (jjm + 1), s_trmb3, zx_tmp_2d) - CALL histwrite(nid_ins, "s_trmb3", itau_w, zx_tmp_2d, iim*(jjm + 1), & - ndex2d) + CALL histwrite(nid_ins, "s_trmb3", itau_w, zx_tmp_2d) !IM cf. AM 081204 END ! Champs 3D: CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), t_seri, zx_tmp_3d) - CALL histwrite(nid_ins, "temp", itau_w, zx_tmp_3d, & - iim*(jjm + 1)*llm, ndex3d) + CALL histwrite(nid_ins, "temp", itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), u_seri, zx_tmp_3d) - CALL histwrite(nid_ins, "vitu", itau_w, zx_tmp_3d, & - iim*(jjm + 1)*llm, ndex3d) + CALL histwrite(nid_ins, "vitu", itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), v_seri, zx_tmp_3d) - CALL histwrite(nid_ins, "vitv", itau_w, zx_tmp_3d, & - iim*(jjm + 1)*llm, ndex3d) + CALL histwrite(nid_ins, "vitv", itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), zphi, zx_tmp_3d) - CALL histwrite(nid_ins, "geop", itau_w, zx_tmp_3d, & - iim*(jjm + 1)*llm, ndex3d) + CALL histwrite(nid_ins, "geop", itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), pplay, zx_tmp_3d) - CALL histwrite(nid_ins, "pres", itau_w, zx_tmp_3d, & - iim*(jjm + 1)*llm, ndex3d) + CALL histwrite(nid_ins, "pres", itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), d_t_vdf, zx_tmp_3d) - CALL histwrite(nid_ins, "dtvdf", itau_w, zx_tmp_3d, & - iim*(jjm + 1)*llm, ndex3d) + CALL histwrite(nid_ins, "dtvdf", itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), d_q_vdf, zx_tmp_3d) - CALL histwrite(nid_ins, "dqvdf", itau_w, zx_tmp_3d, & - iim*(jjm + 1)*llm, ndex3d) + CALL histwrite(nid_ins, "dqvdf", itau_w, zx_tmp_3d) if (ok_sync) then call histsync(nid_ins) @@ -2672,34 +2202,30 @@ ! From phylmd/write_histhf3d.h, v 1.2 2005/05/25 13:10:09 - ndex2d = 0 - ndex3d = 0 + integer itau_w ! pas de temps ecriture + + !------------------------------------------------------- itau_w = itau_phy + itap ! Champs 3D: CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), t_seri, zx_tmp_3d) - CALL histwrite(nid_hf3d, "temp", itau_w, zx_tmp_3d, & - iim*(jjm + 1)*llm, ndex3d) + CALL histwrite(nid_hf3d, "temp", itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), qx(1, 1, ivap), zx_tmp_3d) - CALL histwrite(nid_hf3d, "ovap", itau_w, zx_tmp_3d, & - iim*(jjm + 1)*llm, ndex3d) + CALL histwrite(nid_hf3d, "ovap", itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), u_seri, zx_tmp_3d) - CALL histwrite(nid_hf3d, "vitu", itau_w, zx_tmp_3d, & - iim*(jjm + 1)*llm, ndex3d) + CALL histwrite(nid_hf3d, "vitu", itau_w, zx_tmp_3d) CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), v_seri, zx_tmp_3d) - CALL histwrite(nid_hf3d, "vitv", itau_w, zx_tmp_3d, & - iim*(jjm + 1)*llm, ndex3d) + CALL histwrite(nid_hf3d, "vitv", itau_w, zx_tmp_3d) if (nbtr >= 3) then CALL gr_fi_ecrit(llm, klon, iim, (jjm + 1), tr_seri(1, 1, 3), & zx_tmp_3d) - CALL histwrite(nid_hf3d, "O3", itau_w, zx_tmp_3d, iim*(jjm + 1)*llm, & - ndex3d) + CALL histwrite(nid_hf3d, "O3", itau_w, zx_tmp_3d) end if if (ok_sync) then @@ -2710,39 +2236,4 @@ END SUBROUTINE physiq - !**************************************************** - - FUNCTION qcheck(klon, klev, paprs, q, ql, aire) - - ! From phylmd/physiq.F, v 1.22 2006/02/20 09:38:28 - - use YOMCST - IMPLICIT none - - ! Calculer et imprimer l'eau totale. A utiliser pour verifier - ! la conservation de l'eau - - INTEGER klon, klev - REAL, intent(in):: paprs(klon, klev+1) - real q(klon, klev), ql(klon, klev) - REAL aire(klon) - REAL qtotal, zx, qcheck - INTEGER i, k - - zx = 0.0 - DO i = 1, klon - zx = zx + aire(i) - ENDDO - qtotal = 0.0 - DO k = 1, klev - DO i = 1, klon - qtotal = qtotal + (q(i, k)+ql(i, k)) * aire(i) & - *(paprs(i, k)-paprs(i, k+1))/RG - ENDDO - ENDDO - - qcheck = qtotal/zx - - END FUNCTION qcheck - end module physiq_m