source: codes/icosagcm/devel/src/dissip/sponge.f90 @ 595

Last change on this file since 595 was 533, checked in by dubos, 7 years ago

devel : reorganization of source tree

File size: 4.0 KB
Line 
1MODULE sponge_mod
2  USE icosa
3
4  PRIVATE
5 
6  REAL,SAVE :: tau_sponge !inverse of charactericstic relaxation time scale at the topmost layer (Hz)
7  INTEGER,SAVE :: iflag_sponge !0 --> for no sponge
8                               !1 --> for sponge over 4 topmost layers
9                               !2 --> for sponge from top to ~1% of top layer pressure
10  INTEGER,SAVE :: mode_sponge !1 --> u and v relax towards 0
11                              !2 --> u and v relax towards their zonal mean
12                              !3 --> u,v and pot. temp. relax towards their zonal mean
13!$OMP THREADPRIVATE(tau_sponge,iflag_sponge,mode_sponge)
14  REAL,ALLOCATABLE,SAVE :: rdamp(:) ! quenching coefficient
15  REAL,ALLOCATABLE,SAVE:: lambda(:) ! inverse or quenching time scale (Hz)
16
17  PUBLIC sponge, init_sponge, iflag_sponge
18
19CONTAINS
20
21  SUBROUTINE init_sponge
22  USE icosa
23  USE disvert_mod
24  USE omp_para
25  USE mpipara, ONLY: is_mpi_master
26  IMPLICIT NONE
27    INTEGER :: l
28
29    tau_sponge = 1.e-4
30    CALL getin("tau_sponge",tau_sponge)
31    PRINT*,'tau_sponge = ',tau_sponge
32
33    iflag_sponge = 0
34    CALL getin("iflag_sponge",iflag_sponge)
35    PRINT*,'iflag_sponge = ',iflag_sponge
36   
37    mode_sponge = 1
38    CALL getin("mode_sponge",mode_sponge)
39    PRINT*,'mode_sponge = ',mode_sponge
40
41    IF (iflag_sponge == 0) THEN
42      PRINT*,'init_sponge: no sponge'
43      RETURN
44    ENDIF
45
46!$OMP MASTER
47    ALLOCATE(rdamp(llm))
48    ALLOCATE(lambda(llm))
49
50    IF (iflag_sponge == 1) THEN
51! sponge quenching over the topmost 4 atmospheric layers
52        lambda(:)=0.
53        lambda(llm)=tau_sponge
54        lambda(llm-1)=tau_sponge/2.
55        lambda(llm-2)=tau_sponge/4.
56        lambda(llm-3)=tau_sponge/8.
57    ELSE IF (iflag_sponge == 2) THEN
58! sponge quenching over topmost layers down to pressures which are
59! higher than 100 times the topmost layer pressure
60        lambda(:)=tau_sponge*max(presnivs(llm)/presnivs(:)-0.01,0.)
61    ELSE
62      PRINT*,'Bad selector for variable iflag_sponge : <',iflag_sponge,             &
63            '> options are 0,1,2'
64      STOP
65    ENDIF
66
67! quenching coefficient rdamp(:)
68!         rdamp(:)=dt*lambda(:) ! Explicit Euler approx.
69!      rdamp(:)=1.-exp(-lambda(:)*dt)
70    rdamp(:)=itau_dissip*lambda(:)
71
72
73    IF (is_mpi_master) THEN
74      PRINT*,'lambda = '
75      DO l=ll_begin,ll_end
76        PRINT*,l,lambda(l)
77      ENDDO
78      PRINT*,'rdamp = '
79      DO l=ll_begin,ll_end
80        PRINT*,l,rdamp(l)
81      ENDDO
82    ENDIF
83!$OMP END MASTER
84!$OMP BARRIER
85
86  END SUBROUTINE init_sponge
87
88  SUBROUTINE sponge(f_ue,f_due,f_theta_rhodz,f_dtheta_rhodz)
89  USE icosa
90  USE theta2theta_rhodz_mod
91  USE pression_mod
92  USE exner_mod
93  USE geopotential_mod
94  USE trace
95  USE time_mod
96  USE omp_para
97  IMPLICIT NONE
98    TYPE(t_field),POINTER :: f_ue(:)
99    TYPE(t_field),POINTER :: f_due(:)
100    TYPE(t_field),POINTER :: f_theta_rhodz(:)
101    TYPE(t_field),POINTER :: f_dtheta_rhodz(:)
102
103    REAL(rstd),POINTER         :: due(:,:)!,due_sponge(:,:)
104    REAL(rstd),POINTER         :: ue(:,:)
105    REAL(rstd),POINTER         :: theta_rhodz(:,:,:)
106    REAL(rstd),POINTER         :: dtheta_rhodz(:,:,:)!,dtheta_sponge(:,:)
107
108    INTEGER :: ind
109    INTEGER :: l,ij
110
111!$OMP BARRIER
112   
113    CALL trace_start("sponge")
114
115    IF (mode_sponge == 1) THEN
116      DO ind=1,ndomain
117        IF (.NOT. assigned_domain(ind)) CYCLE
118        CALL swap_dimensions(ind)
119        CALL swap_geometry(ind)
120        ue=f_ue(ind) 
121        due=f_due(ind) 
122        theta_rhodz=f_theta_rhodz(ind)
123        dtheta_rhodz=f_dtheta_rhodz(ind)
124
125        DO l=ll_begin,ll_end
126!$SIMD
127          DO ij=ij_begin,ij_end
128
129            due(ij+u_right,l) = -rdamp(l)*ue(ij+u_right,l)
130            due(ij+u_lup,l)   = -rdamp(l)*ue(ij+u_lup,l)
131            due(ij+u_ldown,l) = -rdamp(l)*ue(ij+u_ldown,l)
132
133            dtheta_rhodz(ij,l,:) = 0.0
134          ENDDO
135        ENDDO
136      END DO
137    ELSE
138      PRINT*,'Bad selector for variable mode_sponge : <',mode_sponge,             &
139            '> options 2 and 3 not available for the moment!'
140      STOP
141    ENDIF
142
143   CALL trace_end("sponge")
144
145!$OMP BARRIER
146  END SUBROUTINE sponge
147
148END MODULE sponge_mod
Note: See TracBrowser for help on using the repository browser.