1 | MODULE gwstress_mod |
---|
2 | |
---|
3 | IMPLICIT NONE |
---|
4 | |
---|
5 | CONTAINS |
---|
6 | |
---|
7 | SUBROUTINE GWSTRESS(ngrid,nlayer,ktest,zrho, BV, pvar,psig,zgeom,zdmod,& |
---|
8 | ! Notice that this 3 variables are actually not used due to illness lines |
---|
9 | ICRIT,IKNU,ZVPH, & |
---|
10 | ! not used variables |
---|
11 | ! IKCRIT,ISECT,IKHLIM, IKCRITH,IKENVH,PVAR1,pgam,zd1,zd2,znu, & |
---|
12 | ! not defined not used variables |
---|
13 | ! ZTFR |
---|
14 | !in(as 0.0)-output: |
---|
15 | ZTAU ) |
---|
16 | |
---|
17 | !---------------------------------------------------------------------------------------------- |
---|
18 | ! MODULE contains SUBROUTINE gwstress to compute low level stresses using subcritical, super |
---|
19 | ! critical forms. |
---|
20 | ! F. LOTT PUT THE NEW GWD ON IFS 22/11/93 |
---|
21 | ! REFERENCE. |
---|
22 | ! SEE ECMWF RESEARCH DEPARTMENT DOCUMENTATION OF THE "I.F.S." |
---|
23 | ! Rewirten by J.Liu 03/03/2022 |
---|
24 | !---------------------------------------------------------------------------------------------- |
---|
25 | |
---|
26 | use dimradmars_mod, only: ndomainsz |
---|
27 | implicit none |
---|
28 | include "yoegwd.h" |
---|
29 | |
---|
30 | ! 0. DECLARATIONS: |
---|
31 | |
---|
32 | ! 0.1 ARGUMENTS |
---|
33 | integer,intent(in):: ngrid ! number of atmospheric columns |
---|
34 | integer,intent(in):: nlayer ! number of atmospheric layers |
---|
35 | INTEGER,intent(in):: ktest(ndomainsz) ! map of calling points |
---|
36 | ! integer,intent(in):: IKCRIT(ndomainsz) ! not used |
---|
37 | integer,intent(in):: ICRIT(ndomainsz) ! actually not used |
---|
38 | ! integer,intent(in):: IKCRITH(ndomainsz)! not used |
---|
39 | ! integer,intent(in):: ISECT(ndomainsz) ! not used |
---|
40 | ! integer,intent(in):: IKHLIM(ndomainsz) ! not used |
---|
41 | ! integer,intent(in):: IKENVH(ndomainsz) ! The line use this variable has been commented |
---|
42 | integer,intent(in):: IKNU(ndomainsz) ! actually not used |
---|
43 | REAL,INTENT(IN):: ZRHO(ndomainsz,nlayer+1) ! Density at 1/2 level |
---|
44 | REAL,INTENT(IN):: BV(ndomainsz,nlayer+1) ! Brunt–Väisälä frequency at 1/2 level |
---|
45 | REAL,INTENT(IN):: ZVPH(ndomainsz,nlayer+1) ! Low level wind speed U_H |
---|
46 | REAL,INTENT(IN):: zgeom(ndomainsz,nlayer) ! Geopotetial height |
---|
47 | REAL,INTENT(IN):: pvar(ndomainsz) ! Sub-grid scale standard deviation |
---|
48 | ! REAL,INTENT(IN):: zd1(ndomainsz) ! not used |
---|
49 | ! REAL,INTENT(IN):: zd2(ndomainsz) ! not used |
---|
50 | ! REAL,INTENT(IN):: znu(ndomainsz) ! not used |
---|
51 | REAL,INTENT(IN):: psig(ndomainsz) ! SUB-GRID SCALE SLOPE |
---|
52 | ! REAL,INTENT(IN):: pgam(ndomainsz) ! not used |
---|
53 | REAL,INTENT(IN):: zdmod(ndomainsz) ! Squre root of tao1 and tao2 without the constant, see equation 17 or 18 |
---|
54 | ! REAL,INTENT(IN):: ZTFR(ndomainsz) ! not used. It is not even defined in this rountine |
---|
55 | REAL,INTENT(INOUT):: ZTAU(ndomainsz,nlayer+1) !GRAVITY WAVE STRESS. |
---|
56 | |
---|
57 | !0.2 LOCAL ARRAYS |
---|
58 | integer jl |
---|
59 | INTEGER kidia,kfdia |
---|
60 | real zvar ! Sub-grid scale standard deviation at the calling points |
---|
61 | real zblock,zeff |
---|
62 | logical lo ! actually not used bucause the if-endif condition that use this |
---|
63 | ! variable has been commented |
---|
64 | |
---|
65 | !--------------------------------------------------------------------------------------------------- |
---|
66 | ! 1. INITIALIZATION (not important initialization at all may be delete in the future) |
---|
67 | !--------------------------------------------------------------------------------------------------- |
---|
68 | kidia=1 |
---|
69 | kfdia=ngrid |
---|
70 | 100 CONTINUE ! continue tag without source, maybe need delete in future |
---|
71 | !* 3.1 Gravity wave stress |
---|
72 | 300 CONTINUE ! continue tag without source, maybe need delete in future |
---|
73 | |
---|
74 | DO JL=kidia,kfdia |
---|
75 | IF(KTEST(JL).EQ.1) THEN |
---|
76 | !Effective mountain height above the blocked flow |
---|
77 | ! IF(IKENVH(JL).EQ.nlayer)THEN |
---|
78 | ZBLOCK=0.0 |
---|
79 | ! ELSE |
---|
80 | ! ZBLOCK=(zgeom(JL,IKENVH(JL))+zgeom(JL,IKENVH(JL)+1))/2./RG |
---|
81 | ! ENDIF |
---|
82 | ZVAR=pvar(JL) |
---|
83 | ZEFF=AMAX1(0.,2.*ZVAR-ZBLOCK) |
---|
84 | ! Evaluate equation 17 to get the GW stress |
---|
85 | ZTAU(JL,nlayer+1)=zrho(JL,nlayer+1)*GKDRAG*psig(jl)*ZEFF**2 & |
---|
86 | /4./ZVAR*ZVPH(JL,nlayer+1)*zdmod(jl)*sqrt(BV(jl,nlayer+1)) |
---|
87 | |
---|
88 | ! Too small value of stress or low level flow include critical level |
---|
89 | ! or low level flow: gravity wave stress nul. |
---|
90 | LO=(ZTAU(JL,nlayer+1).LT.GTSEC).OR.(ICRIT(JL).GE.IKNU(JL)).OR. & |
---|
91 | (ZVPH(JL,nlayer+1).LT.GVCRIT) |
---|
92 | ! IF(LO) ZTAU(JL,nlayer+1)=0.0 |
---|
93 | ELSE |
---|
94 | ZTAU(JL,nlayer+1)=0.0 |
---|
95 | ENDIF |
---|
96 | ENDDO |
---|
97 | |
---|
98 | END SUBROUTINE GWSTRESS |
---|
99 | |
---|
100 | END MODULE gwstress_mod |
---|