source: trunk/LMDZ.MARS/libf/phymars/gwstress_mod.F90 @ 2740

Last change on this file since 2740 was 2651, checked in by emillour, 3 years ago

Mars GCM:

  • turn sugwd.F to sugwd.F90 with extra comments
  • turn yoegwd.h into a module

JL+EM

File size: 4.6 KB
Line 
1MODULE gwstress_mod
2     
3IMPLICIT NONE
4     
5CONTAINS
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      use yoegwd_h, only: gkdrag, gtsec, gvcrit
28
29      implicit none
30     
31      ! 0. DECLARATIONS:
32     
33      ! 0.1   ARGUMENTS
34      integer,intent(in):: ngrid    ! number of atmospheric columns
35      integer,intent(in):: nlayer   ! number of atmospheric layers
36      INTEGER,intent(in):: ktest(ndomainsz)   ! map of calling points
37!      integer,intent(in):: IKCRIT(ndomainsz) ! not used
38      integer,intent(in):: ICRIT(ndomainsz)   ! actually not used
39 !     integer,intent(in):: IKCRITH(ndomainsz)! not used
40 !     integer,intent(in):: ISECT(ndomainsz)  ! not used
41 !     integer,intent(in):: IKHLIM(ndomainsz) ! not used
42 !     integer,intent(in):: IKENVH(ndomainsz) ! The line use this variable has been commented
43      integer,intent(in):: IKNU(ndomainsz)    ! actually not used
44      REAL,INTENT(IN):: ZRHO(ndomainsz,nlayer+1) ! Density at 1/2 level
45      REAL,INTENT(IN):: BV(ndomainsz,nlayer+1)   ! Brunt–Väisälä frequency at 1/2 level
46      REAL,INTENT(IN):: ZVPH(ndomainsz,nlayer+1) ! Low level wind speed U_H
47      REAL,INTENT(IN):: zgeom(ndomainsz,nlayer)  ! Geopotetial height
48      REAL,INTENT(IN):: pvar(ndomainsz)          ! Sub-grid scale standard deviation
49!      REAL,INTENT(IN):: zd1(ndomainsz)       ! not used
50!      REAL,INTENT(IN):: zd2(ndomainsz)       ! not used
51!      REAL,INTENT(IN):: znu(ndomainsz)       ! not used
52      REAL,INTENT(IN):: psig(ndomainsz)       ! SUB-GRID SCALE SLOPE
53!      REAL,INTENT(IN):: pgam(ndomainsz)      ! not used
54      REAL,INTENT(IN):: zdmod(ndomainsz)      ! Squre root of tao1 and tao2 without the constant, see equation 17 or 18
55!      REAL,INTENT(IN):: ZTFR(ndomainsz)      ! not used. It is not even defined in this rountine
56      REAL,INTENT(INOUT):: ZTAU(ndomainsz,nlayer+1) !GRAVITY WAVE STRESS.
57     
58      !0.2   LOCAL ARRAYS
59      integer jl
60      INTEGER kidia,kfdia
61      real zvar    ! Sub-grid scale standard deviation at the calling points
62      real zblock,zeff
63      logical lo   ! actually not used bucause the if-endif condition that use this
64                   ! variable has been commented
65                   
66!---------------------------------------------------------------------------------------------------
67! 1. INITIALIZATION (not important initialization at all may be delete in the future)
68!---------------------------------------------------------------------------------------------------
69      kidia=1
70      kfdia=ngrid
71 100   CONTINUE ! continue tag without source, maybe need delete in future
72!*         3.1     Gravity wave stress
73 300   CONTINUE ! continue tag without source, maybe need delete in future
74
75      DO JL=kidia,kfdia
76        IF(KTEST(JL).EQ.1) THEN
77        !Effective mountain height above the blocked flow     
78!        IF(IKENVH(JL).EQ.nlayer)THEN
79         ZBLOCK=0.0
80!        ELSE
81!         ZBLOCK=(zgeom(JL,IKENVH(JL))+zgeom(JL,IKENVH(JL)+1))/2./RG         
82!        ENDIF   
83        ZVAR=pvar(JL)
84        ZEFF=AMAX1(0.,2.*ZVAR-ZBLOCK)
85        ! Evaluate equation 17 to get the GW stress
86        ZTAU(JL,nlayer+1)=zrho(JL,nlayer+1)*GKDRAG*psig(jl)*ZEFF**2    &
87         /4./ZVAR*ZVPH(JL,nlayer+1)*zdmod(jl)*sqrt(BV(jl,nlayer+1))
88
89      !  Too small value of stress or low level flow include critical level
90      !  or low level flow: gravity wave stress nul.                 
91        LO=(ZTAU(JL,nlayer+1).LT.GTSEC).OR.(ICRIT(JL).GE.IKNU(JL)).OR. &
92        (ZVPH(JL,nlayer+1).LT.GVCRIT)
93!       IF(LO) ZTAU(JL,nlayer+1)=0.0     
94        ELSE     
95          ZTAU(JL,nlayer+1)=0.0         
96        ENDIF     
97      ENDDO
98
99      END SUBROUTINE GWSTRESS
100     
101END MODULE gwstress_mod
Note: See TracBrowser for help on using the repository browser.