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

Last change on this file since 1036 was 1036, checked in by raasch, 11 years ago

code has been put under the GNU General Public License (v3)

  • Property svn:keywords set to Id
File size: 4.2 KB
Line 
1 MODULE advec_w_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-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: advec_w_pw.f90 1036 2012-10-22 13:43:42Z raasch $
27! RCS Log replace by Id keyword, revision history cleaned up
28!
29! Revision 1.15  2006/02/23 09:47:01  raasch
30! nzb_2d replaced by nzb_w_inner
31!
32! Revision 1.1  1997/08/11 06:10:29  raasch
33! Initial revision
34!
35!
36! Description:
37! ------------
38! Advection term for w velocity-component using Piacsek and Williams.
39! Vertical advection at the first grid point above the surface is done with
40! normal centred differences, because otherwise no information from the surface
41! would be communicated upwards due to w=0 at k=nzb.
42!------------------------------------------------------------------------------!
43
44    PRIVATE
45    PUBLIC advec_w_pw
46
47    INTERFACE advec_w_pw
48       MODULE PROCEDURE advec_w_pw
49       MODULE PROCEDURE advec_w_pw_ij
50    END INTERFACE advec_w_pw
51 
52 CONTAINS
53
54
55!------------------------------------------------------------------------------!
56! Call for all grid points
57!------------------------------------------------------------------------------!
58    SUBROUTINE advec_w_pw
59
60       USE arrays_3d
61       USE control_parameters
62       USE grid_variables
63       USE indices
64
65       IMPLICIT NONE
66
67       INTEGER ::  i, j, k
68       REAL    ::  gu, gv
69
70 
71       gu = 2.0 * u_gtrans
72       gv = 2.0 * v_gtrans
73       DO  i = nxl, nxr
74          DO  j = nys, nyn
75             DO  k = nzb_w_inner(j,i)+1, nzt
76                tend(k,j,i) = tend(k,j,i) - 0.25 * (                           &
77                         ( w(k,j,i+1) * ( u(k+1,j,i+1) + u(k,j,i+1) - gu )     &
78                         - w(k,j,i-1) * ( u(k+1,j,i) + u(k,j,i) - gu ) ) * ddx &
79                       + ( w(k,j+1,i) * ( v(k+1,j+1,i) + v(k,j+1,i) - gv )     &
80                         - w(k,j-1,i) * ( v(k+1,j,i) + v(k,j,i) - gv ) ) * ddy &
81                       + ( w(k+1,j,i) * ( w(k+1,j,i) + w(k,j,i) )              &
82                         - w(k-1,j,i) * ( w(k,j,i) + w(k-1,j,i) ) )            &
83                                                                  * ddzu(k+1)  &
84                                                   )
85             ENDDO
86          ENDDO
87       ENDDO
88
89    END SUBROUTINE advec_w_pw
90
91
92!------------------------------------------------------------------------------!
93! Call for grid point i,j
94!------------------------------------------------------------------------------!
95    SUBROUTINE advec_w_pw_ij( i, j )
96
97       USE arrays_3d
98       USE control_parameters
99       USE grid_variables
100       USE indices
101
102       IMPLICIT NONE
103
104       INTEGER ::  i, j, k
105       REAL    ::  gu, gv
106
107       gu = 2.0 * u_gtrans
108       gv = 2.0 * v_gtrans
109       DO  k = nzb_w_inner(j,i)+1, nzt
110          tend(k,j,i) = tend(k,j,i) - 0.25 * (                              &
111                         ( w(k,j,i+1) * ( u(k+1,j,i+1) + u(k,j,i+1) - gu )     &
112                         - w(k,j,i-1) * ( u(k+1,j,i) + u(k,j,i) - gu ) ) * ddx &
113                       + ( w(k,j+1,i) * ( v(k+1,j+1,i) + v(k,j+1,i) - gv )     &
114                         - w(k,j-1,i) * ( v(k+1,j,i) + v(k,j,i) - gv ) ) * ddy &
115                       + ( w(k+1,j,i) * ( w(k+1,j,i) + w(k,j,i) )              &
116                         - w(k-1,j,i) * ( w(k,j,i) + w(k-1,j,i) ) )            &
117                                                                  * ddzu(k+1)  &
118                                                )
119       ENDDO
120    END SUBROUTINE advec_w_pw_ij
121
122 END MODULE advec_w_pw_mod
Note: See TracBrowser for help on using the repository browser.