/[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 3 by guez, Wed Feb 27 13:16:39 2008 UTC revision 27 by guez, Thu Mar 25 14:29:07 2010 UTC
# Line 1  Line 1 
1  module leapfrog_m  module leapfrog_m
2    
   ! This module is clean: no C preprocessor directive, no include line.  
   
3    IMPLICIT NONE    IMPLICIT NONE
4    
5  contains  contains
6    
7    SUBROUTINE leapfrog(ucov, vcov, teta, ps, masse, phis, nq, q, clesphy0, &    SUBROUTINE leapfrog(ucov, vcov, teta, ps, masse, phis, q, time_0)
        time_0)  
   
     ! From dyn3d/leapfrog.F, version 1.6 2005/04/13 08:58:34  
8    
9      ! Version du 10/01/98, avec coordonnees verticales hybrides, avec      ! From dyn3d/leapfrog.F, version 1.6, 2005/04/13 08:58:34
10      ! nouveaux operat. dissipation * (gradiv2, divgrad2, nxgraro2)      ! Authors: P. Le Van, L. Fairhead, F. Hourdin
11    
12      ! Auteur: P. Le Van /L. Fairhead/F.Hourdin      USE calfis_m, ONLY: calfis
13      ! Objet:      USE com_io_dyn, ONLY: histaveid
14      ! GCM LMD nouvelle grille      USE comconst, ONLY: daysec, dtphys, dtvr
15        USE comgeom, ONLY: aire, apoln, apols
16      ! ... Dans inigeom, nouveaux calculs pour les elongations cu, cv      USE comvert, ONLY: ap, bp
17      ! et possibilite d'appeler une fonction f(y) a derivee tangente      USE conf_gcm_m, ONLY: day_step, iconser, iperiod, iphysiq, nday, offline, &
18      ! hyperbolique a la place de la fonction a derivee sinusoidale.           periodav
19        USE dimens_m, ONLY: iim, llm, nqmx
20      ! ... Possibilite de choisir le shema pour l'advection de      USE dynetat0_m, ONLY: day_ini
21      ! q, en modifiant iadv dans "traceur.def" (10/02) .      use dynredem1_m, only: dynredem1
22        USE exner_hyb_m, ONLY: exner_hyb
23      ! Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron, 10/99)      use filtreg_m, only: filtreg
24      ! Pour Van-Leer iadv=10      USE guide_m, ONLY: guide
25        use inidissip_m, only: idissip
26      use dimens_m, only: iim, llm, nqmx      USE logic, ONLY: iflag_phys, ok_guide
27      use paramet_m, only: ip1jmp1, ip1jm, llmp1, ijmllm, ijp1llm, jjp1, iip1, &      USE paramet_m, ONLY: iip1, ip1jm, ip1jmp1, jjp1
28           iip2      USE pression_m, ONLY: pression
29      use comconst, only: dtvr, daysec, dtphys      USE pressure_var, ONLY: p3d
30      use comvert, only: ap, bp      USE temps, ONLY: dt, itau_dyn
     use conf_gcm_m, only: day_step, iconser, idissip, iphysiq, iperiod, nday, &  
          offline, periodav  
     use logic, only: ok_guide, apdiss, apphys, conser, forward, iflag_phys, &  
          leapf, statcl  
     use comgeom  
     use serre  
     use temps, only: itaufin, day_ini, dt  
     use iniprint, only: prt_level  
     use com_io_dyn  
     use abort_gcm_m, only: abort_gcm  
     use ener  
     use calfis_m, only: calfis  
     use exner_hyb_m, only: exner_hyb  
     use guide_m, only: guide  
     use pression_m, only: pression  
   
     integer nq  
   
     INTEGER longcles  
     PARAMETER (longcles = 20)  
     REAL clesphy0(longcles)  
31    
32      ! variables dynamiques      ! Variables dynamiques:
33      REAL vcov(ip1jm, llm), ucov(ip1jmp1, llm) ! vents covariants      REAL vcov(ip1jm, llm), ucov(ip1jmp1, llm) ! vents covariants
34      REAL teta(ip1jmp1, llm) ! temperature potentielle      REAL teta(ip1jmp1, llm) ! temperature potentielle
35        REAL ps(ip1jmp1) ! pression au sol, en Pa
36    
37        REAL masse(ip1jmp1, llm) ! masse d'air
38        REAL phis(ip1jmp1) ! geopotentiel au sol
39      REAL q(ip1jmp1, llm, nqmx) ! mass fractions of advected fields      REAL q(ip1jmp1, llm, nqmx) ! mass fractions of advected fields
40      REAL ps(ip1jmp1) ! pression au sol      REAL, intent(in):: time_0
41      REAL p(ip1jmp1, llmp1) ! pression aux interfac.des couches  
42        ! Variables local to the procedure:
43    
44        ! Variables dynamiques:
45    
46      REAL pks(ip1jmp1) ! exner au sol      REAL pks(ip1jmp1) ! exner au sol
47      REAL pk(ip1jmp1, llm) ! exner au milieu des couches      REAL pk(ip1jmp1, llm) ! exner au milieu des couches
48      REAL pkf(ip1jmp1, llm) ! exner filt.au milieu des couches      REAL pkf(ip1jmp1, llm) ! exner filt.au milieu des couches
     REAL masse(ip1jmp1, llm) ! masse d'air  
     REAL phis(ip1jmp1) ! geopotentiel au sol  
49      REAL phi(ip1jmp1, llm) ! geopotential      REAL phi(ip1jmp1, llm) ! geopotential
50      REAL w(ip1jmp1, llm) ! vitesse verticale      REAL w(ip1jmp1, llm) ! vitesse verticale
51    
# Line 93  contains Line 73  contains
73    
74      REAL tppn(iim), tpps(iim), tpn, tps      REAL tppn(iim), tpps(iim), tpn, tps
75    
76      INTEGER itau, itaufinp1      INTEGER itau ! index of the time step of the dynamics, starts at 0
77        INTEGER itaufin
78      INTEGER iday ! jour julien      INTEGER iday ! jour julien
79      REAL time ! Heure de la journee en fraction d'1 jour      REAL time ! time of day, as a fraction of day length
80        real finvmaold(ip1jmp1, llm)
81      REAL SSUM      LOGICAL:: lafin=.false.
     REAL time_0, finvmaold(ip1jmp1, llm)  
   
     LOGICAL :: lafin=.false.  
82      INTEGER ij, l      INTEGER ij, l
83    
84      REAL rdayvrai, rdaym_ini      REAL rdayvrai, rdaym_ini
     LOGICAL callinigrads  
   
     data callinigrads/.true./  
85    
86      !+jld variables test conservation energie      ! Variables test conservation energie
87      REAL ecin(ip1jmp1, llm), ecin0(ip1jmp1, llm)      REAL ecin(ip1jmp1, llm), ecin0(ip1jmp1, llm)
88      ! Tendance de la temp. potentiel d (theta) / d t due a la      ! Tendance de la temp. potentiel d (theta) / d t due a la
89      ! tansformation d'energie cinetique en energie thermique      ! tansformation d'energie cinetique en energie thermique
90      ! cree par la dissipation      ! cree par la dissipation
91      REAL dtetaecdt(ip1jmp1, llm)      REAL dtetaecdt(ip1jmp1, llm)
92      REAL vcont(ip1jm, llm), ucont(ip1jmp1, llm)      REAL vcont(ip1jm, llm), ucont(ip1jmp1, llm)
93      CHARACTER*15 ztit      logical forward, leapf
     INTEGER ip_ebil_dyn ! PRINT level for energy conserv. diag.  
     SAVE ip_ebil_dyn  
     DATA ip_ebil_dyn /0/  
   
     character(len=*), parameter:: modname = "leapfrog"  
     character*80 abort_message  
   
     logical dissip_conservative  
     save dissip_conservative  
     data dissip_conservative /.true./  
   
     LOGICAL prem  
     save prem  
     DATA prem /.true./  
94    
95      !---------------------------------------------------      !---------------------------------------------------
96    
97      print *, "Call sequence information: leapfrog"      print *, "Call sequence information: leapfrog"
98    
99      itaufin = nday * day_step      itaufin = nday * day_step
     itaufinp1 = itaufin + 1  
   
100      itau = 0      itau = 0
101      iday = day_ini      iday = day_ini
102      time = time_0      time = time_0
103      IF (time > 1.) THEN      dq = 0.
        time = time - 1.  
        iday = iday + 1  
     ENDIF  
   
104      ! On initialise la pression et la fonction d'Exner :      ! On initialise la pression et la fonction d'Exner :
105      dq=0.      CALL pression(ip1jmp1, ap, bp, ps, p3d)
106      CALL pression(ip1jmp1, ap, bp, ps, p)      CALL exner_hyb(ps, p3d, pks, pk, pkf)
     CALL exner_hyb(ps, p, pks, pk, pkf)  
   
     ! Debut de l'integration temporelle:  
     do  
        if (ok_guide.and.(itaufin - itau - 1) * dtvr > 21600) then  
           call guide(itau, ucov, vcov, teta, q, masse, ps)  
        else  
           IF (prt_level > 9) print *, &  
                'Attention : on ne guide pas les 6 dernieres heures.'  
        endif  
   
        CALL SCOPY(ijmllm, vcov, 1, vcovm1, 1)  
        CALL SCOPY(ijp1llm, ucov, 1, ucovm1, 1)  
        CALL SCOPY(ijp1llm, teta, 1, tetam1, 1)  
        CALL SCOPY(ijp1llm, masse, 1, massem1, 1)  
        CALL SCOPY(ip1jmp1, ps, 1, psm1, 1)  
107    
108        ! Début de l'integration temporelle :
109        outer_loop:do
110           if (ok_guide .and. (itaufin - itau - 1) * dtvr > 21600.) &
111                call guide(itau, ucov, vcov, teta, q, masse, ps)
112           vcovm1 = vcov
113           ucovm1 = ucov
114           tetam1 = teta
115           massem1 = masse
116           psm1 = ps
117         forward = .TRUE.         forward = .TRUE.
118         leapf = .FALSE.         leapf = .FALSE.
119         dt = dtvr         dt = dtvr
120           finvmaold = masse
        CALL SCOPY(ijp1llm, masse, 1, finvmaold, 1)  
121         CALL filtreg(finvmaold, jjp1, llm, - 2, 2, .TRUE., 1)         CALL filtreg(finvmaold, jjp1, llm, - 2, 2, .TRUE., 1)
122    
123         do         do
124            ! gestion des appels de la physique et des dissipations:            ! Calcul des tendances dynamiques:
   
           apphys = .FALSE.  
           statcl = .FALSE.  
           conser = .FALSE.  
           apdiss = .FALSE.  
   
           IF (MOD(itau, iconser) == 0) conser = .TRUE.  
           IF (MOD(itau + 1, idissip) == 0) apdiss = .TRUE.  
           IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys /= 0) apphys=.TRUE.  
   
           ! calcul des tendances dynamiques:  
   
125            CALL geopot(ip1jmp1, teta, pk, pks, phis, phi)            CALL geopot(ip1jmp1, teta, pk, pks, phis, phi)
   
126            CALL caldyn(itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &            CALL caldyn(itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
127                 conser, du, dv, dteta, dp, w, pbaru, pbarv, &                 MOD(itau, iconser) == 0, du, dv, dteta, dp, w, pbaru, pbarv, &
128                 time + iday - day_ini)                 time + iday - day_ini)
129    
           ! calcul des tendances advection des traceurs (dont l'humidite)  
   
130            IF (forward .OR. leapf) THEN            IF (forward .OR. leapf) THEN
131               CALL caladvtrac(q, pbaru, pbarv, p, masse, dq, teta, pk)               ! Calcul des tendances advection des traceurs (dont l'humidité)
132                 CALL caladvtrac(q, pbaru, pbarv, p3d, masse, dq, teta, pk)
133               IF (offline) THEN               IF (offline) THEN
134                  !maf stokage du flux de masse pour traceurs OFF-LINE                  ! Stokage du flux de masse pour traceurs off-line
135                  CALL fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, dtvr, &                  CALL fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, dtvr, &
136                       itau)                       itau)
137               ENDIF               ENDIF
# Line 206  contains Line 139  contains
139    
140            ! integrations dynamique et traceurs:            ! integrations dynamique et traceurs:
141            CALL integrd(2, vcovm1, ucovm1, tetam1, psm1, massem1, dv, du, &            CALL integrd(2, vcovm1, ucovm1, tetam1, psm1, massem1, dv, du, &
142                 dteta, dq, dp, vcov, ucov, teta, q, ps, masse, phis, finvmaold)                 dteta, dq, dp, vcov, ucov, teta, q, ps, masse, phis, &
143                   finvmaold, leapf)
           ! calcul des tendances physiques:  
144    
145            IF (apphys) THEN            IF (MOD(itau + 1, iphysiq) == 0 .AND. iflag_phys /= 0) THEN
146                 ! calcul des tendances physiques:
147               IF (itau + 1 == itaufin) lafin = .TRUE.               IF (itau + 1 == itaufin) lafin = .TRUE.
148    
149               CALL pression(ip1jmp1, ap, bp, ps, p)               CALL pression(ip1jmp1, ap, bp, ps, p3d)
150               CALL exner_hyb(ps, p, pks, pk, pkf)               CALL exner_hyb(ps, p3d, pks, pk, pkf)
151    
152               rdaym_ini = itau * dtvr / daysec               rdaym_ini = itau * dtvr / daysec
153               rdayvrai = rdaym_ini + day_ini               rdayvrai = rdaym_ini + day_ini
154    
155               ! Interface avec les routines de phylmd (phymars ...)               CALL calfis(nqmx, lafin, rdayvrai, time, ucov, vcov, teta, q, &
156                      masse, ps, pk, phis, phi, du, dv, dteta, dq, w, &
157               ! Diagnostique de conservation de l'énergie : initialisation                    dufi, dvfi, dtetafi, dqfi, dpfi)
              IF (ip_ebil_dyn >= 1) THEN  
                 ztit='bil dyn'  
                 CALL diagedyn(ztit, 2, 1, 1, dtphys &  
                      , ucov, vcov, ps, p, pk, teta, q(:, :, 1), q(:, :, 2))  
              ENDIF  
   
              CALL calfis(nq, lafin, rdayvrai, time, ucov, vcov, teta, q, &  
                   masse, ps, p, pk, phis, phi, du, dv, dteta, dq, w, &  
                   clesphy0, dufi, dvfi, dtetafi, dqfi, dpfi)  
158    
159               ! ajout des tendances physiques:               ! ajout des tendances physiques:
160               CALL addfi(nqmx, dtphys, &               CALL addfi(nqmx, dtphys, &
161                    ucov, vcov, teta, q, ps, &                    ucov, vcov, teta, q, ps, &
162                    dufi, dvfi, dtetafi, dqfi, dpfi)                    dufi, dvfi, dtetafi, dqfi, dpfi)
   
              ! Diagnostique de conservation de l'énergie : difference  
              IF (ip_ebil_dyn >= 1) THEN  
                 ztit = 'bil phys'  
                 CALL diagedyn(ztit, 2, 1, 1, dtphys, ucov, vcov, ps, p, pk, &  
                      teta, q(:, :, 1), q(:, :, 2))  
              ENDIF  
163            ENDIF            ENDIF
164    
165            CALL pression(ip1jmp1, ap, bp, ps, p)            CALL pression(ip1jmp1, ap, bp, ps, p3d)
166            CALL exner_hyb(ps, p, pks, pk, pkf)            CALL exner_hyb(ps, p3d, pks, pk, pkf)
167    
168            ! dissipation horizontale et verticale des petites echelles:            IF (MOD(itau + 1, idissip) == 0) THEN
169                 ! dissipation horizontale et verticale des petites echelles:
170    
           IF (apdiss) THEN  
171               ! calcul de l'energie cinetique avant dissipation               ! calcul de l'energie cinetique avant dissipation
172               call covcont(llm, ucov, vcov, ucont, vcont)               call covcont(llm, ucov, vcov, ucont, vcont)
173               call enercin(vcov, ucov, vcont, ucont, ecin0)               call enercin(vcov, ucov, vcont, ucont, ecin0)
174    
175               ! dissipation               ! dissipation
176               CALL dissip(vcov, ucov, teta, p, dvdis, dudis, dtetadis)               CALL dissip(vcov, ucov, teta, p3d, dvdis, dudis, dtetadis)
177               ucov=ucov + dudis               ucov=ucov + dudis
178               vcov=vcov + dvdis               vcov=vcov + dvdis
179    
180               if (dissip_conservative) then               ! On rajoute la tendance due a la transform. Ec -> E
181                  ! On rajoute la tendance due a la transform. Ec -> E               ! therm. cree lors de la dissipation
182                  ! therm. cree lors de la dissipation               call covcont(llm, ucov, vcov, ucont, vcont)
183                  call covcont(llm, ucov, vcov, ucont, vcont)               call enercin(vcov, ucov, vcont, ucont, ecin)
184                  call enercin(vcov, ucov, vcont, ucont, ecin)               dtetaecdt= (ecin0 - ecin) / pk
185                  dtetaecdt= (ecin0 - ecin) / pk               dtetadis=dtetadis + dtetaecdt
                 dtetadis=dtetadis + dtetaecdt  
              endif  
186               teta=teta + dtetadis               teta=teta + dtetadis
187    
188               ! Calcul de la valeur moyenne, unique de h aux poles .....               ! Calcul de la valeur moyenne, unique de h aux poles .....
   
189               DO l = 1, llm               DO l = 1, llm
190                  DO ij = 1, iim                  DO ij = 1, iim
191                     tppn(ij) = aire(ij) * teta(ij, l)                     tppn(ij) = aire(ij) * teta(ij, l)
192                     tpps(ij) = aire(ij + ip1jm) * teta(ij + ip1jm, l)                     tpps(ij) = aire(ij + ip1jm) * teta(ij + ip1jm, l)
193                  ENDDO                  ENDDO
194                  tpn = SSUM(iim, tppn, 1) / apoln                  tpn = SUM(tppn) / apoln
195                  tps = SSUM(iim, tpps, 1) / apols                  tps = SUM(tpps) / apols
196    
197                  DO ij = 1, iip1                  DO ij = 1, iip1
198                     teta(ij, l) = tpn                     teta(ij, l) = tpn
# Line 290  contains Line 204  contains
204                  tppn(ij) = aire(ij) * ps(ij)                  tppn(ij) = aire(ij) * ps(ij)
205                  tpps(ij) = aire(ij + ip1jm) * ps(ij + ip1jm)                  tpps(ij) = aire(ij + ip1jm) * ps(ij + ip1jm)
206               ENDDO               ENDDO
207               tpn = SSUM(iim, tppn, 1) / apoln               tpn = SUM(tppn) / apoln
208               tps = SSUM(iim, tpps, 1) / apols               tps = SUM(tpps) / apols
209    
210               DO ij = 1, iip1               DO ij = 1, iip1
211                  ps(ij) = tpn                  ps(ij) = tpn
212                  ps(ij + ip1jm) = tps                  ps(ij + ip1jm) = tps
213               ENDDO               ENDDO
   
214            END IF            END IF
215    
216            ! fin de l'intégration dynamique et physique pour le pas "itau"            ! fin de l'intégration dynamique et physique pour le pas "itau"
# Line 315  contains Line 228  contains
228               ENDIF               ENDIF
229            ENDIF            ENDIF
230    
231            IF (itau == itaufinp1) then            IF (itau == itaufin + 1) exit outer_loop
              abort_message = 'Simulation finished'  
              call abort_gcm(modname, abort_message, 0)  
           ENDIF  
   
           ! ecriture du fichier histoire moyenne:  
232    
           ! Comment out the following calls when you do not want the output  
           ! files "dyn_hist_ave.nc" and "dynzon.nc"  
233            IF (MOD(itau, iperiod) == 0 .OR. itau == itaufin) THEN            IF (MOD(itau, iperiod) == 0 .OR. itau == itaufin) THEN
234                 ! ecriture du fichier histoire moyenne:
235               CALL writedynav(histaveid, nqmx, itau, vcov, &               CALL writedynav(histaveid, nqmx, itau, vcov, &
236                    ucov, teta, pk, phi, q, masse, ps, phis)                    ucov, teta, pk, phi, q, masse, ps, phis)
237               call bilan_dyn(2, dtvr * iperiod, dtvr * day_step * periodav, &               call bilan_dyn(2, dtvr * iperiod, dtvr * day_step * periodav, &
# Line 332  contains Line 239  contains
239            ENDIF            ENDIF
240    
241            IF (itau == itaufin) THEN            IF (itau == itaufin) THEN
242               CALL dynredem1("restart.nc", 0.0, &               CALL dynredem1("restart.nc", vcov, ucov, teta, q, masse, ps, &
243                    vcov, ucov, teta, q, nqmx, masse, ps)                    itau=itau_dyn+itaufin)
              CLOSE(99)  
244            ENDIF            ENDIF
245    
246            ! gestion de l'integration temporelle:            ! gestion de l'integration temporelle:
   
247            IF (MOD(itau, iperiod) == 0) exit            IF (MOD(itau, iperiod) == 0) exit
248            IF (MOD(itau - 1, iperiod) == 0) THEN            IF (MOD(itau - 1, iperiod) == 0) THEN
249               IF (forward) THEN               IF (forward) THEN
# Line 351  contains Line 256  contains
256                  dt = 2. * dtvr                  dt = 2. * dtvr
257               END IF               END IF
258            ELSE            ELSE
259               ! ...... pas leapfrog .....               ! pas leapfrog
260               leapf = .TRUE.               leapf = .TRUE.
261               dt = 2. * dtvr               dt = 2. * dtvr
262            END IF            END IF
263         end do         end do
264      end do      end do outer_loop
265    
266    END SUBROUTINE leapfrog    END SUBROUTINE leapfrog
267    

Legend:
Removed from v.3  
changed lines
  Added in v.27

  ViewVC Help
Powered by ViewVC 1.1.21