source: palm/trunk/SOURCE/advec_v_pw.f90 @ 3909

Last change on this file since 3909 was 3655, checked in by knoop, 5 years ago

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

  • Property svn:keywords set to Id
File size: 6.7 KB
Line 
1!> @file advec_v_pw.f90
2!------------------------------------------------------------------------------!
3!------------------------------------------------------------------------------!
4! This file is part of the PALM model system.
5!
6! PALM is free software: you can redistribute it and/or modify it under the
7! terms of the GNU General Public License as published by the Free Software
8! Foundation, either version 3 of the License, or (at your option) any later
9! version.
10!
11! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
12! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
13! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
14!
15! You should have received a copy of the GNU General Public License along with
16! PALM. If not, see <http://www.gnu.org/licenses/>.
17!
18! Copyright 1997-2019 Leibniz Universitaet Hannover
19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
24!
25! Former revisions:
26! -----------------
27! $Id: advec_v_pw.f90 3655 2019-01-07 16:51:22Z suehring $
28! variables documented
29!
30! 3538 2018-11-20 10:55:41Z suehring
31! Remove unnecessary double-masking of topography
32!
33! 2718 2018-01-02 08:49:38Z maronga
34! Corrected "Former revisions" section
35!
36! 2696 2017-12-14 17:12:51Z kanani
37! Change in file header (GPL part)
38!
39! 2233 2017-05-30 18:08:54Z suehring
40!
41! 2232 2017-05-30 17:47:52Z suehring
42! topography representation via flags
43!
44! 2000 2016-08-20 18:09:15Z knoop
45! Forced header and separation lines into 80 columns
46!
47! 1873 2016-04-18 14:50:06Z maronga
48! Module renamed (removed _mod)
49!
50!
51! 1850 2016-04-08 13:29:27Z maronga
52! Module renamed
53!
54!
55! 1682 2015-10-07 23:56:08Z knoop
56! Code annotations made doxygen readable
57!
58! 1353 2014-04-08 15:21:23Z heinze
59! REAL constants provided with KIND-attribute
60!
61! 1320 2014-03-20 08:40:49Z raasch
62! ONLY-attribute added to USE-statements,
63! kind-parameters added to all INTEGER and REAL declaration statements,
64! kinds are defined in new module kinds,
65! revision history before 2012 removed,
66! comment fields (!:) to be used for variable explanations added to
67! all variable declaration statements
68!
69! 1036 2012-10-22 13:43:42Z raasch
70! code put under GPL (PALM 3.9)
71!
72! Revision 1.1  1997/08/11 06:09:57  raasch
73! Initial revision
74!
75!
76! Description:
77! ------------
78!> Advection term for v velocity-component using Piacsek and Williams.
79!> Vertical advection at the first grid point above the surface is done with
80!> normal centred differences, because otherwise no information from the surface
81!> would be communicated upwards due to w=0 at K=nzb.
82!------------------------------------------------------------------------------!
83 MODULE advec_v_pw_mod
84 
85
86    PRIVATE
87    PUBLIC advec_v_pw
88
89    INTERFACE advec_v_pw
90       MODULE PROCEDURE advec_v_pw
91       MODULE PROCEDURE advec_v_pw_ij
92    END INTERFACE advec_v_pw
93 
94 CONTAINS
95
96
97!------------------------------------------------------------------------------!
98! Description:
99! ------------
100!> Call for all grid points
101!------------------------------------------------------------------------------!
102    SUBROUTINE advec_v_pw
103
104       USE arrays_3d,                                                          &
105           ONLY:  ddzw, tend, u, v, w
106
107       USE control_parameters,                                                 &
108           ONLY:  u_gtrans, v_gtrans
109
110       USE grid_variables,                                                     &
111           ONLY:  ddx, ddy
112
113       USE indices,                                                            &
114           ONLY:  nxl, nxr, nyn, nysv, nzb, nzt
115
116       USE kinds
117
118
119       IMPLICIT NONE
120
121       INTEGER(iwp) ::  i !< grid index along x-direction
122       INTEGER(iwp) ::  j !< grid index along y-direction
123       INTEGER(iwp) ::  k !< grid index along z-direction
124       
125       REAL(wp)    ::  gu !< Galilei-transformation velocity along x
126       REAL(wp)    ::  gv !< Galilei-transformation velocity along y
127 
128
129       gu = 2.0_wp * u_gtrans
130       gv = 2.0_wp * v_gtrans
131       DO  i = nxl, nxr
132          DO  j = nysv, nyn
133             DO  k = nzb+1, nzt
134                tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                        &
135                         ( v(k,j,i+1) * ( u(k,j-1,i+1) + u(k,j,i+1) - gu )     &
136                         - v(k,j,i-1) * ( u(k,j-1,i) + u(k,j,i) - gu ) ) * ddx &
137                       + ( v(k,j+1,i) * ( v(k,j+1,i) + v(k,j,i) - gv )         &
138                         - v(k,j-1,i) * ( v(k,j,i) + v(k,j-1,i) - gv ) ) * ddy &
139                       + ( v(k+1,j,i) * ( w(k,j-1,i) + w(k,j,i) )              &
140                         - v(k-1,j,i) * ( w(k-1,j-1,i) + w(k-1,j,i) ) )        &
141                                                                  * ddzw(k)    &
142                                                      )
143             ENDDO
144          ENDDO
145       ENDDO
146
147    END SUBROUTINE advec_v_pw
148
149
150!------------------------------------------------------------------------------!
151! Description:
152! ------------
153!> Call for grid point i,j
154!------------------------------------------------------------------------------!
155    SUBROUTINE advec_v_pw_ij( i, j )
156
157       USE arrays_3d,                                                          &
158           ONLY:  ddzw, tend, u, v, w
159
160       USE control_parameters,                                                 &
161           ONLY:  u_gtrans, v_gtrans
162
163       USE grid_variables,                                                     &
164           ONLY:  ddx, ddy
165
166       USE indices,                                                            &
167           ONLY:  nzb, nzt
168
169       USE kinds
170
171
172       IMPLICIT NONE
173
174       INTEGER(iwp) ::  i !< grid index along x-direction
175       INTEGER(iwp) ::  j !< grid index along y-direction
176       INTEGER(iwp) ::  k !< grid index along z-direction
177       
178       REAL(wp)    ::  gu !< Galilei-transformation velocity along x
179       REAL(wp)    ::  gv !< Galilei-transformation velocity along y
180
181
182       gu = 2.0_wp * u_gtrans
183       gv = 2.0_wp * v_gtrans
184       DO  k = nzb+1, nzt
185          tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                              &
186                         ( v(k,j,i+1) * ( u(k,j-1,i+1) + u(k,j,i+1) - gu )     &
187                         - v(k,j,i-1) * ( u(k,j-1,i) + u(k,j,i) - gu ) ) * ddx &
188                       + ( v(k,j+1,i) * ( v(k,j+1,i) + v(k,j,i) - gv )         &
189                         - v(k,j-1,i) * ( v(k,j,i) + v(k,j-1,i) - gv ) ) * ddy &
190                       + ( v(k+1,j,i) * ( w(k,j-1,i) + w(k,j,i) )              &
191                         - v(k-1,j,i) * ( w(k-1,j-1,i) + w(k-1,j,i) ) )        &
192                                                                  * ddzw(k)    &
193                                                )
194       ENDDO
195 
196    END SUBROUTINE advec_v_pw_ij
197
198 END MODULE advec_v_pw_mod
199 
Note: See TracBrowser for help on using the repository browser.