source: LMDZ5/trunk/libf/phylmd/aaam_bud.F90 @ 2347

Last change on this file since 2347 was 2346, checked in by Ehouarn Millour, 9 years ago

Physics/dynamics separation:

  • remove all references to dimensions.h from physics. nbp_lon (==iim) , nbp_lat (==jjm+1) and nbp_lev (==llm) from mod_grid_phy_lmdz should be used instead.
  • added module regular_lonlat_mod in phy_common to store information about the global (lon-lat) grid cell boundaries and centers.

EM

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 11.0 KB
Line 
1
2! $Id: aaam_bud.F90 2346 2015-08-21 15:13:46Z emillour $
3
4SUBROUTINE aaam_bud(iam, nlon, nlev, rjour, rsec, rea, rg, ome, plat, plon, &
5    phis, dragu, liftu, phyu, dragv, liftv, phyv, p, u, v, aam, torsfc)
6
7  USE dimphy
8  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
9  IMPLICIT NONE
10  ! ======================================================================
11  ! Auteur(s): F.Lott (LMD/CNRS) date: 20031020
12  ! Object: Compute different terms of the axial AAAM Budget.
13  ! No outputs, every AAM quantities are written on the IAM
14  ! File.
15
16  ! Modif : I.Musat (LMD/CNRS) date : 20041020
17  ! Outputs : axial components of wind AAM "aam" and total surface torque
18  ! "torsfc",
19  ! but no write in the iam file.
20
21  ! WARNING: Only valid for regular rectangular grids.
22  ! REMARK: CALL DANS PHYSIQ AFTER lift_noro:
23  ! CALL aaam_bud (27,klon,klev,rjourvrai,gmtime,
24  ! C               ra,rg,romega,
25  ! C               rlat,rlon,pphis,
26  ! C               zustrdr,zustrli,zustrph,
27  ! C               zvstrdr,zvstrli,zvstrph,
28  ! C               paprs,u,v)
29
30  ! ======================================================================
31  ! Explicit Arguments:
32  ! ==================
33  ! iam-----input-I-File number where AAMs and torques are written
34  ! It is a formatted file that has been opened
35  ! in physiq.F
36  ! nlon----input-I-Total number of horizontal points that get into physics
37  ! nlev----input-I-Number of vertical levels
38  ! rjour        -R-Jour compte depuis le debut de la simu (run.def)
39  ! rsec         -R-Seconde de la journee
40  ! rea          -R-Earth radius
41  ! rg           -R-gravity constant
42  ! ome          -R-Earth rotation rate
43  ! plat ---input-R-Latitude en degres
44  ! plon ---input-R-Longitude en degres
45  ! phis ---input-R-Geopotential at the ground
46  ! dragu---input-R-orodrag stress (zonal)
47  ! liftu---input-R-orolift stress (zonal)
48  ! phyu----input-R-Stress total de la physique (zonal)
49  ! dragv---input-R-orodrag stress (Meridional)
50  ! liftv---input-R-orolift stress (Meridional)
51  ! phyv----input-R-Stress total de la physique (Meridional)
52  ! p-------input-R-Pressure (Pa) at model half levels
53  ! u-------input-R-Horizontal wind (m/s)
54  ! v-------input-R-Meridional wind (m/s)
55  ! aam-----output-R-Axial Wind AAM (=raam(3))
56  ! torsfc--output-R-Total surface torque (=tmou(3)+tsso(3)+tbls(3))
57
58  ! Implicit Arguments:
59  ! ===================
60
61  ! nbp_lon--common-I: Number of longitude intervals
62  ! (nbp_lat-1)--common-I: Number of latitude intervals
63  ! klon-common-I: Number of points seen by the physics
64  ! nbp_lon*(nbp_lat-2)+2 for instance
65  ! klev-common-I: Number of vertical layers
66  ! ======================================================================
67  ! Local Variables:
68  ! ================
69  ! dlat-----R: Latitude increment (Radians)
70  ! dlon-----R: Longitude increment (Radians)
71  ! raam  ---R: Wind AAM (3 Components, 1 & 2 Equatoriales; 3 Axiale)
72  ! oaam  ---R: Mass AAM (3 Components, 1 & 2 Equatoriales; 3 Axiale)
73  ! tmou-----R: Resolved Mountain torque (3 components)
74  ! tsso-----R: Parameterised Moutain drag torque (3 components)
75  ! tbls-----R: Parameterised Boundary layer torque (3 components)
76
77  ! LOCAL ARRAY:
78  ! ===========
79  ! zs    ---R: Topographic height
80  ! ps    ---R: Surface Pressure
81  ! ub    ---R: Barotropic wind zonal
82  ! vb    ---R: Barotropic wind meridional
83  ! zlat  ---R: Latitude in radians
84  ! zlon  ---R: Longitude in radians
85  ! ======================================================================
86
87  ! ARGUMENTS
88
89  INTEGER iam, nlon, nlev
90  REAL, INTENT (IN) :: rjour, rsec, rea, rg, ome
91  REAL plat(nlon), plon(nlon), phis(nlon)
92  REAL dragu(nlon), liftu(nlon), phyu(nlon)
93  REAL dragv(nlon), liftv(nlon), phyv(nlon)
94  REAL p(nlon, nlev+1), u(nlon, nlev), v(nlon, nlev)
95
96  ! Variables locales:
97
98  INTEGER i, j, k, l
99  REAL xpi, hadley, hadday
100  REAL dlat, dlon
101  REAL raam(3), oaam(3), tmou(3), tsso(3), tbls(3)
102  INTEGER iax
103  ! IM ajout aam, torsfc
104  ! aam = composante axiale du Wind AAM raam
105  ! torsfc = composante axiale de (tmou+tsso+tbls)
106  REAL aam, torsfc
107
108  REAL zs(801, 401), ps(801, 401)
109  REAL ub(801, 401), vb(801, 401)
110  REAL ssou(801, 401), ssov(801, 401)
111  REAL blsu(801, 401), blsv(801, 401)
112  REAL zlon(801), zlat(401)
113
114  CHARACTER (LEN=20) :: modname = 'aaam_bud'
115  CHARACTER (LEN=80) :: abort_message
116
117
118
119  ! PUT AAM QUANTITIES AT ZERO:
120
121  IF (nbp_lon+1>801 .OR. nbp_lat>401) THEN
122    abort_message = 'Pb de dimension dans aaam_bud'
123    CALL abort_physic(modname, abort_message, 1)
124  END IF
125
126  xpi = acos(-1.)
127  hadley = 1.E18
128  hadday = 1.E18*24.*3600.
129  dlat = xpi/real(nbp_lat-1)
130  dlon = 2.*xpi/real(nbp_lon)
131
132  DO iax = 1, 3
133    oaam(iax) = 0.
134    raam(iax) = 0.
135    tmou(iax) = 0.
136    tsso(iax) = 0.
137    tbls(iax) = 0.
138  END DO
139
140  ! MOUNTAIN HEIGHT, PRESSURE AND BAROTROPIC WIND:
141
142  ! North pole values (j=1):
143
144  l = 1
145
146  ub(1, 1) = 0.
147  vb(1, 1) = 0.
148  DO k = 1, nlev
149    ub(1, 1) = ub(1, 1) + u(l, k)*(p(l,k)-p(l,k+1))/rg
150    vb(1, 1) = vb(1, 1) + v(l, k)*(p(l,k)-p(l,k+1))/rg
151  END DO
152
153  zlat(1) = plat(l)*xpi/180.
154
155  DO i = 1, nbp_lon + 1
156
157    zs(i, 1) = phis(l)/rg
158    ps(i, 1) = p(l, 1)
159    ub(i, 1) = ub(1, 1)
160    vb(i, 1) = vb(1, 1)
161    ssou(i, 1) = dragu(l) + liftu(l)
162    ssov(i, 1) = dragv(l) + liftv(l)
163    blsu(i, 1) = phyu(l) - dragu(l) - liftu(l)
164    blsv(i, 1) = phyv(l) - dragv(l) - liftv(l)
165
166  END DO
167
168
169  DO j = 2, nbp_lat-1
170
171    ! Values at Greenwich (Periodicity)
172
173    zs(nbp_lon+1, j) = phis(l+1)/rg
174    ps(nbp_lon+1, j) = p(l+1, 1)
175    ssou(nbp_lon+1, j) = dragu(l+1) + liftu(l+1)
176    ssov(nbp_lon+1, j) = dragv(l+1) + liftv(l+1)
177    blsu(nbp_lon+1, j) = phyu(l+1) - dragu(l+1) - liftu(l+1)
178    blsv(nbp_lon+1, j) = phyv(l+1) - dragv(l+1) - liftv(l+1)
179    zlon(nbp_lon+1) = -plon(l+1)*xpi/180.
180    zlat(j) = plat(l+1)*xpi/180.
181
182    ub(nbp_lon+1, j) = 0.
183    vb(nbp_lon+1, j) = 0.
184    DO k = 1, nlev
185      ub(nbp_lon+1, j) = ub(nbp_lon+1, j) + u(l+1, k)*(p(l+1,k)-p(l+1,k+1))/rg
186      vb(nbp_lon+1, j) = vb(nbp_lon+1, j) + v(l+1, k)*(p(l+1,k)-p(l+1,k+1))/rg
187    END DO
188
189
190    DO i = 1, nbp_lon
191
192      l = l + 1
193      zs(i, j) = phis(l)/rg
194      ps(i, j) = p(l, 1)
195      ssou(i, j) = dragu(l) + liftu(l)
196      ssov(i, j) = dragv(l) + liftv(l)
197      blsu(i, j) = phyu(l) - dragu(l) - liftu(l)
198      blsv(i, j) = phyv(l) - dragv(l) - liftv(l)
199      zlon(i) = plon(l)*xpi/180.
200
201      ub(i, j) = 0.
202      vb(i, j) = 0.
203      DO k = 1, nlev
204        ub(i, j) = ub(i, j) + u(l, k)*(p(l,k)-p(l,k+1))/rg
205        vb(i, j) = vb(i, j) + v(l, k)*(p(l,k)-p(l,k+1))/rg
206      END DO
207
208    END DO
209
210  END DO
211
212
213  ! South Pole
214
215  IF (nbp_lat-1>1) THEN
216    l = l + 1
217    ub(1, nbp_lat) = 0.
218    vb(1, nbp_lat) = 0.
219    DO k = 1, nlev
220      ub(1, nbp_lat) = ub(1, nbp_lat) + u(l, k)*(p(l,k)-p(l,k+1))/rg
221      vb(1, nbp_lat) = vb(1, nbp_lat) + v(l, k)*(p(l,k)-p(l,k+1))/rg
222    END DO
223    zlat(nbp_lat) = plat(l)*xpi/180.
224
225    DO i = 1, nbp_lon + 1
226      zs(i, nbp_lat) = phis(l)/rg
227      ps(i, nbp_lat) = p(l, 1)
228      ssou(i, nbp_lat) = dragu(l) + liftu(l)
229      ssov(i, nbp_lat) = dragv(l) + liftv(l)
230      blsu(i, nbp_lat) = phyu(l) - dragu(l) - liftu(l)
231      blsv(i, nbp_lat) = phyv(l) - dragv(l) - liftv(l)
232      ub(i, nbp_lat) = ub(1, nbp_lat)
233      vb(i, nbp_lat) = vb(1, nbp_lat)
234    END DO
235  END IF
236
237
238  ! MOMENT ANGULAIRE
239
240  DO j = 1, nbp_lat-1
241    DO i = 1, nbp_lon
242
243      raam(1) = raam(1) - rea**3*dlon*dlat*0.5*(cos(zlon(i))*sin(zlat(j))*cos &
244        (zlat(j))*ub(i,j)+cos(zlon(i))*sin(zlat(j+1))*cos(zlat(j+ &
245        1))*ub(i,j+1)) + rea**3*dlon*dlat*0.5*(sin(zlon(i))*cos(zlat(j))*vb(i &
246        ,j)+sin(zlon(i))*cos(zlat(j+1))*vb(i,j+1))
247
248      oaam(1) = oaam(1) - ome*rea**4*dlon*dlat/rg*0.5*(cos(zlon(i))*cos(zlat( &
249        j))**2*sin(zlat(j))*ps(i,j)+cos(zlon(i))*cos(zlat(j+ &
250        1))**2*sin(zlat(j+1))*ps(i,j+1))
251
252      raam(2) = raam(2) - rea**3*dlon*dlat*0.5*(sin(zlon(i))*sin(zlat(j))*cos &
253        (zlat(j))*ub(i,j)+sin(zlon(i))*sin(zlat(j+1))*cos(zlat(j+ &
254        1))*ub(i,j+1)) - rea**3*dlon*dlat*0.5*(cos(zlon(i))*cos(zlat(j))*vb(i &
255        ,j)+cos(zlon(i))*cos(zlat(j+1))*vb(i,j+1))
256
257      oaam(2) = oaam(2) - ome*rea**4*dlon*dlat/rg*0.5*(sin(zlon(i))*cos(zlat( &
258        j))**2*sin(zlat(j))*ps(i,j)+sin(zlon(i))*cos(zlat(j+ &
259        1))**2*sin(zlat(j+1))*ps(i,j+1))
260
261      raam(3) = raam(3) + rea**3*dlon*dlat*0.5*(cos(zlat(j))**2*ub(i,j)+cos( &
262        zlat(j+1))**2*ub(i,j+1))
263
264      oaam(3) = oaam(3) + ome*rea**4*dlon*dlat/rg*0.5*(cos(zlat(j))**3*ps(i,j &
265        )+cos(zlat(j+1))**3*ps(i,j+1))
266
267    END DO
268  END DO
269
270
271  ! COUPLE DES MONTAGNES:
272
273
274  DO j = 1, nbp_lat-1
275    DO i = 1, nbp_lon
276      tmou(1) = tmou(1) - rea**2*dlon*0.5*sin(zlon(i))*(zs(i,j)-zs(i,j+1))*( &
277        cos(zlat(j+1))*ps(i,j+1)+cos(zlat(j))*ps(i,j))
278      tmou(2) = tmou(2) + rea**2*dlon*0.5*cos(zlon(i))*(zs(i,j)-zs(i,j+1))*( &
279        cos(zlat(j+1))*ps(i,j+1)+cos(zlat(j))*ps(i,j))
280    END DO
281  END DO
282
283  DO j = 2, nbp_lat-1
284    DO i = 1, nbp_lon
285      tmou(1) = tmou(1) + rea**2*dlat*0.5*sin(zlat(j))*(zs(i+1,j)-zs(i,j))*( &
286        cos(zlon(i+1))*ps(i+1,j)+cos(zlon(i))*ps(i,j))
287      tmou(2) = tmou(2) + rea**2*dlat*0.5*sin(zlat(j))*(zs(i+1,j)-zs(i,j))*( &
288        sin(zlon(i+1))*ps(i+1,j)+sin(zlon(i))*ps(i,j))
289      tmou(3) = tmou(3) - rea**2*dlat*0.5*cos(zlat(j))*(zs(i+1,j)-zs(i,j))*( &
290        ps(i+1,j)+ps(i,j))
291    END DO
292  END DO
293
294
295  ! COUPLES DES DIFFERENTES FRICTION AU SOL:
296
297  l = 1
298  DO j = 2, nbp_lat-1
299    DO i = 1, nbp_lon
300      l = l + 1
301      tsso(1) = tsso(1) - rea**3*cos(zlat(j))*dlon*dlat*ssou(i, j)*sin(zlat(j &
302        ))*cos(zlon(i)) + rea**3*cos(zlat(j))*dlon*dlat*ssov(i, j)*sin(zlon(i &
303        ))
304
305      tsso(2) = tsso(2) - rea**3*cos(zlat(j))*dlon*dlat*ssou(i, j)*sin(zlat(j &
306        ))*sin(zlon(i)) - rea**3*cos(zlat(j))*dlon*dlat*ssov(i, j)*cos(zlon(i &
307        ))
308
309      tsso(3) = tsso(3) + rea**3*cos(zlat(j))*dlon*dlat*ssou(i, j)*cos(zlat(j &
310        ))
311
312      tbls(1) = tbls(1) - rea**3*cos(zlat(j))*dlon*dlat*blsu(i, j)*sin(zlat(j &
313        ))*cos(zlon(i)) + rea**3*cos(zlat(j))*dlon*dlat*blsv(i, j)*sin(zlon(i &
314        ))
315
316      tbls(2) = tbls(2) - rea**3*cos(zlat(j))*dlon*dlat*blsu(i, j)*sin(zlat(j &
317        ))*sin(zlon(i)) - rea**3*cos(zlat(j))*dlon*dlat*blsv(i, j)*cos(zlon(i &
318        ))
319
320      tbls(3) = tbls(3) + rea**3*cos(zlat(j))*dlon*dlat*blsu(i, j)*cos(zlat(j &
321        ))
322
323    END DO
324  END DO
325
326
327  ! write(*,*) 'AAM',rsec,
328  ! write(*,*) 'AAM',rjour+rsec/86400.,
329  ! c      raam(3)/hadday,oaam(3)/hadday,
330  ! c      tmou(3)/hadley,tsso(3)/hadley,tbls(3)/hadley
331
332  ! write(iam,100)rjour+rsec/86400.,
333  ! c      raam(1)/hadday,oaam(1)/hadday,
334  ! c      tmou(1)/hadley,tsso(1)/hadley,tbls(1)/hadley,
335  ! c      raam(2)/hadday,oaam(2)/hadday,
336  ! c      tmou(2)/hadley,tsso(2)/hadley,tbls(2)/hadley,
337  ! c      raam(3)/hadday,oaam(3)/hadday,
338  ! c      tmou(3)/hadley,tsso(3)/hadley,tbls(3)/hadley
339100 FORMAT (F12.5, 15(1X,F12.5))
340
341  ! write(iam+1,*)((zs(i,j),i=1,nbp_lon),j=1,nbp_lat)
342  ! write(iam+1,*)((ps(i,j),i=1,nbp_lon),j=1,nbp_lat)
343  ! write(iam+1,*)((ub(i,j),i=1,nbp_lon),j=1,nbp_lat)
344  ! write(iam+1,*)((vb(i,j),i=1,nbp_lon),j=1,nbp_lat)
345  ! write(iam+1,*)((ssou(i,j),i=1,nbp_lon),j=1,nbp_lat)
346  ! write(iam+1,*)((ssov(i,j),i=1,nbp_lon),j=1,nbp_lat)
347  ! write(iam+1,*)((blsu(i,j),i=1,nbp_lon),j=1,nbp_lat)
348  ! write(iam+1,*)((blsv(i,j),i=1,nbp_lon),j=1,nbp_lat)
349
350  aam = raam(3)
351  torsfc = tmou(3) + tsso(3) + tbls(3)
352
353  RETURN
354END SUBROUTINE aaam_bud
Note: See TracBrowser for help on using the repository browser.