source: trunk/LMDZ.MARS/libf/dyn3d/addfi.F @ 1242

Last change on this file since 1242 was 1238, checked in by emillour, 11 years ago

Mars GCM and common dynamics:

Common dynamics:

  • correction in inidissip (only matters in Martian case)
  • added correction in addfi on theta to account for surface pressure change.

Mars GCM:
Some fixes and updates:

  • addfi (dyn3d): Add correction on theta when surface pressure changes
  • vdif_cd (phymars): Correction for coefficients in stable nighttime case
  • jthermcalc (aeronomars): Fix for some pathological cases (further investigations on the origin of these is needed)

EM

File size: 4.8 KB
Line 
1      SUBROUTINE addfi(nq, pdt, leapf, forward,
2     S          pucov, pvcov, pteta, pq   , pps , pmasse ,
3     S          pdufi, pdvfi, pdhfi,pdqfi, pdpfi  )
4      IMPLICIT NONE
5c
6c=======================================================================
7c
8c    Addition of the physical tendencies
9c    Modif special Mars :
10c       - no special treatment of iq = 1, 2, FF 2003
11c       - recompute mass after incrementation of ps (EM,FF 2008)
12c
13c    Interface :
14c    -----------
15c
16c      Input :
17c      -------
18c      pdt                    time step of integration
19c      leapf                  logical
20c      forward                logical
21c      pucov(ip1jmp1,llm)     first component of the covariant velocity
22c      pvcov(ip1ip1jm,llm)    second component of the covariant velocity
23c      pteta(ip1jmp1,llm)     potential temperature
24c      pts(ip1jmp1,llm)       surface temperature
25c      pdufi(ip1jmp1,llm)     |
26c      pdvfi(ip1jm,llm)       |   respective
27c      pdhfi(ip1jmp1)         |      tendencies
28c      pdtsfi(ip1jmp1)        |
29c
30c      Output :
31c      --------
32c      pucov
33c      pvcov
34c      ph
35c      pts
36c      pmasse(ip1jmp1,llm)    ! mass
37c
38c
39c=======================================================================
40c
41c-----------------------------------------------------------------------
42c
43c    0.  Declarations :
44c    ------------------
45c
46#include "dimensions.h"
47#include "paramet.h"
48#include "comconst.h"
49#include "comgeom.h"
50#include "serre.h"
51#include "comvert.h"
52c
53c    Arguments :
54c    -----------
55c
56      INTEGER nq
57
58      REAL pdt
59c
60      REAL pvcov(ip1jm,llm),pucov(ip1jmp1,llm)
61      REAL pteta(ip1jmp1,llm),pq(ip1jmp1,llm,nq),pps(ip1jmp1)
62c
63      REAL pdvfi(ip1jm,llm),pdufi(ip1jmp1,llm)
64      REAL pdqfi(ip1jmp1,llm,nq),pdhfi(ip1jmp1,llm),pdpfi(ip1jmp1)
65
66      real pmasse(ip1jmp1,llm)
67c
68      LOGICAL leapf,forward
69c
70c
71c    Local variables :
72c    -----------------
73c
74      REAL xpn(iim),xps(iim),tpn,tps
75      INTEGER j,k,iq,ij
76      REAL qtestw, qtestt
77      PARAMETER ( qtestw = 1.0e-15 )
78      PARAMETER ( qtestt = 1.0e-30 )
79
80      real p(ip1jmp1,llmp1) ! pressure
81
82      REAL SSUM
83      EXTERNAL SSUM
84c
85c-----------------------------------------------------------------------
86! increment potential temperature
87      DO k = 1,llm
88         DO j = 1,ip1jmp1
89            pteta(j,k)= pteta(j,k) + pdhfi(j,k) * pdt
90         ENDDO
91      ENDDO
92
93      DO  k    = 1, llm
94       DO  ij   = 1, iim
95         xpn(ij) = aire(   ij   ) * pteta(  ij    ,k)
96         xps(ij) = aire(ij+ip1jm) * pteta(ij+ip1jm,k)
97       ENDDO
98       tpn      = SSUM(iim,xpn,1)/ apoln
99       tps      = SSUM(iim,xps,1)/ apols
100
101       DO ij   = 1, iip1
102         pteta(   ij   ,k)  = tpn
103         pteta(ij+ip1jm,k)  = tps
104       ENDDO
105      ENDDO
106!***********************
107! Correction on teta due to surface pressure changes
108      DO k = 1,llm
109        DO j = 1,ip1jmp1
110           pteta(j,k)= pteta(j,k)*(1+pdpfi(j)*pdt/pps(j))**kappa
111        ENDDO
112      ENDDO
113!***********************
114
115! increment covariant zonal wind
116      DO k = 1,llm
117         DO j = iip2,ip1jm
118            pucov(j,k)= pucov(j,k) + pdufi(j,k) * pdt
119         ENDDO
120      ENDDO
121
122! increment covariant meridional wind
123      DO k = 1,llm
124         DO j = 1,ip1jm
125            pvcov(j,k)= pvcov(j,k) + pdvfi(j,k) * pdt
126         ENDDO
127      ENDDO
128
129c
130! increment surface pressure
131      DO j = 1,ip1jmp1
132         pps(j) = pps(j) + pdpfi(j) * pdt
133      ENDDO
134
135c     DO iq = 1, 2 ! special Mars: no special treatment for water
136c        DO k = 1,llm
137c           DO j = 1,ip1jmp1
138c              pq(j,k,iq)= pq(j,k,iq) + pdqfi(j,k,iq) * pdt
139c              pq(j,k,iq)= AMAX1( pq(j,k,iq), qtestw )
140c           ENDDO
141c        ENDDO
142c     ENDDO
143
144      DO iq = 1, nq
145         DO k = 1,llm
146            DO j = 1,ip1jmp1
147               pq(j,k,iq)= pq(j,k,iq) + pdqfi(j,k,iq) * pdt
148               pq(j,k,iq)= AMAX1( pq(j,k,iq), qtestt )
149            ENDDO
150         ENDDO
151      ENDDO
152                                       
153
154       DO  ij   = 1, iim
155         xpn(ij) = aire(   ij   ) * pps(  ij     )
156         xps(ij) = aire(ij+ip1jm) * pps(ij+ip1jm )
157       ENDDO
158       tpn      = SSUM(iim,xpn,1)/apoln
159       tps      = SSUM(iim,xps,1)/apols
160
161       DO ij   = 1, iip1
162         pps (   ij     )  = tpn
163         pps ( ij+ip1jm )  = tps
164       ENDDO
165
166! recompute mass: (to be synchronous with update of ps)
167      CALL pression ( ip1jmp1, ap, bp, pps, p )
168      CALL massdair (     p  , pmasse         )
169 
170
171
172       DO iq = 1, nq
173         DO  k    = 1, llm
174           DO  ij   = 1, iim
175             xpn(ij) = aire(   ij   ) * pq(  ij    ,k,iq)
176             xps(ij) = aire(ij+ip1jm) * pq(ij+ip1jm,k,iq)
177           ENDDO
178           tpn      = SSUM(iim,xpn,1)/apoln
179           tps      = SSUM(iim,xps,1)/apols
180
181           DO ij   = 1, iip1
182             pq (   ij   ,k,iq)  = tpn
183             pq (ij+ip1jm,k,iq)  = tps
184           ENDDO
185         ENDDO
186       ENDDO
187
188      RETURN
189      END
Note: See TracBrowser for help on using the repository browser.