source: LMDZ6/branches/Amaury_dev/libf/phylmd/aaam_bud.F90 @ 5201

Last change on this file since 5201 was 5116, checked in by abarral, 2 months ago

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

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