/[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 70 by guez, Mon Jun 24 15:39:52 2013 UTC revision 71 by guez, Mon Jul 8 18:12:18 2013 UTC
# Line 74  contains Line 74  contains
74    
75      ! Tendances dynamiques      ! Tendances dynamiques
76      REAL dv((iim + 1) * jjm, llm), dudyn((iim + 1) * (jjm + 1), llm)      REAL dv((iim + 1) * jjm, llm), dudyn((iim + 1) * (jjm + 1), llm)
77      REAL dteta(iim + 1, jjm + 1, llm), dq((iim + 1) * (jjm + 1), llm, nqmx)      REAL dteta(iim + 1, jjm + 1, llm)
78      real dp((iim + 1) * (jjm + 1))      real dp((iim + 1) * (jjm + 1))
79    
80      ! Tendances de la dissipation :      ! Tendances de la dissipation :
# Line 95  contains Line 95  contains
95      INTEGER l      INTEGER l
96      REAL rdayvrai, rdaym_ini      REAL rdayvrai, rdaym_ini
97    
98      ! Variables test conservation energie      ! Variables test conservation énergie
99      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)
100    
101      REAL vcont((iim + 1) * jjm, llm), ucont((iim + 1) * (jjm + 1), llm)      REAL vcont((iim + 1) * jjm, llm), ucont((iim + 1) * (jjm + 1), llm)
# Line 110  contains Line 110  contains
110      itaufin = nday * day_step      itaufin = nday * day_step
111      ! "day_step" is a multiple of "iperiod", therefore so is "itaufin".      ! "day_step" is a multiple of "iperiod", therefore so is "itaufin".
112    
     dq = 0.  
   
113      ! On initialise la pression et la fonction d'Exner :      ! On initialise la pression et la fonction d'Exner :
114      forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps      forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps
115      CALL exner_hyb(ps, p3d, pks, pk, pkf)      CALL exner_hyb(ps, p3d, pks, pk, pkf)
# Line 140  contains Line 138  contains
138              dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, &              dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, &
139              conser=MOD(itau, iconser)==0)              conser=MOD(itau, iconser)==0)
140    
141         ! Calcul des tendances advection des traceurs (dont l'humidité)         CALL caladvtrac(q, pbaru, pbarv, p3d, masse, teta, pk)
        CALL caladvtrac(q, pbaru, pbarv, p3d, masse, dq, teta, pk)  
142    
143         ! Stokage du flux de masse pour traceurs offline:         ! Stokage du flux de masse pour traceurs offline:
144         IF (offline) CALL fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, &         IF (offline) CALL fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, &
# Line 180  contains Line 177  contains
177            time = REAL(mod(itau, day_step)) / day_step + time_0            time = REAL(mod(itau, day_step)) / day_step + time_0
178            IF (time > 1.) time = time - 1.            IF (time > 1.) time = time - 1.
179    
180            CALL calfis(rdayvrai, time, ucov, vcov, teta, q, masse, ps, pk, &            CALL calfis(rdayvrai, time, ucov, vcov, teta, q, ps, pk, phis, phi, &
181                 phis, phi, dudyn, dv, dq, w, dufi, dvfi, dtetafi, dqfi, dpfi, &                 dudyn, dv, w, dufi, dvfi, dtetafi, dqfi, dpfi, &
182                 lafin = itau + 1 == itaufin)                 lafin = itau + 1 == itaufin)
183    
184            ! Ajout des tendances physiques:            ! Ajout des tendances physiques:
185            CALL addfi(nqmx, ucov, vcov, teta, q, ps, dufi, dvfi, dtetafi, &            CALL addfi(ucov, vcov, teta, q, ps, dufi, dvfi, dtetafi, dqfi, dpfi)
                dqfi, dpfi)  
186         ENDIF         ENDIF
187    
188         forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps         forall (l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * ps

Legend:
Removed from v.70  
changed lines
  Added in v.71

  ViewVC Help
Powered by ViewVC 1.1.21