/[lmdze]/trunk/dyn3d/leapfrog.f90
ViewVC logotype

Diff of /trunk/dyn3d/leapfrog.f90

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

trunk/dyn3d/leapfrog.f revision 115 by guez, Fri Sep 19 17:36:20 2014 UTC trunk/Sources/dyn3d/leapfrog.f revision 178 by guez, Fri Mar 11 18:47:26 2016 UTC
# Line 4  module leapfrog_m Line 4  module leapfrog_m
4    
5  contains  contains
6    
7    SUBROUTINE leapfrog(ucov, vcov, teta, ps, masse, phis, q, time_0)    SUBROUTINE leapfrog(ucov, vcov, teta, ps, masse, phis, q)
8    
9      ! From dyn3d/leapfrog.F, version 1.6, 2005/04/13 08:58:34 revision 616      ! From dyn3d/leapfrog.F, version 1.6, 2005/04/13 08:58:34 revision 616
10      ! Authors: P. Le Van, L. Fairhead, F. Hourdin      ! Authors: P. Le Van, L. Fairhead, F. Hourdin
11      ! Matsuno-leapfrog scheme.  
12        ! Intégration temporelle du modèle : Matsuno-leapfrog scheme.
13    
14      use addfi_m, only: addfi      use addfi_m, only: addfi
15      use bilan_dyn_m, only: bilan_dyn      use bilan_dyn_m, only: bilan_dyn
16      use caladvtrac_m, only: caladvtrac      use caladvtrac_m, only: caladvtrac
17      use caldyn_m, only: caldyn      use caldyn_m, only: caldyn
18      USE calfis_m, ONLY: calfis      USE calfis_m, ONLY: calfis
19      USE comconst, ONLY: daysec, dtvr      USE comconst, ONLY: dtvr
20      USE comgeom, ONLY: aire_2d, apoln, apols      USE comgeom, ONLY: aire_2d, apoln, apols
21        use covcont_m, only: covcont
22      USE disvert_m, ONLY: ap, bp      USE disvert_m, ONLY: ap, bp
23      USE conf_gcm_m, ONLY: day_step, iconser, iperiod, iphysiq, nday, offline, &      USE conf_gcm_m, ONLY: day_step, iconser, iperiod, iphysiq, nday, offline, &
24           iflag_phys, iecri           iflag_phys, iecri
# Line 26  contains Line 28  contains
28      USE dynetat0_m, ONLY: day_ini      USE dynetat0_m, ONLY: day_ini
29      use dynredem1_m, only: dynredem1      use dynredem1_m, only: dynredem1
30      USE exner_hyb_m, ONLY: exner_hyb      USE exner_hyb_m, ONLY: exner_hyb
31      use filtreg_m, only: filtreg      use filtreg_scal_m, only: filtreg_scal
32      use fluxstokenc_m, only: fluxstokenc      use fluxstokenc_m, only: fluxstokenc
33      use geopot_m, only: geopot      use geopot_m, only: geopot
34      USE guide_m, ONLY: guide      USE guide_m, ONLY: guide
35      use inidissip_m, only: idissip      use inidissip_m, only: idissip
36      use integrd_m, only: integrd      use integrd_m, only: integrd
37      use nr_util, only: assert      use nr_util, only: assert
     USE pressure_var, ONLY: p3d  
38      USE temps, ONLY: itau_dyn      USE temps, ONLY: itau_dyn
39      use writedynav_m, only: writedynav      use writedynav_m, only: writedynav
40      use writehist_m, only: writehist      use writehist_m, only: writehist
# Line 52  contains Line 53  contains
53      REAL, intent(inout):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)      REAL, intent(inout):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
54      ! mass fractions of advected fields      ! mass fractions of advected fields
55    
     REAL, intent(in):: time_0  
   
56      ! Local:      ! Local:
57    
58      ! Variables dynamiques:      ! Variables dynamiques:
# Line 87  contains Line 86  contains
86      REAL dtetafi(iim + 1, jjm + 1, llm), dqfi(iim + 1, jjm + 1, llm, nqmx)      REAL dtetafi(iim + 1, jjm + 1, llm), dqfi(iim + 1, jjm + 1, llm, nqmx)
87    
88      ! Variables pour le fichier histoire      ! Variables pour le fichier histoire
   
89      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
90      INTEGER itaufin      INTEGER itaufin
     REAL time ! time of day, as a fraction of day length  
     real finvmaold(iim + 1, jjm + 1, llm)  
91      INTEGER l      INTEGER l
     REAL rdayvrai, rdaym_ini  
92    
93      ! Variables test conservation \'energie      ! Variables test conservation \'energie
94      REAL ecin(iim + 1, jjm + 1, llm), ecin0(iim + 1, jjm + 1, llm)      REAL ecin(iim + 1, jjm + 1, llm), ecin0(iim + 1, jjm + 1, llm)
# Line 102  contains Line 97  contains
97      logical leapf      logical leapf
98      real dt ! time step, in s      real dt ! time step, in s
99    
100        REAL p3d(iim + 1, jjm + 1, llm+1) ! pressure at layer interfaces, in Pa
101        ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
102        ! for interface "l")
103    
104      !---------------------------------------------------      !---------------------------------------------------
105    
106      print *, "Call sequence information: leapfrog"      print *, "Call sequence information: leapfrog"
# Line 112  contains Line 111  contains
111    
112      ! On initialise la pression et la fonction d'Exner :      ! On initialise la pression et la fonction d'Exner :
113      forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps      forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
114      CALL exner_hyb(ps, p3d, pks, pk, pkf)      CALL exner_hyb(ps, p3d, pks, pk)
115        pkf = pk
116        CALL filtreg_scal(pkf, direct = .true., intensive = .true.)
117    
118      time_integration: do itau = 0, itaufin - 1      time_integration: do itau = 0, itaufin - 1
119         leapf = mod(itau, iperiod) /= 0         leapf = mod(itau, iperiod) /= 0
# Line 127  contains Line 128  contains
128            tetam1 = teta            tetam1 = teta
129            massem1 = masse            massem1 = masse
130            psm1 = ps            psm1 = ps
           finvmaold = masse  
           CALL filtreg(finvmaold, direct = .false., intensive = .false.)  
131         end if         end if
132    
133         ! Calcul des tendances dynamiques:         ! Calcul des tendances dynamiques:
134         CALL geopot(teta, pk, pks, phis, phi)         CALL geopot(teta, pk, pks, phis, phi)
135         CALL caldyn(itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &         CALL caldyn(itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
136              dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, &              dudyn, dv, dteta, dp, w, pbaru, pbarv, &
137              conser = MOD(itau, iconser) == 0)              conser = MOD(itau, iconser) == 0)
138    
139         CALL caladvtrac(q, pbaru, pbarv, p3d, masse, teta, pk)         CALL caladvtrac(q, pbaru, pbarv, p3d, masse, teta, pk)
# Line 145  contains Line 144  contains
144    
145         ! Int\'egrations dynamique et traceurs:         ! Int\'egrations dynamique et traceurs:
146         CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, dteta, &         CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, dteta, &
147              dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, finvmaold, dt, &              dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, dt, leapf)
             leapf)  
148    
149         forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps         forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
150         CALL exner_hyb(ps, p3d, pks, pk, pkf)         CALL exner_hyb(ps, p3d, pks, pk)
151           pkf = pk
152           CALL filtreg_scal(pkf, direct = .true., intensive = .true.)
153    
154         if (.not. leapf) then         if (.not. leapf) then
155            ! Matsuno backward            ! Matsuno backward
156            ! Calcul des tendances dynamiques:            ! Calcul des tendances dynamiques:
157            CALL geopot(teta, pk, pks, phis, phi)            CALL geopot(teta, pk, pks, phis, phi)
158            CALL caldyn(itau + 1, ucov, vcov, teta, ps, masse, pk, pkf, phis, &            CALL caldyn(itau + 1, ucov, vcov, teta, ps, masse, pk, pkf, phis, &
159                 phi, dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, &                 phi, dudyn, dv, dteta, dp, w, pbaru, pbarv, conser = .false.)
                conser = .false.)  
160    
161            ! integrations dynamique et traceurs:            ! integrations dynamique et traceurs:
162            CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, &            CALL integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, dudyn, &
163                 dteta, dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, &                 dteta, dp, vcov, ucov, teta, q(:, :, :, :2), ps, masse, dtvr, &
164                 finvmaold, dtvr, leapf=.false.)                 leapf=.false.)
165    
166            forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps            forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
167            CALL exner_hyb(ps, p3d, pks, pk, pkf)            CALL exner_hyb(ps, p3d, pks, pk)
168              pkf = pk
169              CALL filtreg_scal(pkf, direct = .true., intensive = .true.)
170         end if         end if
171    
172         IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys /= 0) THEN         IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys /= 0) THEN
173            ! Calcul des tendances physiques:            CALL calfis(ucov, vcov, teta, q, p3d, pk, phis, phi, w, dufi, dvfi, &
174                   dtetafi, dqfi, dayvrai = itau / day_step + day_ini, &
175            rdaym_ini = itau * dtvr / daysec                 time = REAL(mod(itau, day_step)) / day_step, &
176            rdayvrai = rdaym_ini + day_ini                 lafin = itau + 1 == itaufin)
           time = REAL(mod(itau, day_step)) / day_step + time_0  
           IF (time > 1.) time = time - 1.  
   
           CALL calfis(rdayvrai, time, ucov, vcov, teta, q, pk, phis, phi, w, &  
                dufi, dvfi, dtetafi, dqfi, lafin = itau + 1 == itaufin)  
177    
           ! Ajout des tendances physiques:  
178            CALL addfi(ucov, vcov, teta, q, dufi, dvfi, dtetafi, dqfi)            CALL addfi(ucov, vcov, teta, q, dufi, dvfi, dtetafi, dqfi)
179         ENDIF         ENDIF
180    
# Line 221  contains Line 216  contains
216    
217         IF (MOD(itau + 1, iecri * day_step) == 0) THEN         IF (MOD(itau + 1, iecri * day_step) == 0) THEN
218            CALL geopot(teta, pk, pks, phis, phi)            CALL geopot(teta, pk, pks, phis, phi)
219            CALL writehist(itau, vcov, ucov, teta, phi, q, masse, ps)            CALL writehist(itau, vcov, ucov, teta, phi, masse, ps)
220         END IF         END IF
221      end do time_integration      end do time_integration
222    
223      CALL dynredem1("restart.nc", vcov, ucov, teta, q, masse, ps, &      CALL dynredem1(vcov, ucov, teta, q, masse, ps, itau = itau_dyn + itaufin)
          itau = itau_dyn + itaufin)  
224    
225      ! Calcul des tendances dynamiques:      ! Calcul des tendances dynamiques:
226      CALL geopot(teta, pk, pks, phis, phi)      CALL geopot(teta, pk, pks, phis, phi)
227      CALL caldyn(itaufin, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &      CALL caldyn(itaufin, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
228           dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, &           dudyn, dv, dteta, dp, w, pbaru, pbarv, &
229           conser = MOD(itaufin, iconser) == 0)           conser = MOD(itaufin, iconser) == 0)
230    
231    END SUBROUTINE leapfrog    END SUBROUTINE leapfrog

Legend:
Removed from v.115  
changed lines
  Added in v.178

  ViewVC Help
Powered by ViewVC 1.1.21