/[lmdze]/trunk/Sources/dyn3d/leapfrog.f
ViewVC logotype

Diff of /trunk/Sources/dyn3d/leapfrog.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 29 by guez, Tue Mar 30 10:44:42 2010 UTC revision 40 by guez, Tue Feb 22 13:49:36 2011 UTC
# Line 8  contains Line 8  contains
8    
9      ! From dyn3d/leapfrog.F, version 1.6, 2005/04/13 08:58:34      ! From dyn3d/leapfrog.F, version 1.6, 2005/04/13 08:58:34
10      ! Authors: P. Le Van, L. Fairhead, F. Hourdin      ! Authors: P. Le Van, L. Fairhead, F. Hourdin
11        ! Matsuno-leapfrog scheme.
12    
13        use addfi_m, only: addfi
14        use bilan_dyn_m, only: bilan_dyn
15        use caladvtrac_m, only: caladvtrac
16      USE calfis_m, ONLY: calfis      USE calfis_m, ONLY: calfis
17      USE com_io_dyn, ONLY: histaveid      USE com_io_dyn, ONLY: histaveid
18      USE comconst, ONLY: daysec, dtphys, dtvr      USE comconst, ONLY: daysec, dtphys, dtvr
# Line 23  contains Line 27  contains
27      use filtreg_m, only: filtreg      use filtreg_m, only: filtreg
28      USE guide_m, ONLY: guide      USE guide_m, ONLY: guide
29      use inidissip_m, only: idissip      use inidissip_m, only: idissip
30        use integrd_m, only: integrd
31      USE logic, ONLY: iflag_phys, ok_guide      USE logic, ONLY: iflag_phys, ok_guide
32      USE paramet_m, ONLY: ip1jmp1      USE paramet_m, ONLY: ip1jmp1
     USE pression_m, ONLY: pression  
33      USE pressure_var, ONLY: p3d      USE pressure_var, ONLY: p3d
34      USE temps, ONLY: itau_dyn      USE temps, ONLY: itau_dyn
35    
36      ! Variables dynamiques:      ! Variables dynamiques:
37      REAL vcov((iim + 1) * jjm, llm), ucov(ip1jmp1, llm) ! vents covariants      REAL, intent(inout):: ucov(ip1jmp1, llm) ! vent covariant
38        REAL, intent(inout):: vcov((iim + 1) * jjm, llm) ! vent covariant
39      REAL, intent(inout):: teta(iim + 1, jjm + 1, llm) ! potential temperature      REAL, intent(inout):: teta(iim + 1, jjm + 1, llm) ! potential temperature
40      REAL ps(iim + 1, jjm + 1) ! pression au sol, en Pa      REAL ps(iim + 1, jjm + 1) ! pression au sol, en Pa
   
41      REAL masse(ip1jmp1, llm) ! masse d'air      REAL masse(ip1jmp1, llm) ! masse d'air
42      REAL phis(ip1jmp1) ! geopotentiel au sol      REAL phis(ip1jmp1) ! geopotentiel au sol
43      REAL q(ip1jmp1, llm, nqmx) ! mass fractions of advected fields  
44        REAL, intent(inout):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
45        ! mass fractions of advected fields
46    
47      REAL, intent(in):: time_0      REAL, intent(in):: time_0
48    
49      ! Variables local to the procedure:      ! Variables local to the procedure:
# Line 73  contains Line 80  contains
80    
81      INTEGER itau ! index of the time step of the dynamics, starts at 0      INTEGER itau ! index of the time step of the dynamics, starts at 0
82      INTEGER itaufin      INTEGER itaufin
     INTEGER iday ! jour julien  
83      REAL time ! time of day, as a fraction of day length      REAL time ! time of day, as a fraction of day length
84      real finvmaold(ip1jmp1, llm)      real finvmaold(ip1jmp1, llm)
     LOGICAL:: lafin=.false.  
85      INTEGER l      INTEGER l
   
86      REAL rdayvrai, rdaym_ini      REAL rdayvrai, rdaym_ini
87    
88      ! Variables test conservation energie      ! Variables test conservation energie
# Line 88  contains Line 92  contains
92      ! cree par la dissipation      ! cree par la dissipation
93      REAL dtetaecdt(iim + 1, jjm + 1, llm)      REAL dtetaecdt(iim + 1, jjm + 1, llm)
94      REAL vcont((iim + 1) * jjm, llm), ucont(ip1jmp1, llm)      REAL vcont((iim + 1) * jjm, llm), ucont(ip1jmp1, llm)
95      logical forward, leapf      logical leapf
96      REAL dt      real dt
97    
98      !---------------------------------------------------      !---------------------------------------------------
99    
100      print *, "Call sequence information: leapfrog"      print *, "Call sequence information: leapfrog"
101    
102      itaufin = nday * day_step      itaufin = nday * day_step
103      itau = 0      ! "day_step" is a multiple of "iperiod", therefore "itaufin" is one too
104      iday = day_ini  
     time = time_0  
105      dq = 0.      dq = 0.
106    
107      ! On initialise la pression et la fonction d'Exner :      ! On initialise la pression et la fonction d'Exner :
108      CALL pression(ip1jmp1, ap, bp, ps, p3d)      forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
109      CALL exner_hyb(ps, p3d, pks, pk, pkf)      CALL exner_hyb(ps, p3d, pks, pk, pkf)
110    
111      ! Début de l'integration temporelle :      time_integration: do itau = 0, itaufin - 1
112      outer_loop:do         leapf = mod(itau, iperiod) /= 0
113         if (ok_guide .and. (itaufin - itau - 1) * dtvr > 21600.) &         if (leapf) then
114              call guide(itau, ucov, vcov, teta, q, masse, ps)            dt = 2 * dtvr
115         vcovm1 = vcov         else
116         ucovm1 = ucov            ! Matsuno
117         tetam1 = teta            dt = dtvr
118         massem1 = masse            if (ok_guide .and. (itaufin - itau - 1) * dtvr > 21600.) &
119         psm1 = ps                 call guide(itau, ucov, vcov, teta, q, masse, ps)
120         forward = .TRUE.            vcovm1 = vcov
121         leapf = .FALSE.            ucovm1 = ucov
122         dt = dtvr            tetam1 = teta
123         finvmaold = masse            massem1 = masse
124         CALL filtreg(finvmaold, jjm + 1, llm, - 2, 2, .TRUE., 1)            psm1 = ps
125              finvmaold = masse
126              CALL filtreg(finvmaold, jjm + 1, llm, - 2, 2, .TRUE., 1)
127           end if
128    
129           ! Calcul des tendances dynamiques:
130           CALL geopot(ip1jmp1, teta, pk, pks, phis, phi)
131           CALL caldyn(itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
132                MOD(itau, iconser) == 0, du, dv, dteta, dp, w, pbaru, pbarv, &
133                time_0)
134    
135           ! Calcul des tendances advection des traceurs (dont l'humidité)
136           CALL caladvtrac(q, pbaru, pbarv, p3d, masse, dq, teta, pk)
137    
138           ! Stokage du flux de masse pour traceurs offline:
139           IF (offline) CALL fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, &
140                dtvr, itau)
141    
142           ! integrations dynamique et traceurs:
143           CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, du, dteta, dp, &
144                vcov, ucov, teta, q(:, :, :, :2), ps, masse, finvmaold, dt, leapf)
145    
146           if (.not. leapf) then
147              ! Matsuno backward
148              forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
149              CALL exner_hyb(ps, p3d, pks, pk, pkf)
150    
        do  
151            ! Calcul des tendances dynamiques:            ! Calcul des tendances dynamiques:
152            CALL geopot(ip1jmp1, teta, pk, pks, phis, phi)            CALL geopot(ip1jmp1, teta, pk, pks, phis, phi)
153            CALL caldyn(itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &            CALL caldyn(itau + 1, ucov, vcov, teta, ps, masse, pk, pkf, phis, &
154                 MOD(itau, iconser) == 0, du, dv, dteta, dp, w, pbaru, pbarv, &                 phi, .false., du, dv, dteta, dp, w, pbaru, pbarv, time_0)
                time + iday - day_ini)  
   
           IF (forward .OR. leapf) THEN  
              ! Calcul des tendances advection des traceurs (dont l'humidité)  
              CALL caladvtrac(q, pbaru, pbarv, p3d, masse, dq, teta, pk)  
              IF (offline) THEN  
                 ! Stokage du flux de masse pour traceurs off-line  
                 CALL fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, dtvr, &  
                      itau)  
              ENDIF  
           ENDIF  
155    
156            ! integrations dynamique et traceurs:            ! integrations dynamique et traceurs:
157            CALL integrd(2, vcovm1, ucovm1, tetam1, psm1, massem1, dv, du, &            CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, du, dteta, &
158                 dteta, dq, dp, vcov, ucov, teta, q, ps, masse, phis, &                 dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, finvmaold, &
159                 finvmaold, leapf, dt)                 dtvr, leapf=.false.)
160           end if
           IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys /= 0) THEN  
              ! calcul des tendances physiques:  
              IF (itau + 1 == itaufin) lafin = .TRUE.  
   
              CALL pression(ip1jmp1, ap, bp, ps, p3d)  
              CALL exner_hyb(ps, p3d, pks, pk, pkf)  
   
              rdaym_ini = itau * dtvr / daysec  
              rdayvrai = rdaym_ini + day_ini  
   
              CALL calfis(nqmx, lafin, rdayvrai, time, ucov, vcov, teta, q, &  
                   masse, ps, pk, phis, phi, du, dv, dteta, dq, w, &  
                   dufi, dvfi, dtetafi, dqfi, dpfi)  
   
              ! ajout des tendances physiques:  
              CALL addfi(nqmx, dtphys, ucov, vcov, teta, q, ps, dufi, dvfi, &  
                   dtetafi, dqfi, dpfi)  
           ENDIF  
161    
162            CALL pression(ip1jmp1, ap, bp, ps, p3d)         IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys /= 0) THEN
163            CALL exner_hyb(ps, p3d, pks, pk, pkf)            ! calcul des tendances physiques:
164    
165            IF (MOD(itau + 1, idissip) == 0) THEN            forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
166               ! dissipation horizontale et verticale des petites echelles:            CALL exner_hyb(ps, p3d, pks, pk, pkf)
167    
168               ! calcul de l'energie cinetique avant dissipation            rdaym_ini = itau * dtvr / daysec
169               call covcont(llm, ucov, vcov, ucont, vcont)            rdayvrai = rdaym_ini + day_ini
170               call enercin(vcov, ucov, vcont, ucont, ecin0)            time = REAL(mod(itau, day_step)) / day_step + time_0
171              IF (time > 1.) time = time - 1.
172               ! dissipation  
173               CALL dissip(vcov, ucov, teta, p3d, dvdis, dudis, dtetadis)            CALL calfis(rdayvrai, time, ucov, vcov, teta, q, masse, ps, pk, &
174               ucov=ucov + dudis                 phis, phi, du, dv, dteta, dq, w, dufi, dvfi, dtetafi, dqfi, &
175               vcov=vcov + dvdis                 dpfi, lafin=itau+1==itaufin)
176    
177               ! On rajoute la tendance due à la transformation Ec -> E            ! ajout des tendances physiques:
178               ! thermique créée lors de la dissipation            CALL addfi(nqmx, dtphys, ucov, vcov, teta, q, ps, dufi, dvfi, &
179               call covcont(llm, ucov, vcov, ucont, vcont)                 dtetafi, dqfi, dpfi)
180               call enercin(vcov, ucov, vcont, ucont, ecin)         ENDIF
181               dtetaecdt= (ecin0 - ecin) / pk  
182               dtetadis=dtetadis + dtetaecdt         forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
183               teta=teta + dtetadis         CALL exner_hyb(ps, p3d, pks, pk, pkf)
184    
185               ! Calcul de la valeur moyenne unique de h aux pôles         IF (MOD(itau + 1, idissip) == 0) THEN
186               forall (l = 1: llm)            ! dissipation horizontale et verticale des petites echelles:
187                  teta(:, 1, l) = SUM(aire_2d(:iim, 1) * teta(:iim, 1, l)) &  
188                       / apoln            ! calcul de l'energie cinetique avant dissipation
189                  teta(:, jjm + 1, l) = SUM(aire_2d(:iim, jjm+1) &            call covcont(llm, ucov, vcov, ucont, vcont)
190                       * teta(:iim, jjm + 1, l)) / apols            call enercin(vcov, ucov, vcont, ucont, ecin0)
191               END forall  
192              ! dissipation
193               ps(:, 1) = SUM(aire_2d(:iim, 1) * ps(:iim, 1)) / apoln            CALL dissip(vcov, ucov, teta, p3d, dvdis, dudis, dtetadis)
194               ps(:, jjm + 1) = SUM(aire_2d(:iim, jjm+1) * ps(:iim, jjm + 1)) &            ucov=ucov + dudis
195                    / apols            vcov=vcov + dvdis
196            END IF  
197              ! On rajoute la tendance due à la transformation Ec -> E
198            ! fin de l'intégration dynamique et physique pour le pas "itau"            ! thermique créée lors de la dissipation
199            ! préparation du pas d'intégration suivant            call covcont(llm, ucov, vcov, ucont, vcont)
200              call enercin(vcov, ucov, vcont, ucont, ecin)
201            ! schema matsuno + leapfrog            dtetaecdt= (ecin0 - ecin) / pk
202            IF (forward .OR. leapf) THEN            dtetadis=dtetadis + dtetaecdt
203               itau = itau + 1            teta=teta + dtetadis
204               iday = day_ini + itau / day_step  
205               time = REAL(itau - (iday - day_ini) * day_step) / day_step &            ! Calcul de la valeur moyenne aux pôles :
206                    + time_0            forall (l = 1: llm)
207               IF (time > 1.) THEN               teta(:, 1, l) = SUM(aire_2d(:iim, 1) * teta(:iim, 1, l)) &
208                  time = time - 1.                    / apoln
209                  iday = iday + 1               teta(:, jjm + 1, l) = SUM(aire_2d(:iim, jjm+1) &
210               ENDIF                    * teta(:iim, jjm + 1, l)) / apols
211            ENDIF            END forall
212    
213            IF (itau == itaufin + 1) exit outer_loop            ps(:, 1) = SUM(aire_2d(:iim, 1) * ps(:iim, 1)) / apoln
214              ps(:, jjm + 1) = SUM(aire_2d(:iim, jjm+1) * ps(:iim, jjm + 1)) &
215            IF (MOD(itau, iperiod) == 0 .OR. itau == itaufin) THEN                 / apols
216               ! ecriture du fichier histoire moyenne:         END IF
217               CALL writedynav(histaveid, nqmx, itau, vcov, &  
218                    ucov, teta, pk, phi, q, masse, ps, phis)         IF (MOD(itau + 1, iperiod) == 0) THEN
219               call bilan_dyn(2, dtvr * iperiod, dtvr * day_step * periodav, &            ! Écriture du fichier histoire moyenne:
220                    ps, masse, pk, pbaru, pbarv, teta, phi, ucov, vcov, q)            CALL writedynav(histaveid, nqmx, itau + 1, vcov, ucov, teta, pk, &
221            ENDIF                 phi, q, masse, ps, phis)
222              call bilan_dyn(ps, masse, pk, pbaru, pbarv, teta, phi, ucov, vcov, &
223            IF (itau == itaufin) CALL dynredem1("restart.nc", vcov, ucov, teta, &                 q(:, :, :, 1), dt_app = dtvr * iperiod, &
224                 q, masse, ps, itau=itau_dyn+itaufin)                 dt_cum = dtvr * day_step * periodav)
225           ENDIF
226            ! gestion de l'integration temporelle:      end do time_integration
227            IF (MOD(itau, iperiod) == 0) exit  
228            IF (MOD(itau - 1, iperiod) == 0) THEN      CALL dynredem1("restart.nc", vcov, ucov, teta, q, masse, ps, &
229               IF (forward) THEN           itau=itau_dyn+itaufin)
230                  ! fin du pas forward et debut du pas backward  
231                  forward = .FALSE.      ! Calcul des tendances dynamiques:
232                  leapf = .FALSE.      CALL geopot(ip1jmp1, teta, pk, pks, phis, phi)
233               ELSE      CALL caldyn(itaufin, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
234                  ! fin du pas backward et debut du premier pas leapfrog           MOD(itaufin, iconser) == 0, du, dv, dteta, dp, w, pbaru, pbarv, &
235                  leapf = .TRUE.           time_0)
                 dt = 2. * dtvr  
              END IF  
           ELSE  
              ! pas leapfrog  
              leapf = .TRUE.  
              dt = 2. * dtvr  
           END IF  
        end do  
     end do outer_loop  
236    
237    END SUBROUTINE leapfrog    END SUBROUTINE leapfrog
238    

Legend:
Removed from v.29  
changed lines
  Added in v.40

  ViewVC Help
Powered by ViewVC 1.1.21