--- trunk/libf/dyn3d/leapfrog.f90 2010/12/21 15:45:48 37 +++ trunk/libf/dyn3d/leapfrog.f90 2011/04/08 12:43:31 43 @@ -11,6 +11,9 @@ ! 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 com_io_dyn, ONLY: histaveid USE comconst, ONLY: daysec, dtphys, dtvr @@ -23,6 +26,7 @@ use dynredem1_m, only: dynredem1 USE exner_hyb_m, ONLY: exner_hyb use filtreg_m, only: filtreg + use geopot_m, only: geopot USE guide_m, ONLY: guide use inidissip_m, only: idissip use integrd_m, only: integrd @@ -34,11 +38,17 @@ ! Variables dynamiques: REAL, intent(inout):: ucov(ip1jmp1, llm) ! vent covariant REAL, intent(inout):: vcov((iim + 1) * jjm, llm) ! vent covariant - REAL, intent(inout):: teta(iim + 1, jjm + 1, llm) ! potential temperature - REAL ps(iim + 1, jjm + 1) ! pression au sol, en Pa + + REAL, intent(inout):: teta(:, :, :) ! (iim + 1, jjm + 1, llm) + ! potential temperature + + REAL, intent(inout):: ps(iim + 1, jjm + 1) ! pression au sol, en Pa REAL masse(ip1jmp1, llm) ! masse d'air REAL phis(ip1jmp1) ! geopotentiel au sol - REAL q(ip1jmp1, llm, nqmx) ! mass fractions of advected fields + + REAL, intent(inout):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx) + ! mass fractions of advected fields + REAL, intent(in):: time_0 ! Variables local to the procedure: @@ -82,10 +92,11 @@ ! Variables test conservation energie REAL ecin(iim + 1, jjm + 1, llm), ecin0(iim + 1, jjm + 1, llm) - ! Tendance de la temp. potentiel d (theta) / d t due a la - ! tansformation d'energie cinetique en energie thermique - ! cree par la dissipation + REAL dtetaecdt(iim + 1, jjm + 1, llm) + ! tendance de la température potentielle due à la tansformation + ! d'énergie cinétique en énergie thermique créée par la dissipation + REAL vcont((iim + 1) * jjm, llm), ucont(ip1jmp1, llm) logical leapf real dt @@ -103,8 +114,7 @@ forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps CALL exner_hyb(ps, p3d, pks, pk, pkf) - ! Début de l'integration temporelle : - do itau = 0, itaufin - 1 + time_integration: do itau = 0, itaufin - 1 leapf = mod(itau, iperiod) /= 0 if (leapf) then dt = 2 * dtvr @@ -136,8 +146,8 @@ dtvr, itau) ! integrations dynamique et traceurs: - CALL integrd(2, vcovm1, ucovm1, tetam1, psm1, massem1, dv, du, dteta, & - dp, vcov, ucov, teta, q, ps, masse, finvmaold, leapf, dt) + CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, du, dteta, dp, & + vcov, ucov, teta, q(:, :, :, :2), ps, masse, finvmaold, dt, leapf) if (.not. leapf) then ! Matsuno backward @@ -150,9 +160,9 @@ phi, .false., du, dv, dteta, dp, w, pbaru, pbarv, time_0) ! integrations dynamique et traceurs: - CALL integrd(2, vcovm1, ucovm1, tetam1, psm1, massem1, dv, du, & - dteta, dp, vcov, ucov, teta, q, ps, masse, finvmaold, .false., & - dtvr) + CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, du, dteta, & + dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, finvmaold, & + dtvr, leapf=.false.) end if IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys /= 0) THEN @@ -212,13 +222,14 @@ END IF IF (MOD(itau + 1, iperiod) == 0) THEN - ! ecriture du fichier histoire moyenne: + ! Écriture du fichier histoire moyenne: CALL writedynav(histaveid, nqmx, itau + 1, vcov, ucov, teta, pk, & phi, q, masse, ps, phis) - call bilan_dyn(2, dtvr * iperiod, dtvr * day_step * periodav, ps, & - masse, pk, pbaru, pbarv, teta, phi, ucov, vcov, q) + call bilan_dyn(ps, masse, pk, pbaru, pbarv, teta, phi, ucov, vcov, & + q(:, :, :, 1), dt_app = dtvr * iperiod, & + dt_cum = dtvr * day_step * periodav) ENDIF - end do + end do time_integration CALL dynredem1("restart.nc", vcov, ucov, teta, q, masse, ps, & itau=itau_dyn+itaufin)