source: palm/trunk/SOURCE/coriolis_mod.f90 @ 1850

Last change on this file since 1850 was 1850, checked in by maronga, 8 years ago

added _mod string to several filenames to meet the naming convection for modules

  • Property svn:keywords set to Id
File size: 11.0 KB
Line 
1!> @file coriolis_mod.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2016 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21! Module renamed
22!
23!
24! Former revisions:
25! -----------------
26! $Id: coriolis_mod.f90 1850 2016-04-08 13:29:27Z maronga $
27!
28! 1682 2015-10-07 23:56:08Z knoop
29! Code annotations made doxygen readable
30!
31! 1353 2014-04-08 15:21:23Z heinze
32! REAL constants provided with KIND-attribute
33!
34! 1320 2014-03-20 08:40:49Z raasch
35! ONLY-attribute added to USE-statements,
36! kind-parameters added to all INTEGER and REAL declaration statements,
37! kinds are defined in new module kinds,
38! revision history before 2012 removed,
39! comment fields (!:) to be used for variable explanations added to
40! all variable declaration statements
41!
42! 1257 2013-11-08 15:18:40Z raasch
43! openacc loop and loop vector clauses removed
44!
45! 1128 2013-04-12 06:19:32Z raasch
46! loop index bounds in accelerator version replaced by i_left, i_right, j_south,
47! j_north
48!
49! 1036 2012-10-22 13:43:42Z raasch
50! code put under GPL (PALM 3.9)
51!
52! 1015 2012-09-27 09:23:24Z raasch
53! accelerator version (*_acc) added
54!
55! Revision 1.1  1997/08/29 08:57:38  raasch
56! Initial revision
57!
58!
59! Description:
60! ------------
61!> Computation of all Coriolis terms in the equations of motion.
62!------------------------------------------------------------------------------!
63 MODULE coriolis_mod
64 
65
66    PRIVATE
67    PUBLIC coriolis, coriolis_acc
68
69    INTERFACE coriolis
70       MODULE PROCEDURE coriolis
71       MODULE PROCEDURE coriolis_ij
72    END INTERFACE coriolis
73
74    INTERFACE coriolis_acc
75       MODULE PROCEDURE coriolis_acc
76    END INTERFACE coriolis_acc
77
78 CONTAINS
79
80
81!------------------------------------------------------------------------------!
82! Description:
83! ------------
84!> Call for all grid points
85!------------------------------------------------------------------------------!
86    SUBROUTINE coriolis( component )
87
88       USE arrays_3d,                                                          &
89           ONLY:  tend, u, ug, v, vg, w 
90           
91       USE control_parameters,                                                 &
92           ONLY:  f, fs, message_string
93           
94       USE indices,                                                            &
95           ONLY:  nxl, nxlu, nxr, nyn, nys, nysv, nzb_u_inner, nzb_v_inner,    &
96                  nzb_w_inner, nzt
97                   
98       USE kinds
99
100       IMPLICIT NONE
101
102       INTEGER(iwp) ::  component  !<
103       INTEGER(iwp) ::  i          !<
104       INTEGER(iwp) ::  j          !<
105       INTEGER(iwp) ::  k          !<
106
107
108!
109!--    Compute Coriolis terms for the three velocity components
110       SELECT CASE ( component )
111
112!
113!--       u-component
114          CASE ( 1 )
115             DO  i = nxlu, nxr
116                DO  j = nys, nyn
117                   DO  k = nzb_u_inner(j,i)+1, nzt
118                      tend(k,j,i) = tend(k,j,i) + f  *    ( 0.25_wp *          &
119                                   ( v(k,j,i-1) + v(k,j,i) + v(k,j+1,i-1) +    &
120                                     v(k,j+1,i) ) - vg(k) )                    &
121                                                - fs *    ( 0.25_wp *          &
122                                   ( w(k-1,j,i-1) + w(k-1,j,i) + w(k,j,i-1) +  &
123                                     w(k,j,i)   ) &
124                                                          )
125                   ENDDO
126                ENDDO
127             ENDDO
128
129!
130!--       v-component
131          CASE ( 2 )
132             DO  i = nxl, nxr
133                DO  j = nysv, nyn
134                   DO  k = nzb_v_inner(j,i)+1, nzt
135                      tend(k,j,i) = tend(k,j,i) - f *     ( 0.25_wp *          &
136                                   ( u(k,j-1,i) + u(k,j,i) + u(k,j-1,i+1) +    &
137                                     u(k,j,i+1) ) - ug(k) )
138                   ENDDO
139                ENDDO
140             ENDDO
141
142!
143!--       w-component
144          CASE ( 3 )
145             DO  i = nxl, nxr
146                DO  j = nys, nyn
147                   DO  k = nzb_w_inner(j,i)+1, nzt
148                      tend(k,j,i) = tend(k,j,i) + fs * 0.25_wp *               &
149                                   ( u(k,j,i) + u(k+1,j,i) + u(k,j,i+1) +      &
150                                     u(k+1,j,i+1) )
151                   ENDDO
152                ENDDO
153             ENDDO
154
155          CASE DEFAULT
156
157             WRITE( message_string, * ) ' wrong component: ', component
158             CALL message( 'coriolis', 'PA0173', 1, 2, 0, 6, 0 )
159
160       END SELECT
161
162    END SUBROUTINE coriolis
163
164
165!------------------------------------------------------------------------------!
166! Description:
167! ------------
168!> Call for all grid points - accelerator version
169!------------------------------------------------------------------------------!
170    SUBROUTINE coriolis_acc( component )
171
172       USE arrays_3d,                                                          &
173           ONLY:  tend, u, ug, v, vg, w 
174           
175       USE control_parameters,                                                 &
176           ONLY:  f, fs, message_string
177           
178       USE indices,                                                            &
179           ONLY:  i_left, i_right, j_north, j_south, nzb_u_inner,              &
180                  nzb_v_inner, nzb_w_inner, nzt
181                   
182       USE kinds
183
184       IMPLICIT NONE
185
186       INTEGER(iwp) ::  component  !<
187       INTEGER(iwp) ::  i          !<
188       INTEGER(iwp) ::  j          !<
189       INTEGER(iwp) ::  k          !<
190
191
192!
193!--    Compute Coriolis terms for the three velocity components
194       SELECT CASE ( component )
195
196!
197!--       u-component
198          CASE ( 1 )
199             !$acc  kernels present( nzb_u_inner, tend, v, vg, w )
200             DO  i = i_left, i_right
201                DO  j = j_south, j_north
202                   DO  k = 1, nzt
203                      IF  ( k > nzb_u_inner(j,i) )  THEN
204                         tend(k,j,i) = tend(k,j,i) + f  *    ( 0.25_wp *       &
205                                      ( v(k,j,i-1) + v(k,j,i) + v(k,j+1,i-1) + &
206                                        v(k,j+1,i) ) - vg(k) )                 &
207                                                   - fs *    ( 0.25_wp *       &
208                                      ( w(k-1,j,i-1) + w(k-1,j,i) + w(k,j,i-1) &
209                                        + w(k,j,i)   )                         &
210                                                             )
211                      ENDIF
212                   ENDDO
213                ENDDO
214             ENDDO
215             !$acc end kernels
216
217!
218!--       v-component
219          CASE ( 2 )
220             !$acc  kernels present( nzb_v_inner, tend, u, ug )
221             DO  i = i_left, i_right
222                DO  j = j_south, j_north
223                   DO  k = 1, nzt
224                      IF  ( k > nzb_v_inner(j,i) )  THEN
225                         tend(k,j,i) = tend(k,j,i) - f *     ( 0.25_wp *       &
226                                      ( u(k,j-1,i) + u(k,j,i) + u(k,j-1,i+1) + &
227                                        u(k,j,i+1) ) - ug(k) )
228                      ENDIF
229                   ENDDO
230                ENDDO
231             ENDDO
232             !$acc end kernels
233
234!
235!--       w-component
236          CASE ( 3 )
237             !$acc  kernels present( nzb_w_inner, tend, u )
238             DO  i = i_left, i_right
239                DO  j = j_south, j_north
240                   DO  k = 1, nzt
241                      IF  ( k > nzb_w_inner(j,i) )  THEN
242                         tend(k,j,i) = tend(k,j,i) + fs * 0.25_wp *            &
243                                      ( u(k,j,i) + u(k+1,j,i) + u(k,j,i+1) +   &
244                                        u(k+1,j,i+1) )
245                      ENDIF
246                   ENDDO
247                ENDDO
248             ENDDO
249             !$acc end kernels
250
251          CASE DEFAULT
252
253             WRITE( message_string, * ) ' wrong component: ', component
254             CALL message( 'coriolis', 'PA0173', 1, 2, 0, 6, 0 )
255
256       END SELECT
257
258    END SUBROUTINE coriolis_acc
259
260
261!------------------------------------------------------------------------------!
262! Description:
263! ------------
264!> Call for grid point i,j
265!------------------------------------------------------------------------------!
266    SUBROUTINE coriolis_ij( i, j, component )
267
268       USE arrays_3d,                                                          &
269           ONLY:  tend, u, ug, v, vg, w 
270           
271       USE control_parameters,                                                 &
272           ONLY:  f, fs, message_string
273           
274       USE indices,                                                            &
275           ONLY:  nzb_u_inner, nzb_v_inner, nzb_w_inner, nzt
276           
277       USE kinds
278       
279       IMPLICIT NONE
280
281       INTEGER(iwp) ::  component  !<
282       INTEGER(iwp) ::  i          !<
283       INTEGER(iwp) ::  j          !<
284       INTEGER(iwp) ::  k          !<
285
286!
287!--    Compute Coriolis terms for the three velocity components
288       SELECT CASE ( component )
289
290!
291!--       u-component
292          CASE ( 1 )
293             DO  k = nzb_u_inner(j,i)+1, nzt
294                tend(k,j,i) = tend(k,j,i) + f  *    ( 0.25_wp *                &
295                                ( v(k,j,i-1) + v(k,j,i) + v(k,j+1,i-1) +       &
296                                  v(k,j+1,i) ) - vg(k) )                       &
297                                          - fs *    ( 0.25_wp *                &
298                                ( w(k-1,j,i-1) + w(k-1,j,i) + w(k,j,i-1) +     &
299                                  w(k,j,i)   ) )
300             ENDDO
301
302!
303!--       v-component
304          CASE ( 2 )
305             DO  k = nzb_v_inner(j,i)+1, nzt
306                tend(k,j,i) = tend(k,j,i) - f *     ( 0.25_wp *                &
307                                ( u(k,j-1,i) + u(k,j,i) + u(k,j-1,i+1) +       &
308                                  u(k,j,i+1) ) - ug(k) )
309             ENDDO
310
311!
312!--       w-component
313          CASE ( 3 )
314             DO  k = nzb_w_inner(j,i)+1, nzt
315                tend(k,j,i) = tend(k,j,i) + fs * 0.25_wp *                     &
316                                ( u(k,j,i) + u(k+1,j,i) + u(k,j,i+1) +         &
317                                  u(k+1,j,i+1) )
318             ENDDO
319
320          CASE DEFAULT
321
322             WRITE( message_string, * ) ' wrong component: ', component
323             CALL message( 'coriolis', 'PA0173', 1, 2, 0, 6, 0 )
324
325       END SELECT
326
327    END SUBROUTINE coriolis_ij
328
329 END MODULE coriolis_mod
Note: See TracBrowser for help on using the repository browser.