source: palm/trunk/SOURCE/coriolis.f90 @ 1682

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

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