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

Diff of /trunk/libf/dyn3d/leapfrog.f90

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

revision 23 by guez, Mon Dec 14 15:25:16 2009 UTC revision 24 by guez, Wed Mar 3 13:23:49 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
# Line 10  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    
11      ! Version du 10/01/98, avec coordonnees verticales hybrides, avec      ! Version du 10/01/98, avec coordonnées verticales hybrides, avec
12      ! nouveaux operat. dissipation * (gradiv2, divgrad2, nxgraro2)      ! nouveaux opérateurs dissipation "*" (gradiv2, divgrad2, nxgraro2)
13    
14      ! Auteur: P. Le Van /L. Fairhead/F.Hourdin      ! Auteurs : P. Le Van, L. Fairhead, F. Hourdin
15      ! Objet:      ! Objet: nouvelle grille
     ! GCM LMD nouvelle grille  
16    
17      ! ... Dans inigeom, nouveaux calculs pour les elongations cu, cv      ! Dans "inigeom", nouveaux calculs pour les élongations cu, cv
18      ! et possibilite d'appeler une fonction f(y) a derivee tangente      ! et possibilité d'appeler une fonction f(y) à dérivée tangente
19      ! hyperbolique a la place de la fonction a derivee sinusoidale.      ! hyperbolique à la place de la fonction à dérivée sinusoïdale.
20    
21      ! ... Possibilité de choisir le schéma pour l'advection de      ! Possibilité de choisir le schéma pour l'advection de
22      ! q, en modifiant iadv dans "traceur.def" (10/02) .      ! q, en modifiant iadv dans "traceur.def".
23    
24      ! Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron, 10/99)      ! Pour Van-Leer + vapeur d'eau saturée, iadv(1)=4.
25      ! Pour Van-Leer iadv=10      ! Pour Van-Leer iadv=10
26    
27      use dimens_m, only: iim, llm, nqmx      use dimens_m, only: iim, llm, nqmx
28      use paramet_m, only: ip1jmp1, ip1jm, ijmllm, ijp1llm, jjp1, iip1      use paramet_m, only: ip1jmp1, ip1jm, ijp1llm, jjp1, iip1
29      use comconst, only: dtvr, daysec, dtphys      use comconst, only: dtvr, daysec, dtphys
30      use comvert, only: ap, bp      use comvert, only: ap, bp
31      use conf_gcm_m, only: day_step, iconser, idissip, iphysiq, iperiod, nday, &      use conf_gcm_m, only: day_step, iconser, idissip, iphysiq, iperiod, nday, &
# Line 54  contains Line 51  contains
51      REAL masse(ip1jmp1, llm) ! masse d'air      REAL masse(ip1jmp1, llm) ! masse d'air
52      REAL phis(ip1jmp1) ! geopotentiel au sol      REAL phis(ip1jmp1) ! geopotentiel au sol
53    
54      REAL time_0      REAL, intent(in):: time_0
55    
56      ! Variables local to the procedure:      ! Variables local to the procedure:
57    
# Line 91  contains Line 88  contains
88      REAL tppn(iim), tpps(iim), tpn, tps      REAL tppn(iim), tpps(iim), tpn, tps
89    
90      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
     integer itaufinp1  
91      INTEGER iday ! jour julien      INTEGER iday ! jour julien
92      REAL time ! time of day, as a fraction of day length      REAL time ! time of day, as a fraction of day length
93    
# Line 103  contains Line 99  contains
99    
100      REAL rdayvrai, rdaym_ini      REAL rdayvrai, rdaym_ini
101    
102      !+jld variables test conservation energie      ! Variables test conservation energie
103      REAL ecin(ip1jmp1, llm), ecin0(ip1jmp1, llm)      REAL ecin(ip1jmp1, llm), ecin0(ip1jmp1, llm)
104      ! Tendance de la temp. potentiel d (theta) / d t due a la      ! Tendance de la temp. potentiel d (theta) / d t due a la
105      ! tansformation d'energie cinetique en energie thermique      ! tansformation d'energie cinetique en energie thermique
# Line 121  contains Line 117  contains
117      print *, "Call sequence information: leapfrog"      print *, "Call sequence information: leapfrog"
118    
119      itaufin = nday * day_step      itaufin = nday * day_step
     itaufinp1 = itaufin + 1  
   
120      itau = 0      itau = 0
121      iday = day_ini      iday = day_ini
122      time = time_0      time = time_0
# Line 131  contains Line 125  contains
125         iday = iday + 1         iday = iday + 1
126      ENDIF      ENDIF
127    
128        dq = 0.
129      ! On initialise la pression et la fonction d'Exner :      ! On initialise la pression et la fonction d'Exner :
     dq=0.  
130      CALL pression(ip1jmp1, ap, bp, ps, p3d)      CALL pression(ip1jmp1, ap, bp, ps, p3d)
131      CALL exner_hyb(ps, p3d, pks, pk, pkf)      CALL exner_hyb(ps, p3d, pks, pk, pkf)
132    
133      ! Debut de l'integration temporelle:      ! Debut de l'integration temporelle:
134      outer_loop:do      outer_loop:do
135         if (ok_guide.and.(itaufin - itau - 1) * dtvr > 21600) then         if (ok_guide.and.(itaufin - itau - 1) * dtvr > 21600.) then
136            call guide(itau, ucov, vcov, teta, q, masse, ps)            call guide(itau, ucov, vcov, teta, q, masse, ps)
137         else         else
138            IF (prt_level > 9) print *, &            IF (prt_level > 9) print *, &
139                 'Attention : on ne guide pas les 6 dernieres heures.'                 'Attention : on ne guide pas les 6 dernières heures.'
140         endif         endif
141    
142         CALL SCOPY(ijmllm, vcov, 1, vcovm1, 1)         CALL SCOPY(ip1jm * llm, vcov, 1, vcovm1, 1)
143         CALL SCOPY(ijp1llm, ucov, 1, ucovm1, 1)         CALL SCOPY(ijp1llm, ucov, 1, ucovm1, 1)
144         CALL SCOPY(ijp1llm, teta, 1, tetam1, 1)         CALL SCOPY(ijp1llm, teta, 1, tetam1, 1)
145         CALL SCOPY(ijp1llm, masse, 1, massem1, 1)         CALL SCOPY(ijp1llm, masse, 1, massem1, 1)
# Line 300  contains Line 294  contains
294               ENDIF               ENDIF
295            ENDIF            ENDIF
296    
297            IF (itau == itaufinp1) exit outer_loop            IF (itau == itaufin + 1) exit outer_loop
298    
299            ! ecriture du fichier histoire moyenne:            ! ecriture du fichier histoire moyenne:
300    

Legend:
Removed from v.23  
changed lines
  Added in v.24

  ViewVC Help
Powered by ViewVC 1.1.21