source: palm/trunk/SOURCE/advec_w_pw_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: 5.8 KB
Line 
1!> @file advec_w_pw_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: advec_w_pw_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! 1036 2012-10-22 13:43:42Z raasch
43! code put under GPL (PALM 3.9)
44!
45! Revision 1.1  1997/08/11 06:10:29  raasch
46! Initial revision
47!
48!
49! Description:
50! ------------
51!> Advection term for w velocity-component using Piacsek and Williams.
52!> Vertical advection at the first grid point above the surface is done with
53!> normal centred differences, because otherwise no information from the surface
54!> would be communicated upwards due to w=0 at k=nzb.
55!------------------------------------------------------------------------------!
56 MODULE advec_w_pw_mod
57 
58
59    PRIVATE
60    PUBLIC advec_w_pw
61
62    INTERFACE advec_w_pw
63       MODULE PROCEDURE advec_w_pw
64       MODULE PROCEDURE advec_w_pw_ij
65    END INTERFACE advec_w_pw
66 
67 CONTAINS
68
69
70!------------------------------------------------------------------------------!
71! Description:
72! ------------
73!> Call for all grid points
74!------------------------------------------------------------------------------!
75    SUBROUTINE advec_w_pw
76
77       USE arrays_3d,                                                          &
78           ONLY:  ddzu, tend, u, v, w
79
80       USE control_parameters,                                                 &
81           ONLY:  u_gtrans, v_gtrans
82
83       USE grid_variables,                                                     &
84           ONLY:  ddx, ddy
85
86       USE indices,                                                            &
87           ONLY:  nxl, nxr, nyn, nys, nzb_w_inner, nzt
88
89       USE kinds
90
91
92       IMPLICIT NONE
93
94       INTEGER(iwp) ::  i !<
95       INTEGER(iwp) ::  j !<
96       INTEGER(iwp) ::  k !<
97       
98       REAL(wp)    ::  gu !<
99       REAL(wp)    ::  gv !<
100
101 
102       gu = 2.0_wp * u_gtrans
103       gv = 2.0_wp * v_gtrans
104       DO  i = nxl, nxr
105          DO  j = nys, nyn
106             DO  k = nzb_w_inner(j,i)+1, nzt
107                tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                        &
108                         ( w(k,j,i+1) * ( u(k+1,j,i+1) + u(k,j,i+1) - gu )     &
109                         - w(k,j,i-1) * ( u(k+1,j,i) + u(k,j,i) - gu ) ) * ddx &
110                       + ( w(k,j+1,i) * ( v(k+1,j+1,i) + v(k,j+1,i) - gv )     &
111                         - w(k,j-1,i) * ( v(k+1,j,i) + v(k,j,i) - gv ) ) * ddy &
112                       + ( w(k+1,j,i) * ( w(k+1,j,i) + w(k,j,i) )              &
113                         - w(k-1,j,i) * ( w(k,j,i) + w(k-1,j,i) ) )            &
114                                                                  * ddzu(k+1)  &
115                                                      )
116             ENDDO
117          ENDDO
118       ENDDO
119
120    END SUBROUTINE advec_w_pw
121
122
123!------------------------------------------------------------------------------!
124! Description:
125! ------------
126!> Call for grid point i,j
127!------------------------------------------------------------------------------!
128    SUBROUTINE advec_w_pw_ij( i, j )
129
130       USE arrays_3d,                                                          &
131           ONLY:  ddzu, tend, u, v, w
132
133       USE control_parameters,                                                 &
134           ONLY:  u_gtrans, v_gtrans
135
136       USE grid_variables,                                                     &
137           ONLY:  ddx, ddy
138
139       USE indices,                                                            &
140           ONLY:  nzb_w_inner, nzt
141
142       USE kinds
143
144
145       IMPLICIT NONE
146
147       INTEGER(iwp) ::  i !<
148       INTEGER(iwp) ::  j !<
149       INTEGER(iwp) ::  k !<
150       
151       REAL(wp)    ::  gu !<
152       REAL(wp)    ::  gv !<
153
154       gu = 2.0_wp * u_gtrans
155       gv = 2.0_wp * v_gtrans
156       DO  k = nzb_w_inner(j,i)+1, nzt
157          tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                              &
158                         ( w(k,j,i+1) * ( u(k+1,j,i+1) + u(k,j,i+1) - gu )     &
159                         - w(k,j,i-1) * ( u(k+1,j,i) + u(k,j,i) - gu ) ) * ddx &
160                       + ( w(k,j+1,i) * ( v(k+1,j+1,i) + v(k,j+1,i) - gv )     &
161                         - w(k,j-1,i) * ( v(k+1,j,i) + v(k,j,i) - gv ) ) * ddy &
162                       + ( w(k+1,j,i) * ( w(k+1,j,i) + w(k,j,i) )              &
163                         - w(k-1,j,i) * ( w(k,j,i) + w(k-1,j,i) ) )            &
164                                                                  * ddzu(k+1)  &
165                                                )
166       ENDDO
167    END SUBROUTINE advec_w_pw_ij
168
169 END MODULE advec_w_pw_mod
Note: See TracBrowser for help on using the repository browser.