source: palm/trunk/SOURCE/advec_s_pw.f90 @ 1374

Last change on this file since 1374 was 1374, checked in by raasch, 10 years ago

bugfixes:
missing variables added to ONLY lists in USE statements (advec_s_bc, advec_s_pw, advec_s_up, advec_ws, buoyancy, diffusion_e, diffusion_s, fft_xy, flow_statistics, palm, prognostic_equations)
missing module kinds added (cuda_fft_interfaces)
dpk renamed dp (fft_xy)
missing dependency for check_open added (Makefile)
variables removed from acc-present-list (diffusion_e, diffusion_w, diffusivities, production_e, wall_fluxes)
syntax errors removed from openacc-branch (flow_statistics)
USE-statement for nopointer-case added (swap_timelevel)

  • Property svn:keywords set to Id
File size: 6.2 KB
Line 
1 MODULE advec_s_pw_mod
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! missing variables added to ONLY list
23!
24! Former revisions:
25! -----------------
26! $Id: advec_s_pw.f90 1374 2014-04-25 12:55:07Z raasch $
27!
28! 1353 2014-04-08 15:21:23Z heinze
29! REAL constants provided with KIND-attribute
30!
31! 1320 2014-03-20 08:40:49Z raasch
32! ONLY-attribute added to USE-statements,
33! kind-parameters added to all INTEGER and REAL declaration statements,
34! kinds are defined in new module kinds,
35! revision history before 2012 removed,
36! comment fields (!:) to be used for variable explanations added to
37! all variable declaration statements
38!
39! 1036 2012-10-22 13:43:42Z raasch
40! code put under GPL (PALM 3.9)
41!
42! 1010 2012-09-20 07:59:54Z raasch
43! cpp switch __nopointer added for pointer free version
44!
45! Revision 1.1  1997/08/29 08:54:20  raasch
46! Initial revision
47!
48!
49! Description:
50! ------------
51! Advection term for scalar variables using the Piacsek and Williams scheme
52! (form C3). Contrary to PW itself, for reasons of accuracy their scheme is
53! slightly modified as follows: the values of those scalars that are used for
54! the computation of the flux divergence are reduced by the value of the
55! relevant scalar at the location where the difference is computed (sk(k,j,i)).
56! NOTE: at the first grid point above the surface computation still takes place!
57!------------------------------------------------------------------------------!
58
59    PRIVATE
60    PUBLIC advec_s_pw
61
62    INTERFACE advec_s_pw
63       MODULE PROCEDURE advec_s_pw
64       MODULE PROCEDURE advec_s_pw_ij
65    END INTERFACE
66 
67 CONTAINS
68
69
70!------------------------------------------------------------------------------!
71! Call for all grid points
72!------------------------------------------------------------------------------!
73    SUBROUTINE advec_s_pw( sk )
74
75       USE arrays_3d,                                                          &
76           ONLY:  dd2zu, tend, u, v, w
77
78       USE control_parameters,                                                 &
79           ONLY:  u_gtrans, v_gtrans
80
81       USE grid_variables,                                                     &
82           ONLY:  ddx, ddy
83
84       USE indices,                                                            &
85           ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzb_s_inner,&
86                  nzt
87
88       USE kinds
89
90
91       IMPLICIT NONE
92
93       INTEGER(iwp) ::  i !:
94       INTEGER(iwp) ::  j !:
95       INTEGER(iwp) ::  k !:
96
97#if defined( __nopointer )
98       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !:
99#else
100       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
101#endif
102 
103
104       DO  i = nxl, nxr
105          DO  j = nys, nyn
106             DO  k = nzb_s_inner(j,i)+1, nzt
107                tend(k,j,i) = tend(k,j,i)                                      &
108              -0.5_wp * ( ( u(k,j,i+1) - u_gtrans ) * ( sk(k,j,i+1) - sk(k,j,i) ) &
109                        - ( u(k,j,i)   - u_gtrans ) * ( sk(k,j,i-1) - sk(k,j,i) ) &
110                        ) * ddx                                                   &
111              -0.5_wp * ( ( v(k,j+1,i) - v_gtrans ) * ( sk(k,j+1,i) - sk(k,j,i) ) &
112                        - ( v(k,j,i)   - v_gtrans ) * ( sk(k,j-1,i) - sk(k,j,i) ) &
113                        ) * ddy                                                   &
114              -         (   w(k,j,i)                * ( sk(k+1,j,i) - sk(k,j,i) ) &
115                        -   w(k-1,j,i)              * ( sk(k-1,j,i) - sk(k,j,i) ) &
116                        ) * dd2zu(k)
117             ENDDO
118          ENDDO
119       ENDDO
120
121    END SUBROUTINE advec_s_pw
122
123
124!------------------------------------------------------------------------------!
125! Call for grid point i,j
126!------------------------------------------------------------------------------!
127    SUBROUTINE advec_s_pw_ij( i, j, sk )
128
129       USE arrays_3d,                                                          &
130           ONLY:  dd2zu, tend, u, v, w
131
132       USE control_parameters,                                                 &
133           ONLY:  u_gtrans, v_gtrans
134
135       USE grid_variables,                                                     &
136           ONLY:  ddx, ddy
137
138       USE indices,                                                            &
139           ONLY:  nxlg, nxrg, nyng, nysg, nzb, nzb_s_inner, nzt
140
141       USE kinds
142
143
144       IMPLICIT NONE
145
146       INTEGER(iwp) ::  i !:
147       INTEGER(iwp) ::  j !:
148       INTEGER(iwp) ::  k !:
149
150#if defined( __nopointer )
151       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !:
152#else
153       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
154#endif
155
156
157       DO  k = nzb_s_inner(j,i)+1, nzt
158          tend(k,j,i) = tend(k,j,i)                                            &
159              -0.5_wp * ( ( u(k,j,i+1) - u_gtrans ) * ( sk(k,j,i+1) - sk(k,j,i) ) &
160                        - ( u(k,j,i)   - u_gtrans ) * ( sk(k,j,i-1) - sk(k,j,i) ) &
161                        ) * ddx                                                   &
162              -0.5_wp * ( ( v(k,j+1,i) - v_gtrans ) * ( sk(k,j+1,i) - sk(k,j,i) ) &
163                        - ( v(k,j,i)   - v_gtrans ) * ( sk(k,j-1,i) - sk(k,j,i) ) &
164                        ) * ddy                                                   &
165              -         (   w(k,j,i)                * ( sk(k+1,j,i) - sk(k,j,i) ) &
166                        -   w(k-1,j,i)              * ( sk(k-1,j,i) - sk(k,j,i) ) &
167                        ) * dd2zu(k)
168       ENDDO
169
170    END SUBROUTINE advec_s_pw_ij
171
172 END MODULE advec_s_pw_mod
Note: See TracBrowser for help on using the repository browser.