source: codes/icosagcm/trunk/src/dissip/sponge.f90 @ 1004

Last change on this file since 1004 was 953, checked in by adurocher, 5 years ago

trunk : GPU implementation with OpenACC ( merge from glcp.idris.fr )

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