source: trunk/LMDZ.MARS/libf/dyn3d/sponge.F @ 1422

Last change on this file since 1422 was 1422, checked in by milmd, 10 years ago

In GENERIC, MARS and COMMON models replace some include files by modules (usefull for decoupling physics with dynamics).

File size: 3.6 KB
Line 
1      subroutine sponge(ucov,vcov,h,pext,dt,mode)
2
3! Sponge routine: Quench ucov, vcov and potential temperature near the
4!                 top of the model
5! Depending on 'mode' relaxation of variables is towards:
6! mode = 0 : h -> h_mean , ucov -> 0 , vcov -> 0
7! mode = 1 : h -> h_mean , ucov -> ucov_mean , vcov -> 0
8! mode >= 2 : h -> h_mean , ucov -> ucov_mean , vcov -> vcov_mean
9! Number of layer over which sponge is applied is 'nsponge' (read from def file)
10! Time scale for quenching at top level is given by 'tetasponge' (read from
11! def file) and doubles as level indexes decrease.
12
13      USE comvert_mod, ONLY: ap,bp,preff
14
15      implicit none
16#include "dimensions.h"
17#include "paramet.h"
18#include "comdissip.h"
19#include "comgeom2.h"
20#include "sponge.h"
21
22! Arguments:
23!------------
24      real,intent(inout) :: ucov(iip1,jjp1,llm) ! covariant zonal wind
25      real,intent(inout) :: vcov(iip1,jjm,llm) ! covariant meridional wind
26      real,intent(inout) :: h(iip1,jjp1,llm) ! potential temperature
27      real,intent(in) :: pext(iip1,jjp1) ! extensive pressure
28      real,intent(in) :: dt   ! time step
29      integer,intent(in) :: mode  ! sponge mode
30
31c   Local:
32c   ------
33
34      real,save :: sig_s(llm) !sigma au milieu des couches
35      REAL vm,um,hm,ptot(jjp1)
36      real,save :: cst(llm)
37
38      INTEGER l,i,j
39      integer,save :: l0 ! layer down to which sponge is applied
40
41      real ssum
42
43      real echelle,zkm
44      logical,save :: firstcall=.true.
45
46
47
48      if (firstcall) then
49
50       ! build approximative sigma levels at midlayer
51        do l=1,llm
52          sig_s(l)=((ap(l)+ap(l+1))/preff+bp(l)+bp(l+1))/2.
53        enddo
54
55        l0=llm-nsponge+1
56 
57        PRINT*
58        print*,'sponge mode',mode
59        print*,'nsponge tetasponge ',nsponge,tetasponge
60        print*,'Coeffs for the sponge layer'
61        print*,'Z (km)     tau      cst'
62        do l=llm,l0,-1
63          ! double time scale with every level, starting from the top
64          cst(l)=dt/(tetasponge*2**(llm-l))
65        enddo
66
67        echelle=10.
68        do l=l0,llm
69           zkm=-echelle*log(sig_s(l))
70           print*,zkm,dt/cst(l),cst(l)
71        enddo
72        PRINT*
73
74        firstcall=.false.
75      endif ! of if (firstcall)
76
77c-----------------------------------------------------------------------
78c   calcul de la dissipation:
79c   -------------------------
80
81      do j=1,jjp1
82         ptot(j)=ssum(iim,pext(1,j),1)
83      enddo
84 
85c   potential temperature
86      do l=l0,llm
87         do j=1,jjp1
88            hm=0.
89            do i=1,iim
90               hm=hm+h(i,j,l)*pext(i,j)
91            enddo
92            hm=hm/ptot(j)
93            do i=1,iim
94               h(i,j,l)=h(i,j,l)-cst(l)*(h(i,j,l)-hm)
95            enddo
96            h(iip1,j,l)=h(1,j,l)
97         enddo
98      enddo
99
100c   zonal wind
101      do l=l0,llm
102         do j=2,jjm
103            um=0.
104            if(mode.ge.1) then
105               do i=1,iim
106                  um=um+0.5*ucov(i,j,l)*(pext(i,j)+pext(i+1,j))
107     s               /cu(i,j)
108               enddo
109               um=um/ptot(j)
110            endif
111            do i=1,iim
112               ucov(i,j,l)=ucov(i,j,l)-cst(l)*(ucov(i,j,l)-um*cu(i,j))
113            enddo
114            ucov(iip1,j,l)=ucov(1,j,l)
115         enddo
116      enddo
117
118c  meridional wind
119      do l=l0,llm
120         do j=1,jjm
121            vm=0.
122            if(mode.ge.2) then
123               do i=1,iim
124                  vm=vm+vcov(i,j,l)*(pext(i,j)+pext(i,j+1))
125     s               /cv(i,j)
126               enddo
127               vm=vm/(ptot(j)+ptot(j+1))
128            endif
129            do i=1,iim
130               vcov(i,j,l)=vcov(i,j,l)-cst(l)*(vcov(i,j,l)-vm*cv(i,j))
131            enddo
132            vcov(iip1,j,l)=vcov(1,j,l)
133         enddo
134      enddo
135
136      end
Note: See TracBrowser for help on using the repository browser.