source: trunk/LMDZ.TITAN.old/libf/phytitan/drag_noro.F @ 3303

Last change on this file since 3303 was 1530, checked in by emillour, 9 years ago

Venus and Titan GCMs:
Updates in the physics to keep up with updates in LMDZ5 (up to
LMDZ5 trunk, rev 2350) concerning dynamics/physics separation:

  • Adapted makelmdz and makelmdz_fcm script to stop if trying to compile 1d model or newstart or start2archive in parallel.
  • got rid of references to "dimensions.h" in physics. Within physics packages, use nbp_lon (=iim), nbp_lat (=jjmp1) and nbp_lev (=llm) from module mod_grid_phy_lmdz (in phy_common) instead. Only partially done for Titan, because of many hard-coded commons; a necessary first step will be to clean these up (using modules).

EM

File size: 5.2 KB
Line 
1
2C  SUBROUTINE DE PARAMETRISATION DES MONTAGNES D ECHELLE SOUS MAILLE
3
4      SUBROUTINE drag_noro (nlon,nlev,dtime,paprs,pplay,pgeop,pn2,
5     e                   pmea,pstd, psig, pgam, pthe,ppic,pval,
6     e                   kgwd,kdx,ktest,
7     e                   t, u, v,
8     s                   pulow, pvlow, pustr, pvstr,
9     s                   d_t, d_u, d_v)
10c
11      use dimphy
12      IMPLICIT none
13
14c======================================================================
15c Auteur(s): F.Lott (LMD/CNRS) date: 19950201
16c Object: Mountain drag interface. Made necessary because:
17C 1. in the LMD-GCM Layers are from bottom to top,
18C    contrary to most European GCM.
19c 2. the altitude above ground of each model layers
20c    needs to be known (variable zgeom)
21c======================================================================
22c Explicit Arguments:
23c ==================
24c nlon----input-I-Total number of horizontal points that get into physics
25c nlev----input-I-Number of vertical levels
26c dtime---input-R-Time-step (s)
27c paprs---input-R-Pressure in semi layers    (Pa)
28c pplay---input-R-Pressure model-layers      (Pa)
29c pgeop---input-R-Geopotential model layers (reference to ground)
30c pn2-----input-R-Brunt-Vaisala freq.^2 at 1/2 layers
31c t-------input-R-temperature (K)
32c u-------input-R-Horizontal wind (m/s)
33c v-------input-R-Meridional wind (m/s)
34c pmea----input-R-Mean Orography (m)
35C pstd----input-R-SSO standard deviation (m)
36c psig----input-R-SSO slope
37c pgam----input-R-SSO Anisotropy
38c pthe----input-R-SSO Angle
39c ppic----input-R-SSO Peacks elevation (m)
40c pval----input-R-SSO Valleys elevation (m)
41c
42c kgwd- -input-I: Total nb of points where the orography schemes are active
43c ktest--input-I: Flags to indicate active points
44c kdx----input-I: Locate the physical location of an active point.
45
46c pulow, pvlow -output-R: Low-level wind
47c pustr, pvstr -output-R: Surface stress due to SSO drag      (Pa)
48c
49c d_t-----output-R: T increment           
50c d_u-----output-R: U increment             
51c d_v-----output-R: V increment             
52c
53c Implicit Arguments:
54c ===================
55c
56c iim--common-I: Number of longitude intervals
57c jjm--common-I: Number of latitude intervals
58c klon-common-I: Number of points seen by the physics
59c                (iim+1)*(jjm+1) for instance
60c klev-common-I: Number of vertical layers
61c======================================================================
62c Local Variables:
63c ================
64c
65c zgeom-----R: Altitude (m) of layer above ground (from top to bottom)
66c pt, pu, pv --R: t u v from top to bottom
67c pdtdt, pdudt, pdvdt --R: t u v tendencies (from top to bottom)
68c papmf: pressure at model layer (from top to bottom)
69c papmh: pressure at model 1/2 layer (from top to bottom)
70c
71c======================================================================
72
73#include "YOMCST.h"
74#include "YOEGWD.h"
75
76c  ARGUMENTS
77c
78      INTEGER nlon,nlev
79      REAL dtime
80      REAL paprs(nlon,nlev+1)
81      REAL pplay(nlon,nlev)
82      REAL pgeop(nlon,nlev),pn2(nlon,nlev)
83      REAL pmea(nlon),pstd(nlon),psig(nlon),pgam(nlon),pthe(nlon)
84      REAL ppic(nlon),pval(nlon)
85      REAL pulow(nlon),pvlow(nlon),pustr(nlon),pvstr(nlon)
86      REAL t(nlon,nlev), u(nlon,nlev), v(nlon,nlev)
87      REAL d_t(nlon,nlev), d_u(nlon,nlev), d_v(nlon,nlev)
88c
89      INTEGER i, k, kgwd,  kdx(nlon), ktest(nlon)
90c
91c LOCAL VARIABLES:
92c
93      REAL zgeom(klon,klev),zn2(klon,klev)
94      REAL pdtdt(klon,klev), pdudt(klon,klev), pdvdt(klon,klev)
95      REAL pt(klon,klev), pu(klon,klev), pv(klon,klev)
96      REAL papmf(klon,klev),papmh(klon,klev+1)
97c
98c INITIALIZE OUTPUT VARIABLES
99c
100      DO i = 1,klon
101         pulow(i) = 0.0
102         pvlow(i) = 0.0
103         pustr(i) = 0.0
104         pvstr(i) = 0.0
105      ENDDO
106      DO k = 1, klev
107      DO i = 1, klon
108         d_t(i,k) = 0.0
109         d_u(i,k) = 0.0
110         d_v(i,k) = 0.0
111         pdudt(i,k)=0.0
112         pdvdt(i,k)=0.0
113         pdtdt(i,k)=0.0
114      ENDDO
115      ENDDO
116c
117c PREPARE INPUT VARIABLES FOR ORODRAG (i.e., ORDERED FROM TOP TO BOTTOM)
118C CALCULATE LAYERS HEIGHT ABOVE GROUND)
119c
120      DO k = 1, klev
121      DO i = 1, klon
122         pt(i,k) = t(i,klev-k+1)
123         pu(i,k) = u(i,klev-k+1)
124         pv(i,k) = v(i,klev-k+1)
125         papmf(i,k) = pplay(i,klev-k+1)
126      ENDDO
127      ENDDO
128      DO k = 1, klev+1
129      DO i = 1, klon
130         papmh(i,k) = paprs(i,klev-k+2)
131      ENDDO
132      ENDDO
133
134      DO k = klev, 1, -1
135      DO i = 1, klon
136         zgeom(i,k) = pgeop(i,klev-k+1)/RG
137         zn2(i,k)   = pn2(i,klev-k+1)
138      ENDDO
139      ENDDO
140
141c CALL SSO DRAG ROUTINES       
142c
143      CALL orodrag(klon,klev,kgwd,kdx,ktest,
144     .            dtime,
145     .            papmh, papmf, zgeom, zn2,
146     .            pt, pu, pv,
147     .            pmea, pstd, psig, pgam, pthe, ppic,pval,
148     .            pulow,pvlow,
149     .            pdudt,pdvdt,pdtdt)
150C
151C COMPUTE INCREMENTS AND STRESS FROM TENDENCIES
152
153      DO k = 1, klev
154      DO i = 1, klon
155         d_u(i,klev+1-k) = dtime*pdudt(i,k)
156         d_v(i,klev+1-k) = dtime*pdvdt(i,k)
157         d_t(i,klev+1-k) = dtime*pdtdt(i,k)
158         pustr(i)        = pustr(i)
159     .                    +pdudt(i,k)*(papmh(i,k+1)-papmh(i,k))/rg
160         pvstr(i)        = pvstr(i)
161     .                    +pdvdt(i,k)*(papmh(i,k+1)-papmh(i,k))/rg
162      ENDDO
163      ENDDO
164c
165      RETURN
166      END
167
Note: See TracBrowser for help on using the repository browser.