source: palm/trunk/SOURCE/advec_w_pw.f90 @ 1320

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

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

  • Property svn:keywords set to Id
File size: 5.4 KB
RevLine 
[1]1 MODULE advec_w_pw_mod
2
[1036]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!
[1310]17! Copyright 1997-2014 Leibniz Universitaet Hannover
[1036]18!--------------------------------------------------------------------------------!
19!
[484]20! Current revisions:
[1]21! -----------------
[1320]22! ONLY-attribute added to USE-statements,
23! kind-parameters added to all INTEGER and REAL declaration statements,
24! kinds are defined in new module kinds,
25! revision history before 2012 removed,
26! comment fields (!:) to be used for variable explanations added to
27! all variable declaration statements
[1]28!
29! Former revisions:
30! -----------------
[3]31! $Id: advec_w_pw.f90 1320 2014-03-20 08:40:49Z raasch $
[1037]32!
33! 1036 2012-10-22 13:43:42Z raasch
34! code put under GPL (PALM 3.9)
35!
[1]36! Revision 1.1  1997/08/11 06:10:29  raasch
37! Initial revision
38!
39!
40! Description:
41! ------------
42! Advection term for w velocity-component using Piacsek and Williams.
43! Vertical advection at the first grid point above the surface is done with
44! normal centred differences, because otherwise no information from the surface
45! would be communicated upwards due to w=0 at k=nzb.
46!------------------------------------------------------------------------------!
47
48    PRIVATE
49    PUBLIC advec_w_pw
50
51    INTERFACE advec_w_pw
52       MODULE PROCEDURE advec_w_pw
53       MODULE PROCEDURE advec_w_pw_ij
54    END INTERFACE advec_w_pw
55 
56 CONTAINS
57
58
59!------------------------------------------------------------------------------!
60! Call for all grid points
61!------------------------------------------------------------------------------!
62    SUBROUTINE advec_w_pw
63
[1320]64       USE arrays_3d,                                                          &
65           ONLY:  ddzu, tend, u, v, w
[1]66
[1320]67       USE control_parameters,                                                 &
68           ONLY:  u_gtrans, v_gtrans
69
70       USE grid_variables,                                                     &
71           ONLY:  ddx, ddy
72
73       USE indices,                                                            &
74           ONLY:  nxl, nxr, nyn, nys, nzb_w_inner, nzt
75
76       USE kinds
77
78
[1]79       IMPLICIT NONE
80
[1320]81       INTEGER(iwp) ::  i !:
82       INTEGER(iwp) ::  j !:
83       INTEGER(iwp) ::  k !:
84       
85       REAL(wp)    ::  gu !:
86       REAL(wp)    ::  gv !:
[1]87
88 
89       gu = 2.0 * u_gtrans
90       gv = 2.0 * v_gtrans
91       DO  i = nxl, nxr
92          DO  j = nys, nyn
93             DO  k = nzb_w_inner(j,i)+1, nzt
94                tend(k,j,i) = tend(k,j,i) - 0.25 * (                           &
95                         ( w(k,j,i+1) * ( u(k+1,j,i+1) + u(k,j,i+1) - gu )     &
96                         - w(k,j,i-1) * ( u(k+1,j,i) + u(k,j,i) - gu ) ) * ddx &
97                       + ( w(k,j+1,i) * ( v(k+1,j+1,i) + v(k,j+1,i) - gv )     &
98                         - w(k,j-1,i) * ( v(k+1,j,i) + v(k,j,i) - gv ) ) * ddy &
99                       + ( w(k+1,j,i) * ( w(k+1,j,i) + w(k,j,i) )              &
100                         - w(k-1,j,i) * ( w(k,j,i) + w(k-1,j,i) ) )            &
101                                                                  * ddzu(k+1)  &
102                                                   )
103             ENDDO
104          ENDDO
105       ENDDO
106
107    END SUBROUTINE advec_w_pw
108
109
110!------------------------------------------------------------------------------!
111! Call for grid point i,j
112!------------------------------------------------------------------------------!
113    SUBROUTINE advec_w_pw_ij( i, j )
114
[1320]115       USE arrays_3d,                                                          &
116           ONLY:  ddzu, tend, u, v, w
[1]117
[1320]118       USE control_parameters,                                                 &
119           ONLY:  u_gtrans, v_gtrans
120
121       USE grid_variables,                                                     &
122           ONLY:  ddx, ddy
123
124       USE indices,                                                            &
125           ONLY:  nzb_w_inner, nzt
126
127       USE kinds
128
129
[1]130       IMPLICIT NONE
131
[1320]132       INTEGER(iwp) ::  i !:
133       INTEGER(iwp) ::  j !:
134       INTEGER(iwp) ::  k !:
135       
136       REAL(wp)    ::  gu !:
137       REAL(wp)    ::  gv !:
[1]138
139       gu = 2.0 * u_gtrans
140       gv = 2.0 * v_gtrans
141       DO  k = nzb_w_inner(j,i)+1, nzt
[1320]142          tend(k,j,i) = tend(k,j,i) - 0.25 * (                                 &
[1]143                         ( w(k,j,i+1) * ( u(k+1,j,i+1) + u(k,j,i+1) - gu )     &
144                         - w(k,j,i-1) * ( u(k+1,j,i) + u(k,j,i) - gu ) ) * ddx &
145                       + ( w(k,j+1,i) * ( v(k+1,j+1,i) + v(k,j+1,i) - gv )     &
146                         - w(k,j-1,i) * ( v(k+1,j,i) + v(k,j,i) - gv ) ) * ddy &
147                       + ( w(k+1,j,i) * ( w(k+1,j,i) + w(k,j,i) )              &
148                         - w(k-1,j,i) * ( w(k,j,i) + w(k-1,j,i) ) )            &
149                                                                  * ddzu(k+1)  &
150                                                )
151       ENDDO
152    END SUBROUTINE advec_w_pw_ij
153
154 END MODULE advec_w_pw_mod
Note: See TracBrowser for help on using the repository browser.