/[lmdze]/trunk/phylmd/Orography/YOEGWD.f90
ViewVC logotype

Annotation of /trunk/phylmd/Orography/YOEGWD.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 158 - (hide annotations)
Tue Jul 21 14:44:45 2015 UTC (8 years, 11 months ago) by guez
Original Path: trunk/Sources/phylmd/Orography/YOEGWD.f
File size: 1510 byte(s)
Subroutine sugwd sets variables of module yoegwd. Better to put it
into module yoegwd.

Variables of module yoegwd other than NKTOPG, NSTRA can be symbolic
constants. sugwd now only sets NKTOPG, NSTRA. Simplified the
computation of NKTOPG, NSTRA by making the local variable zpm1r an
array instead of a scalar and calling ifirstloc.

1 guez 10 module yoegwd
2 guez 3
3 guez 49 ! From phylmd/YOEGWD.h, version 1.1.1.1 2004/05/19 12:53:08
4     ! Parameters for gravity wave drag calculations
5 guez 3
6 guez 10 implicit none
7    
8 guez 49 integer NKTOPG, NSTRA
9 guez 158 real, parameter:: GFRCRIT = 1., GKWAKE = 0.5, GRCRIT = 0.01, GVCRIT = 0.
10     real, parameter:: GKDRAG = 0.2, GKLIFT = 0.5, GRAHILO = 1., GSIGCR = 0.8
11 guez 10
12 guez 158 ! SECURITY PARAMETERS:
13     real, parameter:: GVSEC = 0.1, GSSEC = 1E-12, GTSEC = 1E-7
14    
15     contains
16    
17     SUBROUTINE sugwd(paprs, pplay)
18    
19     ! Initialize yoegwd, the common that controls the gravity wave
20     ! drag parametrization.
21    
22     ! REFERENCE: ECMWF Research Department documentation of the IFS
23     ! AUTHOR: MARTIN MILLER *ECMWF*
24     ! ORIGINAL : 90-01-01
25    
26     use nr_util, only: assert_eq, ifirstloc
27    
28     REAL, INTENT(IN):: paprs(:, :) ! (klon, llm + 1)
29     REAL, INTENT(IN):: pplay(:, :) ! (klon, llm)
30    
31     ! Local:
32     INTEGER klon, llm
33     real zpm1r(size(pplay, 2)) ! (llm)
34    
35     !------------------------------------------------------------
36    
37     print *, "Call sequence information: sugwd"
38     klon = assert_eq(size(paprs, 1), size(pplay, 1), "sugwd klon")
39     llm = assert_eq(size(paprs, 2) - 1, size(pplay, 2), "sugwd llm")
40    
41     ! 1. SET THE VALUES OF THE PARAMETERS
42    
43     zpm1r = pplay(klon / 2, llm:1:- 1) / paprs(klon / 2, 1)
44     ! inversion car dans orodrag on compte les niveaux \`a l'envers
45    
46     nktopg = ifirstloc(zpm1r >= 0.94)
47     nstra = ifirstloc(zpm1r >= 0.1) - 1
48     PRINT *, 'nktopg = ', nktopg
49     PRINT *, 'nstra = ', nstra
50    
51     END SUBROUTINE sugwd
52    
53 guez 10 end module yoegwd

Properties

Name Value
svn:eol-style native

  ViewVC Help
Powered by ViewVC 1.1.21