/[lmdze]/trunk/phylmd/aaam_bud.f90
ViewVC logotype

Diff of /trunk/phylmd/aaam_bud.f90

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

revision 134 by guez, Wed Apr 29 15:47:56 2015 UTC revision 171 by guez, Tue Sep 29 19:48:59 2015 UTC
# Line 4  module aaam_bud_m Line 4  module aaam_bud_m
4    
5  contains  contains
6    
7    subroutine aaam_bud(rea, rg, ome, plat, plon, phis, dragu, liftu, phyu, &    subroutine aaam_bud(rg, ome, plat, plon, phis, dragu, liftu, phyu, dragv, &
8         dragv, liftv, phyv, p, u, v, aam, torsfc)         liftv, phyv, p, u, v, aam, torsfc)
9    
10      ! Author: F. Lott (LMD/CNRS). Date: 2003/10/20. Object: Compute      ! Author: F. Lott (LMD/CNRS). Date: 2003/10/20. Object: Compute
11      ! different terms of the axial AAAM budget and mountain torque.      ! different terms of the axial AAAM budget and mountain torque.
# Line 14  contains Line 14  contains
14    
15      USE dimens_m, ONLY : iim, jjm      USE dimens_m, ONLY : iim, jjm
16      use nr_util, only: assert_eq, assert, pi      use nr_util, only: assert_eq, assert, pi
17        USE suphec_m, ONLY: ra
18    
     real, intent(in):: rea ! Earth radius  
19      real, intent(in):: rg ! gravity constant      real, intent(in):: rg ! gravity constant
20      real, intent(in):: ome ! Earth rotation rate      real, intent(in):: ome ! Earth rotation rate
21    
# Line 171  contains Line 171  contains
171    
172      DO j = 1, jjm      DO j = 1, jjm
173         DO i = 1, iim         DO i = 1, iim
174            raam(1) = raam(1) - rea**3 * dlon * dlat * 0.5 * (cos(zlon(i )) &            raam(1) = raam(1) - ra**3 * dlon * dlat * 0.5 * (cos(zlon(i )) &
175                 * sin(zlat(j )) * cos(zlat(j )) * ub(i , j ) + cos(zlon(i )) &                 * sin(zlat(j )) * cos(zlat(j )) * ub(i , j ) + cos(zlon(i )) &
176                 * sin(zlat(j + 1)) * cos(zlat(j + 1)) * ub(i , j + 1)) &                 * sin(zlat(j + 1)) * cos(zlat(j + 1)) * ub(i , j + 1)) &
177                 + rea**3 * dlon * dlat * 0.5 * (sin(zlon(i )) * cos(zlat(j )) &                 + ra**3 * dlon * dlat * 0.5 * (sin(zlon(i )) * cos(zlat(j )) &
178                 * vb(i , j ) + sin(zlon(i )) * cos(zlat(j + 1)) * vb(i , j + 1))                 * vb(i , j ) + sin(zlon(i )) * cos(zlat(j + 1)) * vb(i , j + 1))
179    
180            oaam(1) = oaam(1) - ome * rea**4 * dlon * dlat / rg * 0.5 &            oaam(1) = oaam(1) - ome * ra**4 * dlon * dlat / rg * 0.5 &
181                 * (cos(zlon(i )) * cos(zlat(j ))**2 * sin(zlat(j )) &                 * (cos(zlon(i )) * cos(zlat(j ))**2 * sin(zlat(j )) &
182                 * ps(i , j ) + cos(zlon(i )) * cos(zlat(j + 1))**2 &                 * ps(i , j ) + cos(zlon(i )) * cos(zlat(j + 1))**2 &
183                 * sin(zlat(j + 1)) * ps(i , j + 1))                 * sin(zlat(j + 1)) * ps(i , j + 1))
184    
185            raam(2) = raam(2) - rea**3 * dlon * dlat * 0.5 * (sin(zlon(i )) &            raam(2) = raam(2) - ra**3 * dlon * dlat * 0.5 * (sin(zlon(i )) &
186                 * sin(zlat(j )) * cos(zlat(j )) * ub(i , j ) + sin(zlon(i )) &                 * sin(zlat(j )) * cos(zlat(j )) * ub(i , j ) + sin(zlon(i )) &
187                 * sin(zlat(j + 1)) * cos(zlat(j + 1)) * ub(i , j + 1)) &                 * sin(zlat(j + 1)) * cos(zlat(j + 1)) * ub(i , j + 1)) &
188                 - rea**3 * dlon * dlat * 0.5 * (cos(zlon(i )) * cos(zlat(j )) &                 - ra**3 * dlon * dlat * 0.5 * (cos(zlon(i )) * cos(zlat(j )) &
189                 * vb(i , j ) + cos(zlon(i )) * cos(zlat(j + 1)) * vb(i , j + 1))                 * vb(i , j ) + cos(zlon(i )) * cos(zlat(j + 1)) * vb(i , j + 1))
190    
191            oaam(2) = oaam(2) - ome * rea**4 * dlon * dlat / rg * 0.5 &            oaam(2) = oaam(2) - ome * ra**4 * dlon * dlat / rg * 0.5 &
192                 * (sin(zlon(i )) * cos(zlat(j ))**2 * sin(zlat(j )) &                 * (sin(zlon(i )) * cos(zlat(j ))**2 * sin(zlat(j )) &
193                 * ps(i , j ) + sin(zlon(i )) * cos(zlat(j + 1))**2 &                 * ps(i , j ) + sin(zlon(i )) * cos(zlat(j + 1))**2 &
194                 * sin(zlat(j + 1)) * ps(i , j + 1))                 * sin(zlat(j + 1)) * ps(i , j + 1))
195    
196            raam(3) = raam(3) + rea**3 * dlon * dlat * 0.5 * (cos(zlat(j))**2 &            raam(3) = raam(3) + ra**3 * dlon * dlat * 0.5 * (cos(zlat(j))**2 &
197                 * ub(i, j) + cos(zlat(j + 1))**2 * ub(i, j + 1))                 * ub(i, j) + cos(zlat(j + 1))**2 * ub(i, j + 1))
198    
199            oaam(3) = oaam(3) + ome * rea**4 * dlon * dlat / rg * 0.5 &            oaam(3) = oaam(3) + ome * ra**4 * dlon * dlat / rg * 0.5 &
200                 * (cos(zlat(j))**3 * ps(i, j) + cos(zlat(j + 1))**3 &                 * (cos(zlat(j))**3 * ps(i, j) + cos(zlat(j + 1))**3 &
201                 * ps(i, j + 1))                 * ps(i, j + 1))
202         ENDDO         ENDDO
# Line 206  contains Line 206  contains
206    
207      DO j = 1, jjm      DO j = 1, jjm
208         DO i = 1, iim         DO i = 1, iim
209            tmou(1) = tmou(1) - rea**2 * dlon * 0.5 * sin(zlon(i)) &            tmou(1) = tmou(1) - ra**2 * dlon * 0.5 * sin(zlon(i)) &
210                 * (zs(i, j) - zs(i, j + 1)) &                 * (zs(i, j) - zs(i, j + 1)) &
211                 * (cos(zlat(j + 1)) * ps(i, j + 1) + cos(zlat(j)) * ps(i, j))                 * (cos(zlat(j + 1)) * ps(i, j + 1) + cos(zlat(j)) * ps(i, j))
212            tmou(2) = tmou(2) + rea**2 * dlon * 0.5 * cos(zlon(i)) &            tmou(2) = tmou(2) + ra**2 * dlon * 0.5 * cos(zlon(i)) &
213                 * (zs(i, j) - zs(i, j + 1)) &                 * (zs(i, j) - zs(i, j + 1)) &
214                 * (cos(zlat(j + 1)) * ps(i, j + 1) + cos(zlat(j)) * ps(i, j))                 * (cos(zlat(j + 1)) * ps(i, j + 1) + cos(zlat(j)) * ps(i, j))
215         ENDDO         ENDDO
# Line 217  contains Line 217  contains
217    
218      DO j = 2, jjm      DO j = 2, jjm
219         DO i = 1, iim         DO i = 1, iim
220            tmou(1) = tmou(1) + rea**2 * dlat * 0.5 * sin(zlat(j)) &            tmou(1) = tmou(1) + ra**2 * dlat * 0.5 * sin(zlat(j)) &
221                 * (zs(i + 1, j) - zs(i, j)) &                 * (zs(i + 1, j) - zs(i, j)) &
222                 * (cos(zlon(i + 1)) * ps(i + 1, j) + cos(zlon(i)) * ps(i, j))                 * (cos(zlon(i + 1)) * ps(i + 1, j) + cos(zlon(i)) * ps(i, j))
223            tmou(2) = tmou(2) + rea**2 * dlat * 0.5 * sin(zlat(j)) &            tmou(2) = tmou(2) + ra**2 * dlat * 0.5 * sin(zlat(j)) &
224                 * (zs(i + 1, j) - zs(i, j)) &                 * (zs(i + 1, j) - zs(i, j)) &
225                 * (sin(zlon(i + 1)) * ps(i + 1, j) + sin(zlon(i)) * ps(i, j))                 * (sin(zlon(i + 1)) * ps(i + 1, j) + sin(zlon(i)) * ps(i, j))
226            tmou(3) = tmou(3) - rea**2 * dlat * 0.5* cos(zlat(j)) &            tmou(3) = tmou(3) - ra**2 * dlat * 0.5* cos(zlat(j)) &
227                 * (zs(i + 1, j) - zs(i, j)) * (ps(i + 1, j) + ps(i, j))                 * (zs(i + 1, j) - zs(i, j)) * (ps(i + 1, j) + ps(i, j))
228         ENDDO         ENDDO
229      ENDDO      ENDDO
# Line 232  contains Line 232  contains
232    
233      DO j = 2, jjm      DO j = 2, jjm
234         DO i = 1, iim         DO i = 1, iim
235            tsso(1) = tsso(1) - rea**3 * cos(zlat(j)) * dlon * dlat* &            tsso(1) = tsso(1) - ra**3 * cos(zlat(j)) * dlon * dlat* &
236                 ssou(i, j) * sin(zlat(j)) * cos(zlon(i)) &                 ssou(i, j) * sin(zlat(j)) * cos(zlon(i)) &
237                 + rea**3 * cos(zlat(j)) * dlon * dlat* &                 + ra**3 * cos(zlat(j)) * dlon * dlat* &
238                 ssov(i, j) * sin(zlon(i))                 ssov(i, j) * sin(zlon(i))
239    
240            tsso(2) = tsso(2) - rea**3 * cos(zlat(j)) * dlon * dlat* &            tsso(2) = tsso(2) - ra**3 * cos(zlat(j)) * dlon * dlat* &
241                 ssou(i, j) * sin(zlat(j)) * sin(zlon(i)) &                 ssou(i, j) * sin(zlat(j)) * sin(zlon(i)) &
242                 - rea**3 * cos(zlat(j)) * dlon * dlat* &                 - ra**3 * cos(zlat(j)) * dlon * dlat* &
243                 ssov(i, j) * cos(zlon(i))                 ssov(i, j) * cos(zlon(i))
244    
245            tsso(3) = tsso(3) + rea**3 * cos(zlat(j)) * dlon * dlat* &            tsso(3) = tsso(3) + ra**3 * cos(zlat(j)) * dlon * dlat* &
246                 ssou(i, j) * cos(zlat(j))                 ssou(i, j) * cos(zlat(j))
247    
248            tbls(1) = tbls(1) - rea**3 * cos(zlat(j)) * dlon * dlat* &            tbls(1) = tbls(1) - ra**3 * cos(zlat(j)) * dlon * dlat* &
249                 blsu(i, j) * sin(zlat(j)) * cos(zlon(i)) &                 blsu(i, j) * sin(zlat(j)) * cos(zlon(i)) &
250                 + rea**3 * cos(zlat(j)) * dlon * dlat* &                 + ra**3 * cos(zlat(j)) * dlon * dlat* &
251                 blsv(i, j) * sin(zlon(i))                 blsv(i, j) * sin(zlon(i))
252    
253            tbls(2) = tbls(2) - rea**3 * cos(zlat(j)) * dlon * dlat* &            tbls(2) = tbls(2) - ra**3 * cos(zlat(j)) * dlon * dlat* &
254                 blsu(i, j) * sin(zlat(j)) * sin(zlon(i)) &                 blsu(i, j) * sin(zlat(j)) * sin(zlon(i)) &
255                 - rea**3 * cos(zlat(j)) * dlon * dlat* &                 - ra**3 * cos(zlat(j)) * dlon * dlat* &
256                 blsv(i, j) * cos(zlon(i))                 blsv(i, j) * cos(zlon(i))
257    
258            tbls(3) = tbls(3) + rea**3 * cos(zlat(j)) * dlon * dlat* &            tbls(3) = tbls(3) + ra**3 * cos(zlat(j)) * dlon * dlat* &
259                 blsu(i, j) * cos(zlat(j))                 blsu(i, j) * cos(zlat(j))
260         ENDDO         ENDDO
261      ENDDO      ENDDO

Legend:
Removed from v.134  
changed lines
  Added in v.171

  ViewVC Help
Powered by ViewVC 1.1.21