--- trunk/libf/dyn3d/gcm.f90 2008/02/27 13:16:39 3 +++ trunk/libf/dyn3d/gcm.f90 2008/04/18 14:45:53 10 @@ -15,7 +15,7 @@ ! Pour Van-Leer plus vapeur d'eau saturée : iadv(1)=4 ! Pour Van-Leer : iadv=10 - USE IOIPSL, only: ioconf_calendar + USE IOIPSL, only: ioconf_calendar, histclo use dimens_m, only: iim, jjm, llm, nqmx use dimphy, only: klon use paramet_m, only: ip1jm, ip1jmp1 @@ -39,6 +39,7 @@ use grid_change, only: dyn_phy, init_dyn_phy use advtrac_m, only: iniadvtrac use leapfrog_m, only: leapfrog + use dynredem0_m, only: dynredem0 IMPLICIT NONE @@ -52,7 +53,7 @@ REAL ps(ip1jmp1) ! pression au sol (Pa) REAL masse(ip1jmp1, llm) ! masse d'air - REAL phis(ip1jmp1) ! géopotentiel au sol + REAL phis(iim + 1, jjm + 1) ! géopotentiel au sol ! Variables pour le fichier histoire : REAL time_0 @@ -99,20 +100,6 @@ ! Lecture du fichier "start.nc" : CALL dynetat0(vcov, ucov, teta, q, masse, ps, phis, time_0) - ! Begin special experiment -!!$ print *, "This is a special experiment." -!!$ print *, "We are setting:" -!!$ print *, "ucov = vcov = 0, q = 0, ps = 101325" -!!$ print *, "We are averaging 'teta' horizontally." -!!$ ucov = 0. -!!$ vcov = 0. -!!$ q = 0. -!!$ ps = 101325. - ! Average teta over all longitudes and latitudes: -!!$ forall(i = 1:llm) teta(:,i) = sum(teta(:,i)) / ip1jmp1 - ! (it would be better to weight each element with an associated - ! surface area) - ! End special experiment ! Lecture des paramètres de contrôle pour la simulation : ! on recalcule éventuellement le pas de temps @@ -204,7 +191,7 @@ print *, "day_ini = ", day_ini print *, "day_end = ", day_end - CALL dynredem0("restart.nc", day_end, phis, nqmx) + CALL dynredem0("restart.nc", day_end, phis) CALL inithist(day_ref, annee_ref, zdtvr, nqmx, histid, histvid, & infile="dyn_hist.nc", t_ops = iecri * daysec, t_wrt = iecri * daysec) CALL initdynav(day_ref, annee_ref, zdtvr, nqmx, histaveid, & @@ -218,4 +205,8 @@ ! Intégration temporelle du modèle : CALL leapfrog(ucov, vcov, teta, ps, masse, phis, nq, q, clesphy0, time_0) + call histclo + print *, 'Simulation finished' + print *, 'Everything is cool' + END PROGRAM gcm