--- trunk/phylmd/physiq.f 2014/08/29 13:00:05 103 +++ trunk/Sources/phylmd/physiq.f 2015/04/29 15:47:56 134 @@ -4,7 +4,7 @@ contains - SUBROUTINE physiq(lafin, rdayvrai, time, dtphys, paprs, play, pphi, pphis, & + SUBROUTINE physiq(lafin, dayvrai, time, dtphys, paprs, play, pphi, pphis, & u, v, t, qx, omega, d_u, d_v, d_t, d_qx) ! From phylmd/physiq.F, version 1.22 2006/02/20 09:38:28 @@ -38,6 +38,7 @@ USE dimphy, ONLY: klon USE dimsoil, ONLY: nsoilmx use drag_noro_m, only: drag_noro + use dynetat0_m, only: day_ref, annee_ref USE fcttre, ONLY: foeew, qsatl, qsats, thermcep use fisrtilp_m, only: fisrtilp USE hgardfou_m, ONLY: hgardfou @@ -54,9 +55,10 @@ USE qcheck_m, ONLY: qcheck use radlwsw_m, only: radlwsw use readsulfate_m, only: readsulfate + use readsulfate_preind_m, only: readsulfate_preind use sugwd_m, only: sugwd USE suphec_m, ONLY: ra, rcpd, retv, rg, rlvtt, romega, rsigma, rtt - USE temps, ONLY: annee_ref, day_ref, itau_phy + USE temps, ONLY: itau_phy use unit_nml_m, only: unit_nml USE ymds2ju_m, ONLY: ymds2ju USE yoethf_m, ONLY: r2es, rvtmp2 @@ -64,8 +66,8 @@ logical, intent(in):: lafin ! dernier passage - REAL, intent(in):: rdayvrai - ! (elapsed time since January 1st 0h of the starting year, in days) + integer, intent(in):: dayvrai + ! current day number, based at value 1 on January 1st of annee_ref REAL, intent(in):: time ! heure de la journ\'ee en fraction de jour REAL, intent(in):: dtphys ! pas d'integration pour la physique (seconde) @@ -222,8 +224,8 @@ ! Variables propres a la physique INTEGER, save:: radpas - ! (Radiative transfer computations are made every "radpas" call to - ! "physiq".) + ! Radiative transfer computations are made every "radpas" call to + ! "physiq". REAL radsol(klon) SAVE radsol ! bilan radiatif au sol calcule par code radiatif @@ -392,8 +394,8 @@ REAL zxtsol(klon), zxqsurf(klon), zxsnow(klon), zxfluxlat(klon) - REAL dist, rmu0(klon), fract(klon) - real zlongi + REAL dist, mu0(klon), fract(klon) + real longi REAL z_avant(klon), z_apres(klon), z_factor(klon) REAL za, zb REAL zx_t, zx_qs, zcor @@ -646,10 +648,9 @@ ! on remet le calendrier a zero IF (raz_date) itau_phy = 0 - PRINT *, 'cycle_diurne = ', cycle_diurne CALL printflag(radpas, ok_journe, ok_instan, ok_region) - IF (dtphys * REAL(radpas) > 21600. .AND. cycle_diurne) THEN + IF (dtphys * radpas > 21600. .AND. cycle_diurne) THEN print *, "Au minimum 4 appels par jour si cycle diurne" call abort_gcm('physiq', & "Nombre d'appels au rayonnement insuffisant", 1) @@ -680,7 +681,7 @@ ! Initialisation des sorties call ini_histins(dtphys, ok_instan, nid_ins) - CALL ymds2ju(annee_ref, 1, int(day_ref), 0., date0) + CALL ymds2ju(annee_ref, 1, day_ref, 0., date0) ! Positionner date0 pour initialisation de ORCHIDEE print *, 'physiq date0: ', date0 ENDIF test_firstcal @@ -740,7 +741,7 @@ ! Incrémenter le compteur de la physique itap = itap + 1 - julien = MOD(NINT(rdayvrai), 360) + julien = MOD(dayvrai, 360) if (julien == 0) julien = 360 forall (k = 1: llm) zmasse(:, k) = (paprs(:, k) - paprs(:, k + 1)) / rg @@ -770,13 +771,14 @@ frugs = MAX(frugs, 0.000015) zxrugs = sum(frugs * pctsrf, dim = 2) - ! Calculs nécessaires au calcul de l'albedo dans l'interface + ! Calculs nécessaires au calcul de l'albedo dans l'interface avec + ! la surface. - CALL orbite(REAL(julien), zlongi, dist) + CALL orbite(REAL(julien), longi, dist) IF (cycle_diurne) THEN - CALL zenang(zlongi, time, dtphys * REAL(radpas), rmu0, fract) + CALL zenang(longi, time, dtphys * radpas, mu0, fract) ELSE - rmu0 = -999.999 + mu0 = -999.999 ENDIF ! Calcul de l'abedo moyen par maille @@ -797,7 +799,7 @@ ! Couche limite: CALL clmain(dtphys, itap, pctsrf, pctsrf_new, t_seri, q_seri, u_seri, & - v_seri, julien, rmu0, co2_ppm, ftsol, cdmmax, cdhmax, & + v_seri, julien, mu0, co2_ppm, ftsol, cdmmax, cdhmax, & ksta, ksta_ter, ok_kzmin, ftsoil, qsol, paprs, play, fsnow, fqsurf, & fevap, falbe, falblw, fluxlat, rain_fall, snow_fall, fsolsw, fsollw, & fder, rlat, frugs, firstcal, agesno, rugoro, d_t_vdf, d_q_vdf, & @@ -1227,8 +1229,8 @@ ! Introduce the aerosol direct and first indirect radiative forcings: IF (ok_ade .OR. ok_aie) THEN ! Get sulfate aerosol distribution : - CALL readsulfate(rdayvrai, firstcal, sulfate) - CALL readsulfate_preind(rdayvrai, firstcal, sulfate_pi) + CALL readsulfate(dayvrai, time, firstcal, sulfate) + CALL readsulfate_preind(dayvrai, time, firstcal, sulfate_pi) CALL aeropt(play, paprs, t_seri, sulfate, rhcl, tau_ae, piz_ae, cg_ae, & aerindex) @@ -1250,8 +1252,8 @@ bl95_b1, cldtaupi, re, fl) endif - ! Appeler le rayonnement mais calculer tout d'abord l'albedo du sol. IF (MOD(itaprad, radpas) == 0) THEN + ! Appeler le rayonnement mais calculer tout d'abord l'albedo du sol. DO i = 1, klon albsol(i) = falbe(i, is_oce) * pctsrf(i, is_oce) & + falbe(i, is_lic) * pctsrf(i, is_lic) & @@ -1263,7 +1265,7 @@ + falblw(i, is_sic) * pctsrf(i, is_sic) ENDDO ! Rayonnement (compatible Arpege-IFS) : - CALL radlwsw(dist, rmu0, fract, paprs, play, zxtsol, albsol, & + CALL radlwsw(dist, mu0, fract, paprs, play, zxtsol, albsol, & albsollw, t_seri, q_seri, wo, cldfra, cldemi, cldtau, heat, & heat0, cool, cool0, radsol, albpla, topsw, toplw, solsw, sollw, & sollwdown, topsw0, toplw0, solsw0, sollw0, lwdn0, lwdn, lwup0, & @@ -1271,6 +1273,7 @@ cg_ae, topswad, solswad, cldtaupi, topswai, solswai) itaprad = 0 ENDIF + itaprad = itaprad + 1 ! Ajouter la tendance des rayonnements (tous les pas) @@ -1384,11 +1387,10 @@ d_qt, d_ec) ! Calcul des tendances traceurs - call phytrac(itap, lmt_pas, julien, time, firstcal, lafin, dtphys, u, t, & + call phytrac(itap, lmt_pas, julien, time, firstcal, lafin, dtphys, t, & paprs, play, mfu, mfd, pde_u, pen_d, ycoefh, fm_therm, entr_therm, & - yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, pphis, albsol, rhcl, & - cldfra, rneb, diafra, cldliq, pmflxr, pmflxs, prfl, psfl, da, phi, & - mp, upwd, dnwd, tr_seri, zmasse) + yu1, yv1, ftsol, pctsrf, frac_impa, frac_nucl, pphis, da, phi, mp, & + upwd, dnwd, tr_seri, zmasse) IF (offline) call phystokenc(dtphys, rlon, rlat, t, mfu, mfd, pen_u, & pde_u, pen_d, pde_d, fm_therm, entr_therm, ycoefh, yu1, yv1, ftsol, &