--- trunk/dyn3d/leapfrog.f 2014/04/04 11:30:34 96 +++ trunk/dyn3d/leapfrog.f 2018/02/05 10:39:38 254 @@ -4,35 +4,37 @@ contains - SUBROUTINE leapfrog(ucov, vcov, teta, ps, masse, phis, q, time_0) + SUBROUTINE leapfrog(ucov, vcov, teta, ps, masse, phis, q) ! From dyn3d/leapfrog.F, version 1.6, 2005/04/13 08:58:34 revision 616 ! Authors: P. Le Van, L. Fairhead, F. Hourdin - ! Matsuno-leapfrog scheme. + + ! Intégration temporelle du modèle : Matsuno-leapfrog scheme. use addfi_m, only: addfi use bilan_dyn_m, only: bilan_dyn use caladvtrac_m, only: caladvtrac use caldyn_m, only: caldyn USE calfis_m, ONLY: calfis - USE comconst, ONLY: daysec, dtphys, dtvr + USE comconst, ONLY: dtvr USE comgeom, ONLY: aire_2d, apoln, apols + use covcont_m, only: covcont USE disvert_m, ONLY: ap, bp - USE conf_gcm_m, ONLY: day_step, iconser, iperiod, iphysiq, nday, offline, & - iflag_phys, ok_guide, iecri + USE conf_gcm_m, ONLY: day_step, iconser, iperiod, iphysiq, nday, & + iflag_phys, iecri + USE conf_guide_m, ONLY: ok_guide USE dimens_m, ONLY: iim, jjm, llm, nqmx use dissip_m, only: dissip USE dynetat0_m, ONLY: day_ini use dynredem1_m, only: dynredem1 + use enercin_m, only: enercin USE exner_hyb_m, ONLY: exner_hyb - use filtreg_m, only: filtreg - use fluxstokenc_m, only: fluxstokenc + use filtreg_scal_m, only: filtreg_scal use geopot_m, only: geopot USE guide_m, ONLY: guide use inidissip_m, only: idissip use integrd_m, only: integrd use nr_util, only: assert - USE pressure_var, ONLY: p3d USE temps, ONLY: itau_dyn use writedynav_m, only: writedynav use writehist_m, only: writehist @@ -51,8 +53,6 @@ REAL, intent(inout):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx) ! mass fractions of advected fields - REAL, intent(in):: time_0 - ! Local: ! Variables dynamiques: @@ -75,7 +75,7 @@ ! Tendances dynamiques REAL dv((iim + 1) * jjm, llm), dudyn(iim + 1, jjm + 1, llm) REAL dteta(iim + 1, jjm + 1, llm) - real dp((iim + 1) * (jjm + 1)) + real dp(iim + 1, jjm + 1) ! Tendances de la dissipation : REAL dvdis(iim + 1, jjm, llm), dudis(iim + 1, jjm + 1, llm) @@ -86,13 +86,9 @@ REAL dtetafi(iim + 1, jjm + 1, llm), dqfi(iim + 1, jjm + 1, llm, nqmx) ! Variables pour le fichier histoire - INTEGER itau ! index of the time step of the dynamics, starts at 0 INTEGER itaufin - REAL time ! time of day, as a fraction of day length - real finvmaold(iim + 1, jjm + 1, llm) INTEGER l - REAL rdayvrai, rdaym_ini ! Variables test conservation \'energie REAL ecin(iim + 1, jjm + 1, llm), ecin0(iim + 1, jjm + 1, llm) @@ -101,6 +97,10 @@ logical leapf real dt ! time step, in s + REAL p3d(iim + 1, jjm + 1, llm + 1) ! pressure at layer interfaces, in Pa + ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)", + ! for interface "l") + !--------------------------------------------------- print *, "Call sequence information: leapfrog" @@ -111,7 +111,9 @@ ! On initialise la pression et la fonction d'Exner : forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps - CALL exner_hyb(ps, p3d, pks, pk, pkf) + CALL exner_hyb(ps, p3d, pks, pk) + pkf = pk + CALL filtreg_scal(pkf, direct = .true., intensive = .true.) time_integration: do itau = 0, itaufin - 1 leapf = mod(itau, iperiod) /= 0 @@ -120,66 +122,55 @@ else ! Matsuno dt = dtvr - if (ok_guide .and. (itaufin - itau - 1) * dtvr > 21600.) & - call guide(itau, ucov, vcov, teta, q, masse, ps) + if (ok_guide) call guide(itau, ucov, vcov, teta, q(:, :, :, 1), ps) vcovm1 = vcov ucovm1 = ucov tetam1 = teta massem1 = masse psm1 = ps - finvmaold = masse - CALL filtreg(finvmaold, jjm + 1, llm, - 2, 2, .TRUE.) end if ! Calcul des tendances dynamiques: CALL geopot(teta, pk, pks, phis, phi) CALL caldyn(itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, & - dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, & + dudyn, dv, dteta, dp, w, pbaru, pbarv, & conser = MOD(itau, iconser) == 0) CALL caladvtrac(q, pbaru, pbarv, p3d, masse, teta, pk) - ! Stokage du flux de masse pour traceurs offline: - IF (offline) CALL fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, & - dtvr, itau) - ! Int\'egrations dynamique et traceurs: CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, dteta, & - dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, finvmaold, dt, & - leapf) + dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, dt, leapf) + + forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps + CALL exner_hyb(ps, p3d, pks, pk) + pkf = pk + CALL filtreg_scal(pkf, direct = .true., intensive = .true.) if (.not. leapf) then ! Matsuno backward - forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps - CALL exner_hyb(ps, p3d, pks, pk, pkf) - ! Calcul des tendances dynamiques: CALL geopot(teta, pk, pks, phis, phi) CALL caldyn(itau + 1, ucov, vcov, teta, ps, masse, pk, pkf, phis, & - phi, dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, & - conser = .false.) + phi, dudyn, dv, dteta, dp, w, pbaru, pbarv, conser = .false.) ! integrations dynamique et traceurs: CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, & - dteta, dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, & - finvmaold, dtvr, leapf=.false.) - end if - - forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps - CALL exner_hyb(ps, p3d, pks, pk, pkf) + dteta, dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, dtvr, & + leapf=.false.) - IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys /= 0) THEN - ! Calcul des tendances physiques: - - rdaym_ini = itau * dtvr / daysec - rdayvrai = rdaym_ini + day_ini - time = REAL(mod(itau, day_step)) / day_step + time_0 - IF (time > 1.) time = time - 1. + forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps + CALL exner_hyb(ps, p3d, pks, pk) + pkf = pk + CALL filtreg_scal(pkf, direct = .true., intensive = .true.) + end if - CALL calfis(rdayvrai, time, ucov, vcov, teta, q, pk, phis, phi, w, & - dufi, dvfi, dtetafi, dqfi, lafin = itau + 1 == itaufin) + IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys) THEN + CALL calfis(ucov, vcov, teta, q, p3d, pk, phis, phi, w, dufi, dvfi, & + dtetafi, dqfi, dayvrai = itau / day_step + day_ini, & + time = REAL(mod(itau, day_step)) / day_step, & + lafin = itau + 1 == itaufin) - ! Ajout des tendances physiques: CALL addfi(ucov, vcov, teta, q, dufi, dvfi, dtetafi, dqfi) ENDIF @@ -206,7 +197,7 @@ forall (l = 1: llm) teta(:, 1, l) = SUM(aire_2d(:iim, 1) * teta(:iim, 1, l)) & / apoln - teta(:, jjm + 1, l) = SUM(aire_2d(:iim, jjm+1) & + teta(:, jjm + 1, l) = SUM(aire_2d(:iim, jjm + 1) & * teta(:iim, jjm + 1, l)) / apols END forall END IF @@ -221,17 +212,16 @@ IF (MOD(itau + 1, iecri * day_step) == 0) THEN CALL geopot(teta, pk, pks, phis, phi) - CALL writehist(itau, vcov, ucov, teta, phi, q, masse, ps) + CALL writehist(itau, vcov, ucov, teta, phi, masse, ps) END IF end do time_integration - CALL dynredem1("restart.nc", vcov, ucov, teta, q, masse, ps, & - itau = itau_dyn + itaufin) + CALL dynredem1(vcov, ucov, teta, q, masse, ps, itau = itau_dyn + itaufin) ! Calcul des tendances dynamiques: CALL geopot(teta, pk, pks, phis, phi) CALL caldyn(itaufin, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, & - dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, & + dudyn, dv, dteta, dp, w, pbaru, pbarv, & conser = MOD(itaufin, iconser) == 0) END SUBROUTINE leapfrog