source: trunk/libf/phyvenus/sugwd.F @ 101

Last change on this file since 101 was 101, checked in by slebonnois, 14 years ago

SL: modifications pour arriver a compiler le gcm VENUS !
Ca marche !
A noter: modifs de makelmdz

File size: 5.0 KB
Line 
1      SUBROUTINE SUGWD(NLON,NLEV,paprs,pplay)
2C     
3C
4C**** *SUGWD* INITIALIZE COMMON YOEGWD CONTROLLING GRAVITY WAVE DRAG
5C
6C     PURPOSE.
7C     --------
8C           INITIALIZE YOEGWD, THE COMMON THAT CONTROLS THE
9C           GRAVITY WAVE DRAG PARAMETRIZATION.
10C    VERY IMPORTANT:
11C    ______________
12C           THIS ROUTINE SET_UP THE "TUNABLE PARAMETERS" OF THE
13C           VARIOUS SSO SCHEMES
14C
15C**   INTERFACE.
16C     ----------
17C        CALL *SUGWD* FROM *SUPHEC*
18C              -----        ------
19C (called not from suphec but from first call of physiq.F)
20C
21C        EXPLICIT ARGUMENTS :
22C        --------------------
23C        PAPRS,PPLAY : Pressure at semi and full model levels
24C        NLEV        : number of model levels
25c        NLON        : number of points treated in the physics
26C
27C        IMPLICIT ARGUMENTS :
28C        --------------------
29C        COMMON YOEGWD
30C-GFRCRIT-R:  Critical Non-dimensional mountain Height
31C             (HNC in (1),    LOTT 1999)
32C-GKWAKE--R:  Bluff-body drag coefficient for low level wake
33C             (Cd in (2),     LOTT 1999)
34C-GRCRIT--R:  Critical Richardson Number
35C             (Ric, End of first column p791 of LOTT 1999)
36C-GKDRAG--R:  Gravity wave drag coefficient
37C             (G in (3),      LOTT 1999)
38C-GKLIFT--R:  Mountain Lift coefficient
39C             (Cl in (4),     LOTT 1999)
40C-GHMAX---R:  Not used
41C-GRAHILO-R:  Set-up the trapped waves fraction
42C             (Beta , End of first column,  LOTT 1999)
43C
44C-GSIGCR--R:  Security value for blocked flow depth
45C-NKTOPG--I:  Security value for blocked flow level
46C-NTOP----I:  An estimate to qualify the upper levels of
47C             the model where one wants to impose strees
48C             profiles
49C-GSSECC--R:  Security min value for low-level B-V frequency
50C-GTSEC---R:  Security min value for anisotropy and GW stress.
51C-GVSEC---R:  Security min value for ulow
52C         
53C
54C     METHOD.
55C     -------
56C        SEE DOCUMENTATION
57C
58C     EXTERNALS.
59C     ----------
60C        NONE
61C
62C     REFERENCE.
63C     ----------
64C     Lott, 1999: Alleviation of stationary biases in a GCM through...
65C                 Monthly Weather Review, 127, pp 788-801.
66C
67C     AUTHOR.
68C     -------
69C        FRANCOIS LOTT        *LMD*
70C
71C     MODIFICATIONS.
72C     --------------
73C        ORIGINAL : 90-01-01 (MARTIN MILLER, ECMWF)
74C        LAST:  99-07-09     (FRANCOIS LOTT,LMD)
75C     ------------------------------------------------------------------
76      use dimphy
77      IMPLICIT NONE
78
79#include "dimensions.h"
80#include "paramet.h"
81
82#include "YOEGWD.h"
83C
84C  ARGUMENTS
85      integer nlon,nlev
86      REAL paprs(nlon,nlev+1)
87      REAL pplay(nlon,nlev)
88C
89      INTEGER JK
90      REAL ZPR,ZTOP,ZSIGT,ZPM1R
91
92C
93C*       1.    SET THE VALUES OF THE PARAMETERS
94C              --------------------------------
95C
96 100  CONTINUE
97C
98      PRINT *,' DANS SUGWD NLEV=',NLEV
99      GHMAX=10000.
100C
101      ZPR=100000.
102      ZTOP=0.001
103c valeurs dans la dernière routine de FLott
104c      ZSIGT=0.94
105c valeurs dans les routines Mars
106      ZSIGT=0.85
107C
108Coff  CALL gather(pplay,pplay_glo)
109Coff  CALL bcast(pplay_glo)
110Coff  CALL gather(paprs,paprs_glo)
111Coff  CALL bcast(paprs_glo)
112
113      DO 110 JK=1,NLEV
114Coff  ZPM1R=pplay_glo(klon_glo/2,jk)/paprs_glo(klon_glo/2,1)
115      ZPM1R=pplay(klon/2,jk)/paprs(klon/2,1)
116      IF(ZPM1R.GE.ZSIGT)THEN
117         nktopg=JK
118      ENDIF
119Coff  ZPM1R=pplay_glo(klon_glo/2,jk)/paprs_glo(klon_glo/2,1)
120      ZPM1R=pplay(klon/2,jk)/paprs(klon/2,1)
121      IF(ZPM1R.GE.ZTOP)THEN
122         ntop=JK
123      ENDIF
124  110 CONTINUE
125c
126c  inversion car dans orodrag on compte les niveaux a l'envers
127      nktopg=nlev-nktopg+1
128      ntop=nlev-ntop
129      print *,' DANS SUGWD nktopg=', nktopg
130      print *,' DANS SUGWD ntop=', ntop
131C
132      GSIGCR=0.80
133C
134c valeurs dans la dernière routine de FLott
135c      GKDRAG=0.1875
136c      GRAHILO=0.1   
137c      GRCRIT=1.00
138c      GFRCRIT=1.00
139c      GKWAKE=0.50
140C
141c      GKLIFT=0.25
142c      GVCRIT =0.1
143
144c valeurs dans les routines Mars
145      GKDRAG=0.1
146      GRAHILO=1.0   
147      GRCRIT=0.25
148      GFRCRIT=1.00
149      GKWAKE=1.0
150C
151      GKLIFT=0.25
152      GVCRIT =0.0
153
154      WRITE(UNIT=6,FMT='('' *** SSO essential constants ***'')')
155      WRITE(UNIT=6,FMT='('' *** SPECIFIED IN SUGWD ***'')')
156      WRITE(UNIT=6,FMT='('' Gravity wave ct '',E13.7,'' '')')GKDRAG
157      WRITE(UNIT=6,FMT='('' Trapped/total wave dag '',E13.7,'' '')')
158     S      GRAHILO
159      WRITE(UNIT=6,FMT='('' Critical Richardson   = '',E13.7,'' '')')
160     S                  GRCRIT
161      WRITE(UNIT=6,FMT='('' Critical Froude'',e13.7)') GFRCRIT
162      WRITE(UNIT=6,FMT='('' Low level Wake bluff cte'',e13.7)') GKWAKE
163      WRITE(UNIT=6,FMT='('' Low level lift  cte'',e13.7)') GKLIFT
164
165C
166C
167C      ----------------------------------------------------------------
168C
169C*       2.    SET VALUES OF SECURITY PARAMETERS
170C              ---------------------------------
171C
172 200  CONTINUE
173C
174c valeurs dans la dernière routine de FLott
175c      GVSEC=0.10
176c      GSSEC=0.0001
177C
178c      GTSEC=0.00001
179C
180c valeurs dans les routines Mars
181      GVSEC=0.10
182      GSSEC=1.e-12
183C
184      GTSEC=1.e-7
185C
186      RETURN
187      END
188
Note: See TracBrowser for help on using the repository browser.