/[lmdze]/trunk/libf/phylmd/Orography/sugwd.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/Orography/sugwd.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 23 - (show annotations)
Mon Dec 14 15:25:16 2009 UTC (14 years, 5 months ago) by guez
File size: 2615 byte(s)
Split "orografi.f": one file for each procedure. Put the created files
in new directory "Orography".

Removed argument "vcov" of procedure "sortvarc". Removed arguments
"itau" and "time" of procedure "caldyn0". Removed arguments "itau",
"time" and "vcov" of procedure "sortvarc0".

Removed argument "time" of procedure "dynredem1". Removed NetCDF
variable "temps" in files "start.nc" and "restart.nc", because its
value is always 0.

Removed argument "nq" of procedures "iniadvtrac" and "leapfrog". The
number of "tracers read in "traceur.def" must now be equal to "nqmx",
or "nqmx" must equal 4 if there is no file "traceur.def". Replaced
variable "nq" by constant "nqmx" in "leapfrog".

NetCDF variable for ozone field in "coefoz.nc" must now be called
"tro3" instead of "r".

Fixed bug in "zenang".

1 SUBROUTINE sugwd(nlon,nlev,paprs,pplay)
2
3 !**** *SUGWD* INITIALIZE COMMON YOEGWD CONTROLLING GRAVITY WAVE DRAG
4
5 ! PURPOSE.
6 ! --------
7 ! INITIALIZE YOEGWD, THE COMMON THAT CONTROLS THE
8 ! GRAVITY WAVE DRAG PARAMETRIZATION.
9
10 !** INTERFACE.
11 ! ----------
12 ! CALL *SUGWD* FROM *SUPHEC*
13 ! ----- ------
14
15 ! EXPLICIT ARGUMENTS :
16 ! --------------------
17 ! PSIG : VERTICAL COORDINATE TABLE
18 ! NLEV : NUMBER OF MODEL LEVELS
19
20 ! IMPLICIT ARGUMENTS :
21 ! --------------------
22 ! COMMON YOEGWD
23
24 ! METHOD.
25 ! -------
26 ! SEE DOCUMENTATION
27
28 ! EXTERNALS.
29 ! ----------
30 ! NONE
31
32 ! REFERENCE.
33 ! ----------
34 ! ECMWF Research Department documentation of the IFS
35
36 ! AUTHOR.
37 ! -------
38 ! MARTIN MILLER *ECMWF*
39
40 ! MODIFICATIONS.
41 ! --------------
42 ! ORIGINAL : 90-01-01
43 ! ------------------------------------------------------------------
44 USE yoegwd
45 IMPLICIT NONE
46
47 ! -----------------------------------------------------------------
48 ! ----------------------------------------------------------------
49
50 INTEGER nlon, nlev, jk
51 REAL, INTENT (IN) :: paprs(nlon,nlev+1)
52 REAL, INTENT (IN) :: pplay(nlon,nlev)
53 REAL zpr, zstra, zsigt, zpm1r
54
55 !* 1. SET THE VALUES OF THE PARAMETERS
56 ! --------------------------------
57
58 100 CONTINUE
59
60 PRINT *, ' DANS SUGWD NLEV=', nlev
61 ghmax = 10000.
62
63 zpr = 100000.
64 zstra = 0.1
65 zsigt = 0.94
66 !old ZPR=80000.
67 !old ZSIGT=0.85
68
69 DO 110 jk = 1, nlev
70 zpm1r = pplay(nlon/2,jk)/paprs(nlon/2,1)
71 IF (zpm1r>=zsigt) THEN
72 nktopg = jk
73 END IF
74 zpm1r = pplay(nlon/2,jk)/paprs(nlon/2,1)
75 IF (zpm1r>=zstra) THEN
76 nstra = jk
77 END IF
78 110 CONTINUE
79
80 ! inversion car dans orodrag on compte les niveaux a l'envers
81 nktopg = nlev - nktopg + 1
82 nstra = nlev - nstra
83 PRINT *, ' DANS SUGWD nktopg=', nktopg
84 PRINT *, ' DANS SUGWD nstra=', nstra
85
86 gsigcr = 0.80
87
88 gkdrag = 0.2
89 grahilo = 1.
90 grcrit = 0.01
91 gfrcrit = 1.0
92 gkwake = 0.50
93
94 gklift = 0.50
95 gvcrit = 0.0
96
97
98 ! ----------------------------------------------------------------
99
100 !* 2. SET VALUES OF SECURITY PARAMETERS
101 ! ---------------------------------
102
103 200 CONTINUE
104
105 gvsec = 0.10
106 gssec = 1.E-12
107
108 gtsec = 1.E-07
109
110 ! ----------------------------------------------------------------
111
112 RETURN
113 END

  ViewVC Help
Powered by ViewVC 1.1.21