LMDZ
addfi.F
Go to the documentation of this file.
1 !
2 ! $Id: addfi.F 1987 2014-02-24 15:05:47Z emillour $
3 !
4  SUBROUTINE addfi(pdt, leapf, forward,
5  s pucov, pvcov, pteta, pq , pps ,
6  s pdufi, pdvfi, pdhfi,pdqfi, pdpfi )
7 
8  USE infotrac, ONLY : nqtot
9  USE control_mod, ONLY : planet_type
10  IMPLICIT NONE
11 c
12 c=======================================================================
13 c
14 c Addition of the physical tendencies
15 c
16 c Interface :
17 c -----------
18 c
19 c Input :
20 c -------
21 c pdt time step of integration
22 c leapf logical
23 c forward logical
24 c pucov(ip1jmp1,llm) first component of the covariant velocity
25 c pvcov(ip1ip1jm,llm) second component of the covariant velocity
26 c pteta(ip1jmp1,llm) potential temperature
27 c pts(ip1jmp1,llm) surface temperature
28 c pdufi(ip1jmp1,llm) |
29 c pdvfi(ip1jm,llm) | respective
30 c pdhfi(ip1jmp1) | tendencies
31 c pdtsfi(ip1jmp1) |
32 c
33 c Output :
34 c --------
35 c pucov
36 c pvcov
37 c ph
38 c pts
39 c
40 c
41 c=======================================================================
42 c
43 c-----------------------------------------------------------------------
44 c
45 c 0. Declarations :
46 c ------------------
47 c
48 #include "dimensions.h"
49 #include "paramet.h"
50 #include "comconst.h"
51 #include "comgeom.h"
52 #include "serre.h"
53 c
54 c Arguments :
55 c -----------
56 c
57  REAL,INTENT(IN) :: pdt ! time step for the integration (s)
58 c
59  REAL,INTENT(INOUT) :: pvcov(ip1jm,llm) ! covariant meridional wind
60  REAL,INTENT(INOUT) :: pucov(ip1jmp1,llm) ! covariant zonal wind
61  REAL,INTENT(INOUT) :: pteta(ip1jmp1,llm) ! potential temperature
62  REAL,INTENT(INOUT) :: pq(ip1jmp1,llm,nqtot) ! tracers
63  REAL,INTENT(INOUT) :: pps(ip1jmp1) ! surface pressure (Pa)
64 c respective tendencies (.../s) to add
65  REAL,INTENT(IN) :: pdvfi(ip1jm,llm)
66  REAL,INTENT(IN) :: pdufi(ip1jmp1,llm)
67  REAL,INTENT(IN) :: pdqfi(ip1jmp1,llm,nqtot)
68  REAL,INTENT(IN) :: pdhfi(ip1jmp1,llm)
69  REAL,INTENT(IN) :: pdpfi(ip1jmp1)
70 c
71  LOGICAL,INTENT(IN) :: leapf,forward ! not used
72 c
73 c
74 c Local variables :
75 c -----------------
76 c
77  REAL xpn(iim),xps(iim),tpn,tps
78  INTEGER j,k,iq,ij
79  REAL,PARAMETER :: qtestw = 1.0e-15
80  REAL,PARAMETER :: qtestt = 1.0e-40
81 
82  REAL SSUM
83 c
84 c-----------------------------------------------------------------------
85 
86  DO k = 1,llm
87  DO j = 1,ip1jmp1
88  pteta(j,k)= pteta(j,k) + pdhfi(j,k) * pdt
89  ENDDO
90  ENDDO
91 
92  DO k = 1, llm
93  DO ij = 1, iim
94  xpn(ij) = aire( ij ) * pteta( ij ,k)
95  xps(ij) = aire(ij+ip1jm) * pteta(ij+ip1jm,k)
96  ENDDO
97  tpn = ssum(iim,xpn,1)/ apoln
98  tps = ssum(iim,xps,1)/ apols
99 
100  DO ij = 1, iip1
101  pteta( ij ,k) = tpn
102  pteta(ij+ip1jm,k) = tps
103  ENDDO
104  ENDDO
105 c
106 
107  DO k = 1,llm
108  DO j = iip2,ip1jm
109  pucov(j,k)= pucov(j,k) + pdufi(j,k) * pdt
110  ENDDO
111  ENDDO
112 
113  DO k = 1,llm
114  DO j = 1,ip1jm
115  pvcov(j,k)= pvcov(j,k) + pdvfi(j,k) * pdt
116  ENDDO
117  ENDDO
118 
119 c
120  DO j = 1,ip1jmp1
121  pps(j) = pps(j) + pdpfi(j) * pdt
122  ENDDO
123 
124  if (planet_type=="earth") then
125  ! earth case, special treatment for first 2 tracers (water)
126  DO iq = 1, 2
127  DO k = 1,llm
128  DO j = 1,ip1jmp1
129  pq(j,k,iq)= pq(j,k,iq) + pdqfi(j,k,iq) * pdt
130  pq(j,k,iq)= amax1( pq(j,k,iq), qtestw )
131  ENDDO
132  ENDDO
133  ENDDO
134 
135  DO iq = 3, nqtot
136  DO k = 1,llm
137  DO j = 1,ip1jmp1
138  pq(j,k,iq)= pq(j,k,iq) + pdqfi(j,k,iq) * pdt
139  pq(j,k,iq)= amax1( pq(j,k,iq), qtestt )
140  ENDDO
141  ENDDO
142  ENDDO
143  else
144  ! general case, treat all tracers equally)
145  DO iq = 1, nqtot
146  DO k = 1,llm
147  DO j = 1,ip1jmp1
148  pq(j,k,iq)= pq(j,k,iq) + pdqfi(j,k,iq) * pdt
149  pq(j,k,iq)= amax1( pq(j,k,iq), qtestt )
150  ENDDO
151  ENDDO
152  ENDDO
153  endif ! of if (planet_type=="earth")
154 
155 
156  DO ij = 1, iim
157  xpn(ij) = aire( ij ) * pps( ij )
158  xps(ij) = aire(ij+ip1jm) * pps(ij+ip1jm )
159  ENDDO
160  tpn = ssum(iim,xpn,1)/apoln
161  tps = ssum(iim,xps,1)/apols
162 
163  DO ij = 1, iip1
164  pps( ij ) = tpn
165  pps( ij+ip1jm ) = tps
166  ENDDO
167 
168 
169  DO iq = 1, nqtot
170  DO k = 1, llm
171  DO ij = 1, iim
172  xpn(ij) = aire( ij ) * pq( ij ,k,iq)
173  xps(ij) = aire(ij+ip1jm) * pq(ij+ip1jm,k,iq)
174  ENDDO
175  tpn = ssum(iim,xpn,1)/apoln
176  tps = ssum(iim,xps,1)/apols
177 
178  DO ij = 1, iip1
179  pq( ij ,k,iq) = tpn
180  pq(ij+ip1jm,k,iq) = tps
181  ENDDO
182  ENDDO
183  ENDDO
184 
185  RETURN
186  END
!$Header iip2
Definition: paramet.h:14
!$Header llmm1 INTEGER ip1jmp1
Definition: paramet.h:14
!$Header!CDK comgeom COMMON comgeom apols
Definition: comgeom.h:8
subroutine addfi(pdt, leapf, forward, pucov, pvcov, pteta, pq, pps, pdufi, pdvfi, pdhfi, pdqfi, pdpfi)
Definition: addfi.F:7
character(len=10), save planet_type
Definition: control_mod.F90:32
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
!$Header!CDK comgeom COMMON comgeom aire
Definition: comgeom.h:25
integer, save nqtot
Definition: infotrac.F90:6
!$Header llmm1 INTEGER ip1jm
Definition: paramet.h:14
!$Header!CDK comgeom COMMON comgeom apoln
Definition: comgeom.h:8
c c zjulian c cym CALL iim cym klev iim
Definition: ini_bilKP_ave.h:24
INTERFACE SUBROUTINE RRTM_ECRT_140GP && pq